[R] Question about "evalq"

Gabor Grothendieck ggrothendieck at gmail.com
Sun May 27 06:48:42 CEST 2007


evalq looks like this:

   > evalq
   function (expr, envir, enclos)
   eval.parent(substitute(eval(quote(expr), envir, enclos)))
   <environment: namespace:base>

so it seems the difference is that

- eval(quote(), envir, enclos) evaluates envir and enclos
  in the current frame but
- evalq evaluates them in the parent.frame.

This may be easier to see in the following example:

   x <- "G"
   f1 <- function() eval(quote(x), parent.frame())
   f2 <- function() evalq(x, parent.frame())
   f11 <- function() {
   	x <- "a"
   	f1()
   }
   f22 <- function() {
   	x <- "b"
   	f2()
   }
   f11() # a
   f22() # G

To avoid this problem pass a variable whose value is
to be enclos= rather than an expression to compute it:

   f1 <- function(x,digits=5) lapply(x, f2)
   f2 <- function(x) {
      pf2 <- parent.frame(2)
      evalq(print(digits), list(x=x), pf2)
   }
   f1(list(x1=1)) # 5



On 5/26/07, ronggui <ronggui.huang at gmail.com> wrote:
> The help page of eval says: The 'evalq' form is equivalent to
> 'eval(quote(expr), ...)'.  But the following is not equivalent.  Can
> anyone give me some explaination? Thanks very much.
>
> > f1 <- function(x,digits=5) lapply(x, f2)
> > f2 <- function(x) eval(quote(print(x+1,digits=digits)),list(x=x),parent.frame(2))
> > f1(list(x1=1))
> [1] 2
> $x1
> [1] 2
>
> >
> > f1 <- function(x,digits=5) lapply(x, f2)
> > f2 <- function(x) evalq(print(x+1,digits=digits),list(x=x),parent.frame(2))
> > f1(list(x1=1))
> Error in print.default(x + 1, digits = digits) :
>  object "digits" not found
>
>
>
> --
> Ronggui Huang
> Department of Sociology
> Fudan University, Shanghai, China
>
> ______________________________________________
> R-help at stat.math.ethz.ch 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.
>



More information about the R-help mailing list