[Rd] S4 group "Math", "getGroupMembers", "genericForPrimitive"

John Chambers jmc at research.bell-labs.com
Wed Jun 30 23:16:58 CEST 2004


R is not S4, the system that the green book describes, although we try
to be compatible where there is not a serious reason to be different. 
The behavior of group generics and of the basic functions, such as those
in the Math group, differs.

First, functions such as "log", "sin", and their peers are not generic
functions by default in R.

Second, defining methods for the group generic does not automatically
turn the members of the group into generic functions.

Some comments about the reason for this approach are given below.  But
the implication is that code wishing to define methods for the group
generic needs to ensure that all the relevant group members are set to
be generic functions from the group.

We can provide a function that does this in one step (if no problems
arise, it will be in the next release).  A simple version of it would
look like this:

setGroupMembersOn <- function(group) {
    groupFun <- getGeneric(group)
    for(fun in groupFun at groupMembers)
        if(!isGeneric(fun) && !is.primitive(getFunction(fun)))
            setGeneric(fun, group = group)
}

            
The actual version will be somewhat more careful, but this should work
in the obvious cases.

Calling
   setGroupMembersOn("Math")
either before or after the setMethod() calls, seems to give the desired
effect.

End of the practical part.  Some comments on this and on the other
questions in your mail:

- The reason for the two differences noted from S4 is efficiency.  When
S4-style methods were being introduced in R, there was concern not to
slow down basic computations on basic data (e.g, math functions on
ordinary numeric vectors).  Therefore, the math functions are left
non-generic by default and setting group methods does not change that. 
The exception is that functions which are primitives in R have special
code for dispatching methods.  This code exits quickly for ordinary
vectors.  So primitive functions ARE dispatched.

Some of the Math group are primitive functions and some are not.  That's
why there is inconsistent behavior.  It will stay that way unless the R
developers decide that consistency is worth the inefficiency of turning
the non-primitves into generic functions. (Probably will have to wait
until method dispatch can be made more efficient.)

What we can & should do for the next release is to include the
explanation in the documentation of group generic functions.

- as for the getGroupMembers function, yes it seems good to add that for
compatibility.  But notice that the current implementation stores the
members as a slot in the group generic function object.  So
  Math at groupMembers
gives a list of the members, as would getGroupMembers("Math").

- genericForPrimitive does not appear because it is not exported from
the namespace in the methods package (and probably shouldn't be, since
it's not really meaningful apart from the current implementation).

Matthias.Kohl at uni-bayreuth.de wrote:
> 
> Hi,
> 
> I found the following on Windows 2000/NT
> R Version 1.9.1  (2004-06-21) (also Version 1.9.0):
> 
> The S4 group "Math" doesn't work as documented; i.e., "log", "log10",
> "gamma" and "lgamma" are included
> in the documentation but don't work. See example code below.
> 
> Moreover, what about 'genericForPrimitive' which is used
> in 'getGeneric'. It seems that this method is not included in
> the R Version 1.9.1 (also 1.9.0). See the example code of
> John Chambers at the end of this email.
> 
> Why not add the method 'getGroupMembers' as proposed by John Chambers
> to the methods package?
> (see reply to mail: "Missing 'getGroupMembers()'"
>  from Sat May 31 2003 - 15:18:18 EDT)
> 
> Thanks for your attention,
> Matthias
> 
> ###################################################
> ## Example Code
> ###################################################
> ## Example Code from the "green book"
> setClass("track", representation(x = "numeric", y = "numeric"))
> 
> setMethod("Math", "track",
>             function(x){ x at y = callGeneric(x at y); x })
> 
> tr1 <- new("track", x = 1:3, y = 1:3)
> tr1
> 
> ## are documented as belonging to group "Math"
> ## see ?"Math"
> ## but don't work
> log(tr1)
> log10(tr1)
> gamma(tr1)
> lgamma(tr1)
> 
> ## are not generic and don't belong to any group!
> is("log", "genericFunction")
> is("log10", "genericFunction")
> is("gamma", "genericFunction")
> is("lgamma", "genericFunction")
> getGroup("log")
> getGroup("log10")
> getGroup("gamma")
> getGroup("lgamma")
> 
> ## make this functions generic and add to group "Math"
> ## (only local!)
> setGeneric("log", function(x, base) standardGeneric("log"), group = "Math")
> setGeneric("log10", function(x) standardGeneric("log10"), group = "Math")
> setGeneric("gamma", function(x) standardGeneric("gamma"), group = "Math")
> setGeneric("lgamma", function(x) standardGeneric("lgamma"), group = "Math")
> 
> setMethod("Math", "track",
>             function(x){ x at y = callGeneric(x at y); x })
> 
> ## now works as documented
> log(tr1)
> log10(tr1)
> gamma(tr1)
> lgamma(tr1)
> 
> ## By John Chambers:
> ## "... the following code implements what one is
> ## likely to want in most cases." (see reply
> ## to mail: "Missing 'getGroupMembers()'"
> ## from Sat May 31 2003 - 15:18:18 EDT)
> ## Modification of this code
> ## since 'genericForPrimitive' is not defined (?)
> ## although it is called in 'getGeneric'!!!
> getGroups <- function(what = c(getGenerics(), names(.BasicFunsList))) {
>     what <- what[what != "is.function"]
>     what <- what[what != "is.null"]
>     what <- what[what != "is.object"]
>     g <-unlist(sapply(what,
>           function(x){
>                 f <- getGeneric(x)
>                 if(is(f, "genericFunction"))f at group else NULL
>           }))
>     split(names(g), g)
> }
> getGroupMembers <- function(group, whatGenerics) {
>     groups <- if(missing(whatGenerics)) getGroups()
>               else getGroups(whatGenerics)
>     elNamed(groups, group)
> }
> 
> ______________________________________________
> 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