[R] [Rd] How do I modify an exported function in a locked environment?
Gabor Grothendieck
ggrothendieck at gmail.com
Thu Jul 20 23:21:03 CEST 2006
As others have mentioned its not really a good idea
to modify the namespace of a package and writing
a wrapper as Duncan suggested is much preferable.
An intermediate approach that
is not as good as the wrapper but better than modifying
the namespace is to copy the objects of interest
to your workspace, change their environments
appropriately and then modify their functionality:
library(zoo)
# copy objects of interest and set their environment
rollmean <- zoo:::rollmean
environment(rollmean) <- .GlobalEnv
rollmean.zoo <- zoo:::rollmean.zoo
environment(rollmean.zoo) <- .GlobalEnv
rollmean.default <- zoo:::rollmean.default
environment(rollmean.default) <- .GlobalEnv
# modify functionality
rollmean.default0 <- rollmean.default
rollmean.default <- function(x, ...) 100 * rollmean.default0(x, ...)
# test
rollmean(1:5, 3) # 100* used
rollmean(zoo(1:5), 3) # 100* used
On 7/20/06, Steven McKinney <smckinney at bccrc.ca> wrote:
>
>
> Running R.app on Mac OS X 10.4
>
> > version
> _
> platform powerpc-apple-darwin8.6.0
> arch powerpc
> os darwin8.6.0
> system powerpc, darwin8.6.0
> status
> major 2
> minor 3.1
> year 2006
> month 06
> day 01
> svn rev 38247
> language R
> version.string Version 2.3.1 (2006-06-01)
> >
>
>
> I am trying to learn how to modify functions
> in a locked environment.
>
> For an example, suppose I'm using the package "zoo".
>
> zoo contains function "rollmean.default"
>
> > rollmean.default
> function (x, k, na.pad = FALSE, align = c("center", "left", "right"),
> ...)
> {
> x <- unclass(x)
> n <- length(x)
> y <- x[k:n] - x[c(1, 1:(n - k))]
> y[1] <- sum(x[1:k])
> rval <- cumsum(y)/k
> if (na.pad) {
> rval <- switch(match.arg(align), left = {
> c(rval, rep(NA, k - 1))
> }, center = {
> c(rep(NA, floor((k - 1)/2)), rval, rep(NA, ceiling((k -
> 1)/2)))
> }, right = {
> c(rep(NA, k - 1), rval)
> })
> }
> return(rval)
> }
> <environment: namespace:zoo>
>
> Suppose for whatever reason I want output to be
> in percent, so I'd like to modify the result to be
> rval <- 100 * cumsum(y)/k
>
> I cannot just copy the function and change it, as the namespace
> mechanism ensures the rollmean.default in 'zoo' continues to be used.
>
> If I use
> fixInNamespace("rollmean.default", ns = "zoo")
> I can edit the rval <- cumsum(y)/k line to read
> rval <- 100 * cumsum(y)/k
> save the file and exit the R.app GUI editor.
>
> But this does not update the exported copy of the
> function (the documentation for fixInNamespace says
> this is the case) - how do I accomplish this last step?
>
> If I list the function after editing, I see the original
> copy. But if I reinvoke the editor via fixInNamespace(),
> I do see my modification.
> Where is my copy residing? How do I push it out
> to replace the exported copy?
>
> Is this the proper way to modify a package function?
> Are there other ways? I've searched webpages, R news,
> help files and have been unable to find out how to
> get this process fully completed.
>
> Any guidance appreciated.
>
>
> Steven McKinney
>
> Statistician
> Molecular Oncology and Breast Cancer Program
> British Columbia Cancer Research Centre
>
> email: smckinney at bccrc.ca
>
> tel: 604-675-8000 x7561
>
> BCCRC
> Molecular Oncology
> 675 West 10th Ave, Floor 4
> Vancouver B.C.
> V5Z 1L3
> Canada
>
> ______________________________________________
> R-devel at r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-devel
>
More information about the R-help
mailing list