File 0362-beam_jump-Eliminate-undecided_allocation-failure.patch of Package erlang

From 63a2d6b7f966ef0c67ad653ce9e3086b173ea9e0 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Tue, 9 Feb 2021 08:33:01 +0100
Subject: [PATCH] beam_jump: Eliminate 'undecided_allocation' failure

---
 lib/compiler/src/beam_jump.erl        | 38 +++++++++++++++++++++++++--
 lib/compiler/test/beam_jump_SUITE.erl | 28 ++++++++++++++++++--
 2 files changed, 62 insertions(+), 4 deletions(-)

diff --git a/lib/compiler/src/beam_jump.erl b/lib/compiler/src/beam_jump.erl
index 56ffc8c949..b22cec7c1f 100644
--- a/lib/compiler/src/beam_jump.erl
+++ b/lib/compiler/src/beam_jump.erl
@@ -351,13 +351,16 @@ share_1([{label,L}=Lbl|Is], Safe, Dict0, Lbls0, [_|_]=Seq0, Acc) ->
         #{} ->
             %% This is first time we have seen this sequence of instructions.
             %% Find out whether it is safe to share the sequence.
-            case map_size(Safe) =:= 0 orelse is_shareable(Seq) of
+            case (map_size(Safe) =:= 0 orelse
+                  is_shareable(Seq)) andalso
+                unambigous_exit_call(Seq)
+            of
                 true ->
                     %% Either this function does not contain any try/catch
                     %% instructions, in which case it is always safe to share
                     %% exception-raising instructions such as if_end and
                     %% case_end, or it this sequence does not include
-                    %% any of the problematic instructions.
+                    %% any problematic instructions.
                     Dict = Dict0#{Seq => L},
                     share_1(Is, Safe, Dict, Lbls0, [], [[Lbl|Seq]|Acc]);
                 false ->
@@ -399,6 +402,37 @@ share_1([I|Is], Safe, Dict, Lbls, Seq, Acc) ->
 	    share_1(Is, Safe, Dict, Lbls, [I], Acc)
     end.
 
+unambigous_exit_call([{call_ext,A,{extfunc,M,F,A}}|Is]) ->
+    case erl_bifs:is_exit_bif(M, F, A) of
+        true ->
+            %% beam_validator requires that the size of the stack
+            %% frame is unambigously known when a function is called.
+            %%
+            %% That means that we must be careful when sharing function
+            %% calls.
+            %%
+            %% In practice, it seems that only exit BIFs can
+            %% potentially be shared in an unsafe way, and only in
+            %% rare circumstances. (See the undecided_allocation_1/1
+            %% function in beam_jump_SUITE.)
+            %%
+            %% To ensure that the frame size is unambigous, only allow
+            %% sharing of a call to exit BIFs if the call is followed
+            %% by an instruction that indicates the size of the stack
+            %% frame (that is almost always the case in real-world
+            %% code).
+            case Is of
+                [{deallocate,_}|_] -> true;
+                [return] -> true;
+                _ -> false
+            end;
+        false ->
+            true
+    end;
+unambigous_exit_call([_|Is]) ->
+    unambigous_exit_call(Is);
+unambigous_exit_call([]) -> true.
+
 %% If the label has a scope set, assign it to any line instruction
 %% in the sequence.
 maybe_add_scope(Seq, L, Safe) ->
diff --git a/lib/compiler/test/beam_jump_SUITE.erl b/lib/compiler/test/beam_jump_SUITE.erl
index 78f2e8b42a..569d0f7b26 100644
--- a/lib/compiler/test/beam_jump_SUITE.erl
+++ b/lib/compiler/test/beam_jump_SUITE.erl
@@ -23,7 +23,7 @@
 	 init_per_group/2,end_per_group/2,
 	 undefined_label/1,ambiguous_catch_try_state/1,
          unsafe_move_elimination/1,build_tuple/1,
-         coverage/1,call_sharing/1]).
+         coverage/1,call_sharing/1,undecided_allocation/1]).
 
 suite() ->
     [{ct_hooks,[ts_install_cth]}].
@@ -38,7 +38,8 @@ groups() ->
        unsafe_move_elimination,
        build_tuple,
        coverage,
-       call_sharing
+       call_sharing,
+       undecided_allocation
       ]}].
 
 init_per_suite(Config) ->
@@ -316,6 +317,29 @@ cs_1(Key) ->
 
 cs_2(I) -> I.
 
+undecided_allocation(_Config) ->
+    ok = catch undecided_allocation_1(<<10:(3*7)>>),
+    {'EXIT',{{badrecord,rec},_}} = catch undecided_allocation_1(8),
+    ok.
+
+-record(rec, {}).
+undecided_allocation_1(<<10:3/integer-unit:7>>) ->
+    ok;
+undecided_allocation_1(V) ->
+    %% The record update operation would be duplicated by the beam_ssa_bssm
+    %% pass, and beam_jump would incorrectly share the resulting calls to
+    %% error/1, causing beam_validator to issue the following diagnostic
+    %% when this module was compiled with the no_type_opt option:
+    %%
+    %%  Internal consistency check failed - please report this bug.
+    %%  Instruction: {call_ext,1,{extfunc,erlang,error,1}}
+    %%  Error:       {allocated,undecided}:
+
+    <<
+      <<0>> || <<0:V>> <= <<0>>
+    >>#rec{},
+    if whatever -> [] end.
+
 
 id(I) ->
     I.
-- 
2.26.2

openSUSE Build Service is sponsored by