Re: [Rd] New pipe operator and gg plotz

2020-12-09 Thread Hadley Wickham
Another option is https://github.com/hadley/ggplot1 藍
Hadley

On Wed, Dec 9, 2020 at 1:24 PM Duncan Murdoch  wrote:
>
> Looks like Sergio Oller took your ambitious approach:
> https://github.com/zeehio/ggpipe.  It hasn't been updated since 2017, so
> there may be some new things in ggplot2 that aren't there yet.
>
> Duncan Murdoch
>
> On 09/12/2020 2:16 p.m., Greg Snow wrote:
> > Since `+` is already a function we could do regular piping to change this 
> > code:
> >
> > mtcars %>%
> >ggplot(aes(x=wt, y=mpg)) +
> >geom_point()
> >
> > to this:
> >
> > mtcars %>%
> >ggplot(aes(x=wt, y=mpg)) %>%
> >`+`(geom_point())
> >
> > Further we can write wrapper functions like:
> >
> > p_geom_point <- function(x,...) {
> >x + geom_point(...)
> > }
> >
> > The run the code like:
> >
> > mtcars %>%
> >ggplot(aes(x=wt, y=mpg)) %>%
> >p_geom_point()
> >
> > All three of the above give the same plot from what I can see, but I
> > have not tested it with very many options beyond the above.
> >
> > A really ambitious person could create a new package with wrappers for
> > all the ggplot2 functions that can come after the plus sign, then we
> > could use pipes for everything.  I don't know if there are any strange
> > circumstances that would make this cause problems (it probably will
> > slow things down slightly, but probably not enough for people to
> > notice).
> >
> > On Sun, Dec 6, 2020 at 7:18 PM Avi Gross via R-devel
> >  wrote:
> >>
> >> Thanks, Duncan. That answers my question fairly definitively.
> >>
> >> Although it can be DONE it likely won't be for the reasons Hadley 
> >> mentioned until we get some other product that replaces it entirely. There 
> >> are some interesting work-arounds mentioned.
> >>
> >> I was thinking of one that has overhead but might be a pain. Hadley 
> >> mentioned a slight variant. The first argument to a function now is 
> >> expected to be the data argument. The second might be the mapping. Now if 
> >> the function is called with a new first argument that is a ggplot object, 
> >> it could be possible to test the type and if it is a ggplot object than 
> >> slide over carefully any additional matched arguments that were not 
> >> explicitly named. Not sure that is at all easy to do.
> >>
> >> Alternately, you can ask that when used in such a pipeline that the user 
> >> call all other arguments using names like data=whatever, 
> >> mapping=aes(whatever) so no other args need to be adjusted by position.
> >>
> >> But all this is academic and I concede will likely not be done. I can live 
> >> with the plus signs.
> >>
> >>
> >> -Original Message-
> >> From: Duncan Murdoch 
> >> Sent: Sunday, December 6, 2020 2:50 PM
> >> To: Avi Gross ; 'r-devel' 
> >> Subject: Re: [Rd] New pipe operator and gg plotz
> >>
> >> Hadley's answer (#7 here:
> >> https://community.rstudio.com/t/why-cant-ggplot2-use/4372) makes it pretty 
> >> clear that he thinks it would have been nice now if he had made that 
> >> choice when ggplot2 came out, but it's not worth the effort now to change 
> >> it.
> >>
> >> Duncan Murdoch
> >>
> >> On 06/12/2020 2:34 p.m., Avi Gross via R-devel wrote:
> >>> As someone who switches back and forth between using standard R methods 
> >>> and those of the tidyverse, depending on the problem, my mood and whether 
> >>> Jupiter aligns with Saturn in the new age of Aquarius, I have a question 
> >>> about the forthcoming built-in pipe. Will it motivate anyone to 
> >>> eventually change or enhance the ggplot functionality to have a version 
> >>> that gets rid of the odd use of the addition symbol?
> >>>
> >>> I mean I now sometimes have a pipeline that looks like:
> >>>
> >>> Data %>%
> >>>Do_this %>%
> >>>Do_that(whatever) %>%
> >>>ggplot(...) +
> >>>geom_whatever(...) +
> >>>...
> >>>
> >>> My understanding is this is a bit of a historical anomaly that might 
> >>> someday be modified back.
> >>>
> >>> As I understand it, the call to ggplot() creates a partially filled-in 
> >>> object that holds all kinds of useful info. The additi

Re: [Rd] New pipe operator and gg plotz

2020-12-09 Thread Duncan Murdoch
Looks like Sergio Oller took your ambitious approach: 
https://github.com/zeehio/ggpipe.  It hasn't been updated since 2017, so 
there may be some new things in ggplot2 that aren't there yet.


Duncan Murdoch

On 09/12/2020 2:16 p.m., Greg Snow wrote:

Since `+` is already a function we could do regular piping to change this code:

mtcars %>%
   ggplot(aes(x=wt, y=mpg)) +
   geom_point()

to this:

mtcars %>%
   ggplot(aes(x=wt, y=mpg)) %>%
   `+`(geom_point())

Further we can write wrapper functions like:

p_geom_point <- function(x,...) {
   x + geom_point(...)
}

The run the code like:

mtcars %>%
   ggplot(aes(x=wt, y=mpg)) %>%
   p_geom_point()

All three of the above give the same plot from what I can see, but I
have not tested it with very many options beyond the above.

A really ambitious person could create a new package with wrappers for
all the ggplot2 functions that can come after the plus sign, then we
could use pipes for everything.  I don't know if there are any strange
circumstances that would make this cause problems (it probably will
slow things down slightly, but probably not enough for people to
notice).

On Sun, Dec 6, 2020 at 7:18 PM Avi Gross via R-devel
 wrote:


Thanks, Duncan. That answers my question fairly definitively.

Although it can be DONE it likely won't be for the reasons Hadley mentioned 
until we get some other product that replaces it entirely. There are some 
interesting work-arounds mentioned.

I was thinking of one that has overhead but might be a pain. Hadley mentioned a 
slight variant. The first argument to a function now is expected to be the data 
argument. The second might be the mapping. Now if the function is called with a 
new first argument that is a ggplot object, it could be possible to test the 
type and if it is a ggplot object than slide over carefully any additional 
matched arguments that were not explicitly named. Not sure that is at all easy 
to do.

Alternately, you can ask that when used in such a pipeline that the user call 
all other arguments using names like data=whatever, mapping=aes(whatever) so no 
other args need to be adjusted by position.

But all this is academic and I concede will likely not be done. I can live with 
the plus signs.


-Original Message-
From: Duncan Murdoch 
Sent: Sunday, December 6, 2020 2:50 PM
To: Avi Gross ; 'r-devel' 
Subject: Re: [Rd] New pipe operator and gg plotz

Hadley's answer (#7 here:
https://community.rstudio.com/t/why-cant-ggplot2-use/4372) makes it pretty 
clear that he thinks it would have been nice now if he had made that choice 
when ggplot2 came out, but it's not worth the effort now to change it.

Duncan Murdoch

On 06/12/2020 2:34 p.m., Avi Gross via R-devel wrote:

As someone who switches back and forth between using standard R methods and 
those of the tidyverse, depending on the problem, my mood and whether Jupiter 
aligns with Saturn in the new age of Aquarius, I have a question about the 
forthcoming built-in pipe. Will it motivate anyone to eventually change or 
enhance the ggplot functionality to have a version that gets rid of the odd use 
of the addition symbol?

I mean I now sometimes have a pipeline that looks like:

Data %>%
   Do_this %>%
   Do_that(whatever) %>%
   ggplot(...) +
   geom_whatever(...) +
   ...

My understanding is this is a bit of a historical anomaly that might someday be 
modified back.

As I understand it, the call to ggplot() creates a partially filled-in object 
that holds all kinds of useful info. The additional calls to geom_point() and 
so on will add/change that hidden object. Nothing much happens till the object 
is implicitly or explicitly given to print() which switches to the print 
function for objects of that type and creates a graph based on the contents of 
the object at that time. So, in theory, you could have a pipelined version of 
ggplot where the first function accepts something like a  data.frame or tibble 
as the default first argument and at the end returns the object we have been 
describing. All additional functions would then accept such an object as the 
(hidden?) first argument and return the modified object. The final function in 
the pipe would either have the value captured in a variable for later use or 
print implicitly generating a graph.

So the above silly example might become:

Data %>%
   Do_this %>%
   Do_that(whatever) %>%
   ggplot(...) %>%
   geom_whatever(...) %>%
   ...

Or, am I missing something here?

The language and extensions such as are now in the tidyverse might be more 
streamlined and easier to read when using consistent notation. If we now build 
a reasonable version of the pipeline in, might we encourage other uses to 
gradually migrate back closer to the mainstream?

-Original Message-
From: R-devel  On Behalf Of Rui
Barradas
Sent: Sunday, December 6, 2020 2:51 AM
To: Gregory Warnes ; Abby S

Re: [Rd] New pipe operator and gg plotz

2020-12-09 Thread Greg Snow
Since `+` is already a function we could do regular piping to change this code:

mtcars %>%
  ggplot(aes(x=wt, y=mpg)) +
  geom_point()

to this:

mtcars %>%
  ggplot(aes(x=wt, y=mpg)) %>%
  `+`(geom_point())

Further we can write wrapper functions like:

p_geom_point <- function(x,...) {
  x + geom_point(...)
}

The run the code like:

mtcars %>%
  ggplot(aes(x=wt, y=mpg)) %>%
  p_geom_point()

All three of the above give the same plot from what I can see, but I
have not tested it with very many options beyond the above.

A really ambitious person could create a new package with wrappers for
all the ggplot2 functions that can come after the plus sign, then we
could use pipes for everything.  I don't know if there are any strange
circumstances that would make this cause problems (it probably will
slow things down slightly, but probably not enough for people to
notice).

On Sun, Dec 6, 2020 at 7:18 PM Avi Gross via R-devel
 wrote:
>
> Thanks, Duncan. That answers my question fairly definitively.
>
> Although it can be DONE it likely won't be for the reasons Hadley mentioned 
> until we get some other product that replaces it entirely. There are some 
> interesting work-arounds mentioned.
>
> I was thinking of one that has overhead but might be a pain. Hadley mentioned 
> a slight variant. The first argument to a function now is expected to be the 
> data argument. The second might be the mapping. Now if the function is called 
> with a new first argument that is a ggplot object, it could be possible to 
> test the type and if it is a ggplot object than slide over carefully any 
> additional matched arguments that were not explicitly named. Not sure that is 
> at all easy to do.
>
> Alternately, you can ask that when used in such a pipeline that the user call 
> all other arguments using names like data=whatever, mapping=aes(whatever) so 
> no other args need to be adjusted by position.
>
> But all this is academic and I concede will likely not be done. I can live 
> with the plus signs.
>
>
> -Original Message-
> From: Duncan Murdoch 
> Sent: Sunday, December 6, 2020 2:50 PM
> To: Avi Gross ; 'r-devel' 
> Subject: Re: [Rd] New pipe operator and gg plotz
>
> Hadley's answer (#7 here:
> https://community.rstudio.com/t/why-cant-ggplot2-use/4372) makes it pretty 
> clear that he thinks it would have been nice now if he had made that choice 
> when ggplot2 came out, but it's not worth the effort now to change it.
>
> Duncan Murdoch
>
> On 06/12/2020 2:34 p.m., Avi Gross via R-devel wrote:
> > As someone who switches back and forth between using standard R methods and 
> > those of the tidyverse, depending on the problem, my mood and whether 
> > Jupiter aligns with Saturn in the new age of Aquarius, I have a question 
> > about the forthcoming built-in pipe. Will it motivate anyone to eventually 
> > change or enhance the ggplot functionality to have a version that gets rid 
> > of the odd use of the addition symbol?
> >
> > I mean I now sometimes have a pipeline that looks like:
> >
> > Data %>%
> >   Do_this %>%
> >   Do_that(whatever) %>%
> >   ggplot(...) +
> >   geom_whatever(...) +
> >   ...
> >
> > My understanding is this is a bit of a historical anomaly that might 
> > someday be modified back.
> >
> > As I understand it, the call to ggplot() creates a partially filled-in 
> > object that holds all kinds of useful info. The additional calls to 
> > geom_point() and so on will add/change that hidden object. Nothing much 
> > happens till the object is implicitly or explicitly given to print() which 
> > switches to the print function for objects of that type and creates a graph 
> > based on the contents of the object at that time. So, in theory, you could 
> > have a pipelined version of ggplot where the first function accepts 
> > something like a  data.frame or tibble as the default first argument and at 
> > the end returns the object we have been describing. All additional 
> > functions would then accept such an object as the (hidden?) first argument 
> > and return the modified object. The final function in the pipe would either 
> > have the value captured in a variable for later use or print implicitly 
> > generating a graph.
> >
> > So the above silly example might become:
> >
> > Data %>%
> >   Do_this %>%
> >   Do_that(whatever) %>%
> >   ggplot(...) %>%
> >   geom_whatever(...) %>%
> >   ...
> >
> > Or, am I missing something here?
> >
> > The language and extensions such as are now in the tidyverse might be m

Re: [Rd] New pipe operator

2020-12-09 Thread Peter Dalgaard



> On 9 Dec 2020, at 16:20 , Duncan Murdoch  wrote:
> 
> To me curry(mean, na.rm = TRUE)(x) looks a lot more complicated than mean(x, 
> na.rm = TRUE), especially since it has the additional risk that users can 
> define their own function called "curry".

Not to mention that it would make people's data handling scripts look like the 
menu at an Indian restaurant ;-)

-pd

-- 
Peter Dalgaard, Professor,
Center for Statistics, Copenhagen Business School
Solbjerg Plads 3, 2000 Frederiksberg, Denmark
Phone: (+45)38153501
Office: A 4.23
Email: pd@cbs.dk  Priv: pda...@gmail.com

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


Re: [Rd] New pipe operator

2020-12-09 Thread Duncan Murdoch

On 09/12/2020 10:42 a.m., Jan van der Laan wrote:





On 09-12-2020 16:20, Duncan Murdoch wrote:

On 09/12/2020 9:55 a.m., Jan van der Laan wrote:



I think only allowing functions on the right hand side (e.g. only the |>
operator and not the |:>) would be enough to handle most cases and seems
easier to reason about. The limitations of that can easily be worked
around using existing functionality in the language.


I agree that would be sufficient, but I don't see how it makes reasoning
easier.  The transformation is trivial, so I'll assume that doesn't
consume any mental energy compared to understanding what the final
expression actually does.  Using your currying example, the choice is
between

   x |> mean(na.rm = TRUE)

which transforms to mean(x, na.rm = TRUE), or your proposed

   x |> curry(mean, na.rm = TRUE)

which transforms to

   curry(mean, na.rm = TRUE)(x)

To me curry(mean, na.rm = TRUE)(x) looks a lot more complicated than
mean(x, na.rm = TRUE), especially since it has the additional risk that
users can define their own function called "curry".



First, I do agree that

x |> mean(na.rm = TRUE)

is cleaner and this covers most of the use cases of users and many users
are used to the syntax from the magritr pipes.

However, for programmers (there is not distinct line between users and
programmers), it is simpler to reason in the sense that lhs |> rhs
always mean rhs(lhs); this does not depend on whether rhs is call or
(anonymous) function (not sure what is called what; which perhaps
illustrates the difficulty).


I think your proposed rule is pretty simple, with just one case:

lhs |> rhs

would transform to rhs(lhs).  Yes, that's simple.

The current rule is not as simple as yours, but it only has two cases 
instead of 1.  Both involve the rhs being a call, nothing else.


Case 1, the common one:  rhs is a call to a function using regular 
syntax, e.g. f(args) where args might be empty.  Then it is transformed 
to f(lhs, args).


Case 2:  rhs is a call to `function`, which we normally write as 
"function(args) body", which is transformed to (function(args) body)(lhs).


That's it!  Nothing else is allowed.  Not as simple as yours, but simple 
enough to be trivial to reason about.  Most of the effort would be spent 
in figuring out how the transformed expression would evaluate, and since 
your transformed expression is more complicated in the common case where 
currying is needed, I prefer the current proposal.





As soon as you start to have functions returning functions, you have to
think about how many brackets you have to place where. Being able to use
functions returning functions does open up possibilities for
programmers, as illustrated for example in my example using expressions.
This would have been much less clear.


I think your examples would work in the current system, too, with a 
small change to fexpr.  A corresponding change to curry could be made, 
but then it wouldn't be doing currying, so I won't do that.  Here's your 
example rewritten in the R-devel system:


fexpr <- function(x, expr){
  expr <- substitute(expr)
  f <- function(.) {}
  body(f) <- expr
  f(x)
}
. <- fexpr


1:10 |> mean()
c(1,3,NA) |> mean(na.rm = TRUE)
c(1,3,NA) |> .( mean(., na.rm = TRUE) ) |> identity()
c(1,3,NA) |> .( . + 4)
c(1,3,NA) |> fexpr( . + 4)
c(1,3,NA) |> function(x) mean(x, na.rm = TRUE) |> fexpr(. + 1)

That produces the same outputs as your code.

Duncan Murdoch



The argument of users begin able to redefine curry. Yes they can and
this is perhaps a good thing. They can also redefine a lot of other
stuff. And I am not suggesting that curry or fexpr or . are good names.
You could even have a curry operator.

Best,
Jan







Duncan Murdoch



The problem with only allowing

x |> mean

and not

x |> mean()

is with additional arguments. However, this can be solved with a
currying function, for example:

x |> curry(mean, na.rm = TRUE)

The cost is a few additional characters.

In the same way it is possible to write a function that accepts an
expression and returns a function containing that expression. This can
be used to have expressions on the right-hand side and reduces the need
for anonymous functions.

x |> fexpr(. + 10)
dta |> fexpr(lm(y ~ x, data = .))

You could call this function .:

x |> .(. + 10)
dta |> .(lm(y ~ x, data = .))


Dummy example code (thanks to  a colleague of mine)


fexpr <- function(expr){
     expr <- substitute(expr)
     f <- function(.) {}
     body(f) <- expr
     f
}
. <- fexpr

curry <- function(fun,...){
     L <- list(...)
     function(...){
   do.call(fun, c(list(...),L))
     }
}

`%|>%` <- function(e1, e2) {
     e2(e1)
}


1:10 %>% mean
c(1,3,NA) %|>% curry(mean, na.rm = TRUE)
c(1,3,NA) %|>% .( mean(., na.rm = TRUE) ) %>% identity
c(1,3,NA) %|>% .( . + 4)
c(1,3,NA) %|>% fexpr( . + 4)
c(1,3,NA) %|>% function(x) mean(x, na.rm = TRUE) %>% fexpr(. + 1)

--
Jan

__
R-devel@r-project.org mailing list

Re: [Rd] New pipe operator

2020-12-09 Thread Jan van der Laan






On 09-12-2020 16:20, Duncan Murdoch wrote:

On 09/12/2020 9:55 a.m., Jan van der Laan wrote:



I think only allowing functions on the right hand side (e.g. only the |>
operator and not the |:>) would be enough to handle most cases and seems
easier to reason about. The limitations of that can easily be worked
around using existing functionality in the language.


I agree that would be sufficient, but I don't see how it makes reasoning 
easier.  The transformation is trivial, so I'll assume that doesn't 
consume any mental energy compared to understanding what the final 
expression actually does.  Using your currying example, the choice is 
between


  x |> mean(na.rm = TRUE)

which transforms to mean(x, na.rm = TRUE), or your proposed

  x |> curry(mean, na.rm = TRUE)

which transforms to

  curry(mean, na.rm = TRUE)(x)

To me curry(mean, na.rm = TRUE)(x) looks a lot more complicated than 
mean(x, na.rm = TRUE), especially since it has the additional risk that 
users can define their own function called "curry".



First, I do agree that

x |> mean(na.rm = TRUE)

is cleaner and this covers most of the use cases of users and many users 
are used to the syntax from the magritr pipes.


However, for programmers (there is not distinct line between users and 
programmers), it is simpler to reason in the sense that lhs |> rhs 
always mean rhs(lhs); this does not depend on whether rhs is call or 
(anonymous) function (not sure what is called what; which perhaps 
illustrates the difficulty).


As soon as you start to have functions returning functions, you have to 
think about how many brackets you have to place where. Being able to use 
functions returning functions does open up possibilities for 
programmers, as illustrated for example in my example using expressions. 
This would have been much less clear.


The argument of users begin able to redefine curry. Yes they can and 
this is perhaps a good thing. They can also redefine a lot of other 
stuff. And I am not suggesting that curry or fexpr or . are good names. 
You could even have a curry operator.


Best,
Jan







Duncan Murdoch



The problem with only allowing

x |> mean

and not

x |> mean()

is with additional arguments. However, this can be solved with a
currying function, for example:

x |> curry(mean, na.rm = TRUE)

The cost is a few additional characters.

In the same way it is possible to write a function that accepts an
expression and returns a function containing that expression. This can
be used to have expressions on the right-hand side and reduces the need
for anonymous functions.

x |> fexpr(. + 10)
dta |> fexpr(lm(y ~ x, data = .))

You could call this function .:

x |> .(. + 10)
dta |> .(lm(y ~ x, data = .))


Dummy example code (thanks to  a colleague of mine)


fexpr <- function(expr){
    expr <- substitute(expr)
    f <- function(.) {}
    body(f) <- expr
    f
}
. <- fexpr

curry <- function(fun,...){
    L <- list(...)
    function(...){
  do.call(fun, c(list(...),L))
    }
}

`%|>%` <- function(e1, e2) {
    e2(e1)
}


1:10 %>% mean
c(1,3,NA) %|>% curry(mean, na.rm = TRUE)
c(1,3,NA) %|>% .( mean(., na.rm = TRUE) ) %>% identity
c(1,3,NA) %|>% .( . + 4)
c(1,3,NA) %|>% fexpr( . + 4)
c(1,3,NA) %|>% function(x) mean(x, na.rm = TRUE) %>% fexpr(. + 1)

--
Jan

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





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


Re: [Rd] New pipe operator

2020-12-09 Thread Duncan Murdoch

On 09/12/2020 9:55 a.m., Jan van der Laan wrote:



I think only allowing functions on the right hand side (e.g. only the |>
operator and not the |:>) would be enough to handle most cases and seems
easier to reason about. The limitations of that can easily be worked
around using existing functionality in the language.


I agree that would be sufficient, but I don't see how it makes reasoning 
easier.  The transformation is trivial, so I'll assume that doesn't 
consume any mental energy compared to understanding what the final 
expression actually does.  Using your currying example, the choice is 
between


 x |> mean(na.rm = TRUE)

which transforms to mean(x, na.rm = TRUE), or your proposed

 x |> curry(mean, na.rm = TRUE)

which transforms to

 curry(mean, na.rm = TRUE)(x)

To me curry(mean, na.rm = TRUE)(x) looks a lot more complicated than 
mean(x, na.rm = TRUE), especially since it has the additional risk that 
users can define their own function called "curry".


Duncan Murdoch



The problem with only allowing

x |> mean

and not

x |> mean()

is with additional arguments. However, this can be solved with a
currying function, for example:

x |> curry(mean, na.rm = TRUE)

The cost is a few additional characters.

In the same way it is possible to write a function that accepts an
expression and returns a function containing that expression. This can
be used to have expressions on the right-hand side and reduces the need
for anonymous functions.

x |> fexpr(. + 10)
dta |> fexpr(lm(y ~ x, data = .))

You could call this function .:

x |> .(. + 10)
dta |> .(lm(y ~ x, data = .))


Dummy example code (thanks to  a colleague of mine)


fexpr <- function(expr){
expr <- substitute(expr)
f <- function(.) {}
body(f) <- expr
f
}
. <- fexpr

curry <- function(fun,...){
L <- list(...)
function(...){
  do.call(fun, c(list(...),L))
}
}

`%|>%` <- function(e1, e2) {
e2(e1)
}


1:10 %>% mean
c(1,3,NA) %|>% curry(mean, na.rm = TRUE)
c(1,3,NA) %|>% .( mean(., na.rm = TRUE) ) %>% identity
c(1,3,NA) %|>% .( . + 4)
c(1,3,NA) %|>% fexpr( . + 4)
c(1,3,NA) %|>% function(x) mean(x, na.rm = TRUE) %>% fexpr(. + 1)

--
Jan

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



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


Re: [Rd] New pipe operator

2020-12-09 Thread Jan van der Laan




On 08-12-2020 12:46, Gabor Grothendieck wrote:

Duncan Murdoch:

I agree it's all about call expressions, but they aren't all being
treated equally:

x |> f(...)

expands to f(x, ...), while

x |> `function`(...)

expands to `function`(...)(x).  This is an exception to the rule for


Yes, this is the problem.  It is trying to handle two different sorts of right
hand sides, calls and functions, using only syntax level operations and
it really needs to either make use of deeper information or have some
method that is available at the syntax level for identifying whether the
right hand side is a call or function.  In the latter case having two
operators would be one way to do it.

   f <- \(x) x + 1
   x |> f()  # call
   x |:> f  # function
   x |:> \(x) x + 1  # function

In the other case where deeper information is used there would only be one
operator and it would handle all cases but would use more than just syntax
level knowledge.

R solved these sorts of problems long ago using S3 and other object oriented
systems which dispatch different methods based on what the right hand side is.
The attempt to avoid using the existing or equivalent mechanisms seems to have
led to this problem.





I think only allowing functions on the right hand side (e.g. only the |> 
operator and not the |:>) would be enough to handle most cases and seems 
easier to reason about. The limitations of that can easily be worked 
around using existing functionality in the language.


The problem with only allowing

x |> mean

and not

x |> mean()

is with additional arguments. However, this can be solved with a 
currying function, for example:


x |> curry(mean, na.rm = TRUE)

The cost is a few additional characters.

In the same way it is possible to write a function that accepts an 
expression and returns a function containing that expression. This can 
be used to have expressions on the right-hand side and reduces the need 
for anonymous functions.


x |> fexpr(. + 10)
dta |> fexpr(lm(y ~ x, data = .))

You could call this function .:

x |> .(. + 10)
dta |> .(lm(y ~ x, data = .))


Dummy example code (thanks to  a colleague of mine)


fexpr <- function(expr){
  expr <- substitute(expr)
  f <- function(.) {}
  body(f) <- expr
  f
}
. <- fexpr

curry <- function(fun,...){
  L <- list(...)
  function(...){
do.call(fun, c(list(...),L))
  }
}

`%|>%` <- function(e1, e2) {
  e2(e1)
}


1:10 %>% mean
c(1,3,NA) %|>% curry(mean, na.rm = TRUE)
c(1,3,NA) %|>% .( mean(., na.rm = TRUE) ) %>% identity
c(1,3,NA) %|>% .( . + 4)
c(1,3,NA) %|>% fexpr( . + 4)
c(1,3,NA) %|>% function(x) mean(x, na.rm = TRUE) %>% fexpr(. + 1)

--
Jan

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


Re: [Rd] New pipe operator

2020-12-08 Thread Bravington, Mark (Data61, Hobart)
> [Duncan Murdoch responding to...]
> [... Mark Bravington's proposals for placeholders and anonymous functions]
> > x |> foo( _PIPE_)  # placeholder
> > x |> bah( otherarg, _PIPE_)# placeholder
> > x |> { y <- _PIPE_+1; _PIPE_ / y } # anonymous function

> [DM] About your proposal [specifically, the anonymous function bit]:

> I don't find it attractive, but I can see that some people would.  But I
> don't think it's necessary to put it into the base parser.  Other than
> using an illegal name, there doesn't seem to be a reason you couldn't
> write a small function to convert your placeholder proposal to a call to
> a function.  So instead of typing

>   x |> { y <- _PIPE_+1; _PIPE_ / y }

> you would type

>   x |> forpipe({ y <- PIPE_+1; PIPE_ / y })

> I don't think "forpipe" is the right name here.  I proposed a generic
> "as.call" before, but I don't like that one either.  I'm still trying to
> think of a good name, and whether or not it makes sense for it to be
> generic.

Right, yes. Actually that was part of my first email: I had

x |> _ANON_({ y <- _PIPE_+1; _PIPE_ / y })

I deliberately picked otherwise-illegal names, to prevent extrapipular abuse, 
but that's not a big deal. Second email gives that option as well as 
curly-brace version.

It's true that there's no *need* to change the base parser in order to get the 
functionality of your 'forpipe' / my '_ANON_'--- but pipes are really about 
convenience, so "need" becomes quite subjective; perhaps the curly-brace 
version, or something else, is attractive enough to warrant it (I don't know). 
And it seems like the new pipe-aware parser is already having to deal 
differently with expressions inside a pipe vs outside.

However, I was also discussing non-anonymous function calls in pipes, and 
arguing that they should require (or at least be able to use) a reserved-word 
placeholder (PIPE_ or whatever)--- EG

x |> match( LETTERS, _PIPE_) # non-first arg

So that's a separate part of my proposal.

If I was king I actually wouldn't let people do

x |> head

and would force them instead to do 

x |> head( _PIPE_)

but, clearly, I am not.

> But the point is that we don't need to choose just one from all the
> proposed replacements for anonymous function syntax, we can try them out
> and see which ones we like.  We might end up with more than one (like we
> have at least 4 different high level graphics paradigms!), and that's
> not the end of the world.

Good point. Multiple options is no disaster, and experiments are excellent--- 
though once things get embedded in R, it's hard to pull them out... 

However, aren't we limited to experimenting within the confines of the current 
pipe-aware parser? Many of the suggestions on this topic seem to go beyond that 
(including mine). EG I *think*, subject to correction, that

 - you're right that 'forpipe'/'_ANON_' can be implemented to work with the 
current pipe-aware parser
 
 - But, the curly-brace version would require a parser change
 
 - and the use of a reserved-word placeholder also isn't possible as-is
 
If there's some way to try those things out, it would be great.

cheers
Mark


Mark Bravington
CSIRO Marine Lab
Hobart
Australia



From: Duncan Murdoch 
Sent: Wednesday, 9 December 2020 09:28
To: Bravington, Mark (Data61, Hobart); Gabor Grothendieck; Gabriel Becker
Cc: r-devel@r-project.org
Subject: Re: [Rd] New pipe operator

First, one comment:

You're right about the illegality of _PIPE_ as a name, I had
misremembered the rule.

About your proposal:

I don't find it attractive, but I can see that some people would.  But I
don't think it's necessary to put it into the base parser.  Other than
using an illegal name, there doesn't seem to be a reason you couldn't
write a small function to convert your placeholder proposal to a call to
a function.  So instead of typing

  x |> { y <- _PIPE_+1; _PIPE_ / y }

you would type

  x |> forpipe({ y <- PIPE_+1; PIPE_ / y })

I don't think "forpipe" is the right name here.  I proposed a generic
"as.call" before, but I don't like that one either.  I'm still trying to
think of a good name, and whether or not it makes sense for it to be
generic.

But the point is that we don't need to choose just one from all the
proposed replacements for anonymous function syntax, we can try them out
and see which ones we like.  We might end up with more than one (like we
have at least 4 different high level graphics paradigms!), and that's
not the end of the world.

Duncan Murdoch

On 08/12/2020 4:26 p.m., Bravington, Mark (Data61, Hobart) wrote:
>>> On 06/12/2020 8:22 p.m., Bravington, Mark (Data61, Hobart) wrote:
>> (and Duncan Murdoch responded, as below)
>
> It still seems to me that placeholders are via

Re: [Rd] New pipe operator

2020-12-08 Thread Duncan Murdoch
ipe syntax choice for base-R, of 
course...



Then



x |> (_ + 1) + mean(_)



could expand unambiguously to



(function(_) (_  + 1) + mean(_))(x)



but



(_ + 1) + mean(_)



shouldn't be taken to be an anonymous function declaration, otherwise
things like



mean(_ |> _)



do become ambiguous:  is the second placeholder the argument to the anon
function, or is it the placeholder for the embedded pipe?


That wouldn't be allowed in my proposal; the "_ |> _" is illegal because the 
RHS is not a call. For the whole thing, I'd require

x |> _ANON_((_PIPE_ + 1) + mean( _PIPE_))

or the just-curly version

x |> { (_PIPE_ + 1) + mean( _PIPE_)}

but with the implication that this would parse out to

(`_ANON_`( { (_PIPE_ + 1) + mean( _PIPE_)}))( x)


[*] Definition of _ANON_ could be something like this--- almost certainly won't 
work as-is, this is just to point out that it could be done in standard R.



`_ANON_` <- function( expr) {
   #1. Construct a function with arg '_PIPE_' and body 'expr'
   #2. Construct a call() to that function
   #3. Do the call



   f <- function( `_PIPE_`) NULL
   body( f) <- expr
   environment( f) <- parent.frame() # or something... yes these details are 
almost certainly wrong
   expr2 <- substitute( f( `_PIPE_`)) # or something...
   eval.parent( expr2) # or something...
}



Mark Bravington
CSIRO Marine Lab
Hobart
Australia



From: Duncan Murdoch 
Sent: Monday, 7 December 2020 21:31
To: Bravington, Mark (Data61, Hobart); Gabor Grothendieck; Gabriel Becker
Cc: r-devel@r-project.org
Subject: Re: [Rd] New pipe operator

On 06/12/2020 8:22 p.m., Bravington, Mark (Data61, Hobart) wrote:

Seems like this *could* be a good thing, and thanks to R core for considering 
it. But, FWIW:

   - I agree with Gabor G that consistency of "syntax" should be paramount 
here. Enough problems have been caused by earlier superficially-convenient non-standard 
features in R.  In particular:

   -- there should not be any discrepancy between an in-place 
function-definition, and a predefined function attached to a symbol (as per 
Gabor's point).

   -- Hence, the ability to say x |> foo  ie without parentheses, seems bound to lead to 
inconsistency, because x |> foo is allowed, x |> base::foo isn't allowed without tricks, 
but x |> function( y) foo( y) isn't... So, x |> foo is not worth keeping. Parentheses 
are a price well worth paying.

   -- it is still inconsistent and confusing to (apparently) invoke a function 
in some places--- normally--- via 'foo(x)', yet in others--- pipily--- via 
'foo()'. Especially if 'foo' already has a default value for its first argument.

   - I don't see the problem with a placeholder--- doesn't it remove all 
ambiguity? Sure there needs to be a standard unclashable name and people can 
argue about what that should be, but the following seems clear and flexible... 
to me, anyway:

   thing |>
 foo( _PIPE_) |>   # standard
 bah( arg1, _PIPE_) |>   # multi-arg function
 _ANON_({ x <- sum( _PIPE_); _PIPE_/x + x/_PIPE_ })   # anon function

where '_PIPE_' is the ordained name of the placeholder, and '_ANON_' 
constructs-and-calls a function with single argument '_PIPE_'. There is just 
one rule (I think...): each pipe-stage must be a *call* involving the argument 
'_PIPE_'.


I believe there's no ambiguity if the placeholder is *only* allowed in
the RHS of a pipe expression.  I think the ambiguity arises if you allow
the same syntax to be used to generate anonymous functions.  We can't
use _PIPE_ as the placeholder, because it's a legal name.  But we could
use _.  Then

x |> (_ + 1) + mean(_)

could expand unambiguously to

(function(_) (_  + 1) + mean(_))(x)

but

(_ + 1) + mean(_)

shouldn't be taken to be an anonymous function declaration, otherwise
things like

mean(_ |> _)

do become ambiguous:  is the second placeholder the argument to the anon
function, or is it the placeholder for the embedded pipe?

However, implementing this makes the parser pretty ugly:  its handling
of _ depends on the outer context.  I now agree that leaving out
placeholder syntax was the right decision.





   - The proposed anonymous-function syntax looks quite ugly to me, diminishing 
readability and inviting errors. The new pipe symbol |> already looks scarily 
like quantum mechanics; adding \( just puts fishbones into the symbolic soup.

   - IMO it's not worth going too far to try to lure magritter-etc fans to swap 
to the new; my experience is that many people keep using older inferior R 
syntax for years after better replacements become available (even if they are 
aware of replacements), for various reasons. Just provide a good framework, and 
let nature take its course.

   - Disclaimer: personally I'm not much of a pipehead anyway, so maybe I'm not 
the audience. But if I was to consider piping, I wouldn't be 

Re: [Rd] New pipe operator

2020-12-08 Thread Bravington, Mark (Data61, Hobart)
ON_` <- function( expr) { 
> >   #1. Construct a function with arg '_PIPE_' and body 'expr'
> >   #2. Construct a call() to that function
> >   #3. Do the call

> >   f <- function( `_PIPE_`) NULL
> >   body( f) <- expr
> >   environment( f) <- parent.frame() # or something... yes these details are 
> > almost certainly wrong
> >   expr2 <- substitute( f( `_PIPE_`)) # or something...
> >   eval.parent( expr2) # or something... 
> > }


Mark Bravington
CSIRO Marine Lab
Hobart
Australia



From: Duncan Murdoch 
Sent: Monday, 7 December 2020 21:31
To: Bravington, Mark (Data61, Hobart); Gabor Grothendieck; Gabriel Becker
Cc: r-devel@r-project.org
Subject: Re: [Rd] New pipe operator

On 06/12/2020 8:22 p.m., Bravington, Mark (Data61, Hobart) wrote:
> Seems like this *could* be a good thing, and thanks to R core for considering 
> it. But, FWIW:
>
>   - I agree with Gabor G that consistency of "syntax" should be paramount 
> here. Enough problems have been caused by earlier superficially-convenient 
> non-standard features in R.  In particular:
>
>   -- there should not be any discrepancy between an in-place 
> function-definition, and a predefined function attached to a symbol (as per 
> Gabor's point).
>
>   -- Hence, the ability to say x |> foo  ie without parentheses, seems bound 
> to lead to inconsistency, because x |> foo is allowed, x |> base::foo isn't 
> allowed without tricks, but x |> function( y) foo( y) isn't... So, x |> foo 
> is not worth keeping. Parentheses are a price well worth paying.
>
>   -- it is still inconsistent and confusing to (apparently) invoke a function 
> in some places--- normally--- via 'foo(x)', yet in others--- pipily--- via 
> 'foo()'. Especially if 'foo' already has a default value for its first 
> argument.
>
>   - I don't see the problem with a placeholder--- doesn't it remove all 
> ambiguity? Sure there needs to be a standard unclashable name and people can 
> argue about what that should be, but the following seems clear and 
> flexible... to me, anyway:
>
>   thing |>
> foo( _PIPE_) |>   # standard
> bah( arg1, _PIPE_) |>   # multi-arg function
> _ANON_({ x <- sum( _PIPE_); _PIPE_/x + x/_PIPE_ })   # anon function
>
> where '_PIPE_' is the ordained name of the placeholder, and '_ANON_' 
> constructs-and-calls a function with single argument '_PIPE_'. There is just 
> one rule (I think...): each pipe-stage must be a *call* involving the 
> argument '_PIPE_'.

I believe there's no ambiguity if the placeholder is *only* allowed in
the RHS of a pipe expression.  I think the ambiguity arises if you allow
the same syntax to be used to generate anonymous functions.  We can't
use _PIPE_ as the placeholder, because it's a legal name.  But we could
use _.  Then

   x |> (_ + 1) + mean(_)

could expand unambiguously to

   (function(_) (_  + 1) + mean(_))(x)

but

   (_ + 1) + mean(_)

shouldn't be taken to be an anonymous function declaration, otherwise
things like

   mean(_ |> _)

do become ambiguous:  is the second placeholder the argument to the anon
function, or is it the placeholder for the embedded pipe?

However, implementing this makes the parser pretty ugly:  its handling
of _ depends on the outer context.  I now agree that leaving out
placeholder syntax was the right decision.


>
>
>   - The proposed anonymous-function syntax looks quite ugly to me, 
> diminishing readability and inviting errors. The new pipe symbol |> already 
> looks scarily like quantum mechanics; adding \( just puts fishbones into the 
> symbolic soup.
>
>   - IMO it's not worth going too far to try to lure magritter-etc fans to 
> swap to the new; my experience is that many people keep using older inferior 
> R syntax for years after better replacements become available (even if they 
> are aware of replacements), for various reasons. Just provide a good 
> framework, and let nature take its course.
>
>   - Disclaimer: personally I'm not much of a pipehead anyway, so maybe I'm 
> not the audience. But if I was to consider piping, I wouldn't be very tempted 
> by the current proposal. OTOH, I might even be tempted to write--- and 
> use!--- my own version of '%|>%' as above (maybe someone already has). And if 
> R did it for me, that'd be great :)

Yours would suffer one of the same problems as magrittr's:  it has the
wrong operator precedence.  The current precedence ordering (from
?Syntax) is, from highest to lowest:


:: :::  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

Re: [Rd] New pipe operator

2020-12-08 Thread Hadley Wickham
I just wanted to pipe in here (HA HA) to say that I agree with Kevin.
I've never loved the complicated magrittr rule (which has personally
tripped me up a couple of times) and I think the compact inline
function syntax provides a more general solution. It is a bit more
typing, and it will require a little time for your eyes to get used to
the new syntax, but overall I think it's a better solution.

In general, I think the base pipe does an excellent job of taking what
we've learned from 6 years of magrittr, keeping what has been most
successful while discarding complications around the edges.

Hadley

On Mon, Dec 7, 2020 at 1:05 PM Kevin Ushey  wrote:
>
> IMHO the use of anonymous functions is a very clean solution to the
> placeholder problem, and the shorthand lambda syntax makes it much
> more ergonomic to use. Pipe implementations that crawl the RHS for
> usages of `.` are going to be more expensive than the alternatives. It
> is nice that the `|>` operator is effectively the same as a regular R
> function call, and given the identical semantics could then also be
> reasoned about the same way regular R function calls are.
>
> I also agree usages of the `.` placeholder can make the code more
> challenging to read, since understanding the behavior of a piped
> expression then requires scouring the RHS for usages of `.`, which can
> be challenging in dense code. Piping to an anonymous function makes
> the intent clear to the reader: the programmer is likely piping to an
> anonymous function because they care where the argument is used in the
> call, and so the reader of code should be aware of that.
>
> Best,
> Kevin
>
>
>
> On Mon, Dec 7, 2020 at 10:35 AM Gabor Grothendieck
>  wrote:
> >
> > On Mon, Dec 7, 2020 at 12:54 PM Duncan Murdoch  
> > wrote:
> > > An advantage of the current implementation is that it's simple and easy
> > > to understand.  Once you make it a user-modifiable binary operator,
> > > things will go kind of nuts.
> > >
> > > For example, I doubt if there are many users of magrittr's pipe who
> > > really understand its subtleties, e.g. the example in Luke's paper where
> > > 1 %>% c(., 2) gives c(1,2), but 1 %>% c(c(.), 2) gives c(1, 1, 2). (And
> > > I could add 1 %>% c(c(.), 2, .) and  1 %>% c(c(.), 2, . + 2)  to
> > > continue the fun.)
> >
> > The rule is not so complicated.  Automatic insertion is done unless
> > you use dot in the top level function or if you surround it with
> > {...}.  It really makes sense since if you use gsub(pattern,
> > replacement, .) then surely you don't want automatic insertion and if
> > you surround it with { ... } then you are explicitly telling it not
> > to.
> >
> > Assuming the existence of placeholders a possible simplification would
> > be to NOT do automatic insertion if { ... } is used and to use it
> > otherwise although personally having used it for some time I find the
> > existing rule in magrittr generally does what you want.
> >
> > __
> > R-devel@r-project.org mailing list
> > https://stat.ethz.ch/mailman/listinfo/r-devel
>
> __
> R-devel@r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-devel



-- 
http://hadley.nz

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


Re: [Rd] New pipe operator

2020-12-08 Thread Gabor Grothendieck
Duncan Murdoch:
> I agree it's all about call expressions, but they aren't all being
> treated equally:
>
> x |> f(...)
>
> expands to f(x, ...), while
>
> x |> `function`(...)
>
> expands to `function`(...)(x).  This is an exception to the rule for

Yes, this is the problem.  It is trying to handle two different sorts of right
hand sides, calls and functions, using only syntax level operations and
it really needs to either make use of deeper information or have some
method that is available at the syntax level for identifying whether the
right hand side is a call or function.  In the latter case having two
operators would be one way to do it.

  f <- \(x) x + 1
  x |> f()  # call
  x |:> f  # function
  x |:> \(x) x + 1  # function

In the other case where deeper information is used there would only be one
operator and it would handle all cases but would use more than just syntax
level knowledge.

R solved these sorts of problems long ago using S3 and other object oriented
systems which dispatch different methods based on what the right hand side is.
The attempt to avoid using the existing or equivalent mechanisms seems to have
led to this problem.

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


Re: [Rd] New pipe operator

2020-12-07 Thread Gabriel Becker
Hi Denes,

On Mon, Dec 7, 2020 at 2:52 PM Dénes Tóth  wrote:

>
>
> This gave me the idea that naming the arguments can be used to skip the
> placeholder issue:
>
> "funny" |> sub(pattern = "f", replacement = "b")
>
> Of course this breaks if the maintainer changes the order of the
> function arguments (which is not a nice practice but happens).
>

This is true, but only if you are specifying all arguments that appear
before the one you want explicitly. In practice that may often be true? But
I don't really have a strong intuition about that as a non-pipe user. It
would require zero changes to the pipe by the R-core team though, so in
that sense it could be a solution in the cases it does work. It does make
the code subtler to read though, which is a pretty big downside, imho.


> An option could be to allow for missing argument in the first position,
> but this might add further undesired complexity, so probably not worth
> the effort:
>
> "funny" |> sub(x =, "f", "b")
>
> So basically the parsing rule would be:
>
> LHS |> RHS(arg=, ...) -> RHS(arg=LHS, ...)
>

The problem here is that its ambiguous, because myfun(x, y=, z) is
technically syntactically valid, so this would make code that parses now
into valid syntax change its meaning, and would prevent existing,
syntactically valid (Though hopefully quite rare) code in the pipe context.

~G


>
> >
> > (Assuming we could get the parser to handle |^bla^> correctly)
> >
> > For argument position issues would be sufficient. For more complicated
> > expressions, e.g., those that would use the placeholder multiple times or
> > inside compound expressions, requiring anonymous functions seems quite
> > reasonable to me. And honestly, while I kind of like it, I'm not sure if
> > that "stuffed pipe" expression (assuming we could get the parser to
> capture
> > it correctly) reads to me as nicer than the following, anyway.
> >
> > LHS |> \(x) RHS(arg1 = 5, pipearg = x, arg3 = 7)
> >
> > ~G
> >
> >>
> >> I also agree usages of the `.` placeholder can make the code more
> >> challenging to read, since understanding the behavior of a piped
> >> expression then requires scouring the RHS for usages of `.`, which can
> >> be challenging in dense code. Piping to an anonymous function makes
> >> the intent clear to the reader: the programmer is likely piping to an
> >> anonymous function because they care where the argument is used in the
> >> call, and so the reader of code should be aware of that.
> >>
> >> Best,
> >> Kevin
> >>
> >>
> >>
> >> On Mon, Dec 7, 2020 at 10:35 AM Gabor Grothendieck
> >>  wrote:
> >>>
> >>> On Mon, Dec 7, 2020 at 12:54 PM Duncan Murdoch <
> murdoch.dun...@gmail.com>
> >> wrote:
>  An advantage of the current implementation is that it's simple and
> easy
>  to understand.  Once you make it a user-modifiable binary operator,
>  things will go kind of nuts.
> 
>  For example, I doubt if there are many users of magrittr's pipe who
>  really understand its subtleties, e.g. the example in Luke's paper
> >> where
>  1 %>% c(., 2) gives c(1,2), but 1 %>% c(c(.), 2) gives c(1, 1, 2).
> (And
>  I could add 1 %>% c(c(.), 2, .) and  1 %>% c(c(.), 2, . + 2)  to
>  continue the fun.)
> >>>
> >>> The rule is not so complicated.  Automatic insertion is done unless
> >>> you use dot in the top level function or if you surround it with
> >>> {...}.  It really makes sense since if you use gsub(pattern,
> >>> replacement, .) then surely you don't want automatic insertion and if
> >>> you surround it with { ... } then you are explicitly telling it not
> >>> to.
> >>>
> >>> Assuming the existence of placeholders a possible simplification would
> >>> be to NOT do automatic insertion if { ... } is used and to use it
> >>> otherwise although personally having used it for some time I find the
> >>> existing rule in magrittr generally does what you want.
> >>>
> >>> __
> >>> R-devel@r-project.org mailing list
> >>> https://stat.ethz.ch/mailman/listinfo/r-devel
> >>
> >> __
> >> 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
> >
>

[[alternative HTML version deleted]]

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


Re: [Rd] New pipe operator

2020-12-07 Thread Dénes Tóth




On 12/7/20 11:09 PM, Gabriel Becker wrote:

On Mon, Dec 7, 2020 at 11:05 AM Kevin Ushey  wrote:


IMHO the use of anonymous functions is a very clean solution to the
placeholder problem, and the shorthand lambda syntax makes it much
more ergonomic to use. Pipe implementations that crawl the RHS for
usages of `.` are going to be more expensive than the alternatives. It
is nice that the `|>` operator is effectively the same as a regular R
function call, and given the identical semantics could then also be
reasoned about the same way regular R function calls are.



I agree. That said, one thing that maybe could be done, though I'm not
super convinced its needed, is make a "curry-stuffed pipe", where something
like

LHS |^pipearg^> RHS(arg1 = 5, arg3 = 7)

Would parse to

RHS(pipearg = LHS, arg1 = 5, arg3 = 7)



This gave me the idea that naming the arguments can be used to skip the 
placeholder issue:


"funny" |> sub(pattern = "f", replacement = "b")

Of course this breaks if the maintainer changes the order of the 
function arguments (which is not a nice practice but happens).


An option could be to allow for missing argument in the first position, 
but this might add further undesired complexity, so probably not worth 
the effort:


"funny" |> sub(x =, "f", "b")

So basically the parsing rule would be:

LHS |> RHS(arg=, ...) -> RHS(arg=LHS, ...)




(Assuming we could get the parser to handle |^bla^> correctly)

For argument position issues would be sufficient. For more complicated
expressions, e.g., those that would use the placeholder multiple times or
inside compound expressions, requiring anonymous functions seems quite
reasonable to me. And honestly, while I kind of like it, I'm not sure if
that "stuffed pipe" expression (assuming we could get the parser to capture
it correctly) reads to me as nicer than the following, anyway.

LHS |> \(x) RHS(arg1 = 5, pipearg = x, arg3 = 7)

~G



I also agree usages of the `.` placeholder can make the code more
challenging to read, since understanding the behavior of a piped
expression then requires scouring the RHS for usages of `.`, which can
be challenging in dense code. Piping to an anonymous function makes
the intent clear to the reader: the programmer is likely piping to an
anonymous function because they care where the argument is used in the
call, and so the reader of code should be aware of that.

Best,
Kevin



On Mon, Dec 7, 2020 at 10:35 AM Gabor Grothendieck
 wrote:


On Mon, Dec 7, 2020 at 12:54 PM Duncan Murdoch 

wrote:

An advantage of the current implementation is that it's simple and easy
to understand.  Once you make it a user-modifiable binary operator,
things will go kind of nuts.

For example, I doubt if there are many users of magrittr's pipe who
really understand its subtleties, e.g. the example in Luke's paper

where

1 %>% c(., 2) gives c(1,2), but 1 %>% c(c(.), 2) gives c(1, 1, 2). (And
I could add 1 %>% c(c(.), 2, .) and  1 %>% c(c(.), 2, . + 2)  to
continue the fun.)


The rule is not so complicated.  Automatic insertion is done unless
you use dot in the top level function or if you surround it with
{...}.  It really makes sense since if you use gsub(pattern,
replacement, .) then surely you don't want automatic insertion and if
you surround it with { ... } then you are explicitly telling it not
to.

Assuming the existence of placeholders a possible simplification would
be to NOT do automatic insertion if { ... } is used and to use it
otherwise although personally having used it for some time I find the
existing rule in magrittr generally does what you want.

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


__
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



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


Re: [Rd] New pipe operator

2020-12-07 Thread Gabriel Becker
On Mon, Dec 7, 2020 at 11:05 AM Kevin Ushey  wrote:

> IMHO the use of anonymous functions is a very clean solution to the
> placeholder problem, and the shorthand lambda syntax makes it much
> more ergonomic to use. Pipe implementations that crawl the RHS for
> usages of `.` are going to be more expensive than the alternatives. It
> is nice that the `|>` operator is effectively the same as a regular R
> function call, and given the identical semantics could then also be
> reasoned about the same way regular R function calls are.
>

I agree. That said, one thing that maybe could be done, though I'm not
super convinced its needed, is make a "curry-stuffed pipe", where something
like

LHS |^pipearg^> RHS(arg1 = 5, arg3 = 7)

Would parse to

RHS(pipearg = LHS, arg1 = 5, arg3 = 7)


(Assuming we could get the parser to handle |^bla^> correctly)

For argument position issues would be sufficient. For more complicated
expressions, e.g., those that would use the placeholder multiple times or
inside compound expressions, requiring anonymous functions seems quite
reasonable to me. And honestly, while I kind of like it, I'm not sure if
that "stuffed pipe" expression (assuming we could get the parser to capture
it correctly) reads to me as nicer than the following, anyway.

LHS |> \(x) RHS(arg1 = 5, pipearg = x, arg3 = 7)

~G

>
> I also agree usages of the `.` placeholder can make the code more
> challenging to read, since understanding the behavior of a piped
> expression then requires scouring the RHS for usages of `.`, which can
> be challenging in dense code. Piping to an anonymous function makes
> the intent clear to the reader: the programmer is likely piping to an
> anonymous function because they care where the argument is used in the
> call, and so the reader of code should be aware of that.
>
> Best,
> Kevin
>
>
>
> On Mon, Dec 7, 2020 at 10:35 AM Gabor Grothendieck
>  wrote:
> >
> > On Mon, Dec 7, 2020 at 12:54 PM Duncan Murdoch 
> wrote:
> > > An advantage of the current implementation is that it's simple and easy
> > > to understand.  Once you make it a user-modifiable binary operator,
> > > things will go kind of nuts.
> > >
> > > For example, I doubt if there are many users of magrittr's pipe who
> > > really understand its subtleties, e.g. the example in Luke's paper
> where
> > > 1 %>% c(., 2) gives c(1,2), but 1 %>% c(c(.), 2) gives c(1, 1, 2). (And
> > > I could add 1 %>% c(c(.), 2, .) and  1 %>% c(c(.), 2, . + 2)  to
> > > continue the fun.)
> >
> > The rule is not so complicated.  Automatic insertion is done unless
> > you use dot in the top level function or if you surround it with
> > {...}.  It really makes sense since if you use gsub(pattern,
> > replacement, .) then surely you don't want automatic insertion and if
> > you surround it with { ... } then you are explicitly telling it not
> > to.
> >
> > Assuming the existence of placeholders a possible simplification would
> > be to NOT do automatic insertion if { ... } is used and to use it
> > otherwise although personally having used it for some time I find the
> > existing rule in magrittr generally does what you want.
> >
> > __
> > R-devel@r-project.org mailing list
> > https://stat.ethz.ch/mailman/listinfo/r-devel
>
> __
> 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


Re: [Rd] New pipe operator

2020-12-07 Thread Gabriel Becker
On Mon, Dec 7, 2020 at 10:35 AM Gabor Grothendieck 
wrote:

> On Mon, Dec 7, 2020 at 12:54 PM Duncan Murdoch 
> wrote:
> > An advantage of the current implementation is that it's simple and easy
> > to understand.  Once you make it a user-modifiable binary operator,
> > things will go kind of nuts.
> >
> > For example, I doubt if there are many users of magrittr's pipe who
> > really understand its subtleties, e.g. the example in Luke's paper where
> > 1 %>% c(., 2) gives c(1,2), but 1 %>% c(c(.), 2) gives c(1, 1, 2). (And
> > I could add 1 %>% c(c(.), 2, .) and  1 %>% c(c(.), 2, . + 2)  to
> > continue the fun.)
>
> The rule is not so complicated.  Automatic insertion is done unless
> you use dot in the top level function or if you surround it with
> {...}.  It really makes sense since if you use gsub(pattern,
> replacement, .) then surely you don't want automatic insertion and if
> you surround it with { ... } then you are explicitly telling it not
> to.
>
>
This is the point that I believe Duncan is trying to make (and I agree
with) though. Consider the question "after piping LHS into RHS, what is the
first argument in the resulting call?".

For the base pipe, the answer, completely unambiguously, is LHS. Full stop.
That is easy to understand.

For magrittr the answer is "Well, it depends, let me see your RHS
expression, is it wrapped in braces? If not, are you using the placeholder?
If you are using the placeholder, where/how are you using it?".

That is inherently much more complicated. Yes, you understand how the
magrittr pipe behaves, and yes you find it very convenient. Thats great,
but neither of those things equate to simplicity. They just mean that you,
a very experienced pipe user, carry around the cognitive load necessary to
have that understanding.

More concretely, the current base pipe  is extremely simple, all it does i


   1. Figure out RHS exprssion call
 1. If RHS is an anonymous function declaration, construct a call
 to it for a new RHS
  2. Insert LHS expression into first argument position of RHS call
  expression


Done. And (1) would be removed if anonymous functions required () after
them, which would be consistent, and even simpler, but kind of annoying. I
think it is a good compromise which is guaranteed to be safe because
anonymous functions are something the parser recognizes.  Either way, if
that was dropped, what |> does would be *entirely* trivial to understand
and explain. With a single sentence.

I had the equivalent pseudocode for the magrittr pipe written out here but
honestly felt like overkill that came across as mean, so I'll leave that as
an exercise to interested readers.

~G

> Assuming the existence of placeholders a possible simplification would
> be to NOT do automatic insertion if { ... } is used and to use it
> otherwise although personally having used it for some time I find the
> existing rule in magrittr generally does what you want.
>
> __
> 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


Re: [Rd] New pipe operator

2020-12-07 Thread Gabor Grothendieck
On Mon, Dec 7, 2020 at 2:02 PM Kevin Ushey  wrote:
>
> IMHO the use of anonymous functions is a very clean solution to the
> placeholder problem, and the shorthand lambda syntax makes it much
> more ergonomic to use. Pipe implementations that crawl the RHS for
> usages of `.` are going to be more expensive than the alternatives. It

You wouldn't have to crawl the expression.  This does it at the syntax level.

  e <- quote( { gsub("x", "y", .) } )
  c(e[[1]], quote(. <- LHS), e[-1])

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


Re: [Rd] New pipe operator

2020-12-07 Thread Kevin Ushey
IMHO the use of anonymous functions is a very clean solution to the
placeholder problem, and the shorthand lambda syntax makes it much
more ergonomic to use. Pipe implementations that crawl the RHS for
usages of `.` are going to be more expensive than the alternatives. It
is nice that the `|>` operator is effectively the same as a regular R
function call, and given the identical semantics could then also be
reasoned about the same way regular R function calls are.

I also agree usages of the `.` placeholder can make the code more
challenging to read, since understanding the behavior of a piped
expression then requires scouring the RHS for usages of `.`, which can
be challenging in dense code. Piping to an anonymous function makes
the intent clear to the reader: the programmer is likely piping to an
anonymous function because they care where the argument is used in the
call, and so the reader of code should be aware of that.

Best,
Kevin



On Mon, Dec 7, 2020 at 10:35 AM Gabor Grothendieck
 wrote:
>
> On Mon, Dec 7, 2020 at 12:54 PM Duncan Murdoch  
> wrote:
> > An advantage of the current implementation is that it's simple and easy
> > to understand.  Once you make it a user-modifiable binary operator,
> > things will go kind of nuts.
> >
> > For example, I doubt if there are many users of magrittr's pipe who
> > really understand its subtleties, e.g. the example in Luke's paper where
> > 1 %>% c(., 2) gives c(1,2), but 1 %>% c(c(.), 2) gives c(1, 1, 2). (And
> > I could add 1 %>% c(c(.), 2, .) and  1 %>% c(c(.), 2, . + 2)  to
> > continue the fun.)
>
> The rule is not so complicated.  Automatic insertion is done unless
> you use dot in the top level function or if you surround it with
> {...}.  It really makes sense since if you use gsub(pattern,
> replacement, .) then surely you don't want automatic insertion and if
> you surround it with { ... } then you are explicitly telling it not
> to.
>
> Assuming the existence of placeholders a possible simplification would
> be to NOT do automatic insertion if { ... } is used and to use it
> otherwise although personally having used it for some time I find the
> existing rule in magrittr generally does what you want.
>
> __
> R-devel@r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-devel

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


Re: [Rd] New pipe operator

2020-12-07 Thread Gabor Grothendieck
On Mon, Dec 7, 2020 at 12:54 PM Duncan Murdoch  wrote:
> An advantage of the current implementation is that it's simple and easy
> to understand.  Once you make it a user-modifiable binary operator,
> things will go kind of nuts.
>
> For example, I doubt if there are many users of magrittr's pipe who
> really understand its subtleties, e.g. the example in Luke's paper where
> 1 %>% c(., 2) gives c(1,2), but 1 %>% c(c(.), 2) gives c(1, 1, 2). (And
> I could add 1 %>% c(c(.), 2, .) and  1 %>% c(c(.), 2, . + 2)  to
> continue the fun.)

The rule is not so complicated.  Automatic insertion is done unless
you use dot in the top level function or if you surround it with
{...}.  It really makes sense since if you use gsub(pattern,
replacement, .) then surely you don't want automatic insertion and if
you surround it with { ... } then you are explicitly telling it not
to.

Assuming the existence of placeholders a possible simplification would
be to NOT do automatic insertion if { ... } is used and to use it
otherwise although personally having used it for some time I find the
existing rule in magrittr generally does what you want.

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


Re: [Rd] New pipe operator

2020-12-07 Thread Duncan Murdoch

On 07/12/2020 12:09 p.m., Peter Dalgaard wrote:




On 7 Dec 2020, at 17:35 , Duncan Murdoch  wrote:

On 07/12/2020 11:18 a.m., peter dalgaard wrote:

Hmm,
I feel a bit bad coming late to this, but I think I am beginning to side with those who want  
"... |> head" to work. And yes, that has to happen at the expense of |> head().


Just curious, how would you express head(df, 10)?  Currently it is

df |> head(10)

Would I have to write it as

df |> function(d) head(d, 10)


It could be

df |> ~ head(_, 10)

which in a sense is "yes" to your question.


I think that's doing too much weird stuff.  I wouldn't want to have to 
teach it to beginners, whereas I think I could teach "df |> head(10)". 
That's doing one weird thing, but I'd count about three things I'd 
consider weird in yours.








As I think it was Gabor points out, the current structure goes down a 
nonstandard evaluation route, which may be difficult to explain and departs 
from usual operator evaluation paradigms by being an odd mix of syntax and 
semantics. R lets you do these sorts of thing, witness ggplot and tidyverse, 
but the transparency of the language tends to suffer.


I wouldn't call it non-standard evaluation.  There is no function corresponding to |>, so there's no evaluation at 
all.  It is more like the way "x -> y" is parsed as "y <- x", or "if (x) y" is 
transformed to `if`(x, y).


That's a point, but maybe also my point. Currently, the parser is inserting the 
LHS as the 1st argument of the RHS, right? Things might be simpler if it was 
more like a simple binop.


An advantage of the current implementation is that it's simple and easy 
to understand.  Once you make it a user-modifiable binary operator, 
things will go kind of nuts.


For example, I doubt if there are many users of magrittr's pipe who 
really understand its subtleties, e.g. the example in Luke's paper where 
1 %>% c(., 2) gives c(1,2), but 1 %>% c(c(.), 2) gives c(1, 1, 2). (And 
I could add 1 %>% c(c(.), 2, .) and  1 %>% c(c(.), 2, . + 2)  to 
continue the fun.)


Duncan Murdoch




-pd


Duncan Murdoch


It would be neater if it was simply so that the class/type of the object on the 
right hand side decided what should happen. So we could have a rule that we 
could have an object, an expression, and possibly an unevaluated call on the 
RHS. Or maybe a formula, I.e., we could hav
... |> head
but not
... |> head()
because head() does not evaluate to anything useful. Instead, we could have 
some of these
... |> quote(head())
... |> expression(head())
... |> ~ head()
... |> \(_) head(_)
possibly also using a placeholder mechanism for the three first ones. I kind of 
like the idea that the ~ could be equivalent to \(_).
(And yes, I am kicking myself a bit for not using ~ in the NSE arguments in 
subset() and transform())
-pd

On 7 Dec 2020, at 16:20 , Deepayan Sarkar  wrote:

On Mon, Dec 7, 2020 at 6:53 PM Gabor Grothendieck
 wrote:


On Mon, Dec 7, 2020 at 5:41 AM Duncan Murdoch  wrote:

I agree it's all about call expressions, but they aren't all being
treated equally:

x |> f(...)

expands to f(x, ...), while

x |> `function`(...)

expands to `function`(...)(x).  This is an exception to the rule for
other calls, but I think it's a justified one.


This admitted inconsistency is justified by what?  No argument has been
presented.  The justification seems to be implicitly driven by implementation
concerns at the expense of usability and language consistency.


Sorry if I have missed something, but is your consistency argument
basically that if

foo <- function(x) x + 1

then

x |> foo
x |> function(x) x + 1

should both work the same? Suppose it did. Would you then be OK if

x |> foo()

no longer worked as it does now, and produced foo()(x) instead of foo(x)?

If you are not OK with that and want to retain the current behaviour,
what would you want to happen with the following?

bar <- function(x) function(n) rnorm(n, mean = x)

10 |> bar(runif(1))() # works 'as expected' ~ bar(runif(1))(10)
10 |> bar(runif(1)) # currently bar(10, runif(1))

both of which you probably want. But then

baz <-  bar(runif(1))
10 |> baz

(not currently allowed) will not be the same as what you would want from

10 |> bar(runif(1))

which leads to a different kind of inconsistency, doesn't it?

-Deepayan

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






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


Re: [Rd] New pipe operator

2020-12-07 Thread Peter Dalgaard



> On 7 Dec 2020, at 17:35 , Duncan Murdoch  wrote:
> 
> On 07/12/2020 11:18 a.m., peter dalgaard wrote:
>> Hmm,
>> I feel a bit bad coming late to this, but I think I am beginning to side 
>> with those who want  "... |> head" to work. And yes, that has to happen at 
>> the expense of |> head().
> 
> Just curious, how would you express head(df, 10)?  Currently it is
> 
> df |> head(10)
> 
> Would I have to write it as
> 
> df |> function(d) head(d, 10)

It could be 

df |> ~ head(_, 10)

which in a sense is "yes" to your question.

> 
>> As I think it was Gabor points out, the current structure goes down a 
>> nonstandard evaluation route, which may be difficult to explain and departs 
>> from usual operator evaluation paradigms by being an odd mix of syntax and 
>> semantics. R lets you do these sorts of thing, witness ggplot and tidyverse, 
>> but the transparency of the language tends to suffer.
> 
> I wouldn't call it non-standard evaluation.  There is no function 
> corresponding to |>, so there's no evaluation at all.  It is more like the 
> way "x -> y" is parsed as "y <- x", or "if (x) y" is transformed to `if`(x, 
> y).

That's a point, but maybe also my point. Currently, the parser is inserting the 
LHS as the 1st argument of the RHS, right? Things might be simpler if it was 
more like a simple binop.

-pd

> Duncan Murdoch
> 
>> It would be neater if it was simply so that the class/type of the object on 
>> the right hand side decided what should happen. So we could have a rule that 
>> we could have an object, an expression, and possibly an unevaluated call on 
>> the RHS. Or maybe a formula, I.e., we could hav
>> ... |> head
>> but not
>> ... |> head()
>> because head() does not evaluate to anything useful. Instead, we could have 
>> some of these
>> ... |> quote(head())
>> ... |> expression(head())
>> ... |> ~ head()
>> ... |> \(_) head(_)
>> possibly also using a placeholder mechanism for the three first ones. I kind 
>> of like the idea that the ~ could be equivalent to \(_).
>> (And yes, I am kicking myself a bit for not using ~ in the NSE arguments in 
>> subset() and transform())
>> -pd
>>> On 7 Dec 2020, at 16:20 , Deepayan Sarkar  wrote:
>>> 
>>> On Mon, Dec 7, 2020 at 6:53 PM Gabor Grothendieck
>>>  wrote:
 
 On Mon, Dec 7, 2020 at 5:41 AM Duncan Murdoch  
 wrote:
> I agree it's all about call expressions, but they aren't all being
> treated equally:
> 
> x |> f(...)
> 
> expands to f(x, ...), while
> 
> x |> `function`(...)
> 
> expands to `function`(...)(x).  This is an exception to the rule for
> other calls, but I think it's a justified one.
 
 This admitted inconsistency is justified by what?  No argument has been
 presented.  The justification seems to be implicitly driven by 
 implementation
 concerns at the expense of usability and language consistency.
>>> 
>>> Sorry if I have missed something, but is your consistency argument
>>> basically that if
>>> 
>>> foo <- function(x) x + 1
>>> 
>>> then
>>> 
>>> x |> foo
>>> x |> function(x) x + 1
>>> 
>>> should both work the same? Suppose it did. Would you then be OK if
>>> 
>>> x |> foo()
>>> 
>>> no longer worked as it does now, and produced foo()(x) instead of foo(x)?
>>> 
>>> If you are not OK with that and want to retain the current behaviour,
>>> what would you want to happen with the following?
>>> 
>>> bar <- function(x) function(n) rnorm(n, mean = x)
>>> 
>>> 10 |> bar(runif(1))() # works 'as expected' ~ bar(runif(1))(10)
>>> 10 |> bar(runif(1)) # currently bar(10, runif(1))
>>> 
>>> both of which you probably want. But then
>>> 
>>> baz <-  bar(runif(1))
>>> 10 |> baz
>>> 
>>> (not currently allowed) will not be the same as what you would want from
>>> 
>>> 10 |> bar(runif(1))
>>> 
>>> which leads to a different kind of inconsistency, doesn't it?
>>> 
>>> -Deepayan
>>> 
>>> __
>>> R-devel@r-project.org mailing list
>>> https://stat.ethz.ch/mailman/listinfo/r-devel
> 

-- 
Peter Dalgaard, Professor,
Center for Statistics, Copenhagen Business School
Solbjerg Plads 3, 2000 Frederiksberg, Denmark
Phone: (+45)38153501
Office: A 4.23
Email: pd@cbs.dk  Priv: pda...@gmail.com

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


Re: [Rd] New pipe operator

2020-12-07 Thread Duncan Murdoch

On 07/12/2020 11:18 a.m., peter dalgaard wrote:

Hmm,

I feel a bit bad coming late to this, but I think I am beginning to side with those who want  
"... |> head" to work. And yes, that has to happen at the expense of |> head().


Just curious, how would you express head(df, 10)?  Currently it is

 df |> head(10)

Would I have to write it as

 df |> function(d) head(d, 10)



As I think it was Gabor points out, the current structure goes down a 
nonstandard evaluation route, which may be difficult to explain and departs 
from usual operator evaluation paradigms by being an odd mix of syntax and 
semantics. R lets you do these sorts of thing, witness ggplot and tidyverse, 
but the transparency of the language tends to suffer.


I wouldn't call it non-standard evaluation.  There is no function 
corresponding to |>, so there's no evaluation at all.  It is more like 
the way "x -> y" is parsed as "y <- x", or "if (x) y" is transformed to 
`if`(x, y).


Duncan Murdoch


It would be neater if it was simply so that the class/type of the object on the 
right hand side decided what should happen. So we could have a rule that we 
could have an object, an expression, and possibly an unevaluated call on the 
RHS. Or maybe a formula, I.e., we could hav

... |> head

but not

... |> head()

because head() does not evaluate to anything useful. Instead, we could have 
some of these

... |> quote(head())
... |> expression(head())
... |> ~ head()
... |> \(_) head(_)

possibly also using a placeholder mechanism for the three first ones. I kind of 
like the idea that the ~ could be equivalent to \(_).

(And yes, I am kicking myself a bit for not using ~ in the NSE arguments in 
subset() and transform())

-pd


On 7 Dec 2020, at 16:20 , Deepayan Sarkar  wrote:

On Mon, Dec 7, 2020 at 6:53 PM Gabor Grothendieck
 wrote:


On Mon, Dec 7, 2020 at 5:41 AM Duncan Murdoch  wrote:

I agree it's all about call expressions, but they aren't all being
treated equally:

x |> f(...)

expands to f(x, ...), while

x |> `function`(...)

expands to `function`(...)(x).  This is an exception to the rule for
other calls, but I think it's a justified one.


This admitted inconsistency is justified by what?  No argument has been
presented.  The justification seems to be implicitly driven by implementation
concerns at the expense of usability and language consistency.


Sorry if I have missed something, but is your consistency argument
basically that if

foo <- function(x) x + 1

then

x |> foo
x |> function(x) x + 1

should both work the same? Suppose it did. Would you then be OK if

x |> foo()

no longer worked as it does now, and produced foo()(x) instead of foo(x)?

If you are not OK with that and want to retain the current behaviour,
what would you want to happen with the following?

bar <- function(x) function(n) rnorm(n, mean = x)

10 |> bar(runif(1))() # works 'as expected' ~ bar(runif(1))(10)
10 |> bar(runif(1)) # currently bar(10, runif(1))

both of which you probably want. But then

baz <-  bar(runif(1))
10 |> baz

(not currently allowed) will not be the same as what you would want from

10 |> bar(runif(1))

which leads to a different kind of inconsistency, doesn't it?

-Deepayan

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




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


Re: [Rd] New pipe operator

2020-12-07 Thread peter dalgaard
Hmm,

I feel a bit bad coming late to this, but I think I am beginning to side with 
those who want  "... |> head" to work. And yes, that has to happen at the 
expense of |> head().

As I think it was Gabor points out, the current structure goes down a 
nonstandard evaluation route, which may be difficult to explain and departs 
from usual operator evaluation paradigms by being an odd mix of syntax and 
semantics. R lets you do these sorts of thing, witness ggplot and tidyverse, 
but the transparency of the language tends to suffer. 

It would be neater if it was simply so that the class/type of the object on the 
right hand side decided what should happen. So we could have a rule that we 
could have an object, an expression, and possibly an unevaluated call on the 
RHS. Or maybe a formula, I.e., we could have

... |> head

but not  

... |> head() 

because head() does not evaluate to anything useful. Instead, we could have 
some of these

... |> quote(head())
... |> expression(head())
... |> ~ head()
... |> \(_) head(_)

possibly also using a placeholder mechanism for the three first ones. I kind of 
like the idea that the ~ could be equivalent to \(_).

(And yes, I am kicking myself a bit for not using ~ in the NSE arguments in 
subset() and transform())

-pd

> On 7 Dec 2020, at 16:20 , Deepayan Sarkar  wrote:
> 
> On Mon, Dec 7, 2020 at 6:53 PM Gabor Grothendieck
>  wrote:
>> 
>> On Mon, Dec 7, 2020 at 5:41 AM Duncan Murdoch  
>> wrote:
>>> I agree it's all about call expressions, but they aren't all being
>>> treated equally:
>>> 
>>> x |> f(...)
>>> 
>>> expands to f(x, ...), while
>>> 
>>> x |> `function`(...)
>>> 
>>> expands to `function`(...)(x).  This is an exception to the rule for
>>> other calls, but I think it's a justified one.
>> 
>> This admitted inconsistency is justified by what?  No argument has been
>> presented.  The justification seems to be implicitly driven by implementation
>> concerns at the expense of usability and language consistency.
> 
> Sorry if I have missed something, but is your consistency argument
> basically that if
> 
> foo <- function(x) x + 1
> 
> then
> 
> x |> foo
> x |> function(x) x + 1
> 
> should both work the same? Suppose it did. Would you then be OK if
> 
> x |> foo()
> 
> no longer worked as it does now, and produced foo()(x) instead of foo(x)?
> 
> If you are not OK with that and want to retain the current behaviour,
> what would you want to happen with the following?
> 
> bar <- function(x) function(n) rnorm(n, mean = x)
> 
> 10 |> bar(runif(1))() # works 'as expected' ~ bar(runif(1))(10)
> 10 |> bar(runif(1)) # currently bar(10, runif(1))
> 
> both of which you probably want. But then
> 
> baz <-  bar(runif(1))
> 10 |> baz
> 
> (not currently allowed) will not be the same as what you would want from
> 
> 10 |> bar(runif(1))
> 
> which leads to a different kind of inconsistency, doesn't it?
> 
> -Deepayan
> 
> __
> R-devel@r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-devel

-- 
Peter Dalgaard, Professor,
Center for Statistics, Copenhagen Business School
Solbjerg Plads 3, 2000 Frederiksberg, Denmark
Phone: (+45)38153501
Office: A 4.23
Email: pd@cbs.dk  Priv: pda...@gmail.com

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


Re: [Rd] New pipe operator

2020-12-07 Thread Deepayan Sarkar
On Mon, Dec 7, 2020 at 9:23 PM Gabor Grothendieck
 wrote:
>
> One could examine how magrittr works as a reference implementation if
> there is a question on how something should function.  It's in
> widespread use and seems to work well.

Yes, but it has many inconsistencies (including for the example I
gave). Do you want a magrittr clone, or do you want consistency? It's
OK to want either, but I don't think you can get both.

What we actually end up with is another matter, depending on many
other factors. I was just trying to understand your consistency
argument.

-Deepayan

> On Mon, Dec 7, 2020 at 10:20 AM Deepayan Sarkar
>  wrote:
> >
> > On Mon, Dec 7, 2020 at 6:53 PM Gabor Grothendieck
> >  wrote:
> > >
> > > On Mon, Dec 7, 2020 at 5:41 AM Duncan Murdoch  
> > > wrote:
> > > > I agree it's all about call expressions, but they aren't all being
> > > > treated equally:
> > > >
> > > > x |> f(...)
> > > >
> > > > expands to f(x, ...), while
> > > >
> > > > x |> `function`(...)
> > > >
> > > > expands to `function`(...)(x).  This is an exception to the rule for
> > > > other calls, but I think it's a justified one.
> > >
> > > This admitted inconsistency is justified by what?  No argument has been
> > > presented.  The justification seems to be implicitly driven by 
> > > implementation
> > > concerns at the expense of usability and language consistency.
> >
> > Sorry if I have missed something, but is your consistency argument
> > basically that if
> >
> > foo <- function(x) x + 1
> >
> > then
> >
> > x |> foo
> > x |> function(x) x + 1
> >
> > should both work the same? Suppose it did. Would you then be OK if
> >
> > x |> foo()
> >
> > no longer worked as it does now, and produced foo()(x) instead of foo(x)?
> >
> > If you are not OK with that and want to retain the current behaviour,
> > what would you want to happen with the following?
> >
> > bar <- function(x) function(n) rnorm(n, mean = x)
> >
> > 10 |> bar(runif(1))() # works 'as expected' ~ bar(runif(1))(10)
> > 10 |> bar(runif(1)) # currently bar(10, runif(1))
> >
> > both of which you probably want. But then
> >
> > baz <-  bar(runif(1))
> > 10 |> baz
> >
> > (not currently allowed) will not be the same as what you would want from
> >
> > 10 |> bar(runif(1))
> >
> > which leads to a different kind of inconsistency, doesn't it?
> >
> > -Deepayan
>
>
>
> --
> Statistics & Software Consulting
> GKX Group, GKX Associates Inc.
> tel: 1-877-GKX-GROUP
> email: ggrothendieck at gmail.com

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


Re: [Rd] New pipe operator

2020-12-07 Thread Gabor Grothendieck
One could examine how magrittr works as a reference implementation if
there is a question on how something should function.  It's in
widespread use and seems to work well.

On Mon, Dec 7, 2020 at 10:20 AM Deepayan Sarkar
 wrote:
>
> On Mon, Dec 7, 2020 at 6:53 PM Gabor Grothendieck
>  wrote:
> >
> > On Mon, Dec 7, 2020 at 5:41 AM Duncan Murdoch  
> > wrote:
> > > I agree it's all about call expressions, but they aren't all being
> > > treated equally:
> > >
> > > x |> f(...)
> > >
> > > expands to f(x, ...), while
> > >
> > > x |> `function`(...)
> > >
> > > expands to `function`(...)(x).  This is an exception to the rule for
> > > other calls, but I think it's a justified one.
> >
> > This admitted inconsistency is justified by what?  No argument has been
> > presented.  The justification seems to be implicitly driven by 
> > implementation
> > concerns at the expense of usability and language consistency.
>
> Sorry if I have missed something, but is your consistency argument
> basically that if
>
> foo <- function(x) x + 1
>
> then
>
> x |> foo
> x |> function(x) x + 1
>
> should both work the same? Suppose it did. Would you then be OK if
>
> x |> foo()
>
> no longer worked as it does now, and produced foo()(x) instead of foo(x)?
>
> If you are not OK with that and want to retain the current behaviour,
> what would you want to happen with the following?
>
> bar <- function(x) function(n) rnorm(n, mean = x)
>
> 10 |> bar(runif(1))() # works 'as expected' ~ bar(runif(1))(10)
> 10 |> bar(runif(1)) # currently bar(10, runif(1))
>
> both of which you probably want. But then
>
> baz <-  bar(runif(1))
> 10 |> baz
>
> (not currently allowed) will not be the same as what you would want from
>
> 10 |> bar(runif(1))
>
> which leads to a different kind of inconsistency, doesn't it?
>
> -Deepayan



-- 
Statistics & Software Consulting
GKX Group, GKX Associates Inc.
tel: 1-877-GKX-GROUP
email: ggrothendieck at gmail.com

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


Re: [Rd] New pipe operator

2020-12-07 Thread Deepayan Sarkar
On Mon, Dec 7, 2020 at 6:53 PM Gabor Grothendieck
 wrote:
>
> On Mon, Dec 7, 2020 at 5:41 AM Duncan Murdoch  
> wrote:
> > I agree it's all about call expressions, but they aren't all being
> > treated equally:
> >
> > x |> f(...)
> >
> > expands to f(x, ...), while
> >
> > x |> `function`(...)
> >
> > expands to `function`(...)(x).  This is an exception to the rule for
> > other calls, but I think it's a justified one.
>
> This admitted inconsistency is justified by what?  No argument has been
> presented.  The justification seems to be implicitly driven by implementation
> concerns at the expense of usability and language consistency.

Sorry if I have missed something, but is your consistency argument
basically that if

foo <- function(x) x + 1

then

x |> foo
x |> function(x) x + 1

should both work the same? Suppose it did. Would you then be OK if

x |> foo()

no longer worked as it does now, and produced foo()(x) instead of foo(x)?

If you are not OK with that and want to retain the current behaviour,
what would you want to happen with the following?

bar <- function(x) function(n) rnorm(n, mean = x)

10 |> bar(runif(1))() # works 'as expected' ~ bar(runif(1))(10)
10 |> bar(runif(1)) # currently bar(10, runif(1))

both of which you probably want. But then

baz <-  bar(runif(1))
10 |> baz

(not currently allowed) will not be the same as what you would want from

10 |> bar(runif(1))

which leads to a different kind of inconsistency, doesn't it?

-Deepayan

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


Re: [Rd] New pipe operator

2020-12-07 Thread Gabor Grothendieck
On Mon, Dec 7, 2020 at 5:41 AM Duncan Murdoch  wrote:
> I agree it's all about call expressions, but they aren't all being
> treated equally:
>
> x |> f(...)
>
> expands to f(x, ...), while
>
> x |> `function`(...)
>
> expands to `function`(...)(x).  This is an exception to the rule for
> other calls, but I think it's a justified one.

This admitted inconsistency is justified by what?  No argument has been
presented.  The justification seems to be implicitly driven by implementation
concerns at the expense of usability and language consistency.

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


Re: [Rd] New pipe operator

2020-12-07 Thread Duncan Murdoch

On 06/12/2020 9:23 p.m., Gabriel Becker wrote:

Hi Gabor,

On Sun, Dec 6, 2020 at 3:22 PM Gabor Grothendieck 
wrote:


I understand very well that it is implemented at the syntax level;
however, in any case the implementation is irrelevant to the principles.

Here a similar example to the one I gave before but this time written out:

This works:

   3 |> function(x) x + 1

but this does not:

   foo <- function(x) x + 1
   3 |> foo

so it breaks the principle of functions being first class objects.  foo
and its
definition are not interchangeable.



I understood what you meant as well.

The issue is that neither foo nor its definition are being operated on, or
even exist within the scope of what |> is defined to do. You are used to
magrittr's %>% where arguably what you are saying would be true. But its
not here, in my view.

Again, I think the issue is that |>, in as much as it "operates" on
anything at all (it not being a function, regardless of appearances),
operates on call expression objects, NOT on functions, ever.

function(x) x *parses to a call expression *as does RHSfun(), while RHSfun does
not, it parses to a name, *regardless of whether that symbol will
eventually evaluate to a closure or not.*

So in fact, it seems to me that, technically, all name symbols are being
treated exactly the same (none are allowed, including those which will
lookup to functions during evaluation), while all* call expressions are
also being treated the same. And again, there are no functions anywhere in
either case.


I agree it's all about call expressions, but they aren't all being 
treated equally:


x |> f(...)

expands to f(x, ...), while

x |> `function`(...)

expands to `function`(...)(x).  This is an exception to the rule for 
other calls, but I think it's a justified one.


Duncan Murdoch



* except those that include that the parser flags as syntactically special.



You have
to write 3 |> foo() but don't have to write 3 |> (function(x) x + 1)().



I think you should probably be careful what you wish for here. I'm not
involved with this work and do not speak for any of those who were, but the
principled way to make that consistent while remaining entirely in the
parser seems very likely to be to require the latter, rather than not
require the former.



This isn't just a matter of notation, i.e. foo vs foo(), but is a
matter of breaking
the way R works as a functional language with first class functions.



I don't agree. Consider `+`

Having

foo <- get("+") ## note no `` here
foo(x,y)

parse and work correctly while

+(x,y)

  does not does not mean + isn't a function or that it is a "second class
citizen", it simply means that the parser has constraints on the syntax for
writing code that calls it that calling other functions are not subject to.
The fact that such *syntactic* constraints can exist proves that there is
not some overarching inviolable principle being violated here, I think. Now
you may say "well thats just the parser, it has to parse + specially
because its an operator with specific precedence etc". Well, the same exact
thing is true of |> I think.

Best,
~G



On Sun, Dec 6, 2020 at 4:06 PM Gabriel Becker 
wrote:


Hi Gabor,

On Sun, Dec 6, 2020 at 12:52 PM Gabor Grothendieck <

ggrothendi...@gmail.com> wrote:


I think the real issue here is that functions are supposed to be
first class objects in R
or are supposed to be and |> would break that if if is possible
to write function(x) x + 1 on the RHS but not foo (assuming foo
was defined as that function).

I don't think getting experience with using it can change that
inconsistency which seems serious to me and needs to
be addressed even if it complicates the implementation
since it drives to the heart of what R is.



With respect I think this is a misunderstanding of what is happening

here.


Functions are first class citizens. |> is, for all intents and purposes,

a macro.


LHS |> RHS(arg2=5)

parses to

RHS(LHS, arg2 = 5)

There are no functions at the point in time when the pipe transformation

happens, because no code has been evaluated. To know if a symbol is going
to evaluate to a function requires evaluation which is a step entirely
after the one where the |> pipe is implemented.


Another way to think about it is that

LHS |> RHS(arg2 = 5)

is another way of writing RHS(LHS, arg2 = 5), NOT R code that is (or

even can be) evaluated.



Now this is a subtle point that only really has implications in as much

as it is not the case for magrittr pipes, but its relevant for discussions
like this, I think.


~G


On Sat, Dec 5, 2020 at 1:08 PM Gabor Grothendieck
 wrote:


The construct utils::head  is not that common but bare functions are
very common and to make it harder to use the common case so that
the uncommon case is slightly easier is not desirable.

Also it is trivial to write this which does work:

mtcars %>% (utils::head)

On Sat, Dec 5, 2020 at 11:59 AM Hugh Parsonage <

hugh.parson...@gmail.com> wrote:


I'm 

Re: [Rd] New pipe operator

2020-12-07 Thread Duncan Murdoch
-is, this is just to point out that it could be done in standard R.


`_ANON_` <- function( expr) {
   #1. Construct a function with arg '_PIPE_' and body 'expr'
   #2. Construct a call() to that function
   #3. Do the call

   f <- function( `_PIPE_`) NULL
   body( f) <- expr
   environment( f) <- parent.frame() # or something... yes these details are 
almost certainly wrong
   expr2 <- substitute( f( `_PIPE_`)) # or something...
   eval.parent( expr2) # or something...
}

cheers
Mark

Mark Bravington
CSIRO Marine Lab
Hobart
Australia


________
From: R-devel  on behalf of Gabor Grothendieck 

Sent: Monday, 7 December 2020 10:21
To: Gabriel Becker
Cc: r-devel@r-project.org
Subject: Re: [Rd] New pipe operator

I understand very well that it is implemented at the syntax level;
however, in any case the implementation is irrelevant to the principles.

Here a similar example to the one I gave before but this time written out:

This works:

   3 |> function(x) x + 1

but this does not:

   foo <- function(x) x + 1
   3 |> foo

so it breaks the principle of functions being first class objects.  foo and its
definition are not interchangeable.  You have
to write 3 |> foo() but don't have to write 3 |> (function(x) x + 1)().

This isn't just a matter of notation, i.e. foo vs foo(), but is a
matter of breaking
the way R works as a functional language with first class functions.

On Sun, Dec 6, 2020 at 4:06 PM Gabriel Becker  wrote:


Hi Gabor,

On Sun, Dec 6, 2020 at 12:52 PM Gabor Grothendieck  
wrote:


I think the real issue here is that functions are supposed to be
first class objects in R
or are supposed to be and |> would break that if if is possible
to write function(x) x + 1 on the RHS but not foo (assuming foo
was defined as that function).

I don't think getting experience with using it can change that
inconsistency which seems serious to me and needs to
be addressed even if it complicates the implementation
since it drives to the heart of what R is.



With respect I think this is a misunderstanding of what is happening here.

Functions are first class citizens. |> is, for all intents and purposes, a 
macro.

LHS |> RHS(arg2=5)

parses to

RHS(LHS, arg2 = 5)

There are no functions at the point in time when the pipe transformation happens, 
because no code has been evaluated. To know if a symbol is going to evaluate to a 
function requires evaluation which is a step entirely after the one where the 
|> pipe is implemented.

Another way to think about it is that

LHS |> RHS(arg2 = 5)

is another way of writing RHS(LHS, arg2 = 5), NOT R code that is (or even can 
be) evaluated.


Now this is a subtle point that only really has implications in as much as it 
is not the case for magrittr pipes, but its relevant for discussions like this, 
I think.

~G


On Sat, Dec 5, 2020 at 1:08 PM Gabor Grothendieck
 wrote:


The construct utils::head  is not that common but bare functions are
very common and to make it harder to use the common case so that
the uncommon case is slightly easier is not desirable.

Also it is trivial to write this which does work:

mtcars %>% (utils::head)

On Sat, Dec 5, 2020 at 11:59 AM Hugh Parsonage  wrote:


I'm surprised by the aversion to

mtcars |> nrow

over

mtcars |> nrow()

and I think the decision to disallow the former should be
reconsidered.  The pipe operator is only going to be used when the rhs
is a function, so there is no ambiguity with omitting the parentheses.
If it's disallowed, it becomes inconsistent with other treatments like
sapply(mtcars, typeof) where sapply(mtcars, typeof()) would just be
noise.  I'm not sure why this decision was taken

If the only issue is with the double (and triple) colon operator, then
ideally `mtcars |> base::head` should resolve to `base::head(mtcars)`
-- in other words, demote the precedence of |>

Obviously (looking at the R-Syntax branch) this decision was
considered, put into place, then dropped, but I can't see why
precisely.

Best,


Hugh.







On Sat, 5 Dec 2020 at 04:07, Deepayan Sarkar  wrote:


On Fri, Dec 4, 2020 at 7:35 PM Duncan Murdoch  wrote:


On 04/12/2020 8:13 a.m., Hiroaki Yutani wrote:

   Error: function '::' not supported in RHS call of a pipe


To me, this error looks much more friendly than magrittr's error.
Some of them got too used to specify functions without (). This
is OK until they use `::`, but when they need to use it, it takes
hours to figure out why

mtcars %>% base::head
#> Error in .::base : unused argument (head)

won't work but

mtcars %>% head

works. I think this is a too harsh lesson for ordinary R users to
learn `::` is a function. I've been wanting for magrittr to drop the
support for a function name without () to avoid this confusion,
so I would very much welcome the new pipe operator's behavior.
Thank you all the developers who implemented this!


I agree, it's an improvement on the corresponding 

Re: [Rd] New pipe operator

2020-12-06 Thread Gabor Grothendieck
This is really irrelevant.

On Sun, Dec 6, 2020 at 9:23 PM Gabriel Becker  wrote:
>
> Hi Gabor,
>
> On Sun, Dec 6, 2020 at 3:22 PM Gabor Grothendieck  
> wrote:
>>
>> I understand very well that it is implemented at the syntax level;
>> however, in any case the implementation is irrelevant to the principles.
>>
>> Here a similar example to the one I gave before but this time written out:
>>
>> This works:
>>
>>   3 |> function(x) x + 1
>>
>> but this does not:
>>
>>   foo <- function(x) x + 1
>>   3 |> foo
>>
>> so it breaks the principle of functions being first class objects.  foo and 
>> its
>> definition are not interchangeable.
>
>
> I understood what you meant as well.
>
> The issue is that neither foo nor its definition are being operated on, or 
> even exist within the scope of what |> is defined to do. You are used to 
> magrittr's %>% where arguably what you are saying would be true. But its not 
> here, in my view.
>
> Again, I think the issue is that |>, in as much as it "operates" on anything 
> at all (it not being a function, regardless of appearances), operates on call 
> expression objects, NOT on functions, ever.
>
> function(x) x parses to a call expression as does RHSfun(), while RHSfun does 
> not, it parses to a name, regardless of whether that symbol will eventually 
> evaluate to a closure or not.
>
> So in fact, it seems to me that, technically, all name symbols are being 
> treated exactly the same (none are allowed, including those which will lookup 
> to functions during evaluation), while all* call expressions are also being 
> treated the same. And again, there are no functions anywhere in either case.
>
> * except those that include that the parser flags as syntactically special.
>
>>
>> You have
>> to write 3 |> foo() but don't have to write 3 |> (function(x) x + 1)().
>
>
> I think you should probably be careful what you wish for here. I'm not 
> involved with this work and do not speak for any of those who were, but the 
> principled way to make that consistent while remaining entirely in the parser 
> seems very likely to be to require the latter, rather than not require the 
> former.
>
>>
>> This isn't just a matter of notation, i.e. foo vs foo(), but is a
>> matter of breaking
>> the way R works as a functional language with first class functions.
>
>
> I don't agree. Consider `+`
>
> Having
>
> foo <- get("+") ## note no `` here
> foo(x,y)
>
> parse and work correctly while
>
> +(x,y)
>
>  does not does not mean + isn't a function or that it is a "second class 
> citizen", it simply means that the parser has constraints on the syntax for 
> writing code that calls it that calling other functions are not subject to. 
> The fact that such syntactic constraints can exist proves that there is not 
> some overarching inviolable principle being violated here, I think. Now you 
> may say "well thats just the parser, it has to parse + specially because its 
> an operator with specific precedence etc". Well, the same exact thing is true 
> of |> I think.
>
> Best,
> ~G
>>
>>
>> On Sun, Dec 6, 2020 at 4:06 PM Gabriel Becker  wrote:
>> >
>> > Hi Gabor,
>> >
>> > On Sun, Dec 6, 2020 at 12:52 PM Gabor Grothendieck 
>> >  wrote:
>> >>
>> >> I think the real issue here is that functions are supposed to be
>> >> first class objects in R
>> >> or are supposed to be and |> would break that if if is possible
>> >> to write function(x) x + 1 on the RHS but not foo (assuming foo
>> >> was defined as that function).
>> >>
>> >> I don't think getting experience with using it can change that
>> >> inconsistency which seems serious to me and needs to
>> >> be addressed even if it complicates the implementation
>> >> since it drives to the heart of what R is.
>> >>
>> >
>> > With respect I think this is a misunderstanding of what is happening here.
>> >
>> > Functions are first class citizens. |> is, for all intents and purposes, a 
>> > macro.
>> >
>> > LHS |> RHS(arg2=5)
>> >
>> > parses to
>> >
>> > RHS(LHS, arg2 = 5)
>> >
>> > There are no functions at the point in time when the pipe transformation 
>> > happens, because no code has been evaluated. To know if a symbol is going 
>> > to evaluate to a function requires evaluation which is a step entirely 
>> > after the one where the |> pipe is implemented.
>> >
>> > Another way to think about it is that
>> >
>> > LHS |> RHS(arg2 = 5)
>> >
>> > is another way of writing RHS(LHS, arg2 = 5), NOT R code that is (or even 
>> > can be) evaluated.
>> >
>> >
>> > Now this is a subtle point that only really has implications in as much as 
>> > it is not the case for magrittr pipes, but its relevant for discussions 
>> > like this, I think.
>> >
>> > ~G
>> >
>> >> On Sat, Dec 5, 2020 at 1:08 PM Gabor Grothendieck
>> >>  wrote:
>> >> >
>> >> > The construct utils::head  is not that common but bare functions are
>> >> > very common and to make it harder to use the common case so that
>> >> > the uncommon case is slightly easier is not desirable.
>> >> 

Re: [Rd] New pipe operator

2020-12-06 Thread Gabriel Becker
Hi Gabor,

On Sun, Dec 6, 2020 at 3:22 PM Gabor Grothendieck 
wrote:

> I understand very well that it is implemented at the syntax level;
> however, in any case the implementation is irrelevant to the principles.
>
> Here a similar example to the one I gave before but this time written out:
>
> This works:
>
>   3 |> function(x) x + 1
>
> but this does not:
>
>   foo <- function(x) x + 1
>   3 |> foo
>
> so it breaks the principle of functions being first class objects.  foo
> and its
> definition are not interchangeable.


I understood what you meant as well.

The issue is that neither foo nor its definition are being operated on, or
even exist within the scope of what |> is defined to do. You are used to
magrittr's %>% where arguably what you are saying would be true. But its
not here, in my view.

Again, I think the issue is that |>, in as much as it "operates" on
anything at all (it not being a function, regardless of appearances),
operates on call expression objects, NOT on functions, ever.

function(x) x *parses to a call expression *as does RHSfun(), while RHSfun does
not, it parses to a name, *regardless of whether that symbol will
eventually evaluate to a closure or not.*

So in fact, it seems to me that, technically, all name symbols are being
treated exactly the same (none are allowed, including those which will
lookup to functions during evaluation), while all* call expressions are
also being treated the same. And again, there are no functions anywhere in
either case.

* except those that include that the parser flags as syntactically special.


> You have
> to write 3 |> foo() but don't have to write 3 |> (function(x) x + 1)().
>

I think you should probably be careful what you wish for here. I'm not
involved with this work and do not speak for any of those who were, but the
principled way to make that consistent while remaining entirely in the
parser seems very likely to be to require the latter, rather than not
require the former.


> This isn't just a matter of notation, i.e. foo vs foo(), but is a
> matter of breaking
> the way R works as a functional language with first class functions.
>

I don't agree. Consider `+`

Having

foo <- get("+") ## note no `` here
foo(x,y)

parse and work correctly while

+(x,y)

 does not does not mean + isn't a function or that it is a "second class
citizen", it simply means that the parser has constraints on the syntax for
writing code that calls it that calling other functions are not subject to.
The fact that such *syntactic* constraints can exist proves that there is
not some overarching inviolable principle being violated here, I think. Now
you may say "well thats just the parser, it has to parse + specially
because its an operator with specific precedence etc". Well, the same exact
thing is true of |> I think.

Best,
~G

>
> On Sun, Dec 6, 2020 at 4:06 PM Gabriel Becker 
> wrote:
> >
> > Hi Gabor,
> >
> > On Sun, Dec 6, 2020 at 12:52 PM Gabor Grothendieck <
> ggrothendi...@gmail.com> wrote:
> >>
> >> I think the real issue here is that functions are supposed to be
> >> first class objects in R
> >> or are supposed to be and |> would break that if if is possible
> >> to write function(x) x + 1 on the RHS but not foo (assuming foo
> >> was defined as that function).
> >>
> >> I don't think getting experience with using it can change that
> >> inconsistency which seems serious to me and needs to
> >> be addressed even if it complicates the implementation
> >> since it drives to the heart of what R is.
> >>
> >
> > With respect I think this is a misunderstanding of what is happening
> here.
> >
> > Functions are first class citizens. |> is, for all intents and purposes,
> a macro.
> >
> > LHS |> RHS(arg2=5)
> >
> > parses to
> >
> > RHS(LHS, arg2 = 5)
> >
> > There are no functions at the point in time when the pipe transformation
> happens, because no code has been evaluated. To know if a symbol is going
> to evaluate to a function requires evaluation which is a step entirely
> after the one where the |> pipe is implemented.
> >
> > Another way to think about it is that
> >
> > LHS |> RHS(arg2 = 5)
> >
> > is another way of writing RHS(LHS, arg2 = 5), NOT R code that is (or
> even can be) evaluated.
> >
> >
> > Now this is a subtle point that only really has implications in as much
> as it is not the case for magrittr pipes, but its relevant for discussions
> like this, I think.
> >
> > ~G
> >
> >> On Sat, Dec 5, 2020 at 1:08 PM Gabor Grothendieck
> >>  wrote:
> >> >
> >> > The construct utils::head  is not that common but bare functions are
> >> > very common and to make it harder to use the common case so that
> >> > the uncommon case is slightly easier is not desirable.
> >> >
> >> > Also it is trivial to write this which does work:
> >> >
> >> > mtcars %>% (utils::head)
> >> >
> >> > On Sat, Dec 5, 2020 at 11:59 AM Hugh Parsonage <
> hugh.parson...@gmail.com> wrote:
> >> > >
> >> > > I'm surprised by the aversion to
> >> > >
> >> > > mtcars |> nrow

Re: [Rd] New pipe operator and gg plotz

2020-12-06 Thread Avi Gross via R-devel
Thanks, Duncan. That answers my question fairly definitively.

Although it can be DONE it likely won't be for the reasons Hadley mentioned 
until we get some other product that replaces it entirely. There are some 
interesting work-arounds mentioned. 

I was thinking of one that has overhead but might be a pain. Hadley mentioned a 
slight variant. The first argument to a function now is expected to be the data 
argument. The second might be the mapping. Now if the function is called with a 
new first argument that is a ggplot object, it could be possible to test the 
type and if it is a ggplot object than slide over carefully any additional 
matched arguments that were not explicitly named. Not sure that is at all easy 
to do.

Alternately, you can ask that when used in such a pipeline that the user call 
all other arguments using names like data=whatever, mapping=aes(whatever) so no 
other args need to be adjusted by position.

But all this is academic and I concede will likely not be done. I can live with 
the plus signs.


-Original Message-
From: Duncan Murdoch  
Sent: Sunday, December 6, 2020 2:50 PM
To: Avi Gross ; 'r-devel' 
Subject: Re: [Rd] New pipe operator and gg plotz

Hadley's answer (#7 here: 
https://community.rstudio.com/t/why-cant-ggplot2-use/4372) makes it pretty 
clear that he thinks it would have been nice now if he had made that choice 
when ggplot2 came out, but it's not worth the effort now to change it.

Duncan Murdoch

On 06/12/2020 2:34 p.m., Avi Gross via R-devel wrote:
> As someone who switches back and forth between using standard R methods and 
> those of the tidyverse, depending on the problem, my mood and whether Jupiter 
> aligns with Saturn in the new age of Aquarius, I have a question about the 
> forthcoming built-in pipe. Will it motivate anyone to eventually change or 
> enhance the ggplot functionality to have a version that gets rid of the odd 
> use of the addition symbol?
> 
> I mean I now sometimes have a pipeline that looks like:
> 
> Data %>%
>   Do_this %>%
>   Do_that(whatever) %>%
>   ggplot(...) +
>   geom_whatever(...) +
>   ...
> 
> My understanding is this is a bit of a historical anomaly that might someday 
> be modified back.
> 
> As I understand it, the call to ggplot() creates a partially filled-in object 
> that holds all kinds of useful info. The additional calls to geom_point() and 
> so on will add/change that hidden object. Nothing much happens till the 
> object is implicitly or explicitly given to print() which switches to the 
> print function for objects of that type and creates a graph based on the 
> contents of the object at that time. So, in theory, you could have a 
> pipelined version of ggplot where the first function accepts something like a 
>  data.frame or tibble as the default first argument and at the end returns 
> the object we have been describing. All additional functions would then 
> accept such an object as the (hidden?) first argument and return the modified 
> object. The final function in the pipe would either have the value captured 
> in a variable for later use or print implicitly generating a graph.
> 
> So the above silly example might become:
> 
> Data %>%
>   Do_this %>%
>   Do_that(whatever) %>%
>   ggplot(...) %>%
>   geom_whatever(...) %>%
>   ...
> 
> Or, am I missing something here?
> 
> The language and extensions such as are now in the tidyverse might be more 
> streamlined and easier to read when using consistent notation. If we now 
> build a reasonable version of the pipeline in, might we encourage other uses 
> to gradually migrate back closer to the mainstream?
> 
> -Original Message-
> From: R-devel  On Behalf Of Rui 
> Barradas
> Sent: Sunday, December 6, 2020 2:51 AM
> To: Gregory Warnes ; Abby Spurdle 
> 
> Cc: r-devel 
> Subject: Re: [Rd] New pipe operator
> 
> Hello,
> 
> If Hilbert liked beer, I like "pipe".
> 
> More seriously, a new addition like this one is going to cause problems yet 
> unknown. But it's a good idea to have a pipe operator available. As someone 
> used to magrittr's data pipelines, I will play with this base one before 
> making up my mind. I don't expect its behavior to be exactly like magrittr 
> "%>%" (and it's not). For the moment all I can say is that it is something R 
> users are used to and that it now avoids loading a package.
> As for the new way to define anonymous functions, I am less sure. Too much 
> syntatic sugar? Or am I finding the syntax ugly?
> 
> Hope this helps,
> 
> Rui Barradas
> 
> 
> Às 03:22 de 06/12/20, Gregory Warnes escreveu:
>> If we’re being mathematically pedantic, the “pip

Re: [Rd] New pipe operator

2020-12-06 Thread Bravington, Mark (Data61, Hobart)
Seems like this *could* be a good thing, and thanks to R core for considering 
it. But, FWIW:

 - I agree with Gabor G that consistency of "syntax" should be paramount here. 
Enough problems have been caused by earlier superficially-convenient 
non-standard features in R.  In particular:

 -- there should not be any discrepancy between an in-place 
function-definition, and a predefined function attached to a symbol (as per 
Gabor's point). 
 
 -- Hence, the ability to say x |> foo  ie without parentheses, seems bound to 
lead to inconsistency, because x |> foo is allowed, x |> base::foo isn't 
allowed without tricks, but x |> function( y) foo( y) isn't... So, x |> foo is 
not worth keeping. Parentheses are a price well worth paying.
 
 -- it is still inconsistent and confusing to (apparently) invoke a function in 
some places--- normally--- via 'foo(x)', yet in others--- pipily--- via 
'foo()'. Especially if 'foo' already has a default value for its first argument.

 - I don't see the problem with a placeholder--- doesn't it remove all 
ambiguity? Sure there needs to be a standard unclashable name and people can 
argue about what that should be, but the following seems clear and flexible... 
to me, anyway:
 
 thing |> 
   foo( _PIPE_) |>   # standard
   bah( arg1, _PIPE_) |>   # multi-arg function
   _ANON_({ x <- sum( _PIPE_); _PIPE_/x + x/_PIPE_ })   # anon function
  
where '_PIPE_' is the ordained name of the placeholder, and '_ANON_' 
constructs-and-calls a function with single argument '_PIPE_'. There is just 
one rule (I think...): each pipe-stage must be a *call* involving the argument 
'_PIPE_'.


 - The proposed anonymous-function syntax looks quite ugly to me, diminishing 
readability and inviting errors. The new pipe symbol |> already looks scarily 
like quantum mechanics; adding \( just puts fishbones into the symbolic soup.

 - IMO it's not worth going too far to try to lure magritter-etc fans to swap 
to the new; my experience is that many people keep using older inferior R 
syntax for years after better replacements become available (even if they are 
aware of replacements), for various reasons. Just provide a good framework, and 
let nature take its course.
 
 - Disclaimer: personally I'm not much of a pipehead anyway, so maybe I'm not 
the audience. But if I was to consider piping, I wouldn't be very tempted by 
the current proposal. OTOH, I might even be tempted to write--- and use!--- my 
own version of '%|>%' as above (maybe someone already has). And if R did it for 
me, that'd be great :)
 
[*] Definition of _ANON_ could be something like this--- almost certainly won't 
work as-is, this is just to point out that it could be done in standard R.

`_ANON_` <- function( expr) { 
  #1. Construct a function with arg '_PIPE_' and body 'expr'
  #2. Construct a call() to that function
  #3. Do the call

  f <- function( `_PIPE_`) NULL
  body( f) <- expr
  environment( f) <- parent.frame() # or something... yes these details are 
almost certainly wrong
  expr2 <- substitute( f( `_PIPE_`)) # or something...
  eval.parent( expr2) # or something... 
}

cheers
Mark

Mark Bravington
CSIRO Marine Lab
Hobart
Australia



From: R-devel  on behalf of Gabor Grothendieck 

Sent: Monday, 7 December 2020 10:21
To: Gabriel Becker
Cc: r-devel@r-project.org
Subject: Re: [Rd] New pipe operator

I understand very well that it is implemented at the syntax level;
however, in any case the implementation is irrelevant to the principles.

Here a similar example to the one I gave before but this time written out:

This works:

  3 |> function(x) x + 1

but this does not:

  foo <- function(x) x + 1
  3 |> foo

so it breaks the principle of functions being first class objects.  foo and its
definition are not interchangeable.  You have
to write 3 |> foo() but don't have to write 3 |> (function(x) x + 1)().

This isn't just a matter of notation, i.e. foo vs foo(), but is a
matter of breaking
the way R works as a functional language with first class functions.

On Sun, Dec 6, 2020 at 4:06 PM Gabriel Becker  wrote:
>
> Hi Gabor,
>
> On Sun, Dec 6, 2020 at 12:52 PM Gabor Grothendieck  
> wrote:
>>
>> I think the real issue here is that functions are supposed to be
>> first class objects in R
>> or are supposed to be and |> would break that if if is possible
>> to write function(x) x + 1 on the RHS but not foo (assuming foo
>> was defined as that function).
>>
>> I don't think getting experience with using it can change that
>> inconsistency which seems serious to me and needs to
>> be addressed even if it complicates the implementation
>> since it drives to the heart of what R is.
>>
>
> With respect I think this is a misunderstanding of what is happening here.
>
> Functions are first class citiz

Re: [Rd] New pipe operator

2020-12-06 Thread Gabriel Becker
Hi Gabor,

On Sun, Dec 6, 2020 at 12:52 PM Gabor Grothendieck 
wrote:

> I think the real issue here is that functions are supposed to be
> first class objects in R
> or are supposed to be and |> would break that if if is possible
> to write function(x) x + 1 on the RHS but not foo (assuming foo
> was defined as that function).
>
> I don't think getting experience with using it can change that
> inconsistency which seems serious to me and needs to
> be addressed even if it complicates the implementation
> since it drives to the heart of what R is.
>
>
With respect I think this is a misunderstanding of what is happening here.

Functions are first class citizens. |> is, for all intents and purposes, a
*macro. *

LHS |> RHS(arg2=5)

*parses to*

RHS(LHS, arg2 = 5)

There are no functions at the point in time when the pipe transformation
happens, because no code has been evaluated. To know if a symbol is going
to evaluate to a function requires evaluation which is a step entirely
after the one where the |> pipe is implemented.

Another way to think about it is that

LHS |> RHS(arg2 = 5)

is another way of *writing* RHS(LHS, arg2 = 5), NOT R code that is (or even
can be) evaluated.


Now this is a subtle point that only really has implications in as much as
it is not the case for magrittr pipes, but its relevant for discussions
like this, I think.

~G

On Sat, Dec 5, 2020 at 1:08 PM Gabor Grothendieck
>  wrote:
> >
> > The construct utils::head  is not that common but bare functions are
> > very common and to make it harder to use the common case so that
> > the uncommon case is slightly easier is not desirable.
> >
> > Also it is trivial to write this which does work:
> >
> > mtcars %>% (utils::head)
> >
> > On Sat, Dec 5, 2020 at 11:59 AM Hugh Parsonage 
> wrote:
> > >
> > > I'm surprised by the aversion to
> > >
> > > mtcars |> nrow
> > >
> > > over
> > >
> > > mtcars |> nrow()
> > >
> > > and I think the decision to disallow the former should be
> > > reconsidered.  The pipe operator is only going to be used when the rhs
> > > is a function, so there is no ambiguity with omitting the parentheses.
> > > If it's disallowed, it becomes inconsistent with other treatments like
> > > sapply(mtcars, typeof) where sapply(mtcars, typeof()) would just be
> > > noise.  I'm not sure why this decision was taken
> > >
> > > If the only issue is with the double (and triple) colon operator, then
> > > ideally `mtcars |> base::head` should resolve to `base::head(mtcars)`
> > > -- in other words, demote the precedence of |>
> > >
> > > Obviously (looking at the R-Syntax branch) this decision was
> > > considered, put into place, then dropped, but I can't see why
> > > precisely.
> > >
> > > Best,
> > >
> > >
> > > Hugh.
> > >
> > >
> > >
> > >
> > >
> > >
> > >
> > > On Sat, 5 Dec 2020 at 04:07, Deepayan Sarkar <
> deepayan.sar...@gmail.com> wrote:
> > > >
> > > > On Fri, Dec 4, 2020 at 7:35 PM Duncan Murdoch <
> murdoch.dun...@gmail.com> wrote:
> > > > >
> > > > > On 04/12/2020 8:13 a.m., Hiroaki Yutani wrote:
> > > > > >>   Error: function '::' not supported in RHS call of a pipe
> > > > > >
> > > > > > To me, this error looks much more friendly than magrittr's error.
> > > > > > Some of them got too used to specify functions without (). This
> > > > > > is OK until they use `::`, but when they need to use it, it takes
> > > > > > hours to figure out why
> > > > > >
> > > > > > mtcars %>% base::head
> > > > > > #> Error in .::base : unused argument (head)
> > > > > >
> > > > > > won't work but
> > > > > >
> > > > > > mtcars %>% head
> > > > > >
> > > > > > works. I think this is a too harsh lesson for ordinary R users to
> > > > > > learn `::` is a function. I've been wanting for magrittr to drop
> the
> > > > > > support for a function name without () to avoid this confusion,
> > > > > > so I would very much welcome the new pipe operator's behavior.
> > > > > > Thank you all the developers who implemented this!
> > > > >
> > > > > I agree, it's an improvement on the corresponding magrittr error.
> > > > >
> > > > > I think the semantics of not evaluating the RHS, but treating the
> pipe
> > > > > as purely syntactical is a good decision.
> > > > >
> > > > > I'm not sure I like the recommended way to pipe into a particular
> argument:
> > > > >
> > > > >mtcars |> subset(cyl == 4) |> \(d) lm(mpg ~ disp, data = d)
> > > > >
> > > > > or
> > > > >
> > > > >mtcars |> subset(cyl == 4) |> function(d) lm(mpg ~ disp, data =
> d)
> > > > >
> > > > > both of which are equivalent to
> > > > >
> > > > >mtcars |> subset(cyl == 4) |> (function(d) lm(mpg ~ disp, data
> = d))()
> > > > >
> > > > > It's tempting to suggest it should allow something like
> > > > >
> > > > >mtcars |> subset(cyl == 4) |> lm(mpg ~ disp, data = .)
> > > >
> > > > Which is really not that far off from
> > > >
> > > > mtcars |> subset(cyl == 4) |> \(.) lm(mpg ~ disp, data = .)
> > > >
> > > > once you get used to it.
> > > >
> > > > One 

Re: [Rd] New pipe operator

2020-12-06 Thread Gabor Grothendieck
I think the real issue here is that functions are supposed to be
first class objects in R
or are supposed to be and |> would break that if if is possible
to write function(x) x + 1 on the RHS but not foo (assuming foo
was defined as that function).

I don't think getting experience with using it can change that
inconsistency which seems serious to me and needs to
be addressed even if it complicates the implementation
since it drives to the heart of what R is.

On Sat, Dec 5, 2020 at 1:08 PM Gabor Grothendieck
 wrote:
>
> The construct utils::head  is not that common but bare functions are
> very common and to make it harder to use the common case so that
> the uncommon case is slightly easier is not desirable.
>
> Also it is trivial to write this which does work:
>
> mtcars %>% (utils::head)
>
> On Sat, Dec 5, 2020 at 11:59 AM Hugh Parsonage  
> wrote:
> >
> > I'm surprised by the aversion to
> >
> > mtcars |> nrow
> >
> > over
> >
> > mtcars |> nrow()
> >
> > and I think the decision to disallow the former should be
> > reconsidered.  The pipe operator is only going to be used when the rhs
> > is a function, so there is no ambiguity with omitting the parentheses.
> > If it's disallowed, it becomes inconsistent with other treatments like
> > sapply(mtcars, typeof) where sapply(mtcars, typeof()) would just be
> > noise.  I'm not sure why this decision was taken
> >
> > If the only issue is with the double (and triple) colon operator, then
> > ideally `mtcars |> base::head` should resolve to `base::head(mtcars)`
> > -- in other words, demote the precedence of |>
> >
> > Obviously (looking at the R-Syntax branch) this decision was
> > considered, put into place, then dropped, but I can't see why
> > precisely.
> >
> > Best,
> >
> >
> > Hugh.
> >
> >
> >
> >
> >
> >
> >
> > On Sat, 5 Dec 2020 at 04:07, Deepayan Sarkar  
> > wrote:
> > >
> > > On Fri, Dec 4, 2020 at 7:35 PM Duncan Murdoch  
> > > wrote:
> > > >
> > > > On 04/12/2020 8:13 a.m., Hiroaki Yutani wrote:
> > > > >>   Error: function '::' not supported in RHS call of a pipe
> > > > >
> > > > > To me, this error looks much more friendly than magrittr's error.
> > > > > Some of them got too used to specify functions without (). This
> > > > > is OK until they use `::`, but when they need to use it, it takes
> > > > > hours to figure out why
> > > > >
> > > > > mtcars %>% base::head
> > > > > #> Error in .::base : unused argument (head)
> > > > >
> > > > > won't work but
> > > > >
> > > > > mtcars %>% head
> > > > >
> > > > > works. I think this is a too harsh lesson for ordinary R users to
> > > > > learn `::` is a function. I've been wanting for magrittr to drop the
> > > > > support for a function name without () to avoid this confusion,
> > > > > so I would very much welcome the new pipe operator's behavior.
> > > > > Thank you all the developers who implemented this!
> > > >
> > > > I agree, it's an improvement on the corresponding magrittr error.
> > > >
> > > > I think the semantics of not evaluating the RHS, but treating the pipe
> > > > as purely syntactical is a good decision.
> > > >
> > > > I'm not sure I like the recommended way to pipe into a particular 
> > > > argument:
> > > >
> > > >mtcars |> subset(cyl == 4) |> \(d) lm(mpg ~ disp, data = d)
> > > >
> > > > or
> > > >
> > > >mtcars |> subset(cyl == 4) |> function(d) lm(mpg ~ disp, data = d)
> > > >
> > > > both of which are equivalent to
> > > >
> > > >mtcars |> subset(cyl == 4) |> (function(d) lm(mpg ~ disp, data = 
> > > > d))()
> > > >
> > > > It's tempting to suggest it should allow something like
> > > >
> > > >mtcars |> subset(cyl == 4) |> lm(mpg ~ disp, data = .)
> > >
> > > Which is really not that far off from
> > >
> > > mtcars |> subset(cyl == 4) |> \(.) lm(mpg ~ disp, data = .)
> > >
> > > once you get used to it.
> > >
> > > One consequence of the implementation is that it's not clear how
> > > multiple occurrences of the placeholder would be interpreted. With
> > > magrittr,
> > >
> > > sort(runif(10)) %>% ecdf(.)(.)
> > > ## [1] 0.1 0.2 0.3 0.4 0.5 0.6 0.7 0.8 0.9 1.0
> > >
> > > This is probably what you would expect, if you expect it to work at all, 
> > > and not
> > >
> > > ecdf(sort(runif(10)))(sort(runif(10)))
> > >
> > > There would be no such ambiguity with anonymous functions
> > >
> > > sort(runif(10)) |> \(.) ecdf(.)(.)
> > >
> > > -Deepayan
> > >
> > > > which would be expanded to something equivalent to the other versions:
> > > > but that makes it quite a bit more complicated.  (Maybe _ or \. should
> > > > be used instead of ., since those are not legal variable names.)
> > > >
> > > > I don't think there should be an attempt to copy magrittr's special
> > > > casing of how . is used in determining whether to also include the
> > > > previous value as first argument.
> > > >
> > > > Duncan Murdoch
> > > >
> > > >
> > > > >
> > > > > Best,
> > > > > Hiroaki Yutani
> > > > >
> > > > > 2020年12月4日(金) 20:51 Duncan Murdoch :
> > > > >>
> > > > >> 

Re: [Rd] New pipe operator and gg plotz

2020-12-06 Thread Duncan Murdoch
Hadley's answer (#7 here: 
https://community.rstudio.com/t/why-cant-ggplot2-use/4372) makes it 
pretty clear that he thinks it would have been nice now if he had made 
that choice when ggplot2 came out, but it's not worth the effort now to 
change it.


Duncan Murdoch

On 06/12/2020 2:34 p.m., Avi Gross via R-devel wrote:

As someone who switches back and forth between using standard R methods and 
those of the tidyverse, depending on the problem, my mood and whether Jupiter 
aligns with Saturn in the new age of Aquarius, I have a question about the 
forthcoming built-in pipe. Will it motivate anyone to eventually change or 
enhance the ggplot functionality to have a version that gets rid of the odd use 
of the addition symbol?

I mean I now sometimes have a pipeline that looks like:

Data %>%
Do_this %>%
Do_that(whatever) %>%
ggplot(...) +
geom_whatever(...) +
...

My understanding is this is a bit of a historical anomaly that might someday be 
modified back.

As I understand it, the call to ggplot() creates a partially filled-in object 
that holds all kinds of useful info. The additional calls to geom_point() and 
so on will add/change that hidden object. Nothing much happens till the object 
is implicitly or explicitly given to print() which switches to the print 
function for objects of that type and creates a graph based on the contents of 
the object at that time. So, in theory, you could have a pipelined version of 
ggplot where the first function accepts something like a  data.frame or tibble 
as the default first argument and at the end returns the object we have been 
describing. All additional functions would then accept such an object as the 
(hidden?) first argument and return the modified object. The final function in 
the pipe would either have the value captured in a variable for later use or 
print implicitly generating a graph.

So the above silly example might become:

Data %>%
Do_this %>%
Do_that(whatever) %>%
ggplot(...) %>%
geom_whatever(...) %>%
...

Or, am I missing something here?

The language and extensions such as are now in the tidyverse might be more 
streamlined and easier to read when using consistent notation. If we now build 
a reasonable version of the pipeline in, might we encourage other uses to 
gradually migrate back closer to the mainstream?

-Original Message-
From: R-devel  On Behalf Of Rui Barradas
Sent: Sunday, December 6, 2020 2:51 AM
To: Gregory Warnes ; Abby Spurdle 
Cc: r-devel 
Subject: Re: [Rd] New pipe operator

Hello,

If Hilbert liked beer, I like "pipe".

More seriously, a new addition like this one is going to cause problems yet unknown. But 
it's a good idea to have a pipe operator available. As someone used to magrittr's data 
pipelines, I will play with this base one before making up my mind. I don't expect its 
behavior to be exactly like magrittr "%>%" (and it's not). For the moment all I 
can say is that it is something R users are used to and that it now avoids loading a package.
As for the new way to define anonymous functions, I am less sure. Too much 
syntatic sugar? Or am I finding the syntax ugly?

Hope this helps,

Rui Barradas


Às 03:22 de 06/12/20, Gregory Warnes escreveu:

If we’re being mathematically pedantic, the “pipe” operator is
actually function composition > That being said, pipes are a simple
and well-known idiom. While being less
than mathematically exact, it seems a reasonable   label for the (very
useful) behavior.

On Sat, Dec 5, 2020 at 9:43 PM Abby Spurdle  wrote:


This is a good addition


I can't understand why so many people are calling this a "pipe".
Pipes connect processes, via their I/O streams.
Arguably, a more general interpretation would include sockets and files.

https://en.wikipedia.org/wiki/Pipeline_(Unix)
https://en.wikipedia.org/wiki/Named_pipe
https://en.wikipedia.org/wiki/Anonymous_pipe

As far as I can tell, the magrittr-like operators are functions (not
pipes), with nonstandard syntax.
This is not consistent with R's original design philosophy, building
on C, Lisp and S, along with lots of *important* math and stats.

It's possible that some parties are interested in creating a kind of
"data pipeline".
I'm interested in this myself, and I think we could discuss this more.
But I'm not convinced the magrittr-like operators help to achieve
this goal.
Which, in my opinion, would require one to model programs as directed
graphs, along with some degree of asynchronous input.

Presumably, these operators will be added to R anyway, and (almost)
no one will listen to me.

So, I would like to make one suggestion:
Is it possible for these operators to *not* be named:
  The R Pipe
  The S Pipe
  Or anything with a similar meaning.

Maybe tidy pipe, or something else that links it to its proponents?

_

Re: [Rd] New pipe operator and gg plotz

2020-12-06 Thread Avi Gross via R-devel
As someone who switches back and forth between using standard R methods and 
those of the tidyverse, depending on the problem, my mood and whether Jupiter 
aligns with Saturn in the new age of Aquarius, I have a question about the 
forthcoming built-in pipe. Will it motivate anyone to eventually change or 
enhance the ggplot functionality to have a version that gets rid of the odd use 
of the addition symbol?

I mean I now sometimes have a pipeline that looks like:

Data %>%
Do_this %>%
Do_that(whatever) %>%
ggplot(...) +
geom_whatever(...) +
...

My understanding is this is a bit of a historical anomaly that might someday be 
modified back.

As I understand it, the call to ggplot() creates a partially filled-in object 
that holds all kinds of useful info. The additional calls to geom_point() and 
so on will add/change that hidden object. Nothing much happens till the object 
is implicitly or explicitly given to print() which switches to the print 
function for objects of that type and creates a graph based on the contents of 
the object at that time. So, in theory, you could have a pipelined version of 
ggplot where the first function accepts something like a  data.frame or tibble 
as the default first argument and at the end returns the object we have been 
describing. All additional functions would then accept such an object as the 
(hidden?) first argument and return the modified object. The final function in 
the pipe would either have the value captured in a variable for later use or 
print implicitly generating a graph.

So the above silly example might become:

Data %>%
Do_this %>%
Do_that(whatever) %>%
ggplot(...) %>%
geom_whatever(...) %>%
...

Or, am I missing something here? 

The language and extensions such as are now in the tidyverse might be more 
streamlined and easier to read when using consistent notation. If we now build 
a reasonable version of the pipeline in, might we encourage other uses to 
gradually migrate back closer to the mainstream?

-Original Message-
From: R-devel  On Behalf Of Rui Barradas
Sent: Sunday, December 6, 2020 2:51 AM
To: Gregory Warnes ; Abby Spurdle 
Cc: r-devel 
Subject: Re: [Rd] New pipe operator

Hello,

If Hilbert liked beer, I like "pipe".

More seriously, a new addition like this one is going to cause problems yet 
unknown. But it's a good idea to have a pipe operator available. As someone 
used to magrittr's data pipelines, I will play with this base one before making 
up my mind. I don't expect its behavior to be exactly like magrittr "%>%" (and 
it's not). For the moment all I can say is that it is something R users are 
used to and that it now avoids loading a package.
As for the new way to define anonymous functions, I am less sure. Too much 
syntatic sugar? Or am I finding the syntax ugly?

Hope this helps,

Rui Barradas


Às 03:22 de 06/12/20, Gregory Warnes escreveu:
> If we’re being mathematically pedantic, the “pipe” operator is 
> actually function composition > That being said, pipes are a simple 
> and well-known idiom. While being less
> than mathematically exact, it seems a reasonable   label for the (very
> useful) behavior.
> 
> On Sat, Dec 5, 2020 at 9:43 PM Abby Spurdle  wrote:
> 
>>> This is a good addition
>>
>> I can't understand why so many people are calling this a "pipe".
>> Pipes connect processes, via their I/O streams.
>> Arguably, a more general interpretation would include sockets and files.
>>
>> https://en.wikipedia.org/wiki/Pipeline_(Unix)
>> https://en.wikipedia.org/wiki/Named_pipe
>> https://en.wikipedia.org/wiki/Anonymous_pipe
>>
>> As far as I can tell, the magrittr-like operators are functions (not 
>> pipes), with nonstandard syntax.
>> This is not consistent with R's original design philosophy, building 
>> on C, Lisp and S, along with lots of *important* math and stats.
>>
>> It's possible that some parties are interested in creating a kind of 
>> "data pipeline".
>> I'm interested in this myself, and I think we could discuss this more.
>> But I'm not convinced the magrittr-like operators help to achieve 
>> this goal.
>> Which, in my opinion, would require one to model programs as directed 
>> graphs, along with some degree of asynchronous input.
>>
>> Presumably, these operators will be added to R anyway, and (almost) 
>> no one will listen to me.
>>
>> So, I would like to make one suggestion:
>> Is it possible for these operators to *not* be named:
>>  The R Pipe
>>  The S Pipe
>>  Or anything with a similar meaning.
>>
>> Maybe tidy pipe, or something else that links it to its proponents?
>>
>>

Re: [Rd] New pipe operator

2020-12-06 Thread Avi Gross via R-devel
Topic is more about anonymous functions but also pipes.

Rui thought the proposed syntax was a bit ugly. I assume the \(x) ... was what 
he means, not the function(x)... version.

Many current languages have played games on adding some form of anonymous 
function that is defined and used in place. Some go to great pains to make 
various parts optional to the point where there are many valid way to create a 
function that takes no arguments so you can leave out almost everything else as 
optional.

I admit having to type "lambda" all the time (in some languages)  is not 
preferable but in English, something shorter like fun(...) or func(...) instead 
of function(...) might be more readable than the weird choice of \(. Yes. You 
can view the combo to bring attention to the fact the "(" is meant not as any 
old paren for other uses but specifically for function invocation/definition 
purposes. But overuse of the backslash to mean other things such as in regular 
expressions and the parentheses for so many things, makes parsing for humans 
harder. So does "|>" for the new pipe symbol as it can also look like "or 
greater than" and since some humans do not insert spaces to make code even 
shorter, it can be a challenge to rapidly see a line of code as tokens.

If programming were being invented today with a larger set of symbols, it might 
use more of them and perhaps look more like APL. We might have all of the 
built-in to the language tokens be single symbols including real arrows instead 
of -> and a not-equals symbol like  ≠ instead of != or ~= s some languages use. 
In that system, what might the pipe symbol look like?

ǂ

But although making things concise is nice, sometimes there is clarity in using 
enough room, to make things clear or we might as well code in binary.

-Original Message-
From: R-devel  On Behalf Of Rui Barradas
Sent: Sunday, December 6, 2020 2:51 AM
To: Gregory Warnes ; Abby Spurdle 
Cc: r-devel 
Subject: Re: [Rd] New pipe operator

Hello,

If Hilbert liked beer, I like "pipe".

More seriously, a new addition like this one is going to cause problems yet 
unknown. But it's a good idea to have a pipe operator available. As someone 
used to magrittr's data pipelines, I will play with this base one before making 
up my mind. I don't expect its behavior to be exactly like magrittr "%>%" (and 
it's not). For the moment all I can say is that it is something R users are 
used to and that it now avoids loading a package.
As for the new way to define anonymous functions, I am less sure. Too much 
syntatic sugar? Or am I finding the syntax ugly?

Hope this helps,

Rui Barradas


Às 03:22 de 06/12/20, Gregory Warnes escreveu:
> If we’re being mathematically pedantic, the “pipe” operator is 
> actually function composition > That being said, pipes are a simple 
> and well-known idiom. While being less
> than mathematically exact, it seems a reasonable   label for the (very
> useful) behavior.
> 
> On Sat, Dec 5, 2020 at 9:43 PM Abby Spurdle  wrote:
> 
>>> This is a good addition
>>
>> I can't understand why so many people are calling this a "pipe".
>> Pipes connect processes, via their I/O streams.
>> Arguably, a more general interpretation would include sockets and files.
>>
>> https://en.wikipedia.org/wiki/Pipeline_(Unix)
>> https://en.wikipedia.org/wiki/Named_pipe
>> https://en.wikipedia.org/wiki/Anonymous_pipe
>>
>> As far as I can tell, the magrittr-like operators are functions (not 
>> pipes), with nonstandard syntax.
>> This is not consistent with R's original design philosophy, building 
>> on C, Lisp and S, along with lots of *important* math and stats.
>>
>> It's possible that some parties are interested in creating a kind of 
>> "data pipeline".
>> I'm interested in this myself, and I think we could discuss this more.
>> But I'm not convinced the magrittr-like operators help to achieve 
>> this goal.
>> Which, in my opinion, would require one to model programs as directed 
>> graphs, along with some degree of asynchronous input.
>>
>> Presumably, these operators will be added to R anyway, and (almost) 
>> no one will listen to me.
>>
>> So, I would like to make one suggestion:
>> Is it possible for these operators to *not* be named:
>>  The R Pipe
>>  The S Pipe
>>  Or anything with a similar meaning.
>>
>> Maybe tidy pipe, or something else that links it to its proponents?
>>
>> __
>> R-devel@r-project.org mailing list
>> https://stat.ethz.ch/mailman/listinfo/r-devel
>>

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


Scanned by McAfee and confirmed virus-free. 
Find out more here: https://bit.ly/2zCJMrO

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


Re: [Rd] New pipe operator

2020-12-06 Thread Avi Gross via R-devel
Naming is another whole topic.

I have seen suggestions that the current pipeline symbol used be phrased as 
THEN so

data %>% f1 %>% f2()

would be said as something like:
take data then apply f1 then f2

or some variants.

There are words other than pipe or pipeline that might also work such as 
"assembly line" or "conveyor belt" that might fit some kinds of pipelining 
better than others. My original exposure to UNIX in the early 80's used a 
pipeline of multiple processes whose standard input and/or standard output (and 
sometimes also standard error) were redirected to an anonymous "pipe" device 
that buffered whatever (usually) text that was thrown at it and the processes 
reading and writing from it were paused and restarted as needed when data was 
ready. Problems often could be decomposed into multiple parts that had a 
solution using some program and it was not unusual to do something like:

cat *.c | grep -v ... | grep ... | sed ... | cut ... >output

Of course something like the above was often rewritten to be done within a 
single awk script or perl or whatever. You could view the above though from the 
perspective of "data" in some form, often text, being passed from one 
function(ality) to another and changing a bit each step of the way. A very 
common use of this form of pipeline was used to deal with embedded text in a 
different language in typsetting:

tbl filename | eqn | pic | troff | ...

The above would open a file, pass through all lines except those between 
markers that specified a table starting and ending. Those lines would be 
processed and transformed into the troff language equivalent. The old plus new 
lines now went to eqn which found and transformed equations similarly then to 
pic which transformed instructions it knew to image descriptions in troff and 
finally troff processed the whole mess and then off to the printer.

Clearly the above can be seen as a data pipeline using full processes as nodes.

The way R is using the pipeline may just use functions but you can imagine it 
as having similarities and differences. Current implementations may be linear 
with lazy evaluation and with every part running to completion before the next 
part starts. Every "object" is fully made, then used, then often removed as a 
temporary object. There is no buffering. But in principle, you can make 
UNIX-like pipelines using parallelism within a process too. 

Would there be scenarios where phrases like "assembly line" or "conveyor belt" 
make sense to describe the method properly? The word pipe suggests a linearity 
to some whereas conveyor belts these days also can be used to selectively shunt 
things one way or another as in assembling all parts of your order from 
different parts of a warehouse and arranging they all end up in the same 
delivery area. Making applications do that dynamically may have other names. 
Think flowchart!

Time to go do something useful.

-Original Message-
From: R-devel  On Behalf Of Hiroaki Yutani
Sent: Saturday, December 5, 2020 10:29 PM
To: Abby Spurdle 
Cc: r-devel 
Subject: Re: [Rd] New pipe operator

It is common practice to call |> as pipe (or pipeline operator) among many 
languages including ones that recently introduced it as an experimental feature.
Pipeline is a
common feature for functional programming, not just for "data pipeline."

F#: 
https://docs.microsoft.com/en-us/dotnet/fsharp/language-reference/symbol-and-operator-reference/
Elixir: https://hexdocs.pm/elixir/operators.html#general-operators
Typescript:
https://developer.mozilla.org/en-US/docs/Web/JavaScript/Reference/Operators/Pipeline_operator
Ruby: https://bugs.ruby-lang.org/issues/15799

(This blog post about the history of pipe operator might be
interesting: 
https://mamememo.blogspot.com/2019/06/a-brief-history-of-pipeline-operator.html
)

I agree this is a bit confusing for those who are familiar with other "pipe" 
concepts, but there's no other appropriate term to call |>.

2020年12月6日(日) 12:22 Gregory Warnes :
>
> If we’re being mathematically pedantic, the “pipe” operator is 
> actually function composition.
>
> That being said, pipes are a simple and well-known idiom. While being less
> than mathematically exact, it seems a reasonable   label for the (very
> useful) behavior.
>
> On Sat, Dec 5, 2020 at 9:43 PM Abby Spurdle  wrote:
>
> > > This is a good addition
> >
> > I can't understand why so many people are calling this a "pipe".
> > Pipes connect processes, via their I/O streams.
> > Arguably, a more general interpretation would include sockets and files.
> >
> > https://en.wikipedia.org/wiki/Pipeline_(Unix)
> > https://en.wikipedia.org/wiki/Named_pipe
> > https://en.wikipedia.org/wiki/Anonymous_pipe
> >
> > As f

Re: [Rd] New pipe operator

2020-12-05 Thread Rui Barradas

Hello,

If Hilbert liked beer, I like "pipe".

More seriously, a new addition like this one is going to cause problems 
yet unknown. But it's a good idea to have a pipe operator available. As 
someone used to magrittr's data pipelines, I will play with this base 
one before making up my mind. I don't expect its behavior to be exactly 
like magrittr "%>%" (and it's not). For the moment all I can say is that 
it is something R users are used to and that it now avoids loading a 
package.
As for the new way to define anonymous functions, I am less sure. Too 
much syntatic sugar? Or am I finding the syntax ugly?


Hope this helps,

Rui Barradas


Às 03:22 de 06/12/20, Gregory Warnes escreveu:

If we’re being mathematically pedantic, the “pipe” operator is actually
function composition >
That being said, pipes are a simple and well-known idiom. While being less
than mathematically exact, it seems a reasonable   label for the (very
useful) behavior.

On Sat, Dec 5, 2020 at 9:43 PM Abby Spurdle  wrote:


This is a good addition


I can't understand why so many people are calling this a "pipe".
Pipes connect processes, via their I/O streams.
Arguably, a more general interpretation would include sockets and files.

https://en.wikipedia.org/wiki/Pipeline_(Unix)
https://en.wikipedia.org/wiki/Named_pipe
https://en.wikipedia.org/wiki/Anonymous_pipe

As far as I can tell, the magrittr-like operators are functions (not
pipes), with nonstandard syntax.
This is not consistent with R's original design philosophy, building
on C, Lisp and S, along with lots of *important* math and stats.

It's possible that some parties are interested in creating a kind of
"data pipeline".
I'm interested in this myself, and I think we could discuss this more.
But I'm not convinced the magrittr-like operators help to achieve this
goal.
Which, in my opinion, would require one to model programs as directed
graphs, along with some degree of asynchronous input.

Presumably, these operators will be added to R anyway, and (almost) no
one will listen to me.

So, I would like to make one suggestion:
Is it possible for these operators to *not* be named:
 The R Pipe
 The S Pipe
 Or anything with a similar meaning.

Maybe tidy pipe, or something else that links it to its proponents?

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



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


Re: [Rd] New pipe operator

2020-12-05 Thread Hiroaki Yutani
It is common practice to call |> as pipe (or pipeline operator) among
many languages
including ones that recently introduced it as an experimental feature.
Pipeline is a
common feature for functional programming, not just for "data pipeline."

F#: 
https://docs.microsoft.com/en-us/dotnet/fsharp/language-reference/symbol-and-operator-reference/
Elixir: https://hexdocs.pm/elixir/operators.html#general-operators
Typescript:
https://developer.mozilla.org/en-US/docs/Web/JavaScript/Reference/Operators/Pipeline_operator
Ruby: https://bugs.ruby-lang.org/issues/15799

(This blog post about the history of pipe operator might be
interesting: 
https://mamememo.blogspot.com/2019/06/a-brief-history-of-pipeline-operator.html
)

I agree this is a bit confusing for those who are familiar with other
"pipe" concepts,
but there's no other appropriate term to call |>.

2020年12月6日(日) 12:22 Gregory Warnes :
>
> If we’re being mathematically pedantic, the “pipe” operator is actually
> function composition.
>
> That being said, pipes are a simple and well-known idiom. While being less
> than mathematically exact, it seems a reasonable   label for the (very
> useful) behavior.
>
> On Sat, Dec 5, 2020 at 9:43 PM Abby Spurdle  wrote:
>
> > > This is a good addition
> >
> > I can't understand why so many people are calling this a "pipe".
> > Pipes connect processes, via their I/O streams.
> > Arguably, a more general interpretation would include sockets and files.
> >
> > https://en.wikipedia.org/wiki/Pipeline_(Unix)
> > https://en.wikipedia.org/wiki/Named_pipe
> > https://en.wikipedia.org/wiki/Anonymous_pipe
> >
> > As far as I can tell, the magrittr-like operators are functions (not
> > pipes), with nonstandard syntax.
> > This is not consistent with R's original design philosophy, building
> > on C, Lisp and S, along with lots of *important* math and stats.
> >
> > It's possible that some parties are interested in creating a kind of
> > "data pipeline".
> > I'm interested in this myself, and I think we could discuss this more.
> > But I'm not convinced the magrittr-like operators help to achieve this
> > goal.
> > Which, in my opinion, would require one to model programs as directed
> > graphs, along with some degree of asynchronous input.
> >
> > Presumably, these operators will be added to R anyway, and (almost) no
> > one will listen to me.
> >
> > So, I would like to make one suggestion:
> > Is it possible for these operators to *not* be named:
> > The R Pipe
> > The S Pipe
> > Or anything with a similar meaning.
> >
> > Maybe tidy pipe, or something else that links it to its proponents?
> >
> > __
> > R-devel@r-project.org mailing list
> > https://stat.ethz.ch/mailman/listinfo/r-devel
> >
> --
> "Whereas true religion and good morals are the only solid foundations of
> public liberty and happiness . . . it is hereby earnestly recommended to
> the several States to take the most effectual measures for the
> encouragement thereof." Continental Congress, 1778
>
> [[alternative HTML version deleted]]
>
> __
> R-devel@r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-devel

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


Re: [Rd] New pipe operator

2020-12-05 Thread Gregory Warnes
If we’re being mathematically pedantic, the “pipe” operator is actually
function composition.

That being said, pipes are a simple and well-known idiom. While being less
than mathematically exact, it seems a reasonable   label for the (very
useful) behavior.

On Sat, Dec 5, 2020 at 9:43 PM Abby Spurdle  wrote:

> > This is a good addition
>
> I can't understand why so many people are calling this a "pipe".
> Pipes connect processes, via their I/O streams.
> Arguably, a more general interpretation would include sockets and files.
>
> https://en.wikipedia.org/wiki/Pipeline_(Unix)
> https://en.wikipedia.org/wiki/Named_pipe
> https://en.wikipedia.org/wiki/Anonymous_pipe
>
> As far as I can tell, the magrittr-like operators are functions (not
> pipes), with nonstandard syntax.
> This is not consistent with R's original design philosophy, building
> on C, Lisp and S, along with lots of *important* math and stats.
>
> It's possible that some parties are interested in creating a kind of
> "data pipeline".
> I'm interested in this myself, and I think we could discuss this more.
> But I'm not convinced the magrittr-like operators help to achieve this
> goal.
> Which, in my opinion, would require one to model programs as directed
> graphs, along with some degree of asynchronous input.
>
> Presumably, these operators will be added to R anyway, and (almost) no
> one will listen to me.
>
> So, I would like to make one suggestion:
> Is it possible for these operators to *not* be named:
> The R Pipe
> The S Pipe
> Or anything with a similar meaning.
>
> Maybe tidy pipe, or something else that links it to its proponents?
>
> __
> R-devel@r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-devel
>
-- 
"Whereas true religion and good morals are the only solid foundations of
public liberty and happiness . . . it is hereby earnestly recommended to
the several States to take the most effectual measures for the
encouragement thereof." Continental Congress, 1778

[[alternative HTML version deleted]]

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


Re: [Rd] New pipe operator

2020-12-05 Thread Abby Spurdle
> This is a good addition

I can't understand why so many people are calling this a "pipe".
Pipes connect processes, via their I/O streams.
Arguably, a more general interpretation would include sockets and files.

https://en.wikipedia.org/wiki/Pipeline_(Unix)
https://en.wikipedia.org/wiki/Named_pipe
https://en.wikipedia.org/wiki/Anonymous_pipe

As far as I can tell, the magrittr-like operators are functions (not
pipes), with nonstandard syntax.
This is not consistent with R's original design philosophy, building
on C, Lisp and S, along with lots of *important* math and stats.

It's possible that some parties are interested in creating a kind of
"data pipeline".
I'm interested in this myself, and I think we could discuss this more.
But I'm not convinced the magrittr-like operators help to achieve this goal.
Which, in my opinion, would require one to model programs as directed
graphs, along with some degree of asynchronous input.

Presumably, these operators will be added to R anyway, and (almost) no
one will listen to me.

So, I would like to make one suggestion:
Is it possible for these operators to *not* be named:
The R Pipe
The S Pipe
Or anything with a similar meaning.

Maybe tidy pipe, or something else that links it to its proponents?

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


Re: [Rd] New pipe operator

2020-12-05 Thread John Mount
The :: is a case that we worked to get right with wrapr dot-pipe. I shared 
notes on this S3/S4 pipe in the R journal 
https://journal.r-project.org/archive/2018/RJ-2018-042/index.html

library(magrittr)
packageVersion("magrittr")
# [1] ‘2.0.1’
5 %>% base::sin
# Error in .::base : unused argument (sin)

library(wrapr)
5 %.>% base::sin
# [1] -0.9589243


On Dec 5, 2020, at 10:08 AM, Gabor Grothendieck 
mailto:ggrothendi...@gmail.com>> wrote:

The construct utils::head  is not that common but bare functions are
very common and to make it harder to use the common case so that
the uncommon case is slightly easier is not desirable.

Also it is trivial to write this which does work:

mtcars %>% (utils::head)

On Sat, Dec 5, 2020 at 11:59 AM Hugh Parsonage 
mailto:hugh.parson...@gmail.com>> wrote:

I'm surprised by the aversion to

mtcars |> nrow

over

mtcars |> nrow()

and I think the decision to disallow the former should be
reconsidered.  The pipe operator is only going to be used when the rhs
is a function, so there is no ambiguity with omitting the parentheses.
If it's disallowed, it becomes inconsistent with other treatments like
sapply(mtcars, typeof) where sapply(mtcars, typeof()) would just be
noise.  I'm not sure why this decision was taken

If the only issue is with the double (and triple) colon operator, then
ideally `mtcars |> base::head` should resolve to `base::head(mtcars)`
-- in other words, demote the precedence of |>

Obviously (looking at the R-Syntax branch) this decision was
considered, put into place, then dropped, but I can't see why
precisely.

Best,


Hugh.







On Sat, 5 Dec 2020 at 04:07, Deepayan Sarkar 
mailto:deepayan.sar...@gmail.com>> wrote:

On Fri, Dec 4, 2020 at 7:35 PM Duncan Murdoch 
mailto:murdoch.dun...@gmail.com>> wrote:

On 04/12/2020 8:13 a.m., Hiroaki Yutani wrote:
 Error: function '::' not supported in RHS call of a pipe

To me, this error looks much more friendly than magrittr's error.
Some of them got too used to specify functions without (). This
is OK until they use `::`, but when they need to use it, it takes
hours to figure out why

mtcars %>% base::head
#> Error in .::base : unused argument (head)

won't work but

mtcars %>% head

works. I think this is a too harsh lesson for ordinary R users to
learn `::` is a function. I've been wanting for magrittr to drop the
support for a function name without () to avoid this confusion,
so I would very much welcome the new pipe operator's behavior.
Thank you all the developers who implemented this!

I agree, it's an improvement on the corresponding magrittr error.

I think the semantics of not evaluating the RHS, but treating the pipe
as purely syntactical is a good decision.

I'm not sure I like the recommended way to pipe into a particular argument:

  mtcars |> subset(cyl == 4) |> \(d) lm(mpg ~ disp, data = d)

or

  mtcars |> subset(cyl == 4) |> function(d) lm(mpg ~ disp, data = d)

both of which are equivalent to

  mtcars |> subset(cyl == 4) |> (function(d) lm(mpg ~ disp, data = d))()

It's tempting to suggest it should allow something like

  mtcars |> subset(cyl == 4) |> lm(mpg ~ disp, data = .)

Which is really not that far off from

mtcars |> subset(cyl == 4) |> \(.) lm(mpg ~ disp, data = .)

once you get used to it.

One consequence of the implementation is that it's not clear how
multiple occurrences of the placeholder would be interpreted. With
magrittr,

sort(runif(10)) %>% ecdf(.)(.)
## [1] 0.1 0.2 0.3 0.4 0.5 0.6 0.7 0.8 0.9 1.0

This is probably what you would expect, if you expect it to work at all, and not

ecdf(sort(runif(10)))(sort(runif(10)))

There would be no such ambiguity with anonymous functions

sort(runif(10)) |> \(.) ecdf(.)(.)

-Deepayan

which would be expanded to something equivalent to the other versions:
but that makes it quite a bit more complicated.  (Maybe _ or \. should
be used instead of ., since those are not legal variable names.)

I don't think there should be an attempt to copy magrittr's special
casing of how . is used in determining whether to also include the
previous value as first argument.

Duncan Murdoch



Best,
Hiroaki Yutani

2020年12月4日(金) 20:51 Duncan Murdoch 
mailto:murdoch.dun...@gmail.com>>:

Just saw this on the R-devel news:


R now provides a simple native pipe syntax ‘|>’ as well as a shorthand
notation for creating functions, e.g. ‘\(x) x + 1’ is parsed as
‘function(x) x + 1’. The pipe implementation as a syntax transformation
was motivated by suggestions from Jim Hester and Lionel Henry. These
features are experimental and may change prior to release.


This is a good addition; by using "|>" instead of "%>%" there should be
a chance to get operator precedence right.  That said, the ?Syntax help
topic hasn't been updated, so I'm not sure where it fits in.

There are some choices that take a little getting used to:

mtcars |> head
Error: The pipe operator requires a function call or an anonymous
function expression as RHS

(I need to say mtcars |> head() 

Re: [Rd] New pipe operator

2020-12-05 Thread Gabor Grothendieck
The construct utils::head  is not that common but bare functions are
very common and to make it harder to use the common case so that
the uncommon case is slightly easier is not desirable.

Also it is trivial to write this which does work:

mtcars %>% (utils::head)

On Sat, Dec 5, 2020 at 11:59 AM Hugh Parsonage  wrote:
>
> I'm surprised by the aversion to
>
> mtcars |> nrow
>
> over
>
> mtcars |> nrow()
>
> and I think the decision to disallow the former should be
> reconsidered.  The pipe operator is only going to be used when the rhs
> is a function, so there is no ambiguity with omitting the parentheses.
> If it's disallowed, it becomes inconsistent with other treatments like
> sapply(mtcars, typeof) where sapply(mtcars, typeof()) would just be
> noise.  I'm not sure why this decision was taken
>
> If the only issue is with the double (and triple) colon operator, then
> ideally `mtcars |> base::head` should resolve to `base::head(mtcars)`
> -- in other words, demote the precedence of |>
>
> Obviously (looking at the R-Syntax branch) this decision was
> considered, put into place, then dropped, but I can't see why
> precisely.
>
> Best,
>
>
> Hugh.
>
>
>
>
>
>
>
> On Sat, 5 Dec 2020 at 04:07, Deepayan Sarkar  
> wrote:
> >
> > On Fri, Dec 4, 2020 at 7:35 PM Duncan Murdoch  
> > wrote:
> > >
> > > On 04/12/2020 8:13 a.m., Hiroaki Yutani wrote:
> > > >>   Error: function '::' not supported in RHS call of a pipe
> > > >
> > > > To me, this error looks much more friendly than magrittr's error.
> > > > Some of them got too used to specify functions without (). This
> > > > is OK until they use `::`, but when they need to use it, it takes
> > > > hours to figure out why
> > > >
> > > > mtcars %>% base::head
> > > > #> Error in .::base : unused argument (head)
> > > >
> > > > won't work but
> > > >
> > > > mtcars %>% head
> > > >
> > > > works. I think this is a too harsh lesson for ordinary R users to
> > > > learn `::` is a function. I've been wanting for magrittr to drop the
> > > > support for a function name without () to avoid this confusion,
> > > > so I would very much welcome the new pipe operator's behavior.
> > > > Thank you all the developers who implemented this!
> > >
> > > I agree, it's an improvement on the corresponding magrittr error.
> > >
> > > I think the semantics of not evaluating the RHS, but treating the pipe
> > > as purely syntactical is a good decision.
> > >
> > > I'm not sure I like the recommended way to pipe into a particular 
> > > argument:
> > >
> > >mtcars |> subset(cyl == 4) |> \(d) lm(mpg ~ disp, data = d)
> > >
> > > or
> > >
> > >mtcars |> subset(cyl == 4) |> function(d) lm(mpg ~ disp, data = d)
> > >
> > > both of which are equivalent to
> > >
> > >mtcars |> subset(cyl == 4) |> (function(d) lm(mpg ~ disp, data = d))()
> > >
> > > It's tempting to suggest it should allow something like
> > >
> > >mtcars |> subset(cyl == 4) |> lm(mpg ~ disp, data = .)
> >
> > Which is really not that far off from
> >
> > mtcars |> subset(cyl == 4) |> \(.) lm(mpg ~ disp, data = .)
> >
> > once you get used to it.
> >
> > One consequence of the implementation is that it's not clear how
> > multiple occurrences of the placeholder would be interpreted. With
> > magrittr,
> >
> > sort(runif(10)) %>% ecdf(.)(.)
> > ## [1] 0.1 0.2 0.3 0.4 0.5 0.6 0.7 0.8 0.9 1.0
> >
> > This is probably what you would expect, if you expect it to work at all, 
> > and not
> >
> > ecdf(sort(runif(10)))(sort(runif(10)))
> >
> > There would be no such ambiguity with anonymous functions
> >
> > sort(runif(10)) |> \(.) ecdf(.)(.)
> >
> > -Deepayan
> >
> > > which would be expanded to something equivalent to the other versions:
> > > but that makes it quite a bit more complicated.  (Maybe _ or \. should
> > > be used instead of ., since those are not legal variable names.)
> > >
> > > I don't think there should be an attempt to copy magrittr's special
> > > casing of how . is used in determining whether to also include the
> > > previous value as first argument.
> > >
> > > Duncan Murdoch
> > >
> > >
> > > >
> > > > Best,
> > > > Hiroaki Yutani
> > > >
> > > > 2020年12月4日(金) 20:51 Duncan Murdoch :
> > > >>
> > > >> Just saw this on the R-devel news:
> > > >>
> > > >>
> > > >> R now provides a simple native pipe syntax ‘|>’ as well as a shorthand
> > > >> notation for creating functions, e.g. ‘\(x) x + 1’ is parsed as
> > > >> ‘function(x) x + 1’. The pipe implementation as a syntax transformation
> > > >> was motivated by suggestions from Jim Hester and Lionel Henry. These
> > > >> features are experimental and may change prior to release.
> > > >>
> > > >>
> > > >> This is a good addition; by using "|>" instead of "%>%" there should be
> > > >> a chance to get operator precedence right.  That said, the ?Syntax help
> > > >> topic hasn't been updated, so I'm not sure where it fits in.
> > > >>
> > > >> There are some choices that take a little getting used to:
> > > >>
> > > >>   > mtcars |> head
> > > 

Re: [Rd] New pipe operator

2020-12-05 Thread Hugh Parsonage
I'm surprised by the aversion to

mtcars |> nrow

over

mtcars |> nrow()

and I think the decision to disallow the former should be
reconsidered.  The pipe operator is only going to be used when the rhs
is a function, so there is no ambiguity with omitting the parentheses.
If it's disallowed, it becomes inconsistent with other treatments like
sapply(mtcars, typeof) where sapply(mtcars, typeof()) would just be
noise.  I'm not sure why this decision was taken

If the only issue is with the double (and triple) colon operator, then
ideally `mtcars |> base::head` should resolve to `base::head(mtcars)`
-- in other words, demote the precedence of |>

Obviously (looking at the R-Syntax branch) this decision was
considered, put into place, then dropped, but I can't see why
precisely.

Best,


Hugh.







On Sat, 5 Dec 2020 at 04:07, Deepayan Sarkar  wrote:
>
> On Fri, Dec 4, 2020 at 7:35 PM Duncan Murdoch  
> wrote:
> >
> > On 04/12/2020 8:13 a.m., Hiroaki Yutani wrote:
> > >>   Error: function '::' not supported in RHS call of a pipe
> > >
> > > To me, this error looks much more friendly than magrittr's error.
> > > Some of them got too used to specify functions without (). This
> > > is OK until they use `::`, but when they need to use it, it takes
> > > hours to figure out why
> > >
> > > mtcars %>% base::head
> > > #> Error in .::base : unused argument (head)
> > >
> > > won't work but
> > >
> > > mtcars %>% head
> > >
> > > works. I think this is a too harsh lesson for ordinary R users to
> > > learn `::` is a function. I've been wanting for magrittr to drop the
> > > support for a function name without () to avoid this confusion,
> > > so I would very much welcome the new pipe operator's behavior.
> > > Thank you all the developers who implemented this!
> >
> > I agree, it's an improvement on the corresponding magrittr error.
> >
> > I think the semantics of not evaluating the RHS, but treating the pipe
> > as purely syntactical is a good decision.
> >
> > I'm not sure I like the recommended way to pipe into a particular argument:
> >
> >mtcars |> subset(cyl == 4) |> \(d) lm(mpg ~ disp, data = d)
> >
> > or
> >
> >mtcars |> subset(cyl == 4) |> function(d) lm(mpg ~ disp, data = d)
> >
> > both of which are equivalent to
> >
> >mtcars |> subset(cyl == 4) |> (function(d) lm(mpg ~ disp, data = d))()
> >
> > It's tempting to suggest it should allow something like
> >
> >mtcars |> subset(cyl == 4) |> lm(mpg ~ disp, data = .)
>
> Which is really not that far off from
>
> mtcars |> subset(cyl == 4) |> \(.) lm(mpg ~ disp, data = .)
>
> once you get used to it.
>
> One consequence of the implementation is that it's not clear how
> multiple occurrences of the placeholder would be interpreted. With
> magrittr,
>
> sort(runif(10)) %>% ecdf(.)(.)
> ## [1] 0.1 0.2 0.3 0.4 0.5 0.6 0.7 0.8 0.9 1.0
>
> This is probably what you would expect, if you expect it to work at all, and 
> not
>
> ecdf(sort(runif(10)))(sort(runif(10)))
>
> There would be no such ambiguity with anonymous functions
>
> sort(runif(10)) |> \(.) ecdf(.)(.)
>
> -Deepayan
>
> > which would be expanded to something equivalent to the other versions:
> > but that makes it quite a bit more complicated.  (Maybe _ or \. should
> > be used instead of ., since those are not legal variable names.)
> >
> > I don't think there should be an attempt to copy magrittr's special
> > casing of how . is used in determining whether to also include the
> > previous value as first argument.
> >
> > Duncan Murdoch
> >
> >
> > >
> > > Best,
> > > Hiroaki Yutani
> > >
> > > 2020年12月4日(金) 20:51 Duncan Murdoch :
> > >>
> > >> Just saw this on the R-devel news:
> > >>
> > >>
> > >> R now provides a simple native pipe syntax ‘|>’ as well as a shorthand
> > >> notation for creating functions, e.g. ‘\(x) x + 1’ is parsed as
> > >> ‘function(x) x + 1’. The pipe implementation as a syntax transformation
> > >> was motivated by suggestions from Jim Hester and Lionel Henry. These
> > >> features are experimental and may change prior to release.
> > >>
> > >>
> > >> This is a good addition; by using "|>" instead of "%>%" there should be
> > >> a chance to get operator precedence right.  That said, the ?Syntax help
> > >> topic hasn't been updated, so I'm not sure where it fits in.
> > >>
> > >> There are some choices that take a little getting used to:
> > >>
> > >>   > mtcars |> head
> > >> Error: The pipe operator requires a function call or an anonymous
> > >> function expression as RHS
> > >>
> > >> (I need to say mtcars |> head() instead.)  This sometimes leads to error
> > >> messages that are somewhat confusing:
> > >>
> > >>   > mtcars |> magrittr::debug_pipe |> head
> > >> Error: function '::' not supported in RHS call of a pipe
> > >>
> > >> but
> > >>
> > >> mtcars |> magrittr::debug_pipe() |> head()
> > >>
> > >> works.
> > >>
> > >> Overall, I think this is a great addition, though it's going to be
> > >> disruptive for a while.
> > >>
> > >> Duncan Murdoch
> > 

Re: [Rd] New pipe operator

2020-12-04 Thread Duncan Murdoch

On 04/12/2020 12:06 p.m., Deepayan Sarkar wrote:

On Fri, Dec 4, 2020 at 7:35 PM Duncan Murdoch  wrote:


On 04/12/2020 8:13 a.m., Hiroaki Yutani wrote:

   Error: function '::' not supported in RHS call of a pipe


To me, this error looks much more friendly than magrittr's error.
Some of them got too used to specify functions without (). This
is OK until they use `::`, but when they need to use it, it takes
hours to figure out why

mtcars %>% base::head
#> Error in .::base : unused argument (head)

won't work but

mtcars %>% head

works. I think this is a too harsh lesson for ordinary R users to
learn `::` is a function. I've been wanting for magrittr to drop the
support for a function name without () to avoid this confusion,
so I would very much welcome the new pipe operator's behavior.
Thank you all the developers who implemented this!


I agree, it's an improvement on the corresponding magrittr error.

I think the semantics of not evaluating the RHS, but treating the pipe
as purely syntactical is a good decision.

I'm not sure I like the recommended way to pipe into a particular argument:

mtcars |> subset(cyl == 4) |> \(d) lm(mpg ~ disp, data = d)

or

mtcars |> subset(cyl == 4) |> function(d) lm(mpg ~ disp, data = d)

both of which are equivalent to

mtcars |> subset(cyl == 4) |> (function(d) lm(mpg ~ disp, data = d))()

It's tempting to suggest it should allow something like

mtcars |> subset(cyl == 4) |> lm(mpg ~ disp, data = .)


Which is really not that far off from

mtcars |> subset(cyl == 4) |> \(.) lm(mpg ~ disp, data = .)

once you get used to it.

One consequence of the implementation is that it's not clear how
multiple occurrences of the placeholder would be interpreted. With
magrittr,

sort(runif(10)) %>% ecdf(.)(.)
## [1] 0.1 0.2 0.3 0.4 0.5 0.6 0.7 0.8 0.9 1.0

This is probably what you would expect, if you expect it to work at all, and not

ecdf(sort(runif(10)))(sort(runif(10)))


I didn't suggest that.  That would be a bad.  All I suggested was 
different sugar to write (function(d) ecdf(d)(d))().


Duncan Murdoch



There would be no such ambiguity with anonymous functions

sort(runif(10)) |> \(.) ecdf(.)(.)

-Deepayan


which would be expanded to something equivalent to the other versions:
but that makes it quite a bit more complicated.  (Maybe _ or \. should
be used instead of ., since those are not legal variable names.)

I don't think there should be an attempt to copy magrittr's special
casing of how . is used in determining whether to also include the
previous value as first argument.

Duncan Murdoch




Best,
Hiroaki Yutani

2020年12月4日(金) 20:51 Duncan Murdoch :


Just saw this on the R-devel news:


R now provides a simple native pipe syntax ‘|>’ as well as a shorthand
notation for creating functions, e.g. ‘\(x) x + 1’ is parsed as
‘function(x) x + 1’. The pipe implementation as a syntax transformation
was motivated by suggestions from Jim Hester and Lionel Henry. These
features are experimental and may change prior to release.


This is a good addition; by using "|>" instead of "%>%" there should be
a chance to get operator precedence right.  That said, the ?Syntax help
topic hasn't been updated, so I'm not sure where it fits in.

There are some choices that take a little getting used to:

   > mtcars |> head
Error: The pipe operator requires a function call or an anonymous
function expression as RHS

(I need to say mtcars |> head() instead.)  This sometimes leads to error
messages that are somewhat confusing:

   > mtcars |> magrittr::debug_pipe |> head
Error: function '::' not supported in RHS call of a pipe

but

mtcars |> magrittr::debug_pipe() |> head()

works.

Overall, I think this is a great addition, though it's going to be
disruptive for a while.

Duncan Murdoch

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


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



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


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


Re: [Rd] New pipe operator

2020-12-04 Thread Deepayan Sarkar
On Fri, Dec 4, 2020 at 7:35 PM Duncan Murdoch  wrote:
>
> On 04/12/2020 8:13 a.m., Hiroaki Yutani wrote:
> >>   Error: function '::' not supported in RHS call of a pipe
> >
> > To me, this error looks much more friendly than magrittr's error.
> > Some of them got too used to specify functions without (). This
> > is OK until they use `::`, but when they need to use it, it takes
> > hours to figure out why
> >
> > mtcars %>% base::head
> > #> Error in .::base : unused argument (head)
> >
> > won't work but
> >
> > mtcars %>% head
> >
> > works. I think this is a too harsh lesson for ordinary R users to
> > learn `::` is a function. I've been wanting for magrittr to drop the
> > support for a function name without () to avoid this confusion,
> > so I would very much welcome the new pipe operator's behavior.
> > Thank you all the developers who implemented this!
>
> I agree, it's an improvement on the corresponding magrittr error.
>
> I think the semantics of not evaluating the RHS, but treating the pipe
> as purely syntactical is a good decision.
>
> I'm not sure I like the recommended way to pipe into a particular argument:
>
>mtcars |> subset(cyl == 4) |> \(d) lm(mpg ~ disp, data = d)
>
> or
>
>mtcars |> subset(cyl == 4) |> function(d) lm(mpg ~ disp, data = d)
>
> both of which are equivalent to
>
>mtcars |> subset(cyl == 4) |> (function(d) lm(mpg ~ disp, data = d))()
>
> It's tempting to suggest it should allow something like
>
>mtcars |> subset(cyl == 4) |> lm(mpg ~ disp, data = .)

Which is really not that far off from

mtcars |> subset(cyl == 4) |> \(.) lm(mpg ~ disp, data = .)

once you get used to it.

One consequence of the implementation is that it's not clear how
multiple occurrences of the placeholder would be interpreted. With
magrittr,

sort(runif(10)) %>% ecdf(.)(.)
## [1] 0.1 0.2 0.3 0.4 0.5 0.6 0.7 0.8 0.9 1.0

This is probably what you would expect, if you expect it to work at all, and not

ecdf(sort(runif(10)))(sort(runif(10)))

There would be no such ambiguity with anonymous functions

sort(runif(10)) |> \(.) ecdf(.)(.)

-Deepayan

> which would be expanded to something equivalent to the other versions:
> but that makes it quite a bit more complicated.  (Maybe _ or \. should
> be used instead of ., since those are not legal variable names.)
>
> I don't think there should be an attempt to copy magrittr's special
> casing of how . is used in determining whether to also include the
> previous value as first argument.
>
> Duncan Murdoch
>
>
> >
> > Best,
> > Hiroaki Yutani
> >
> > 2020年12月4日(金) 20:51 Duncan Murdoch :
> >>
> >> Just saw this on the R-devel news:
> >>
> >>
> >> R now provides a simple native pipe syntax ‘|>’ as well as a shorthand
> >> notation for creating functions, e.g. ‘\(x) x + 1’ is parsed as
> >> ‘function(x) x + 1’. The pipe implementation as a syntax transformation
> >> was motivated by suggestions from Jim Hester and Lionel Henry. These
> >> features are experimental and may change prior to release.
> >>
> >>
> >> This is a good addition; by using "|>" instead of "%>%" there should be
> >> a chance to get operator precedence right.  That said, the ?Syntax help
> >> topic hasn't been updated, so I'm not sure where it fits in.
> >>
> >> There are some choices that take a little getting used to:
> >>
> >>   > mtcars |> head
> >> Error: The pipe operator requires a function call or an anonymous
> >> function expression as RHS
> >>
> >> (I need to say mtcars |> head() instead.)  This sometimes leads to error
> >> messages that are somewhat confusing:
> >>
> >>   > mtcars |> magrittr::debug_pipe |> head
> >> Error: function '::' not supported in RHS call of a pipe
> >>
> >> but
> >>
> >> mtcars |> magrittr::debug_pipe() |> head()
> >>
> >> works.
> >>
> >> Overall, I think this is a great addition, though it's going to be
> >> disruptive for a while.
> >>
> >> Duncan Murdoch
> >>
> >> __
> >> R-devel@r-project.org mailing list
> >> https://stat.ethz.ch/mailman/listinfo/r-devel
> >
> > __
> > R-devel@r-project.org mailing list
> > https://stat.ethz.ch/mailman/listinfo/r-devel
> >
>
> __
> R-devel@r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-devel

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


Re: [Rd] New pipe operator

2020-12-04 Thread Sebastian Meyer
Am 04.12.20 um 15:05 schrieb Duncan Murdoch:
> On 04/12/2020 8:13 a.m., Hiroaki Yutani wrote:
>>>   Error: function '::' not supported in RHS call of a pipe
>>
>> To me, this error looks much more friendly than magrittr's error.
>> Some of them got too used to specify functions without (). This
>> is OK until they use `::`, but when they need to use it, it takes
>> hours to figure out why
>>
>> mtcars %>% base::head
>> #> Error in .::base : unused argument (head)
>>
>> won't work but
>>
>> mtcars %>% head
>>
>> works. I think this is a too harsh lesson for ordinary R users to
>> learn `::` is a function. I've been wanting for magrittr to drop the
>> support for a function name without () to avoid this confusion,
>> so I would very much welcome the new pipe operator's behavior.
>> Thank you all the developers who implemented this!
> 
> I agree, it's an improvement on the corresponding magrittr error.


Thank you for this example. I agree but think that the new base R pipe
might trigger some initial confusion as well:

mtcars |> function(x) dim(x)[1L]
#> [1] 32

mtcars |> nrow
#> Error: The pipe operator requires a function call or an anonymous
function expression as RHS

The RHS evaluates to the same thing in both cases (bar attributes and
environments), but only the anonymous variant is supported. I admit that
I haven't used %>% before; maybe the above discrepancy is less
irritating for those who have. The error message is clear though!

That said, I think the code is very readable when piping explicitly into
an anonymous function and I also prefer

mtcars |> nrow()

over mtcars |> nrow, because we are visibly calling something.

IMO, readability is lost when using the cryptic short-hand notation

mtcars |> \(x) dim(x)[1L]

which really only saves 7 letters.


> I think the semantics of not evaluating the RHS, but treating the pipe
> as purely syntactical is a good decision.
> 
> I'm not sure I like the recommended way to pipe into a particular argument:
> 
>   mtcars |> subset(cyl == 4) |> \(d) lm(mpg ~ disp, data = d)
> 
> or
> 
>   mtcars |> subset(cyl == 4) |> function(d) lm(mpg ~ disp, data = d)
> 
> both of which are equivalent to
> 
>   mtcars |> subset(cyl == 4) |> (function(d) lm(mpg ~ disp, data = d))()
> 
> It's tempting to suggest it should allow something like
> 
>   mtcars |> subset(cyl == 4) |> lm(mpg ~ disp, data = .)
> 
> which would be expanded to something equivalent to the other versions:
> but that makes it quite a bit more complicated.  (Maybe _ or \. should
> be used instead of ., since those are not legal variable names.)


I guess "_" as a placeholder would be difficult to implement precisely
because it currently is a syntax error.

Best regards,

Sebastian Meyer


> I don't think there should be an attempt to copy magrittr's special
> casing of how . is used in determining whether to also include the
> previous value as first argument.
> 
> Duncan Murdoch
> 
> 
>>
>> Best,
>> Hiroaki Yutani
>>
>> 2020年12月4日(金) 20:51 Duncan Murdoch :
>>>
>>> Just saw this on the R-devel news:
>>>
>>>
>>> R now provides a simple native pipe syntax ‘|>’ as well as a shorthand
>>> notation for creating functions, e.g. ‘\(x) x + 1’ is parsed as
>>> ‘function(x) x + 1’. The pipe implementation as a syntax transformation
>>> was motivated by suggestions from Jim Hester and Lionel Henry. These
>>> features are experimental and may change prior to release.
>>>
>>>
>>> This is a good addition; by using "|>" instead of "%>%" there should be
>>> a chance to get operator precedence right.  That said, the ?Syntax help
>>> topic hasn't been updated, so I'm not sure where it fits in.
>>>
>>> There are some choices that take a little getting used to:
>>>
>>>   > mtcars |> head
>>> Error: The pipe operator requires a function call or an anonymous
>>> function expression as RHS
>>>
>>> (I need to say mtcars |> head() instead.)  This sometimes leads to error
>>> messages that are somewhat confusing:
>>>
>>>   > mtcars |> magrittr::debug_pipe |> head
>>> Error: function '::' not supported in RHS call of a pipe
>>>
>>> but
>>>
>>> mtcars |> magrittr::debug_pipe() |> head()
>>>
>>> works.
>>>
>>> Overall, I think this is a great addition, though it's going to be
>>> disruptive for a while.
>>>
>>> Duncan Murdoch
>>>
>>> __
>>> R-devel@r-project.org mailing list
>>> https://stat.ethz.ch/mailman/listinfo/r-devel
>>
>> __
>> R-devel@r-project.org mailing list
>> https://stat.ethz.ch/mailman/listinfo/r-devel
>>
> 
> __
> R-devel@r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-devel

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


Re: [Rd] New pipe operator

2020-12-04 Thread Dénes Tóth



On 12/4/20 3:05 PM, Duncan Murdoch wrote:

...

It's tempting to suggest it should allow something like

   mtcars |> subset(cyl == 4) |> lm(mpg ~ disp, data = .)

which would be expanded to something equivalent to the other versions: 
but that makes it quite a bit more complicated.  (Maybe _ or \. should 
be used instead of ., since those are not legal variable names.)


I support the idea of using an underscore (_) as the placeholder symbol. 
 Syntactic sugars work the the best if 1) they require less keystrokes 
and/or 2) are easier to read compared to the "normal" syntax, and 3) can 
not lead to unexpected bugs (which is a major problem with the magrittr 
pipe). Using '_' fulfills all of these criteria since '_' can not clash 
with any variable in the environment.


Denes

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


Re: [Rd] New pipe operator

2020-12-04 Thread Duncan Murdoch

On 04/12/2020 8:13 a.m., Hiroaki Yutani wrote:

  Error: function '::' not supported in RHS call of a pipe


To me, this error looks much more friendly than magrittr's error.
Some of them got too used to specify functions without (). This
is OK until they use `::`, but when they need to use it, it takes
hours to figure out why

mtcars %>% base::head
#> Error in .::base : unused argument (head)

won't work but

mtcars %>% head

works. I think this is a too harsh lesson for ordinary R users to
learn `::` is a function. I've been wanting for magrittr to drop the
support for a function name without () to avoid this confusion,
so I would very much welcome the new pipe operator's behavior.
Thank you all the developers who implemented this!


I agree, it's an improvement on the corresponding magrittr error.

I think the semantics of not evaluating the RHS, but treating the pipe 
as purely syntactical is a good decision.


I'm not sure I like the recommended way to pipe into a particular argument:

  mtcars |> subset(cyl == 4) |> \(d) lm(mpg ~ disp, data = d)

or

  mtcars |> subset(cyl == 4) |> function(d) lm(mpg ~ disp, data = d)

both of which are equivalent to

  mtcars |> subset(cyl == 4) |> (function(d) lm(mpg ~ disp, data = d))()

It's tempting to suggest it should allow something like

  mtcars |> subset(cyl == 4) |> lm(mpg ~ disp, data = .)

which would be expanded to something equivalent to the other versions: 
but that makes it quite a bit more complicated.  (Maybe _ or \. should 
be used instead of ., since those are not legal variable names.)


I don't think there should be an attempt to copy magrittr's special 
casing of how . is used in determining whether to also include the 
previous value as first argument.


Duncan Murdoch




Best,
Hiroaki Yutani

2020年12月4日(金) 20:51 Duncan Murdoch :


Just saw this on the R-devel news:


R now provides a simple native pipe syntax ‘|>’ as well as a shorthand
notation for creating functions, e.g. ‘\(x) x + 1’ is parsed as
‘function(x) x + 1’. The pipe implementation as a syntax transformation
was motivated by suggestions from Jim Hester and Lionel Henry. These
features are experimental and may change prior to release.


This is a good addition; by using "|>" instead of "%>%" there should be
a chance to get operator precedence right.  That said, the ?Syntax help
topic hasn't been updated, so I'm not sure where it fits in.

There are some choices that take a little getting used to:

  > mtcars |> head
Error: The pipe operator requires a function call or an anonymous
function expression as RHS

(I need to say mtcars |> head() instead.)  This sometimes leads to error
messages that are somewhat confusing:

  > mtcars |> magrittr::debug_pipe |> head
Error: function '::' not supported in RHS call of a pipe

but

mtcars |> magrittr::debug_pipe() |> head()

works.

Overall, I think this is a great addition, though it's going to be
disruptive for a while.

Duncan Murdoch

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


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



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


Re: [Rd] New pipe operator

2020-12-04 Thread Hiroaki Yutani
>  Error: function '::' not supported in RHS call of a pipe

To me, this error looks much more friendly than magrittr's error.
Some of them got too used to specify functions without (). This
is OK until they use `::`, but when they need to use it, it takes
hours to figure out why

mtcars %>% base::head
#> Error in .::base : unused argument (head)

won't work but

mtcars %>% head

works. I think this is a too harsh lesson for ordinary R users to
learn `::` is a function. I've been wanting for magrittr to drop the
support for a function name without () to avoid this confusion,
so I would very much welcome the new pipe operator's behavior.
Thank you all the developers who implemented this!

Best,
Hiroaki Yutani

2020年12月4日(金) 20:51 Duncan Murdoch :
>
> Just saw this on the R-devel news:
>
>
> R now provides a simple native pipe syntax ‘|>’ as well as a shorthand
> notation for creating functions, e.g. ‘\(x) x + 1’ is parsed as
> ‘function(x) x + 1’. The pipe implementation as a syntax transformation
> was motivated by suggestions from Jim Hester and Lionel Henry. These
> features are experimental and may change prior to release.
>
>
> This is a good addition; by using "|>" instead of "%>%" there should be
> a chance to get operator precedence right.  That said, the ?Syntax help
> topic hasn't been updated, so I'm not sure where it fits in.
>
> There are some choices that take a little getting used to:
>
>  > mtcars |> head
> Error: The pipe operator requires a function call or an anonymous
> function expression as RHS
>
> (I need to say mtcars |> head() instead.)  This sometimes leads to error
> messages that are somewhat confusing:
>
>  > mtcars |> magrittr::debug_pipe |> head
> Error: function '::' not supported in RHS call of a pipe
>
> but
>
> mtcars |> magrittr::debug_pipe() |> head()
>
> works.
>
> Overall, I think this is a great addition, though it's going to be
> disruptive for a while.
>
> Duncan Murdoch
>
> __
> R-devel@r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-devel

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


[Rd] New pipe operator

2020-12-04 Thread Duncan Murdoch

Just saw this on the R-devel news:


R now provides a simple native pipe syntax ‘|>’ as well as a shorthand 
notation for creating functions, e.g. ‘\(x) x + 1’ is parsed as 
‘function(x) x + 1’. The pipe implementation as a syntax transformation 
was motivated by suggestions from Jim Hester and Lionel Henry. These 
features are experimental and may change prior to release.



This is a good addition; by using "|>" instead of "%>%" there should be 
a chance to get operator precedence right.  That said, the ?Syntax help 
topic hasn't been updated, so I'm not sure where it fits in.


There are some choices that take a little getting used to:

> mtcars |> head
Error: The pipe operator requires a function call or an anonymous 
function expression as RHS


(I need to say mtcars |> head() instead.)  This sometimes leads to error 
messages that are somewhat confusing:


> mtcars |> magrittr::debug_pipe |> head
Error: function '::' not supported in RHS call of a pipe

but

mtcars |> magrittr::debug_pipe() |> head()

works.

Overall, I think this is a great addition, though it's going to be 
disruptive for a while.


Duncan Murdoch

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