[Rd] setMethod("c") [was: setMethod("Summary")]

Martin Maechler maechler at stat.math.ethz.ch
Tue Sep 5 17:47:59 CEST 2006


One reference to a very similar problem 
is  help(cbind2), 
about the cbind2() and rbind2() functions which I had added
to R a little while ago exactly for the same reason as we talk
about 'c()' or "c" here,
and thanks to original "hand holding" by you, John.

Martin

>>>>> "JMC" == John Chambers <jmc at r-project.org>
>>>>>     on Tue, 05 Sep 2006 11:28:12 -0400 writes:

    JMC> It's all very well to go on about efficiency, but the purpose of 
    JMC> statistical computing is insight into data, not saving CPU cycles (to 
    JMC> paraphrase Dick Hamming).

    JMC> S3 methods do some things fine; other tasks need more flexibility.  One 
    JMC> should ask what's important in a particular application and try to find 
    JMC> tools that match the needs well.

    JMC> Now, the c() function.  This has been discussed in various forms (and 
    JMC> languages) for some time.  As I remember and as far as I know, the only 
    JMC> really general way to ensure dispatch on _any_ applicable argument is to 
    JMC> turn the computation into a pair-wise one and define the methods (NOT S3 
    JMC> methods) for the two arguments of the pairwise function.

    JMC> I won't try to reproduce the details off the top of my head (if I locate 
    JMC> a reference I'll pass it on), but very roughly the idea is to say 
    JMC> something like

    JMC> cWithMethods <- function(x, ...) {
    JMC> if(nargs()<3)
    JMC> cPair(x,...)
    JMC> else
    JMC> cPair(x, cWithMethods(...))
    JMC> }

    JMC> and then write methods for cPair().

    JMC> John

    JMC> Robin Hankin wrote:
    >> Hello everybody.
    >> 
    >> I didn't see Franklin's first message; sorry.
    >> 
    >> Bearing in mind Professor Ripley's comments
    >> on the efficiency of S4 vs S3, I'm beginning to think I
    >> should just stick with S3 methods for my brob objects.  After
    >> all, S3 was perfectly adequate for the onion package.
    >> 
    >> Notwithstanding that,  here's my next problem.  I want to define a
    >> brob method for "c".  Using the example in package "arules" as a
    >> template (I couldn't see one in Matrix), I have
    >> 
    >> 
    >> setClass("brob",
    >> representation = representation 
    >> (x="numeric",positive="logical"),
    >> prototype      = list(x=numeric(),positive=logical())
    >> )
    >> 
    >> "brob" <- function(x,positive){
    >> if(missing(positive)){
    >> positive <- rep(TRUE,length(x))
    >> }
    >> if(length(positive)==1){
    >> positive <- rep(positive,length(x))
    >> }
    >> new("brob",x=x,positive=positive)
    >> }
    >> 
    >> setGeneric("getX",function(x){standardGeneric("getX")})
    >> setGeneric("getP",function(x){standardGeneric("getP")})
    >> setMethod("getX","brob",function(x){x at x})
    >> setMethod("getP","brob",function(x){x at positive})
    >> 
    >> 
    >> setMethod("c",signature(x="brob"),
    >> function(x, ..., recursive=FALSE){
    >> xx <- x at x
    >> xpos <- x at positive
    >> z <- list(...)
    >> return(
    >> brob(
    >> c(xx,do.call("c",lapply(z,getX))),
    >> c(xpos,do.call("c",lapply(z,getP)))
    >> )
    >> )
    >> }
    >> )
    >> 
    >> 
    >> 
    >> 
    >> Now,  this works for something like
    >> 
    >> > x <- new("brob",x=pi,positive=T)
    >> > c(x,x)
    >> 
    >> but c(1,x) isn't dispatched to my function.  How to
    >> deal cleanly with this case?   Perhaps if any argument
    >> to c() is a brob object, I would like to coerce them all to brobs.
    >> Is this possible?
    >> 
    >> 
    >> 
    >> 
    >> 
    >> 
    >> 
    >> 
    >> 
    >> 
    >> 
    >> 
    >> 
    >> --
    >> Robin Hankin
    >> Uncertainty Analyst
    >> National Oceanography Centre, Southampton
    >> European Way, Southampton SO14 3ZH, UK
    >> tel  023-8059-7743
    >> 
    >> ______________________________________________
    >> R-devel at r-project.org mailing list
    >> https://stat.ethz.ch/mailman/listinfo/r-devel
    >> 
    >> 

    JMC> ______________________________________________
    JMC> R-devel at r-project.org mailing list
    JMC> https://stat.ethz.ch/mailman/listinfo/r-devel




More information about the R-devel mailing list