I get an error when using self-defined (not standard) functions with mapply
with S4 objects from the raster package that I develop: "Error in
as.character(sys.call(sys.parent())[[1]]) :   cannot coerce type 'closure'
to vector of type 'character'".  Does anyone understand why? The problem is
illustrated below. Thanks, Robert


> # First a general example that works
> setClass('Foo',representation (value = 'numeric'))
> setMethod("Math", signature(x='Foo'),function(x){ x@value <-
callGeneric(x@value); x } )
[1] "Math"
> f <- new('Foo')
> f@value = 1
> ff <- list(f,f)
> e1 <- exp(f)
> e2 <- mapply(exp, ff)
> e3 <- mapply(function(x)exp(x), ff)
>


# Now for the raster package that also has the Math group generic
implemented
> library(raster)
Loading required package: sp
raster 2.0-41 (21-December-2012)
> r <- raster(ncol=3, nrow=3)
> r[] <- 1:9
> rr <- list(r,r)
> g1 <- exp(r)
> g2 <- mapply(exp, rr)
> g3 <- mapply(function(x)exp(x), rr)
Error in as.character(sys.call(sys.parent())[[1]]) :
  cannot coerce type 'closure' to vector of type 'character'
>
# For this simple example we could use lapply, and that works fine:
> gl <- lapply(rr, function(x)exp(x))


# but the below works fine (log is defined as a single method, overriding
its definition in the group generic)
> g4 <- mapply(function(x)log(x), rr)
# or when combining with methods from group generic Arith:
> g5 <- mapply(function(x)log(x*3), rr)


# Yet, I also fond problems with the Summary group generic; similar but
different error message.
> m1 <- max(rr[[1]], rr[[1]])
> m2 <- mapply(max, rr, rr)
Error in as.character(sys.call()[[1L]]) :
  cannot coerce type 'builtin' to vector of type 'character'





> sessionInfo()
R version 2.15.2 (2012-10-26)
Platform: x86_64-w64-mingw32/x64 (64-bit)

locale:
[1] LC_COLLATE=English_United States.1252  LC_CTYPE=English_United
States.1252    LC_MONETARY=English_United States.1252
[4] LC_NUMERIC=C                           LC_TIME=English_United
States.1252

attached base packages:
[1] stats     graphics  grDevices utils     datasets  methods   base

other attached packages:
[1] raster_2.0-41 sp_0.9-99

loaded via a namespace (and not attached):
[1] grid_2.15.2     lattice_0.20-10 tools_2.15.2
>

        [[alternative HTML version deleted]]

______________________________________________
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel

Reply via email to