[Rd] [External] brief update on the pipe operator in R-devel

Bill Dunlap w||||@mwdun|@p @end|ng |rom gm@||@com
Wed Jan 13 18:19:35 CET 2021


I agree that the precedence looks reasonable.  E.g.,

> str.language(quote(A > 0 & A<=B & B <= C => A <= C & 0 < C))
language: `=>`(A > 0 & A <= B & B <= C, A <= C ...
  symbol: =>
  language: A > 0 & A <= B & B <= C
    symbol: &
    language: A > 0 & A <= B
      symbol: &
      language: A > 0
        symbol: >
        symbol: A
        double: 0
      language: A <= B
        symbol: <=
        symbol: A
        symbol: B
    language: B <= C
      symbol: <=
      symbol: B
      symbol: C
  language: A <= C & 0 < C
    symbol: &
    language: A <= C
      symbol: <=
      symbol: A
      symbol: C
    language: 0 < C
      symbol: <
      double: 0
      symbol: C
> str.language(quote(data |> tmp1 => f1(x, arg1=tmp1) |> f2(y) |> tmp3 =>
f3(z, arg3=tmp3)))
language: f3(z, arg3 = f2(f1(x, arg1 = data), y))
  symbol: f3
  symbol: z
  language: arg3 = f2(f1(x, arg1 = data), y)
    symbol: f2
    language: f1(x, arg1 = data)
      symbol: f1
      symbol: x
      symbol: arg1 = data
    symbol: y

Where str.language is

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.recursive(expr)) {
        if (!is.list(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)

                                                 }

On Tue, Jan 12, 2021 at 1:16 PM Duncan Murdoch <murdoch.duncan using gmail.com>
wrote:

> On 12/01/2021 3:52 p.m., Bill Dunlap wrote:
> > '=>' can be defined as a function.  E.g., it could be the logical
> "implies"
> > function:
> >      > `=>` <- function(x, y) !x | y
> >      > TRUE => FALSE
> >      [1] FALSE
> >      > FALSE => TRUE
> >      [1] TRUE
> > It might be nice then to have deparse() display it as an infix operator
> > instead of the current prefix:
> >      > deparse(quote(p => q))
> >      [1] "`=>`(p, q)"
> > There was a user who recently wrote asking for an infix operator like ->
> or
> > => that would deparse nicely for use in some sort of model specification.
>
> The precedence of it as an operator is determined by what makes sense in
> the pipe construction.  Currently precedence appears to be
>
>
> :: :::  access variables in a namespace
> $ @     component / slot extraction
> [ [[    indexing
> ^       exponentiation (right to left)
> - +     unary minus and plus
> :       sequence operator
> %any%   special operators (including %% and %/%)
> * /     multiply, divide
> + -     (binary) add, subtract
> < > <= >= == != ordering and comparison
> !       negation
> & &&    and
> | ||    or
> =>      PIPE BIND
> |>      PIPE
> ~       as in formulae
> -> ->>  rightwards assignment
> <- <<-  assignment (right to left)
> =       assignment (right to left)
> ?       help (unary and binary)
>
> (Most of this is taken from ?Syntax, but I added the new operators in
> based on the gram.y file).  So
>
> A & B => C & D
>
> would appear to be parsed as
>
> (A & B) => (C & D)
>
> I think this also makes sense; do you?
>
> Duncan Murdoch
>
>
> >
> > When used with |>, the parser will turn the |> and => into an ordinary
> > looking function call so deparsing is irrelevant.
> >      > deparse(quote(x |> tmp => f(7,arg2=tmp)))
> >      [1] "f(7, arg2 = x)"
> >
> > -Bill
> >
> > On Tue, Jan 12, 2021 at 12:01 PM Dirk Eddelbuettel <edd using debian.org>
> wrote:
> >
> >>
> >> On 12 January 2021 at 20:38, Iñaki Ucar wrote:
> >> | On Tue, 12 Jan 2021 at 20:23, <luke-tierney using uiowa.edu> wrote:
> >> | >
> >> | > After some discussions we've settled on a syntax of the form
> >> | >
> >> | >      mtcars |> subset(cyl == 4) |> d => lm(mpg ~ disp, data = d)
> >> | >
> >> | > to handle cases where the pipe lhs needs to be passed to an argument
> >> | > other than the first of the function called on the rhs. This seems a
> >> | > to be a reasonable balance between making these non-standard cases
> >> | > easy to see but still easy to write. This is now committed to
> R-devel.
> >> |
> >> | Interesting. Is the use of "d =>" restricted to pipelines? In other
> >> | words, I think that it shouldn't be equivalent to "function(d)", i.e.,
> >> | that this:
> >> |
> >> | x <- d => lm(mpg ~ disp, data = d)
> >> |
> >> | shouldn't work.
> >>
> >> Looks like your wish was already granted:
> >>
> >>    > mtcars |> subset(cyl == 4) |> d => lm(mpg ~ disp, data = d)
> >>
> >>    Call:
> >>    lm(formula = mpg ~ disp, data = subset(mtcars, cyl == 4))
> >>
> >>    Coefficients:
> >>    (Intercept)         disp
> >>         40.872       -0.135
> >>
> >>    > d => lm(mpg ~ disp, data = d)
> >>    Error in `=>`(d, lm(mpg ~ disp, data = d)) : could not find function
> "=>"
> >>    > x <- d => lm(mpg ~ disp, data = d)
> >>    Error in `=>`(d, lm(mpg ~ disp, data = d)) : could not find function
> "=>"
> >>    >
> >>
> >> Dirk
> >>
> >> --
> >> https://dirk.eddelbuettel.com | @eddelbuettel | edd using debian.org
> >>
> >> ______________________________________________
> >> R-devel using r-project.org mailing list
> >> https://stat.ethz.ch/mailman/listinfo/r-devel
> >>
> >
> >       [[alternative HTML version deleted]]
> >
> > ______________________________________________
> > R-devel using r-project.org mailing list
> > https://stat.ethz.ch/mailman/listinfo/r-devel
> >
>
>

	[[alternative HTML version deleted]]



More information about the R-devel mailing list