[R] Google's R Style Guide

Gabor Grothendieck ggrothendieck at gmail.com
Tue Sep 1 15:34:00 CEST 2009


On Tue, Sep 1, 2009 at 8:58 AM, Martin Morgan<mtmorgan at fhcrc.org> wrote:
> It seems relevant to compare S3 and S4 code for doing S3-style
> programming, leaving more 'advanced' S4 for another day. In S3 I might
> define a simple class and method as
>
>
> makeS3Foo <-
>    function(x=numeric(), y=numeric())
> {
>    if (class(x) != "numeric")
>        stop("'x' must be numeric")
>    if (class(y) != "numeric")
>        stop("'y' must be numeric")
>    l <- list(x=x, y=y)
>    class(l) <- "S3Foo"
>    l
> }

This shorter version would suffice:

makeS3Foo <- function(x = numeric(), y = numeric()) {
   stopifnot(inherits(x, "numeric"), inherits(y, "numeric"))
   structure(list(x = x, y = y), class = "S3Foo")
}
doS3 <- function(x, ...) UseMethod("doS3")
doS3.S3Foo <- function(x, ...) "doS3 of S3Foo"
doS3.default <- function(x, ...) "doS3 default"

>
> doS3 <- function(x, ...) NextMethod("doS3")
>
> doS3.default <- function(x, ...) "doS3 default"
>
> doS3.S3Foo <- function(x, ...) "doS3 of S3Foo"
>
>
> with an example of use being
>
>> doS3(makeS3Foo())
> [1] "doS3 of S3Foo"
>
>
> I use 'makeS3Foo' as a constructor, so that whenever I make an instance
> of what I'm calling class S3Foo, I have some guarantees about its structure.
>
> The S4 implementation might be
>
>
> setClass("S4Foo", representation(x="numeric", y="numeric"))
>
> makeS4Foo <-
>    function(x = numeric(), y=numeric(), ...)
> {
>    new("S4Foo", x=x, y=y, ...)
> }
>
> setGeneric("doS4", function(x, ...) standardGeneric("doS4"),
>           useAsDefault=function(x, ...) "do default")
>
> setMethod("doS4", "S4Foo", function(x, ...) "doS4 of S4Foo")
>
> and use with
>
>> doS4(makeS4Foo())
> [1] "doS4 of S4Foo"
>
> It seems like the translation between the two is really quite
> transparent, and equally arcane to someone new to R.
>
> Some things I get from S4 are a level of automatic type checking
>
>> makeS4Foo(x="bar")
> Error in validObject(.Object) :
>  invalid class "S4Foo" object: invalid object for slot "x" in class
> "S4Foo": got class "character", should be or extend class "numeric"

This is also the case for S3 (despite the use of less code for S3).

  > makeS3Foo(x = "bar")
  Error: inherits(x, "numeric") is not TRUE

>
> a way of knowing that my 'S4Foo' conforms to expectations -- in S3 I can say
>
>  l = list(a=1, b=2)
>  class(l) <- "S3Foo"
>
> and have no way of knowing whether this is 'valid' or not; in S4 I would
> not use this method of creating a class (I'd use my constructor, or
> perhaps 'new' if I were being undisciplined, and get type checking as
> above) but if I did I'd be able to find

Its not too likely that one will do the above if they are given a
constructor like makeS3Foo.  On the other hand the ability
to work at a lower level means that one can create variations
of objects which were not originally anticipated thus avoiding
having to design the system for every possible eventuality.

>
>> class(l) <- "S4Foo"
>> validObject(l)
> Error in validObject(l) :
>  invalid class "S4Foo" object: slots in class definition but not in
> object: "x", "y"
>
> an error when I try and access data not in the class (normally I'd have
> made a constructor, and not use slot access @ directly)
>
>> makeS3Foo()$z
> NULL
>> makeS4Foo()@z
> Error: no slot of name "z" for this object of class "S4Foo"
>
> and reflection on the class
>
>> getClass("S4Foo")
> Class “S4Foo” [in ".GlobalEnv"]
>
> Slots:
>
> Name:        x       y
> Class: numeric numeric

But overall its easier to access the methods and objects in
S3 so discovering what is going on is easier.




More information about the R-help mailing list