Skip to content

Commit 27c1c63

Browse files
committed
dialyzer: Rename t_is_none_or_unit/1 to t_is_impossible/1
Calling this function t_is_none_or_unit/1 is like saying t_is_integer_or_float/1 instead of t_is_number/1. I wouldn't be the least bit surprised if this weird naming was the root cause of GH-6580.
1 parent f54fca4 commit 27c1c63

File tree

5 files changed

+28
-23
lines changed

5 files changed

+28
-23
lines changed

lib/dialyzer/src/dialyzer_contracts.erl

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -346,11 +346,11 @@ check_contract_inf_list(List, SuccType, Opaques) ->
346346

347347
check_contract_inf_list([{Contract, FunType}|Left], SuccType, Opaques, OM) ->
348348
FunArgs = erl_types:t_fun_args(FunType),
349-
case lists:any(fun erl_types:t_is_none_or_unit/1, FunArgs) of
349+
case lists:any(fun erl_types:t_is_impossible/1, FunArgs) of
350350
true -> check_contract_inf_list(Left, SuccType, Opaques, OM);
351351
false ->
352352
STRange = erl_types:t_fun_range(SuccType),
353-
case erl_types:t_is_none_or_unit(STRange) of
353+
case erl_types:t_is_impossible(STRange) of
354354
true -> ok;
355355
false ->
356356
Range = erl_types:t_fun_range(FunType),

lib/dialyzer/src/dialyzer_dataflow.erl

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -43,7 +43,7 @@
4343
t_is_any/1, t_is_atom/1, t_is_atom/2, t_is_any_atom/3,
4444
t_is_boolean/2,
4545
t_is_integer/2, t_is_list/1,
46-
t_is_nil/2, t_is_none/1, t_is_none_or_unit/1,
46+
t_is_nil/2, t_is_none/1, t_is_impossible/1,
4747
t_is_number/2, t_is_reference/2, t_is_pid/2, t_is_port/2,
4848
t_is_unit/1,
4949
t_limit/2, t_list/0, t_list_elements/2,
@@ -256,7 +256,7 @@ traverse(Tree, Map, State) ->
256256
Arg = cerl:seq_arg(Tree),
257257
Body = cerl:seq_body(Tree),
258258
{State1, Map1, ArgType} = SMA = traverse(Arg, Map, State),
259-
case t_is_none_or_unit(ArgType) of
259+
case t_is_impossible(ArgType) of
260260
true ->
261261
SMA;
262262
false ->
@@ -924,7 +924,7 @@ handle_case(Tree, Map, State) ->
924924
Arg = cerl:case_arg(Tree),
925925
Clauses = cerl:case_clauses(Tree),
926926
{State1, Map1, ArgType} = SMA = traverse(Arg, Map, State),
927-
case t_is_none_or_unit(ArgType) of
927+
case t_is_impossible(ArgType) of
928928
true -> SMA;
929929
false ->
930930
Map2 = join_maps_begin(Map1),
@@ -974,7 +974,7 @@ handle_let(Tree, Map, State) ->
974974
end,
975975
Body = cerl:let_body(Tree),
976976
{State1, Map1, ArgTypes} = SMA = traverse(Arg, Map0, State0),
977-
case t_is_none_or_unit(ArgTypes) of
977+
case t_is_impossible(ArgTypes) of
978978
true -> SMA;
979979
false ->
980980
Map2 = enter_type_lists(Vars, t_to_tlist(ArgTypes), Map1),
@@ -1059,7 +1059,7 @@ handle_map(Tree,Map,State) ->
10591059
Arg = cerl:map_arg(Tree),
10601060
{State1, Map1, ArgType} = traverse(Arg, Map, State),
10611061
ArgType1 = t_inf(t_map(), ArgType),
1062-
case t_is_none_or_unit(ArgType1) of
1062+
case t_is_impossible(ArgType1) of
10631063
true ->
10641064
{State1, Map1, ArgType1};
10651065
false ->
@@ -1681,7 +1681,7 @@ bitstr_bitsize_type(Size) ->
16811681
%% possible value (not 'none' or 'unit'), otherwise raise a bind_error().
16821682
bind_checked_inf(Pat, ExpectedType, Type, Opaques) ->
16831683
Inf = t_inf(ExpectedType, Type, Opaques),
1684-
case t_is_none_or_unit(Inf) of
1684+
case t_is_impossible(Inf) of
16851685
true ->
16861686
case t_find_opaque_mismatch(ExpectedType, Type, Opaques) of
16871687
{ok, T1, T2} ->
@@ -2411,7 +2411,7 @@ handle_guard_map(Guard, Map, Env, State) ->
24112411
Arg = cerl:map_arg(Guard),
24122412
{Map1, ArgType0} = bind_guard(Arg, Map, Env, dont_know, State),
24132413
ArgType1 = t_inf(t_map(), ArgType0),
2414-
case t_is_none_or_unit(ArgType1) of
2414+
case t_is_impossible(ArgType1) of
24152415
true -> {Map1, t_none()};
24162416
false ->
24172417
{Map2, TypePairs} = bind_guard_map_pairs(Pairs, Map1, Env, State, []),

lib/dialyzer/src/dialyzer_typesig.erl

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -42,7 +42,7 @@
4242
t_is_float/1, t_is_fun/1,
4343
t_is_integer/1, t_non_neg_integer/0,
4444
t_is_list/1, t_is_nil/1, t_is_none/1, t_is_number/1,
45-
t_is_singleton/1, t_is_none_or_unit/1,
45+
t_is_singleton/1, t_is_impossible/1,
4646

4747
t_limit/2, t_list/0, t_list/1,
4848
t_list_elements/1, t_nonempty_list/1, t_maybe_improper_list/0,
@@ -534,14 +534,14 @@ traverse(Tree, DefinedVars, State) ->
534534
false -> t_any();
535535
true ->
536536
MT = t_inf(lookup_type(MapVar, Map), t_map()),
537-
case t_is_none_or_unit(MT) of
537+
case t_is_impossible(MT) of
538538
true -> t_none();
539539
false ->
540540
DisjointFromKeyType =
541541
fun(ShadowKey) ->
542542
ST = t_inf(lookup_type(ShadowKey, Map),
543543
KeyType),
544-
t_is_none_or_unit(ST)
544+
t_is_impossible(ST)
545545
end,
546546
case lists:all(DisjointFromKeyType, ShadowKeys) of
547547
true -> t_map_get(KeyType, MT);
@@ -575,7 +575,7 @@ traverse(Tree, DefinedVars, State) ->
575575
cerl:concrete(OpTree) =:= exact of
576576
true ->
577577
ST = t_inf(ShadowedKeys, KeyType),
578-
case t_is_none_or_unit(ST) of
578+
case t_is_impossible(ST) of
579579
true ->
580580
t_map_put({KeyType, t_any()}, AccType);
581581
false ->

lib/dialyzer/src/erl_bif_types.erl

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -67,10 +67,10 @@
6767
t_is_cons/2,
6868
t_is_float/2,
6969
t_is_fun/2,
70+
t_is_impossible/1,
7071
t_is_integer/2,
7172
t_is_nil/1, t_is_nil/2,
7273
t_is_none/1,
73-
t_is_none_or_unit/1,
7474
t_is_number/2,
7575
t_is_pid/2,
7676
t_is_port/2,
@@ -1680,7 +1680,7 @@ list_replace(1, E, [_X | Xs]) ->
16801680
[E | Xs].
16811681

16821682
any_is_none_or_unit(Ts) ->
1683-
lists:any(fun erl_types:t_is_none_or_unit/1, Ts).
1683+
lists:any(fun erl_types:t_is_impossible/1, Ts).
16841684

16851685
check_guard([X], Test, Type, Opaques) ->
16861686
check_guard_single(X, Test, Type, Opaques).
@@ -2565,15 +2565,15 @@ check_fun_application(Fun, Args, Opaques) ->
25652565
true ->
25662566
case t_fun_args(Fun, Opaques) of
25672567
unknown ->
2568-
case t_is_none_or_unit(t_fun_range(Fun, Opaques)) of
2568+
case t_is_impossible(t_fun_range(Fun, Opaques)) of
25692569
true -> error;
25702570
false -> ok
25712571
end;
25722572
FunDom when length(FunDom) =:= length(Args) ->
25732573
case any_is_none_or_unit(inf_lists(FunDom, Args, Opaques)) of
25742574
true -> error;
25752575
false ->
2576-
case t_is_none_or_unit(t_fun_range(Fun, Opaques)) of
2576+
case t_is_impossible(t_fun_range(Fun, Opaques)) of
25772577
true -> error;
25782578
false -> ok
25792579
end

lib/dialyzer/src/erl_types.erl

Lines changed: 11 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -116,6 +116,7 @@
116116
t_is_float/1, t_is_float/2,
117117
t_is_fun/1, t_is_fun/2,
118118
t_is_identifier/1,
119+
t_is_impossible/1,
119120
t_is_instance/2,
120121
t_is_integer/1, t_is_integer/2,
121122
t_is_list/1,
@@ -794,11 +795,15 @@ t_unit() ->
794795
t_is_unit(?unit) -> true;
795796
t_is_unit(_) -> false.
796797

798+
-spec t_is_impossible(erl_type()) -> boolean().
799+
800+
t_is_impossible(?none) -> true;
801+
t_is_impossible(?unit) -> true;
802+
t_is_impossible(_) -> false.
803+
797804
-spec t_is_none_or_unit(erl_type()) -> boolean().
798805

799-
t_is_none_or_unit(?none) -> true;
800-
t_is_none_or_unit(?unit) -> true;
801-
t_is_none_or_unit(_) -> false.
806+
t_is_none_or_unit(T) -> t_is_impossible(T).
802807

803808
%%-----------------------------------------------------------------------------
804809
%% Atoms and the derived type boolean
@@ -1679,7 +1684,7 @@ t_map(L) ->
16791684
t_map(Pairs0, DefK0, DefV0) ->
16801685
DefK1 = lists:foldl(fun({K,_,_},Acc)->t_subtract(Acc,K)end, DefK0, Pairs0),
16811686
{DefK2, DefV1} =
1682-
case t_is_none_or_unit(DefK1) orelse t_is_none_or_unit(DefV0) of
1687+
case t_is_impossible(DefK1) orelse t_is_impossible(DefV0) of
16831688
true -> {?none, ?none};
16841689
false -> {DefK1, DefV0}
16851690
end,
@@ -1940,7 +1945,7 @@ t_map_put(KV, Map, Opaques) ->
19401945
map_put(_, ?none, _) -> ?none;
19411946
map_put(_, ?unit, _) -> ?none;
19421947
map_put({Key, Value}, ?map(Pairs,DefK,DefV), Opaques) ->
1943-
case t_is_none_or_unit(Key) orelse t_is_none_or_unit(Value) of
1948+
case t_is_impossible(Key) orelse t_is_impossible(Value) of
19441949
true -> ?none;
19451950
false ->
19461951
case is_singleton_type(Key) of
@@ -3994,7 +3999,7 @@ t_is_instance(ConcreteType, Type) ->
39943999
-spec t_do_overlap(erl_type(), erl_type()) -> boolean().
39954000

39964001
t_do_overlap(TypeA, TypeB) ->
3997-
not (t_is_none_or_unit(t_inf(TypeA, TypeB))).
4002+
not (t_is_impossible(t_inf(TypeA, TypeB))).
39984003

39994004
-spec t_unopaque(erl_type()) -> erl_type().
40004005

0 commit comments

Comments
 (0)