Avoid argument duplication when passing through (…)

人盡茶涼 提交于 2019-12-30 07:51:54

问题


Consider the function

f <- function(x, X) mean(c(x,X))

How can I automatically (by manipulation of f()) change the signature of f() such that it can be used with lapply(), i.e., without returning the following obvious error?

lapply(X=list(1), FUN=f, X=1)
Error in lapply(X = list(1), FUN = f, X = 1) : 
  formal argument "X" matched by multiple actual arguments

The approach I used so far is to remove all arguments from f(), assign them into an environment, and evaluatef() in that environment.

integrateArgs <- function (f, args) 
{
    form <- formals(f)
    if (!is.null(form)) 
        for (i in seq_along(form)) assign(names(form)[i], form[[i]])
    if (!is.null(args)) 
        for (i in seq_along(args)) assign(names(args)[i], args[[i]])
    ff <- function() {
    }
    parent.env(environment(ff)) <- parent.env(environment(f))
    body(ff) <- body(f)
    if (any(names(form) == "...")) 
        formals(ff) <- form[names(form) == "..."]
    ff
}
fnew <- integrateArgs(f, list(x=1, X=4))
lapply(list(fnew), function(x) x())
[[1]]
[1] 2.5

However, that approach leads to the following error if f() is a function from another R package that calls compiled code.

fnew2 <- integrateArgs(dnorm, list(x=1, mean=4))
lapply(list(fnew2), function(x) x())
Error in x() (from #1) : object 'C_dnorm' not found

Are there better solutions?


回答1:


As suggested in a comment by MrFlick, one solution is

library(purrr)
integrateArgs <- function(f, args){
    do.call(partial, c(list(f), args))
}
fnew2 <- integrateArgs(dnorm, list(x=1, mean=4))
lapply(list(fnew2), function(x) x())
[[1]]
[1] 0.004431848

The following similar approach does not require the package purrr:

integrateArgs <- function(f, args){
    do.call(function(f, ...) {
        eval(call("function", NULL,
                  substitute(f(...))), envir = environment(f))}, 
        c(f = list(f), args))
}
fnew2 <- integrateArgs(dnorm, list(x=1, mean=4))
lapply(list(fnew2), function(x) x())
[[1]]
[1] 0.004431848

A similar approach is now used in optimParallel version 0.7-4 to execute functions in parallel using parallel::parLapply(): https://cran.r-project.org/package=optimParallel



来源:https://stackoverflow.com/questions/52771870/avoid-argument-duplication-when-passing-through

易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!