[Rd] as.function()

Gabor Grothendieck ggrothendieck at gmail.com
Mon Jan 14 19:16:17 CET 2008


The gsubfn package can do something like that too.  If you
preface a function with fn$ then it will interpret certain formula
arguments as functions.  If all we want is the function itself we
can use force, the identity function, to recover it:

> library(gsubfn)
> fn$force(~ 2*x + 3*y^2)
function (x, y)
2 * x + 3 * y^2

If there are free variables in the formula that you don't want to
include in the argument list the left hand side can be used to
specify the argument list:

> fn$force(x + y ~ 2*x + a*y^2)
function (x, y)
2 * x + a * y^2



On Jan 14, 2008 1:05 PM, Tony Plate <tplate at acm.org> wrote:
> How about this as a version  that automatically constructs the argument
> list (and make into a method for as.function as appropriate)?
>
> makefun <- function(expr)
> {
>    f <- function() {}
>    body(f) <- expr
>    vars <- all.vars(expr)
>    if (length(vars)) {
>        args <- alist(x=)[rep(1,length(vars))]
>        names(args) <- vars
>        formals(f) <- args
>    }
>    environment(f) <- globalenv()
>    return(f)
> }
>
>  > makefun(expression(2*x + 3*y^2))
> function (x, y)
> 2 * x + 3 * y^2
>  > makefun(expression(2*x + 3*y^2 - z))
> function (x, y, z)
> 2 * x + 3 * y^2 - z
>  > makefun(expression(p1 + p2))
> function (p1, p2)
> p1 + p2
>  >
>
> -- Tony Plate
>
>
>
>
> Henrique Dallazuanna wrote:
> > Try this:
> >
> > as.function.foo <- function(obj, ...)
> > {
> > newobj <- function(x, ...){}
> > body(newobj) <- obj
> > return(newobj)
> > }
> >
> > x <- expression(2*x + 3*x^2)
> >
> > foo <- as.function.foo(x)
> > foo(2)
> >
> >
> > Hope this help
> >
> > On 14/01/2008, Robin Hankin <r.hankin at noc.soton.ac.uk> wrote:
> >
> >> Antonio
> >>
> >>
> >> thanks for your help here, but it doesn't answer my question.
> >>
> >> Perhaps if I outline my motivation it would help.
> >>
> >>
> >> I want to recreate the ability of
> >> the "polynom" package to do the following:
> >>
> >>
> >>  > library(polynom)
> >>  > p <- polynomial(1:4)
> >>  > p
> >> 1 + 2*x + 3*x^2 + 4*x^3
> >>  > MySpecialFunction <- as.function(p)
> >>  > MySpecialFunction(1:10)
> >>   [1]   10   49  142  313  586  985 1534 2257 3178 4321
> >>  > p <- 4
> >>  > MySpecialFunction(1:10)
> >>   [1]   10   49  142  313  586  985 1534 2257 3178 4321
> >>  >
> >>
> >>
> >> See how the user can define object "MySpecialFunction",
> >>   which outlives short-lived polynomial "p".
> >>
> >> Unfortunately, I don't see a way to modify as.function.polynomial()
> >> to do what I want.
> >>
> >>
> >> best wishes
> >>
> >>
> >> rksh
> >>
> >>
> >>
> >>
> >>
> >>
> >>
> >>
> >>
> >> On 14 Jan 2008, at 08:45, Antonio, Fabio Di Narzo wrote:
> >>
> >>
> >>> 2008/1/14, Robin Hankin <r.hankin at noc.soton.ac.uk>:
> >>>
> >>>> Hi
> >>>>
> >>>> [this after some considerable thought as to R-help vs R-devel]
> >>>>
> >>>>
> >>>>
> >>>> I want to write a (S3) method for as.function();
> >>>> toy example follows.
> >>>>
> >>>> Given a matrix "a", I need to evaluate trace(ax) as a function of
> >>>> (matrix) "x".
> >>>>
> >>>> Here's a trace function:
> >>>>
> >>>> tr <-  function (a)  {
> >>>>     i <- seq_len(nrow(a))
> >>>>     return(sum(a[cbind(i, i)]))
> >>>> }
> >>>>
> >>>>
> >>>> How do I accomplish the following:
> >>>>
> >>>>
> >>>> a <- crossprod(matrix(rnorm(12),ncol=3))
> >>>> class(a) <- "foo"
> >>>>
> >>>> f <- as.function(a)       # need help to write as.function.foo()
> >>>> x <- diag(3)
> >>>>
> >>>> f(x)             #should give tr(ax)
> >>>>
> >>> What about the following?
> >>>
> >>> as.function.foo <- function(a, ...)
> >>>  function(x)
> >>>    sum(diag(a*x))
> >>>
> >>> However, I don't see the need for an S3 method. Why don't simply use
> >>> (?):
> >>> mulTraceFun <- function(a)
> >>>  function(x)
> >>>   sum(diag(a*x))
> >>>
> >>> So you also have a more meaningful name than an anonymous
> >>> 'as.function'.
> >>>
> >>> HTH,
> >>> Antonio.
> >>>
> >>>
> >>>> a <- 4
> >>>> f(x)           # should still give tr(ax) even though "a" has been
> >>>> reassigned.
> >>>>
> >>> This would'nt work with my proposal, because of lexical scoping.
> >>>
> >>>
> >>>>
> >>>>
> >>>>
> >>>> [my real example is very much more complicated than this but
> >>>> I need this toy one too and I can't see how to modify
> >>>> as.function.polynomial()
> >>>> to do what I want]
> >>>>
> >>>>
> >>>>
> >>>>
> >>>> --
> >>>> Robin Hankin
> >>>> Uncertainty Analyst and Neutral Theorist,
> >>>> National Oceanography Centre, Southampton
> >>>> European Way, Southampton SO14 3ZH, UK
> >>>>  tel  023-8059-7743
> >>>>
> >>>> ______________________________________________
> >>>> R-devel at r-project.org mailing list
> >>>> https://stat.ethz.ch/mailman/listinfo/r-devel
> >>>>
> >>>>
> >>> --
> >>> Antonio, Fabio Di Narzo
> >>> Ph.D. student at
> >>> Department of Statistical Sciences
> >>> University of Bologna, Italy
> >>>
> >> --
> >> Robin Hankin
> >> Uncertainty Analyst and Neutral Theorist,
> >> National Oceanography Centre, Southampton
> >> European Way, Southampton SO14 3ZH, UK
> >>   tel  023-8059-7743
> >>
> >> ______________________________________________
> >> R-devel at r-project.org mailing list
> >> https://stat.ethz.ch/mailman/listinfo/r-devel
> >>
> >>
> >
> >
> >
>
> ______________________________________________
> R-devel at r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-devel
>



More information about the R-devel mailing list