Dear all, I have the following problem. Given an expression object 'expr' containing a certain set of symbols (say 'a', 'b', 'c'), I would like to translate the expression object in an R function of, say, 'a', programmatically. Here an example of what I mean. Given:> expr <- expression(a+b+c)a call like:> asFunctionOf(expr, 'a', list(b=1, c=2))should return a function (not necessarly formally) equivalent to> function(a) a+1+2Some suggestions? Best regards, Antonio.
This is what I tried, and it seemed to work, but maybe others can give 
better ideas, and also explain why the first attempt to assign the 
formal arguments didn't work (but the second did.)
 > f <- function() NULL
 > formals(f) <- list(b=1, c=2)
 > f
function (b = 1)
2
 > formals(f) <- list(b=1, c=2)
 > f
function (b = 1, c = 2)
2
 > body(f)
[1] 2
 > body(f) <- expression(a+b+c)
 > f
function (b = 1, c = 2)
a + b + c
 > a <- 3
 > f()
[1] 6
 >
One thing you may want to be careful of is the environment of the function.
(If I don't start out with f having a NULL body, the first attempt to 
assign the formals works.)
-- Tony Plate
 > sessionInfo()
R version 2.4.0 (2006-10-03)
i386-pc-mingw32
locale:
LC_COLLATE=English_United States.1252;LC_CTYPE=English_United 
States.1252;LC_MONETARY=English_United 
States.1252;LC_NUMERIC=C;LC_TIME=English_United States.1252
attached base packages:
[1] "methods"   "stats"     "graphics" 
"grDevices" "utils"     "datasets"
[7] "base"
other attached packages:
     MASS  foreign
"7.2-29" "0.8-17"
 >
Antonio, Fabio Di Narzo wrote:> Dear all,
> I have the following problem.
> 
> Given an expression object 'expr' containing a certain set of
symbols
> (say 'a', 'b', 'c'), I would like to translate the
expression object
> in an R function of, say, 'a', programmatically. Here an example of
> what I mean.
> 
> Given:
> 
>>expr <- expression(a+b+c)
> 
> 
> a call like:
> 
>>asFunctionOf(expr, 'a', list(b=1, c=2))
> 
> 
> should return a function (not necessarly formally) equivalent to
> 
>>function(a) a+1+2
> 
> 
> Some suggestions?
> 
> Best regards,
> Antonio.
> 
> ______________________________________________
> R-devel at r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-devel
>
On Mon, 2006-12-18 at 19:06 +0100, Antonio, Fabio Di Narzo wrote:> Dear all, > I have the following problem. > > Given an expression object 'expr' containing a certain set of symbols > (say 'a', 'b', 'c'), I would like to translate the expression object > in an R function of, say, 'a', programmatically. Here an example of > what I mean. > > Given: > > expr <- expression(a+b+c) > > a call like: > > asFunctionOf(expr, 'a', list(b=1, c=2)) > > should return a function (not necessarly formally) equivalent to > > function(a) a+1+2 > > Some suggestions? > > Best regards, > Antonio.Let me offer some pointers and a couple of possible examples: ?call ?as.function ?alist ?eval ?parse expr <- expression(a + b + c)> as.function(alist(a = , b = 1, c = 2, eval(expr)))(5)[1] 8> as.function(alist(a = , b = 1, c = 2, eval(expr)))(5, 10, 8)[1] 23 MyExpr <- paste(letters[1:3], collapse = " + ")> MyExpr[1] "a + b + c"> as.function(alist(a = , b = 1, c = 2, eval(parse(text = MyExpr))))(6)[1] 9 HTH, Marc Schwartz
Here is one possibility.  It does not use the second argument in your function
call but instead assumes the arguments of the output function are
those variables
in the expression that have not been assigned in the list L in the
order encountered.
library(gsubfn)
asFun <- function(e, L = NULL, env = parent.frame()) {
  fo <- ~ x
  fo[[2]] <- e[[1]]
  fun <- fn$force(as.formula(do.call(substitute, list(fo, L))))
  environment(fun) <- env
  fun
}
asFun(expression(a+b+c), list(b = 1, c = 2)) # function (a) a + 1 + 2
On 12/18/06, Antonio, Fabio Di Narzo <antonio.fabio at gmail.com>
wrote:> Dear all,
> I have the following problem.
>
> Given an expression object 'expr' containing a certain set of
symbols
> (say 'a', 'b', 'c'), I would like to translate the
expression object
> in an R function of, say, 'a', programmatically. Here an example of
> what I mean.
>
> Given:
> > expr <- expression(a+b+c)
>
> a call like:
> > asFunctionOf(expr, 'a', list(b=1, c=2))
>
> should return a function (not necessarly formally) equivalent to
> > function(a) a+1+2
>
> Some suggestions?
>
> Best regards,
> Antonio.
>
> ______________________________________________
> R-devel at r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-devel
>