File 2019-hipe-Faster-unreachable-basic-block-removal.patch of Package erlang

From 4e2d74858fbcd7b62b6538722d5bed0887897c40 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Magnus=20L=C3=A5ng?= <margnus1@telia.com>
Date: Thu, 17 Mar 2016 23:47:08 +0100
Subject: [PATCH 09/10] hipe: Faster unreachable basic block removal

---
 lib/hipe/flow/cfg.inc | 78 ++++++++++++++++++++++++++++++++++-----------------
 1 file changed, 53 insertions(+), 25 deletions(-)

diff --git a/lib/hipe/flow/cfg.inc b/lib/hipe/flow/cfg.inc
index 0bad2a8..a18bfbc 100644
--- a/lib/hipe/flow/cfg.inc
+++ b/lib/hipe/flow/cfg.inc
@@ -343,7 +343,7 @@ remove_pred(HT, FromL, PredL) ->
   case gb_trees:lookup(FromL, HT) of
     {value, {Block, Succ, Preds}} ->
       Code = hipe_bb:code(Block),
-      NewCode = remove_pred_from_phis(Code, PredL, []),
+      NewCode = remove_pred_from_phis(PredL, Code),
       NewBlock = hipe_bb:code_update(Block, NewCode),      
       gb_trees:update(FromL, {NewBlock,Succ,lists:delete(PredL,Preds)}, HT);
     none ->
@@ -374,20 +374,20 @@ add_pred(HT, ToL, PredL) ->
 -ifdef(CFG_CAN_HAVE_PHI_NODES).
 %% phi-instructions in a removed block's successors must be aware of
 %% the change.
-remove_pred_from_phis(List = [I|Left], Label, Acc) ->
+remove_pred_from_phis(Label, List = [I|Left]) ->
   case is_phi(I) of
-    true -> 
-      NewAcc = [phi_remove_pred(I, Label)|Acc],
-      remove_pred_from_phis(Left, Label, NewAcc);
+    true ->
+      NewI = phi_remove_pred(I, Label),
+      [NewI | remove_pred_from_phis(Label, Left)];
     false ->
-      lists:reverse(Acc) ++ List
+      List
   end;
-remove_pred_from_phis([], _Label, Acc) ->
-  lists:reverse(Acc).
+remove_pred_from_phis(_Label, []) ->
+  [].
 -else.
 %% this is used for code representations like those of back-ends which
 %% do not have phi-nodes.
-remove_pred_from_phis(Code, _Label, _Acc) ->
+remove_pred_from_phis(_Label, Code) ->
   Code.
 -endif.
 
@@ -927,24 +927,52 @@ merge(BB, BB2, BB2_Label) ->
 
 remove_unreachable_code(CFG) ->
   Start = start_label(CFG),
-  Reachable = find_reachable([Start], CFG, gb_sets:from_list([Start])),
-  %% Reachable is an ordset: it comes from gb_sets:to_list/1.
-  %% So use ordset:subtract instead of '--' below.
-  Labels = ordsets:from_list(labels(CFG)),
-  case ordsets:subtract(Labels, Reachable) of
-    [] ->
-      CFG;
+  %% No unreachable block will make another block reachable, so no fixpoint
+  %% looping is required
+  Reachable = find_reachable([], [Start], CFG, #{Start=>[]}),
+  case [L || L <- labels(CFG), not maps:is_key(L, Reachable)] of
+    [] -> CFG;
     Remove ->
-      NewCFG = lists:foldl(fun(X, Acc) -> bb_remove(Acc, X) end, CFG, Remove),
-      remove_unreachable_code(NewCFG)
+      HT0 = CFG#cfg.table,
+      HT1 = lists:foldl(fun gb_trees:delete/2, HT0, Remove),
+      ReachableP = fun(Lbl) -> maps:is_key(Lbl, Reachable) end,
+      HT = gb_trees:map(fun(_,B)->prune_preds(B, ReachableP)end, HT1),
+      CFG#cfg{table=HT}
   end.
 
-find_reachable([Label|Left], CFG, Acc) ->
-  NewAcc = gb_sets:add(Label, Acc),
-  Succ = succ(CFG, Label),
-  find_reachable([X || X <- Succ, not gb_sets:is_member(X, Acc)] ++ Left,
-		 CFG, NewAcc);
-find_reachable([], _CFG, Acc) ->
-  gb_sets:to_list(Acc).
+find_reachable([], [], _CFG, Acc) -> Acc;
+find_reachable([Succ|Succs], Left, CFG, Acc) ->
+  case Acc of
+    #{Succ := _} -> find_reachable(Succs, Left, CFG, Acc);
+    #{} -> find_reachable(Succs, [Succ|Left], CFG, Acc#{Succ => []})
+  end;
+find_reachable([], [Label|Left], CFG, Acc) ->
+  find_reachable(succ(CFG, Label), Left, CFG, Acc).
+
+%% Batch prune unreachable predecessors. Asymptotically faster than deleting
+%% unreachable blocks one at a time with bb_remove, at least when
+%% CFG_CAN_HAVE_PHI_NODES is undefined. Otherwise a phi_remove_preds might be
+%% needed to achieve that.
+prune_preds(B={Block, Succ, Preds}, ReachableP) ->
+  case lists:partition(ReachableP, Preds) of
+    {_, []} -> B;
+    {NewPreds, Unreach} ->
+      NewCode = remove_preds_from_phis(Unreach, hipe_bb:code(Block)),
+      {hipe_bb:code_update(Block, NewCode), Succ, NewPreds}
+  end.
 
+-ifdef(CFG_CAN_HAVE_PHI_NODES).
+remove_preds_from_phis(_, []) -> [];
+remove_preds_from_phis(Preds, List=[I|Left]) ->
+  case is_phi(I) of
+    false -> List;
+    true ->
+      NewI = lists:foldl(fun(L,IA)->phi_remove_pred(IA,L)end,
+			 I, Preds),
+      [NewI | remove_preds_from_phis(Preds, Left)]
+  end.
+-else.
+remove_preds_from_phis(_, Code) -> Code.
 -endif.
+
+-endif. %% -ifdef(REMOVE_UNREACHABLE_CODE)
-- 
2.9.3

openSUSE Build Service is sponsored by