File 2882-beam_jump-Don-t-share-bs_init_writable-if-stack-size.patch of Package erlang

From 584fc905075a5eac15bd6ad6d0564e701cc0cbfd Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?John=20H=C3=B6gberg?= <john@erlang.org>
Date: Tue, 20 Dec 2022 16:45:14 +0100
Subject: [PATCH 2/2] beam_jump: Don't share bs_init_writable if stack size is
 unknown

---
 lib/compiler/src/beam_jump.erl        | 39 ++++++++++++++++++---------
 lib/compiler/test/beam_jump_SUITE.erl | 18 +++++++++++++
 2 files changed, 44 insertions(+), 13 deletions(-)

diff --git a/lib/compiler/src/beam_jump.erl b/lib/compiler/src/beam_jump.erl
index 6d3a04b3b3..90672bab7c 100644
--- a/lib/compiler/src/beam_jump.erl
+++ b/lib/compiler/src/beam_jump.erl
@@ -407,30 +407,43 @@ share_1([I|Is], Safe, Dict, Lbls, Seq, Acc) ->
 	    share_1(Is, Safe, Dict, Lbls, [I], Acc)
     end.
 
-unambigous_deallocation([{call_ext,_,_}|Is]) ->
+unambigous_deallocation([{bs_init,_,bs_init_writable,_,_,_}|Is]) ->
     %% beam_validator requires that the size of the stack frame is
-    %% unambigously known when a function is called.
+    %% unambigously known when certain instructions are used.
     %%
-    %% That means that we must be careful when sharing function calls.
+    %% That means that we must be careful when sharing them.
     %%
     %% To ensure that the frame size is unambigous, only allow sharing
     %% of calls if the call is followed by instructions that
     %% indicates the size of the stack frame.
     find_deallocation(Is);
+unambigous_deallocation([{call_ext,_,_}|Is]) ->
+    find_deallocation(Is);
 unambigous_deallocation([{call,_,_}|Is]) ->
     find_deallocation(Is);
 unambigous_deallocation([_|Is]) ->
     unambigous_deallocation(Is);
-unambigous_deallocation([]) -> true.
-
-find_deallocation([{line,_}|Is]) -> find_deallocation(Is);
-find_deallocation([{call,_,_}|Is]) -> find_deallocation(Is);
-find_deallocation([{call_ext,_,_}|Is]) -> find_deallocation(Is);
-find_deallocation([{init_yregs,_}|Is]) -> find_deallocation(Is);
-find_deallocation([{block,_}|Is]) -> find_deallocation(Is);
-find_deallocation([{deallocate,_}|_]) -> true;
-find_deallocation([return]) -> true;
-find_deallocation(_) -> false.
+unambigous_deallocation([]) ->
+    true.
+
+find_deallocation([{block,_}|Is]) ->
+    find_deallocation(Is);
+find_deallocation([{bs_init,_,bs_init_writable,_,_,_}|Is]) ->
+    find_deallocation(Is);
+find_deallocation([{call,_,_}|Is]) ->
+    find_deallocation(Is);
+find_deallocation([{call_ext,_,_}|Is]) ->
+    find_deallocation(Is);
+find_deallocation([{deallocate,_}|_]) ->
+    true;
+find_deallocation([{init_yregs,_}|Is]) ->
+    find_deallocation(Is);
+find_deallocation([{line,_}|Is]) ->
+    find_deallocation(Is);
+find_deallocation([return]) ->
+    true;
+find_deallocation(_) ->
+    false.
 
 %% If the label has a scope set, assign it to any line instruction
 %% in the sequence.
diff --git a/lib/compiler/test/beam_jump_SUITE.erl b/lib/compiler/test/beam_jump_SUITE.erl
index f90eec9446..8475aa096b 100644
--- a/lib/compiler/test/beam_jump_SUITE.erl
+++ b/lib/compiler/test/beam_jump_SUITE.erl
@@ -329,6 +329,9 @@ undecided_allocation(_Config) ->
     {'EXIT',_} = catch undecided_allocation_2(id(foobar)),
     {'EXIT',_} = catch undecided_allocation_2(id(make_ref())),
 
+    ok = undecided_allocation_3(id(<<0>>), gurka),
+    {'EXIT', {badarith, _}} = catch undecided_allocation_3(id(<<>>), gurka),
+
     ok.
 
 -record(rec, {}).
@@ -381,6 +384,21 @@ undecided_allocation_2(Order) ->
                 error
         end.
 
+%% GH-6571: bs_init_writable can only be shared when the stack frame size is
+%% known.
+undecided_allocation_3(<<_>>, _) ->
+    ok;
+undecided_allocation_3(X, _) ->
+    case 0 + get_keys() of
+        X ->
+            ok;
+        _ ->
+            (node() orelse garbage_collect()) =:=
+                case <<0 || false>> of
+                    #{} ->
+                        ok
+                end
+    end.
 
 id(I) ->
     I.
-- 
2.35.3

openSUSE Build Service is sponsored by