File 4852-Avoid-optimization-that-beam_validator-might-conside.patch of Package erlang

From 589631210aadcb046452c9b27045261a79632bfa Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Tue, 30 May 2023 16:01:08 +0200
Subject: [PATCH 2/2] Avoid optimization that beam_validator might consider
 unsafe

Eliminating a repeated `=:=` test can result in code that
beam_validator doesn't consider safe. This commit makes the optimization
keep the `=:=` if it seems to be significant, that is, if one or both
operands will gain type information from it.

That makes it possible to compile code from #6599 such as:

    f(X, X) when is_integer(X) ->
        ok;
    f(Y, Y = #{}) ->
        Y#{ok := ok}.

(Six other examples from #6599 can now also be compiled.)

Running `scripts/diffable` shows that this fix prevented the
optimization in 14 modules (out of about 1000).

Closes #6599
---
 lib/compiler/src/beam_ssa_dead.erl   | 43 +++++++++++++-
 lib/compiler/test/beam_ssa_SUITE.erl | 87 +++++++++++++++++++++++++++-
 2 files changed, 125 insertions(+), 5 deletions(-)

diff --git a/lib/compiler/src/beam_ssa_dead.erl b/lib/compiler/src/beam_ssa_dead.erl
index 27a6baaab4..0319dd600e 100644
--- a/lib/compiler/src/beam_ssa_dead.erl
+++ b/lib/compiler/src/beam_ssa_dead.erl
@@ -1176,9 +1176,19 @@ opt_redundant_tests_is([#b_set{op=Op,args=Args,dst=Bool}=I0], Tests, Acc) ->
         {Test,MustInvert} ->
             case old_result(Test, Tests) of
                 Result0 when is_boolean(Result0) ->
-                    Result = #b_literal{val=Result0 xor MustInvert},
-                    I = I0#b_set{op={bif,'=:='},args=[Result,#b_literal{val=true}]},
-                    {old_test,reverse(Acc, [I]),Bool,Result};
+                    case gains_type_information(I0) of
+                        false ->
+                            Result = #b_literal{val=Result0 xor MustInvert},
+                            I = I0#b_set{op={bif,'=:='},args=[Result,#b_literal{val=true}]},
+                            {old_test,reverse(Acc, [I]),Bool,Result};
+                        true ->
+                            %% At least one variable will gain type
+                            %% information from this `=:=`
+                            %% operation. Removing it could make it
+                            %% impossible for beam_validator to
+                            %% realize that the code is type-safe.
+                            none
+                    end;
                 none ->
                     {new_test,Bool,Test,MustInvert}
             end
@@ -1187,6 +1197,33 @@ opt_redundant_tests_is([I|Is], Tests, Acc) ->
     opt_redundant_tests_is(Is, Tests, [I|Acc]);
 opt_redundant_tests_is([], _Tests, _Acc) -> none.
 
+%% Will any of the variables gain type information from this
+%% operation?
+gains_type_information(#b_set{anno=Anno,op={bif,'=:='},args=Args}) ->
+    Types0 = maps:get(arg_types, Anno, #{}),
+    Types = complete_type_information(Args, 0, Types0),
+    case map_size(Types) of
+        0 ->
+            false;
+        1 ->
+            true;
+        2 ->
+            case Types of
+                #{0 := Same,1 := Same} ->
+                    false;
+                #{} ->
+                    true
+            end
+    end;
+gains_type_information(#b_set{}) -> false.
+
+complete_type_information([#b_literal{val=Value}|As], N, Types) ->
+    Type = beam_types:make_type_from_value(Value),
+    complete_type_information(As, N+1, Types#{N => Type});
+complete_type_information([#b_var{}|As], N, Types) ->
+    complete_type_information(As, N+1, Types);
+complete_type_information([], _, Types) -> Types.
+
 old_result(Test, Tests) ->
     case Tests of
         #{Test := Val} -> Val;
diff --git a/lib/compiler/test/beam_ssa_SUITE.erl b/lib/compiler/test/beam_ssa_SUITE.erl
index 1076daa23b..08c32e87b0 100644
--- a/lib/compiler/test/beam_ssa_SUITE.erl
+++ b/lib/compiler/test/beam_ssa_SUITE.erl
@@ -26,7 +26,8 @@
          beam_ssa_dead_crash/1,stack_init/1,
          mapfoldl/0,mapfoldl/1,
          grab_bag/1,redundant_br/1,
-         coverage/1]).
+         coverage/1,
+         gh_6599/1]).
 
 suite() -> [{ct_hooks,[ts_install_cth]}].
 
@@ -47,7 +48,8 @@ groups() ->
        stack_init,
        grab_bag,
        redundant_br,
-       coverage
+       coverage,
+       gh_6599
       ]}].
 
 init_per_suite(Config) ->
@@ -1153,5 +1155,87 @@ coverage_3() ->
     get(),
     ok.
 
+%% GH-6599. beam_validator would not realize that the code was safe.
+gh_6599(_Config) ->
+    ok = gh_6599_1(id(42), id(42)),
+    #{ok := ok} = gh_6599_1(id(#{ok => 0}), id(#{ok => 0})),
+
+    {'EXIT',{{try_clause,#{ok:=ok}},_}} =
+        catch gh_6599_2(id(whatever), id(#{0 => whatever})),
+
+    ok = gh_6599_3(id(true), id(true)),
+    {'EXIT',{function_clause,_}} = catch gh_6599_3(id(false), id(false)),
+    0.0 = gh_6599_3(id(0.0), id(0.0)),
+
+    {'EXIT',{{badmatch,true},_}} = catch gh_6599_4(id(false)),
+
+    {'EXIT',{{badmatch,ok},_}} = catch gh_6599_5(id([a]), id(#{0 => [a]}), id([a])),
+
+    #{ok := ok} = gh_6599_6(id(#{}), id(#{})),
+    {'EXIT',{{badmap,a},_}} = catch gh_6599_6(id(a), id(a)),
+
+    {'EXIT',{{badarg,ok},_}} = catch gh_6599_7(id([a]), id([a])),
+
+    ok.
+
+gh_6599_1(X, X) when is_integer(X) ->
+    ok;
+gh_6599_1(Y, Y = #{}) ->
+    Y#{ok := ok}.
+
+gh_6599_2(X, #{0 := X, 0 := Y}) ->
+    try #{ok => ok} of
+        Y ->
+            bnot (Y = X)
+    after
+        ok
+    end.
+
+gh_6599_3(X, X) when X ->
+    ok;
+gh_6599_3(X, X = 0.0) ->
+    X + X.
+
+gh_6599_4(X) ->
+    Y =
+        try
+            false = X
+        catch
+            _ ->
+                ok
+        end /= ok,
+    X = Y,
+    false = Y,
+    0 = ok.
+
+%% Crashes in beam_ssa_type because a type assertion fails.
+gh_6599_5(X, #{0 := X, 0 := Y}, Y=[_ | _]) ->
+    try
+        Y = ok
+    catch
+        _ ->
+            [_ | []] = Y = X
+    end.
+
+gh_6599_6(A, B = A) ->
+    A#{},
+    case A of B -> B end#{ok => ok}.
+
+gh_6599_7(X, Y) ->
+    try Y of
+        X ->
+            (id(
+                try ([_ | _] = Y) of
+                    X ->
+                        ok
+                after
+                    ok
+                end
+            ) orelse X) bsl 0
+    after
+        ok
+    end.
+
+
 %% The identity function.
 id(I) -> I.
-- 
2.35.3

openSUSE Build Service is sponsored by