otp icon indicating copy to clipboard operation
otp copied to clipboard

EEP 70: Implement non-skipping generators (as an experimental feature)

Open dszoboszlay opened this issue 1 year ago • 15 comments

First of all, this is a big PR and it's not 100% completed either. However, I'd like to get some feedback from you on how to proceed. I'll try to explain everything in this description.

What's in this PR?

  • The first two commits are minor fixes that are not strictly related to the rest of the PR. These could go on to the maint branch too, and if you're ok with them, I can create a separate PR for them. However, I also need these commits here to avoid merge conflicts with adjacent changes.
  • The bulk of the work is in the [WIP] labelled commit: I'm implementing a new language feature, non-skipping generators, for the comprehensions that corresponds to EEP 70, outline in erlang/eep#62. I wanted to do this as an experimental feature, so it could be dropped if nobody else likes my idea (a quick informal survey across my colleagues showed that they would like to have it, but they are not a representative sample of the Erlang community), but I have questions about how experimental features are intended to work. More on that below.
  • Finally, the last commit is the result of running ./otp_build update_primary (because I changed files in stdlib and compiler too). Here my question is whether I'm supposed to check in these compiled modules myself? I thought you may rather want to run this step in a trusted environment (like in CI) instead of on my laptop, but I'm not familiar with the process.

What are non-skipping generators?

Currently existing generators are "skipping": they ignore terms in the right-hand side expression that do not match the left-hand side pattern. Non-skipping generators on the other hand fail with exception badmatch.

The motivation for non-skipping generators is that skipping generators can hide the presence of unexpected elements in the input data of a comprehension. For example consider the below snippet:

[{User, Email} || #{user := User, email := Email} <- all_users()]

This list comprehension would skip users that don't have an email address. This may be an issue if we suspect potentially incorrect input data, like in case all_users/0 would read the users from a JSON file. Therefore cautious code that would prefer crashing instead of silently skipping incorrect input would have to use a more verbose map function:

lists:map(fun(#{user := User, email := Email}) -> {User, Email} end,
          all_users())

Unlike the generator, the anonymous function would crash on a user without an email address. Non-skipping generators would allow similar semantics in comprehensions too:

[{User, Email} || #{user := User, email := Email} <-:- all_users()]

This generator would crash (with a badmatch error) if the pattern wouldn't match an element of the list.

Syntactically non-skipping generators use <-:- (for lists and maps) and <=:= (for binaries) instead of <- and <=. This syntax was chosen because <-:- and <=:= resemble the =:= operator that tests whether two terms match. Since <-:- and <=:= were invalid syntax in previous versions of Erlang, they avoid backward compatibility issues.

Nevertheless, I aim to add non-skipping generators as an experimental feature, that has to be explicitly enabled:

 -feature(non_skipping_generators,enable).

What is left to do?

While I've already declared the non_skipping_generators feature, in practice it doesn't work (the feature is never disabled), because I'm not sure how to best implement the feature check?

The only feature Erlang had so far introduced a new keyword, maybe, and made it possible to enable/disable the feature based on this keyword. Namely epp:parse_file/2 gained a new reserved_word_fun option that allows customizing what unquoted atoms should be treated as keywords. erl_features also assumes features may introduce new keywords and has API-s for dealing with them.

However, the non-skipping generator features doesn't introduce any new features, but new operators: <-:- and <=:=. Neither erl_features nor epp:parse_file/2 are prepared to deal with new operators unfortunately.

I see a number of possible ways forward, but I'd need some guidance on which one would you prefer (or if you have a better idea):

  • Make new operators a first-class citizen in erl_features. On one hand this would make sense, since I believe features introducing new operators are not less likely to come than features introducing new keywords. However, erl_scan currently implements a hand-rolled scanner (I guess for performance reasons) that would be quite hard to change to accept arbitrary new operators returned by the erl_features module.
  • An other option would be to pass down to erl_scan the list of currently enabled features too. Then the logic about what operators to support per feature could be baked in to the hand-rolled scanner code.
  • A third option would be to allow the scanner to always accept optional operators, and raise an error in a later stage of the compilation. But I don't know which phase would be suitable?

The issue of features and operators aside I'd need some feedback on whether I found all the places of the code base to update? I based my work on #5411 and the various PR-s related to the introduction of map comprehensions, but this is my first PR changing the language itself, so I may very well have missed something. And there are places, like the erlang.el Emacs code where I'm basically just shooting in the dark (I have no experience with writing Emacs Lisp at all).

Finally, I verified that the tests I changed do pass, but haven't run the entire OTP test suite myself. I'll keep an eye on CI results of course!

dszoboszlay avatar Jun 28 '24 14:06 dszoboszlay

CT Test Results

     8 files     578 suites   2h 6m 2s :stopwatch:  4 432 tests  4 312 :white_check_mark: 119 :zzz: 1 :x: 10 515 runs  10 369 :white_check_mark: 145 :zzz: 1 :x:

For more details on these failures, see this check.

Results for commit 46f14959.

:recycle: This comment has been updated with latest results.

To speed up review, make sure that you have read Contributing to Erlang/OTP and that all checks pass.

See the TESTING and DEVELOPMENT HowTo guides for details about how to run test locally.

Artifacts

// Erlang/OTP Github Action Bot

github-actions[bot] avatar Jun 28 '24 14:06 github-actions[bot]

I see only one test failure here:

/buildroot/otp/Erlang ∅⊤℞/lib/stdlib-6.0/src/peer.erl:51:2: can't find moduledoc file "../doc/src/peer.md"
%   51| -moduledoc({file, "../doc/src/peer.md"}).
%     |  ^

Doesn't seem to be related to my changes?

dszoboszlay avatar Jun 28 '24 16:06 dszoboszlay

Created an EEP about the proposed feature: erlang/eep#62

dszoboszlay avatar Jul 02 '24 05:07 dszoboszlay

Updated with syntax proposed by @kikofernandez : <:- and <:=

dszoboszlay avatar Aug 24 '24 22:08 dszoboszlay

I will look at this once the EEP is approved and we have some feedback from the community I will wait a week or so to see if we can gather feedback from ErlangForums and other places.

Thanks for your contribution

kikofernandez avatar Aug 29 '24 07:08 kikofernandez

Sorry for the delay. We will schedule an internal discussion in two weeks time. Expect news after two weeks.

kikofernandez avatar Sep 16 '24 08:09 kikofernandez

OTB has approved this PR (see this Erlang Forum post).

Please remove the code defining this as a feature. Also remove the update of the primary bootstrap; we will take care of that.

bjorng avatar Oct 03 '24 15:10 bjorng

Thank you for the approval! I'll probably have time next week to make the requested changes.

dszoboszlay avatar Oct 03 '24 15:10 dszoboszlay

I've done the requested changes:

  • Changed the name to strict/relaxed generators.
  • Removed the feature declaration
  • Removed the update of the primary bootstrap
  • Moved one (very tiny) commit to its separate PR, #8933
  • Rebased the branch to current master

dszoboszlay avatar Oct 12 '24 15:10 dszoboszlay

I've now started to take a closer look at your code.

When looking at the difference in the generated code for this branch (using $ERL_TOP/scripts/diffable):

https://github.com/bjorng/otp/tree/bjorn/use-strict-generators

I noticed that changing <= to <:= made a huge difference in code size:

diff -u 0/beam_types.S 1/beam_types.S
--- 0/beam_types.S	2024-10-18 07:16:56
+++ 1/beam_types.S	2024-10-18 09:33:18
@@ -32,7 +32,7 @@
 
 {attributes, []}.
 
-{labels, 763}.
+{labels, 766}.
 
 
 {function, meet, 1, {meet,1}}.
@@ -8185,7 +8185,8 @@
   {label,{'-convert_ext/2-lbc$^0/2-0-',2}}.
     {'%',{var_info,{x,0},[accepts_match_context]}}.
     {'%',{var_info,{x,1},[{type,{t_bitstring,16,true}}]}}.
-    {test,bs_start_match3,{f,6},2,[{x,0}],{x,2}}.
+    {test,bs_start_match3,{f,7},2,[{x,0}],{x,2}}.
+    {bs_get_position,{x,2},{x,0},3}.
     {bs_match,{f,5},
               {x,2},
               {commands,[{ensure_at_least,144,1},
@@ -8261,13 +8262,35 @@
     {move,{x,2},{x,0}}.
     {call_only,2,{f,{'-convert_ext/2-lbc$^0/2-0-',2}}}. % '-convert_ext/2-lbc$^0/2-0-'/2
   {label,5}.
+    {bs_set_position,{x,2},{x,0}}.
+    {line,[{location,"/Users/bjorng/git/otp/lib/compiler/src/beam_types.erl",
+                     1483}]}.
+    {gc_bif,bit_size,{f,0},3,[{tr,{x,2},{t_bs_context,1}}],{x,0}}.
+    {test,is_ge,
+          {f,6},
+          [{tr,{x,0},{t_integer,{0,288230376151711743}}},{integer,1}]}.
+    {bs_get_tail,{x,2},{x,0},3}.
+    {test_heap,3,1}.
+    {put_tuple2,{x,0},{list,[{atom,badmatch},{x,0}]}}.
+    {call_ext_only,1,{extfunc,erlang,error,1}}.
+  {label,6}.
     {move,{x,1},{x,0}}.
     return.
-  {label,6}.
+  {label,7}.
+    {gc_bif,bit_size,{f,8},2,[{x,0}],{x,2}}.
+    {test,is_ge,
+          {f,8},
+          [{tr,{x,2},{t_integer,{0,288230376151711743}}},{integer,1}]}.
     {test_heap,3,1}.
+    {put_tuple2,{x,0},{list,[{atom,badmatch},{x,0}]}}.
+    {call_ext_only,1,{extfunc,erlang,error,1}}.
+  {label,8}.
+    {test,is_bitstr,{f,9},[{x,0}]}.
+    {move,{x,1},{x,0}}.
+    return.
+  {label,9}.
+    {test_heap,3,1}.
     {put_tuple2,{x,0},{list,[{atom,bad_generator},{x,0}]}}.
-    {line,[{location,"/Users/bjorng/git/otp/lib/compiler/src/beam_types.erl",
-                     1483}]}.
     {call_ext_only,1,{extfunc,erlang,error,1}}.

Some increase in code size is unavoidable, but I think this code can be improved. Consider this function:

s(Bin) ->
    [A || <<A:16>> <:= Bin].

Translating your Core Erlang code to its nearest equivalent Erlang code, it looks like this:

s_pr(Bin) ->
    case Bin of
        <<A:16,T/bitstring>> ->
            [A|s_pr(T)];
        Other when bit_size(Other) > 0 ->
            error({badmatch,Other});
        <<_/bitstring>> ->
            []
    end.

I suggest the following, which will result in shorter and simpler BEAM code than s_pr/1:

s_bjorn(Bin) ->
    case Bin of
        <<A:16,T/bitstring>> ->
            [A|s_bjorn(T)];
        <<>> ->
            [];
        Other ->
            error({badmatch,Other})
    end.

bjorng avatar Oct 18 '24 12:10 bjorng

I noticed that changing <= to <:= made a huge difference in code size

Good catch! I rewrote the generated code to look like this on your example:

s_fixed(Bin) ->
    case Bin of
        <<A:16,T/bitstring>> ->
            [A|s_fixed(T)];
        <<T/bitstring>> when T =/= <<>> ->
            error({badmatch, T});
        <<_/bitstring>> ->
            [];
        Other ->
            error({bad_generator, Other});
    end.

It's a bit more verbose than s_bjorn/1, but the final assembly code seems to be nice and compact:

{function, '-s_fixed/1-lc$^0/1-0-', 1, 19}.
  {label,18}.
    {line,[{location,"test.erl",15}]}.
    {func_info,{atom,test},{atom,'-s_fixed/1-lc$^0/1-0-'},1}.
  {label,19}.
    {'%',{var_info,{x,0},[accepts_match_context]}}.
    {test,bs_start_match3,{f,22},1,[{x,0}],{x,1}}.
    {bs_get_position,{x,1},{x,0},2}.
    {bs_match,{f,20},
              {x,1},
              {commands,[{ensure_at_least,16,1},
                         {integer,2,{literal,[]},16,1,{x,0}}]}}.
    {allocate,1,2}.
    {move,{x,0},{y,0}}.
    {move,{x,1},{x,0}}.
    {call,1,{f,19}}. % '-s_fixed/1-lc$^0/1-0-'/1
    {'%',{var_info,{x,0},[{type,{t_list,{t_integer,{0,65535}},nil}}]}}.
    {test_heap,2,1}.
    {put_list,{y,0},{x,0},{x,0}}.
    {deallocate,1}.
    return.
  {label,20}.
    {bs_set_position,{x,1},{x,0}}.
    {bs_get_tail,{x,1},{x,0},2}.
    {test,is_eq_exact,
          {f,21},
          [{tr,{x,0},{t_bitstring,1,false}},{literal,<<>>}]}.
    {move,nil,{x,0}}.
    return.
  {label,21}.
    {test_heap,3,1}.
    {put_tuple2,{x,0},{list,[{atom,badmatch},{x,0}]}}.
    {call_ext_only,1,{extfunc,erlang,error,1}}.
  {label,22}.
    {test_heap,3,1}.
    {put_tuple2,{x,0},{list,[{atom,bad_generator},{x,0}]}}.
    {call_ext_only,1,{extfunc,erlang,error,1}}.

dszoboszlay avatar Oct 19 '24 23:10 dszoboszlay

I don't see how the tprof_SUITE:call_count_ad_hoc/1 failure could be caused by this change. Feels like a net_kernel tick event was also captured by the profiler.

dszoboszlay avatar Oct 20 '24 20:10 dszoboszlay

I don't see how the tprof_SUITE:call_count_ad_hoc/1 failure could be caused by this change. Feels like a net_kernel tick event was also captured by the profiler.

That test has been failing sporadically in our internal builds over the last 10 days. It's very likely a separate issue, not caused by your change.

lucioleKi avatar Oct 20 '24 20:10 lucioleKi

Good catch! I rewrote the generated code to look like this on your example

That's look much better. It will still create one unnecessary binary in the success case, but I'll accept it. @lucioleKi or I might revisit this in the future when this PR and the zip generators PR have been merged.

I pushed a commit with a few nit-picky changes: breaking some lines, eliminating TABs on touched lines, and fixing broken indentation near touched lines.

If you accept these changes, please squash the last four commits and force-push. (It seems that the first commit should remain a separate.)

bjorng avatar Oct 21 '24 07:10 bjorng

Thanks for the fixes! Squashed & pushed.

dszoboszlay avatar Oct 21 '24 19:10 dszoboszlay