R has long supported user defined binary (infix) functions, defined
with `%fun%`. A one line change [1] to R's grammar allows users to
define unary (prefix) functions in the same manner.
    `%chr%` <- function(x) as.character(x)
    `%identical%` <- function(x, y) identical(x, y)
    %chr% 100
    #> [1] "100"
    %chr% 100 %identical% "100"
    #> [1] TRUE
This seems a natural extension of the existing functionality and
requires only a minor change to the grammar. If this change seems
acceptable I am happy to provide a complete patch with suitable tests
and documentation.
[1]:
Index: src/main/gram.y
==================================================================---
src/main/gram.y     (revision 72358)
+++ src/main/gram.y     (working copy)
@@ -357,6 +357,7 @@
        |       '+' expr %prec UMINUS           { $$ = xxunary($1,$2);
 setId( $$, @$); }
        |       '!' expr %prec UNOT             { $$ = xxunary($1,$2);
 setId( $$, @$); }
        |       '~' expr %prec TILDE            { $$ = xxunary($1,$2);
 setId( $$, @$); }
+       |       SPECIAL expr                    { $$ = xxunary($1,$2);
 setId( $$, @$); }
        |       '?' expr                        { $$ = xxunary($1,$2);
 setId( $$, @$); }
        |       expr ':'  expr                  { $$ xxbinary($2,$1,$3);
setId( $$, @$); }
Jim, This seems cool. Thanks for proposing it. To be concrete, he user-defined unary operations would be of the same precedence (or just slightly below?) built-in unary ones? So "100" %identical% %chr% 100 would work and return TRUE under your patch? And with %num% <- as.numeric, then 1 + - %num% "5" would also be legal (though quite ugly imo) and work? Best, ~G On Thu, Mar 16, 2017 at 7:24 AM, Jim Hester <james.f.hester at gmail.com> wrote:> R has long supported user defined binary (infix) functions, defined > with `%fun%`. A one line change [1] to R's grammar allows users to > define unary (prefix) functions in the same manner. > > `%chr%` <- function(x) as.character(x) > `%identical%` <- function(x, y) identical(x, y) > > %chr% 100 > #> [1] "100" > > %chr% 100 %identical% "100" > #> [1] TRUE > > This seems a natural extension of the existing functionality and > requires only a minor change to the grammar. If this change seems > acceptable I am happy to provide a complete patch with suitable tests > and documentation. > > [1]: > Index: src/main/gram.y > ==================================================================> --- src/main/gram.y (revision 72358) > +++ src/main/gram.y (working copy) > @@ -357,6 +357,7 @@ > | '+' expr %prec UMINUS { $$ = xxunary($1,$2); > setId( $$, @$); } > | '!' expr %prec UNOT { $$ = xxunary($1,$2); > setId( $$, @$); } > | '~' expr %prec TILDE { $$ = xxunary($1,$2); > setId( $$, @$); } > + | SPECIAL expr { $$ = xxunary($1,$2); > setId( $$, @$); } > | '?' expr { $$ = xxunary($1,$2); > setId( $$, @$); } > > | expr ':' expr { $$ > xxbinary($2,$1,$3); setId( $$, @$); } > > ______________________________________________ > R-devel at r-project.org mailing list > https://stat.ethz.ch/mailman/listinfo/r-devel >-- Gabriel Becker, PhD Associate Scientist (Bioinformatics) Genentech Research [[alternative HTML version deleted]]
Gabe,
The unary functions have the same precedence as normal SPECIALS
(although the new unary forms take precedence over binary SPECIALS).
So they are lower precedence than unary + and -. Yes, both of your
examples are valid with this patch, here are the results and quoted
forms to see the precedence.
    `%chr%` <- function(x) as.character(x)
    `%identical%` <- function(x, y) identical(x, y)
    quote("100" %identical% %chr% 100)
    #>  "100" %identical% (`%chr%`(100))
    "100" %identical% %chr% 100
    #> [1] TRUE
    `%num%` <- as.numeric
    quote(1 + - %num% "5")
    #> 1 + -(`%num%`("5"))
    1 + - %num% "5"
    #> [1] -4
Jim
On Thu, Mar 16, 2017 at 12:01 PM, Gabriel Becker <gmbecker at ucdavis.edu>
wrote:> Jim,
>
> This seems cool. Thanks for proposing it. To be concrete, he user-defined
> unary operations would be of the same precedence (or just slightly below?)
> built-in unary ones? So
>
> "100" %identical% %chr% 100
>
> would work and return TRUE under your patch?
>
> And  with %num% <- as.numeric, then
>
> 1 + - %num% "5"
>
> would also be legal (though quite ugly imo) and work?
>
> Best,
> ~G
>
> On Thu, Mar 16, 2017 at 7:24 AM, Jim Hester <james.f.hester at
gmail.com>
> wrote:
>>
>> R has long supported user defined binary (infix) functions, defined
>> with `%fun%`. A one line change [1] to R's grammar allows users to
>> define unary (prefix) functions in the same manner.
>>
>>     `%chr%` <- function(x) as.character(x)
>>     `%identical%` <- function(x, y) identical(x, y)
>>
>>     %chr% 100
>>     #> [1] "100"
>>
>>     %chr% 100 %identical% "100"
>>     #> [1] TRUE
>>
>> This seems a natural extension of the existing functionality and
>> requires only a minor change to the grammar. If this change seems
>> acceptable I am happy to provide a complete patch with suitable tests
>> and documentation.
>>
>> [1]:
>> Index: src/main/gram.y
>>
==================================================================>> ---
src/main/gram.y     (revision 72358)
>> +++ src/main/gram.y     (working copy)
>> @@ -357,6 +357,7 @@
>>         |       '+' expr %prec UMINUS           { $$ =
xxunary($1,$2);
>>  setId( $$, @$); }
>>         |       '!' expr %prec UNOT             { $$ =
xxunary($1,$2);
>>  setId( $$, @$); }
>>         |       '~' expr %prec TILDE            { $$ =
xxunary($1,$2);
>>  setId( $$, @$); }
>> +       |       SPECIAL expr                    { $$ = xxunary($1,$2);
>>  setId( $$, @$); }
>>         |       '?' expr                        { $$ =
xxunary($1,$2);
>>  setId( $$, @$); }
>>
>>         |       expr ':'  expr                  { $$ >>
xxbinary($2,$1,$3);      setId( $$, @$); }
>>
>> ______________________________________________
>> R-devel at r-project.org mailing list
>> https://stat.ethz.ch/mailman/listinfo/r-devel
>
>
>
>
> --
> Gabriel Becker, PhD
> Associate Scientist (Bioinformatics)
> Genentech Research
I don't have a positive or negative opinion on this yet, but I do have a question. If I define both unary and binary operators with the same name (in different frames, presumably), what would happen? Is "a %chr% b" a syntax error if unary %chr% is found first? If both might be found, does "a %chr% %chr% b" mean "%chr%(a, %chr% b)", or is it a syntax error (like typing "a %chr%(%chr%(b))" would be)? Duncan Murdoch On 16/03/2017 10:24 AM, Jim Hester wrote:> R has long supported user defined binary (infix) functions, defined > with `%fun%`. A one line change [1] to R's grammar allows users to > define unary (prefix) functions in the same manner. > > `%chr%` <- function(x) as.character(x) > `%identical%` <- function(x, y) identical(x, y) > > %chr% 100 > #> [1] "100" > > %chr% 100 %identical% "100" > #> [1] TRUE > > This seems a natural extension of the existing functionality and > requires only a minor change to the grammar. If this change seems > acceptable I am happy to provide a complete patch with suitable tests > and documentation. > > [1]: > Index: src/main/gram.y > ==================================================================> --- src/main/gram.y (revision 72358) > +++ src/main/gram.y (working copy) > @@ -357,6 +357,7 @@ > | '+' expr %prec UMINUS { $$ = xxunary($1,$2); > setId( $$, @$); } > | '!' expr %prec UNOT { $$ = xxunary($1,$2); > setId( $$, @$); } > | '~' expr %prec TILDE { $$ = xxunary($1,$2); > setId( $$, @$); } > + | SPECIAL expr { $$ = xxunary($1,$2); > setId( $$, @$); } > | '?' expr { $$ = xxunary($1,$2); > setId( $$, @$); } > > | expr ':' expr { $$ > xxbinary($2,$1,$3); setId( $$, @$); } > > ______________________________________________ > R-devel at r-project.org mailing list > https://stat.ethz.ch/mailman/listinfo/r-devel >
This works the same way as `?` is defined in R code, and `-`, `+`
(defined in C) do now, you define one function that handles calls with
both unary and binary arguments.
    quote(a %f% %f% b)
    #> a %f% (`%f%`(b))
    `%f%` <- function(a, b) if (missing(b)) { force(a);
cat("unary\n")
} else { force(a);force(b);cat("binary\n") }
    a <- 1
    b <- 2
    a %f% %f% b
    #> unary
    #> binary
This also brings up the point about what happens to existing user
defined functions such as `%in%` when they are used as unary functions
(likely by mistake). Happily this provides a useful error when run
assuming no default value of the second argument.
    %in% a
    #> Error in match(x, table, nomatch = 0L) :
    #>   argument "table" is missing, with no default
On Thu, Mar 16, 2017 at 7:13 PM, Duncan Murdoch
<murdoch.duncan at gmail.com> wrote:> I don't have a positive or negative opinion on this yet, but I do have
a
> question.  If I define both unary and binary operators with the same name
> (in different frames, presumably), what would happen?
>
> Is "a %chr% b" a syntax error if unary %chr% is found first?  If
both might
> be found, does "a %chr% %chr% b" mean "%chr%(a, %chr%
b)", or is it a syntax
> error (like typing "a %chr%(%chr%(b))" would be)?
>
> Duncan Murdoch
>
>
>
>
>
> On 16/03/2017 10:24 AM, Jim Hester wrote:
>>
>> R has long supported user defined binary (infix) functions, defined
>> with `%fun%`. A one line change [1] to R's grammar allows users to
>> define unary (prefix) functions in the same manner.
>>
>>     `%chr%` <- function(x) as.character(x)
>>     `%identical%` <- function(x, y) identical(x, y)
>>
>>     %chr% 100
>>     #> [1] "100"
>>
>>     %chr% 100 %identical% "100"
>>     #> [1] TRUE
>>
>> This seems a natural extension of the existing functionality and
>> requires only a minor change to the grammar. If this change seems
>> acceptable I am happy to provide a complete patch with suitable tests
>> and documentation.
>>
>> [1]:
>> Index: src/main/gram.y
>>
==================================================================>> ---
src/main/gram.y     (revision 72358)
>> +++ src/main/gram.y     (working copy)
>> @@ -357,6 +357,7 @@
>>         |       '+' expr %prec UMINUS           { $$ =
xxunary($1,$2);
>>  setId( $$, @$); }
>>         |       '!' expr %prec UNOT             { $$ =
xxunary($1,$2);
>>  setId( $$, @$); }
>>         |       '~' expr %prec TILDE            { $$ =
xxunary($1,$2);
>>  setId( $$, @$); }
>> +       |       SPECIAL expr                    { $$ = xxunary($1,$2);
>>  setId( $$, @$); }
>>         |       '?' expr                        { $$ =
xxunary($1,$2);
>>  setId( $$, @$); }
>>
>>         |       expr ':'  expr                  { $$ >>
xxbinary($2,$1,$3);      setId( $$, @$); }
>>
>> ______________________________________________
>> R-devel at r-project.org mailing list
>> https://stat.ethz.ch/mailman/listinfo/r-devel
>>
>