On 5/20/06, Prof Brian Ripley <[EMAIL PROTECTED]> wrote: > Here are three examples where this matters, and I think the bug is > elsewhere! > > 1) Package accuracy does > > ZeligHooks<-function (...) { > if (exists(".simHooked",envir=.GlobalEnv)) { > return(TRUE) > } > origsim=get("sim",envir=as.environment("package:Zelig")) > sim.replacement=function (object, x, ...) { > if (inherits(object,"sensitivity")) { > psim(object,x,...) > } else { > origsim(object,x,...) > } > } > assignInNamespace("sim",sim.replacement,"Zelig") > unlockBinding("sim",as.environment("package:Zelig")) > assign("sim",sim.replacement, envir=as.environment("package:Zelig")) > assign("sim",sim.replacement, envir=.GlobalEnv) > assign(".simHooked",TRUE,envir=.GlobalEnv) > } > > Now, origsim() becomes a generic calling "sim", with defining environment > namespace:Zelig. However, sim in namespace:Zelig has been altered to be a > new function, whose enclosure is not namespace:Zelig and hence cannot see > the methods registered on the original sim() in namespace:Zelig. I think > that is the correct behaviour (the new sim might have nothing to do with > the old one). The fix would appear to be to set the environment of the > replacement to namespace:Zelig, but then origsim will not be visible from > sim. > > Note that the package writes in the workspace and clobbers any object > called 'sim' there. Surely a less intrusive solution is needed? > > There's a similar (maybe the same) problem in package VDCutil. > > > 2) Package arules fails its tests. The problem is in Matrix: > > > base::as.matrix > function (x) > UseMethod("as.matrix") > <environment: namespace:base> > > library(Matrix) > > base::as.matrix > standardGeneric for "as.matrix" defined from package "base" > > function (x) > standardGeneric("as.matrix") > <environment: 0x1453cc8> > Methods may be defined for arguments: x > > Now is converting to an S4 generic *not* supposed to alter the function in > the original package/namespace? It does not do it if I do it by hand: > > > setClass("foo", "numeric") > [1] "foo" > > setMethod("as.matrix", "foo", function(x) x) > Creating a new generic function for 'as.matrix' in '.GlobalEnv' > [1] "as.matrix" > > base::as.matrix > function (x) > UseMethod("as.matrix") > <environment: namespace:base> > > and this looks like a bug. > > > 3) Package R.oo has things like UseMethod("$") whereas this is documented > to work for functions (not operators). This is unnecessary ($ does > internal dispatch) and the existing code is getting the wrong defining > environment (and although I've reinstated this as a workaround, I think it > should be an error).
First, when coding I treat operators as being functions. I think this is valid, cf. "Except for the syntax, there is no difference between applying an operator and calling a function. In fact, x + y can equivalently be written "+"(x, y). Notice that since + is a non-standard function name, it needs to be quoted." (R Language Definition). Second, I went to look at my code, and I found an old note of mine saying "get("$")(x, name)" won't work. At the time, I never tried to figure out why. However, if I try that, or "$"(x, name) the name of the 'name' argument becomes "name" (through some internal substitute() I believe). Example in R v2.3.0 patched (2006-04-28) on WinXP: o <- structure(1, class="A") "$.A" <- function(x, name) { cat("$.A(x,", name, ")\n") } "[[.A" <- function(x, name) { UseMethod("$") } o[["a"]] # gives $.A(x, a ) as wanted But "[[.A" <- function(x, name) { "$"(x, name) } o[["a"]] # gives $.A(x, name )! Same for: "[[.A" <- function(x, name) { .Primitive("$")(x, name) } o[["a"]] # $.A(x, name ) and "[[.A" <- function(x, name) { get("$")(x, name) } o[["a"]] # $.A(x, name ) I expected/hoped that 'name' would equal "a". Bug? A workaround is to use do.call(); "[[.A" <- function(x, name) { do.call("$", arg=list(x, name)) } o[["a"]] # $.A(x, a ) However, I would prefer not use do.call() because that adds quite a extra overhead. I guess I didn't understand the problem last time, which is also why I went for UseMethod("$"). > > Aargh ... fixing one bug is not supposed to uncover three others. One less for your update, but a new one in the old code. Thanks Henrik > > On Fri, 19 May 2006, Prof Brian Ripley wrote: > > > If I do > > > >> example(lm) > > ... > >> mycoef <- function(object, ...) UseMethod("coef", object) > >> mycoef(lm.D9) > > Error in mycoef(lm.D9) : no applicable method for "coef" > > > > which is pretty surprising, as coef has a default method. > > > > After a bit of digging, this comes from do_usemethod having > > > > defenv = environment where the generic was defined */ > > defenv = ENCLOS(env); > > > > so it is assuming that UseMethod() is called within the defining generic > > for its first argument. That plainly does not need to be true, e.g. > > > >> coefficients > > function (object, ...) > > UseMethod("coef") > > <environment: namespace:stats> > > > > It is clear to me that we need to search for 'generic' and find its > > defining environment rather than that of the current caller. It is not > > entirely clear where to search from as I think we need to avoid > > > > mycoef <- function(x) > > { > > mycoef <- function(x) stop("not this one") > > UseMethod("mycoef") > > } > > > > so I used ENCLOS(env). > > > > This adds some overhead, hopefully no more than searching for methods. > > > > BTW, I noticed that R_LookupMethod uses findVar, that is looks for any > > object not for functions: that must be another infelicity. > > > > > > -- > Brian D. Ripley, [EMAIL PROTECTED] > Professor of Applied Statistics, http://www.stats.ox.ac.uk/~ripley/ > University of Oxford, Tel: +44 1865 272861 (self) > 1 South Parks Road, +44 1865 272866 (PA) > Oxford OX1 3TG, UK Fax: +44 1865 272595 ______________________________________________ R-devel@r-project.org mailing list https://stat.ethz.ch/mailman/listinfo/r-devel