[R] slot assignment in S4 classes
    Martin Morgan 
    mtmorgan at fhcrc.org
       
    Wed May 12 15:21:48 CEST 2010
    
    
  
On 05/12/2010 01:48 AM, Albert-Jan Roskam wrote:
> Hi R friends,
>  
> I'm still studying S4 classes and I have a question about slot
assignment. Why would I have to use a special setter method [example 2
below] if I can assign data to a slot directly when I call new()
[example 1 below]?
>  
> ## first way to do it (the idiosyncratic way?)
> setClass(Class = "TestClass", representation = representation(myDf = "data.frame"))
> setGeneric(name = "doStuff", def = function(object, ...){standardGeneric("doStuff")})
> setMethod(f = "doStuff",
>    signature = "TestClass",
>    definition = function(object, ...) {
>      return( object at myDf )
> }) 
> df_a <- data.frame(cbind(letters=letters, digits=runif(26)))
> instance <- new(Class = "TestClass", myDf = df_a) # direct slot assignment. Is this bad? If so, why?
'new' is useful for constructing new objects, exactly as is being done
here. It is probably better to write
  TestClass <- function(df)
  {
      new("TestClass", myDf=df)
  }
This is easier to enter at the command line ('TestClass(df_a)'), allows
you to document for your users the arguments to the constructor, and
helps to separate the implementation details from the interface. On the
latter point, you might decide to change the representation to contain
two slots 'letters' and 'digits', and add a validity method to ensure
that these were the same length. Your user might still naturally want to
create an object from a data.frame, and you'd merely change your constructor
  TestClass <- function(df)
  {
      new("TestClass", letters=df[["letters"]], digits=df[["digits"]])
  }
> doStuff(instance)
>  
> ## second way to do it (the R way?)
> setClass(Class = "TestClass", representation = representation(myDf = "data.frame"))
> setGeneric(name = "doStuff", def = function(object, ...){standardGeneric("doStuff")})
> setMethod(f = "doStuff",
>    signature = "TestClass",
>    definition = function(object, ...) {
>      return( object at myDf )
> }) 
> setGeneric(name = "setDoStuff<-", def = function(object, value){standardGeneric("setDoStuff<-")})
> setReplaceMethod(f = "setDoStuff",
>    signature = "TestClass",
>    definition = function(object, value) {
>      object at myDf <- value
>      return( object )
> }) 
> df_b <- data.frame(cbind(letters=LETTERS, digits=runif(26)))
> instance <- new(Class = "TestClass")
> setDoStuff(instance)<-df_b
It would be unusual to require that your user _construct_ an instance
this way, but very natural for the user to update the instance using a
replacement method like this (rather than direct slot access using @ or
slot<-).
A more advanced variation on the replacement method implementation is to
write
  initialize(object, myDf=value)
rather than
  object at myDf <- value
  object
This places restrictions on how 'initialize' methods are implemented,
but calls validObject and allows for multiple slots to be updated at the
same time (reducing the amount of copying involved).
Martin
> doStuff(instance)
> 
> Thank you in advance for your replies!
> 
> Cheers!!
> Albert-Jan
> 
> ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
> All right, but apart from the sanitation, the medicine, education, wine, public order, irrigation, roads, a fresh water system, and public health, what have the Romans ever done for us?
> ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
> 
> 
>       
> 	[[alternative HTML version deleted]]
> 
> 
> 
> 
> ______________________________________________
> R-help at r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-help
> PLEASE do read the posting guide http://www.R-project.org/posting-guide.html
> and provide commented, minimal, self-contained, reproducible code.
-- 
Martin Morgan
Computational Biology / Fred Hutchinson Cancer Research Center
1100 Fairview Ave. N.
PO Box 19024 Seattle, WA 98109
Location: Arnold Building M1 B861
Phone: (206) 667-2793
    
    
More information about the R-help
mailing list