[Rd] Parser oddity with <- and =
Mikael Jagan
j@g@nmn2 @end|ng |rom gm@||@com
Fri Feb 18 20:49:33 CET 2022
The `<-` operator has higher precedence than the `=` operator,
so it makes sense to me that `a <- b = c` would be parsed as
call("=", call("<-", quote(a), quote(b)), quote(c))
For `a <- b = c` to be parsed instead as
call("<-", quote(a), call("=", quote(b), quote(c)))
R would need to assign equal precedence to `<-` and `=`, but
I'm guessing that `=` _needs_ to have lower precedence than `<-`
for calls with named arguments to be parsed in a sensible way.
Mikael
> Sorry, I wrote in a sloppy way. The parsing I see is just what you saw.
> It's the evaluation of that expression that tries to call `<-<-`:
>
> > a <- 1
> > a <- b = c
> Error in a <- b = c : could not find function "<-<-"
>
> This happens because R is trying to make an assignment using = with a
> LHS that is the function call a <- b.
>
> Duncan Murdoch
>
>
> On 04/02/2022 3:28 p.m., Bill Dunlap wrote:
>> In R-4.1.2 and R-devel from two weeks ago I do not get the `<-<-`:
>>
>> > str.language(parse(text = "a <- b = c"))
>> expression: structure(expression(a <- b = c), sr ...
>> language: a <- b = c
>> symbol: =
>> language: a <- b
>> symbol: <-
>> symbol: a
>> symbol: b
>> symbol: c
>> > identical(parse(text = "a <- b = c")[[1]], parse(text = "`=`(
>> `<-`(a, b), c)")[[1]])
>> [1] TRUE
>>
>> str.language() is a rudimentary parse tree displayer:
>>
>> str.language <- function(expr, name = "", indent = 0)
>> {
>> trim... <- function(string, width.cutoff) {
>> if (nchar(string) > width.cutoff) {
>> string <- sprintf("%.*s ...", width.cutoff-4, string)
>> }
>> string
>> }
>> cat(sep="", rep(" ", indent), typeof(expr), ": ",
>> if(length(name)==1 && nzchar(name)) { paste0(name, " = ") },
>> trim...(deparse1(expr, width.cutoff=40), width.cutoff=40),
>> "\n")
>> if (is.function(expr)) {
>> str.language(formals(expr), name="[formals]", indent =
>> indent + 1)
>> str.language(body(expr), name="[body]", indent = indent + 1)
>> } else if (is.recursive(expr)) {
>> expr <- as.list(expr)
>> nms <- names(expr)
>> for (i in seq_along(expr)) {
>> str.language(expr[[i]], name=nms[[i]], indent = indent + 1)
>> }
>> }
>> invisible(expr)
>> }
>>
>>
>> -Bill
>>
>> On Fri, Feb 4, 2022 at 9:34 AM Duncan Murdoch <murdoch.duncan using gmail.com
>> <mailto:murdoch.duncan using gmail.com>> wrote:
>>
>> Here's an odd parse:
>>
>> a <- b = 1
>>
>> This appears to be parsed as
>>
>> `<-<-`(a, b, 1)
>>
>> instead of being equivalent to
>>
>> a <- b <- 1
>>
>> I wonder if that's intentional?
>>
>> (This showed up at https://stackoverflow.com/q/70989067/2554330
>> <https://stackoverflow.com/q/70989067/2554330>, where
>> it caused a lot of confusion. I think the original intent was that `a`
>> would be a macro holding `b = 1`, but I'm not sure of that.)
>>
>> Duncan Murdoch
>>
>> ______________________________________________
>> R-devel using r-project.org <mailto:R-devel using r-project.org> mailing list
>> https://stat.ethz.ch/mailman/listinfo/r-devel
>> <https://stat.ethz.ch/mailman/listinfo/r-devel>
>>
More information about the R-devel
mailing list