Skip to content

Commit

Permalink
compiler destructive update: Patch every element of a list
Browse files Browse the repository at this point in the history
The initial value tracker in the destructive update pass could
sometimes fail to ensure that a term which was destructively updated
was forced onto the heap as it did not have a way to easily follow
list tails. This patch corrects that error by ensuring that if the
first element of a literal list is forced onto the heap, all
elements of the list will be forced onto the heap.
  • Loading branch information
frej committed Aug 16, 2024
1 parent ee9628e commit dadf00b
Show file tree
Hide file tree
Showing 2 changed files with 45 additions and 6 deletions.
25 changes: 20 additions & 5 deletions lib/compiler/src/beam_ssa_destructive_update.erl
Original file line number Diff line number Diff line change
Expand Up @@ -891,13 +891,28 @@ patch_literal_term(<<>>, {self,init_writable}, Cnt0) ->
{V,Cnt} = new_var(Cnt0),
I = #b_set{op=bs_init_writable,dst=V,args=[#b_literal{val=256}]},
{V,[I],Cnt};
patch_literal_term([H0|T0], {hd,Element,_}, Cnt0) ->
{H,Extra,Cnt1} = patch_literal_term(H0, Element, Cnt0),
{T,[],Cnt1} = patch_literal_term(T0, [], Cnt1),
{Dst,Cnt} = new_var(Cnt1),
patch_literal_term(Lst, {hd,_,_}=E, Cnt0) ->
patch_literal_list(Lst, E, Cnt0);
patch_literal_term(Lit, [], Cnt) ->
{#b_literal{val=Lit}, [], Cnt}.

%%
%% The initial value tracker is unable to easily follow list tails, to
%% compensate for this a patch for the head of a literal list is
%% applied to all elements of the list. Sometimes this is unnecessary,
%% but as it appears to be infrequent and mostly harmless, this avoids
%% extra complexity in the tracker.
%%
patch_literal_list([H0|T0], {hd,Element,_}=E, Cnt0) ->
{H,Extra2,Cnt1} = patch_literal_term(H0, Element, Cnt0),
{T,Extra1,Cnt2} = patch_literal_term(T0, E, Cnt1),
Extra = Extra2 ++ Extra1,
{Dst,Cnt} = new_var(Cnt2),
I = #b_set{op=put_list,dst=Dst,args=[H,T]},
{Dst, [I|Extra], Cnt};
patch_literal_term(Lit, [], Cnt) ->
patch_literal_list(Lit, {hd,_,_}, Cnt) ->
%% Lit is normally [], but if it is not, we know that it is not a
%% cons that needs to end up on the heap, so it can be left as is.
{#b_literal{val=Lit}, [], Cnt}.

patch_literal_tuple(Tuple, Elements0, Cnt) ->
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,8 @@

-export([do0a/0, do0b/2, different_sizes/2, ambiguous_inits/1,
update_record0/0, fc/0, track_update_record/1,
gh8124_a/0, gh8124_b/0]).
gh8124_a/0, gh8124_b/0,
failure_to_patch_list/0]).

-record(r, {a=0,b=0,c=0,tot=0}).
-record(r1, {a}).
Expand Down Expand Up @@ -236,3 +237,26 @@ gh8124_b() ->
[R] = gh8124_b_inner(),
R#r{a = <<"value 2">>}.


%% Check that the list of tuples is built on the heap.

failure_to_patch_list() ->
%ssa% () when post_ssa_opt ->
%ssa% T0 = put_tuple(...),
%ssa% L0 = put_list(T0, []),
%ssa% T1 = put_tuple(...),
%ssa% L1 = put_list(T1, L0),
%ssa% _ = call(_, L1).
_ = [
ftpl(ClassDef) ||
ClassDef <- [#r{a={}},
#r{}
]
],
ok.

ftpl(Ts0) ->
%ssa% (X) when post_ssa_opt ->
%ssa% _ = update_record(inplace, 5, X,...).
A = erlang:timestamp(),
Ts0#r{a=A}.

0 comments on commit dadf00b

Please sign in to comment.