Skip to content

Commit

Permalink
dialyzer: Rename t_is_none_or_unit/1 to t_is_impossible/1
Browse files Browse the repository at this point in the history
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.
  • Loading branch information
jhogberg committed Dec 21, 2022
1 parent 3dc51db commit 0c59cb0
Show file tree
Hide file tree
Showing 5 changed files with 28 additions and 23 deletions.
4 changes: 2 additions & 2 deletions lib/dialyzer/src/dialyzer_contracts.erl
Original file line number Diff line number Diff line change
Expand Up @@ -346,11 +346,11 @@ check_contract_inf_list(List, SuccType, Opaques) ->

check_contract_inf_list([{Contract, FunType}|Left], SuccType, Opaques, OM) ->
FunArgs = erl_types:t_fun_args(FunType),
case lists:any(fun erl_types:t_is_none_or_unit/1, FunArgs) of
case lists:any(fun erl_types:t_is_impossible/1, FunArgs) of
true -> check_contract_inf_list(Left, SuccType, Opaques, OM);
false ->
STRange = erl_types:t_fun_range(SuccType),
case erl_types:t_is_none_or_unit(STRange) of
case erl_types:t_is_impossible(STRange) of
true -> ok;
false ->
Range = erl_types:t_fun_range(FunType),
Expand Down
14 changes: 7 additions & 7 deletions lib/dialyzer/src/dialyzer_dataflow.erl
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@
t_is_any/1, t_is_atom/1, t_is_atom/2, t_is_any_atom/3,
t_is_boolean/2,
t_is_integer/2, t_is_list/1,
t_is_nil/2, t_is_none/1, t_is_none_or_unit/1,
t_is_nil/2, t_is_none/1, t_is_impossible/1,
t_is_number/2, t_is_reference/2, t_is_pid/2, t_is_port/2,
t_is_unit/1,
t_limit/2, t_list/0, t_list_elements/2,
Expand Down Expand Up @@ -256,7 +256,7 @@ traverse(Tree, Map, State) ->
Arg = cerl:seq_arg(Tree),
Body = cerl:seq_body(Tree),
{State1, Map1, ArgType} = SMA = traverse(Arg, Map, State),
case t_is_none_or_unit(ArgType) of
case t_is_impossible(ArgType) of
true ->
SMA;
false ->
Expand Down Expand Up @@ -924,7 +924,7 @@ handle_case(Tree, Map, State) ->
Arg = cerl:case_arg(Tree),
Clauses = cerl:case_clauses(Tree),
{State1, Map1, ArgType} = SMA = traverse(Arg, Map, State),
case t_is_none_or_unit(ArgType) of
case t_is_impossible(ArgType) of
true -> SMA;
false ->
Map2 = join_maps_begin(Map1),
Expand Down Expand Up @@ -974,7 +974,7 @@ handle_let(Tree, Map, State) ->
end,
Body = cerl:let_body(Tree),
{State1, Map1, ArgTypes} = SMA = traverse(Arg, Map0, State0),
case t_is_none_or_unit(ArgTypes) of
case t_is_impossible(ArgTypes) of
true -> SMA;
false ->
Map2 = enter_type_lists(Vars, t_to_tlist(ArgTypes), Map1),
Expand Down Expand Up @@ -1059,7 +1059,7 @@ handle_map(Tree,Map,State) ->
Arg = cerl:map_arg(Tree),
{State1, Map1, ArgType} = traverse(Arg, Map, State),
ArgType1 = t_inf(t_map(), ArgType),
case t_is_none_or_unit(ArgType1) of
case t_is_impossible(ArgType1) of
true ->
{State1, Map1, ArgType1};
false ->
Expand Down Expand Up @@ -1681,7 +1681,7 @@ bitstr_bitsize_type(Size) ->
%% possible value (not 'none' or 'unit'), otherwise raise a bind_error().
bind_checked_inf(Pat, ExpectedType, Type, Opaques) ->
Inf = t_inf(ExpectedType, Type, Opaques),
case t_is_none_or_unit(Inf) of
case t_is_impossible(Inf) of
true ->
case t_find_opaque_mismatch(ExpectedType, Type, Opaques) of
{ok, T1, T2} ->
Expand Down Expand Up @@ -2411,7 +2411,7 @@ handle_guard_map(Guard, Map, Env, State) ->
Arg = cerl:map_arg(Guard),
{Map1, ArgType0} = bind_guard(Arg, Map, Env, dont_know, State),
ArgType1 = t_inf(t_map(), ArgType0),
case t_is_none_or_unit(ArgType1) of
case t_is_impossible(ArgType1) of
true -> {Map1, t_none()};
false ->
{Map2, TypePairs} = bind_guard_map_pairs(Pairs, Map1, Env, State, []),
Expand Down
8 changes: 4 additions & 4 deletions lib/dialyzer/src/dialyzer_typesig.erl
Original file line number Diff line number Diff line change
Expand Up @@ -42,7 +42,7 @@
t_is_float/1, t_is_fun/1,
t_is_integer/1, t_non_neg_integer/0,
t_is_list/1, t_is_nil/1, t_is_none/1, t_is_number/1,
t_is_singleton/1, t_is_none_or_unit/1,
t_is_singleton/1, t_is_impossible/1,

t_limit/2, t_list/0, t_list/1,
t_list_elements/1, t_nonempty_list/1, t_maybe_improper_list/0,
Expand Down Expand Up @@ -534,14 +534,14 @@ traverse(Tree, DefinedVars, State) ->
false -> t_any();
true ->
MT = t_inf(lookup_type(MapVar, Map), t_map()),
case t_is_none_or_unit(MT) of
case t_is_impossible(MT) of
true -> t_none();
false ->
DisjointFromKeyType =
fun(ShadowKey) ->
ST = t_inf(lookup_type(ShadowKey, Map),
KeyType),
t_is_none_or_unit(ST)
t_is_impossible(ST)
end,
case lists:all(DisjointFromKeyType, ShadowKeys) of
true -> t_map_get(KeyType, MT);
Expand Down Expand Up @@ -575,7 +575,7 @@ traverse(Tree, DefinedVars, State) ->
cerl:concrete(OpTree) =:= exact of
true ->
ST = t_inf(ShadowedKeys, KeyType),
case t_is_none_or_unit(ST) of
case t_is_impossible(ST) of
true ->
t_map_put({KeyType, t_any()}, AccType);
false ->
Expand Down
8 changes: 4 additions & 4 deletions lib/dialyzer/src/erl_bif_types.erl
Original file line number Diff line number Diff line change
Expand Up @@ -67,10 +67,10 @@
t_is_cons/2,
t_is_float/2,
t_is_fun/2,
t_is_impossible/1,
t_is_integer/2,
t_is_nil/1, t_is_nil/2,
t_is_none/1,
t_is_none_or_unit/1,
t_is_number/2,
t_is_pid/2,
t_is_port/2,
Expand Down Expand Up @@ -1680,7 +1680,7 @@ list_replace(1, E, [_X | Xs]) ->
[E | Xs].

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

check_guard([X], Test, Type, Opaques) ->
check_guard_single(X, Test, Type, Opaques).
Expand Down Expand Up @@ -2565,15 +2565,15 @@ check_fun_application(Fun, Args, Opaques) ->
true ->
case t_fun_args(Fun, Opaques) of
unknown ->
case t_is_none_or_unit(t_fun_range(Fun, Opaques)) of
case t_is_impossible(t_fun_range(Fun, Opaques)) of
true -> error;
false -> ok
end;
FunDom when length(FunDom) =:= length(Args) ->
case any_is_none_or_unit(inf_lists(FunDom, Args, Opaques)) of
true -> error;
false ->
case t_is_none_or_unit(t_fun_range(Fun, Opaques)) of
case t_is_impossible(t_fun_range(Fun, Opaques)) of
true -> error;
false -> ok
end
Expand Down
17 changes: 11 additions & 6 deletions lib/dialyzer/src/erl_types.erl
Original file line number Diff line number Diff line change
Expand Up @@ -116,6 +116,7 @@
t_is_float/1, t_is_float/2,
t_is_fun/1, t_is_fun/2,
t_is_identifier/1,
t_is_impossible/1,
t_is_instance/2,
t_is_integer/1, t_is_integer/2,
t_is_list/1,
Expand Down Expand Up @@ -794,11 +795,15 @@ t_unit() ->
t_is_unit(?unit) -> true;
t_is_unit(_) -> false.

-spec t_is_impossible(erl_type()) -> boolean().

t_is_impossible(?none) -> true;
t_is_impossible(?unit) -> true;
t_is_impossible(_) -> false.

-spec t_is_none_or_unit(erl_type()) -> boolean().

t_is_none_or_unit(?none) -> true;
t_is_none_or_unit(?unit) -> true;
t_is_none_or_unit(_) -> false.
t_is_none_or_unit(T) -> t_is_impossible(T).

%%-----------------------------------------------------------------------------
%% Atoms and the derived type boolean
Expand Down Expand Up @@ -1679,7 +1684,7 @@ t_map(L) ->
t_map(Pairs0, DefK0, DefV0) ->
DefK1 = lists:foldl(fun({K,_,_},Acc)->t_subtract(Acc,K)end, DefK0, Pairs0),
{DefK2, DefV1} =
case t_is_none_or_unit(DefK1) orelse t_is_none_or_unit(DefV0) of
case t_is_impossible(DefK1) orelse t_is_impossible(DefV0) of
true -> {?none, ?none};
false -> {DefK1, DefV0}
end,
Expand Down Expand Up @@ -1940,7 +1945,7 @@ t_map_put(KV, Map, Opaques) ->
map_put(_, ?none, _) -> ?none;
map_put(_, ?unit, _) -> ?none;
map_put({Key, Value}, ?map(Pairs,DefK,DefV), Opaques) ->
case t_is_none_or_unit(Key) orelse t_is_none_or_unit(Value) of
case t_is_impossible(Key) orelse t_is_impossible(Value) of
true -> ?none;
false ->
case is_singleton_type(Key) of
Expand Down Expand Up @@ -3994,7 +3999,7 @@ t_is_instance(ConcreteType, Type) ->
-spec t_do_overlap(erl_type(), erl_type()) -> boolean().

t_do_overlap(TypeA, TypeB) ->
not (t_is_none_or_unit(t_inf(TypeA, TypeB))).
not (t_is_impossible(t_inf(TypeA, TypeB))).

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

Expand Down

0 comments on commit 0c59cb0

Please sign in to comment.