[Rd] R 2.5.0 devel try issue in conjuntion with S4 method dispatch
ml-it-r-devel at epigenomics.com
ml-it-r-devel at epigenomics.com
Thu Mar 15 19:06:21 CET 2007
Hi,
after updating R 2.5.0 devel yesterday we today observed many new
unexpected failures in our daily package build and test system runs,
which can be traced to recent changes in the implementation in try()
(as noted in NEWS).
Investigating this new implementation I come across an issue in
conjuntion with using S4 classes and methods. try(expr) does not return an
object with attribute 'try-error' in case of method dispatch failure
in the wrapped expression which to me seems not
quite correct.
Examples to reproduce the observation:
## using functions all is well:
f <- function(x) { print(x); ret<-try(stop("forced.")); print(ret)}
f(3)
[1] 3
Error in try(stop("forced.")) : forced.
[1] "Error in try(stop(\"forced.\")) : forced.\n"
attr(,"class")
[1] "try-error"
## using S4 classes and methods
setClass("fooBase",
representation("VIRTUAL",
width = "numeric",
height = "numeric"),
prototype(width = 1024,
height = 1024),
validity = NULL,
where = .GlobalEnv,
sealed = TRUE,
)
if (!isGeneric("plotObject")) {
setGeneric("plotObject",
def=function(x, y, ...) {
value <- standardGeneric("plotObject")
return(value)
},
where=.GlobalEnv,
useAsDefault=TRUE
)
}
setClass("foo",
representation("fooBase"),
validity = NULL,
where = .GlobalEnv,
sealed = TRUE)
plotObject.foo <- function(x, y) {
plot(x,y)
}
setMethod("plotObject", signature=c("foo", "numeric"), plotObject.foo,
where=.GlobalEnv)
fooObject <- new("foo")
## should fail and return object with attribute 'try-error' set
ret <- try(plotObject(fooObject, character(1)))
Error in as.list(call)[[1]] == "doTryCatch" :
comparison (1) is possible only for atomic and list types
>is(ret)
Error in .class1(object) : object "ret" not found
which I belive is in contradiction to the documentation, where in
Details:
The value of the expression if 'expr' is evaluated without error,
but an invisible object of class '"try-error"' containing the
error message if it fails.
This is crucial for our current implementation of check functions in
package RUnit.
Is this new behaviour 'as intended' and only the documentation has not
caught up?
Regards,
Matthias
>sessionInfo()
R version 2.5.0 Under development (unstable) (2007-03-13 r40832)
i686-pc-linux-gnu
locale:
C
attached base packages:
[1] "stats" "graphics" "grDevices" "datasets" "utils" "methods"
[7] "base"
other attached packages:
rcompletion rcompgen
"0.1-2" "0.1-5"
--
Matthias Burger Project Manager/ Biostatistician
Epigenomics AG Kleine Praesidentenstr. 1 10178 Berlin, Germany
phone:+49-30-24345-371 fax:+49-30-24345-555
http://www.epigenomics.com matthias.burger at epigenomics.com
--
Epigenomics AG Berlin Amtsgericht Charlottenburg HRB 75861
Vorstand: Geert Nygaard (CEO/Vorsitzender), Dr. Kurt Berlin (CSO)
Oliver Schacht PhD (CFO), Christian Piepenbrock (COO)
Aufsichtsrat: Prof. Dr. Dr. hc. Rolf Krebs (Chairman/Vorsitzender)
More information about the R-devel
mailing list