File 2020-hipe_vectors-Change-implementation-to-array.patch of Package erlang

From fd97ddb2c3031140f12c98c93a31325b15ea8cb6 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Magnus=20L=C3=A5ng?= <margnus1@telia.com>
Date: Fri, 18 Mar 2016 16:31:34 +0100
Subject: [PATCH 10/10] hipe_vectors: Change implementation to 'array'

The 'array' module is highly optimised for the hipe_vectors use-case,
and seems to perform slightly better than the gb_trees implementation.

Also, we remove the completely unnecessary hipe_vectors.hrl header.
---
 lib/hipe/regalloc/Makefile          |  1 -
 lib/hipe/regalloc/hipe_ig_moves.erl | 11 +++++-----
 lib/hipe/util/Makefile              |  1 -
 lib/hipe/util/hipe_vectors.erl      | 40 +++++++++++++++++++++++++++++--------
 lib/hipe/util/hipe_vectors.hrl      | 29 ---------------------------
 5 files changed, 38 insertions(+), 44 deletions(-)
 delete mode 100644 lib/hipe/util/hipe_vectors.hrl

diff --git a/lib/hipe/regalloc/Makefile b/lib/hipe/regalloc/Makefile
index aaa4418..ceb535f 100644
--- a/lib/hipe/regalloc/Makefile
+++ b/lib/hipe/regalloc/Makefile
@@ -123,7 +123,6 @@ $(EBIN)/hipe_amd64_specific_x87.beam: hipe_x86_specific_x87.erl
 $(EBIN)/hipe_coalescing_regalloc.beam: ../main/hipe.hrl
 $(EBIN)/hipe_graph_coloring_regalloc.beam: ../main/hipe.hrl
 $(EBIN)/hipe_ig.beam: ../main/hipe.hrl ../flow/cfg.hrl hipe_spillcost.hrl
-$(EBIN)/hipe_ig_moves.beam: ../util/hipe_vectors.hrl
 $(EBIN)/hipe_ls_regalloc.beam: ../main/hipe.hrl
 $(EBIN)/hipe_optimistic_regalloc.beam: ../main/hipe.hrl
 $(EBIN)/hipe_regalloc_loop.beam: ../main/hipe.hrl
diff --git a/lib/hipe/regalloc/hipe_ig_moves.erl b/lib/hipe/regalloc/hipe_ig_moves.erl
index b679453..2a70606 100644
--- a/lib/hipe/regalloc/hipe_ig_moves.erl
+++ b/lib/hipe/regalloc/hipe_ig_moves.erl
@@ -25,8 +25,6 @@
 	 new_move/3,
 	 get_moves/1]).
 
--include("../util/hipe_vectors.hrl").
-
 %%-----------------------------------------------------------------------------
 %% The main data structure; its fields are:
 %%  - movelist  : mapping from temp to set of associated move numbers
@@ -34,11 +32,13 @@
 %%  - moveinsns : list of move instructions, in descending move number order
 %%  - moveset   : set of move instructions
 
--record(ig_moves, {movelist                    :: hipe_vector(),	
+-record(ig_moves, {movelist                    :: movelist(),
 		   nrmoves   = 0               :: non_neg_integer(),
 		   moveinsns = []              :: [{_,_}],
 		   moveset   = gb_sets:empty() :: gb_sets:set()}).
 
+-type movelist() :: hipe_vectors:vector(ordsets:ordset(non_neg_integer())).
+
 %%-----------------------------------------------------------------------------
 
 -spec new(non_neg_integer()) -> #ig_moves{}.
@@ -66,7 +66,8 @@ new_move(Dst, Src, IG_moves) ->
 			moveset = gb_sets:insert(MoveInsn, MoveSet)}
   end.
 
--spec add_movelist(non_neg_integer(), non_neg_integer(), hipe_vector()) -> hipe_vector().
+-spec add_movelist(non_neg_integer(), non_neg_integer(), movelist())
+		  -> movelist().
 
 add_movelist(MoveNr, Temp, MoveList) ->
   AssocMoves = hipe_vectors:get(MoveList, Temp),
@@ -74,7 +75,7 @@ add_movelist(MoveNr, Temp, MoveList) ->
   %% ordset due to the ordsets:union in hipe_coalescing_regalloc:combine().
   hipe_vectors:set(MoveList, Temp, ordsets:add_element(MoveNr, AssocMoves)).
 
--spec get_moves(#ig_moves{}) -> {hipe_vector(), non_neg_integer(), tuple()}.
+-spec get_moves(#ig_moves{}) -> {movelist(), non_neg_integer(), tuple()}.
 
 get_moves(IG_moves) -> % -> {MoveList, NrMoves, MoveInsns}
   {IG_moves#ig_moves.movelist,
diff --git a/lib/hipe/util/Makefile b/lib/hipe/util/Makefile
index 66e9421..04de7f7 100644
--- a/lib/hipe/util/Makefile
+++ b/lib/hipe/util/Makefile
@@ -113,4 +113,3 @@ release_docs_spec:
 
 
 $(EBIN)/hipe_timing.beam: ../main/hipe.hrl
-$(EBIN)/hipe_vectors.beam: hipe_vectors.hrl
diff --git a/lib/hipe/util/hipe_vectors.erl b/lib/hipe/util/hipe_vectors.erl
index 7f6c8e9..90d736d 100644
--- a/lib/hipe/util/hipe_vectors.erl
+++ b/lib/hipe/util/hipe_vectors.erl
@@ -33,11 +33,25 @@
 	 %% list_to_vector/1,
 	 list/1]).
 
--include("hipe_vectors.hrl").
+%%-define(USE_TUPLES, true).
+%%-define(USE_GBTREES, true).
+-define(USE_ARRAYS, true).
+
+-type vector() :: vector(_).
+-export_type([vector/0, vector/1]).
+
+-spec new(non_neg_integer(), V) -> vector(E) when V :: E.
+-spec set(vector(E), non_neg_integer(), V :: E) -> vector(E).
+-spec get(vector(E), non_neg_integer()) -> E.
+-spec size(vector(_)) -> non_neg_integer().
+-spec vector_to_list(vector(E)) -> [E].
+%% -spec list_to_vector([E]) -> vector(E).
+-spec list(vector(E)) -> [{non_neg_integer(), E}].
 
 %% ---------------------------------------------------------------------
 
 -ifdef(USE_TUPLES).
+-opaque vector(_) :: tuple().
 
 new(N, V) ->
     erlang:make_tuple(N, V).
@@ -68,8 +82,8 @@ get(Vec, Ix) -> element(Ix+1, Vec).
 %% ---------------------------------------------------------------------
 
 -ifdef(USE_GBTREES).
+-opaque vector(E) :: gb_trees:tree(non_neg_integer(), E).
 
--spec new(non_neg_integer(), _) -> hipe_vector().
 new(N, V) when is_integer(N), N >= 0 ->
     gb_trees:from_orddict(mklist(N, V)).
 
@@ -81,14 +95,11 @@ mklist(M, N, V) when M < N ->
 mklist(_, _, _) ->
     [].
 
--spec size(hipe_vector()) -> non_neg_integer().
 size(V) -> gb_trees:size(V).
 
--spec list(hipe_vector()) -> [{_, _}].
 list(Vec) ->
     gb_trees:to_list(Vec).
 
-%% -spec list_to_vector([_]) -> hipe_vector().
 %% list_to_vector(Xs) ->
 %%     gb_trees:from_orddict(index(Xs, 0)).
 %% 
@@ -97,16 +108,29 @@ list(Vec) ->
 %% index([],_) ->
 %%     [].
 
--spec vector_to_list(hipe_vector()) -> [_].
 vector_to_list(V) ->
     gb_trees:values(V).
 
--spec set(hipe_vector(), non_neg_integer(), _) -> hipe_vector().
 set(Vec, Ix, V) ->
     gb_trees:update(Ix, V, Vec).
 
--spec get(hipe_vector(), non_neg_integer()) -> any().
 get(Vec, Ix) ->
     gb_trees:get(Ix, Vec).
 
 -endif. %% ifdef USE_GBTREES
+
+%% ---------------------------------------------------------------------
+
+-ifdef(USE_ARRAYS).
+%%-opaque vector(E) :: array:array(E).
+-type vector(E) :: array:array(E). % Work around dialyzer bug
+
+new(N, V) -> array:new(N, {default, V}).
+size(V) -> array:size(V).
+list(Vec) -> array:to_orddict(Vec).
+%% list_to_vector(Xs) -> array:from_list(Xs).
+vector_to_list(V) -> array:to_list(V).
+set(Vec, Ix, V) -> array:set(Ix, V, Vec).
+get(Vec, Ix) -> array:get(Ix, Vec).
+
+-endif. %% ifdef USE_ARRAYS
diff --git a/lib/hipe/util/hipe_vectors.hrl b/lib/hipe/util/hipe_vectors.hrl
deleted file mode 100644
index d4556e9..0000000
--- a/lib/hipe/util/hipe_vectors.hrl
+++ /dev/null
@@ -1,29 +0,0 @@
-%%
-%% %CopyrightBegin%
-%% 
-%% Copyright Ericsson AB 2008-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%
-%%
-%%-define(USE_TUPLES, true).
--define(USE_GBTREES, true).
-
--ifdef(USE_TUPLES).
--type hipe_vector() :: tuple().
--endif.
-
--ifdef(USE_GBTREES).
--type hipe_vector() :: gb_trees:tree().
--endif.
-- 
2.9.3

openSUSE Build Service is sponsored by