Skip to content

Commit

Permalink
compiler: Avoid reuse hint for update_record with > 1 update
Browse files Browse the repository at this point in the history
Take care to not produce a reuse hint when more than one update
exists. There is no point in attempting the reuse optimization when
more than one element is updated, as checking more than one element at
runtime is known to be slower than just copying the tuple in most
cases. Additionally, using a copy hint occasionally allows the alias
analysis pass to do a better job.
  • Loading branch information
frej committed Jul 31, 2024
1 parent 5473f58 commit 902574c
Show file tree
Hide file tree
Showing 2 changed files with 18 additions and 4 deletions.
18 changes: 16 additions & 2 deletions lib/compiler/src/beam_ssa_type.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1561,12 +1561,26 @@ will_succeed_1(#b_set{op=wait_timeout}, _Src, _Ts) ->
will_succeed_1(#b_set{}, _Src, _Ts) ->
'maybe'.

%% Take care to not produce a reuse hint when more than one update
%% exists. There is no point in attempting the reuse optimization when
%% more than one element is updated, as checking more than one element
%% at runtime is known to be slower than just copying the tuple in
%% most cases. Additionally, using a copy hint occasionally allows the
%% alias analysis pass to do a better job.
simplify_update_record(Src, Hint0, Updates, Ts) ->
case sur_1(Updates, concrete_type(Src, Ts), Ts, Hint0, []) of
{#b_literal{val=reuse}, []} when length(Updates) > 2 ->
{changed, #b_literal{val=copy}, Updates};
{Hint0, []} ->
unchanged;
{Hint, Skipped} ->
{changed, Hint, sur_skip(Updates, Skipped)}
{Hint1, Skipped} ->
Updates1 = sur_skip(Updates, Skipped),
Hint = if length(Updates1) > 2 ->
#b_literal{val=copy};
true ->
Hint1
end,
{changed, Hint, Updates1}
end.

sur_1([Index, Arg | Updates], RecordType, Ts, Hint, Skipped) ->
Expand Down
4 changes: 2 additions & 2 deletions lib/compiler/test/beam_ssa_check_SUITE_data/alias.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1077,7 +1077,7 @@ update_record0() ->

update_record0([Val|Ls], Acc=#r0{not_aliased=N}) ->
%ssa% (_, Rec) when post_ssa_opt ->
%ssa% _ = update_record(reuse, 3, Rec, 3, A, 2, NA) {unique => [Rec, NA], aliased => [A]}.
%ssa% _ = update_record(copy, 3, Rec, 3, A, 2, NA) {unique => [Rec, NA], aliased => [A]}.
R = Acc#r0{not_aliased=N+1,aliased=Val},
update_record0(Ls, R);
update_record0([], Acc) ->
Expand All @@ -1090,7 +1090,7 @@ update_record1() ->

update_record1([Val|Ls], Acc=#r1{not_aliased0=N0,not_aliased1=N1}) ->
%ssa% (_, Rec) when post_ssa_opt ->
%ssa% _ = update_record(reuse, 3, Rec, 3, NA0, 2, NA1) {unique => [Rec, NA1, NA0], source_dies => true}.
%ssa% _ = update_record(copy, 3, Rec, 3, NA0, 2, NA1) {unique => [Rec, NA1, NA0], source_dies => true}.
R = Acc#r1{not_aliased0=N0+1,not_aliased1=[Val|N1]},
update_record1(Ls, R);
update_record1([], Acc) ->
Expand Down

0 comments on commit 902574c

Please sign in to comment.