Skip to content

Commit 0ff39ca

Browse files
committed
Fix register allocation in the presence of singled-valued phi nodes
With optimizations disabled, the register allocator in `beam_ssa_pre_codegen` could allocate different variables to the same register if single-valued phi nodes in a try/catch construct were present. Closes #7248
1 parent 8c0ea6b commit 0ff39ca

File tree

2 files changed

+109
-35
lines changed

2 files changed

+109
-35
lines changed

lib/compiler/src/beam_ssa_pre_codegen.erl

Lines changed: 56 additions & 33 deletions
Original file line numberDiff line numberDiff line change
@@ -815,9 +815,8 @@ do_sanitize_is(#b_set{op=Op,dst=Dst,args=Args0}=I0,
815815
Is, Last, InBlocks, Blocks, Count, Values, Changed0, Acc) ->
816816
Args = sanitize_args(Args0, Values),
817817
case sanitize_instr(Op, Args, I0, Blocks) of
818-
{value,Value0} ->
819-
Value = #b_literal{val=Value0},
820-
sanitize_is(Is, Last, InBlocks, Blocks, Count, Values#{Dst=>Value},
818+
{subst,Subst} ->
819+
sanitize_is(Is, Last, InBlocks, Blocks, Count, Values#{Dst => Subst},
821820
true, Acc);
822821
{ok,I} ->
823822
sanitize_is(Is, Last, InBlocks, Blocks, Count, Values, true, [I|Acc]);
@@ -865,20 +864,43 @@ sanitize_arg(Arg, _Values) ->
865864
sanitize_instr(phi, PhiArgs0, I, Blocks) ->
866865
PhiArgs = [{V,L} || {V,L} <- PhiArgs0,
867866
is_map_key(L, Blocks)],
868-
case phi_all_same_literal(PhiArgs) of
867+
case phi_all_same(PhiArgs) of
869868
true ->
870869
%% (Can only happen when some optimizations have been
871870
%% turned off.)
872871
%%
873-
%% This phi node always produces the same literal value.
874-
%% We must do constant propagation of the value to ensure
875-
%% that we can sanitize any instructions that don't accept
876-
%% literals (such as `get_hd`). This is necessary for
877-
%% correctness, because beam_ssa_codegen:prefer_xregs/2
878-
%% does constant propagation and could propagate a literal
879-
%% into an instruction that don't accept literals.
880-
[{#b_literal{val=Val},_}|_] = PhiArgs,
881-
{value,Val};
872+
%% This phi node always produces the same literal value or
873+
%% variable.
874+
%%
875+
%% We must do constant propagation of literal values to
876+
%% ensure that we can sanitize any instructions that don't
877+
%% accept literals (such as `get_hd`). This is necessary
878+
%% for correctness, because
879+
%% beam_ssa_codegen:prefer_xregs/2 does constant
880+
%% propagation and could propagate a literal into an
881+
%% instruction that don't accept literals.
882+
%%
883+
%% The singleton phi nodes generated for the try/catch
884+
%% construct are problematic. For example:
885+
%%
886+
%% try B = (A = bit_size(iolist_to_binary("a"))) rem 1 of
887+
%% _ -> A;
888+
%% _ -> B
889+
%% after
890+
%% ok
891+
%% end.
892+
%%
893+
%% The try expression exports three values, resulting in three
894+
%% singleton phi nodes (with optimizations disabled):
895+
%%
896+
%% _4 = phi { B, ^15 }
897+
%% A = phi { _2, ^15 }
898+
%% _14 = phi { B, ^15 }
899+
%%
900+
%% All three variable will be assigned to the same register,
901+
%% causing the correct variable (`A`) to be overwritten by `_14`.
902+
[{Subst,_}|_] = PhiArgs,
903+
{subst,Subst};
882904
false ->
883905
{ok,I#b_set{args=PhiArgs}}
884906
end;
@@ -891,7 +913,7 @@ sanitize_instr({bif,Bif}, [#b_literal{val=Lit}], _I) ->
891913
ok;
892914
true ->
893915
try
894-
{value,erlang:Bif(Lit)}
916+
{subst,#b_literal{val=erlang:Bif(Lit)}}
895917
catch
896918
error:_ ->
897919
ok
@@ -900,7 +922,7 @@ sanitize_instr({bif,Bif}, [#b_literal{val=Lit}], _I) ->
900922
sanitize_instr({bif,Bif}, [#b_literal{val=Lit1},#b_literal{val=Lit2}], _I) ->
901923
true = erl_bifs:is_pure(erlang, Bif, 2), %Assertion.
902924
try
903-
{value,erlang:Bif(Lit1, Lit2)}
925+
{subst,#b_literal{val=erlang:Bif(Lit1, Lit2)}}
904926
catch
905927
error:_ ->
906928
ok
@@ -913,43 +935,44 @@ sanitize_instr(bs_match, Args, I) ->
913935
%% other data types as well.
914936
{ok,I#b_set{op=bs_get,args=Args}};
915937
sanitize_instr(get_hd, [#b_literal{val=[Hd|_]}], _I) ->
916-
{value,Hd};
938+
{subst,#b_literal{val=Hd}};
917939
sanitize_instr(get_tl, [#b_literal{val=[_|Tl]}], _I) ->
918-
{value,Tl};
940+
{subst,#b_literal{val=Tl}};
919941
sanitize_instr(get_tuple_element, [#b_literal{val=T},
920942
#b_literal{val=I}], _I)
921943
when I < tuple_size(T) ->
922-
{value,element(I+1, T)};
923-
sanitize_instr(is_nonempty_list, [#b_literal{val=Lit}], _I) ->
924-
{value,case Lit of
925-
[_|_] -> true;
926-
_ -> false
927-
end};
944+
{subst,#b_literal{val=element(I+1, T)}};
945+
sanitize_instr(is_nonempty_list, [#b_literal{val=Term}], _I) ->
946+
Lit = case Term of
947+
[_|_] -> true;
948+
_ -> false
949+
end,
950+
{subst,#b_literal{val=Lit}};
928951
sanitize_instr(is_tagged_tuple, [#b_literal{val=Tuple},
929952
#b_literal{val=Arity},
930953
#b_literal{val=Tag}], _I)
931954
when is_integer(Arity), is_atom(Tag) ->
932955
if
933956
tuple_size(Tuple) =:= Arity, element(1, Tuple) =:= Tag ->
934-
{value,true};
957+
{subst,#b_literal{val=true}};
935958
true ->
936-
{value,false}
959+
{subst,#b_literal{val=false}}
937960
end;
938961
sanitize_instr(succeeded, [#b_literal{}], _I) ->
939-
{value,true};
962+
{subst,#b_literal{val=true}};
940963
sanitize_instr(_, _, _) ->
941964
ok.
942965

943-
phi_all_same_literal([{#b_literal{}=Arg, _From} | Phis]) ->
944-
phi_all_same_literal_1(Phis, Arg);
945-
phi_all_same_literal([_|_]) ->
966+
phi_all_same([{Arg,_From}|Phis]) ->
967+
phi_all_same_1(Phis, Arg);
968+
phi_all_same([_|_]) ->
946969
false.
947970

948-
phi_all_same_literal_1([{Arg, _From} | Phis], Arg) ->
949-
phi_all_same_literal_1(Phis, Arg);
950-
phi_all_same_literal_1([], _Arg) ->
971+
phi_all_same_1([{Arg,_From}|Phis], Arg) ->
972+
phi_all_same_1(Phis, Arg);
973+
phi_all_same_1([], _Arg) ->
951974
true;
952-
phi_all_same_literal_1(_Phis, _Arg) ->
975+
phi_all_same_1(_Phis, _Arg) ->
953976
false.
954977

955978
%%% Rewrite certain calls to erlang:error/{1,2} to specialized

lib/compiler/test/beam_ssa_SUITE.erl

Lines changed: 53 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -27,7 +27,8 @@
2727
beam_ssa_dead_crash/1,stack_init/1,
2828
mapfoldl/0,mapfoldl/1,
2929
grab_bag/1,redundant_br/1,
30-
coverage/1,normalize/1]).
30+
coverage/1,normalize/1,
31+
trycatch/1]).
3132

3233
suite() -> [{ct_hooks,[ts_install_cth]}].
3334

@@ -49,7 +50,8 @@ groups() ->
4950
grab_bag,
5051
redundant_br,
5152
coverage,
52-
normalize
53+
normalize,
54+
trycatch
5355
]}].
5456

5557
init_per_suite(Config) ->
@@ -1346,5 +1348,54 @@ unpack_bset({b_set,Anno,{b_var,1000},Op,Args}) ->
13461348
ArgTypes = maps:get(arg_types, Anno, #{}),
13471349
{lists:sort(maps:to_list(ArgTypes)),Op,Args}.
13481350

1351+
trycatch(_Config) ->
1352+
8 = trycatch_1(),
1353+
1354+
ok = trycatch_2(id(ok)),
1355+
ok = trycatch_2(id(z)),
1356+
1357+
false = trycatch_3(id(42)),
1358+
1359+
ok.
1360+
1361+
trycatch_1() ->
1362+
try B = (A = bit_size(iolist_to_binary("a"))) rem 1 of
1363+
_ ->
1364+
A;
1365+
_ ->
1366+
B
1367+
after
1368+
ok
1369+
end.
1370+
1371+
trycatch_2(A) ->
1372+
try not (B = (ok >= A)) of
1373+
B ->
1374+
iolist_size(maybe
1375+
[] ?= B,
1376+
<<>> ?= list_to_binary(ok)
1377+
end);
1378+
_ ->
1379+
ok
1380+
after
1381+
ok
1382+
end.
1383+
1384+
trycatch_3(A) ->
1385+
try erlang:bump_reductions(A) of
1386+
B ->
1387+
try not (C = (B andalso is_number(ok))) of
1388+
C ->
1389+
ok andalso ok;
1390+
_ ->
1391+
C
1392+
catch
1393+
_ ->
1394+
ok
1395+
end
1396+
after
1397+
ok
1398+
end.
1399+
13491400
%% The identity function.
13501401
id(I) -> I.

0 commit comments

Comments
 (0)