Skip to content

Commit a5064e9

Browse files
authored
Merge pull request #7902 from jhogberg/john/compiler/float-confusion/GH-7901
compiler: Fix some vestigial +0.0/-0.0 issues
2 parents 389ba97 + 34ef50c commit a5064e9

File tree

2 files changed

+121
-37
lines changed

2 files changed

+121
-37
lines changed

lib/compiler/src/beam_types.erl

Lines changed: 77 additions & 35 deletions
Original file line numberDiff line numberDiff line change
@@ -45,7 +45,6 @@
4545
make_boolean/0,
4646
make_cons/2,
4747
make_float/1,
48-
make_float/2,
4948
make_integer/1,
5049
make_integer/2]).
5150

@@ -169,10 +168,16 @@ mts_records([{Key, A} | RsA], [{Key, B} | RsB], Acc) ->
169168
none -> mts_records(RsA, RsB, Acc);
170169
T -> mts_records(RsA, RsB, [{Key, T} | Acc])
171170
end;
172-
mts_records([{KeyA, _} | _ ]=RsA, [{KeyB, _} | RsB], Acc) when KeyA > KeyB ->
173-
mts_records(RsA, RsB, Acc);
174-
mts_records([{KeyA, _} | RsA], [{KeyB, _} | _] = RsB, Acc) when KeyA < KeyB ->
175-
mts_records(RsA, RsB, Acc);
171+
mts_records([{KeyA, _} | _]=RsA, [{KeyB, _} | _]=RsB, Acc) ->
172+
%% We must use total ordering rather than plain '<' as -0.0 differs from
173+
%% +0.0
174+
case total_compare(KeyA, KeyB, fun erlang:'<'/2) of
175+
true ->
176+
mts_records(tl(RsA), RsB, Acc);
177+
false ->
178+
true = KeyA =/= KeyB, %Assertion.
179+
mts_records(RsA, tl(RsB), Acc)
180+
end;
176181
mts_records(_RsA, [], [_|_]=Acc) ->
177182
reverse(Acc);
178183
mts_records([], _RsB, [_|_]=Acc) ->
@@ -320,10 +325,16 @@ jts_records(RsA, RsB, N, Acc) when N > ?TUPLE_SET_LIMIT ->
320325
#t_tuple{} = normalize_tuple_set(Acc, B);
321326
jts_records([{Key, A} | RsA], [{Key, B} | RsB], N, Acc) ->
322327
jts_records(RsA, RsB, N + 1, [{Key, lub(A, B)} | Acc]);
323-
jts_records([{KeyA, _} | _]=RsA, [{KeyB, B} | RsB], N, Acc) when KeyA > KeyB ->
324-
jts_records(RsA, RsB, N + 1, [{KeyB, B} | Acc]);
325-
jts_records([{KeyA, A} | RsA], [{KeyB, _} | _] = RsB, N, Acc) when KeyA < KeyB ->
326-
jts_records(RsA, RsB, N + 1, [{KeyA, A} | Acc]);
328+
jts_records([{KeyA, A} | _]=RsA, [{KeyB, B} | _]=RsB, N, Acc) ->
329+
%% We must use total ordering rather than plain '<' as -0.0 differs from
330+
%% +0.0
331+
case total_compare(KeyA, KeyB, fun erlang:'<'/2) of
332+
true ->
333+
jts_records(tl(RsA), RsB, N + 1, [{KeyA, A} | Acc]);
334+
false ->
335+
true = KeyA =/= KeyB, %Assertion.
336+
jts_records(RsA, tl(RsB), N + 1, [{KeyB, B} | Acc])
337+
end;
327338
jts_records([{KeyA, A} | RsA], [], N, Acc) ->
328339
jts_records(RsA, [], N + 1, [{KeyA, A} | Acc]);
329340
jts_records([], [{KeyB, B} | RsB], N, Acc) ->
@@ -479,8 +490,7 @@ is_bs_matchable_type(Type) ->
479490
Result :: {ok, term()} | error.
480491
get_singleton_value(#t_atom{elements=[Atom]}) ->
481492
{ok, Atom};
482-
get_singleton_value(#t_float{elements={Float,Float}}) when Float /= 0 ->
483-
%% 0.0 is not actually a singleton as it has two encodings: 0.0 and -0.0
493+
get_singleton_value(#t_float{elements={Float,Float}}) ->
484494
{ok, Float};
485495
get_singleton_value(#t_integer{elements={Int,Int}}) ->
486496
{ok, Int};
@@ -697,11 +707,7 @@ make_cons(Head0, Tail) ->
697707

698708
-spec make_float(float()) -> type().
699709
make_float(Float) when is_float(Float) ->
700-
make_float(Float, Float).
701-
702-
-spec make_float(float(), float()) -> type().
703-
make_float(Min, Max) when is_float(Min), is_float(Max), Min =< Max ->
704-
#t_float{elements={Min, Max}}.
710+
#t_float{elements={Float,Float}}.
705711

706712
-spec make_integer(integer()) -> type().
707713
make_integer(Int) when is_integer(Int) ->
@@ -882,7 +888,7 @@ glb(#t_integer{elements=R1}, #t_integer{elements=R2}) ->
882888
glb(#t_integer{elements=R1}, #t_number{elements=R2}) ->
883889
integer_from_range(glb_ranges(R1, R2));
884890
glb(#t_float{elements=R1}, #t_number{elements=R2}) ->
885-
float_from_range(glb_ranges(R1, R2));
891+
float_from_range(glb_ranges(R1, number_to_float_range(R2)));
886892
glb(#t_list{type=TypeA,terminator=TermA},
887893
#t_list{type=TypeB,terminator=TermB}) ->
888894
%% A list is a union of `[type() | _]` and `[]`, so we're left with
@@ -903,7 +909,7 @@ glb(#t_number{elements=R1}, #t_number{elements=R2}) ->
903909
glb(#t_number{elements=R1}, #t_integer{elements=R2}) ->
904910
integer_from_range(glb_ranges(R1, R2));
905911
glb(#t_number{elements=R1}, #t_float{elements=R2}) ->
906-
float_from_range(glb_ranges(R1, R2));
912+
float_from_range(glb_ranges(number_to_float_range(R1), R2));
907913
glb(#t_map{super_key=SKeyA,super_value=SValueA},
908914
#t_map{super_key=SKeyB,super_value=SValueB}) ->
909915
%% Note the use of meet/2; elements don't need to be normal types.
@@ -1132,6 +1138,14 @@ lub_ranges({MinA,MaxA}, {MinB,MaxB}) ->
11321138
lub_ranges(_, _) ->
11331139
any.
11341140

1141+
%% Expands integer 0 to `-0.0 .. +0.0`
1142+
number_to_float_range({Min, 0}) ->
1143+
number_to_float_range({Min, +0.0});
1144+
number_to_float_range({0, Max}) ->
1145+
number_to_float_range({-0.0, Max});
1146+
number_to_float_range(Other) ->
1147+
Other.
1148+
11351149
lub_bs_matchable(UnitA, UnitB) ->
11361150
#t_bs_matchable{tail_unit=gcd(UnitA, UnitB)}.
11371151

@@ -1179,12 +1193,13 @@ float_from_range(none) ->
11791193
none;
11801194
float_from_range(any) ->
11811195
#t_float{};
1182-
float_from_range({Min0,Max0}) ->
1183-
case {safe_float(Min0),safe_float(Max0)} of
1196+
float_from_range({Min0, Max0}) ->
1197+
true = inf_le(Min0, Max0), %Assertion.
1198+
case {safe_float(Min0), safe_float(Max0)} of
11841199
{'-inf','+inf'} ->
11851200
#t_float{};
1186-
{Min,Max} ->
1187-
#t_float{elements={Min,Max}}
1201+
{Min, Max} ->
1202+
#t_float{elements={Min, Max}}
11881203
end.
11891204

11901205
safe_float(N) when is_number(N) ->
@@ -1218,21 +1233,48 @@ number_from_range(N) ->
12181233
none
12191234
end.
12201235

1221-
inf_le('-inf', _) -> true;
1222-
inf_le(A, B) -> A =< B.
1223-
1224-
inf_ge(_, '-inf') -> true;
1225-
inf_ge('-inf', _) -> false;
1226-
inf_ge(A, B) -> A >= B.
1236+
inf_le('-inf', _) ->
1237+
true;
1238+
inf_le(A, B) when is_float(A), is_float(B) ->
1239+
%% When float ranges are compared to float ranges, the total ordering
1240+
%% function must be used to preserve `-0.0 =/= +0.0`.
1241+
total_compare(A, B, fun erlang:'=<'/2);
1242+
inf_le(A, B) ->
1243+
A =< B.
1244+
1245+
inf_ge(_, '-inf') ->
1246+
true;
1247+
inf_ge('-inf', _) ->
1248+
false;
1249+
inf_ge(A, B) when is_float(A), is_float(B) ->
1250+
total_compare(A, B, fun erlang:'>='/2);
1251+
inf_ge(A, B) ->
1252+
A >= B.
1253+
1254+
inf_min(A, B) when A =:= '-inf'; B =:= '-inf' ->
1255+
'-inf';
1256+
inf_min(A, B) when is_float(A), is_float(B) ->
1257+
case total_compare(A, B, fun erlang:'=<'/2) of
1258+
true -> A;
1259+
false -> B
1260+
end;
1261+
inf_min(A, B) ->
1262+
min(A, B).
12271263

1228-
inf_min(A, B) when A =:= '-inf'; B =:= '-inf' -> '-inf';
1229-
inf_min(A, B) when A =< B -> A;
1230-
inf_min(A, B) when A > B -> B.
1264+
inf_max('-inf', B) ->
1265+
B;
1266+
inf_max(A, '-inf') ->
1267+
A;
1268+
inf_max(A, B) when is_float(A), is_float(B) ->
1269+
case total_compare(A, B, fun erlang:'>='/2) of
1270+
true -> A;
1271+
false -> B
1272+
end;
1273+
inf_max(A, B) ->
1274+
max(A, B).
12311275

1232-
inf_max('-inf', B) -> B;
1233-
inf_max(A, '-inf') -> A;
1234-
inf_max(A, B) when A >= B -> A;
1235-
inf_max(A, B) when A < B -> B.
1276+
total_compare(A, B, Order) ->
1277+
Order(erts_internal:cmp_term(A, B), 0).
12361278

12371279
%%
12381280

lib/compiler/test/beam_type_SUITE.erl

Lines changed: 44 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -31,7 +31,7 @@
3131
switch_fail_inference/1,failures/1,
3232
cover_maps_functions/1,min_max_mixed_types/1,
3333
not_equal/1,infer_relops/1,binary_unit/1,premature_concretization/1,
34-
funs/1,will_succeed/1]).
34+
funs/1,will_succeed/1,float_confusion/1]).
3535

3636
%% Force id/1 to return 'any'.
3737
-export([id/1]).
@@ -76,7 +76,8 @@ groups() ->
7676
binary_unit,
7777
premature_concretization,
7878
funs,
79-
will_succeed
79+
will_succeed,
80+
float_confusion
8081
]}].
8182

8283
init_per_suite(Config) ->
@@ -1505,6 +1506,47 @@ will_succeed_1(_V0, _V1)
15051506
will_succeed_1(_, _) ->
15061507
b.
15071508

1509+
%% GH-7901: Range operations did not honor the total order of floats.
1510+
float_confusion(_Config) ->
1511+
ok = float_confusion_1(catch (true = ok), -0.0),
1512+
ok = float_confusion_1(ok, 0.0),
1513+
{'EXIT', _} = catch float_confusion_2(),
1514+
{'EXIT', _} = catch float_confusion_3(id(0.0)),
1515+
ok = float_confusion_4(id(1)),
1516+
{'EXIT', _} = catch float_confusion_5(),
1517+
ok.
1518+
1519+
float_confusion_1(_, _) ->
1520+
ok.
1521+
1522+
float_confusion_2() ->
1523+
[ok || _ := _ <- ok,
1524+
float_confusion_crash(catch float_confusion_crash(ok, -1), -0.0)].
1525+
1526+
float_confusion_crash(_, 18446744073709551615) ->
1527+
ok.
1528+
1529+
float_confusion_3(V) ->
1530+
-0.0 = abs(V),
1531+
ok.
1532+
1533+
float_confusion_4(V) when -0.0 < floor(V band 1) ->
1534+
ok.
1535+
1536+
float_confusion_5() ->
1537+
-0.0 =
1538+
case
1539+
fun() ->
1540+
ok
1541+
end
1542+
of
1543+
_V2 when (_V2 > ok) ->
1544+
2147483647.0;
1545+
_ ->
1546+
-2147483648
1547+
end * 0,
1548+
ok.
1549+
15081550
%%%
15091551
%%% Common utilities.
15101552
%%%

0 commit comments

Comments
 (0)