File 2011-hipe_icode_-bincomp-range-Improve-complexity.patch of Package erlang

From 1bdaee9393a3cf45d7a62fba815c2a73ab637781 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Magnus=20L=C3=A5ng?= <margnus1@telia.com>
Date: Fri, 18 Mar 2016 11:20:42 +0100
Subject: [PATCH 01/10] hipe_icode_{bincomp,range}: Improve complexity

hipe_icode_bincomp:find_bs_get_integer/3 was quadratic for no good reason. By observing
that NewSuccs and Rest are always disjoint, we can see that the worklist
does not need to be a set. Furthermore, by replacing the ordset Visited
with a map, we reduce complexity to (a very low) O(n lg n).

On cuter_binlib, this change reduced the time for hipe_icode_bincomp
from 60s to .25s. Using a gb_set for Visited gives .5s, and a sets:set
1s.

We apply the same optimisation to hipe_icode_range.
---
 lib/hipe/icode/hipe_icode_bincomp.erl | 28 ++++++++++++++++++++++------
 lib/hipe/icode/hipe_icode_range.erl   | 29 +++++++++++++++++++++++------
 2 files changed, 45 insertions(+), 12 deletions(-)

diff --git a/lib/hipe/icode/hipe_icode_bincomp.erl b/lib/hipe/icode/hipe_icode_bincomp.erl
index 5a27519..5ee6fe2 100644
--- a/lib/hipe/icode/hipe_icode_bincomp.erl
+++ b/lib/hipe/icode/hipe_icode_bincomp.erl
@@ -40,8 +40,8 @@
 -spec cfg(cfg()) -> cfg().
 
 cfg(Cfg1) ->
-  StartLbls = ordsets:from_list([hipe_icode_cfg:start_label(Cfg1)]),
-  find_bs_get_integer(StartLbls, Cfg1, StartLbls).
+  StartLbl = hipe_icode_cfg:start_label(Cfg1),
+  find_bs_get_integer([StartLbl], Cfg1, set_from_list([StartLbl])).
 
 find_bs_get_integer([Lbl|Rest], Cfg, Visited) ->
   BB = hipe_icode_cfg:bb(Cfg, Lbl),
@@ -55,10 +55,10 @@ find_bs_get_integer([Lbl|Rest], Cfg, Visited) ->
        not_ok ->
 	 Cfg
      end,
-  Succs = ordsets:from_list(hipe_icode_cfg:succ(NewCfg, Lbl)),
-  NewSuccs = ordsets:subtract(Succs, Visited),
-  NewLbls = ordsets:union(NewSuccs, Rest),
-  NewVisited = ordsets:union(NewSuccs, Visited),
+  Succs = hipe_icode_cfg:succ(NewCfg, Lbl),
+  NewSuccs = not_visited(Succs, Visited),
+  NewLbls = NewSuccs ++ Rest,
+  NewVisited = set_union(set_from_list(NewSuccs), Visited),
   find_bs_get_integer(NewLbls, NewCfg, NewVisited);
 find_bs_get_integer([], Cfg, _) ->
   Cfg.
@@ -177,3 +177,19 @@ make_butlast([{Res, Size}|Rest], Var) ->
 			[Var, hipe_icode:mk_const((1 bsl Size)-1)]),
    hipe_icode:mk_primop([NewVar], 'bsr', [Var, hipe_icode:mk_const(Size)])
    |make_butlast(Rest, NewVar)].
+
+%%--------------------------------------------------------------------
+%% Sets
+
+set_from_list([]) -> #{};
+set_from_list(L) ->
+  maps:from_list([{E, []} || E <- L]).
+
+not_visited([], _) -> [];
+not_visited([E|T], M) ->
+  case M of
+    #{E := _} -> not_visited(T, M);
+    _ -> [E|not_visited(T, M)]
+  end.
+
+set_union(A, B) -> maps:merge(A, B).
diff --git a/lib/hipe/icode/hipe_icode_range.erl b/lib/hipe/icode/hipe_icode_range.erl
index 12ed796..0cacdb8 100644
--- a/lib/hipe/icode/hipe_icode_range.erl
+++ b/lib/hipe/icode/hipe_icode_range.erl
@@ -187,17 +187,16 @@ safe_analyse(CFG, Data={MFA,_,_,_}) ->
 rewrite_blocks(State) ->
   CFG = state__cfg(State),
   Start = hipe_icode_cfg:start_label(CFG),
-  rewrite_blocks([Start], State, [Start]).
+  rewrite_blocks([Start], State, set_from_list([Start])).
 
--spec rewrite_blocks([label()], state(), [label()]) -> state().
+-spec rewrite_blocks([label()], state(), set(label())) -> state().
 
 rewrite_blocks([Next|Rest], State, Visited) ->
   Info = state__info_in(State, Next),
   {NewState, NewLabels} = analyse_block(Next, Info, State, true),
-  NewLabelsSet = ordsets:from_list(NewLabels),
-  RealNew = ordsets:subtract(NewLabelsSet, Visited),
-  NewVisited = ordsets:union([RealNew, Visited, [Next]]),
-  NewWork = ordsets:union([RealNew, Rest]),
+  RealNew = not_visited(NewLabels, Visited),
+  NewVisited = set_union(set_from_list(RealNew), Visited),
+  NewWork = RealNew ++ Rest,
   rewrite_blocks(NewWork, NewState, NewVisited);
 rewrite_blocks([], State, _) ->
   State.
@@ -1959,3 +1958,21 @@ next_down_limit(X) when is_integer(X), X > -16#8000000 -> -16#8000000;
 next_down_limit(X) when is_integer(X), X > -16#80000000 -> -16#80000000;
 next_down_limit(X) when is_integer(X), X > -16#800000000000000 -> -16#800000000000000;
 next_down_limit(_X) -> neg_inf.
+
+%%--------------------------------------------------------------------
+%% Sets
+
+-type set(E) :: #{E => []}.
+
+set_from_list([]) -> #{};
+set_from_list(L) ->
+  maps:from_list([{E, []} || E <- L]).
+
+not_visited([], _) -> [];
+not_visited([E|T], M) ->
+  case M of
+    #{E := []} -> not_visited(T, M);
+    _ -> [E|not_visited(T, M)]
+  end.
+
+set_union(A, B) -> maps:merge(A, B).
-- 
2.9.3

openSUSE Build Service is sponsored by