File 2741-v3_kernel-Fix-slow-compilation-of-repeated-record-ma.patch of Package erlang
From bd3297b98e452265b877a8abdb38d9a1b9ed0a08 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?John=20H=C3=B6gberg?= <john@erlang.org>
Date: Thu, 31 Oct 2019 11:26:18 +0100
Subject: [PATCH] v3_kernel: Fix slow compilation of repeated record matches
---
lib/compiler/src/v3_kernel.erl | 109 ++++++++++++++++++++++++-------------
lib/compiler/test/record_SUITE.erl | 49 ++++++++++++++++-
2 files changed, 117 insertions(+), 41 deletions(-)
diff --git a/lib/compiler/src/v3_kernel.erl b/lib/compiler/src/v3_kernel.erl
index e2b8787224..bcdc59699b 100644
--- a/lib/compiler/src/v3_kernel.erl
+++ b/lib/compiler/src/v3_kernel.erl
@@ -1301,51 +1301,81 @@ pattern_list(Ces, Isub, Osub, St) ->
%% set_vsub(Name, Sub, Subs) -> Subs.
%% subst_vsub(Name, Sub, Subs) -> Subs.
%% get_vsub(Name, Subs) -> SubName.
-%% Add/get substitute Sub for Name to VarSub. Use orddict so we know
-%% the format is a list {Name,Sub} pairs. When adding a new
-%% substitute we fold substitute chains so we never have to search
-%% more than once.
+%% Add/get substitute Sub for Name to VarSub.
+%%
+%% We're using a many-to-one bimap so we can rename all references to a
+%% variable without having to scan through all of them, which can cause
+%% compile times to explode (see record_SUITE:slow_compilation/1).
+
+new_sub() -> {#{}, #{}}.
+
+get_vsub(Key, Subs) ->
+ bimap_get(Key, Subs, Key).
+
+get_fsub(Name, Arity, Subs) ->
+ bimap_get({Name, Arity}, Subs, Name).
+
+set_vsub(Same, Same, Subs) ->
+ Subs;
+set_vsub(Key, Val, Subs) ->
+ bimap_set(Key, Val, Subs).
+
+set_fsub(Name, Arity, Val, Subs) ->
+ set_vsub({Name, Arity}, Val, Subs).
-new_sub() -> orddict:new().
+subst_vsub(Key, Val, Subs) ->
+ bimap_rename(Key, Val, Subs).
-get_vsub(V, Vsub) ->
- case orddict:find(V, Vsub) of
- {ok,Val} -> Val;
- error -> V
+bimap_get(Key, {Map, _InvMap}, Default) ->
+ case Map of
+ #{ Key := Val } -> Val;
+ _ -> Default
end.
-set_vsub(V, S, Vsub) ->
- orddict:store(V, S, Vsub).
-
-subst_vsub(Key, New, Vsub) ->
- orddict:from_list(subst_vsub_1(Key, New, Vsub)).
-
-subst_vsub_1(Key, New, [{K,Key}|Dict]) ->
- %% Fold chained substitution.
- [{K,New}|subst_vsub_1(Key, New, Dict)];
-subst_vsub_1(Key, New, [{K,_}|_]=Dict) when Key < K ->
- %% Insert the new substitution here, and continue
- %% look for chained substitutions.
- [{Key,New}|subst_vsub_2(Key, New, Dict)];
-subst_vsub_1(Key, New, [{K,_}=E|Dict]) when Key > K ->
- [E|subst_vsub_1(Key, New, Dict)];
-subst_vsub_1(Key, New, []) -> [{Key,New}].
-
-subst_vsub_2(V, S, [{K,V}|Dict]) ->
- %% Fold chained substitution.
- [{K,S}|subst_vsub_2(V, S, Dict)];
-subst_vsub_2(V, S, [E|Dict]) ->
- [E|subst_vsub_2(V, S, Dict)];
-subst_vsub_2(_, _, []) -> [].
-
-get_fsub(F, A, Fsub) ->
- case orddict:find({F,A}, Fsub) of
- {ok,Val} -> Val;
- error -> F
+%% Maps Key to Val without touching existing references to Key.
+bimap_set(Key, Val, {Map0, InvMap0}) ->
+ InvMap = bm_update_inv_lookup(Key, Val, Map0, InvMap0),
+ Map = Map0#{ Key => Val },
+ {Map, InvMap}.
+
+bm_update_inv_lookup(Key, Val, Map, InvMap0) ->
+ InvMap = bm_cleanup_inv_lookup(Key, Map, InvMap0),
+ case InvMap of
+ #{ Val := Keys } ->
+ %% Other keys map to the same value, add ours to the set.
+ InvMap#{ Val := ordsets:add_element(Key, Keys) };
+ #{} ->
+ InvMap#{ Val => [Key] }
end.
-set_fsub(F, A, S, Fsub) ->
- orddict:store({F,A}, S, Fsub).
+bm_cleanup_inv_lookup(Key, Map, InvMap) ->
+ case Map of
+ #{Key := Old} ->
+ case InvMap of
+ #{Old := [Key]} ->
+ maps:remove(Old, InvMap);
+ #{Old := [_|_] = Keys} ->
+ InvMap#{Old := ordsets:del_element(Key, Keys)}
+ end;
+ _ ->
+ InvMap
+ end.
+
+%% Maps Key to Val, and replaces all existing references to Key with Val.
+bimap_rename(Key, Val, {Map0, InvMap0} = Subs) when is_map(InvMap0) ->
+ case maps:take(Key, InvMap0) of
+ {Keys, InvMap1} ->
+ {bimap_update_lookup(Keys, Val, Map0#{Key => Val}), InvMap1#{Val => ordsets:add_element(Key, Keys)}};
+ error ->
+ bimap_set(Key, Val, Subs)
+ end;
+bimap_rename(Key, Val, Subs) ->
+ bimap_set(Key, Val, Subs).
+
+bimap_update_lookup([Key | Keys], Val, Map) ->
+ bimap_update_lookup(Keys, Val, Map#{ Key := Val });
+bimap_update_lookup([], _Val, Map) ->
+ Map.
new_fun_name(St) ->
new_fun_name("anonymous", St).
diff --git a/lib/compiler/test/record_SUITE.erl b/lib/compiler/test/record_SUITE.erl
index 4ed7f39780..94804529b6 100644
--- a/lib/compiler/test/record_SUITE.erl
+++ b/lib/compiler/test/record_SUITE.erl
@@ -28,7 +28,7 @@
init_per_testcase/2,end_per_testcase/2,
errors/1,record_test_2/1,record_test_3/1,record_access_in_guards/1,
guard_opt/1,eval_once/1,foobar/1,missing_test_heap/1,
- nested_access/1,coverage/1,grab_bag/1]).
+ nested_access/1,coverage/1,grab_bag/1,slow_compilation/1]).
init_per_testcase(_Case, Config) ->
Config.
@@ -47,7 +47,8 @@ groups() ->
[{p,test_lib:parallel(),
[errors,record_test_2,record_test_3,
record_access_in_guards,guard_opt,eval_once,foobar,
- missing_test_heap,nested_access,coverage,grab_bag]}].
+ missing_test_heap,nested_access,coverage,grab_bag,
+ slow_compilation]}].
init_per_suite(Config) ->
@@ -655,6 +656,50 @@ grab_bag(_Config) ->
ok.
+%% ERIERL-436; the following code used to be very slow to compile.
+%%
+%% #slow_r{} should have about 4x as many fields for the test to be effective
+%% (all of them matched in slow_compilation/1), but unfortunately the memory
+%% use scales together with the speed so we'll run out of memory on many of
+%% our test machines before we reach noticeable levels (2+ minutes before the
+%% fix).
+%%
+%% We've therefore scaled it down to the current level, at least it it'll guard
+%% against excessive regressions.
+
+-record(slow_r,
+ {f0, f1, f2, f3, f4, f5, f6, f7, f8, f9,
+ f10,f11,f12,f13,f14,f15,f16,f17,f18,f19,
+ f20,f21,f22,f23,f24,f25,f26,f27,f28,f29,
+ f30,f31,f32,f33,f34,f35,f36,f37,f38,f39,
+ f40,f41,f42,f43,f44,f45,f46,f47,f48,f49,
+ f50,f51,f52,f53,f54,f55,f56,f57,f58,f59}).
+
+slow_compilation(Config) when is_list(Config) ->
+ R = id(#slow_r{}),
+
+ [{f0,R#slow_r.f0},{f1,R#slow_r.f0},{f1,R#slow_r.f1},
+ {f2,R#slow_r.f2},{f3,R#slow_r.f3},{f4,R#slow_r.f4},
+ {f5,R#slow_r.f5},{f6,R#slow_r.f6},{f7,R#slow_r.f7},
+ {f8,R#slow_r.f8},{f9,R#slow_r.f9},{f10,R#slow_r.f10},
+ {f11,R#slow_r.f11},{f12,R#slow_r.f12},{f13,R#slow_r.f13},
+ {f14,R#slow_r.f14},{f15,R#slow_r.f15},{f16,R#slow_r.f16},
+ {f17,R#slow_r.f17},{f18,R#slow_r.f18},{f19,R#slow_r.f19},
+ {f20,R#slow_r.f20},{f21,R#slow_r.f21},{f22,R#slow_r.f22},
+ {f23,R#slow_r.f23},{f24,R#slow_r.f24},{f25,R#slow_r.f25},
+ {f26,R#slow_r.f26},{f27,R#slow_r.f27},{f28,R#slow_r.f28},
+ {f29,R#slow_r.f29},{f30,R#slow_r.f30},{f31,R#slow_r.f31},
+ {f32,R#slow_r.f32},{f33,R#slow_r.f33},{f34,R#slow_r.f34},
+ {f35,R#slow_r.f35},{f36,R#slow_r.f36},{f37,R#slow_r.f37},
+ {f38,R#slow_r.f38},{f39,R#slow_r.f39},{f40,R#slow_r.f40},
+ {f41,R#slow_r.f41},{f42,R#slow_r.f42},{f43,R#slow_r.f43},
+ {f44,R#slow_r.f44},{f45,R#slow_r.f45},{f46,R#slow_r.f46},
+ {f47,R#slow_r.f47},{f48,R#slow_r.f48},{f49,R#slow_r.f49},
+ {f40,R#slow_r.f50},{f51,R#slow_r.f51},{f52,R#slow_r.f52},
+ {f53,R#slow_r.f53},{f54,R#slow_r.f54},{f55,R#slow_r.f55},
+ {f56,R#slow_r.f56},{f57,R#slow_r.f57},{f58,R#slow_r.f58},
+ {f59,R#slow_r.f59}].
+
first_arg(First, _) -> First.
id(I) -> I.
--
2.16.4