File 2221-Collect-unused-vars-instead-of-used-ones.patch of Package erlang

From f52918aa4833ceb4f22f89bd436a6c52919b7015 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Jos=C3=A9=20Valim?= <jose.valim@plataformatec.com.br>
Date: Sun, 30 Jun 2019 22:56:52 +0200
Subject: [PATCH] Collect unused vars instead of used ones

Previously, we would build a large list of used
variables only to compute the intersection. This
commit changes it to compute the unused variables
from given a set which we then subtract from the
original set.
---
 lib/compiler/src/beam_ssa.erl             | 51 ++++++++++++++-----------------
 lib/compiler/src/beam_ssa_pre_codegen.erl | 12 ++++----
 2 files changed, 29 insertions(+), 34 deletions(-)

diff --git a/lib/compiler/src/beam_ssa.erl b/lib/compiler/src/beam_ssa.erl
index 7a766623b0..c007c7f8d2 100644
--- a/lib/compiler/src/beam_ssa.erl
+++ b/lib/compiler/src/beam_ssa.erl
@@ -21,7 +21,7 @@
 
 -module(beam_ssa).
 -export([add_anno/3,get_anno/2,get_anno/3,
-         clobbers_xregs/1,def/2,def_used/2,
+         clobbers_xregs/1,def/2,def_unused/3,
          definitions/1,
          dominators/1,common_dominators/3,
          flatmapfold_instrs_rpo/4,
@@ -123,7 +123,7 @@
                       'copy' | 'put_tuple_arity' | 'put_tuple_element' |
                       'put_tuple_elements' | 'set_tuple_element'.
 
--import(lists, [foldl/3,keyfind/3,mapfoldl/3,member/2,reverse/1,umerge/1]).
+-import(lists, [foldl/3,keyfind/3,mapfoldl/3,member/2,reverse/1]).
 
 -spec add_anno(Key, Value, Construct) -> Construct when
       Key :: atom(),
@@ -319,17 +319,18 @@ def(Ls, Blocks) ->
     Blks = [map_get(L, Blocks) || L <- Top],
     def_1(Blks, []).
 
--spec def_used(Ls, Blocks) -> {Def,Used} when
+-spec def_unused(Ls, Used, Blocks) -> {Def,Unused} when
       Ls :: [label()],
+      Used :: ordsets:ordset(var_name()),
       Blocks :: block_map(),
       Def :: ordsets:ordset(var_name()),
-      Used :: ordsets:ordset(var_name()).
+      Unused :: ordsets:ordset(var_name()).
 
-def_used(Ls, Blocks) ->
+def_unused(Ls, Unused, Blocks) ->
     Top = rpo(Ls, Blocks),
     Blks = [map_get(L, Blocks) || L <- Top],
     Preds = cerl_sets:from_list(Top),
-    def_used_1(Blks, Preds, [], []).
+    def_unused_1(Blks, Preds, [], Unused).
 
 %% dominators(BlockMap) -> {Dominators,Numbering}.
 %%  Calculate the dominator tree, returning a map where each entry
@@ -651,34 +652,28 @@ is_commutative('=/=') -> true;
 is_commutative('/=') -> true;
 is_commutative(_) -> false.
 
-def_used_1([#b_blk{is=Is,last=Last}|Bs], Preds, Def0, UsedAcc) ->
-    {Def,Used} = def_used_is(Is, Preds, Def0, used(Last)),
-    case Used of
-        [] ->
-            def_used_1(Bs, Preds, Def, UsedAcc);
-        [_|_] ->
-            def_used_1(Bs, Preds, Def, [Used|UsedAcc])
-    end;
-def_used_1([], _Preds, Def0, UsedAcc) ->
-    Def = ordsets:from_list(Def0),
-    Used = umerge(UsedAcc),
-    {Def,Used}.
+def_unused_1([#b_blk{is=Is,last=Last}|Bs], Preds, Def0, Unused0) ->
+    Unused1 = ordsets:subtract(Unused0, used(Last)),
+    {Def,Unused} = def_unused_is(Is, Preds, Def0, Unused1),
+    def_unused_1(Bs, Preds, Def, Unused);
+def_unused_1([], _Preds, Def, Unused) ->
+    {ordsets:from_list(Def), Unused}.
 
-def_used_is([#b_set{op=phi,dst=Dst,args=Args}|Is],
-            Preds, Def0, Used0) ->
+def_unused_is([#b_set{op=phi,dst=Dst,args=Args}|Is],
+            Preds, Def0, Unused0) ->
     Def = [Dst|Def0],
     %% We must be careful to only include variables that will
     %% be used when arriving from one of the predecessor blocks
     %% in Preds.
-    Used1 = [V || {#b_var{}=V,L} <- Args, cerl_sets:is_element(L, Preds)],
-    Used = ordsets:union(ordsets:from_list(Used1), Used0),
-    def_used_is(Is, Preds, Def, Used);
-def_used_is([#b_set{dst=Dst}=I|Is], Preds, Def0, Used0) ->
+    Unused1 = [V || {#b_var{}=V,L} <- Args, cerl_sets:is_element(L, Preds)],
+    Unused = ordsets:subtract(Unused0, ordsets:from_list(Unused1)),
+    def_unused_is(Is, Preds, Def, Unused);
+def_unused_is([#b_set{dst=Dst}=I|Is], Preds, Def0, Unused0) ->
     Def = [Dst|Def0],
-    Used = ordsets:union(used(I), Used0),
-    def_used_is(Is, Preds, Def, Used);
-def_used_is([], _Preds, Def, Used) ->
-    {Def,Used}.
+    Unused = ordsets:subtract(Unused0, used(I)),
+    def_unused_is(Is, Preds, Def, Unused);
+def_unused_is([], _Preds, Def, Unused) ->
+    {Def,Unused}.
 
 def_1([#b_blk{is=Is}|Bs], Def0) ->
     Def = def_is(Is, Def0),
diff --git a/lib/compiler/src/beam_ssa_pre_codegen.erl b/lib/compiler/src/beam_ssa_pre_codegen.erl
index a5fcb91cc0..2c68ab88fa 100644
--- a/lib/compiler/src/beam_ssa_pre_codegen.erl
+++ b/lib/compiler/src/beam_ssa_pre_codegen.erl
@@ -1340,9 +1340,9 @@ recv_common(_Defs, none, _Blocks) ->
     %% in the tail position of a function.
     [];
 recv_common(Defs, Exit, Blocks) ->
-    {ExitDefs,ExitUsed} = beam_ssa:def_used([Exit], Blocks),
+    {ExitDefs,ExitUnused} = beam_ssa:def_unused([Exit], Defs, Blocks),
     Def = ordsets:subtract(Defs, ExitDefs),
-    ordsets:intersection(Def, ExitUsed).
+    ordsets:subtract(Def, ExitUnused).
 
 %% recv_crit_edges([RemoveMessageLabel], LoopExit,
 %%                 Blocks0, Count0) -> {Blocks,Count}.
@@ -1447,9 +1447,9 @@ exit_predecessors([], _Exit, _Blocks) -> [].
 %%  later used within a clause of the receive.
 
 fix_receive([L|Ls], Defs, Blocks0, Count0) ->
-    {RmDefs,Used0} = beam_ssa:def_used([L], Blocks0),
+    {RmDefs,Unused} = beam_ssa:def_unused([L], Defs, Blocks0),
     Def = ordsets:subtract(Defs, RmDefs),
-    Used = ordsets:intersection(Def, Used0),
+    Used = ordsets:subtract(Def, Unused),
     {NewVars,Count} = new_vars([Base || #b_var{name=Base} <- Used], Count0),
     Ren = zip(Used, NewVars),
     Blocks1 = beam_ssa:rename_vars(Ren, [L], Blocks0),
@@ -2075,8 +2075,8 @@ reserve_yregs(#st{frames=Frames}=St0) ->
 reserve_yregs_1(L, #st{ssa=Blocks0,cnt=Count0,res=Res0}=St) ->
     Blk = map_get(L, Blocks0),
     Yregs = beam_ssa:get_anno(yregs, Blk),
-    {Def,Used} = beam_ssa:def_used([L], Blocks0),
-    UsedYregs = ordsets:intersection(Yregs, Used),
+    {Def,Unused} = beam_ssa:def_unused([L], Yregs, Blocks0),
+    UsedYregs = ordsets:subtract(Yregs, Unused),
     DefBefore = ordsets:subtract(UsedYregs, Def),
     {BeforeVars,Blocks,Count} = rename_vars(DefBefore, L, Blocks0, Count0),
     InsideVars = ordsets:subtract(UsedYregs, DefBefore),
-- 
2.16.4

openSUSE Build Service is sponsored by