[Rd] force promises inside lapply

William Dunlap wdunlap at tibco.com
Tue Aug 1 01:28:43 CEST 2017


quote(expr) will make no changes in expr, it just returns its one argument,
unevaluated.
substitute could be used in your lapply(..., library) example to give
library a name instead
of a character string for an input (which might be necessary if the
character.only argument
were not available)
    lapply(c("MASS", "splines"), function(pkg)
eval(substitute(library(pkg), list(pkg=as.name(pkg)))))
bquote() could be used as well
    lapply(c("MASS", "splines"), function(pkg) eval(bquote(library(.(pkg)),
list(pkg=as.name(pkg)))))
But avoiding such things is much easier.


Bill Dunlap
TIBCO Software
wdunlap tibco.com

On Mon, Jul 31, 2017 at 2:41 PM, Benjamin Tyner <btyner at gmail.com> wrote:

> Thanks again Bill; I agree that substitute is overkill here.
>
> As an aside, for cases where someone may be tempted to use substitute(),
> it seems quote() might be a safer alternative; compare
>
>    > lapply(list(1), function(y) c(quote(y), substitute(y)))
>    [[1]]
>    [[1]][[1]]
>    y
>
>    [[1]][[2]]
>    X[[i]]
>
> versus in R < 3.2,
>
>    > lapply(list(1), function(y) c(quote(y), substitute(y)))
>    [[1]]
>    [[1]][[1]]
>    y
>
>    [[1]][[2]]
>    X[[1L]]
>
> in any case, the lesson seems to be that quote and substitute are not
> interchangeable, even though for example
>
>    > (function() identical(quote({a}), substitute({a})))()
>    [1] TRUE
>
>
> On 07/29/2017 09:39 AM, William Dunlap wrote:
>
>> Functions, like your loader(), that use substitute to let users confound
>> things and their names, should give the user a way to avoid the use of
>> substitute.  E.g., library() has the 'character.only' argument; if TRUE
>> then the package argument is treated as an ordinary argument and not passed
>> through substitute().
>>
>> myLoader <- function(package, quietly = TRUE) {
>>        wrapper <- if (quietly) suppressPackageStartupMessages else `{`
>>        wrapper(library(package = package, character.only=TRUE))
>>    }
>>
>> > lapply(c("MASS","boot"), myLoader, quietly=FALSE)
>> [[1]]
>>  [1] "MASS"  "splines"   "pryr"      "stats"     "graphics"  "grDevices"
>>  [7] "utils" "datasets"  "methods"   "base"
>>
>> [[2]]
>>  [1] "boot"      "MASS"      "splines"   "pryr"      "stats"
>>  "graphics"
>>  [7] "grDevices" "utils"     "datasets"  "methods"   "base"
>>
>> "Non-standard" evaluation (using substitute(), formulas, promises, the
>> rlang or lazyeval packages, etc.) has it uses but I wouldn't use it for
>> such a function as your loader().
>>
>>
>> Bill Dunlap
>> TIBCO Software
>> wdunlap tibco.com <http://tibco.com>
>>
>>
>> On Fri, Jul 28, 2017 at 8:20 PM, Benjamin Tyner <btyner at gmail.com
>> <mailto:btyner at gmail.com>> wrote:
>>
>>     Thanks Bill. I think my confusion may have been in part due to my
>>     conflating two distinct meanings of the term "evaluate"; the help
>>     for force says it "forces the evaluation of a function argument"
>>     whereas the help for eval says it "evaluates the ... argument ...
>>     and returns the computed value". I found it helpful to compare:
>>
>>        > lapply(list(a=1,b=2,c=3), function(x){ force(substitute(x)) })
>>        $a
>>        X[[i]]
>>
>>        $b
>>        X[[i]]
>>
>>        $c
>>        X[[i]]
>>
>>     versus
>>
>>        > lapply(list(a=1,b=2,c=3), function(x){ eval(substitute(x)) })
>>        Error in eval(substitute(x)) : object 'X' not found
>>
>>     Now for the context my question arose in: given a function
>>
>>        loader <- function(package, quietly = TRUE) {
>>
>>            wrapper <- if (quietly) suppressPackageStartupMessages else `{`
>>
>>            expr <- substitute(wrapper(library(package = package)))
>>
>>            eval(expr)
>>        }
>>
>>     prior to R version 3.2, one could do things like
>>
>>         lapply(c("MASS", "boot"), loader)
>>
>>     but not anymore (which is fine; I agree that one should not depend
>>     on lapply's implementation details).
>>
>>     Regards,
>>     Ben
>>
>>
>>     On 07/28/2017 06:53 PM, William Dunlap wrote:
>>
>>         1: substitute(), when given an argument to a function (which
>>         will be a promise) gives you the unevaluated expression given
>>         as the argument:
>>
>>         >  L <- list(a=1, b=2, c=3)
>>         > str(lapply(L, function(x) substitute(x)))
>>         List of 3
>>          $ a: language X[[i]]
>>          $ b: language X[[i]]
>>          $ c: language X[[i]]
>>
>>         The 'X' and 'i' are in a frame constructed by lapply and you
>>         are not really supposed to depend on the precise form of those
>>         expressions.
>>
>>         2: An evaluated promise is still a promise: it has the
>>         'evaled' field set to TRUE and the 'value' field set to the
>>         result of evaluating 'code' in 'env'.
>>
>>         > f <- function(x, force) {
>>              if (force) force(x)
>>              if (pryr::is_promise(x)) promise_info(x)
>>              else "not a promise"
>>          }
>>         > str(f(log(-1), force=FALSE))
>>         List of 4
>>          $ code  : language log(-1)
>>          $ env   :<environment: R_GlobalEnv>
>>          $ evaled: logi FALSE
>>          $ value : NULL
>>         > str(f(log(-1), force=TRUE))
>>         List of 4
>>          $ code  : language log(-1)
>>          $ env   : NULL
>>          $ evaled: logi TRUE
>>          $ value : num NaN
>>         Warning message:
>>         In log(-1) : NaNs produced
>>
>>         Can you give a concrete example of what you are try to accomplish?
>>
>>         Bill Dunlap
>>         TIBCO Software
>>         wdunlap tibco.com <http://tibco.com> <http://tibco.com>
>>
>>
>>         On Fri, Jul 28, 2017 at 3:04 PM, Benjamin Tyner
>>         <btyner at gmail.com <mailto:btyner at gmail.com>
>>         <mailto:btyner at gmail.com <mailto:btyner at gmail.com>>> wrote:
>>
>>             Hi,
>>
>>             I thought I understood the change to lapply semantics
>>         resulting
>>             from this,
>>
>>         https://bugs.r-project.org/bugzilla/show_bug.cgi?id=16093
>>         <https://bugs.r-project.org/bugzilla/show_bug.cgi?id=16093>
>>             <https://bugs.r-project.org/bugzilla/show_bug.cgi?id=16093
>>         <https://bugs.r-project.org/bugzilla/show_bug.cgi?id=16093>>
>>
>>             However, would someone care to explain why this does not work?
>>
>>                > L <- list(a=1, b=2, c=3)
>>                > str(lapply(L, function(x){ y <- substitute(x); force(x);
>>             eval(y) }))
>>                Error in eval(y) : object 'X' not found
>>
>>             Basically, my primary goal is to achieve the same result as,
>>
>>                > str(lapply(L, function(x){ eval.parent(substitute(x)) }))
>>                List of 3
>>                 $ a: num 1
>>                 $ b: num 2
>>                 $ c: num 3
>>
>>             but without having to resort to eval.parent as that seems
>>         to rely
>>             on an implementation detail of lapply.
>>
>>             My secondary goal is to understand why force(x) does not
>>         actually
>>             force the promise here,
>>
>>                > str(lapply(L, function(x){ force(x);
>>         pryr::is_promise(x) }))
>>                List of 3
>>                 $ a: logi TRUE
>>                 $ b: logi TRUE
>>                 $ c: logi TRUE
>>             ,
>>             Regards
>>             Ben
>>
>>             ______________________________________________
>>         R-devel at r-project.org <mailto:R-devel at r-project.org>
>>         <mailto:R-devel at r-project.org <mailto:R-devel at r-project.org>>
>>         mailing list
>>         https://stat.ethz.ch/mailman/listinfo/r-devel
>>         <https://stat.ethz.ch/mailman/listinfo/r-devel>
>>             <https://stat.ethz.ch/mailman/listinfo/r-devel
>>         <https://stat.ethz.ch/mailman/listinfo/r-devel>>
>>
>>
>>
>>
>>
>

	[[alternative HTML version deleted]]



More information about the R-devel mailing list