File 2881-beam_ssa_bc_size-Fix-two-bugs-that-would-crash-the-c.patch of Package erlang

From c26b10c661ac7e177967233c8b319c66e3356431 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Tue, 2 Feb 2021 08:47:50 +0100
Subject: [PATCH] beam_ssa_bc_size: Fix two bugs that would crash the compiler

---
 lib/compiler/src/beam_ssa_bc_size.erl  | 14 ++++++++---
 lib/compiler/test/bs_bincomp_SUITE.erl | 34 ++++++++++++++++++++++++++
 2 files changed, 45 insertions(+), 3 deletions(-)

diff --git a/lib/compiler/src/beam_ssa_bc_size.erl b/lib/compiler/src/beam_ssa_bc_size.erl
index 9af43f17d5..f795641592 100644
--- a/lib/compiler/src/beam_ssa_bc_size.erl
+++ b/lib/compiler/src/beam_ssa_bc_size.erl
@@ -244,8 +244,13 @@ update_successors(#b_br{bool=Bool,succ=Succ,fail=Fail}, Bs0, Map0) ->
             update_successor(Fail, maps:remove(Var, Bs0), Map);
         {'if',Var,TrueType,FalseType} ->
             Bs = maps:remove(Bool, Bs0),
-            Map = update_successor(Succ, Bs#{Var => TrueType}, Map0),
-            update_successor(Fail, Bs#{Var => FalseType}, Map);
+            case Var of
+                #b_var{} ->
+                    Map = update_successor(Succ, Bs#{Var => TrueType}, Map0),
+                    update_successor(Fail, Bs#{Var => FalseType}, Map);
+                #b_literal{} ->
+                    Bs
+            end;
         any ->
             Map = update_successor(Succ, Bs0#{Bool := #b_literal{val=true}}, Map0),
             update_successor(Fail, Bs0#{Bool := #b_literal{val=false}}, Map)
@@ -473,13 +478,16 @@ opt_expr_1({bif,'div'}=Op, [Numerator,#b_literal{val=Denominator}]=Args) ->
         opt_expr_div(Numerator, Denominator)
     catch
         throw:not_possible ->
-            case Denominator band (Denominator - 1) of
+            try Denominator band (Denominator - 1) of
                 0 ->
                     %% The denominator is a power of two.
                     Shift = round(math:log2(Denominator)),
                     {{bif,'bsr'},[Numerator,#b_literal{val=Shift}]};
                 _ ->
                     {Op,Args}
+            catch
+                _:_ ->
+                    {Op,Args}
             end
     end;
 opt_expr_1({bif,'*'}, [{{safe,_},_},#b_literal{val=0}=Zero]) ->
diff --git a/lib/compiler/test/bs_bincomp_SUITE.erl b/lib/compiler/test/bs_bincomp_SUITE.erl
index a3900c7a9a..d76d26e515 100644
--- a/lib/compiler/test/bs_bincomp_SUITE.erl
+++ b/lib/compiler/test/bs_bincomp_SUITE.erl
@@ -146,6 +146,9 @@ mixed(Config) when is_list(Config) ->
     <<1,2,3>> = cs_default(match_context_1(<<1,2,3>>)),
     <<4,5,6>> = cs_default(match_context_2(<<4,5,6>>)),
 
+    <<255>> = over_complex_generator(),
+    {'EXIT',_} = catch float_segment_size(),
+
     cs_end().
 
 mixed_nested(L) ->
@@ -186,6 +189,37 @@ match_context_2(<<B/binary>>) ->
 do_match_context_2(B) ->
     << <<V>> || <<V>> <= B >>.
 
+%% Would crash beam_ssa_bc_size when the no_copt option was given.
+over_complex_generator() ->
+    <<
+      <<255>> ||
+        <<0:2>> <= <<0:2>>,
+        <<_:8>> <=
+            case true of
+                true ->
+                    <<8>>;
+                [6.6 | bad_tail] ->
+                    ok;
+                [3 | 4] ->
+                    error
+            end
+    >>.
+
+float_segment_size() ->
+    try
+        V = 0.79
+    of
+        _ ->
+            %% Would crash beam_ssa_bc_size when trying to
+            %% interpret V * U = 0.79 * 8 as a size.
+            <<
+              0 || <<5.9:V/unit:8-float>> <= 42
+            >>
+    catch
+        _:_ ->
+            error
+    end.
+
 filters(Config) when is_list(Config) ->
     cs_init(),
     <<"BDF">> =
-- 
2.26.2

openSUSE Build Service is sponsored by