Skip to content

Commit

Permalink
Merge branch 'maint'
Browse files Browse the repository at this point in the history
* maint:
  beam_ssa_bool: Fix miscompilation
  Fix crash when compiling is_list/1 call
  • Loading branch information
bjorng committed Aug 1, 2023
2 parents 68a8ab5 + cd1bfd0 commit 3fcb4ce
Show file tree
Hide file tree
Showing 4 changed files with 65 additions and 11 deletions.
32 changes: 23 additions & 9 deletions lib/compiler/src/beam_ssa_bool.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1040,15 +1040,11 @@ ensure_no_failing_instructions(First, Second, G, St) ->

can_fail({succeeded,_}, V, G) -> not eaten_by_phi(V, G);
can_fail(put_map, _, _) -> true;
can_fail(_, _, _) -> false.

eaten_by_phi(V, G) ->
{br,_,Fail} = get_targets(V, G),
case beam_digraph:vertex(G, Fail) of
br ->
[To] = beam_digraph:out_neighbours(G, Fail),
case beam_digraph:vertex(G, To) of
#b_set{op=phi} ->
can_fail(_, V, G) ->
case get_targets(V, G) of
{br,_Succ,Fail} ->
case follow_branch(G, Fail) of
{external,_} ->
true;
_ ->
false
Expand All @@ -1057,6 +1053,24 @@ eaten_by_phi(V, G) ->
false
end.

eaten_by_phi(V, G) ->
{br,_,Fail} = get_targets(V, G),
case follow_branch(G, Fail) of
#b_set{op=phi} ->
true;
_ ->
false
end.

follow_branch(G, Br) ->
case beam_digraph:vertex(G, Br) of
br ->
[To] = beam_digraph:out_neighbours(G, Br),
beam_digraph:vertex(G, To);
_ ->
none
end.

%% order_args([Arg1,Arg2], G, St) -> {First,Second}.
%% Order arguments for a boolean operator so that there is path in the
%% digraph from the instruction referered to by the first operand to
Expand Down
17 changes: 15 additions & 2 deletions lib/compiler/src/beam_ssa_codegen.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1266,9 +1266,22 @@ cg_block([#cg_set{op=is_tagged_tuple,anno=Anno,dst=Bool,args=Args0}], {Bool,Fail
[Src,{integer,Arity},Tag] = typed_args(Args0, Anno, St),
{[{test,is_tagged_tuple,ensure_label(Fail, St),[Src,Arity,Tag]}],St}
end;
cg_block([#cg_set{op=is_nonempty_list,dst=Bool,args=Args0}], {Bool,Fail}, St) ->
cg_block([#cg_set{op=is_nonempty_list,dst=Bool0,args=Args0}=Set], {Bool0,Fail0}, St) ->
Fail = ensure_label(Fail0, St),
Args = beam_args(Args0, St),
{[{test,is_nonempty_list,ensure_label(Fail, St),Args}],St};
case beam_args([Bool0|Args0], St) of
[{z,0}|Args] ->
{[{test,is_nonempty_list,Fail,Args}],St};
[Dst|Args] ->
%% This instruction was a call to is_list/1, which was
%% rewritten to an is_nonempty_list test by
%% beam_ssa_type. BEAM has no is_nonempty_list instruction
%% that will return a boolean, so we must revert it to an
%% is_list/1 call.
#cg_set{anno=#{was_bif_is_list := true}} = Set, %Assertion.
{[{bif,is_list,Fail0,Args,Dst},
{test,is_eq_exact,Fail,[Dst,{atom,true}]}],St}
end;
cg_block([#cg_set{op=has_map_field,dst=Dst0,args=Args0}], {Dst0,Fail0}, St) ->
Fail = ensure_label(Fail0, St),
case beam_args([Dst0|Args0], St) of
Expand Down
15 changes: 15 additions & 0 deletions lib/compiler/test/beam_type_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1137,6 +1137,11 @@ cs_2({bar,baz}) ->
is_list_opt(_Config) ->
true = is_list_opt_1(id(<<"application/a2l">>)),
false = is_list_opt_1(id(<<"">>)),

ok = is_list_opt_3(id([])),
true = is_list_opt_3(id([a])),
{'EXIT',{badarg,_}} = catch is_list_opt_3(id(no_list)),

ok.

is_list_opt_1(Type) ->
Expand All @@ -1148,6 +1153,16 @@ is_list_opt_1(Type) ->
is_list_opt_2(<<"application/a2l">>) -> [<<"a2l">>];
is_list_opt_2(_Type) -> nil.

is_list_opt_3([]) ->
ok;
is_list_opt_3(A) ->
%% The call to is_list/1 would be optimized to an is_nonempty_list
%% instruction, which only exists as a guard test that cannot
%% produce boolean value.
_ = (Bool = is_list(A)) orelse binary_to_integer(<<"">>),
Bool.


%% We used to determine the type of `get_tuple_element` at the time of
%% extraction, which is simple but sometimes throws away type information when
%% on tuple unions.
Expand Down
12 changes: 12 additions & 0 deletions lib/compiler/test/guard_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -2636,6 +2636,7 @@ beam_bool_SUITE(_Config) ->
gh_7252(),
gh_7339(),
gh_7370(),
gh_7517(),
ok.

before_and_inside_if() ->
Expand Down Expand Up @@ -3242,6 +3243,17 @@ gh_7370(A) when (not (not is_float(A))) =/= ((ok and ok) or true) ->
gh_7370(_) ->
b.

gh_7517() ->
ok = catch do_gh_7517([]),
ok = catch do_gh_7517([a,b,c]),
{'EXIT',{function_clause,_}} = catch do_gh_7517(ok),
{'EXIT',{function_clause,_}} = catch do_gh_7517(<<>>),
ok.

do_gh_7517(A) when (ok /= A) or is_float(is_list(A) orelse ok andalso ok) ->
ok.


%%%
%%% End of beam_bool_SUITE tests.
%%%
Expand Down

0 comments on commit 3fcb4ce

Please sign in to comment.