Skip to content

Commit ae1ce45

Browse files
authored
Merge pull request #10144 from bjorng/bjorn/compiler/eliminate-set_tuple_element/GH-10125/OTP-19751
Eliminate the set_tuple_element instruction
2 parents cd3f64f + a144913 commit ae1ce45

File tree

10 files changed

+244
-152
lines changed

10 files changed

+244
-152
lines changed

erts/emulator/beam/jit/arm/instr_common.cpp

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1102,6 +1102,11 @@ void BeamModuleAssembler::emit_update_record_in_place(
11021102
void BeamModuleAssembler::emit_set_tuple_element(const ArgSource &Element,
11031103
const ArgRegister &Tuple,
11041104
const ArgWord &Offset) {
1105+
/* TODO: As of Erlang/OTP 29, this instruction is no longer
1106+
* emitted by the compiler. It can be removed when the runtime
1107+
* system no longer supports loading code compiled by Erlang/OTP
1108+
* 28 or earlier. */
1109+
11051110
auto tuple = load_source(Tuple, TMP1);
11061111
auto element = load_source(Element, TMP2);
11071112
a64::Gp boxed_ptr = emit_ptr_val(TMP1, tuple.reg);

erts/emulator/beam/jit/x86/instr_common.cpp

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1115,6 +1115,11 @@ void BeamModuleAssembler::emit_update_record_in_place(
11151115
void BeamModuleAssembler::emit_set_tuple_element(const ArgSource &Element,
11161116
const ArgRegister &Tuple,
11171117
const ArgWord &Offset) {
1118+
/* TODO: As of Erlang/OTP 29, this instruction is no longer
1119+
* emitted by the compiler. It can be removed when the runtime
1120+
* system no longer supports loading code compiled by Erlang/OTP
1121+
* 28 or earlier. */
1122+
11181123
mov_arg(ARG1, Tuple);
11191124

11201125
x86::Gp boxed_ptr = emit_ptr_val(ARG1, ARG1);

lib/compiler/src/beam_ssa_opt.erl

Lines changed: 75 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -298,7 +298,8 @@ early_epilogue_passes(Opts) ->
298298
Ps = [?PASS(ssa_opt_type_finish),
299299
?PASS(ssa_opt_float),
300300
?PASS(ssa_opt_sw),
301-
?PASS(ssa_opt_no_reuse)],
301+
?PASS(ssa_opt_no_reuse),
302+
?PASS(ssa_opt_deoptimize_update_tuple)],
302303
passes_1(Ps, Opts).
303304

304305
late_epilogue_passes(Opts) ->
@@ -3830,6 +3831,79 @@ cannot_reuse([V|Values], New) ->
38303831
cannot_reuse([], _New) ->
38313832
false.
38323833

3834+
3835+
%%%
3836+
%%% Undo the merging of `update_tuple` instructions performed by the
3837+
%%% beam_ssa_update_tuple sub-pass. The beam_ssa_pre_codegen pass will soon
3838+
%%% convert each `update_tuple` pseudo-instruction back into a setelement/3
3839+
%%% call. To minimize the number of such calls, each `update_tuple`
3840+
%%% instruction should ideally update only a single element of the tuple.
3841+
%%%
3842+
3843+
ssa_opt_deoptimize_update_tuple({#opt_st{ssa=Linear0}=St, FuncDb})
3844+
when is_list(Linear0) ->
3845+
Linear = deoptimize_update_tuple(Linear0),
3846+
{St#opt_st{ssa=Linear}, FuncDb}.
3847+
3848+
deoptimize_update_tuple(Linear) ->
3849+
Map = #{0 => #{}},
3850+
deoptimize_update_tuple(Linear, Map).
3851+
3852+
deoptimize_update_tuple([{L,Blk0}|Bs], Map0) ->
3853+
Data0 = maps:get(L, Map0, #{}),
3854+
#b_blk{is=Is0} = Blk0,
3855+
{Is,Data} = deoptimize_update_tuple_is(Is0, Data0, []),
3856+
Blk = if
3857+
Is =:= Is0 -> Blk0;
3858+
true -> Blk0#b_blk{is=Is}
3859+
end,
3860+
Successors = beam_ssa:successors(Blk),
3861+
Map = dut_update_successors(Successors, Data, Map0),
3862+
[{L,Blk}|deoptimize_update_tuple(Bs, Map)];
3863+
deoptimize_update_tuple([], _) ->
3864+
[].
3865+
3866+
dut_update_successors([L|Ls], Data0, Map) ->
3867+
case Map of
3868+
#{L := Data1} ->
3869+
Data = maps:intersect(Data1, Data0),
3870+
dut_update_successors(Ls, Data0, Map#{L := Data});
3871+
#{} ->
3872+
dut_update_successors(Ls, Data0, Map#{L => Data0})
3873+
end;
3874+
dut_update_successors([], _, Map) ->
3875+
Map.
3876+
3877+
deoptimize_update_tuple_is([#b_set{op=update_tuple,dst=Dst,
3878+
args=Args0}=I0|Is], Data0, Acc) ->
3879+
[Src|Args1] = Args0,
3880+
Args = dut_simplify(Src, Args1, Data0),
3881+
I = I0#b_set{args=Args},
3882+
Data = Data0#{Dst => {Src,Args1}},
3883+
deoptimize_update_tuple_is(Is, Data, [I|Acc]);
3884+
deoptimize_update_tuple_is([I|Is], Data, Acc) ->
3885+
deoptimize_update_tuple_is(Is, Data, [I|Acc]);
3886+
deoptimize_update_tuple_is([], Data, Acc) ->
3887+
{reverse(Acc),Data}.
3888+
3889+
dut_simplify(Src, Args0, Data) ->
3890+
L0 = [{V,dut_simplify_1(Args0, As)} || V := {S,As} <:- Data, S =:= Src],
3891+
L1 = [{length(As),[V|As]} || {V,As} <:- L0, As =/= none],
3892+
case sort(L1) of
3893+
[] ->
3894+
[Src|Args0];
3895+
[{_,Args}|_] ->
3896+
Args
3897+
end.
3898+
3899+
dut_simplify_1([P,V|Args], [P,V|As]) ->
3900+
dut_simplify_1(Args, As);
3901+
dut_simplify_1([_|_]=Args, []) ->
3902+
Args;
3903+
dut_simplify_1(_, _) ->
3904+
none.
3905+
3906+
38333907
%%%
38343908
%%% Common utilities.
38353909
%%%

lib/compiler/src/beam_ssa_pre_codegen.erl

Lines changed: 34 additions & 36 deletions
Original file line numberDiff line numberDiff line change
@@ -1164,10 +1164,12 @@ find_fc_errors([#b_function{bs=Blocks}|Fs], Acc0) ->
11641164
find_fc_errors([], Acc) ->
11651165
Acc.
11661166

1167-
%%% expand_update_tuple(St0) -> St
1168-
%%%
1169-
%%% Expands the update_tuple psuedo-instruction into its actual instructions.
1170-
%%%
1167+
%%% Expands the `update_tuple` pseudo-instruction into `setelement/3`
1168+
%%% calls. Provided that the ssa_opt_deoptimize_update_tuple sub-pass
1169+
%%% in beam_ssa_opt has completely broken apart all `update_tuple`
1170+
%%% instructions, this should result in the same number of
1171+
%%% `setelement/3`calls as in the original source code.
1172+
11711173
expand_update_tuple(#st{ssa=Blocks0,cnt=Count0}=St) ->
11721174
Linear0 = beam_ssa:linearize(Blocks0),
11731175
{Linear, Count} = expand_update_tuple_1(Linear0, Count0, []),
@@ -1179,9 +1181,9 @@ expand_update_tuple_1([{L, #b_blk{is=Is0}=B0} | Bs], Count0, Acc0) ->
11791181
{Is, Count} ->
11801182
expand_update_tuple_1(Bs, Count, [{L, B0#b_blk{is=Is}} | Acc0]);
11811183
{Is, NextIs, Count1} ->
1182-
%% There are `set_tuple_element` instructions that we must put into
1183-
%% a new block to avoid separating the `setelement` instruction from
1184-
%% its `succeeded` instruction.
1184+
%% There are `setelement/3` calls that we must put into a
1185+
%% new block to avoid separating the first `setelement/3`
1186+
%% instruction from its `succeeded` instruction.
11851187
#b_blk{last=Br} = B0,
11861188
#b_br{succ=Succ} = Br,
11871189
NextL = Count1,
@@ -1193,14 +1195,14 @@ expand_update_tuple_1([{L, #b_blk{is=Is0}=B0} | Bs], Count0, Acc0) ->
11931195
expand_update_tuple_1(Bs, Count, Acc)
11941196
end;
11951197
expand_update_tuple_1([], Count, Acc) ->
1196-
{Acc, Count}.
1198+
{reverse(Acc), Count}.
11971199

11981200
expand_update_tuple_is([#b_set{op=update_tuple, args=[Src | Args]}=I0 | Is],
1199-
Count0, Acc) ->
1201+
Count0, Acc) ->
12001202
{SetElement, Sets, Count} = expand_update_tuple_list(Args, I0, Src, Count0),
12011203
case {Sets, Is} of
1202-
{[_ | _], [#b_set{op=succeeded}]} ->
1203-
{reverse(Acc, [SetElement | Is]), reverse(Sets), Count};
1204+
{[_ | _], [#b_set{op=succeeded}=I]} ->
1205+
{reverse(Acc, [SetElement, I]), reverse(Sets), Count};
12041206
{_, _} ->
12051207
expand_update_tuple_is(Is, Count, Sets ++ [SetElement | Acc])
12061208
end;
@@ -1209,36 +1211,32 @@ expand_update_tuple_is([I | Is], Count, Acc) ->
12091211
expand_update_tuple_is([], Count, Acc) ->
12101212
{reverse(Acc), Count}.
12111213

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

1218-
%% set_tuple_element is destructive, so we have to start off with a
1219-
%% setelement/3 call to give them something to work on.
1220-
I = I0#b_set{op=call,
1221-
args=[#b_remote{mod=#b_literal{val=erlang},
1222-
name=#b_literal{val=setelement},
1223-
arity=3},
1224-
Index, Src, Value]},
1225-
{Sets, Count} = expand_update_tuple_list_1(Rest, I#b_set.dst, Count0, []),
1226-
{I, Sets, Count}.
1227-
1228-
expand_update_tuple_list_1([], _Src, Count, Acc) ->
1229-
{Acc, Count};
1230-
expand_update_tuple_list_1([Index0, Value | Updates], Src, Count0, Acc) ->
1231-
%% Change to the 0-based indexing used by `set_tuple_element`.
1232-
Index = #b_literal{val=(Index0#b_literal.val - 1)},
1221+
expand_update_tuple_list_1([Index, Value | Updates], Src, I0, Count0, Acc) ->
12331222
{Dst, Count} = new_var(Count0),
1234-
SetOp = #b_set{op=set_tuple_element,
1235-
dst=Dst,
1236-
args=[Value, Src, Index]},
1237-
expand_update_tuple_list_1(Updates, Src, Count, [SetOp | Acc]).
1238-
1239-
%% Sorts updates so that the highest index comes first, letting us use
1240-
%% set_tuple_element for all subsequent operations as we know their indexes
1241-
%% will be valid.
1223+
I = I0#b_set{op=call,
1224+
dst=Dst,
1225+
args=[#b_remote{mod=#b_literal{val=erlang},
1226+
name=#b_literal{val=setelement},
1227+
arity=3},
1228+
Index, Src, Value]},
1229+
expand_update_tuple_list_1(Updates, Dst, I0, Count, [I | Acc]);
1230+
expand_update_tuple_list_1([], _Src, #b_set{dst=Dst}, Count, [I0|Acc]) ->
1231+
I1 = I0#b_set{dst=Dst},
1232+
Is0 = [I1|Acc],
1233+
I = last(Is0),
1234+
Is = lists:droplast(Is0),
1235+
{I, Is, Count}.
1236+
1237+
%% Sorts updates so that the highest index comes first letting us use
1238+
%% `setelement/3` calls not followed by `succeeded` for all
1239+
%% subsequent operations as we know that their indices will be valid.
12421240
sort_update_tuple([_Index, _Value]=Args, []) ->
12431241
Args;
12441242
sort_update_tuple([#b_literal{}=Index, Value | Updates], Acc) ->

lib/compiler/src/beam_validator.erl

Lines changed: 1 addition & 49 deletions
Original file line numberDiff line numberDiff line change
@@ -204,10 +204,6 @@ validate_0([{function, Name, Arity, Entry, Code} | Fs], Module, Level, Ft) ->
204204
hf=0,
205205
%% List of hot catch/try tags
206206
ct=[],
207-
%% Previous instruction was setelement/3.
208-
setelem=false,
209-
%% put/1 instructions left.
210-
puts_left=none,
211207
%% Current receive state:
212208
%%
213209
%% * 'none' - Not in a receive loop.
@@ -331,10 +327,9 @@ validate_branches(MFA, Vst) ->
331327
Vst
332328
end.
333329

334-
validate_instrs([I|Is], MFA, Offset, Vst0) ->
330+
validate_instrs([I|Is], MFA, Offset, Vst) ->
335331
validate_instrs(Is, MFA, Offset+1,
336332
try
337-
Vst = validate_mutation(I, Vst0),
338333
vi(I, Vst)
339334
catch Error ->
340335
error({MFA, {I, Offset, Error}})
@@ -635,20 +630,6 @@ vi({put_tuple2,Dst,{list,Elements}}, Vst0) ->
635630
end, {#{}, 1}, Elements),
636631
Type = #t_tuple{exact=true,size=Size,elements=Es},
637632
create_term(Type, put_tuple2, [], Dst, Vst);
638-
vi({set_tuple_element,Src,Tuple,N}, Vst) ->
639-
%% This instruction never fails, though it may be invalid in some contexts;
640-
%% see validate_mutation/2
641-
I = N + 1,
642-
assert_term(Src, Vst),
643-
assert_type(#t_tuple{size=I}, Tuple, Vst),
644-
%% Manually update the tuple type; we can't rely on the ordinary update
645-
%% helpers as we must support overwriting (rather than just widening or
646-
%% narrowing) known elements, and we can't use extract_term either since
647-
%% the source tuple may be aliased.
648-
TupleType0 = get_term_type(Tuple, Vst),
649-
ArgType = get_term_type(Src, Vst),
650-
TupleType = beam_types:update_tuple(TupleType0, [{I, ArgType}]),
651-
override_type(TupleType, Tuple, Vst);
652633
vi({update_record,_Hint,Size,Src,Dst,{list,Ss}}, Vst) ->
653634
verify_update_record(Size, Src, Dst, Ss, Vst);
654635

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

1845-
%%
1846-
%% Special state handling for setelement/3 and set_tuple_element/3 instructions.
1847-
%% A possibility for garbage collection must not occur between setelement/3 and
1848-
%% set_tuple_element/3.
1849-
%%
1850-
%% Note that #vst.current will be 'none' if the instruction is unreachable.
1851-
%%
1852-
1853-
validate_mutation(I, Vst) ->
1854-
vm_1(I, Vst).
1855-
1856-
vm_1({move,_,_}, Vst) ->
1857-
Vst;
1858-
vm_1({swap,_,_}, Vst) ->
1859-
Vst;
1860-
vm_1({call_ext,3,{extfunc,erlang,setelement,3}}, #vst{current=#st{}=St}=Vst) ->
1861-
Vst#vst{current=St#st{setelem=true}};
1862-
vm_1({set_tuple_element,_,_,_}, #vst{current=#st{setelem=false}}) ->
1863-
error(illegal_context_for_set_tuple_element);
1864-
vm_1({set_tuple_element,_,_,_}, #vst{current=#st{setelem=true}}=Vst) ->
1865-
Vst;
1866-
vm_1({get_tuple_element,_,_,_}, Vst) ->
1867-
Vst;
1868-
vm_1({line,_}, Vst) ->
1869-
Vst;
1870-
vm_1(_, #vst{current=#st{setelem=true}=St}=Vst) ->
1871-
Vst#vst{current=St#st{setelem=false}};
1872-
vm_1(_, Vst) -> Vst.
1873-
18741826
kill_state(Vst) ->
18751827
Vst#vst{current=none}.
18761828

lib/compiler/src/genop.tab

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -327,6 +327,9 @@ BEAM_FORMAT_NUMBER=0
327327
## @spec set_tuple_element NewElement Tuple Position
328328
## @doc Update the element at position Position of the tuple Tuple
329329
## with the new element NewElement.
330+
##
331+
## TODO: As of Erlang/OTP 29, this instruction is no longer emitted
332+
## by the compiler.
330333
67: set_tuple_element/3
331334

332335
#

lib/compiler/test/beam_validator_SUITE.erl

Lines changed: 2 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -31,7 +31,7 @@
3131
overwrite_catchtag/1,overwrite_trytag/1,accessing_tags/1,bad_catch_try/1,
3232
cons_guard/1,
3333
freg_range/1,freg_uninit/1,
34-
bad_bin_match/1,bad_dsetel/1,
34+
bad_bin_match/1,
3535
state_after_fault_in_catch/1,no_exception_in_catch/1,
3636
undef_label/1,illegal_instruction/1,failing_gc_guard_bif/1,
3737
map_field_lists/1,cover_bin_opt/1,
@@ -70,7 +70,7 @@ groups() ->
7070
dead_code,
7171
overwrite_catchtag,overwrite_trytag,accessing_tags,
7272
bad_catch_try,cons_guard,freg_range,freg_uninit,
73-
bad_bin_match,bad_dsetel,
73+
bad_bin_match,
7474
state_after_fault_in_catch,no_exception_in_catch,
7575
undef_label,illegal_instruction,failing_gc_guard_bif,
7676
map_field_lists,cover_bin_opt,val_dsetel,
@@ -299,14 +299,6 @@ bad_bin_match(Config) when is_list(Config) ->
299299
do_val(bad_bin_match, Config),
300300
ok.
301301

302-
bad_dsetel(Config) when is_list(Config) ->
303-
Errors = do_val(bad_dsetel, Config),
304-
[{{t,t,1},
305-
{{set_tuple_element,{x,1},{x,0},1},
306-
17,
307-
illegal_context_for_set_tuple_element}}] = Errors,
308-
ok.
309-
310302
state_after_fault_in_catch(Config) when is_list(Config) ->
311303
Errors = do_val(state_after_fault_in_catch, Config),
312304
[{{state_after_fault_in_catch,badmatch,1},

lib/compiler/test/beam_validator_SUITE_data/bad_dsetel.S

Lines changed: 0 additions & 54 deletions
This file was deleted.

0 commit comments

Comments
 (0)