Hey everyone,
I would like to develop a package using S4 classes.
I have to define several S4 classes that inherits from each others as
follow:
# A <- B <- C <- D
I also would like to define .DollarNames methods for these class so, if I
have understood well, I also have to define an old class as follow:
# AOld <- A <- B <- C <- D
setOldClass(Classes = "AOld")
setClass(
  Class = "A",
  contains = "AOld",
  slots = list(A = "character")
)
.DollarNames.A <- function(x, pattern)
  grep(pattern, slotNames(x), value = TRUE)
setClass(
  Class = "B",
  contains = "A",
  slots = list(B = "character"),
  validity = function(object){
    cat("Testing an object of class '", class(object),
        "'' with valitity function of class 'B'", sep
= "")
    cat("Validity test for class 'B': ", object at A, sep =
"")
    return(TRUE)
  }
)
setClass(
  Class = "C",
  contains = c("B"),
  slots = list(C = "character"),
  validity = function(object){
    cat("Testing an object of class '", class(object),
        "'' with valitity function of class 'C'", sep
= "")
    cat("Validity test for class 'C': ", object at A, sep =
"")
    return(TRUE)
  }
)
setClass(
  Class = "D",
  contains = "C",
  slots = list(D = "character"),
  validity = function(object){
    cat("Testing an object of class '", class(object),
        "'' with valitity function of class 'D'", sep
= "")
    cat("Validity test for class 'D': ", object at A, sep =
"")
    return(TRUE)
  }
)
My problem is that when I try to create an object of class "D" and
test its
validity
validObject(new("D"))
it seems that at some point the object is coerced to an object of class
"AOld" and tested by the validity function of class "B".
What am I missing
here?
Julien
	[[alternative HTML version deleted]]
On 05/28/2015 02:49 AM, Julien Id? wrote:> Hey everyone, > > I would like to develop a package using S4 classes. > I have to define several S4 classes that inherits from each others as > follow: > > # A <- B <- C <- D > > I also would like to define .DollarNames methods for these class so, if I > have understood well, I also have to define an old class as follow: > > # AOld <- A <- B <- C <- D > > setOldClass(Classes = "AOld") > > setClass( > Class = "A", > contains = "AOld", > slots = list(A = "character") > ) > > .DollarNames.A <- function(x, pattern) > grep(pattern, slotNames(x), value = TRUE)Instead of setOldClass, define a $ method on A setMethod("$", "A", function(x, name) slot(x, name)) And then a = new("A") a$<tab> d = new("D") d$<tab> I don't know about the setOldClass problem; it seems like a bug. Martin Morgan> > setClass( > Class = "B", > contains = "A", > slots = list(B = "character"), > validity = function(object){ > cat("Testing an object of class '", class(object), > "'' with valitity function of class 'B'", sep = "") > cat("Validity test for class 'B': ", object at A, sep = "") > return(TRUE) > } > ) > > setClass( > Class = "C", > contains = c("B"), > slots = list(C = "character"), > validity = function(object){ > cat("Testing an object of class '", class(object), > "'' with valitity function of class 'C'", sep = "") > cat("Validity test for class 'C': ", object at A, sep = "") > return(TRUE) > } > ) > > setClass( > Class = "D", > contains = "C", > slots = list(D = "character"), > validity = function(object){ > cat("Testing an object of class '", class(object), > "'' with valitity function of class 'D'", sep = "") > cat("Validity test for class 'D': ", object at A, sep = "") > return(TRUE) > } > ) > > My problem is that when I try to create an object of class "D" and test its > validity > > validObject(new("D")) > > it seems that at some point the object is coerced to an object of class > "AOld" and tested by the validity function of class "B". What am I missing > here? > > Julien > > [[alternative HTML version deleted]] > > ______________________________________________ > R-devel at r-project.org mailing list > https://stat.ethz.ch/mailman/listinfo/r-devel >-- 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
The problem seems to be with coercion, actually, not validity methods per se:> mydObject of class "D" <S4 Type Object> attr(,"class") [1] "AOldclass" Slot "D": character(0) Slot "C": character(0) Slot "B": character(0) Slot "A": character(0)> as(myd, "B")Object of class "AOldclass" <S4 Type Object> attr(,"class") [1] "AOldclass" This comes from the coercion method that is automatically generated for going from D to B. Recreating what as() does, we get (emphasis mine, of course):> thisClass = "D" > Class = "B" > where <- .classEnv(thisClass, mustFind = FALSE) > coerceMethods <- methods:::.getMethodsTable(coerceFun,environment(coerceFun), + inherited=TRUE)> asMethod = methods:::.quickCoerceSelect(thisClass, Class, coerceFun,+ coerceMethods, where)> asMethodMethod Definition: function (from, to = "B", *strict = TRUE*) *if (strict) { S3Part(from)* } else from Signatures: from to target "D" "B" defined "D" "B" Since S3 classes can't have validity methods anyway, I would conjecture that passing strict = FALSE to the line errors <- c(errors, anyStrings(validityMethod(as(object, superClass)))) in validObject() would fix this. I haven't tested that hypothesis though, so there may be cases where such a patch breaks other functionality. ~G On Thu, May 28, 2015 at 7:30 AM, Martin Morgan <mtmorgan at fredhutch.org> wrote:> On 05/28/2015 02:49 AM, Julien Id? wrote: > >> Hey everyone, >> >> I would like to develop a package using S4 classes. >> I have to define several S4 classes that inherits from each others as >> follow: >> >> # A <- B <- C <- D >> >> I also would like to define .DollarNames methods for these class so, if I >> have understood well, I also have to define an old class as follow: >> >> # AOld <- A <- B <- C <- D >> >> setOldClass(Classes = "AOld") >> >> setClass( >> Class = "A", >> contains = "AOld", >> slots = list(A = "character") >> ) >> >> .DollarNames.A <- function(x, pattern) >> grep(pattern, slotNames(x), value = TRUE) >> > > Instead of setOldClass, define a $ method on A > > setMethod("$", "A", function(x, name) slot(x, name)) > > And then > > a = new("A") > a$<tab> > d = new("D") > d$<tab> > > I don't know about the setOldClass problem; it seems like a bug. > > Martin Morgan > > > >> setClass( >> Class = "B", >> contains = "A", >> slots = list(B = "character"), >> validity = function(object){ >> cat("Testing an object of class '", class(object), >> "'' with valitity function of class 'B'", sep = "") >> cat("Validity test for class 'B': ", object at A, sep = "") >> return(TRUE) >> } >> ) >> >> setClass( >> Class = "C", >> contains = c("B"), >> slots = list(C = "character"), >> validity = function(object){ >> cat("Testing an object of class '", class(object), >> "'' with valitity function of class 'C'", sep = "") >> cat("Validity test for class 'C': ", object at A, sep = "") >> return(TRUE) >> } >> ) >> >> setClass( >> Class = "D", >> contains = "C", >> slots = list(D = "character"), >> validity = function(object){ >> cat("Testing an object of class '", class(object), >> "'' with valitity function of class 'D'", sep = "") >> cat("Validity test for class 'D': ", object at A, sep = "") >> return(TRUE) >> } >> ) >> >> My problem is that when I try to create an object of class "D" and test >> its >> validity >> >> validObject(new("D")) >> >> it seems that at some point the object is coerced to an object of class >> "AOld" and tested by the validity function of class "B". What am I missing >> here? >> >> Julien >> >> [[alternative HTML version deleted]] >> >> ______________________________________________ >> R-devel at r-project.org mailing list >> https://stat.ethz.ch/mailman/listinfo/r-devel >> >> > > -- > 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 > > > ______________________________________________ > R-devel at r-project.org mailing list > https://stat.ethz.ch/mailman/listinfo/r-devel >-- Gabriel Becker, PhD Computational Biologist Bioinformatics and Computational Biology Genentech, Inc. [[alternative HTML version deleted]]
On Thu, May 28, 2015 at 2:49 AM, Julien Id? <julien.ide.fr at gmail.com> wrote:> Hey everyone, > > I would like to develop a package using S4 classes. > I have to define several S4 classes that inherits from each others as > follow: > > # A <- B <- C <- D > > I also would like to define .DollarNames methods for these class so, if I > have understood well, I also have to define an old class as follow: > > # AOld <- A <- B <- C <- D > > setOldClass(Classes = "AOld") >No, you don't need to define an old class for dispatching on an S3 generic. Forget the AOld and things will dispatch to .DollarNames.A just fine. That said, a few notes for posterity: First, if you're going to define an S4 class that extends an old class, you probably want to give the old class a prototype, so that calling e.g. new("A") will actually give an object that is valid for existing S3 methods on that class. Second, there seems to be a bug that breaks that strategy, because even when the old class has a prototype, it is not taken as the prototype of the extension (A). Instead, there is a plain "S4" prototype, with the class set to "Old".> setOldClass("Old", prototype=structure(list(), class="Old")) > setClass("New", contains="Old") > new("New")Object of class "New" <S4 Type Object> attr(,"class") [1] "Old" But this is still possible:> new("New", structure(list(), class="Old"))Object of class "New" An object of class "Old" Third, the fact that as(new("C"), "B") works as expected but not as(new("D"), "B") is probably also a bug. Fourth, calling setOldClass is essentially specifying a contract to which the S3 system is not bound, so it is extremely risky. If it is absolutely necessary to include an S3 object in an S4 representation, best practice is to isolate that dependency to the greatest extent possible, i.e., create an object that specifically encapsulates that S3 object, thus centralizing all of the necessary consistency checks.> setClass( > Class = "A", > contains = "AOld", > slots = list(A = "character") > ) > > .DollarNames.A <- function(x, pattern) > grep(pattern, slotNames(x), value = TRUE) > > setClass( > Class = "B", > contains = "A", > slots = list(B = "character"), > validity = function(object){ > cat("Testing an object of class '", class(object), > "'' with valitity function of class 'B'", sep = "") > cat("Validity test for class 'B': ", object at A, sep = "") > return(TRUE) > } > ) > > setClass( > Class = "C", > contains = c("B"), > slots = list(C = "character"), > validity = function(object){ > cat("Testing an object of class '", class(object), > "'' with valitity function of class 'C'", sep = "") > cat("Validity test for class 'C': ", object at A, sep = "") > return(TRUE) > } > ) > > setClass( > Class = "D", > contains = "C", > slots = list(D = "character"), > validity = function(object){ > cat("Testing an object of class '", class(object), > "'' with valitity function of class 'D'", sep = "") > cat("Validity test for class 'D': ", object at A, sep = "") > return(TRUE) > } > ) > > My problem is that when I try to create an object of class "D" and test its > validity > > validObject(new("D")) > > it seems that at some point the object is coerced to an object of class > "AOld" and tested by the validity function of class "B". What am I missing > here? > > Julien > > [[alternative HTML version deleted]] > > ______________________________________________ > R-devel at r-project.org mailing list > https://stat.ethz.ch/mailman/listinfo/r-devel