File 2012-hipe_sdi-Use-segment-trees-to-represent-PARENTS.patch of Package erlang

From e74636ef2489d436b38726ae19bca2d8e7455cec Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Magnus=20L=C3=A5ng?= <margnus1@telia.com>
Date: Fri, 18 Mar 2016 11:42:31 +0100
Subject: [PATCH 02/10] hipe_sdi: Use segment trees to represent PARENTS

This speeds up parentsOfChild/2 from O(n) to O(lg n + k).

A new module misc/hipe_segment_trees.erl is introduced.
---
 lib/hipe/main/hipe.app.src           |   1 +
 lib/hipe/misc/Makefile               |   2 +-
 lib/hipe/misc/hipe_sdi.erl           |  60 +++++++-------
 lib/hipe/misc/hipe_segment_trees.erl | 150 +++++++++++++++++++++++++++++++++++
 4 files changed, 184 insertions(+), 29 deletions(-)
 create mode 100644 lib/hipe/misc/hipe_segment_trees.erl

diff --git a/lib/hipe/main/hipe.app.src b/lib/hipe/main/hipe.app.src
index f848715..acae2c6 100644
--- a/lib/hipe/main/hipe.app.src
+++ b/lib/hipe/main/hipe.app.src
@@ -171,6 +171,7 @@
 	     hipe_rtl_to_sparc,
 	     hipe_rtl_to_x86,
 	     hipe_rtl_varmap,
+	     hipe_segment_trees,
 	     hipe_sdi,
 	     hipe_sparc,
 	     hipe_sparc_assemble,
diff --git a/lib/hipe/misc/Makefile b/lib/hipe/misc/Makefile
index 72cfff2..e5033e4 100644
--- a/lib/hipe/misc/Makefile
+++ b/lib/hipe/misc/Makefile
@@ -44,7 +44,7 @@ RELSYSDIR = $(RELEASE_PATH)/lib/hipe-$(VSN)
 # Target Specs
 # ----------------------------------------------------
 ifdef HIPE_ENABLED
-HIPE_MODULES = hipe_data_pp hipe_pack_constants hipe_sdi 
+HIPE_MODULES = hipe_data_pp hipe_pack_constants hipe_sdi hipe_segment_trees
 else
 HIPE_MODULES =
 endif
diff --git a/lib/hipe/misc/hipe_sdi.erl b/lib/hipe/misc/hipe_sdi.erl
index fbb4b10..38a7988 100644
--- a/lib/hipe/misc/hipe_sdi.erl
+++ b/lib/hipe/misc/hipe_sdi.erl
@@ -36,10 +36,13 @@
 %%------------------------------------------------------------------------
 
 -type hipe_array() :: integer(). % declare this in hipe.hrl or builtin?
+-type hipe_vector(E) :: {} | {E} | {E, E} | {E, E, E} | tuple().
 
 -type label()      :: non_neg_integer().
 -type address()    :: non_neg_integer().
 
+-type parents()    :: {hipe_vector(_ :: integer()), hipe_segment_trees:tree()}.
+
 %%------------------------------------------------------------------------
 
 -record(label_data, {address :: address(),
@@ -168,9 +171,11 @@ mk_long(N) ->
 %%% - Since the graph is traversed from child to parent nodes in
 %%%   Step 3, the edges are represented by a vector PARENTS[0..n-1]
 %%%   such that PARENTS[j] = { i | i is a parent of j }.
-%%% - An explicit PARENTS graph would have size O(n^2). Instead we
-%%%   compute PARENTS[j] from the SDI vector when needed. This
-%%%   reduces memory overheads, and may reduce time overheads too.
+%%% - An explicit PARENTS graph would have size O(n^2). Instead, we
+%%%   observe that (i is a parent of j) iff (j \in range(i)), where
+%%%   range(i) is a constant function. We can thus precompute all the
+%%%   ranges i and insert them into a data structure built for such
+%%%   queries. In this case, we use a segment tree.
 
 -spec mk_span(non_neg_integer(), tuple()) -> hipe_array().
 mk_span(N, SDIS) ->
@@ -188,7 +193,19 @@ initSPAN(SdiNr, N, SDIS, SPAN) ->
       initSPAN(SdiNr+1, N, SDIS, SPAN)
   end.
 
-mk_parents(N, SDIS) -> {N,SDIS}.
+-spec mk_parents(non_neg_integer(), tuple()) -> parents().
+mk_parents(N, SDIS) ->
+  Ranges = parents_generate_ranges(N-1, SDIS, []),
+  hipe_segment_trees:build(Ranges).
+
+parents_generate_ranges(-1, _SDIS, Acc) -> Acc;
+parents_generate_ranges(SdiNr, SDIS, Acc) ->
+  #sdi_data{prevSdi=PrevSdi} = vector_sub(SDIS, SdiNr),
+  {LO,HI} =	% inclusive
+    if SdiNr =< PrevSdi -> {SdiNr+1, PrevSdi};	% forwards
+       true -> {PrevSdi+1, SdiNr-1}		% backwards
+    end,
+  parents_generate_ranges(SdiNr-1, SDIS, [{LO,HI}|Acc]).
 
 %%% "After the structure is built we process it as follows.
 %%% For any node i whose listed span exceeds the architectural
@@ -209,7 +226,7 @@ mk_parents(N, SDIS) -> {N,SDIS}.
 %%%   and PARENTS are no longer useful.
 
 -spec update_long(non_neg_integer(), tuple(), hipe_array(),
-		  {non_neg_integer(),tuple()},hipe_array()) -> 'ok'.
+		  parents(),hipe_array()) -> 'ok'.
 update_long(N, SDIS, SPAN, PARENTS, LONG) ->
   WKL = initWKL(N-1, SDIS, SPAN, []),
   processWKL(WKL, SDIS, SPAN, PARENTS, LONG).
@@ -225,14 +242,14 @@ initWKL(SdiNr, SDIS, SPAN, WKL) ->
   end.
 
 -spec processWKL([non_neg_integer()], tuple(), hipe_array(),
-		 {non_neg_integer(), tuple()}, hipe_array()) -> 'ok'.
+		 parents(), hipe_array()) -> 'ok'.
 processWKL([], _SDIS, _SPAN, _PARENTS, _LONG) -> ok;
 processWKL([Child|WKL], SDIS, SPAN, PARENTS, LONG) ->
   WKL2 = updateChild(Child, WKL, SDIS, SPAN, PARENTS, LONG),
   processWKL(WKL2, SDIS, SPAN, PARENTS, LONG).
 
 -spec updateChild(non_neg_integer(), [non_neg_integer()], tuple(), hipe_array(),
-		  {non_neg_integer(),tuple()}, hipe_array()) -> [non_neg_integer()].
+		  parents(), hipe_array()) -> [non_neg_integer()].
 updateChild(Child, WKL, SDIS, SPAN, PARENTS, LONG) ->
   case array_sub(SPAN, Child) of
     0 -> WKL;						% removed
@@ -245,26 +262,9 @@ updateChild(Child, WKL, SDIS, SPAN, PARENTS, LONG) ->
       updateParents(PS, Child, Incr, SDIS, SPAN, WKL)
   end.
 
--spec parentsOfChild({non_neg_integer(),tuple()},
-		     non_neg_integer()) -> [non_neg_integer()].
-parentsOfChild({N,SDIS}, Child) ->
-  parentsOfChild(N-1, SDIS, Child, []).
-
--spec parentsOfChild(integer(), tuple(), non_neg_integer(),
-		     [non_neg_integer()]) -> [non_neg_integer()].
-parentsOfChild(-1, _SDIS, _Child, PS) -> PS;
-parentsOfChild(SdiNr, SDIS, Child, PS) ->
-  SdiData = vector_sub(SDIS, SdiNr),
-  #sdi_data{prevSdi=PrevSdi} = SdiData,
-  {LO,HI} =	% inclusive
-    if SdiNr =< PrevSdi -> {SdiNr+1, PrevSdi};	% forwards
-       true -> {PrevSdi+1, SdiNr-1}		% backwards
-    end,
-  NewPS =
-    if LO =< Child, Child =< HI -> [SdiNr | PS];
-       true -> PS
-    end,
-  parentsOfChild(SdiNr-1, SDIS, Child, NewPS).
+-spec parentsOfChild(parents(), non_neg_integer()) -> [non_neg_integer()].
+parentsOfChild(IntervalTree, Child) ->
+  hipe_segment_trees:intersect(Child, IntervalTree).
 
 -spec updateParents([non_neg_integer()], non_neg_integer(),
 		    byte(), tuple(), hipe_array(),
@@ -361,9 +361,11 @@ applyIncr([{Label,LabelData}|List], INCREMENT, LabelMap) ->
 %%% Currently implemented as tuples.
 %%% Used for the 'SDIS' and 'PARENTS' vectors.
 
--spec vector_from_list([#sdi_data{}]) -> tuple().
+-spec vector_from_list([E]) -> hipe_vector(E).
 vector_from_list(Values) -> list_to_tuple(Values).
 
+-compile({inline, vector_sub/2}).
+-spec vector_sub(hipe_vector(E), non_neg_integer()) -> V when V :: E.
 vector_sub(Vec, I) -> element(I+1, Vec).
 
 %%% ADT for mutable integer arrays, indexed from 0 to N-1.
@@ -373,8 +375,10 @@ vector_sub(Vec, I) -> element(I+1, Vec).
 -spec mk_array_of_zeros(non_neg_integer()) -> hipe_array().
 mk_array_of_zeros(N) -> hipe_bifs:array(N, 0).
 
+-compile({inline, array_update/3}).
 -spec array_update(hipe_array(), non_neg_integer(), integer()) -> hipe_array().
 array_update(A, I, V) -> hipe_bifs:array_update(A, I, V).
 
+-compile({inline, array_sub/2}).
 -spec array_sub(hipe_array(), non_neg_integer()) -> integer().
 array_sub(A, I) -> hipe_bifs:array_sub(A, I).
diff --git a/lib/hipe/misc/hipe_segment_trees.erl b/lib/hipe/misc/hipe_segment_trees.erl
new file mode 100644
index 0000000..cbee328
--- /dev/null
+++ b/lib/hipe/misc/hipe_segment_trees.erl
@@ -0,0 +1,150 @@
+%%%
+%%% %CopyrightBegin%
+%%%
+%%% Copyright Ericsson AB 2016. All Rights Reserved.
+%%%
+%%% Licensed under the Apache License, Version 2.0 (the "License");
+%%% you may not use this file except in compliance with the License.
+%%% You may obtain a copy of the License at
+%%%
+%%%     http://www.apache.org/licenses/LICENSE-2.0
+%%%
+%%% Unless required by applicable law or agreed to in writing, software
+%%% distributed under the License is distributed on an "AS IS" BASIS,
+%%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%%% See the License for the specific language governing permissions and
+%%% limitations under the License.
+%%%
+%%% %CopyrightEnd%
+%%%
+%%% Segment trees.
+%%%
+%%% Keys are the (0-based) indices into the list passed to build/1.
+%%%
+%%% Range bounds are inclusive.
+%%%
+%%% TODO: Change the shape of the tree to a perfect binary tree, and pack it as
+%%% an implicit data structure into tuples (like a binary heap would be) for
+%%% improved efficiency.
+
+-module(hipe_segment_trees).
+
+-export([build/1, intersect/2]).
+
+-record(segment_tree, {
+	  lo            :: integer(),
+	  hi            :: integer(),
+	  root          :: tnode()
+	 }).
+
+%% X =< Mid belongs in Left
+-define(NODE(Left, Right, Mid, Segments), {Left, Right, Mid, Segments}).
+
+-define(POINT_LEAF(Val), Val).
+-define(RANGE_LEAF(Lo, Hi), {Lo, Hi}).
+
+-type segments() :: [non_neg_integer()].
+-type leaf()     :: segments().
+-type tnode()    :: ?NODE(tnode(), tnode(), integer(), segments()) | leaf().
+
+-opaque tree() :: #segment_tree{} | nil.
+-export_type([tree/0]).
+
+%% @doc Builds a segment tree of the given intervals.
+-spec build([{integer(), integer()}]) -> tree().
+build(ListOfIntervals) ->
+    case
+	lists:usort(
+	  lists:append(
+	    [[Lo, Hi] || {Lo, Hi} <- ListOfIntervals, Lo =< Hi]))
+    of
+	[] -> nil;
+	Endpoints ->
+	    Tree0 = empty_tree_from_endpoints(Endpoints),
+	    [Lo|_] = Endpoints,
+	    Hi = lists:last(Endpoints),
+	    Tree1 = insert_intervals(0, ListOfIntervals, Lo, Hi, Tree0),
+	    Tree = squash_empty_subtrees(Tree1),
+	    #segment_tree{lo=Lo, hi=Hi, root=Tree}
+    end.
+
+empty_tree_from_endpoints(Endpoints) ->
+    Leaves = leaves(Endpoints),
+    {T, [], _, _} = balanced_bst(Leaves, length(Leaves)),
+    T.
+
+leaves([Endpoint]) -> [?POINT_LEAF(Endpoint)];
+leaves([A | [B|_] = Tail]) ->
+    %% We could omit the range leaf if it's empty, but we want to pack this data
+    %% structure into an array (tuple) eventually, and then we *really* want
+    %% every other leaf to be a range
+    case A<B-1 of
+	true  -> [?POINT_LEAF(A),?RANGE_LEAF(A+1,B-1) | leaves(Tail)];
+	false -> [?POINT_LEAF(A) | leaves(Tail)]
+    end.
+
+balanced_bst(L, S) when S > 1 ->
+    Sm = S, %% - 1
+    S2 = Sm div 2,
+    S1 = Sm - S2,
+    {Left, L1, LeftLo, LeftHi} = balanced_bst(L, S1),
+    {Right, L2, _, RightHi} = balanced_bst(L1, S2),
+    T = ?NODE(Left, Right, LeftHi, []),
+    {T, L2, LeftLo, RightHi};
+balanced_bst([?RANGE_LEAF(Lo, Hi) | L], 1) ->
+    {[], L, Lo, Hi};
+balanced_bst([?POINT_LEAF(Val) | L], 1) ->
+    {[], L, Val, Val}.
+
+insert_intervals(_Ix, [], _Lo, _Hi, Tree) -> Tree;
+insert_intervals(Ix, [Int|Ints], Lo, Hi, Tree) ->
+    insert_intervals(Ix + 1, Ints, Lo, Hi,
+		     insert_interval(Ix, Int, Lo, Hi, Tree)).
+
+insert_interval(_, {Lo, Hi}, _, _, Node) when Lo > Hi -> Node;
+insert_interval(I, Int={Lo,Hi}, NLo, NHi,
+		?NODE(Left0, Right0, Mid, Segments)) ->
+    if Lo =< NLo, NHi =< Hi ->
+	    ?NODE(Left0, Right0, Mid, [I|Segments]);
+       true ->
+	    Left = case intervals_intersect(Lo, Hi,    NLo, Mid) of
+		       true -> insert_interval(I, Int, NLo, Mid, Left0);
+		       false -> Left0
+		   end,
+	    Right = case intervals_intersect(Lo, Hi,    Mid+1, NHi) of
+			true -> insert_interval(I, Int, Mid+1, NHi, Right0);
+			false -> Right0
+		   end,
+	    ?NODE(Left, Right, Mid, Segments)
+    end;
+insert_interval(I, {_Lo,_Hi}, _NLo, _NHi, Leaf) -> [I|Leaf].
+
+intervals_intersect(ALo, AHi, BLo, BHi) ->
+    (ALo =< AHi) andalso (BLo =< BHi) %% both nonempty
+	andalso (BLo =< AHi) andalso (ALo =< BHi).
+
+%% Purely optional optimisation
+squash_empty_subtrees(?NODE(Left0, Right0, Mid, Segs)) ->
+    build_squash_node(squash_empty_subtrees(Left0),
+		      squash_empty_subtrees(Right0),
+		      Mid, Segs);
+squash_empty_subtrees(Leaf) -> Leaf.
+
+build_squash_node([], [], _, Segs) -> Segs;
+build_squash_node(Left, Right, Mid, Segs) ->
+    ?NODE(Left, Right, Mid, Segs).
+
+%% @doc Returns the indices of the intervals in the tree that contains Point.
+-spec intersect(integer(), tree()) -> [non_neg_integer()].
+intersect(Point, nil) when is_integer(Point) -> [];
+intersect(Point, #segment_tree{lo=Lo, hi=Hi, root=Root})
+  when is_integer(Point) ->
+    case Lo =< Point andalso Point =< Hi of
+	false -> [];
+	true -> intersect_1(Point, Root, [])
+    end.
+
+intersect_1(Point, ?NODE(Left, Right, Mid, Segs), Acc0) ->
+    Child = if Point =< Mid -> Left; true -> Right end,
+    intersect_1(Point, Child, Segs ++ Acc0);
+intersect_1(_, LeafSegs, Acc) -> LeafSegs ++ Acc.
-- 
2.9.3

openSUSE Build Service is sponsored by