@@ -1164,10 +1164,12 @@ find_fc_errors([#b_function{bs=Blocks}|Fs], Acc0) ->
11641164find_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+
11711173expand_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 ;
11951197expand_update_tuple_1 ([], Count , Acc ) ->
1196- {Acc , Count }.
1198+ {reverse ( Acc ) , Count }.
11971199
11981200expand_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) ->
12091211expand_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.
12151217expand_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.
12421240sort_update_tuple ([_Index , _Value ]= Args , []) ->
12431241 Args ;
12441242sort_update_tuple ([# b_literal {}= Index , Value | Updates ], Acc ) ->
0 commit comments