Skip to content

Commit d754f32

Browse files
author
Erlang/OTP
committed
Merge branch 'bjorn/compiler/beam_validator/25/GH-7147/OTP-18565' into maint-25
* bjorn/compiler/beam_validator/25/GH-7147/OTP-18565: Fix two type-related bugs
2 parents 5612d3d + e5f3fea commit d754f32

File tree

4 files changed

+110
-9
lines changed

4 files changed

+110
-9
lines changed

lib/compiler/src/beam_ssa.erl

Lines changed: 15 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -372,13 +372,22 @@ successors(#b_blk{last=Terminator}) ->
372372
-spec normalize(b_set() | terminator()) ->
373373
b_set() | terminator().
374374

375-
normalize(#b_set{op={bif,Bif},args=Args}=Set) ->
375+
normalize(#b_set{anno=Anno0,op={bif,Bif},args=Args}=Set) ->
376376
case {is_commutative(Bif),Args} of
377-
{false,_} ->
378-
Set;
379-
{true,[#b_literal{}=Lit,#b_var{}=Var]} ->
380-
Set#b_set{args=[Var,Lit]};
381-
{true,_} ->
377+
{true, [#b_literal{}=Lit,#b_var{}=Var]} ->
378+
Anno = case Anno0 of
379+
#{arg_types := ArgTypes0} ->
380+
case ArgTypes0 of
381+
#{1 := Type} ->
382+
Anno0#{arg_types => #{0 => Type}};
383+
#{} ->
384+
Anno0
385+
end;
386+
#{} ->
387+
Anno0
388+
end,
389+
Set#b_set{anno=Anno,args=[Var,Lit]};
390+
{_, _} ->
382391
Set
383392
end;
384393
normalize(#b_set{}=Set) ->

lib/compiler/src/beam_validator.erl

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1463,7 +1463,7 @@ update_create_bin_list([], Vst) -> Vst.
14631463
update_create_bin_type(append) -> #t_bitstring{};
14641464
update_create_bin_type(private_append) -> #t_bitstring{};
14651465
update_create_bin_type(binary) -> #t_bitstring{};
1466-
update_create_bin_type(float) -> #t_float{};
1466+
update_create_bin_type(float) -> number;
14671467
update_create_bin_type(integer) -> #t_integer{};
14681468
update_create_bin_type(utf8) -> #t_integer{};
14691469
update_create_bin_type(utf16) -> #t_integer{};

lib/compiler/test/beam_ssa_SUITE.erl

Lines changed: 88 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -26,7 +26,7 @@
2626
beam_ssa_dead_crash/1,stack_init/1,
2727
mapfoldl/0,mapfoldl/1,
2828
grab_bag/1,redundant_br/1,
29-
coverage/1]).
29+
coverage/1,normalize/1]).
3030

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

@@ -47,7 +47,8 @@ groups() ->
4747
stack_init,
4848
grab_bag,
4949
redundant_br,
50-
coverage
50+
coverage,
51+
normalize
5152
]}].
5253

5354
init_per_suite(Config) ->
@@ -1178,5 +1179,90 @@ coverage_5() ->
11781179
error
11791180
end#coverage{name = whatever}.
11801181

1182+
%% Test beam_ssa:normalize/1, especially that argument types are
1183+
%% correctly updated when arguments are swapped.
1184+
normalize(_Config) ->
1185+
normalize_commutative({bif,'band'}),
1186+
normalize_commutative({bif,'+'}),
1187+
1188+
normalize_noncommutative({bif,'div'}),
1189+
1190+
ok.
1191+
1192+
-record(b_var, {name}).
1193+
-record(b_literal, {val}).
1194+
1195+
normalize_commutative(Op) ->
1196+
A = #b_var{name=a},
1197+
B = #b_var{name=b},
1198+
Lit = #b_literal{val=42},
1199+
1200+
normalize_same(Op, [A,B]),
1201+
normalize_same(Op, [A,Lit]),
1202+
1203+
normalize_swapped(Op, [Lit,A]),
1204+
1205+
ok.
1206+
1207+
normalize_noncommutative(Op) ->
1208+
A = #b_var{name=a},
1209+
B = #b_var{name=b},
1210+
Lit = #b_literal{val=42},
1211+
1212+
normalize_same(Op, [A,B]),
1213+
normalize_same(Op, [A,Lit]),
1214+
1215+
ArgTypes0 = [{1,beam_types:make_integer(0, 1023)}],
1216+
I1 = make_bset(ArgTypes0, Op, [Lit,A]),
1217+
I1 = beam_ssa:normalize(I1),
1218+
1219+
ok.
1220+
1221+
normalize_same(Op, Args) ->
1222+
I0 = make_bset(#{}, Op, Args),
1223+
I0 = beam_ssa:normalize(I0),
1224+
1225+
ArgTypes0 = [{0,beam_types:make_integer(0, 1023)}],
1226+
I1 = make_bset(ArgTypes0, Op, Args),
1227+
I1 = beam_ssa:normalize(I1),
1228+
1229+
case Args of
1230+
[#b_var{},#b_var{}] ->
1231+
ArgTypes1 = [{0,beam_types:make_integer(0, 1023)},
1232+
{1,beam_types:make_integer(42)}],
1233+
I2 = make_bset(ArgTypes1, Op, Args),
1234+
I2 = beam_ssa:normalize(I2);
1235+
[_,_] ->
1236+
ok
1237+
end,
1238+
1239+
ok.
1240+
1241+
normalize_swapped(Op, [#b_literal{}=Lit,#b_var{}=Var]=Args) ->
1242+
EmptyAnno = #{},
1243+
I0 = make_bset(EmptyAnno, Op, Args),
1244+
{b_set,EmptyAnno,#b_var{name=1000},Op,[Var,Lit]} = beam_ssa:normalize(I0),
1245+
1246+
EmptyTypes = #{arg_types => #{}},
1247+
I1 = make_bset(EmptyTypes, Op, Args),
1248+
{b_set,EmptyTypes,#b_var{name=1000},Op,[Var,Lit]} = beam_ssa:normalize(I1),
1249+
1250+
IntRange = beam_types:make_integer(0, 1023),
1251+
ArgTypes0 = [{1,IntRange}],
1252+
I2 = make_bset(ArgTypes0, Op, Args),
1253+
{[{0,IntRange}],Op,[Var,Lit]} = unpack_bset(beam_ssa:normalize(I2)),
1254+
1255+
ok.
1256+
1257+
make_bset(ArgTypes, Op, Args) when is_list(ArgTypes) ->
1258+
Anno = #{arg_types => maps:from_list(ArgTypes)},
1259+
{b_set,Anno,#b_var{name=1000},Op,Args};
1260+
make_bset(Anno, Op, Args) when is_map(Anno) ->
1261+
{b_set,Anno,#b_var{name=1000},Op,Args}.
1262+
1263+
unpack_bset({b_set,Anno,{b_var,1000},Op,Args}) ->
1264+
ArgTypes = maps:get(arg_types, Anno, #{}),
1265+
{lists:sort(maps:to_list(ArgTypes)),Op,Args}.
1266+
11811267
%% The identity function.
11821268
id(I) -> I.

lib/compiler/test/beam_type_SUITE.erl

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -499,11 +499,17 @@ record_float(R, N0) ->
499499

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

504505
binary_negate_float(<<Float/float>>) ->
505506
<<-Float/float>>.
506507

508+
%% GH-7147.
509+
binary_float_1(X, Y) ->
510+
_ = <<Y:(ceil(64.0 = X))/float, (binary_to_integer(ok))>>,
511+
ceil(X) band Y.
512+
507513
float_compare(_Config) ->
508514
false = do_float_compare(-42.0),
509515
false = do_float_compare(-42),

0 commit comments

Comments
 (0)