Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
5 changes: 5 additions & 0 deletions erts/emulator/beam/jit/arm/instr_common.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -1102,6 +1102,11 @@ void BeamModuleAssembler::emit_update_record_in_place(
void BeamModuleAssembler::emit_set_tuple_element(const ArgSource &Element,
const ArgRegister &Tuple,
const ArgWord &Offset) {
/* TODO: As of Erlang/OTP 29, this instruction is no longer
* emitted by the compiler. It can be removed when the runtime
* system no longer supports loading code compiled by Erlang/OTP
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Thank you for this!

* 28 or earlier. */

auto tuple = load_source(Tuple, TMP1);
auto element = load_source(Element, TMP2);
a64::Gp boxed_ptr = emit_ptr_val(TMP1, tuple.reg);
Expand Down
5 changes: 5 additions & 0 deletions erts/emulator/beam/jit/x86/instr_common.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -1115,6 +1115,11 @@ void BeamModuleAssembler::emit_update_record_in_place(
void BeamModuleAssembler::emit_set_tuple_element(const ArgSource &Element,
const ArgRegister &Tuple,
const ArgWord &Offset) {
/* TODO: As of Erlang/OTP 29, this instruction is no longer
* emitted by the compiler. It can be removed when the runtime
* system no longer supports loading code compiled by Erlang/OTP
* 28 or earlier. */

mov_arg(ARG1, Tuple);

x86::Gp boxed_ptr = emit_ptr_val(ARG1, ARG1);
Expand Down
76 changes: 75 additions & 1 deletion lib/compiler/src/beam_ssa_opt.erl
Original file line number Diff line number Diff line change
Expand Up @@ -298,7 +298,8 @@ early_epilogue_passes(Opts) ->
Ps = [?PASS(ssa_opt_type_finish),
?PASS(ssa_opt_float),
?PASS(ssa_opt_sw),
?PASS(ssa_opt_no_reuse)],
?PASS(ssa_opt_no_reuse),
?PASS(ssa_opt_deoptimize_update_tuple)],
passes_1(Ps, Opts).

late_epilogue_passes(Opts) ->
Expand Down Expand Up @@ -3830,6 +3831,79 @@ cannot_reuse([V|Values], New) ->
cannot_reuse([], _New) ->
false.


%%%
%%% Undo the merging of `update_tuple` instructions performed by the
%%% beam_ssa_update_tuple sub-pass. The beam_ssa_pre_codegen pass will soon
%%% convert each `update_tuple` pseudo-instruction back into a setelement/3
%%% call. To minimize the number of such calls, each `update_tuple`
%%% instruction should ideally update only a single element of the tuple.
%%%

ssa_opt_deoptimize_update_tuple({#opt_st{ssa=Linear0}=St, FuncDb})
when is_list(Linear0) ->
Linear = deoptimize_update_tuple(Linear0),
{St#opt_st{ssa=Linear}, FuncDb}.

deoptimize_update_tuple(Linear) ->
Map = #{0 => #{}},
deoptimize_update_tuple(Linear, Map).

deoptimize_update_tuple([{L,Blk0}|Bs], Map0) ->
Data0 = maps:get(L, Map0, #{}),
#b_blk{is=Is0} = Blk0,
{Is,Data} = deoptimize_update_tuple_is(Is0, Data0, []),
Blk = if
Is =:= Is0 -> Blk0;
true -> Blk0#b_blk{is=Is}
end,
Successors = beam_ssa:successors(Blk),
Map = dut_update_successors(Successors, Data, Map0),
[{L,Blk}|deoptimize_update_tuple(Bs, Map)];
deoptimize_update_tuple([], _) ->
[].

dut_update_successors([L|Ls], Data0, Map) ->
case Map of
#{L := Data1} ->
Data = maps:intersect(Data1, Data0),
dut_update_successors(Ls, Data0, Map#{L := Data});
#{} ->
dut_update_successors(Ls, Data0, Map#{L => Data0})
end;
dut_update_successors([], _, Map) ->
Map.

deoptimize_update_tuple_is([#b_set{op=update_tuple,dst=Dst,
args=Args0}=I0|Is], Data0, Acc) ->
[Src|Args1] = Args0,
Args = dut_simplify(Src, Args1, Data0),
I = I0#b_set{args=Args},
Data = Data0#{Dst => {Src,Args1}},
deoptimize_update_tuple_is(Is, Data, [I|Acc]);
deoptimize_update_tuple_is([I|Is], Data, Acc) ->
deoptimize_update_tuple_is(Is, Data, [I|Acc]);
deoptimize_update_tuple_is([], Data, Acc) ->
{reverse(Acc),Data}.

dut_simplify(Src, Args0, Data) ->
L0 = [{V,dut_simplify_1(Args0, As)} || V := {S,As} <:- Data, S =:= Src],
L1 = [{length(As),[V|As]} || {V,As} <:- L0, As =/= none],
case sort(L1) of
[] ->
[Src|Args0];
[{_,Args}|_] ->
Args
end.

dut_simplify_1([P,V|Args], [P,V|As]) ->
dut_simplify_1(Args, As);
dut_simplify_1([_|_]=Args, []) ->
Args;
dut_simplify_1(_, _) ->
none.


%%%
%%% Common utilities.
%%%
Expand Down
70 changes: 34 additions & 36 deletions lib/compiler/src/beam_ssa_pre_codegen.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1164,10 +1164,12 @@ find_fc_errors([#b_function{bs=Blocks}|Fs], Acc0) ->
find_fc_errors([], Acc) ->
Acc.

%%% expand_update_tuple(St0) -> St
%%%
%%% Expands the update_tuple psuedo-instruction into its actual instructions.
%%%
%%% Expands the `update_tuple` pseudo-instruction into `setelement/3`
%%% calls. Provided that the ssa_opt_deoptimize_update_tuple sub-pass
%%% in beam_ssa_opt has completely broken apart all `update_tuple`
%%% instructions, this should result in the same number of
%%% `setelement/3`calls as in the original source code.

expand_update_tuple(#st{ssa=Blocks0,cnt=Count0}=St) ->
Linear0 = beam_ssa:linearize(Blocks0),
{Linear, Count} = expand_update_tuple_1(Linear0, Count0, []),
Expand All @@ -1179,9 +1181,9 @@ expand_update_tuple_1([{L, #b_blk{is=Is0}=B0} | Bs], Count0, Acc0) ->
{Is, Count} ->
expand_update_tuple_1(Bs, Count, [{L, B0#b_blk{is=Is}} | Acc0]);
{Is, NextIs, Count1} ->
%% There are `set_tuple_element` instructions that we must put into
%% a new block to avoid separating the `setelement` instruction from
%% its `succeeded` instruction.
%% There are `setelement/3` calls that we must put into a
%% new block to avoid separating the first `setelement/3`
%% instruction from its `succeeded` instruction.
#b_blk{last=Br} = B0,
#b_br{succ=Succ} = Br,
NextL = Count1,
Expand All @@ -1193,14 +1195,14 @@ expand_update_tuple_1([{L, #b_blk{is=Is0}=B0} | Bs], Count0, Acc0) ->
expand_update_tuple_1(Bs, Count, Acc)
end;
expand_update_tuple_1([], Count, Acc) ->
{Acc, Count}.
{reverse(Acc), Count}.

expand_update_tuple_is([#b_set{op=update_tuple, args=[Src | Args]}=I0 | Is],
Count0, Acc) ->
Count0, Acc) ->
{SetElement, Sets, Count} = expand_update_tuple_list(Args, I0, Src, Count0),
case {Sets, Is} of
{[_ | _], [#b_set{op=succeeded}]} ->
{reverse(Acc, [SetElement | Is]), reverse(Sets), Count};
{[_ | _], [#b_set{op=succeeded}=I]} ->
{reverse(Acc, [SetElement, I]), reverse(Sets), Count};
{_, _} ->
expand_update_tuple_is(Is, Count, Sets ++ [SetElement | Acc])
end;
Expand All @@ -1209,36 +1211,32 @@ expand_update_tuple_is([I | Is], Count, Acc) ->
expand_update_tuple_is([], Count, Acc) ->
{reverse(Acc), Count}.

%% Expands an update_tuple list into setelement/3 + set_tuple_element.
%% Expands an update_tuple list into a chain of `setelement/3` instructions.
%%
%% Note that it returns the instructions in reverse order.
expand_update_tuple_list(Args, I0, Src, Count0) ->
[Index, Value | Rest] = sort_update_tuple(Args, []),
SortedUpdates = sort_update_tuple(Args, []),
expand_update_tuple_list_1(SortedUpdates, Src, I0, Count0, []).

%% set_tuple_element is destructive, so we have to start off with a
%% setelement/3 call to give them something to work on.
I = I0#b_set{op=call,
args=[#b_remote{mod=#b_literal{val=erlang},
name=#b_literal{val=setelement},
arity=3},
Index, Src, Value]},
{Sets, Count} = expand_update_tuple_list_1(Rest, I#b_set.dst, Count0, []),
{I, Sets, Count}.

expand_update_tuple_list_1([], _Src, Count, Acc) ->
{Acc, Count};
expand_update_tuple_list_1([Index0, Value | Updates], Src, Count0, Acc) ->
%% Change to the 0-based indexing used by `set_tuple_element`.
Index = #b_literal{val=(Index0#b_literal.val - 1)},
expand_update_tuple_list_1([Index, Value | Updates], Src, I0, Count0, Acc) ->
{Dst, Count} = new_var(Count0),
SetOp = #b_set{op=set_tuple_element,
dst=Dst,
args=[Value, Src, Index]},
expand_update_tuple_list_1(Updates, Src, Count, [SetOp | Acc]).

%% Sorts updates so that the highest index comes first, letting us use
%% set_tuple_element for all subsequent operations as we know their indexes
%% will be valid.
I = I0#b_set{op=call,
dst=Dst,
args=[#b_remote{mod=#b_literal{val=erlang},
name=#b_literal{val=setelement},
arity=3},
Index, Src, Value]},
expand_update_tuple_list_1(Updates, Dst, I0, Count, [I | Acc]);
expand_update_tuple_list_1([], _Src, #b_set{dst=Dst}, Count, [I0|Acc]) ->
I1 = I0#b_set{dst=Dst},
Is0 = [I1|Acc],
I = last(Is0),
Is = lists:droplast(Is0),
{I, Is, Count}.

%% Sorts updates so that the highest index comes first letting us use
%% `setelement/3` calls not followed by `succeeded` for all
%% subsequent operations as we know that their indices will be valid.
sort_update_tuple([_Index, _Value]=Args, []) ->
Args;
sort_update_tuple([#b_literal{}=Index, Value | Updates], Acc) ->
Expand Down
50 changes: 1 addition & 49 deletions lib/compiler/src/beam_validator.erl
Original file line number Diff line number Diff line change
Expand Up @@ -204,10 +204,6 @@ validate_0([{function, Name, Arity, Entry, Code} | Fs], Module, Level, Ft) ->
hf=0,
%% List of hot catch/try tags
ct=[],
%% Previous instruction was setelement/3.
setelem=false,
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

We can do a drive-by removal of puts_left too, it's not used anywhere.

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Good idea. Done.

%% put/1 instructions left.
puts_left=none,
%% Current receive state:
%%
%% * 'none' - Not in a receive loop.
Expand Down Expand Up @@ -331,10 +327,9 @@ validate_branches(MFA, Vst) ->
Vst
end.

validate_instrs([I|Is], MFA, Offset, Vst0) ->
validate_instrs([I|Is], MFA, Offset, Vst) ->
validate_instrs(Is, MFA, Offset+1,
try
Vst = validate_mutation(I, Vst0),
vi(I, Vst)
catch Error ->
error({MFA, {I, Offset, Error}})
Expand Down Expand Up @@ -635,20 +630,6 @@ vi({put_tuple2,Dst,{list,Elements}}, Vst0) ->
end, {#{}, 1}, Elements),
Type = #t_tuple{exact=true,size=Size,elements=Es},
create_term(Type, put_tuple2, [], Dst, Vst);
vi({set_tuple_element,Src,Tuple,N}, Vst) ->
%% This instruction never fails, though it may be invalid in some contexts;
%% see validate_mutation/2
I = N + 1,
assert_term(Src, Vst),
assert_type(#t_tuple{size=I}, Tuple, Vst),
%% Manually update the tuple type; we can't rely on the ordinary update
%% helpers as we must support overwriting (rather than just widening or
%% narrowing) known elements, and we can't use extract_term either since
%% the source tuple may be aliased.
TupleType0 = get_term_type(Tuple, Vst),
ArgType = get_term_type(Src, Vst),
TupleType = beam_types:update_tuple(TupleType0, [{I, ArgType}]),
override_type(TupleType, Tuple, Vst);
vi({update_record,_Hint,Size,Src,Dst,{list,Ss}}, Vst) ->
verify_update_record(Size, Src, Dst, Ss, Vst);

Expand Down Expand Up @@ -1842,35 +1823,6 @@ type_test(Fail, Type, Reg0, Vst) ->
update_type(fun meet/2, Type, Reg, SuccVst)
end).

%%
%% Special state handling for setelement/3 and set_tuple_element/3 instructions.
%% A possibility for garbage collection must not occur between setelement/3 and
%% set_tuple_element/3.
%%
%% Note that #vst.current will be 'none' if the instruction is unreachable.
%%

validate_mutation(I, Vst) ->
vm_1(I, Vst).

vm_1({move,_,_}, Vst) ->
Vst;
vm_1({swap,_,_}, Vst) ->
Vst;
vm_1({call_ext,3,{extfunc,erlang,setelement,3}}, #vst{current=#st{}=St}=Vst) ->
Vst#vst{current=St#st{setelem=true}};
vm_1({set_tuple_element,_,_,_}, #vst{current=#st{setelem=false}}) ->
error(illegal_context_for_set_tuple_element);
vm_1({set_tuple_element,_,_,_}, #vst{current=#st{setelem=true}}=Vst) ->
Vst;
vm_1({get_tuple_element,_,_,_}, Vst) ->
Vst;
vm_1({line,_}, Vst) ->
Vst;
vm_1(_, #vst{current=#st{setelem=true}=St}=Vst) ->
Vst#vst{current=St#st{setelem=false}};
vm_1(_, Vst) -> Vst.

kill_state(Vst) ->
Vst#vst{current=none}.

Expand Down
3 changes: 3 additions & 0 deletions lib/compiler/src/genop.tab
Original file line number Diff line number Diff line change
Expand Up @@ -327,6 +327,9 @@ BEAM_FORMAT_NUMBER=0
## @spec set_tuple_element NewElement Tuple Position
## @doc Update the element at position Position of the tuple Tuple
## with the new element NewElement.
##
## TODO: As of Erlang/OTP 29, this instruction is no longer emitted
## by the compiler.
67: set_tuple_element/3

#
Expand Down
12 changes: 2 additions & 10 deletions lib/compiler/test/beam_validator_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,7 @@
overwrite_catchtag/1,overwrite_trytag/1,accessing_tags/1,bad_catch_try/1,
cons_guard/1,
freg_range/1,freg_uninit/1,
bad_bin_match/1,bad_dsetel/1,
bad_bin_match/1,
state_after_fault_in_catch/1,no_exception_in_catch/1,
undef_label/1,illegal_instruction/1,failing_gc_guard_bif/1,
map_field_lists/1,cover_bin_opt/1,
Expand Down Expand Up @@ -70,7 +70,7 @@ groups() ->
dead_code,
overwrite_catchtag,overwrite_trytag,accessing_tags,
bad_catch_try,cons_guard,freg_range,freg_uninit,
bad_bin_match,bad_dsetel,
bad_bin_match,
state_after_fault_in_catch,no_exception_in_catch,
undef_label,illegal_instruction,failing_gc_guard_bif,
map_field_lists,cover_bin_opt,val_dsetel,
Expand Down Expand Up @@ -299,14 +299,6 @@ bad_bin_match(Config) when is_list(Config) ->
do_val(bad_bin_match, Config),
ok.

bad_dsetel(Config) when is_list(Config) ->
Errors = do_val(bad_dsetel, Config),
[{{t,t,1},
{{set_tuple_element,{x,1},{x,0},1},
17,
illegal_context_for_set_tuple_element}}] = Errors,
ok.

state_after_fault_in_catch(Config) when is_list(Config) ->
Errors = do_val(state_after_fault_in_catch, Config),
[{{state_after_fault_in_catch,badmatch,1},
Expand Down
54 changes: 0 additions & 54 deletions lib/compiler/test/beam_validator_SUITE_data/bad_dsetel.S

This file was deleted.

Loading
Loading