[Rd] S4 and Namespaces problems {was "error message from lmer"}

Robert Gentleman rgentlem at fhcrc.org
Wed Jul 18 18:15:50 CEST 2007


Hi,

Martin Maechler wrote:
> Here is a reproducible example for the Bug that both Sebastian
> and Dale Barr found.
> 
> As Brian mentioned in an another thread,
> the problem is in the interaction of Namespaces and S4 generics
> and which S4 generic should keep which methods.
> 
> We know there are workarounds, but till now they seem either
> ugly or very much against the idea that conceptually there
> should be only one generic which may have methods defined in
> many different packages / namespaces.

   There should *not* be one generic. Generics are no different than any 
other function. Package A can have a generic named foo, and so can 
package B.  Other packages that want to add methods to a generic named 
foo need to know which one they would like to add to.  These generics 
can be masked. If Package A is first on the search path then that is the 
foo that is found first (and if Package B is first then that is the foo, 
users that specifically want foo from B should use B::foo).


> 
> I would like us (R-core, mostly) to resolve this as quickly as
> possible.
> 
> -------------------------------------------------------------------------
> 
> ### Do this in a fresh  R session:
> 
> summary # S3 generic
> find("summary") # base
> 
> library(stats4)
> summary # S4 generic
> find("summary") # stats4 , base
> 
> library(lme4)
> ## -> loads Matrix (and lattice)
> find("summary") # lme4, Matrix, stats4 , base   --- 4 times ! ---

   Have they all defined generics? If that is the case then there are 4.

   We did discuss, and I hope to make progress on the following 
proposal. For functions in base that have an S4 method defined for them 
(and hence we need a generic function), that we create a new package 
that lives slightly above base (and potentially other recommended 
packages) where these generics will live.  Developers can then rely on 
finding the generic there, and using it - if their intention is to 
extend the base generic.  Note that they may want to have their own 
generic with the same name as the one from base, and that is fine, it 
will mask the one in base.

   best wishes
    Robert
> 
> fm1 <- lmer(Reaction ~ Days + (Days|Subject), sleepstudy)
> ## -->
> ## Error in lmer(Reaction ~ Days + (Days | Subject), sleepstudy) :
> ## 	cannot get a slot ("Dim") from an object of type "NULL"
> 
> -------------------------------------------------------------------------
> Martin Maechler
> 
> 
>>>>>> "BDR" == Prof Brian Ripley <ripley at stats.ox.ac.uk>
>>>>>>     on Thu, 28 Jun 2007 06:08:45 +0100 (BST) writes:
> 
>     BDR> See the thread starting
>     BDR> https://stat.ethz.ch/pipermail/r-devel/2007-June/046157.html
>     BDR> https://stat.ethz.ch/pipermail/r-devel/2007-June/046160.html
> 
>     BDR> I can't reproduce this without knowing what is in your
>     BDR> startup files: it should work with --vanilla, so please
>     BDR> try that and try to eliminate whatever is in your
>     BDR> .Rprofile etc that is causing the problem.
> 
>     BDR> Incidentally, using rcompletion is counterproductive in
>     BDR> R 2.5.1 RC: the base functionality using rcompgen is a
>     BDR> more sophisticated version.
> 
>     BDR> On Wed, 27 Jun 2007, Sebastian P. Luque wrote:
> 
>     >> Hi,
>     >> 
>     >> I've begun to use the lme4 package, rather than nlme, for more flexibility
>     >> during modelling, and running the examples in lmer I receive this error
>     >> message:
>     >> 
>     >> ---<---------------cut here---------------start-------------->---
>     R> (fm1 <- lmer(Reaction ~ Days + (Days|Subject), sleepstudy))
>     >> Error in printMer(object) : no slot of name "status" for this object of class "table"
>     >> 
>     R> sessionInfo()
>     >> R version 2.5.1 RC (2007-06-25 r42057)
>     >> x86_64-pc-linux-gnu
>     >> 
>     >> locale:
>     >> LC_CTYPE=en_CA.UTF-8;LC_NUMERIC=C;LC_TIME=en_CA.UTF-8;LC_COLLATE=en_CA.UTF-8;LC_MONETARY=en_CA.UTF-8;LC_MESSAGES=en_CA.UTF-8;LC_PAPER=en_CA.UTF-8;LC_NAME=C;LC_ADDRESS=C;LC_TELEPHONE=C;LC_MEASUREMENT=en_CA.UTF-8;LC_IDENTIFICATION=C
>     >> 
>     >> attached base packages:
>     >> [1] "stats4"    "stats"     "graphics"  "grDevices" "utils"     "datasets"
>     >> [7] "methods"   "base"
>     >> 
>     >> other attached packages:
>     >> lme4      Matrix rcompletion    rcompgen     lattice    diveMove
>     >> "0.99875-2" "0.99875-2"     "0.1-2"    "0.1-13"   "0.15-11"     "0.7-9"
>     >> reshape
>     >> "0.7.4"
>     >> ---<---------------cut here---------------end---------------->---
>     >> 
>     >> Since this is happening in a fresh session, and with code from examples
>     >> help file, this looks like a potential bug.  Any thoughts?
>     >> 
>     >> 
>     >> Cheers,
> 
> ______________________________________________
> R-devel at r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-devel
> 

-- 
Robert Gentleman, PhD
Program in Computational Biology
Division of Public Health Sciences
Fred Hutchinson Cancer Research Center
1100 Fairview Ave. N, M2-B876
PO Box 19024
Seattle, Washington 98109-1024
206-667-7700
rgentlem at fhcrc.org



More information about the R-devel mailing list