Kevin,

Thanks for the explanation. Based on your analysis, I tried to reproduce
the problem without lapply, and sure enough:

(function(x,y) "$"(x,y)) (list(a=2),"a") => NULL
(function(x,...) "$"(x,...)) (list(a=2),"a") => NULL


although

"$"(list(a=2),"a") => 2


Looking for even simpler examples, I found

"$"(list(a=2),("a")) => ERROR invalid subscript type 'language'
"$"(list(a=2),`a`) => 2

So the real issue is that "$" does not evaluate its second argument. Which
makes perfect sense, but ought to be documented in the man page for $
(base::Extract).

Also, I'd think that $ should be giving an error in these cases:


"$"(list(a=2,b=4),...)  => NULL
"$"(list(a=2,b=4),)  => NULL
"$"(list(a=2),)  => 2                # strange...

​as it does for other illegal arguments:

​​
"$"(list(a=2,b=4),2)
​​ =>
Error in list(a = 2, b = 4)$2 : invalid subscript type 'double'
"$"(list(a=2,b=4),2L)
​ =>
Error in list(a = 2, b = 4)$2L : invalid subscript type 'integer'
"$"(list(a=2,b=4),c())
​ =>
Error in list(a = 2, b = 4)$c() : invalid subscript type 'language'
"$"(list(a=2,b=4),TRUE)
​ =>
Error in list(a = 2, b = 4)$TRUE : invalid subscript type 'logical'


           -s


On Tue, Jun 24, 2014 at 2:28 AM, Kevin Ushey <kevinus...@gmail.com> wrote:

> `lapply` basically takes its call and massages into calls of the following
> form:
>
>     FUN(X[[1L]], ...)
>     FUN(X[[2L]], ...)
>     ... <up to length of X>
>
> that get evaluated in the appropriate environment.
>
> For `lapply(list(list(a=3,b=4)),"$","b")`, you can imagine that a
> function `FUN` of the form:
>
>     FUN <- function(x, ...) "$"(x, ...)
>
> is being generated, and then evaluated as
>
>     FUN(list(list(a=3, b=4))[[1L]], "b") ## returns NULL
>
> and I can only guess that the non-standard evaluation of `$` is not
> interpreting `...` as you expect.
>
> Moral of the story -- lapply does non-standard evaluation, and does
> not compose nicely with other functions performing non-standard
> evaluation. This is discussed a bit in the Note: section of `?lapply`.
> Copied from there (emphasis mine):
>
> For historical reasons, the calls created by lapply are unevaluated,
> and code has been written (e.g. bquote) that relies on this. This
> means that the recorded call is always of the form FUN(X[[i]], ...),
> with i replaced by the current (integer or double) index. This is not
> normally a problem, but it can be if FUN uses sys.call or match.call
> or if it __is a primitive function that makes use of the call__. This
> means that it is often safer to call primitive functions with a
> wrapper, so that e.g. lapply(ll, function(x) is.numeric(x)) is
> required to ensure that method dispatch for is.numeric occurs
> correctly.
>
> Cheers,
> Kevin
>
>
> On Mon, Jun 23, 2014 at 3:04 PM, Stavros Macrakis (Σταῦρος 
> Μακράκης)
> <macra...@alum.mit.edu> wrote:
> > There seems to be a funny interaction between lapply and "$" -- also, "$"
> > doesn't signal an error in some cases where "[[" does.
> >
> > The $ operator accepts a string second argument in functional form:
> >
> >> `$`(list(a=3,b=4),"b")
> > [1] 4
> >
> > lapply(list(list(a=3,b=4)),function(x) `$`(x,"b"))
> > [[1]]
> > [1] 4
> >
> > ... but using an lapply "..." argument, this returns NULL:
> >
> >> lapply(list(list(a=3,b=4)),"$","b")
> > [[1]]
> > NULL
> >
> > Equally strangely, a symbol is an error in functional form:
> >
> >>  `$`(list(a=3,b=4),quote(`b`))
> > Error in list(a = 3, b = 4)$quote(b) : invalid subscript type 'language'
> >
> > ... but not an error in lapply, where it returns NULL:
> >
> >> lapply(list(list(a=3,b=4)),`$`,quote(`b`))
> > [[1]]
> > NULL
> >
> > I wonder if lapply is failing to pass the second argument to $ correctly,
> > since $ with various unreasonable second arguments returns NULL
> (shouldn't
> > it given an error?):
> >
> > "$"(list(list(a=3,b=4)),) => NULL
> > lapply(list(list(a=3,b=4)),`$`,function(i)i) => NULL
> >
> > Compare
> >
> > "[["(list(list(a=3,b=4)),) => <<error>>
> >
> > But with [[, lapply correctly gives an error:
> >
> > lapply(list(list(a=3,b=4)),`[[`,function(i)i) => <<error>>
> >
> >         [[alternative HTML version deleted]]
> >
> > ______________________________________________
> > R-devel@r-project.org mailing list
> > https://stat.ethz.ch/mailman/listinfo/r-devel
>

        [[alternative HTML version deleted]]

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

Reply via email to