File 1266-beam_ssa_bool-Fix-miscompilation-of-or-guards.patch of Package erlang

From 47d4f3543cee4353e333e669471dc125e45b570c Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Mon, 22 May 2023 15:01:21 +0200
Subject: [PATCH] beam_ssa_bool: Fix miscompilation of 'or' guards

Closes #7252
---
 lib/compiler/src/beam_ssa_bool.erl | 33 ++++++++++++++++++++++--------
 lib/compiler/test/guard_SUITE.erl  | 28 +++++++++++++++++++++++++
 2 files changed, 52 insertions(+), 9 deletions(-)

diff --git a/lib/compiler/src/beam_ssa_bool.erl b/lib/compiler/src/beam_ssa_bool.erl
index fb72a78c29..5cd281819c 100644
--- a/lib/compiler/src/beam_ssa_bool.erl
+++ b/lib/compiler/src/beam_ssa_bool.erl
@@ -126,7 +126,8 @@
              ldefs=#{},
              count :: beam_ssa:label(),
              dom,
-             uses}).
+             uses,
+             in_or=false :: boolean()}).
 
 -spec module(beam_ssa:b_module(), [compile:option()]) ->
                     {'ok',beam_ssa:b_module()}.
@@ -909,7 +910,7 @@ do_opt_digraph([A|As], G0, St) ->
         G ->
             do_opt_digraph(As, G, St)
     catch
-        throw:not_possible ->
+        throw:not_possible when not St#st.in_or ->
             do_opt_digraph(As, G0, St)
     end;
 do_opt_digraph([], G, _St) -> G.
@@ -923,19 +924,33 @@ opt_digraph_instr(#b_set{dst=Dst}=I, G0, St) ->
         #b_set{op={bif,'and'},args=Args} ->
             G2 = convert_to_br_node(I, Succ, G1, St),
             {First,Second} = order_args(Args, G2, St),
+            case St of
+                #st{in_or=true} ->
+                    %% This code is part of the left-hand side operand
+                    %% of `or`.  The optimization is unsafe if there
+                    %% any instructions that may fail.
+                    ensure_no_failing_instructions(First, Second, G1, St);
+                #st{} ->
+                    ok
+            end,
             G = redirect_test(First, {fail,Fail}, G2, St),
             redirect_test(Second, {fail,Fail}, G, St);
         #b_set{op={bif,'or'},args=Args} ->
             {First,Second} = order_args(Args, G1, St),
 
-            %% Here we give up the optimization if the optimization
-            %% would skip instructions that may fail. A possible
-            %% future improvement would be to hoist the failing
-            %% instructions so that they would always be executed.
+            %% Here we give up if the optimization would skip
+            %% instructions that may fail in the right-hand side
+            %% operand.
             ensure_no_failing_instructions(First, Second, G1, St),
 
             G2 = convert_to_br_node(I, Succ, G1, St),
-            G = redirect_test(First, {succ,Succ}, G2, St),
+
+            %% Be sure to give up if the left-hand side operation of
+            %% the `or` has a failing operation thay may be
+            %% skipped. Example:
+            %%
+            %%   f(_, B) when ((ok == B) and (ok =/= trunc(ok))) or (ok < B) -> ...
+            G = redirect_test(First, {succ,Succ}, G2, St#st{in_or=true}),
             redirect_test(Second, {fail,Fail}, G, St);
         #b_set{op={bif,'xor'}} ->
             %% Rewriting 'xor' is not practical. Fortunately,
@@ -999,8 +1014,8 @@ convert_to_br_node(I, Target, G0, St) ->
 
 %% ensure_no_failing_instructions(First, Second, G, St) -> ok.
 %%  Ensure that there are no instructions that can fail that would not
-%%  be executed if right-hand side of the `or` would be skipped. That
-%%  means that the `or` could succeed when it was supposed to
+%%  be executed if right-hand side of the operation would be skipped. That
+%%  means that the operation could succeed when it was supposed to
 %%  fail. Example:
 %%
 %%    (element(1, T) =:= tag) or
diff --git a/lib/compiler/test/guard_SUITE.erl b/lib/compiler/test/guard_SUITE.erl
index 1a96fa4b6c..b0124be476 100644
--- a/lib/compiler/test/guard_SUITE.erl
+++ b/lib/compiler/test/guard_SUITE.erl
@@ -2314,6 +2314,7 @@ beam_bool_SUITE(_Config) ->
     gh4788(),
     gh_6164(),
     gh_6184(),
+    gh_7252(),
     ok.
 
 before_and_inside_if() ->
@@ -2831,6 +2832,33 @@ gh_6184() ->
 do_gh_6184(V1, V2) when (false and is_tuple(V2)) andalso (V1 orelse V2) ->
     V2 orelse V2.
 
+gh_7252() ->
+    bar = gh_7252_a(id(bar), id([])),
+    bar = gh_7252_a(id(bar), id(ok)),
+
+    foo = gh_7252_b(id(ok), id(<<>>)),
+    bar = gh_7252_b(id(ok), id(ok)),
+
+    bar = gh_7252_c(id(ok)),
+
+    ok.
+
+gh_7252_a(_, B) when ((ok == B) and (ok =/= trunc(ok))) or (ok < B) ->
+    foo;
+gh_7252_a(A, _) ->
+    A.
+
+gh_7252_b(A, B)
+  when (true xor is_float(A)) or (is_bitstring(B) orelse <<(ok):(ok)>>) ->
+    foo;
+gh_7252_b(_, _) ->
+    bar.
+
+gh_7252_c(A) when ((ok > A) and ((bnot ok) =:= ok)) or (not (ok > A)) ->
+    foo;
+gh_7252_c(_) ->
+    bar.
+
 %%%
 %%% End of beam_bool_SUITE tests.
 %%%
-- 
2.35.3

openSUSE Build Service is sponsored by