[Rd] Problem with setValidity() or resetClass() or ... ?

Matthias Kohl Matthias.Kohl at uni-bayreuth.de
Fri Jun 18 11:48:02 CEST 2004


Hi,

I'm working with Version 1.9.0  (2004-04-12) on Windows 98/NT/2000 where 
I found the following wrong (?) behavior of setValidity().
I already mentioned this on the R-help list (2004-06-11, was 
"setValidity changes Extends?") , but as I got no answer I tried to 
figure out what's happening.

Well, setValidity() behaves not as I would expect (something about the 
superclasses is lost,
but nothing about the subclasses, see code below)
So, I did some debugging and it seems to be caused by resetClass() which 
calls completeClassDefinition() which calls ... (see the example code 
and the explanations below)

Unfortunately, I couldn't really figure out which of the called methods 
is doing the "wrong thing".

Would someone explain me this?

Best regards,
Matthias


##########################################
## Example code
##########################################
setClass("Class1", representation("name" = "character"))

if(!isGeneric("name")) setGeneric("name", function(object)
standardGeneric("name"))
setMethod("name", "Class1", function(object) object at name)

setClass("Class2", representation("Class1"))
setClass("Class3", representation("Class2"))
setClass("Class4", representation("Class3"))
setClass("Class5", representation("Class4"))

getClass("Class3") # as I expected

Class3Def <- getClassDef("Class3", where = topenv(parent.frame()))

## the following is called in setValidity() via resetClass()
## (further explanations, see below)
completeClassDefinition("Class3", Class3Def,
        where = topenv(parent.frame()), doExtends = TRUE)
## 'Extends' includs only "Class2"
##
## would give the right result *in this case*
completeClassDefinition("Class3", Class3Def,
        where = topenv(parent.frame()), doExtends = FALSE)
## (no call to completeExtends(), as doExtends = FALSE)
## probably no good idea

validClass3 <- function(object){TRUE}
setValidity("Class3", validClass3)
## nothing seems to be lost
## concerning the subclasses!

C3 <- new("Class3")
is(C3, "Class1") # o.k.
extends("Class3", "Class1") # o.k.

## But something gets lost
## concerning the superclasses!
name(C3) # generates an error!

## The subclasses work as expected
getClass("Class4") # o.k.
getClass("Class5") # o.k.
C4 <- new("Class4")
name(C4) # o.k.
C5 <- new("Class5")
name(C5) # o.k.

## Some debugging ...
##
## after the call of resetClass() in the setValidity() method
## the complete definition of the Class3 is (see: ?resetClass)
##      "(...) re-computed, from the representation
##      and superclasses specified in the original
##      call to 'setClass' (...)
##      (but doing that in the  middle of a session is living
##      dangerously, since it may invalidate existing objects)"
##      (seems to happen here)
##
## The original call to 'setClass' "finds" all
## superclasses, but resetClass() doesn't. Why?

## resetClass() calls completeClassDefinition() which
##      "Completes the definition of 'Class', relative to the
##      class definitions visible from environment 'where'. 
##      If 'doExtends' is 'TRUE', complete the super- and
##      sub-class information." (see: ?completeClassDefinition())
##      (the default value of 'doExtends' is TRUE)
##
## Shouldn't this give the *complete* class definition?

## completeClassDefinition() calls completeExtends() as
## 'doExtends = TRUE' (by default)
## Using debug(completeExtends) shows
## .uncompleteClassDefinition(ClassDef, "contains")
## is called. After this call "Extends" of ClassDef contains
## only 'Class2'
##
## Why is this necessary?
## In this step (I think) the information about
## 'Class1' is lost.
##
## The variable 'exts' which is involved in the calculations
## has length = 2 and would still contain the information
## that 'Class2' extends 'Class1'.
## But, then 'getAllSuperClasses(ClassDef)' is called which
## returns "only" 'Class2' (as already 'ClassDef' contains
## only 'Class2') and 'exts' is reduced to exts["Class2"]
## which is then returned.
##
## 'getAllSuperClasses(ClassDef)' calls 'superClassDepth()'
## which don't get "all" but only 'Class2'
## But, for me this seems to be right, since 'ClassDef'
## (in the call) contains only the information about 'Class2'.



More information about the R-devel mailing list