Skip to content

Commit

Permalink
Merge branch 'frej/gh9100-for-27/OTP-19374' into maint
Browse files Browse the repository at this point in the history
* frej/gh9100-for-27/OTP-19374:
  compiler destructive update: Handle nested patches for phis
  compiler destructive update: Fix bug in handling of nested patches
  • Loading branch information
bjorng committed Nov 27, 2024
2 parents 323a3e1 + 4d6e406 commit c9848b6
Show file tree
Hide file tree
Showing 2 changed files with 82 additions and 28 deletions.
67 changes: 40 additions & 27 deletions lib/compiler/src/beam_ssa_destructive_update.erl
Original file line number Diff line number Diff line change
Expand Up @@ -740,8 +740,7 @@ patch_is([I0=#b_set{dst=Dst}|Rest], PD0, Cnt0, Acc, BlockAdditions0)
no_reuse(I0)
end,
0 = length(Patches) - length(Forced) - length(OpArgs),
Ps = keysort(1, OpArgs),
{Is,Cnt} = patch_opargs(I1, Ps, Cnt0),
{Is,Cnt} = patch_opargs(I1, OpArgs, Cnt0),
patch_is(Rest, PD, Cnt, Is++Acc, BlockAdditions0);
[{appendable_binary,Dst,#b_literal{val= <<>>}=Lit}] ->
%% Special case for when the first fragment is a literal
Expand Down Expand Up @@ -816,50 +815,55 @@ aggregate_ret_patches_tuple([]) ->
[].

%% Should return the instructions in reversed order
patch_opargs(I0=#b_set{args=Args}, Patches0, Cnt0) ->
patch_opargs(I0=#b_set{args=Args}, OpArgs, Cnt0) ->
?DP("Patching args in ~p~n Args: ~p~n Patches: ~p~n",
[I0,Args,Patches0]),
Patches = merge_arg_patches(Patches0),
[I0,Args,OpArgs]),
Patches = merge_arg_patches(keysort(1, OpArgs), #{}),
?DP(" Merged patches: ~p~n", [Patches]),
{PatchedArgs,Is,Cnt} = patch_opargs(Args, Patches, 0, [], [], Cnt0),
{[I0#b_set{args=reverse(PatchedArgs)}|Is], Cnt}.

patch_opargs([#b_literal{val=Lit}|Args], [{Idx,Lit,Element}|Patches],
Idx, PatchedArgs, Is, Cnt0) ->
patch_opargs([#b_literal{val=Lit}|Args], Patches,
Idx, PatchedArgs, Is, Cnt0) when is_map_key(Idx, Patches) ->
#{Idx:=Element} = Patches,
?DP("Patching arg idx ~p~n lit: ~p~n elem: ~p~n", [Idx,Lit,Element]),
{Arg,Extra,Cnt} = patch_literal_term(Lit, Element, Cnt0),
patch_opargs(Args, Patches, Idx + 1, [Arg|PatchedArgs], Extra++Is, Cnt);
patch_opargs([Arg|Args], Patches, Idx, PatchedArgs, Is, Cnt) ->
?DP("Skipping arg idx ~p~n arg: ~p~n patches: ~p~n", [Idx,Arg,Patches]),
patch_opargs(Args, Patches, Idx + 1, [Arg|PatchedArgs], Is, Cnt);
patch_opargs([], [], _, PatchedArgs, Is, Cnt) ->
patch_opargs([], _, _, PatchedArgs, Is, Cnt) ->
{PatchedArgs, Is, Cnt}.

%% The way find_initial_values work, we can end up with multiple
%% patches patching different parts of a tuple or pair. We merge them
%% here.
merge_arg_patches([{Idx,Lit,P0},{Idx,Lit,P1}=Next|Patches]) ->
case {P0, P1} of
{{tuple_element,I0,E0,_},{tuple_element,I1,E1,_}} ->
P = {tuple_elements,[{I0,E0},{I1,E1}]},
merge_arg_patches([{Idx,Lit,P}|Patches]);
{{tuple_elements,Es},{tuple_element,I,E,_}} ->
P = {tuple_elements,[{I,E}|Es]},
merge_arg_patches([{Idx,Lit,P}|Patches]);
{{self,heap_tuple},_} ->
%% P0 forces this argument onto the heap, as P1 patches
%% something inside the same tuple, First can be dropped.
merge_arg_patches([Next|Patches])
merge_arg_patches([{Idx,_Lit,E1}|Patches], Acc) ->
case Acc of
#{Idx:=E0} ->
merge_arg_patches(Patches, Acc#{Idx=>merge_patches(E0, E1)});
#{} ->
merge_arg_patches(Patches, Acc#{Idx=>E1})
end;
merge_arg_patches([P|Patches]) ->
[P|merge_arg_patches(Patches)];
merge_arg_patches([]) ->
[].
merge_arg_patches([], Acc) ->
Acc.

merge_patches({tuple_element,I,E0,D0}, {tuple_element,I,E1,D1}) ->
{tuple_element, I, merge_patches(E0, E1), max(D0,D1)};
merge_patches({tuple_element,IA,EA,_}, {tuple_element,IB,EB,_}) ->
{tuple_elements, [{IA,EA}, {IB,EB}]};
merge_patches({tuple_element,IA,EA,_}, {tuple_elements,Es}) ->
{tuple_elements,[{IA,EA}|Es]};
merge_patches({tuple_elements,Es}, {tuple_element,IA,EA,_}) ->
{tuple_elements,[{IA,EA}|Es]};
merge_patches({self,heap_tuple}, Other) ->
%% We're already patching this element in Other and as it will
%% force the term onto the heap, we can ignore the new patch.
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 @@ -875,6 +879,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 @@ -81,7 +81,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 @@ -1035,3 +1037,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 c9848b6

Please sign in to comment.