r语言 - S4方法调度慢吗?



我的S4类有一个被多次调用的方法。我注意到执行时间比单独调用类似函数要慢得多。因此,我在类中添加了一个类型为"function"的插槽,并使用该函数而不是方法。下面的示例展示了两种方法,它们都比相应的方法运行得快得多。此外,该示例还表明,方法的较低速度并不是因为方法必须从类中检索数据,因为即使函数也这样做,它们的速度也更快。

当然,这样做是不理想的。我想知道是否有一种方法来加速方法调度。有什么建议吗?
    setClass(Class = "SpeedTest", 
      representation = representation(
        x = "numeric",
        foo1 = "function",
        foo2 = "function"
      )
    )
    speedTest <- function(n) {
      new("SpeedTest",
        x = rnorm(n),
        foo1 = function(z) sqrt(abs(z)),
        foo2 = function() {}
      )
    }
    setGeneric(
      name = "method.foo",
      def = function(object) {standardGeneric("method.foo")}
    )
    setMethod(
      f = "method.foo", 
      signature = "SpeedTest",
      definition = function(object) {
        sqrt(abs(object@x))
      }
    )
    setGeneric(
      name = "create.foo2",
      def = function(object) {standardGeneric("create.foo2")}
    )
    setMethod(
      f = "create.foo2", 
      signature = "SpeedTest",
      definition = function(object) {
        z <- object@x
        object@foo2 <- function() sqrt(abs(z))
        object
      }
    )
    > st <- speedTest(1000)
    > st <- create.foo2(st)
    > 
    > iters <- 100000
    > 
    > system.time(for (i in seq(iters)) method.foo(st)) # slowest by far
       user  system elapsed 
       3.26    0.00    3.27 
    > # much faster 
    > system.time({foo1 <- st@foo1; x <- st@x; for (i in seq(iters)) foo1(x)}) 
       user  system elapsed 
      1.47    0.00    1.46 
    > # retrieving st@x instead of x does not affect speed
    > system.time({foo1 <- st@foo1; for (i in seq(iters)) foo1(st@x)}) 
       user  system elapsed 
       1.47    0.00    1.49 
    > # same speed as foo1 although no explicit argument
    > system.time({foo2 <- st@foo2; for (i in seq(iters)) foo2()}) 
       user  system elapsed 
       1.44    0.00    1.45 
     # Cannot increase speed by using a lambda to "eliminate" the argument of method.foo
     > system.time({foo <- function() method.foo(st); for (i in seq(iters)) foo()})  
        user  system elapsed 
        3.28    0.00    3.29

成本是方法查找,它在计时的每次迭代中从头开始。这可以通过计算一次方法调度来缩短时间

METHOD <- selectMethod(method.foo, class(st))
for (i in seq(iters)) METHOD(st)

这个(更好的方法查找)将是一个非常有趣和值得的项目;我们可以从其他动态语言中学到宝贵的经验,例如,维基百科动态调度页面上提到的内联缓存。

我想知道你做很多方法调用的原因是不是因为你的数据表示和方法的不完全向量化?

这并不能直接帮助您解决问题,但是使用微基准测试包对这类东西进行基准测试要容易得多:

f <- function(x) NULL
s3 <- function(x) UseMethod("s3")
s3.integer <- function(x) NULL
A <- setClass("A", representation(a = "list"))
setGeneric("s4", function(x) standardGeneric("s4"))
setMethod(s4, "A", function(x) NULL)
B <- setRefClass("B")
B$methods(r5 = function(x) NULL)
a <- A()
b <- B$new()
library(microbenchmark)
options(digits = 3)
microbenchmark(
  bare = NULL,
  fun = f(),
  s3 = s3(1L),
  s4 = s4(a),
  r5 = b$r5()
)
# Unit: nanoseconds
#  expr   min    lq median    uq   max neval
#  bare    13    20     22    29    36   100
#   fun   171   236    270   310   805   100
#    s3  2025  2478   2651  2869  8603   100
#    s4 10017 11029  11528 11905 36149   100
#    r5  9080 10003  10390 10804 61864   100

在我的计算机上,裸调用大约需要20 ns。将其封装在函数中会增加大约200ns的额外时间——这是创建函数执行环境的成本。S3方法调度大约增加3µs, S4/ref类大约增加12µs。

最新更新