File 1242-Fix-code-generation-in-guard-for-not-X-true.patch of Package erlang

From 3452b8ccbb6dbc5cfa0a9c3436a2bd1f08ffa793 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Mon, 28 Jun 2021 08:16:03 +0200
Subject: [PATCH] Fix code generation in guard for not (X =:= true)

In a guard, `not (X =:= true)` would incorrectly evaluate to `false`
for non-boolean values of `X`.

The reason for the bug is an unsafe transformation in the `v3_core`
pass that transforms `not (X =:= true)` to `X =:= false`. That
transformation is safe only if `not (X =:= true)` was transformed from
`not X` by the compiler itself. (This bug was introduced in OTP R13.)

Eliminate the problem by only doing the transformation when `X =:= true`
is known to have been expanded from `not X` by the compiler.

While at it, also improve the comments.

Fixes #5007.
---
 lib/compiler/src/v3_core.erl                  | 58 +++++++++++++++----
 lib/compiler/test/guard_SUITE.erl             |  4 ++
 .../indent_SUITE_data/results/guard_warnings  |  4 +-
 .../small_SUITE_data/results/guard_warnings   |  2 +-
 4 files changed, 54 insertions(+), 14 deletions(-)

diff --git a/lib/compiler/src/v3_core.erl b/lib/compiler/src/v3_core.erl
index 396ae6f25d..ffdcea18a2 100644
--- a/lib/compiler/src/v3_core.erl
+++ b/lib/compiler/src/v3_core.erl
@@ -380,7 +380,7 @@ gexpr({call,Line,{remote,_,{atom,_,erlang},{atom,_,'not'}},[A]}, Bools, St) ->
 gexpr(E0, Bools, St0) ->
     gexpr_test(E0, Bools, St0).
 
-%% gexpr_not(L, R, Bools, State) -> {Cexpr,[PreExp],Bools,State}.
+%% gexpr_bool(L, R, Bools, State) -> {Cexpr,[PreExp],Bools,State}.
 %%  Generate a guard for boolean operators
 
 gexpr_bool(Op, L, R, Bools0, St0, Line) ->
@@ -400,13 +400,32 @@ gexpr_bool(Op, L, R, Bools0, St0, Line) ->
 gexpr_not(A, Bools0, St0, Line) ->
     {Ae0,Aps,Bools,St1} = gexpr(A, Bools0, St0),
     case Ae0 of
-        #icall{module=#c_literal{val=erlang},
+        #icall{anno=#a{anno=[v3_core,compiler_generated]},
+               module=#c_literal{val=erlang},
                name=#c_literal{val='=:='},
                args=[E,#c_literal{val=true}]}=EqCall ->
             %%
-            %% Doing the following transformation
-            %%    not(Expr =:= true)  ==>  Expr =:= false
-            %% will help eliminating redundant is_boolean/1 tests.
+            %% We here have the expression:
+            %%
+            %%    not(Expr =:= true)
+            %%
+            %% The annotations tested in the code above guarantees
+            %% that the original expression in the Erlang source
+            %% code was:
+            %%
+            %%    not Expr
+            %%
+            %% That expression can be transformed as follows:
+            %%
+            %%    not Expr  ==>  Expr =:= false
+            %%
+            %% which will produce the same result, but may eliminate
+            %% redundant is_boolean/1 tests (see unforce/3).
+            %%
+            %% Note that this tranformation would not be safe if the
+            %% original expression had been:
+            %%
+            %%    not(Expr =:= true)
             %%
             Ae = EqCall#icall{args=[E,#c_literal{val=false}]},
             {Al,Alps,St2} = force_safe(Ae, St1),
@@ -474,14 +493,30 @@ gexpr_test(E0, Bools0, St0) ->
     end.
 
 icall_eq_true(Arg) ->
-    #icall{anno=#a{anno=[compiler_generated]},
+    %% We need to recognize a '=:=' added by this pass, so we will add
+    %% an extra 'v3_core' annotation. (Being paranoid, we don't want
+    %% to trust 'compiler_generated' alone as it could have been added
+    %% by a parse transform.)
+    #icall{anno=#a{anno=[v3_core,compiler_generated]},
 	   module=#c_literal{val=erlang},
 	   name=#c_literal{val='=:='},
 	   args=[Arg,#c_literal{val=true}]}.
 
+%% force_booleans([Var], E, Eps, St) -> Expr.
+%%  Variables used in the top-level of a guard must be booleans.
+%%
+%%  Add necessary is_boolean/1 guard tests to ensure that the guard
+%%  will fail if any of the variables is not a boolean.
+
 force_booleans(Vs0, E, Eps, St) ->
     Vs1 = [set_anno(V, []) || V <- Vs0],
+
+    %% Prune the list of variables that will need is_boolean/1
+    %% tests. Basically, if the guard consists of simple expressions
+    %% joined by 'and's no is_boolean/1 tests are needed.
     Vs = unforce(E, Eps, Vs1),
+
+    %% Add is_boolean/1 tests for the remaining variables.
     force_booleans_1(Vs, E, Eps, St).
 
 force_booleans_1([], E, Eps, St) ->
@@ -505,7 +540,7 @@ force_booleans_1([V|Vs], E0, Eps0, St0) ->
 %%  Filter BoolExprList. BoolExprList is a list of simple expressions
 %%  (variables or literals) of which we are not sure whether they are booleans.
 %%
-%%  The basic idea for filtering is the following transformation
+%%  The basic idea for filtering is the following transformation:
 %%
 %%      (E =:= Bool) and is_boolean(E)   ==>  E =:= Bool
 %%
@@ -516,12 +551,13 @@ force_booleans_1([V|Vs], E0, Eps0, St0) ->
 %%
 %%      E1 and (E2 =:= true) and E3 and is_boolean(E)   ==>  E1 and (E2 =:= true) and E3
 %%
-%%  but expressions such as
+%%  but expressions such as:
 %%
 %%     not (E =:= true) and is_boolean(E)
 %%
-%%  cannot be transformed in this way (such expressions are the reason for
-%%  adding the is_boolean/1 test in the first place).
+%%  or expression using 'or' or 'xor' cannot be transformed in this
+%%  way (such expressions are the reason for adding the is_boolean/1
+%%  test in the first place).
 %%
 unforce(_, _, []) ->
     [];
@@ -2757,7 +2793,7 @@ cexpr(#ifun{anno=#a{us=Us0}=A0,name={named,Name},fc=#iclause{pats=Ps}}=Fun0,
 cexpr(#iapply{anno=A,op=Op,args=Args}, _As, St) ->
     {#c_apply{anno=A#a.anno,op=Op,args=Args},[],A#a.us,St};
 cexpr(#icall{anno=A,module=Mod,name=Name,args=Args}, _As, St) ->
-    {#c_call{anno=A#a.anno,module=Mod,name=Name,args=Args},[],A#a.us,St};
+    {#c_call{anno=A#a.anno -- [v3_core],module=Mod,name=Name,args=Args},[],A#a.us,St};
 cexpr(#iprimop{anno=A,name=Name,args=Args}, _As, St) ->
     {#c_primop{anno=A#a.anno,name=Name,args=Args},[],A#a.us,St};
 cexpr(#iprotect{anno=A,body=Es}, _As, St0) ->
diff --git a/lib/compiler/test/guard_SUITE.erl b/lib/compiler/test/guard_SUITE.erl
index 85e0bc0edd..69eb7f26b9 100644
--- a/lib/compiler/test/guard_SUITE.erl
+++ b/lib/compiler/test/guard_SUITE.erl
@@ -165,6 +165,10 @@ basic_not(Config) when is_list(Config) ->
     check(fun() -> if not glurf -> ok; true -> error end end, error),
     check(fun() -> if not Glurf -> ok; true -> error end end, error),
 
+    check(fun() -> if not (True =:= true) -> ok; true -> error end end, error),
+    check(fun() -> if not (False =:= true) -> ok; true -> error end end, ok),
+    check(fun() -> if not (Glurf =:= true) -> ok; true -> error end end, ok),
+
     ok.
 
 complex_not(Config) when is_list(Config) ->
diff --git a/lib/dialyzer/test/small_SUITE_data/results/guard_warnings b/lib/dialyzer/test/small_SUITE_data/results/guard_warnings
index c9c63656b3..d1647b0936 100644
--- a/lib/dialyzer/test/small_SUITE_data/results/guard_warnings
+++ b/lib/dialyzer/test/small_SUITE_data/results/guard_warnings
@@ -92,6 +92,6 @@ guard_warnings.erl:92: Function test41/0 has no local return
 guard_warnings.erl:94: Function test42/0 has no local return
 guard_warnings.erl:94: Guard test 'true' == 'false' can never succeed
 guard_warnings.erl:96: Function test43/0 has no local return
-guard_warnings.erl:96: Guard test 'true' =:= 'false' can never succeed
+guard_warnings.erl:96: Guard test not('true' =:= 'true') can never succeed
 guard_warnings.erl:98: Function test44/0 has no local return
 guard_warnings.erl:98: Guard test not('true' == 'true') can never succeed
-- 
2.26.2

openSUSE Build Service is sponsored by