Skip to content

Commit

Permalink
Merge branch 'bjorn/compiler/beam_validator/25/GH-7147/OTP-18565' int…
Browse files Browse the repository at this point in the history
…o maint-25

* bjorn/compiler/beam_validator/25/GH-7147/OTP-18565:
  Fix two type-related bugs
  • Loading branch information
Erlang/OTP committed May 4, 2023
2 parents 5612d3d + e5f3fea commit d754f32
Show file tree
Hide file tree
Showing 4 changed files with 110 additions and 9 deletions.
21 changes: 15 additions & 6 deletions lib/compiler/src/beam_ssa.erl
Original file line number Diff line number Diff line change
Expand Up @@ -372,13 +372,22 @@ successors(#b_blk{last=Terminator}) ->
-spec normalize(b_set() | terminator()) ->
b_set() | terminator().

normalize(#b_set{op={bif,Bif},args=Args}=Set) ->
normalize(#b_set{anno=Anno0,op={bif,Bif},args=Args}=Set) ->
case {is_commutative(Bif),Args} of
{false,_} ->
Set;
{true,[#b_literal{}=Lit,#b_var{}=Var]} ->
Set#b_set{args=[Var,Lit]};
{true,_} ->
{true, [#b_literal{}=Lit,#b_var{}=Var]} ->
Anno = case Anno0 of
#{arg_types := ArgTypes0} ->
case ArgTypes0 of
#{1 := Type} ->
Anno0#{arg_types => #{0 => Type}};
#{} ->
Anno0
end;
#{} ->
Anno0
end,
Set#b_set{anno=Anno,args=[Var,Lit]};
{_, _} ->
Set
end;
normalize(#b_set{}=Set) ->
Expand Down
2 changes: 1 addition & 1 deletion lib/compiler/src/beam_validator.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1463,7 +1463,7 @@ update_create_bin_list([], Vst) -> Vst.
update_create_bin_type(append) -> #t_bitstring{};
update_create_bin_type(private_append) -> #t_bitstring{};
update_create_bin_type(binary) -> #t_bitstring{};
update_create_bin_type(float) -> #t_float{};
update_create_bin_type(float) -> number;
update_create_bin_type(integer) -> #t_integer{};
update_create_bin_type(utf8) -> #t_integer{};
update_create_bin_type(utf16) -> #t_integer{};
Expand Down
90 changes: 88 additions & 2 deletions lib/compiler/test/beam_ssa_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,7 @@
beam_ssa_dead_crash/1,stack_init/1,
mapfoldl/0,mapfoldl/1,
grab_bag/1,redundant_br/1,
coverage/1]).
coverage/1,normalize/1]).

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

Expand All @@ -47,7 +47,8 @@ groups() ->
stack_init,
grab_bag,
redundant_br,
coverage
coverage,
normalize
]}].

init_per_suite(Config) ->
Expand Down Expand Up @@ -1178,5 +1179,90 @@ coverage_5() ->
error
end#coverage{name = whatever}.

%% Test beam_ssa:normalize/1, especially that argument types are
%% correctly updated when arguments are swapped.
normalize(_Config) ->
normalize_commutative({bif,'band'}),
normalize_commutative({bif,'+'}),

normalize_noncommutative({bif,'div'}),

ok.

-record(b_var, {name}).
-record(b_literal, {val}).

normalize_commutative(Op) ->
A = #b_var{name=a},
B = #b_var{name=b},
Lit = #b_literal{val=42},

normalize_same(Op, [A,B]),
normalize_same(Op, [A,Lit]),

normalize_swapped(Op, [Lit,A]),

ok.

normalize_noncommutative(Op) ->
A = #b_var{name=a},
B = #b_var{name=b},
Lit = #b_literal{val=42},

normalize_same(Op, [A,B]),
normalize_same(Op, [A,Lit]),

ArgTypes0 = [{1,beam_types:make_integer(0, 1023)}],
I1 = make_bset(ArgTypes0, Op, [Lit,A]),
I1 = beam_ssa:normalize(I1),

ok.

normalize_same(Op, Args) ->
I0 = make_bset(#{}, Op, Args),
I0 = beam_ssa:normalize(I0),

ArgTypes0 = [{0,beam_types:make_integer(0, 1023)}],
I1 = make_bset(ArgTypes0, Op, Args),
I1 = beam_ssa:normalize(I1),

case Args of
[#b_var{},#b_var{}] ->
ArgTypes1 = [{0,beam_types:make_integer(0, 1023)},
{1,beam_types:make_integer(42)}],
I2 = make_bset(ArgTypes1, Op, Args),
I2 = beam_ssa:normalize(I2);
[_,_] ->
ok
end,

ok.

normalize_swapped(Op, [#b_literal{}=Lit,#b_var{}=Var]=Args) ->
EmptyAnno = #{},
I0 = make_bset(EmptyAnno, Op, Args),
{b_set,EmptyAnno,#b_var{name=1000},Op,[Var,Lit]} = beam_ssa:normalize(I0),

EmptyTypes = #{arg_types => #{}},
I1 = make_bset(EmptyTypes, Op, Args),
{b_set,EmptyTypes,#b_var{name=1000},Op,[Var,Lit]} = beam_ssa:normalize(I1),

IntRange = beam_types:make_integer(0, 1023),
ArgTypes0 = [{1,IntRange}],
I2 = make_bset(ArgTypes0, Op, Args),
{[{0,IntRange}],Op,[Var,Lit]} = unpack_bset(beam_ssa:normalize(I2)),

ok.

make_bset(ArgTypes, Op, Args) when is_list(ArgTypes) ->
Anno = #{arg_types => maps:from_list(ArgTypes)},
{b_set,Anno,#b_var{name=1000},Op,Args};
make_bset(Anno, Op, Args) when is_map(Anno) ->
{b_set,Anno,#b_var{name=1000},Op,Args}.

unpack_bset({b_set,Anno,{b_var,1000},Op,Args}) ->
ArgTypes = maps:get(arg_types, Anno, #{}),
{lists:sort(maps:to_list(ArgTypes)),Op,Args}.

%% The identity function.
id(I) -> I.
6 changes: 6 additions & 0 deletions lib/compiler/test/beam_type_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -499,11 +499,17 @@ record_float(R, N0) ->

binary_float(_Config) ->
<<-1/float>> = binary_negate_float(<<1/float>>),
{'EXIT',{badarg,_}} = catch binary_float_1(id(64.0), id(0)),
ok.

binary_negate_float(<<Float/float>>) ->
<<-Float/float>>.

%% GH-7147.
binary_float_1(X, Y) ->
_ = <<Y:(ceil(64.0 = X))/float, (binary_to_integer(ok))>>,
ceil(X) band Y.

float_compare(_Config) ->
false = do_float_compare(-42.0),
false = do_float_compare(-42),
Expand Down

0 comments on commit d754f32

Please sign in to comment.