Skip to content

Commit

Permalink
compiler destructive update: Handle nested patches for phis
Browse files Browse the repository at this point in the history
The code responsible for patching Phi-instructions could not handle
multiple patches to a single literal value, it silently discarded all
but one of the updates. This MR corrects this by merging patches,
using the same mechanism as used for patching function arguments.

Closes #9100
  • Loading branch information
frej committed Nov 26, 2024
1 parent 10aa614 commit bb17fb6
Show file tree
Hide file tree
Showing 2 changed files with 53 additions and 4 deletions.
14 changes: 11 additions & 3 deletions lib/compiler/src/beam_ssa_destructive_update.erl
Original file line number Diff line number Diff line change
Expand Up @@ -961,9 +961,8 @@ merge_patches({self,heap_tuple}, Other) ->
Other.

patch_phi(I0=#b_set{op=phi,args=Args0}, Patches, Cnt0) ->
L2P = foldl(fun(Phi={phi,_,Lbl,_,_}, Acc) ->
Acc#{Lbl => Phi}
end, #{}, Patches),
?DP("Patching Phi:~n args: ~p~n patches: ~p~n", [Args0, Patches]),
L2P = foldl(fun merge_phi_patch/2, #{}, Patches),
{Args, Extra, Cnt} =
foldr(fun(Arg0={_,Lbl}, {ArgsAcc,ExtraAcc,CntAcc}) ->
case L2P of
Expand All @@ -979,6 +978,15 @@ patch_phi(I0=#b_set{op=phi,args=Args0}, Patches, Cnt0) ->
I = I0#b_set{op=phi,args=Args},
{I, Extra, Cnt}.

merge_phi_patch({phi,Var,Lbl,Lit,E}, Acc) ->
case Acc of
#{Lbl:={phi,Var,Lbl,Lit,Old}} ->
Acc#{Lbl => {phi,Var,Lbl,Lit,merge_patches(E, Old)}};
#{} ->
false = is_map_key(Lbl, Acc), %% Assert
Acc#{Lbl => {phi,Var,Lbl,Lit,E}}
end.

%% Should return the instructions in reversed order
patch_literal_term(Tuple, {tuple_elements,Elems}, Cnt) ->
Es = [{tuple_element,I,E,0} || {I,E} <:- keysort(1, Elems)],
Expand Down
43 changes: 42 additions & 1 deletion lib/compiler/test/beam_ssa_check_SUITE_data/private_append.erl
Original file line number Diff line number Diff line change
Expand Up @@ -82,7 +82,9 @@
bs_create_bin_on_literal/0,

crash_in_value_tracking/3,
crash_in_value_tracking_inner/3]).
crash_in_value_tracking_inner/3,

gh9100/0]).

%% Trivial smoke test
transformable0(L) ->
Expand Down Expand Up @@ -1036,3 +1038,42 @@ crash_in_value_tracking(_, _V0, _) ->
((<<((crash_in_value_tracking_inner(
{#{#{ ok => ok || _ := _ <- ok} => ok},
_V0, false, _V0, "Bo"}, _V0, ok)))/bytes>>) =/= ok).

gh9100() ->
gh9100(#{prev => nil,
next =>
[{equal, <<"a">>},
{delete, <<"y">>}]},
{{<<>>, <<>>}}).

%% We could fail to update multiple elements of a tuple, it was a
%% literal tuple in a Phi-instruction.
gh9100(#{next := [{Op, Text} | Next]} = Diffs,
{{TextDelete, TextInsert}}) ->
%ssa% (_, Acc) when post_ssa_opt ->
%ssa% switch(X, Fail, [{'delete',_},{'equal',Equal},...]),
%ssa% label Equal,
%ssa% A = bs_init_writable(_),
%ssa% B = bs_init_writable(_),
%ssa% C = put_tuple(A, B),
%ssa% D = put_tuple(C).
Acc =
case Op of
insert ->
{{TextDelete,
<<TextInsert/binary,Text/binary>>}};
delete ->
{{<<TextDelete/binary,Text/binary>>,
TextInsert}};
equal ->
{{<<>>, <<>>}} %% Bug is here.
end,
gh9100(#{prev =>
case Diffs of
#{prev := Prev} ->
Prev;
Other ->
ex:no_parens_remote(Other)
end,
next => Next},
Acc).

0 comments on commit bb17fb6

Please sign in to comment.