File 2152-compiler-Optimize-maps-pattern-matching.patch of Package erlang

From caa3c36a331009fa69c7a524090f455e9e296987 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn-Egil=20Dahlberg?= <egil@erlang.org>
Date: Tue, 6 Sep 2016 08:05:32 +0200
Subject: [PATCH 2/3] compiler: Optimize maps pattern matching

---
 lib/compiler/src/v3_kernel.erl | 65 ++++++++++++++++++++++++++++++++++++++++--
 1 file changed, 63 insertions(+), 2 deletions(-)

diff --git a/lib/compiler/src/v3_kernel.erl b/lib/compiler/src/v3_kernel.erl
index 450547d69..a535cc4fc 100644
--- a/lib/compiler/src/v3_kernel.erl
+++ b/lib/compiler/src/v3_kernel.erl
@@ -151,6 +151,7 @@ include_attribute(optional_callbacks) -> false;
 include_attribute(_) -> true.
 
 function({#c_var{name={F,Arity}=FA},Body}, St0) ->
+    %%io:format("~w/~w~n", [F,Arity]),
     try
 	St1 = St0#kern{func=FA,ff=undefined,vcount=0,fcount=0,ds=cerl_sets:new()},
 	{#ifun{anno=Ab,vars=Kvs,body=B0},[],St2} = expr(Body, new_sub(), St1),
@@ -1351,9 +1352,69 @@ select(T, Cs) -> [ C || C <- Cs, clause_con(C) =:= T ].
 %%  now separate them according to value.
 
 match_value(Us0, T, Cs0, Def, St0) ->
-    UCss = group_value(T, Us0, Cs0),
+    {Us1,Cs1,St1} = partition_intersection(T, Us0, Cs0, St0),
+    UCss = group_value(T, Us1, Cs1),
     %%ok = io:format("match_value ~p ~p~n", [T, Css]),
-    mapfoldl(fun ({Us,Cs}, St) -> match_clause(Us, Cs, Def, St) end, St0, UCss).
+    mapfoldl(fun ({Us,Cs}, St) -> match_clause(Us, Cs, Def, St) end, St1, UCss).
+
+%% partition_intersection
+%%  Partitions a map into two maps with the most common keys to the first map.
+%%      case <M> of
+%%          <#{a}>
+%%          <#{a,b}>
+%%          <#{a,c}>
+%%          <#{c}>
+%%      end
+%%  becomes
+%%      case <M,M> of
+%%          <#{a}, #{ }>
+%%          <#{a}, #{b}>
+%%          <#{ }, #{c}>
+%%          <#{a}, #{c}>
+%%      end
+%% The intention is to group as many keys together as possible and thus
+%% reduce the number of lookups to that key.
+partition_intersection(k_map, [U|_]=Us0, [_,_|_]=Cs0,St0) ->
+    Ps = [clause_val(C) || C <- Cs0],
+    case find_key_partition(Ps) of
+        no_partition ->
+            {Us0,Cs0,St0};
+        Ks ->
+            {Cs1,St1} = mapfoldl(fun(#iclause{pats=[Arg|Args]}=C, Sti) ->
+                                         {{Arg1,Arg2},St} = partition_key_intersection(Arg, Ks, Sti),
+                                         {C#iclause{pats=[Arg1,Arg2|Args]}, St}
+                                 end, St0, Cs0),
+            {[U|Us0],Cs1,St1}
+    end;
+partition_intersection(_, Us, Cs, St) ->
+    {Us,Cs,St}.
+
+partition_key_intersection(#k_map{es=Pairs}=Map,Ks,St0) ->
+    F = fun(#k_map_pair{key=Key}) -> member(map_key_clean(Key), Ks) end,
+    {Ps1,Ps2} = partition(F, Pairs),
+    {{Map#k_map{es=Ps1},Map#k_map{es=Ps2}},St0};
+partition_key_intersection(#ialias{pat=Map}=Alias,Ks,St0) ->
+    %% only alias one of them
+    {{Map1,Map2},St1} = partition_key_intersection(Map, Ks, St0),
+    {{Map1,Alias#ialias{pat=Map2}},St1}.
+
+% Only check for the complete intersection of keys and not commonality
+find_key_partition(Ps) ->
+    Sets = [sets:from_list(Ks)||Ks <- Ps],
+    Is   = sets:intersection(Sets),
+    case sets:to_list(Is) of
+        [] -> no_partition;
+        KeyIntersection ->
+            %% Check if the intersection are all keys in all clauses.
+            %% Don't split if they are since this will only
+            %% infer extra is_map instructions with no gain.
+            All = foldl(fun (Kset, Bool) ->
+                                Bool andalso sets:is_subset(Kset, Is)
+                        end, true, Sets),
+            if All  -> no_partition;
+               true -> KeyIntersection
+            end
+    end.
 
 %% group_value([Clause]) -> [[Clause]].
 %%  Group clauses according to value.  Here we know that
-- 
2.11.0

openSUSE Build Service is sponsored by