[R] How to define S4 methods for '['

Gabor Grothendieck ggrothendieck at gmail.com
Tue Jun 21 14:10:28 CEST 2005


I don't think conversion to a list is necessary, e.g.

f <- function(x, y, ...) {
	cl <- sys.call()
	if (missing(y)) cl$y <- FALSE
	cl[[1]] <- as.name("cat")
	cl[[2]] <- rev(x)
	eval(cl)
}
f(1:4)  # 4 3 2 1 FALSE



On 6/21/05, giles.heywood at uk.abnamro.com <giles.heywood at uk.abnamro.com> wrote:
> 
> 
> 
> 
> I have found this a useful correspondence.  My own wish is to define a new
> S4 class which differs from
> class 'array' only in its default handling of the 'drop' argument i.e.
> drop=FALSE - not an unusual wish.
> 
> My solution is the following:
> 
> setClass("noDropArray",representation("array"),prototype=array(NA,2:4))
> 
> setMethod('[','noDropArray',function(x,i,j,drop,...){
>    cl<-as.list(sys.call())
>    if( !("drop"%in%names(as.list(sys.call()))) )
>        cl <-  c(cl,drop=FALSE)
>    cl[[2]]<-x at .Data
>    eval(as.call(cl))
>    })
> 
> new("noDropArray")[1,1,1]
> 
> This behaves as I would expect.  However I have an uncomfortable feeling
> that this is not the most
> elegant solution.
> 
> Any comments?
> 
> - Giles
> 
> 
> > Thanks to Robert and Gabor for their replies, but neither was what I was
> > looking for, undoubtedly because of the poor phrasing of my question (+ a
> > typo -- however, even if correctly typed it doesn't work). I finally
> > realized that the "elegant" approach I sought can easily be done without
> > setGeneric:
> 
> > setMethod('[','foo',function(x,i,j,drop,...){
> >    cl<-as.list(sys.call())
> >    cl[[2]]<-x at dat
> >    eval(as.call(cl))
> >    })
> 
> > Indeed, this is a general template for this sort of thing. Should have
> > thought of this before, as V&R's S PROGRAMMING has numerous such
> examples...
> > Sigh...
> 
> > -- Bert
> 
> -----Original Message-----
> From: Gabor Grothendieck [mailto:ggrothendieck at gmail.com]
> Sent: Monday, June 20, 2005 1:31 PM
> To: Berton Gunter
> Cc: r-help at stat.math.ethz.ch
> Subject: Re: [R] How to define S4 methods for '['
> 
> On 6/20/05, Berton Gunter <gunter.berton at gene.com> wrote:
> > Folks:
> >
> > This is a question about the S4 formal class system.
> >
> > Suppose I have a class, 'foo', defined by:
> >
> > setClass('foo',representation(dat='matrix', id='character') )
> >
> > I wish to define a '[' method for foo that will extract from the 'dat'
> slot.
> > I would have thought that the following would work, but it doesn't:
> >
> > setMethod("[","foo",function(x,i, j, .,drop=TRUE)callGeneric(x at dat,i,
> > j,drop=drop) )
> >
> > The only way I have succeeded in defining this method is using brute
> force
> > eval(parse(. :
> >
> > {eval(parse(text=paste('.dat(x)[',
> >        ifelse(missing(i),',','i,'),
> >        ifelse(missing(j),']','j]'))))
> >        }
> >
> > This works. However, I am not able under any circumstances to pass the
> drop
> > argument -- it is ignored.
> >
> > I would appreciate any pointers about how to do this properly. If  this
> is
> > explicitly in the Green Book (I do not have it with me at the moment),
> that
> > will suffice.
> >
> 
> Download the source to the 'its' package where an S4 [ method is defined.
> 
> ______________________________________________
> R-help at stat.math.ethz.ch mailing list
> https://stat.ethz.ch/mailman/listinfo/r-help
> PLEASE do read the posting guide!
> http://www.R-project.org/posting-guide.html
> 
> 
> ---------------------------------------------------------------------------
> This message (including any attachments) is confidential and...{{dropped}}
> 
> ______________________________________________
> R-help at stat.math.ethz.ch mailing list
> https://stat.ethz.ch/mailman/listinfo/r-help
> PLEASE do read the posting guide! http://www.R-project.org/posting-guide.html
>




More information about the R-help mailing list