File 2072-beam_ssa_dead-Extend-combining-of-switches-to-also-i.patch of Package erlang

From 7895cde3bb34a336fe14e28c48f505a26ee6af0d Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Tue, 26 May 2020 13:01:25 +0200
Subject: [PATCH 2/3] beam_ssa_dead: Extend combining of switches to also
 include is_boolean tests

---
 lib/compiler/src/beam_ssa_dead.erl | 65 ++++++++++++++++++++----------
 lib/compiler/test/guard_SUITE.erl  | 50 +++++++++++++++++++++--
 2 files changed, 89 insertions(+), 26 deletions(-)

diff --git a/lib/compiler/src/beam_ssa_dead.erl b/lib/compiler/src/beam_ssa_dead.erl
index b4710d6797..cf0132ebb1 100644
--- a/lib/compiler/src/beam_ssa_dead.erl
+++ b/lib/compiler/src/beam_ssa_dead.erl
@@ -852,7 +852,7 @@ eval_type_test_1(Test, Arg) ->
     erlang:Test(Arg).
 
 %%%
-%%% Combine bif:'=:=' and switch instructions
+%%% Combine bif:'=:=', is_boolean/1 tests, and switch instructions
 %%% to switch instructions.
 %%%
 %%% Consider this code:
@@ -904,10 +904,11 @@ combine_eqs_1([L|Ls], #st{bs=Blocks0}=St0) ->
         none ->
             combine_eqs_1(Ls, St0);
         {_,Arg,_,Fail0,List0} ->
+            %% Look for a switch instruction at the fail label
             case comb_get_sw(Fail0, St0) of
                 {true,Arg,Fail1,Fail,List1} ->
                     %% Another switch/br with the same arguments was
-                    %% found. Try combining them.
+                    %% found at the fail label. Try combining them.
                     case combine_lists(Fail1, List0, List1, Blocks0) of
                         none ->
                             %% Different types of literals in the lists,
@@ -916,30 +917,46 @@ combine_eqs_1([L|Ls], #st{bs=Blocks0}=St0) ->
                             %% (increasing code size and repeating tests).
                             combine_eqs_1(Ls, St0);
                         List ->
-                            %% Everything OK! Combine the lists.
-                            Sw0 = #b_switch{arg=Arg,fail=Fail,list=List},
-                            Sw = beam_ssa:normalize(Sw0),
-                            Blk0 = map_get(L, Blocks0),
-                            Blk = Blk0#b_blk{last=Sw},
-                            Blocks = Blocks0#{L:=Blk},
-                            St = St0#st{bs=Blocks},
+                            %% The lists were successfully combined.
+                            St = combine_build_sw(L, Arg, Fail, List, St0),
                             combine_eqs_1(Ls, St)
                     end;
-                {true,_OtherArg,_,_,_} ->
-                    %% The other switch/br uses a different Arg.
-                    combine_eqs_1(Ls, St0);
-                {false,_,_,_,_} ->
-                    %% Not safe: Bindings of variables that will be used
-                    %% or execution of instructions with potential
-                    %% side effects will be skipped.
-                    combine_eqs_1(Ls, St0);
-                none ->
-                    %% No switch/br at this label.
-                    combine_eqs_1(Ls, St0)
+                _ ->
+                    %% There was no switch of the correct kind found at the
+                    %% fail label. Look for a switch at the first success label.
+                    [{_,Succ}|_] = List0,
+                    case comb_get_sw(Succ, St0) of
+                        {true,Arg,_,_,_} ->
+                            %% Since we found a switch at the success
+                            %% label, the switch for this block (L)
+                            %% must have been constructed out of a
+                            %% is_boolean test or a two-way branch
+                            %% instruction (if the switch at L had
+                            %% been present when the shortcut_opt/1
+                            %% pass was run, its success branches
+                            %% would have been cut short and no longer
+                            %% point at the switch at the fail label).
+                            %%
+                            %% Therefore, keep this constructed
+                            %% switch. It will be further optimized
+                            %% the next time shortcut_opt/1 is run.
+                            St = combine_build_sw(L, Arg, Fail0, List0, St0),
+                            combine_eqs_1(Ls, St);
+                        _ ->
+                            combine_eqs_1(Ls, St0)
+                    end
             end
     end;
 combine_eqs_1([], St) -> St.
 
+combine_build_sw(From, Arg, Fail, List, #st{bs=Blocks0}=St) ->
+    Sw0 = #b_switch{arg=Arg,fail=Fail,list=List},
+    Sw = beam_ssa:normalize(Sw0),
+    Blk0 = map_get(From, Blocks0),
+    Blk = Blk0#b_blk{last=Sw},
+    Blocks = Blocks0#{From := Blk},
+    St#st{bs=Blocks}.
+
 comb_get_sw(L, #st{bs=Blocks,skippable=Skippable}) ->
     #b_blk{is=Is,last=Last} = map_get(L, Blocks),
     Safe0 = is_map_key(L, Skippable),
@@ -948,10 +965,14 @@ comb_get_sw(L, #st{bs=Blocks,skippable=Skippable}) ->
             none;
         #b_br{bool=#b_var{}=Bool,succ=Succ,fail=Fail} ->
             case comb_is(Is, Bool, Safe0) of
-                {none,_} ->
-                    none;
+                {none,Safe} ->
+                    {Safe,Bool,L,Fail,[{#b_literal{val=true},Succ}]};
                 {#b_set{op={bif,'=:='},args=[#b_var{}=Arg,#b_literal{}=Lit]},Safe} ->
                     {Safe,Arg,L,Fail,[{Lit,Succ}]};
+                {#b_set{op={bif,is_boolean},args=[#b_var{}=Arg]},Safe} ->
+                    SwList = [{#b_literal{val=false},Succ},
+                              {#b_literal{val=true},Succ}],
+                    {Safe,Arg,L,Fail,SwList};
                 {#b_set{},_} ->
                     none
             end;
diff --git a/lib/compiler/test/guard_SUITE.erl b/lib/compiler/test/guard_SUITE.erl
index 0558b8f300..05ec491efc 100644
--- a/lib/compiler/test/guard_SUITE.erl
+++ b/lib/compiler/test/guard_SUITE.erl
@@ -1084,15 +1084,50 @@ on(V) when number(V) -> number;
 on(_) -> not_number.
 
 complex_guard(_Config) ->
-    _ = [true = do_complex_guard(X, Y, Z) ||
+    _ = [true = do_complex_guard_1(X, Y, Z) ||
 	    X <- [4,5], Y <- [4,5], Z <- [4,5]],
-    _ = [true = do_complex_guard(X, Y, Z) ||
+    _ = [true = do_complex_guard_1(X, Y, Z) ||
 	    X <- [1,2,3], Y <- [1,2,3], Z <- [1,2,3]],
-    _ = [catch do_complex_guard(X, Y, Z) ||
+    _ = [catch do_complex_guard_1(X, Y, Z) ||
 	    X <- [1,2,3,4,5], Y <- [0,6], Z <- [1,2,3,4,5]],
+
+    b = do_complex_guard_2(false, false, true),
+    c = do_complex_guard_2(false, false, false),
+    c = do_complex_guard_2(false, true,  true),
+    a = do_complex_guard_2(false, true,  false),
+
+    c = do_complex_guard_2(true,  false, true),
+    a = do_complex_guard_2(true,  false, false),
+    c = do_complex_guard_2(true,  true,  true),
+    a = do_complex_guard_2(true,  true,  false),
+
+    c = do_complex_guard_2(other, false, true),
+    c = do_complex_guard_2(other, false, false),
+    c = do_complex_guard_2(other, true,  true),
+    c = do_complex_guard_2(other, true,  false),
+
+    c = do_complex_guard_2(false, other, true),
+    c = do_complex_guard_2(false, other, false),
+    c = do_complex_guard_2(true,  other, true),
+    a = do_complex_guard_2(true,  other, false),
+
+    c = do_complex_guard_2(false, false, other),
+    c = do_complex_guard_2(false, true,  other),
+    c = do_complex_guard_2(true,  false, other),
+    c = do_complex_guard_2(true,  true,  other),
+
+    c = do_complex_guard_2(false, other, other),
+    c = do_complex_guard_2(true,  other, other),
+    c = do_complex_guard_2(other, other, true),
+    c = do_complex_guard_2(other, other, false),
+    c = do_complex_guard_2(other, false, other),
+    c = do_complex_guard_2(other, true,  other),
+
+    c = do_complex_guard_2(other, other, other),
+
     ok.
 
-do_complex_guard(X1, Y1, Z1) ->
+do_complex_guard_1(X1, Y1, Z1) ->
     if
 	((X1 =:= 4) or (X1 =:= 5)) and
 	((Y1 =:= 4) or (Y1 =:= 5)) and
@@ -1103,6 +1138,13 @@ do_complex_guard(X1, Y1, Z1) ->
 	    true
     end.
 
+do_complex_guard_2(X, Y, Z) ->
+  if
+      (X orelse Y) andalso (not Z) -> a;
+      Z andalso (not (X orelse Y)) -> b;
+      true                         -> c
+  end.
+
 gbif(Config) when is_list(Config) ->
     error = gbif_1(1, {false,true}),
     ok = gbif_1(2, {false,true}),
-- 
2.26.2

openSUSE Build Service is sponsored by