[Rd] UseMethod infelicity

Prof Brian Ripley ripley at stats.ox.ac.uk
Sat May 20 19:54:12 CEST 2006


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).


Aargh ... fixing one bug is not supposed to uncover three others.


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,                  ripley at stats.ox.ac.uk
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



More information about the R-devel mailing list