[Rd] R 2.5.0 devel try issue in conjuntion with S4 method dispatch

Seth Falcon sfalcon at fhcrc.org
Fri Mar 16 16:24:29 CET 2007


This is off-topic, but since the discussion moved towards coding
style...  Here are some comments on S4 style.

ml-it-r-devel at epigenomics.com writes:
> ##  using S4 classes and methods
> setClass("fooBase",
>          representation("VIRTUAL",
>                         width      = "numeric",
>                         height     = "numeric"),
>          prototype(width      = 1024,
>                    height     = 1024),
>          validity = NULL,
>          where    = .GlobalEnv,
>          sealed   = TRUE,
>          )

I think for package code, you don't want to specify the where to be
.GlobalEnv.  If you omit the where argument, the class will be defined
within the package environment which is what one usually wants.


> if (!isGeneric("plotObject")) {
>
>   setGeneric("plotObject",
>              def=function(x, y, ...) {
>                value <- standardGeneric("plotObject")
>                return(value)
>              },
>              where=.GlobalEnv,
>              useAsDefault=TRUE
>              )
> }

This idiom of conditionally defining an S4 generic is wide-spread and
I suspect was required at some point in time.  However, at this point,
I don't understand why one would do this and it seems that it can only
lead to hard to catch bugs.  I think it should be strongly discouraged.

To define a method on a generic, you need to know what that generic
is.  For example, you need to know the names of the formal arguments.
With conditional definition as above, you risk attempting to define a
method on a generic you know nothing about.

If you want your own generic, define it.  If you want to set a method
on someone else's generic, say so.  For example, you can do:

   setMethod(otherPkg::theirGeneric, ...)

> plotObject.foo <- function(x, y) {
>   plot(x,y)
> }
>
> setMethod("plotObject", signature=c("foo", "numeric"), plotObject.foo,
> where=.GlobalEnv)

This code is a bit confusing to read since an S3 method for class
"foo" and S3 generic plotObject would be plotObject.foo.  Maybe not
worth worrying about.

Finally, a further subtle point about how the generic was defined in
your example code.  Especially for a standardGeneric, it is best not
to name the result before returning as this can affect when results
get copied.  Here's an illustration:

   setGeneric("frob1", function(x) {
       value <- standardGeneric("frob1")
       value
   })
   
   setGeneric("frob2", function(x) {
       standardGeneric("frob2")
   })
   
   setMethod("frob1", "integer",
             function(x) vector(mode="integer", length=x))
   
   setMethod("frob2", "integer",
             function(x) vector(mode="integer", length=x))


   ###
   
   x1 <- frob1(5L)
   > tracemem(x1)
   [1] "<0x3de8098>"
   > x1[1L] <- 5L
   tracemem[0x3de8098 -> 0x3de80d0]: 
   > 
   > x2 <- frob2(5L)
   > tracemem(x2)
   [1] "<0x3de8140>"
   > x2[1L] <- 5L

Best Wishes,

+ seth

-- 
Seth Falcon | Computational Biology | Fred Hutchinson Cancer Research Center
http://bioconductor.org



More information about the R-devel mailing list