[Rd] S3, S4, namespace

John Chambers jmc at research.bell-labs.com
Mon Jan 12 21:14:43 MET 2004


John Chambers wrote:
> 
> You're caught in a subtle "gotcha" with the combination of things you're
> doing.  We're trying to sort out some of the interactions among
> namespace & methods at the moment, so there may be a nicer solution in
> the future.  Meanwhile, I can tell you the problem and suggest various
> work-arounds.
> 
> The basic problem is that by importing barpkg, rather than requiring it,
> the generic version of "print" is not seen from the recursive call to
> print inside the S4 method for class "bar".  (It's possible this is just
> a simple bug, but the thread of environments is a bit tricky at this
> point.)

It turned out this was indeed just a bug ("simple" might be an
exaggeration).  A quick fix should be available in r-devel now, a more
thorough fix will arrive later--the difference being mainly to make
dispatch a little faster.

(The bug was a result of the function being called coming from base,
causing the dispatch code to look for the generic, but in the wrong
environment.)

> 
> Here's a dump (using options(error=recover)) of your example
> (NameSpace4==wazpkg, NameSpace3==barpkg)
> 
> R> library(NameSpace4)
> R> wazbar(99)
> Error in .setMethodsForDispatch(f, fdef, resetMlist) :
>         Internal error: did not get a valid generic function object for
> function "print"
> 
> Enter a frame number, or 0 to exit
> 1:wazbar(99)
> 2:barprint(new("bar", x))
> 3:barprint(new("bar", x))
> 4:print("barprint method for bar")
> 5:MethodsListSelect("print", <environment>, structure(list(), methods =
> structure(
> 6:.setMethodsForDispatch(f, fdef, resetMlist)
> Selection: 5
> Called from: eval(expr, envir, enclos)
> Browse[1]> find("print")
> [1] "package:base"
> 
> So only the S3 version of print on base is seen at this juncture.
> Hence, crash.
> 
> This leads to the first work-around: require(barpkg) (e.g., in a .onLoad
> function for wazpkg)
> 
> R> require(NameSpace3)
> Loading required package: NameSpace3
> [1] TRUE
> R> wazbar(99)
> [1] "barprint method for bar"
> [1] 99
> 
> (because the S4 generic for print is now in the search path).
> 
> Other probable workarounds (haven't tried them out):
> 
> - force S4 generics for print, etc. in the wazbar package as well.
> 
> - don't make S3 generics on base into S4 generics.
> 
> John
> 
> "Heywood, Giles" wrote:
> >
> > I have encountered an issue which I have been unable to resolve, involving
> > an S3 generic (print) being declared S4 generic in a package, and the method
> > being exported.  This all works fine - the problem occurs when I try to
> > import the method to another package.
> >
> > Here is the bit that works fine. -------------
> >
> > #the .r file for package bar
> >
> > setClass("bar",representation("numeric"))
> >
> > if(!isGeneric("print")) {setGeneric("print",useAsDefault=print)}
> > setMethod("print",signature(x="bar"),
> >     print.bar <- function(x,...)
> >         {
> >         print("print method for bar")
> >         print(x at .Data,...)
> >         }
> >     )
> >
> > if(!isGeneric("barprint")) {setGeneric("barprint",useAsDefault=print)}
> > setMethod("barprint",signature(x="bar"),
> >     printBar <- function(x,...)
> >         {
> >         print("barprint method for bar")
> >         print(x at .Data,...)
> >         }
> >     )
> >
> > #the NAMESPACE file for package bar
> >
> > import(methods)
> > exportMethods(barprint,print)
> > exportClasses("bar")
> >
> > #then in R:
> >
> > > require(barpkg)
> > Loading required package: barpkg
> > [1] TRUE
> > > x <- new("bar",99)
> > > print(x)
> > [1] "print method for bar"
> > [1] 99
> > > barprint(x)
> > [1] "barprint method for bar"
> > [1] 99
> >
> > Fine.
> >
> > Here is the bit that I have not figured out. -------------
> >
> > #the .r file for package waz
> >
> > wazbar <- function(x)
> >     {
> >     barprint(new("bar",x))
> >     }
> >
> > #the NAMESPACE file for package waz
> >
> > import(methods,barpkg)
> > importMethodsFrom(barpkg)
> > importClassesFrom(barpkg)
> > export(wazbar)
> >
> > #then in R
> >
> > > require(wazpkg)
> > Loading required package: wazpkg
> > [1] TRUE
> > > wazbar(99)
> > Error in .setMethodsForDispatch(f, fdef, resetMlist) :
> >         Internal error: did not get a valid generic function object for
> > function "print"
> > Error in print("barprint method for bar") :
> >         S language method selection got an error when called from internal
> > dispatch for function "print"
> >
> > end of R bit ---------------------------
> >
> > The problem goes away if I don't set print as an S4 generic in bar.
> >
> > Can anyone help - maybe an error is obvious?
> >
> > As a bit of background, I am package maintainer for its (Irregular
> > Time-Series), and have been obliged to put it in a namespace or suffer a
> > significant performance penalty (about 6x slower).  In the package I make S3
> > generics (plot, print, summary etc) S4 generic in this package, and so far
> > have not got into trouble for doing so.  However, I have now got stuck -
> > possibly I have not seen the right documentation (I refer to the newsletter
> > article, and John Chambers' correspondence on R-devel early September).
> >
> > - Giles
> >
> > platform i386-pc-mingw32
> > arch     i386
> > os       mingw32
> > system   i386, mingw32
> > status
> > major    1
> > minor    8.1
> > year     2003
> > month    11
> > day      21
> > language R
> >
> > Rcmd install --doc="none"  barpkg
> >
> > **********************************************************************
> > This is a commercial communication from Commerzbank AG.\ \ T...{{dropped}}
> >
> > ______________________________________________
> > R-devel at stat.math.ethz.ch mailing list
> > https://www.stat.math.ethz.ch/mailman/listinfo/r-devel
> 
> --
> John M. Chambers                  jmc at bell-labs.com
> Bell Labs, Lucent Technologies    office: (908)582-2681
> 700 Mountain Avenue, Room 2C-282  fax:    (908)582-3340
> Murray Hill, NJ  07974            web: http://www.cs.bell-labs.com/~jmc
> 
> ______________________________________________
> R-devel at stat.math.ethz.ch mailing list
> https://www.stat.math.ethz.ch/mailman/listinfo/r-devel

-- 
John M. Chambers                  jmc at bell-labs.com
Bell Labs, Lucent Technologies    office: (908)582-2681
700 Mountain Avenue, Room 2C-282  fax:    (908)582-3340
Murray Hill, NJ  07974            web: http://www.cs.bell-labs.com/~jmc



More information about the R-devel mailing list