File 2453-compiler-Eliminate-crash-in-the-beam_ssa_bsm-pass.patch of Package erlang

From cba322b2fab260d1ac8fe45fbbfb75358a2e6710 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Wed, 2 Nov 2022 13:02:32 +0100
Subject: [PATCH] compiler: Eliminate crash in the beam_ssa_bsm pass

Closes #6410
---
 lib/compiler/src/beam_ssa_bsm.erl    | 25 ++++++++++++++++++----
 lib/compiler/test/bs_match_SUITE.erl | 31 ++++++++++++++++++++++++----
 2 files changed, 48 insertions(+), 8 deletions(-)

diff --git a/lib/compiler/src/beam_ssa_bsm.erl b/lib/compiler/src/beam_ssa_bsm.erl
index f84ae7dced..71736b3bc0 100644
--- a/lib/compiler/src/beam_ssa_bsm.erl
+++ b/lib/compiler/src/beam_ssa_bsm.erl
@@ -473,10 +473,27 @@ combine_matches(#b_function{bs=Blocks0,cnt=Counter0}=F, ModInfo) ->
             %% so we can reuse the RPO computed for Blocks0.
             Blocks2 = beam_ssa:rename_vars(State#cm.renames, RPO, Blocks1),
 
-            {Blocks, Counter} = alias_matched_binaries(Blocks2, Counter0,
-                                                       State#cm.match_aliases),
-
-            F#b_function{ bs=beam_ssa:trim_unreachable(Blocks),
+            %% Replacing variables with the atom `true` can cause
+            %% branches to phi nodes to be omitted, with the phi nodes
+            %% still referencing the unreachable blocks. Therefore,
+            %% trim now to update the phi nodes.
+            Blocks3 = beam_ssa:trim_unreachable(Blocks2),
+
+            Aliases = State#cm.match_aliases,
+            {Blocks4, Counter} = alias_matched_binaries(Blocks3, Counter0,
+                                                        Aliases),
+            Blocks = if
+                         map_size(Aliases) =:= 0 ->
+                             %% No need to trim because there were no aliases.
+                             Blocks4;
+                         true ->
+                             %% Play it safe. It is unclear whether
+                             %% the call to alias_matched_binaries/3
+                             %% could ever make any blocks
+                             %% unreachable.
+                             beam_ssa:trim_unreachable(Blocks4)
+                     end,
+            F#b_function{ bs=Blocks,
                           cnt=Counter };
         false ->
             F
diff --git a/lib/compiler/test/bs_match_SUITE.erl b/lib/compiler/test/bs_match_SUITE.erl
index 0ab2566cf8..1b4d73f642 100644
--- a/lib/compiler/test/bs_match_SUITE.erl
+++ b/lib/compiler/test/bs_match_SUITE.erl
@@ -48,7 +48,8 @@
          exceptions_after_match_failure/1,
          bad_phi_paths/1,many_clauses/1,
          combine_empty_segments/1,hangs_forever/1,
-         bs_saved_position_units/1,empty_matches/1]).
+         bs_saved_position_units/1,empty_matches/1,
+         gh_6410/1]).
 
 -export([coverage_id/1,coverage_external_ignore/2]).
 
@@ -87,7 +88,8 @@ groups() ->
        matching_meets_apply,bs_start_match2_defs,
        exceptions_after_match_failure,bad_phi_paths,
        many_clauses,combine_empty_segments,hangs_forever,
-       bs_saved_position_units,empty_matches]}].
+       bs_saved_position_units,empty_matches,
+       gh_6410]}].
 
 init_per_suite(Config) ->
     test_lib:recompile(?MODULE),
@@ -2502,8 +2504,6 @@ em_3(<<V:0/binary,Rest/bits>>) ->
 
 em_3_1(I) -> I.
 
-id(I) -> I.
-
 %% GH-6426/OTP-xxxxx
 em_4(<<X:0, _:X>>, <<Y:0, _:Y>>) ->
     ok.
@@ -2641,3 +2641,26 @@ many_clauses(_Config) ->
 
 one_clause(I) ->
     ?Q(<<"{_@I@,<<L:8,Val:L>>} -> _@I@ + Val">>).
+
+%% GH-6410: Fix crash in beam_ssa_bsm.
+gh_6410(_Config) ->
+    0 = do_gh_6410(<<42>>),
+    {'EXIT',{{case_clause,<<>>},[_|_]}} = catch do_gh_6410(<<>>),
+    {'EXIT',{{case_clause,a},[_|_]}} = catch do_gh_6410(a),
+    {'EXIT',{badarith,[_|_]}} = catch do_gh_6410([]),
+
+    ok.
+
+do_gh_6410(<<_>>) ->
+    0;
+do_gh_6410(X) ->
+    +(case X of
+        <<_>> ->
+            X;
+        [] ->
+            X
+    end).
+
+%%% Utilities.
+id(I) -> I.
+
-- 
2.35.3

openSUSE Build Service is sponsored by