File 0405-Fix-compiler-crash-for-binary-matching-in-receive.patch of Package erlang

From 5053917fd9fb76cf8dc8aa5fb1dae63d7d6c6aaf Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Mon, 3 Oct 2022 15:37:49 +0200
Subject: [PATCH] Fix compiler crash for binary matching in receive

Closes #6341
---
 lib/compiler/src/beam_ssa.erl             |  4 +-
 lib/compiler/src/beam_ssa_pre_codegen.erl | 57 ++++++++++++++++++-----
 lib/compiler/test/receive_SUITE.erl       | 21 ++++++++-
 3 files changed, 66 insertions(+), 16 deletions(-)

diff --git a/lib/compiler/src/beam_ssa.erl b/lib/compiler/src/beam_ssa.erl
index e07a38ca85..5037811614 100644
--- a/lib/compiler/src/beam_ssa.erl
+++ b/lib/compiler/src/beam_ssa.erl
@@ -635,8 +635,8 @@ rename_vars(Rename, Labels, Blocks) when is_map(Rename)->
         end,
     map_instrs_1(Labels, F, Blocks).
 
-%% split_blocks(Predicate, Blocks0, Count0) -> {Blocks,Count}.
-%%  Call Predicate(Instruction) for each instruction in all
+%% split_blocks(Labels, Predicate, Blocks0, Count0) -> {Blocks,Count}.
+%%  Call Predicate(Instruction) for each instruction in the given
 %%  blocks. If Predicate/1 returns true, split the block
 %%  before this instruction.
 
diff --git a/lib/compiler/src/beam_ssa_pre_codegen.erl b/lib/compiler/src/beam_ssa_pre_codegen.erl
index 498fd8ce64..bb9aa75797 100644
--- a/lib/compiler/src/beam_ssa_pre_codegen.erl
+++ b/lib/compiler/src/beam_ssa_pre_codegen.erl
@@ -1338,16 +1338,17 @@ fix_receives(#st{ssa=Blocks0,cnt=Count0}=St) ->
 fix_receives_1([{L,Blk}|Ls], Blocks0, Count0) ->
     case Blk of
         #b_blk{is=[#b_set{op=peek_message}|_]} ->
-            Rm = find_rm_blocks(L, Blocks0),
-            LoopExit = find_loop_exit(Rm, Blocks0),
-            RPO = beam_ssa:rpo([L], Blocks0),
-            Defs0 = beam_ssa:def(RPO, Blocks0),
-            CommonUsed = recv_common(Defs0, LoopExit, Blocks0),
-            {Blocks1,Count1} = recv_crit_edges(Rm, LoopExit, Blocks0, Count0),
-            {Blocks2,Count2} = recv_fix_common(CommonUsed, LoopExit, Rm,
-                                               Blocks1, Count1),
+            Rm0 = find_rm_blocks(L, Blocks0),
+            {Rm,Blocks1,Count1} = split_rm_blocks(Rm0, Blocks0, Count0, []),
+            LoopExit = find_loop_exit(Rm, Blocks1),
+            RPO = beam_ssa:rpo([L], Blocks1),
+            Defs0 = beam_ssa:def(RPO, Blocks1),
+            CommonUsed = recv_common(Defs0, LoopExit, Blocks1),
+            {Blocks2,Count2} = recv_crit_edges(Rm, LoopExit, Blocks1, Count1),
+            {Blocks3,Count3} = recv_fix_common(CommonUsed, LoopExit, Rm,
+                                               Blocks2, Count2),
             Defs = ordsets:subtract(Defs0, CommonUsed),
-            {Blocks,Count} = fix_receive(Rm, Defs, Blocks2, Count2),
+            {Blocks,Count} = fix_receive(Rm, Defs, Blocks3, Count3),
             fix_receives_1(Ls, Blocks, Count);
         #b_blk{} ->
             fix_receives_1(Ls, Blocks0, Count0)
@@ -1355,6 +1356,38 @@ fix_receives_1([{L,Blk}|Ls], Blocks0, Count0) ->
 fix_receives_1([], Blocks, Count) ->
     {Blocks,Count}.
 
+split_rm_blocks([L|Ls], Blocks0, Count0, Acc) ->
+    #b_blk{is=Is} = map_get(L, Blocks0),
+    case need_split(Is) of
+        false ->
+            %% Don't split because there are no unsafe instructions.
+            split_rm_blocks(Ls, Blocks0, Count0, [L|Acc]);
+        true ->
+            %% An unsafe instruction, such as `bs_get_tail`, was
+            %% found. Split the block before `remove_message`.
+            P = fun(#b_set{op=Op}) ->
+                        Op =:= remove_message
+                end,
+            Next = Count0,
+            {Blocks,Count} = beam_ssa:split_blocks([L], P, Blocks0, Count0),
+            true = Count0 =/= Count,            %Assertion.
+            split_rm_blocks(Ls, Blocks, Count, [Next|Acc])
+    end;
+split_rm_blocks([], Blocks, Count, Acc) ->
+    {reverse(Acc),Blocks,Count}.
+
+need_split([#b_set{op=Op}|T]) ->
+    case Op of
+        %% Unnecessarily splitting the block can introduce extra
+        %% `move` instructions, so we will avoid splitting as long
+        %% there are only known safe instructions before the
+        %% `remove_message` instruction.
+        get_tuple_element -> need_split(T);
+        recv_marker_clear -> need_split(T);
+        remove_message -> false;
+        _ -> true
+    end.
+
 recv_common(_Defs, none, _Blocks) ->
     %% There is no common exit block because receive is used
     %% in the tail position of a function.
@@ -1443,7 +1476,7 @@ recv_fix_common_1([V|Vs], [Rm|Rms], Msg, Blocks0) ->
     Blocks1 = beam_ssa:rename_vars(Ren, RPO, Blocks0),
     #b_blk{is=Is0} = Blk0 = map_get(Rm, Blocks1),
     Copy = #b_set{op=copy,dst=V,args=[Msg]},
-    Is = insert_after_phis(Is0, [Copy]),
+    Is = [Copy|Is0],
     Blk = Blk0#b_blk{is=Is},
     Blocks = Blocks1#{Rm:=Blk},
     recv_fix_common_1(Vs, Rms, Msg, Blocks);
@@ -1478,8 +1511,8 @@ fix_receive([L|Ls], Defs, Blocks0, Count0) ->
     Ren = zip(Used, NewVars),
     Blocks1 = beam_ssa:rename_vars(Ren, RPO, Blocks0),
     #b_blk{is=Is0} = Blk1 = map_get(L, Blocks1),
-    CopyIs = [#b_set{op=copy,dst=New,args=[Old]} || {Old,New} <- Ren],
-    Is = insert_after_phis(Is0, CopyIs),
+    Is = [#b_set{op=copy,dst=New,args=[Old]} ||
+             {Old,New} <- Ren] ++ Is0,
     Blk = Blk1#b_blk{is=Is},
     Blocks = Blocks1#{L:=Blk},
     fix_receive(Ls, Defs, Blocks, Count);
diff --git a/lib/compiler/test/receive_SUITE.erl b/lib/compiler/test/receive_SUITE.erl
index a99443c419..5b52dd8288 100644
--- a/lib/compiler/test/receive_SUITE.erl
+++ b/lib/compiler/test/receive_SUITE.erl
@@ -29,7 +29,8 @@
          match_built_terms/1,elusive_common_exit/1,
          return_before_receive/1,trapping/1,
          after_expression/1,in_after/1,
-         type_optimized_markers/1]).
+         type_optimized_markers/1,
+         bs_get_tail/1]).
 
 -include_lib("common_test/include/ct.hrl").
 
@@ -53,7 +54,8 @@ groups() ->
        match_built_terms,elusive_common_exit,
        return_before_receive,trapping,
        after_expression,in_after,
-       type_optimized_markers]},
+       type_optimized_markers,
+       bs_get_tail]},
      {slow,[],[ref_opt]}].
 
 init_per_suite(Config) ->
@@ -897,6 +899,21 @@ tom_2(Ref) ->
             gaffel
     end.
 
+bs_get_tail(_Config) ->
+    Ref = make_ref(),
+    self() ! {<<1,"abc">>, Ref},
+    {<<"abc">>,Ref} = do_bs_get_tail(),
+
+    ok.
+
+do_bs_get_tail() ->
+    receive
+        {<<1, FieldsBin/bits>>, StreamRef} ->
+            A = id(FieldsBin),
+            B = id(StreamRef),
+            {A,B}
+    end.
+
 %%%
 %%% Common utilities.
 %%%
-- 
2.35.3

openSUSE Build Service is sponsored by