[R] Building the call of an arbitrary function
Vincent Goulet
vincent.goulet at act.ulaval.ca
Wed Sep 20 19:41:27 CEST 2006
Le Dimanche 17 Septembre 2006 14:12, Duncan Murdoch a écrit :
> On 9/17/2006 12:36 PM, Vincent Goulet wrote:
> > Hy all,
> >
> > Is there a direct way to build the complete function call of an arbitrary
> > function?
> >
> > Here's what I want to do. A function will build a function which will
> > itself call a probability density function for some law given in argument
> > to the
> >
> > first function:
> >> f("gamma", 1000)
> >
> > will return, say,
> >
> > function(x, shape, rate, scale = 1/rate)
> > dgamma(x + 1000, shape, rate, scale = 1/rate)
> >
> > (Notice that the arguments of the output function are those of dgamma().)
> >
> > I tried all sorts of combinations of call(), formals(), args() et al. to
> > no avail. But then, I avoided, so far, to build the whole thing as a
> > character string. Would it be the only option?
>
> No, do.call is what you want.
>
> dgamma(x + 1000, shape, rate, scale = 1/rate)
>
> is the same as
>
> do.call("dgamma", list(x+1000, shape, rate, scale=1/rate))
>
> But since you're going to have to look up the parameters that are
> appropriate to your target density (i.e. shape, rate, scale), I'm not
> sure how useful this will be. It might be easier just to code the call
> to dgamma directly.
>
> Duncan Murdoch
First, thanks to both Duncan and Gabor for their useful reply. do.call() was
part of the "et al." functions I looked up, but I only tried it
interactively (where the call is immediately executed after being built) and
so dismissed it.
After some more struggling (hence the delay in my reply), I was able to do
exactly what I want without using strings. For the record, here's my
solution:
f <- function(dist, y)
{
dist <- paste("d", dist, sep = "")
args <- sapply(names(formals(dist)[-1]), as.name)
x <- substitute(x + y, list(y = y))
eval(substitute(FUN <- function() do.call(f, a),
list(f = dist, a = c(x = x, args))))
formals(FUN) <- formals(pdf)
FUN
}
Then, for example,
> f("gamma", 1000)
function (x, shape, rate = 1, scale = 1/rate, log = FALSE)
do.call("dgamma", list(x = x + 1000, shape = shape, rate = rate,
scale = scale, log = log))
<environment: 0x8a9b330>
I think this is pretty neat! ;-)
Vincent
--
Vincent Goulet, Associate Professor
École d'actuariat
Université Laval, Québec
Vincent.Goulet at act.ulaval.ca http://vgoulet.act.ulaval.ca
More information about the R-help
mailing list