Re: [Rd] as.function()

2008-01-14 Thread Gabor Grothendieck
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 <[EMAIL PROTECTED]> 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 <[EMAIL PROTECTED]> 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 <[EMAIL PROTECTED]>:
> >>>
>  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@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
> >>   te

Re: [Rd] as.function()

2008-01-14 Thread Tony Plate
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 <[EMAIL PROTECTED]> 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 <[EMAIL PROTECTED]>:
>>>   
 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@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@r-project.org mailing list
>> https://stat.ethz.ch/mailman/listinfo/r-devel
>>
>> 
>
>
>

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


Re: [Rd] as.function()

2008-01-14 Thread Gabor Grothendieck
On Jan 14, 2008 6:50 AM, Duncan Murdoch <[EMAIL PROTECTED]> wrote:
> Robin Hankin wrote:
> > 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)
> >
> > a <- 4
> > f(x)   # should still give tr(ax) even though "a" has been
> > reassigned.
> >
> >
> Brian's answer was what you want.  A less general version is this:
>
>  > as.function.foo <- function(x, ...) {
> +function(b) tr(x %*% b)
> + }
>

This can also be done using the proto package.  p has two
components b and f.  q inherits f from p but has its own b.

library(proto)
p <- proto(b = 1:4, f = function(., x) sum(diag(x %*% .$b)))
q <- p$proto(b = 5:8)
p$f(1:4)
q$f(1:4)

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


Re: [Rd] as.function()

2008-01-14 Thread Prof Brian Ripley
On Mon, 14 Jan 2008, Duncan Murdoch wrote:

> Robin Hankin wrote:
>> 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)
>>
>> a <- 4
>> f(x)   # should still give tr(ax) even though "a" has been
>> reassigned.
>>
>>
> Brian's answer was what you want.  A less general version is this:
>
> > as.function.foo <- function(x, ...) {
> +function(b) tr(x %*% b)
> + }

And see the R version of as.function.polynomial called Rpoly in 'S 
Programming' p.95 for a similar example, in case yet another is needed 
(and to set the record straight after RH's unthinking reply).

> (I switched the names of the args, because the first arg to
> as.function.foo should match the name of the first arg to as.function).
>
> I was a little surprised that this worked even if a was changed without
> ever evaluating f, because I thought lazy evaluation would mess up that
> case.  But of course the value of x is forced when R evaluates it to
> find out the class for dispatch to the method.
>
> Duncan Murdoch

-- 
Brian D. Ripley,  [EMAIL PROTECTED]
Professor of Applied Statistics,  http://www.stats.ox.ac.uk/~ripley/
University of Oxford, Tel:  +44 1865 272861 (self)
1 South Parks Road, +44 1865 272866 (PA)
Oxford OX1 3TG, UKFax:  +44 1865 272595

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


Re: [Rd] as.function()

2008-01-14 Thread Robin Hankin

On 14 Jan 2008, at 11:50, Duncan Murdoch wrote:

> Robin Hankin wrote:
>> Hi
>>

[snip]

>> 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)
>>
>> a <- 4
>> f(x)   # should still give tr(ax) even though "a" has been   
>> reassigned.
>>
>>
> Brian's answer was what you want.  A less general version is this:
>
> > as.function.foo <- function(x, ...) {
> +function(b) tr(x %*% b)
> + }
>


Wow.  Got it!  Looks like I'll have to read the R Language Definition  
again.

Thanks everyone.




> (I switched the names of the args, because the first arg to  
> as.function.foo should match the name of the first arg to  
> as.function).
>
> I was a little surprised that this worked even if a was changed  
> without ever evaluating f, because I thought lazy evaluation would  
> mess up that case.  But of course the value of x is forced when R  
> evaluates it to find out the class for dispatch to the method.
>
> Duncan Murdoch

--
Robin Hankin
Uncertainty Analyst and Neutral Theorist,
National Oceanography Centre, Southampton
European Way, Southampton SO14 3ZH, UK
  tel  023-8059-7743

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


Re: [Rd] as.function()

2008-01-14 Thread Duncan Murdoch
Robin Hankin wrote:
> 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)
>
> a <- 4
> f(x)   # should still give tr(ax) even though "a" has been  
> reassigned.
>
>   
Brian's answer was what you want.  A less general version is this:

 > as.function.foo <- function(x, ...) {
+function(b) tr(x %*% b)
+ }

(I switched the names of the args, because the first arg to 
as.function.foo should match the name of the first arg to as.function).

I was a little surprised that this worked even if a was changed without 
ever evaluating f, because I thought lazy evaluation would mess up that 
case.  But of course the value of x is forced when R evaluates it to 
find out the class for dispatch to the method.

Duncan Murdoch

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


Re: [Rd] as.function()

2008-01-14 Thread Robin Hankin

On 14 Jan 2008, at 10:57, Prof Brian Ripley wrote:

> On Mon, 14 Jan 2008, 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)
>
> Well, that copies what as.function.polynomial did but that was  
> written for S3 well before R was started.  Here you can use  
> environments:
>
> as.function.foo <- function(obj, ...) function(x, ...) eval(obj)
>


Yes, "did" is the operative word here.The new  
as.function.polynomial() is considerably slicker
and more general.

But both old and new versions 'unpick' the polynomial "x" into its  
elements
and create a function, line by line, that depends on the elements of  
"x".

The new version uses:

as.function.polynomial <- function (x, ...)
{

<< clever and efficient creation of list "ex"  as a function of vector  
"x" snipped>>

 f <- function(x) NULL
 body(f) <- ex
 f
}


The old version uses:


as.function.polynomial <- function (x, ...)
{

<< clever and efficient creation of character string "jj"  as a  
function of vector "x" snipped>>

f <- function(x) NULL
 body(f) <- parse(text = jj )[[1]]
f
}



If f <- as.function.foo(x),  somehow the "f" object has to include  
within itself
the entirety of "x".   In my case, "x" is [of course] an arbitrary- 
dimensional
array of possibly complex elements.

So I can't use Bill/Kurt's method (at least not easily)  because my
object is considerably more complicated than a vector.
And I don't have an example  that works on a complicated object
to copy.


>
>>
>>
>> Hope this help
>>
>> On 14/01/2008, Robin Hankin <[EMAIL PROTECTED]> 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
>>>

--
Robin Hankin
Uncertainty Analyst and Neutral Theorist,
National Oceanography Centre, Southampton
European Way, Southampton SO14 3ZH, UK
  tel  023-8059-7743

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


Re: [Rd] as.function()

2008-01-14 Thread Prof Brian Ripley
On Mon, 14 Jan 2008, 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)

Well, that copies what as.function.polynomial did but that was written 
for S3 well before R was started.  Here you can use environments:

as.function.foo <- function(obj, ...) function(x, ...) eval(obj)


>
>
> Hope this help
>
> On 14/01/2008, Robin Hankin <[EMAIL PROTECTED]> 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 <[EMAIL PROTECTED]>:
 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@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@r-project.org mailing list
>> https://stat.ethz.ch/mailman/listinfo/r-devel
>>
>
>
>

-- 
Brian D. Ripley,  [EMAIL PROTECTED]
Professor of Applied Statistics,  http://www.stats.ox.ac.uk/~ripley/
University of Oxford, Tel:  +44 1865 272861 (self)
1 South Parks Road, +44 1865 272866 (PA)
Oxford OX1 3TG, UKFax:  +44 1865 272595

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


Re: [Rd] as.function()

2008-01-14 Thread Henrique Dallazuanna
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 <[EMAIL PROTECTED]> 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 <[EMAIL PROTECTED]>:
> >> 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@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@r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-devel
>


-- 
Henrique Dallazuanna
Curitiba-Paraná-Brasil
25° 25' 40" S 49° 16' 22" O

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


Re: [Rd] as.function()

2008-01-14 Thread Robin Hankin
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 <[EMAIL PROTECTED]>:
>> 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@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@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


Re: [Rd] as.function()

2008-01-14 Thread Antonio, Fabio Di Narzo
2008/1/14, Robin Hankin <[EMAIL PROTECTED]>:
> 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@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

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel