File 2936-Slightly-optimize-union-of-a-short-list-and-a-set.patch of Package erlang
From 6b78afccc9bf01584e1d8460c98e893190ada6b1 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Sat, 20 Feb 2021 13:56:56 +0100
Subject: [PATCH 6/6] Slightly optimize union of a short list and a set
---
lib/compiler/src/beam_ssa.erl | 3 +++
lib/compiler/src/beam_ssa_dead.erl | 15 +++++++++++----
lib/compiler/src/beam_ssa_opt.erl | 20 ++++++++++++--------
3 files changed, 26 insertions(+), 12 deletions(-)
diff --git a/lib/compiler/src/beam_ssa.erl b/lib/compiler/src/beam_ssa.erl
index 8ed508ef48..0163f59ae7 100644
--- a/lib/compiler/src/beam_ssa.erl
+++ b/lib/compiler/src/beam_ssa.erl
@@ -889,6 +889,9 @@ trim_unreachable_1([{L,Blk0}|Bs], Seen0) ->
case successors(Blk) of
[] ->
[{L,Blk}|trim_unreachable_1(Bs, Seen0)];
+ [Next] ->
+ Seen = sets:add_element(Next, Seen0),
+ [{L,Blk}|trim_unreachable_1(Bs, Seen)];
[_|_]=Successors ->
Seen = sets:union(Seen0, sets:from_list(Successors, [{version, 2}])),
[{L,Blk}|trim_unreachable_1(Bs, Seen)]
diff --git a/lib/compiler/src/beam_ssa_dead.erl b/lib/compiler/src/beam_ssa_dead.erl
index 7af48c0860..037887529b 100644
--- a/lib/compiler/src/beam_ssa_dead.erl
+++ b/lib/compiler/src/beam_ssa_dead.erl
@@ -383,7 +383,7 @@ update_unset_vars(L, Is, Br, UnsetVars, #st{skippable=Skippable}) ->
%% Some variables defined in this block are used by
%% successors. We must update the set of unset variables.
SetInThisBlock = [V || #b_set{dst=V} <- Is],
- sets:union(UnsetVars, sets:from_list(SetInThisBlock, [{version, 2}]))
+ list_set_union(SetInThisBlock, UnsetVars)
end.
shortcut_two_way(#b_br{succ=Succ,fail=Fail}, From, Bs0, UnsetVars0, St0) ->
@@ -1108,7 +1108,7 @@ used_vars_phis(Is, L, Live0, UsedVars0) ->
case [{P,V} || {#b_var{}=V,P} <- PhiArgs] of
[_|_]=PhiVars ->
PhiLive0 = rel2fam(PhiVars),
- PhiLive = [{{L,P},sets:union(sets:from_list(Vs, [{version, 2}]), Live0)} ||
+ PhiLive = [{{L,P},list_set_union(Vs, Live0)} ||
{P,Vs} <- PhiLive0],
maps:merge(UsedVars, maps:from_list(PhiLive));
[] ->
@@ -1118,13 +1118,13 @@ used_vars_phis(Is, L, Live0, UsedVars0) ->
end.
used_vars_blk(#b_blk{is=Is,last=Last}, Used0) ->
- Used = sets:union(Used0, sets:from_list(beam_ssa:used(Last), [{version, 2}])),
+ Used = list_set_union(beam_ssa:used(Last), Used0),
used_vars_is(reverse(Is), Used).
used_vars_is([#b_set{op=phi}|Is], Used) ->
used_vars_is(Is, Used);
used_vars_is([#b_set{dst=Dst}=I|Is], Used0) ->
- Used1 = sets:union(Used0, sets:from_list(beam_ssa:used(I), [{version, 2}])),
+ Used1 = list_set_union(beam_ssa:used(I), Used0),
Used = sets:del_element(Dst, Used1),
used_vars_is(Is, Used);
used_vars_is([], Used) ->
@@ -1134,6 +1134,13 @@ used_vars_is([], Used) ->
%%% Common utilities.
%%%
+list_set_union([], Set) ->
+ Set;
+list_set_union([E], Set) ->
+ sets:add_element(E, Set);
+list_set_union(List, Set) ->
+ sets:union(sets:from_list(List, [{version, 2}]), Set).
+
sub(#b_set{args=Args}=I, Sub) when map_size(Sub) =/= 0 ->
I#b_set{args=[sub_arg(A, Sub) || A <- Args]};
sub(I, _Sub) -> I.
diff --git a/lib/compiler/src/beam_ssa_opt.erl b/lib/compiler/src/beam_ssa_opt.erl
index 68445906fb..165330cfff 100644
--- a/lib/compiler/src/beam_ssa_opt.erl
+++ b/lib/compiler/src/beam_ssa_opt.erl
@@ -1299,7 +1299,7 @@ live_opt_phis(Is, L, Live0, LiveMap0) ->
case [{P,V} || {#b_var{}=V,P} <- PhiArgs] of
[_|_]=PhiVars ->
PhiLive0 = rel2fam(PhiVars),
- PhiLive = [{{L,P},sets:union(sets:from_list(Vs, [{version, 2}]), Live0)} ||
+ PhiLive = [{{L,P},list_set_union(Vs, Live0)} ||
{P,Vs} <- PhiLive0],
maps:merge(LiveMap, maps:from_list(PhiLive));
[] ->
@@ -1309,7 +1309,7 @@ live_opt_phis(Is, L, Live0, LiveMap0) ->
end.
live_opt_blk(#b_blk{is=Is0,last=Last}=Blk, Live0) ->
- Live1 = sets:union(Live0, sets:from_list(beam_ssa:used(Last), [{version, 2}])),
+ Live1 = list_set_union(beam_ssa:used(Last), Live0),
{Is,Live} = live_opt_is(reverse(Is0), Live1, []),
{Blk#b_blk{is=Is},Live}.
@@ -1359,8 +1359,7 @@ live_opt_is([#b_set{op={succeeded,guard},dst=SuccDst,args=[Dst]}=SuccI,
live_opt_is([#b_set{dst=Dst}=I|Is], Live0, Acc) ->
case sets:is_element(Dst, Live0) of
true ->
- LiveUsed = sets:from_list(beam_ssa:used(I), [{version, 2}]),
- Live1 = sets:union(Live0, LiveUsed),
+ Live1 = list_set_union(beam_ssa:used(I), Live0),
Live = sets:del_element(Dst, Live1),
live_opt_is(Is, Live, [I|Acc]);
false ->
@@ -1368,8 +1367,7 @@ live_opt_is([#b_set{dst=Dst}=I|Is], Live0, Acc) ->
true ->
live_opt_is(Is, Live0, Acc);
false ->
- LiveUsed = sets:from_list(beam_ssa:used(I), [{version, 2}]),
- Live = sets:union(Live0, LiveUsed),
+ Live = list_set_union(beam_ssa:used(I), Live0),
live_opt_is(Is, Live, [I|Acc])
end
end;
@@ -1444,8 +1442,7 @@ do_reduce_try([{L, Blk} | Bs]=Bs0, Ws0) ->
%% This block does not execute any instructions
%% that would require a try. Analyze successors.
Successors = beam_ssa:successors(Blk),
- Ws = sets:union(sets:from_list(Successors, [{version, 2}]),
- Ws1),
+ Ws = list_set_union(Successors, Ws1),
[{L, Blk#b_blk{is=Is}} | do_reduce_try(Bs, Ws)];
unsafe ->
%% There is something unsafe in the block, for
@@ -3056,6 +3053,13 @@ is_tail_call_is([], _Bool, _Ret, _Acc) -> no.
%%% Common utilities.
%%%
+list_set_union([], Set) ->
+ Set;
+list_set_union([E], Set) ->
+ sets:add_element(E, Set);
+list_set_union(List, Set) ->
+ sets:union(sets:from_list(List, [{version, 2}]), Set).
+
non_guards(Linear) ->
gb_sets:from_list(non_guards_1(Linear)).
--
2.26.2