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 ;
176181mts_records (_RsA , [], [_ |_ ]= Acc ) ->
177182 reverse (Acc );
178183mts_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 );
321326jts_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 ;
327338jts_records ([{KeyA , A } | RsA ], [], N , Acc ) ->
328339 jts_records (RsA , [], N + 1 , [{KeyA , A } | Acc ]);
329340jts_records ([], [{KeyB , B } | RsB ], N , Acc ) ->
@@ -479,8 +490,7 @@ is_bs_matchable_type(Type) ->
479490 Result :: {ok , term ()} | error .
480491get_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 };
485495get_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 ().
699709make_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 ().
707713make_integer (Int ) when is_integer (Int ) ->
@@ -882,7 +888,7 @@ glb(#t_integer{elements=R1}, #t_integer{elements=R2}) ->
882888glb (# t_integer {elements = R1 }, # t_number {elements = R2 }) ->
883889 integer_from_range (glb_ranges (R1 , R2 ));
884890glb (# 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 ) ));
886892glb (# 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}) ->
903909glb (# t_number {elements = R1 }, # t_integer {elements = R2 }) ->
904910 integer_from_range (glb_ranges (R1 , R2 ));
905911glb (# 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 ));
907913glb (# 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}) ->
11321138lub_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+
11351149lub_bs_matchable (UnitA , UnitB ) ->
11361150 # t_bs_matchable {tail_unit = gcd (UnitA , UnitB )}.
11371151
@@ -1179,12 +1193,13 @@ float_from_range(none) ->
11791193 none ;
11801194float_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
11901205safe_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
0 commit comments