[R] forcing evaluation of a char string argument

William Dunlap wdunlap at tibco.com
Thu Dec 23 20:04:43 CET 2010


> -----Original Message-----
> From: r-help-bounces at r-project.org 
> [mailto:r-help-bounces at r-project.org] On Behalf Of Charles C. Berry
> Sent: Thursday, December 23, 2010 9:39 AM
> To: rballen
> Cc: r-help at r-project.org
> Subject: Re: [R] forcing evaluation of a char string argument
> 
> On Wed, 22 Dec 2010, rballen wrote:
> 
> >
> > Why does x in "assign(x)" correctly evaluate to "rank" where
> > UseMethod(func) does not get correctly evaluated?
> 
> Because it is the body of a function definition.

More generally, because it is in an expression and you
need something like substitute() to change the expression.

> 
> If you want to plug in the value of 'func' in the body of 
> that function, 
> you need to do something like this:
> 
> toGeneric <- 
> function(func) {
>          env<-environment(get(func))
> 
>          # default method of new generic = the original function
>          assign(paste(func,".default",sep=""),get(func),pos=env)
>          foo <- function(x,...) {}
>          lf <- list(x=func)
>          body.foo <- substitute(UseMethod(x),lf)
>          body(foo)<-body.foo
>          assign(func,foo,pos=env)
> }
> 
> BTW, are you sure you know what 'env' evaluates to?? (It is NOT the 
> environment of the object named by the value of func in the 
> parent.frame 
> of toGeneric.)

Yes, environment(someFunction) gives you the
environment in which the function was created
(which controls where it looks up names of objects).
It does not have much to do with the environment
in which the name of the function is placed, which
find("someFunction") gives you (roughly).

local() can make a function in an arbitrary environment
but you can put the name for that function in any other
writable environment.
  > myEnv <- list2env(list(pi=3))
  > f <- local(function(r) pi * r^2, envir=myEnv)
  > f(2)
  [1] 12
  > environment(f) # where it looks up `pi`
  <environment: 046602d8>
  > objects(environment(f))
  [1] "pi"
  > find("f") # where the name `f` is stashed
  [1] ".GlobalEnv"

If you have a function that creates a new function (by
calling the special function called "function") the
new function's environment is the execution environment
of the creator.  This can lead to surprises like
  > makeFunc <- function(expr) {
  +   func <- function(x){}
  +   functionBody(func) <- substitute(expr)
  +   func
  + }
  > f <- makeFunc(x+4)
  > f(10) # good, expected 14
  [1] 14
  > g <- makeFunc(func)
  > g(10) # bad, expected a 'func not found' error
  function (x) 
  func
  <environment: 04598488>
See how g() got the symbol func's value from the
execution environment of the call to makeFunc()
in which g() was made.

The following version of makeFunc creates the function
in the desired environment so it looks things up there.
  > makeFunc2 <- function (expr, envir) {
  +      eval(substitute(function(x) expr), envir = envir)
  + }
  > h <- makeFunc(func, environment())
  > environment(h)
  <environment: R_GlobalEnv>
  > h(10)
  Error in h(10) : object 'func' not found

toGeneric() really needs two environment-related arguments,
one to say where the generic and default method should look
things up and one to say where the the names of the new
functions should be stored.

Bill Dunlap
Spotfire, TIBCO Software
wdunlap tibco.com 

> 
> HTH,
> 
> Chuck
> >
> > Can we use as.call(list(UseMethod,func))?
> >
> >>> assign(paste(func,".default",sep=""),get(func),pos=env)
> >>>
> >>> assign(func,function(x,...) UseMethod(func),pos=env)
> >
> > On Wed, Dec 22, 2010 at 9:03 PM, William Dunlap [via R]
> > <ml-node+3161542-1898476570-206552 at n4.nabble.com> wrote:
> >> Try the following, which I haven't tested much
> >> and needs more error checking (e.g., to see that
> >> the function is not already generic and that
> >> its argument list is compatible with (x,...)).
> >> I put in the print statements to show what
> >> the calls to substitute() do.
> >>
> >> toGeneric <- function (funcName) {
> >>     stopifnot(is.character(funcName))
> >>     funcItself <- get(funcName)
> >>     stopifnot(is.function(funcItself))
> >>     envir <- environment(funcItself)
> >>     tmp <- substitute(funcSymbol <- function(x, ...)
> >> UseMethod(funcName),
> >>         list(funcSymbol = as.symbol(funcName), 
> funcName = funcName))
> >>     print(tmp)
> >>     eval(tmp, envir = envir)
> >>     tmp <- substitute(defaultSymbol <- funcItself, 
> list(defaultSymbol =
> >> as.symbol(paste(sep = ".",
> >>         funcName, "default")), funcItself = funcItself))
> >>     print(tmp)
> >>     eval(tmp, envir = envir)
> >> }
> >>
> >> E.g.,
> >>
> >>    > wsx <- function(x, base=2)log(x, base=base)
> >>    > toGeneric("wsx")
> >>    wsx <- function(x, ...) UseMethod("wsx")
> >>    wsx.default <- function (x, base = 2)
> >>    log(x, base = base)
> >>    > wsx
> >>    function (x, ...)
> >>    UseMethod("wsx")
> >>    > wsx.default
> >>    function (x, base = 2)
> >>    log(x, base = base)
> >>
> >> Bill Dunlap
> >> Spotfire, TIBCO Software
> >> wdunlap tibco.com
> >>
> >>> -----Original Message-----
> >>> From: [hidden email]
> >>> [mailto:[hidden email]] On Behalf Of rballen
> >>> Sent: Wednesday, December 22, 2010 2:42 PM
> >>> To: [hidden email]
> >>> Subject: [R] forcing evaluation of a char string argument
> >>>
> >>>
> >>> I'm trying to make a function to turn a regular function into
> >>> an S3 generic
> >>> one. I want myMethod to be:
> >>>
> >>> function(x,...) UseMethod("myMethod")
> >>>
> >>> But I keep getting:
> >>>
> >>> function(x,...) UseMethod(func)
> >>>
> >>> Here's the function:
> >>>
> >>> toGeneric<-function(func) {
> >>> env<-environment(get(func))
> >>>
> >>> # default method of new generic = the original function
> >>> assign(paste(func,".default",sep=""),get(func),pos=env)
> >>>
> >>> assign(func,function(x,...) UseMethod(func),pos=env)
> >>> }
> >>>
> >>> toGeneric("myMethod")
> >>>
> >>> I messed around with force, substitute, and deparse, but I
> >>> can't get any of
> >>> those to help.
> >>>
> >>> Thanks.
> >>> --
> >>> View this message in context:
> >>> http://r.789695.n4.nabble.com/forcing-evaluation-of-a-char-str
> >> ing-argument-tp3161365p3161365.html
> >>> Sent from the R help mailing list archive at Nabble.com.
> >>>
> >>> ______________________________________________
> >>> [hidden email] mailing list
> >>> https://stat.ethz.ch/mailman/listinfo/r-help
> >>> PLEASE do read the posting guide
> >>> http://www.R-project.org/posting-guide.html
> >>> and provide commented, minimal, self-contained, reproducible code.
> >>>
> >>
> >> ______________________________________________
> >> [hidden email] mailing list
> >> https://stat.ethz.ch/mailman/listinfo/r-help
> >> PLEASE do read the posting guide 
> http://www.R-project.org/posting-guide.html
> >> and provide commented, minimal, self-contained, reproducible code.
> >>
> >>
> >> ________________________________
> >> View message @
> >> 
> http://r.789695.n4.nabble.com/forcing-evaluation-of-a-char-str
ing-argument-tp3161365p3161542.html
> >> To unsubscribe from forcing evaluation of a char string 
> argument, click
> >> here.
> >
> > -- 
> > View this message in context: 
> http://r.789695.n4.nabble.com/forcing-evaluation-of-a-char-str
ing-argument-tp3161365p3161666.html
> > Sent from the R help mailing list archive at Nabble.com.
> >
> > 	[[alternative HTML version deleted]]
> >
> >
> 
> Charles C. Berry                            Dept of 
> Family/Preventive Medicine
> cberry at tajo.ucsd.edu			    UC San Diego
> http://famprevmed.ucsd.edu/faculty/cberry/  La Jolla, San 
> Diego 92093-0901
> 
> 



More information about the R-help mailing list