aboutsummaryrefslogtreecommitdiffstats
path: root/lib/dialyzer
diff options
context:
space:
mode:
Diffstat (limited to 'lib/dialyzer')
-rw-r--r--lib/dialyzer/src/dialyzer_dataflow.erl74
-rw-r--r--lib/dialyzer/src/dialyzer_typesig.erl206
-rw-r--r--lib/dialyzer/test/Makefile2
-rw-r--r--lib/dialyzer/test/r9c_SUITE_data/results/asn18
-rw-r--r--lib/dialyzer/test/r9c_SUITE_data/results/inets43
-rw-r--r--lib/dialyzer/test/r9c_SUITE_data/results/mnesia3
-rw-r--r--lib/dialyzer/test/race_SUITE_data/results/extract_translations4
-rw-r--r--lib/dialyzer/test/small_SUITE_data/results/common_eunit2
-rw-r--r--lib/dialyzer/test/small_SUITE_data/results/comparisons153
-rw-r--r--lib/dialyzer/test/small_SUITE_data/results/failing_funs20
-rw-r--r--lib/dialyzer/test/small_SUITE_data/results/flatten2
-rw-r--r--lib/dialyzer/test/small_SUITE_data/results/my_sofs4
-rw-r--r--lib/dialyzer/test/small_SUITE_data/src/binary_lc_bug.erl8
-rw-r--r--lib/dialyzer/test/small_SUITE_data/src/codec_can.erl35
-rw-r--r--lib/dialyzer/test/small_SUITE_data/src/common_eunit.erl121
-rw-r--r--lib/dialyzer/test/small_SUITE_data/src/comparisons.erl322
-rw-r--r--lib/dialyzer/test/small_SUITE_data/src/failing_funs.erl250
-rw-r--r--lib/dialyzer/test/small_SUITE_data/src/file_open_encoding.erl4
-rw-r--r--lib/dialyzer/test/small_SUITE_data/src/list_to_bitstring.erl21
-rw-r--r--lib/dialyzer/test/small_SUITE_data/src/no_return_bug.erl42
-rw-r--r--lib/dialyzer/test/small_SUITE_data/src/nowarnunused.erl7
-rw-r--r--lib/dialyzer/test/small_SUITE_data/src/rebar_no_return.erl19
22 files changed, 1212 insertions, 138 deletions
diff --git a/lib/dialyzer/src/dialyzer_dataflow.erl b/lib/dialyzer/src/dialyzer_dataflow.erl
index 7137dbc036..d74c04385b 100644
--- a/lib/dialyzer/src/dialyzer_dataflow.erl
+++ b/lib/dialyzer/src/dialyzer_dataflow.erl
@@ -528,7 +528,7 @@ handle_apply(Tree, Map, State) ->
{CallSitesKnown, FunList} =
case state__lookup_call_site(Tree, State2) of
error -> {false, []};
- {ok, [external]} -> {false, {}};
+ {ok, [external]} -> {false, []};
{ok, List} -> {true, List}
end,
case CallSitesKnown of
@@ -554,7 +554,13 @@ handle_apply(Tree, Map, State) ->
{State3, enter_type(Op, OpType1, Map2), t_none()};
false ->
Map3 = enter_type_lists(Args, NewArgs, Map2),
- {State2, enter_type(Op, OpType1, Map3), t_fun_range(OpType1)}
+ Range0 = t_fun_range(OpType1),
+ Range =
+ case t_is_unit(Range0) of
+ true -> t_none();
+ false -> Range0
+ end,
+ {State2, enter_type(Op, OpType1, Map3), Range}
end
end;
true ->
@@ -1393,10 +1399,14 @@ do_clause(C, Arg, ArgType0, OrigArgType, Map,
true -> Any = t_any(), [Any || _ <- Pats];
false -> t_to_tlist(OrigArgType)
end,
- case bind_pat_vars(Pats, OrigArgTypes, [], Map1, State1) of
- {error, bind, _, _, _} -> {{pattern_match, PatTypes}, false};
- {_, _} -> {{pattern_match_cov, PatTypes}, false}
- end;
+ Tag =
+ case bind_pat_vars(Pats, OrigArgTypes, [], Map1, State1) of
+ {error, bind, _, _, _} -> pattern_match;
+ {error, record, _, _, _} -> record_match;
+ {error, opaque, _, _, _} -> opaque_match;
+ {_, _} -> pattern_match_cov
+ end,
+ {{Tag, PatTypes}, false};
false ->
%% Try to find out if this is a default clause in a list
%% comprehension and supress this. A real Hack(tm)
@@ -1414,6 +1424,17 @@ do_clause(C, Arg, ArgType0, OrigArgType, Map,
false ->
true
end;
+ [Pat0, Pat1] -> % binary comprehension
+ case cerl:is_c_cons(Pat0) of
+ true ->
+ not (cerl:is_c_var(cerl:cons_hd(Pat0)) andalso
+ cerl:is_c_var(cerl:cons_tl(Pat0)) andalso
+ cerl:is_c_var(Pat1) andalso
+ cerl:is_literal(Guard) andalso
+ (cerl:concrete(Guard) =:= true));
+ false ->
+ true
+ end;
_ -> true
end;
false ->
@@ -1425,12 +1446,12 @@ do_clause(C, Arg, ArgType0, OrigArgType, Map,
opaque -> [PatString, format_type(Type, State1),
format_type(OpaqueTerm, State1)]
end,
- FailedMsg = case ErrorType of
- bind -> {pattern_match, PatTypes};
- record -> {record_match, PatTypes};
- opaque -> {opaque_match, PatTypes}
+ FailedTag = case ErrorType of
+ bind -> pattern_match;
+ record -> record_match;
+ opaque -> opaque_match
end,
- {FailedMsg, Force0}
+ {{FailedTag, PatTypes}, Force0}
end,
WarnType = case Msg of
{opaque_match, _} -> ?WARN_OPAQUE;
@@ -2915,7 +2936,7 @@ state__get_warnings(#state{tree_map = TreeMap, fun_tab = FunTab,
{Warn, Msg} =
case dialyzer_callgraph:lookup_name(FunLbl, Callgraph) of
error -> {true, {unused_fun, []}};
- {ok, {_M, F, A}} = MFA ->
+ {ok, {_M, F, A} = MFA} ->
{not sets:is_element(MFA, NoWarnUnused),
{unused_fun, [F, A]}}
end,
@@ -2935,7 +2956,7 @@ state__get_warnings(#state{tree_map = TreeMap, fun_tab = FunTab,
%% Check if the function has a contract that allows this.
Warn =
case Contract of
- none -> true;
+ none -> not parent_allows_this(FunLbl, State);
{value, C} ->
GenRet = dialyzer_contracts:get_contract_return(C),
not t_is_unit(GenRet)
@@ -3423,6 +3444,33 @@ map_pats(Pats) ->
end,
cerl_trees:map(Fun, Pats).
+parent_allows_this(FunLbl, #state{callgraph = Callgraph, plt = Plt} =State) ->
+ case state__is_escaping(FunLbl, State) of
+ false -> false; % if it isn't escaping it can't be a return value
+ true ->
+ case state__lookup_name(FunLbl, State) of
+ {_M, _F, _A} -> false; % if it has a name it is not a fun
+ _ ->
+ case dialyzer_callgraph:in_neighbours(FunLbl, Callgraph) of
+ [Parent] ->
+ case state__lookup_name(Parent, State) of
+ {_M, _F, _A} = PMFA ->
+ case dialyzer_plt:lookup_contract(Plt, PMFA) of
+ none -> false;
+ {value, C} ->
+ GenRet = dialyzer_contracts:get_contract_return(C),
+ case erl_types:t_is_fun(GenRet) of
+ false -> false; % element of structure? far-fetched...
+ true -> t_is_unit(t_fun_range(GenRet))
+ end
+ end;
+ _ -> false % parent should have a name to have a contract
+ end;
+ _ -> false % called in other funs? far-fetched...
+ end
+ end
+ end.
+
classify_returns(Tree) ->
case find_terminals(cerl:fun_body(Tree)) of
{false, false} -> no_match;
diff --git a/lib/dialyzer/src/dialyzer_typesig.erl b/lib/dialyzer/src/dialyzer_typesig.erl
index c45615d670..30aec59d22 100644
--- a/lib/dialyzer/src/dialyzer_typesig.erl
+++ b/lib/dialyzer/src/dialyzer_typesig.erl
@@ -2,7 +2,7 @@
%%-----------------------------------------------------------------------
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2006-2010. All Rights Reserved.
+%% Copyright Ericsson AB 2006-2011. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -62,7 +62,8 @@
-type dep() :: integer(). %% type variable names used as constraint ids
-type type_var() :: erl_types:erl_type(). %% actually: {'c','var',_,_}
--record(fun_var, {'fun' :: fun((_) -> erl_types:erl_type()), deps :: [dep()]}).
+-record(fun_var, {'fun' :: fun((_) -> erl_types:erl_type()), deps :: [dep()],
+ origin :: integer()}).
-type constr_op() :: 'eq' | 'sub'.
-type fvar_or_type() :: #fun_var{} | erl_types:erl_type().
@@ -121,8 +122,10 @@
-ifdef(DEBUG).
-define(debug(__String, __Args), io:format(__String, __Args)).
+-define(mk_fun_var(Fun, Vars), mk_fun_var(?LINE, Fun, Vars)).
-else.
-define(debug(__String, __Args), ok).
+-define(mk_fun_var(Fun, Vars), mk_fun_var(Fun, Vars)).
-endif.
%% ============================================================================
@@ -218,10 +221,10 @@ traverse(Tree, DefinedVars, State) ->
binary ->
{State1, SegTypes} = traverse_list(cerl:binary_segments(Tree),
DefinedVars, State),
- Type = mk_fun_var(fun(Map) ->
- TmpSegTypes = lookup_type_list(SegTypes, Map),
- t_bitstr_concat(TmpSegTypes)
- end, SegTypes),
+ Type = ?mk_fun_var(fun(Map) ->
+ TmpSegTypes = lookup_type_list(SegTypes, Map),
+ t_bitstr_concat(TmpSegTypes)
+ end, SegTypes),
{state__store_conj(mk_var(Tree), sub, Type, State1), mk_var(Tree)};
bitstr ->
Size = cerl:bitstr_size(Tree),
@@ -236,7 +239,7 @@ traverse(Tree, DefinedVars, State) ->
N when is_integer(N) -> {State1, t_bitstr(0, N)};
any -> % Size is not a literal
{state__store_conj(SizeType, sub, t_non_neg_integer(), State1),
- mk_fun_var(bitstr_constr(SizeType, UnitVal), [SizeType])}
+ ?mk_fun_var(bitstr_constr(SizeType, UnitVal), [SizeType])}
end,
ValTypeConstr =
case cerl:concrete(cerl:bitstr_type(Tree)) of
@@ -250,8 +253,8 @@ traverse(Tree, DefinedVars, State) ->
case state__is_in_match(State1) of
true ->
Flags = cerl:concrete(cerl:bitstr_flags(Tree)),
- mk_fun_var(bitstr_val_constr(SizeType, UnitVal, Flags),
- [SizeType]);
+ ?mk_fun_var(bitstr_val_constr(SizeType, UnitVal, Flags),
+ [SizeType]);
false -> t_integer()
end;
utf8 -> t_integer();
@@ -281,24 +284,24 @@ traverse(Tree, DefinedVars, State) ->
{State, t_cons(HdVar, TlVar)};
false ->
ConsVar = mk_var(Tree),
- ConsType = mk_fun_var(fun(Map) ->
- t_cons(lookup_type(HdVar, Map),
- lookup_type(TlVar, Map))
- end, [HdVar, TlVar]),
- HdType = mk_fun_var(fun(Map) ->
- Cons = lookup_type(ConsVar, Map),
- case t_is_cons(Cons) of
- false -> t_any();
- true -> t_cons_hd(Cons)
- end
- end, [ConsVar]),
- TlType = mk_fun_var(fun(Map) ->
- Cons = lookup_type(ConsVar, Map),
- case t_is_cons(Cons) of
- false -> t_any();
- true -> t_cons_tl(Cons)
- end
- end, [ConsVar]),
+ ConsType = ?mk_fun_var(fun(Map) ->
+ t_cons(lookup_type(HdVar, Map),
+ lookup_type(TlVar, Map))
+ end, [HdVar, TlVar]),
+ HdType = ?mk_fun_var(fun(Map) ->
+ Cons = lookup_type(ConsVar, Map),
+ case t_is_cons(Cons) of
+ false -> t_any();
+ true -> t_cons_hd(Cons)
+ end
+ end, [ConsVar]),
+ TlType = ?mk_fun_var(fun(Map) ->
+ Cons = lookup_type(ConsVar, Map),
+ case t_is_cons(Cons) of
+ false -> t_any();
+ true -> t_cons_tl(Cons)
+ end
+ end, [ConsVar]),
State2 = state__store_conj_lists([HdVar, TlVar, ConsVar], sub,
[HdType, TlType, ConsType],
State1),
@@ -656,25 +659,25 @@ get_plt_constr(MFA, Dst, ArgVars, State) ->
{RetType, ArgCs} =
case PltRes of
none ->
- {mk_fun_var(fun(Map) ->
- ArgTypes = lookup_type_list(ArgVars, Map),
- dialyzer_contracts:get_contract_return(C, ArgTypes)
- end, ArgVars), GenArgs};
+ {?mk_fun_var(fun(Map) ->
+ ArgTypes = lookup_type_list(ArgVars, Map),
+ dialyzer_contracts:get_contract_return(C, ArgTypes)
+ end, ArgVars), GenArgs};
{value, {PltRetType, PltArgTypes}} ->
%% Need to combine the contract with the success typing.
- {mk_fun_var(
- fun(Map) ->
- ArgTypes0 = lookup_type_list(ArgVars, Map),
- ArgTypes = case FunModule =:= Module of
- false ->
- List = lists:zip(PltArgTypes, ArgTypes0),
- [erl_types:t_unopaque_on_mismatch(T1, T2, Opaques)
- || {T1, T2} <- List];
- true -> ArgTypes0
- end,
- CRet = dialyzer_contracts:get_contract_return(C, ArgTypes),
- t_inf(CRet, PltRetType, opaque)
- end, ArgVars),
+ {?mk_fun_var(
+ fun(Map) ->
+ ArgTypes0 = lookup_type_list(ArgVars, Map),
+ ArgTypes = case FunModule =:= Module of
+ false ->
+ List = lists:zip(PltArgTypes, ArgTypes0),
+ [erl_types:t_unopaque_on_mismatch(T1, T2, Opaques)
+ || {T1, T2} <- List];
+ true -> ArgTypes0
+ end,
+ CRet = dialyzer_contracts:get_contract_return(C, ArgTypes),
+ t_inf(CRet, PltRetType, opaque)
+ end, ArgVars),
[t_inf(X, Y, opaque) || {X, Y} <- lists:zip(GenArgs, PltArgTypes)]}
end,
state__store_conj_lists([Dst|ArgVars], sub, [RetType|ArgCs], State)
@@ -766,10 +769,10 @@ handle_clauses_1([Clause|Tail], TopVar, Arg, DefinedVars,
case SubtrTypes =:= overflow of
true -> S;
false ->
- SubtrPatVar = mk_fun_var(fun(Map) ->
- TmpType = lookup_type(Arg, Map),
- t_subtract_list(TmpType, SubtrTypes)
- end, [Arg]),
+ SubtrPatVar = ?mk_fun_var(fun(Map) ->
+ TmpType = lookup_type(Arg, Map),
+ t_subtract_list(TmpType, SubtrTypes)
+ end, [Arg]),
state__store_conj(Arg, sub, SubtrPatVar, S)
end
end,
@@ -1043,10 +1046,10 @@ handle_guard(Guard, DefinedVars, State) ->
get_bif_constr({erlang, Op, 2}, Dst, Args = [Arg1, Arg2], _State)
when Op =:= '+'; Op =:= '-'; Op =:= '*' ->
- ReturnType = mk_fun_var(fun(Map) ->
- TmpArgTypes = lookup_type_list(Args, Map),
- erl_bif_types:type(erlang, Op, 2, TmpArgTypes)
- end, Args),
+ ReturnType = ?mk_fun_var(fun(Map) ->
+ TmpArgTypes = lookup_type_list(Args, Map),
+ erl_bif_types:type(erlang, Op, 2, TmpArgTypes)
+ end, Args),
ArgFun =
fun(A, Pos) ->
F =
@@ -1074,7 +1077,7 @@ get_bif_constr({erlang, Op, 2}, Dst, Args = [Arg1, Arg2], _State)
end
end
end,
- mk_fun_var(F, [Dst, A])
+ ?mk_fun_var(F, [Dst, A])
end,
Arg1FunVar = ArgFun(Arg2, 2),
Arg2FunVar = ArgFun(Arg1, 1),
@@ -1131,12 +1134,12 @@ get_bif_constr({erlang, Op, 2}, Dst, [Arg1, Arg2] = Args, _State)
'>=' -> {ArgFun(Arg1, Arg2, '>='), ArgFun(Arg2, Arg1, '=<')}
end,
DstArgs = [Dst, Arg1, Arg2],
- Arg1Var = mk_fun_var(Arg1Fun, DstArgs),
- Arg2Var = mk_fun_var(Arg2Fun, DstArgs),
- DstVar = mk_fun_var(fun(Map) ->
- TmpArgTypes = lookup_type_list(Args, Map),
- erl_bif_types:type(erlang, Op, 2, TmpArgTypes)
- end, Args),
+ Arg1Var = ?mk_fun_var(Arg1Fun, DstArgs),
+ Arg2Var = ?mk_fun_var(Arg2Fun, DstArgs),
+ DstVar = ?mk_fun_var(fun(Map) ->
+ TmpArgTypes = lookup_type_list(Args, Map),
+ erl_bif_types:type(erlang, Op, 2, TmpArgTypes)
+ end, Args),
mk_conj_constraint_list([mk_constraint(Dst, sub, DstVar),
mk_constraint(Arg1, sub, Arg1Var),
mk_constraint(Arg2, sub, Arg2Var)]);
@@ -1172,13 +1175,13 @@ get_bif_constr({erlang, '++', 2}, Dst, [Hd, Tl] = Args, _State) ->
end
end,
DstL = [Dst],
- HdVar = mk_fun_var(HdFun, DstL),
- TlVar = mk_fun_var(TlFun, DstL),
+ HdVar = ?mk_fun_var(HdFun, DstL),
+ TlVar = ?mk_fun_var(TlFun, DstL),
ArgTypes = erl_bif_types:arg_types(erlang, '++', 2),
- ReturnType = mk_fun_var(fun(Map) ->
- TmpArgTypes = lookup_type_list(Args, Map),
- erl_bif_types:type(erlang, '++', 2, TmpArgTypes)
- end, Args),
+ ReturnType = ?mk_fun_var(fun(Map) ->
+ TmpArgTypes = lookup_type_list(Args, Map),
+ erl_bif_types:type(erlang, '++', 2, TmpArgTypes)
+ end, Args),
Cs = mk_constraints(Args, sub, ArgTypes),
mk_conj_constraint_list([mk_constraint(Dst, sub, ReturnType),
mk_constraint(Hd, sub, HdVar),
@@ -1209,7 +1212,7 @@ get_bif_constr({erlang, is_function, 2}, Dst, [Fun, Arity], _State) ->
false -> t_any()
end
end,
- ArgV = mk_fun_var(ArgFun, [Dst, Arity]),
+ ArgV = ?mk_fun_var(ArgFun, [Dst, Arity]),
mk_conj_constraint_list([mk_constraint(Dst, sub, t_boolean()),
mk_constraint(Arity, sub, t_integer()),
mk_constraint(Fun, sub, ArgV)]);
@@ -1232,12 +1235,12 @@ get_bif_constr({erlang, is_record, 2}, Dst, [Var, Tag] = Args, _State) ->
false -> t_any()
end
end,
- ArgV = mk_fun_var(ArgFun, [Dst]),
+ ArgV = ?mk_fun_var(ArgFun, [Dst]),
DstFun = fun(Map) ->
TmpArgTypes = lookup_type_list(Args, Map),
erl_bif_types:type(erlang, is_record, 2, TmpArgTypes)
end,
- DstV = mk_fun_var(DstFun, Args),
+ DstV = ?mk_fun_var(DstFun, Args),
mk_conj_constraint_list([mk_constraint(Dst, sub, DstV),
mk_constraint(Tag, sub, t_atom()),
mk_constraint(Var, sub, ArgV)]);
@@ -1280,7 +1283,7 @@ get_bif_constr({erlang, is_record, 3}, Dst, [Var, Tag, Arity] = Args, State) ->
false -> t_any()
end
end,
- ArgV = mk_fun_var(ArgFun, [Tag, Arity, Dst]),
+ ArgV = ?mk_fun_var(ArgFun, [Tag, Arity, Dst]),
DstFun = fun(Map) ->
[TmpVar, TmpTag, TmpArity] = TmpArgTypes = lookup_type_list(Args, Map),
TmpArgTypes2 =
@@ -1314,7 +1317,7 @@ get_bif_constr({erlang, is_record, 3}, Dst, [Var, Tag, Arity] = Args, State) ->
end,
erl_bif_types:type(erlang, is_record, 3, TmpArgTypes2)
end,
- DstV = mk_fun_var(DstFun, Args),
+ DstV = ?mk_fun_var(DstFun, Args),
mk_conj_constraint_list([mk_constraint(Dst, sub, DstV),
mk_constraint(Arity, sub, t_integer()),
mk_constraint(Tag, sub, t_atom()),
@@ -1359,9 +1362,9 @@ get_bif_constr({erlang, 'and', 2}, Dst, [Arg1, Arg2] = Args, _State) ->
end
end
end,
- ArgV1 = mk_fun_var(ArgFun(Arg2), [Arg2, Dst]),
- ArgV2 = mk_fun_var(ArgFun(Arg1), [Arg1, Dst]),
- DstV = mk_fun_var(DstFun, Args),
+ ArgV1 = ?mk_fun_var(ArgFun(Arg2), [Arg2, Dst]),
+ ArgV2 = ?mk_fun_var(ArgFun(Arg1), [Arg1, Dst]),
+ DstV = ?mk_fun_var(DstFun, Args),
mk_conj_constraint_list([mk_constraint(Dst, sub, DstV),
mk_constraint(Arg1, sub, ArgV1),
mk_constraint(Arg2, sub, ArgV2)]);
@@ -1403,9 +1406,9 @@ get_bif_constr({erlang, 'or', 2}, Dst, [Arg1, Arg2] = Args, _State) ->
end
end
end,
- ArgV1 = mk_fun_var(ArgFun(Arg2), [Arg2, Dst]),
- ArgV2 = mk_fun_var(ArgFun(Arg1), [Arg1, Dst]),
- DstV = mk_fun_var(DstFun, Args),
+ ArgV1 = ?mk_fun_var(ArgFun(Arg2), [Arg2, Dst]),
+ ArgV2 = ?mk_fun_var(ArgFun(Arg1), [Arg1, Dst]),
+ DstV = ?mk_fun_var(DstFun, Args),
F = fun(A) ->
try [mk_constraint(A, sub, True)]
catch throw:error -> []
@@ -1433,8 +1436,8 @@ get_bif_constr({erlang, 'not', 1}, Dst, [Arg] = Args, _State) ->
end
end
end,
- ArgV = mk_fun_var(Fun(Dst), [Dst]),
- DstV = mk_fun_var(Fun(Arg), Args),
+ ArgV = ?mk_fun_var(Fun(Dst), [Dst]),
+ DstV = ?mk_fun_var(Fun(Arg), Args),
mk_conj_constraint_list([mk_constraint(Arg, sub, ArgV),
mk_constraint(Dst, sub, DstV)]);
get_bif_constr({erlang, '=:=', 2}, Dst, [Arg1, Arg2] = Args, _State) ->
@@ -1467,9 +1470,9 @@ get_bif_constr({erlang, '=:=', 2}, Dst, [Arg1, Arg2] = Args, _State) ->
end
end,
DstArgs = [Dst, Arg1, Arg2],
- ArgV1 = mk_fun_var(ArgFun(Arg1, Arg2), DstArgs),
- ArgV2 = mk_fun_var(ArgFun(Arg2, Arg1), DstArgs),
- DstV = mk_fun_var(DstFun, Args),
+ ArgV1 = ?mk_fun_var(ArgFun(Arg1, Arg2), DstArgs),
+ ArgV2 = ?mk_fun_var(ArgFun(Arg2, Arg1), DstArgs),
+ DstV = ?mk_fun_var(DstFun, Args),
mk_conj_constraint_list([mk_constraint(Dst, sub, DstV),
mk_constraint(Arg1, sub, ArgV1),
mk_constraint(Arg2, sub, ArgV2)]);
@@ -1510,10 +1513,10 @@ get_bif_constr({erlang, '==', 2}, Dst, [Arg1, Arg2] = Args, _State) ->
end
end
end,
- DstV = mk_fun_var(DstFun, Args),
+ DstV = ?mk_fun_var(DstFun, Args),
ArgL = [Arg1, Arg2, Dst],
- ArgV1 = mk_fun_var(ArgFun(Arg2, Arg1), ArgL),
- ArgV2 = mk_fun_var(ArgFun(Arg1, Arg2), ArgL),
+ ArgV1 = ?mk_fun_var(ArgFun(Arg2, Arg1), ArgL),
+ ArgV2 = ?mk_fun_var(ArgFun(Arg1, Arg2), ArgL),
mk_conj_constraint_list([mk_constraint(Dst, sub, DstV),
mk_constraint(Arg1, sub, ArgV1),
mk_constraint(Arg2, sub, ArgV2)]);
@@ -1531,7 +1534,7 @@ get_bif_constr({erlang, element, 2} = _BIF, Dst, Args,
end,
erl_bif_types:type(erlang, element, 2, ATs2)
end,
- ReturnType = mk_fun_var(Fun, Args),
+ ReturnType = ?mk_fun_var(Fun, Args),
ArgTypes = erl_bif_types:arg_types(erlang, element, 2),
Cs = mk_constraints(Args, sub, ArgTypes),
NewCs =
@@ -1553,7 +1556,7 @@ get_bif_constr({M, F, A} = _BIF, Dst, Args, State) ->
false -> T
end
end,
- ReturnType = mk_fun_var(fun(Map) ->
+ ReturnType = ?mk_fun_var(fun(Map) ->
TmpArgTypes0 = lookup_type_list(Args, Map),
TmpArgTypes = [UnopaqueFun(T) || T<- TmpArgTypes0],
erl_bif_types:type(M, F, A, TmpArgTypes)
@@ -1608,7 +1611,7 @@ get_bif_test_constr(Dst, Arg, Type, State) ->
false -> t_any()
end
end,
- ArgV = mk_fun_var(ArgFun, [Dst]),
+ ArgV = ?mk_fun_var(ArgFun, [Dst]),
DstFun = fun(Map) ->
ArgType = lookup_type(Arg, Map),
case t_is_none(t_inf(ArgType, Type)) of
@@ -1633,7 +1636,7 @@ get_bif_test_constr(Dst, Arg, Type, State) ->
end
end
end,
- DstV = mk_fun_var(DstFun, [Arg]),
+ DstV = ?mk_fun_var(DstFun, [Arg]),
mk_conj_constraint_list([mk_constraint(Dst, sub, DstV),
mk_constraint(Arg, sub, ArgV)]).
@@ -1684,11 +1687,14 @@ solve_scc(SCC, Map, State, TryingUnit) ->
true ->
?debug("SCC ~w reached fixpoint\n", [SCC]),
NewTypes = unsafe_lookup_type_list(Funs, Map2),
- case lists:all(fun(T) -> t_is_none(t_fun_range(T)) end, NewTypes)
+ case erl_types:any_none([t_fun_range(T) || T <- NewTypes])
andalso TryingUnit =:= false of
true ->
- UnitTypes = [t_fun(state__fun_arity(F, State), t_unit())
- || F <- Funs],
+ UnitTypes =
+ [case t_is_none(t_fun_range(T)) of
+ false -> T;
+ true -> t_fun(t_fun_args(T), t_unit())
+ end || T <- NewTypes],
Map3 = enter_type_lists(Funs, UnitTypes, Map2),
solve_scc(SCC, Map3, State, true);
false ->
@@ -2320,12 +2326,25 @@ mk_constraint(Lhs, Op, Rhs) ->
constraint_opnd_is_any(#fun_var{}) -> false;
constraint_opnd_is_any(Type) -> t_is_any(Type).
+-ifdef(DEBUG).
+
+-spec mk_fun_var(fun((_) -> erl_types:erl_type()), [erl_types:erl_type()],
+ integer()) -> #fun_var{}.
+
+mk_fun_var(Line, Fun, Types) ->
+ Deps = [t_var_name(Var) || Var <- t_collect_vars(t_product(Types))],
+ #fun_var{'fun' = Fun, deps = ordsets:from_list(Deps), origin = Line}.
+
+-else.
+
-spec mk_fun_var(fun((_) -> erl_types:erl_type()), [erl_types:erl_type()]) -> #fun_var{}.
mk_fun_var(Fun, Types) ->
Deps = [t_var_name(Var) || Var <- t_collect_vars(t_product(Types))],
#fun_var{'fun' = Fun, deps = ordsets:from_list(Deps)}.
+-endif.
+
-spec get_deps(constr()) -> [dep()].
get_deps(#constraint{deps = D}) -> D;
@@ -2676,8 +2695,9 @@ find_constraint(Tuple, [_|Cs]) ->
-endif.
-ifdef(DEBUG).
-format_type(#fun_var{deps = Deps}) ->
- io_lib:format("Fun(~s)", [lists:flatten([format_type(t_var(X))||X<-Deps])]);
+format_type(#fun_var{deps = Deps, origin = Origin}) ->
+ io_lib:format("Fun@L~p(~s)",
+ [Origin, lists:flatten([format_type(t_var(X))||X<-Deps])]);
format_type(Type) ->
case cerl:is_literal(Type) of
true -> io_lib:format("~w", [cerl:concrete(Type)]);
diff --git a/lib/dialyzer/test/Makefile b/lib/dialyzer/test/Makefile
index 69a8fd742e..47deb17f1d 100644
--- a/lib/dialyzer/test/Makefile
+++ b/lib/dialyzer/test/Makefile
@@ -26,7 +26,7 @@ include $(ERL_TOP)/make/otp_release_targets.mk
release_tests_spec:
$(INSTALL_DIR) $(RELSYSDIR)
- chmod -f -R u+w $(RELSYSDIR)
+ chmod -R u+w $(RELSYSDIR)
$(INSTALL_DATA) $(AUXILIARY_FILES) $(RELSYSDIR)
@tar cf - *_SUITE_data | (cd $(RELSYSDIR); tar xf -)
cd $(RELSYSDIR);\
diff --git a/lib/dialyzer/test/r9c_SUITE_data/results/asn1 b/lib/dialyzer/test/r9c_SUITE_data/results/asn1
index ac83366bc8..292275dd6e 100644
--- a/lib/dialyzer/test/r9c_SUITE_data/results/asn1
+++ b/lib/dialyzer/test/r9c_SUITE_data/results/asn1
@@ -2,11 +2,11 @@
asn1ct.erl:1500: The variable Err can never match since previous clauses completely covered the type #type{}
asn1ct.erl:1596: The variable _ can never match since previous clauses completely covered the type 'ber_bin_v2'
asn1ct.erl:1673: The pattern 'all' can never match the type 'asn1_module' | 'exclusive_decode' | 'partial_decode'
-asn1ct.erl:672: The pattern <{'false', Result}, _, _> can never match the type <{'true','true'},atom() | binary() | [atom() | binary() | [atom() | binary() | [any()] | char()] | char()],[any()]>
+asn1ct.erl:672: The pattern <{'false', Result}, _, _> can never match the type <{'true','true'},atom() | binary() | [atom() | [any()] | char()],[any()]>
asn1ct.erl:909: Guard test is_atom(Ext::[49 | 97 | 98 | 100 | 110 | 115]) can never succeed
asn1ct_check.erl:1698: The pattern {'error', _} can never match the type [any()]
asn1ct_check.erl:2733: The pattern {'type', Tag, _, _, _, _} can never match the type 'ASN1_OPEN_TYPE' | {_,_} | {'fixedtypevaluefield',_,_}
-asn1ct_check.erl:2738: The pattern <_S, _> can never match since previous clauses completely covered the type <#state{},#ObjectClassFieldType{class::#objectclass{fields::maybe_improper_list() | {_,_,_,_}},fieldname::{_,maybe_improper_list()},type::'ASN1_OPEN_TYPE' | {_,_} | {'fixedtypevaluefield',_,_}}>
+asn1ct_check.erl:2738: The pattern <_S, _> can never match since previous clauses completely covered the type <#state{},#'ObjectClassFieldType'{class::#objectclass{fields::maybe_improper_list() | {_,_,_,_}},fieldname::{_,maybe_improper_list()},type::'ASN1_OPEN_TYPE' | {_,_} | {'fixedtypevaluefield',_,_}}>
asn1ct_check.erl:2887: The variable Other can never match since previous clauses completely covered the type any()
asn1ct_check.erl:3188: The pattern <_S, [], B> can never match the type <#state{},{'SingleValue',_},{'ValueRange',_}>
asn1ct_check.erl:3190: The pattern <_S, A, []> can never match the type <#state{},{'SingleValue',_},{'ValueRange',_}>
@@ -29,8 +29,8 @@ asn1ct_check.erl:5128: Guard test is_record(Type::{_,_} | {'fixedtypevaluefield'
asn1ct_check.erl:540: The pattern <_S, {'poc', _ObjSet, _Params}> can never match since previous clauses completely covered the type <#state{},_>
asn1ct_check.erl:5517: The pattern <_, []> can never match the type <_,[{'ABSTRACT-SYNTAX',{_,_,_}} | {'TYPE-IDENTIFIER',{_,_,_}},...]>
asn1ct_constructed_ber.erl:1075: The pattern {{{'ObjectClassFieldType', _, _, _, {'objectfield', PrimFieldName1, PFNList}}, _}, {'componentrelation', _, _}} can never match the type {#type{},_}
-asn1ct_constructed_ber.erl:695: The pattern {'EXTENSIONMARK', _, _} can never match the type #ComponentType{}
-asn1ct_constructed_ber.erl:748: The pattern <Erules, TopType, {CompList, _ExtList}> can never match the type <_,maybe_improper_list(),[#ComponentType{typespec::{_,_,_,_,_,_}}]>
+asn1ct_constructed_ber.erl:695: The pattern {'EXTENSIONMARK', _, _} can never match the type #'ComponentType'{}
+asn1ct_constructed_ber.erl:748: The pattern <Erules, TopType, {CompList, _ExtList}> can never match the type <_,maybe_improper_list(),[#'ComponentType'{typespec::{_,_,_,_,_,_}}]>
asn1ct_constructed_ber_bin_v2.erl:914: The pattern {{{'ObjectClassFieldType', _, _, _, {'objectfield', PrimFieldName1, PFNList}}, _}, {'componentrelation', _, _}} can never match the type {#type{},_}
asn1ct_gen.erl:740: The pattern [] can never match the type [any(),...]
asn1ct_gen_ber.erl:974: The pattern <Erules, [{Name, Def} | Rest]> can never match the type <_,[#typedef{name::atom(),typespec::{_,_,_,_,_,_}}]>
diff --git a/lib/dialyzer/test/r9c_SUITE_data/results/inets b/lib/dialyzer/test/r9c_SUITE_data/results/inets
index fd5e36a3cd..0177dcc88c 100644
--- a/lib/dialyzer/test/r9c_SUITE_data/results/inets
+++ b/lib/dialyzer/test/r9c_SUITE_data/results/inets
@@ -3,13 +3,15 @@ ftp.erl:1243: The pattern {'ok', {N, Bytes}} can never match the type 'eof' | {'
ftp.erl:640: The pattern {'closed', _Why} can never match the type 'perm_fname_not_allowed' | 'perm_neg_compl' | 'perm_no_space' | 'pos_compl' | 'pos_interm' | 'pos_interm_acct' | 'trans_neg_compl' | 'trans_no_space' | {'error' | 'perm_fname_not_allowed' | 'perm_neg_compl' | 'perm_no_space' | 'pos_compl' | 'pos_interm' | 'pos_interm_acct' | 'pos_prel' | 'trans_neg_compl' | 'trans_no_space',atom() | [any()] | {'invalid_server_response',[any(),...]}}
http.erl:117: The pattern {'error', Reason} can never match the type #req_headers{connection::[45 | 97 | 101 | 105 | 107 | 108 | 112 | 118,...],content_length::[48,...],other::[{_,_}]}
http.erl:138: Function close_session/2 will never be called
-http_lib.erl:286: The call http_lib:close('ip_comm' | {'ssl',_},any()) will never return since it differs in the 1st argument from the success typing arguments: ('http' | 'https',any())
-http_lib.erl:424: The variable _ can never match since previous clauses completely covered the type any()
-http_lib.erl:438: The variable _ can never match since previous clauses completely covered the type any()
+http_lib.erl:286: The call http_lib:close('ip_comm' | {'ssl',_},port() | {'sslsocket',_,_}) will never return since it differs in the 1st argument from the success typing arguments: ('http' | 'https',port() | {'sslsocket',_,pid() | {_,{'config',_,_,_,_,{_,_,_,_}}} | {'sslsocket',_,pid() | {'sslsocket',_,pid() | {_,_,_}}}})
+http_lib.erl:415: The pattern 61 can never match the type 'http_eoh' | binary() | maybe_improper_list(any(),binary() | []) | {'http_error',binary() | string()} | #http_request{method::'DELETE' | 'GET' | 'HEAD' | 'OPTIONS' | 'POST' | 'PUT' | 'TRACE' | binary() | string(),path::'*' | binary() | string() | {'abs_path',binary() | string()} | {'scheme',binary() | string(),binary() | string()} | {'absoluteURI','http' | 'https',binary() | string(),'undefined' | non_neg_integer(),binary() | string()},version::{non_neg_integer(),non_neg_integer()}} | #http_response{version::{non_neg_integer(),non_neg_integer()},status::integer(),phrase::binary() | string()} | {'http_header',integer(),atom() | binary() | string(),_,binary() | string()}
+http_lib.erl:417: The pattern 59 can never match the type 'http_eoh' | binary() | maybe_improper_list(any(),binary() | []) | {'http_error',binary() | string()} | #http_request{method::'DELETE' | 'GET' | 'HEAD' | 'OPTIONS' | 'POST' | 'PUT' | 'TRACE' | binary() | string(),path::'*' | binary() | string() | {'abs_path',binary() | string()} | {'scheme',binary() | string(),binary() | string()} | {'absoluteURI','http' | 'https',binary() | string(),'undefined' | non_neg_integer(),binary() | string()},version::{non_neg_integer(),non_neg_integer()}} | #http_response{version::{non_neg_integer(),non_neg_integer()},status::integer(),phrase::binary() | string()} | {'http_header',integer(),atom() | binary() | string(),_,binary() | string()}
+http_lib.erl:420: The pattern 13 can never match the type 'http_eoh' | binary() | maybe_improper_list(any(),binary() | []) | {'http_error',binary() | string()} | #http_request{method::'DELETE' | 'GET' | 'HEAD' | 'OPTIONS' | 'POST' | 'PUT' | 'TRACE' | binary() | string(),path::'*' | binary() | string() | {'abs_path',binary() | string()} | {'scheme',binary() | string(),binary() | string()} | {'absoluteURI','http' | 'https',binary() | string(),'undefined' | non_neg_integer(),binary() | string()},version::{non_neg_integer(),non_neg_integer()}} | #http_response{version::{non_neg_integer(),non_neg_integer()},status::integer(),phrase::binary() | string()} | {'http_header',integer(),atom() | binary() | string(),_,binary() | string()}
+http_lib.erl:424: The variable _ can never match since previous clauses completely covered the type 'http_eoh' | binary() | maybe_improper_list(any(),binary() | []) | {'http_error',binary() | string()} | #http_request{method::'DELETE' | 'GET' | 'HEAD' | 'OPTIONS' | 'POST' | 'PUT' | 'TRACE' | binary() | string(),path::'*' | binary() | string() | {'abs_path',binary() | string()} | {'scheme',binary() | string(),binary() | string()} | {'absoluteURI','http' | 'https',binary() | string(),'undefined' | non_neg_integer(),binary() | string()},version::{non_neg_integer(),non_neg_integer()}} | #http_response{version::{non_neg_integer(),non_neg_integer()},status::integer(),phrase::binary() | string()} | {'http_header',integer(),atom() | binary() | string(),_,binary() | string()}
+http_lib.erl:428: Function read_chunk_ext_val/6 will never be called
+http_lib.erl:444: The pattern 10 can never match the type 'http_eoh' | binary() | maybe_improper_list(any(),binary() | []) | {'http_error',binary() | string()} | #http_request{method::'DELETE' | 'GET' | 'HEAD' | 'OPTIONS' | 'POST' | 'PUT' | 'TRACE' | binary() | string(),path::'*' | binary() | string() | {'abs_path',binary() | string()} | {'scheme',binary() | string(),binary() | string()} | {'absoluteURI','http' | 'https',binary() | string(),'undefined' | non_neg_integer(),binary() | string()},version::{non_neg_integer(),non_neg_integer()}} | #http_response{version::{non_neg_integer(),non_neg_integer()},status::integer(),phrase::binary() | string()} | {'http_header',integer(),atom() | binary() | string(),_,binary() | string()}
+http_lib.erl:552: Call to missing or unexported function ssl:accept/2
http_lib.erl:99: Function getHeaderValue/2 will never be called
-httpc_handler.erl:322: Function status_continue/2 has no local return
-httpc_handler.erl:37: Function init_connection/2 has no local return
-httpc_handler.erl:65: Function next_response_with_request/2 has no local return
httpc_handler.erl:660: Function exit_session_ok/2 has no local return
httpc_manager.erl:145: The pattern {ErrorReply, State2} can never match the type {{'ok',number()},number(),#state{reqid::number()}}
httpc_manager.erl:160: The pattern {ErrorReply, State2} can never match the type {{'ok',number()},number(),#state{reqid::number()}}
@@ -24,11 +26,14 @@ httpd_manager.erl:885: The pattern {'EXIT', Reason} can never match since previo
httpd_manager.erl:919: Function auth_status/1 will never be called
httpd_manager.erl:926: Function sec_status/1 will never be called
httpd_manager.erl:933: Function acceptor_status/1 will never be called
-httpd_request_handler.erl:374: The call httpd_response:send_status(Info::#mod{parsed_header::maybe_improper_list()},417,[32 | 66 | 98 | 100 | 103 | 105 | 111 | 116 | 121,...]) will never return since it differs in the 2nd argument from the success typing arguments: (#mod{socket_type::'ip_comm' | {'ssl',_}},100 | 301 | 304 | 400 | 401 | 403 | 404 | 412 | 414 | 416 | 500 | 501 | 503,any())
-httpd_request_handler.erl:378: The call httpd_response:send_status(Info::#mod{parsed_header::maybe_improper_list()},417,[32 | 77 | 97 | 100 | 101 | 104 | 108 | 110 | 111 | 116 | 119,...]) will never return since it differs in the 2nd argument from the success typing arguments: (#mod{socket_type::'ip_comm' | {'ssl',_}},100 | 301 | 304 | 400 | 401 | 403 | 404 | 412 | 414 | 416 | 500 | 501 | 503,any())
-httpd_request_handler.erl:401: The call httpd_response:send_status(Info::#mod{parsed_header::maybe_improper_list()},417,[32 | 77 | 97 | 100 | 101 | 104 | 108 | 110 | 111 | 116 | 119,...]) will never return since it differs in the 2nd argument from the success typing arguments: (#mod{socket_type::'ip_comm' | {'ssl',_}},100 | 301 | 304 | 400 | 401 | 403 | 404 | 412 | 414 | 416 | 500 | 501 | 503,any())
-httpd_request_handler.erl:644: The call lists:reverse(Fields0::{'error',_} | {'ok',[[any()]]}) will never return since it differs in the 1st argument from the success typing arguments: ([any()])
+httpd_request_handler.erl:374: The call httpd_response:send_status(Info::#mod{parsed_header::maybe_improper_list()},417,[32 | 66 | 98 | 100 | 103 | 105 | 111 | 116 | 121,...]) will never return since it differs in the 2nd argument from the success typing arguments: (#mod{socket_type::'ip_comm' | {'ssl',_},socket::port() | {'sslsocket',_,_}},100 | 301 | 304 | 400 | 401 | 403 | 404 | 412 | 414 | 416 | 500 | 501 | 503,any())
+httpd_request_handler.erl:378: The call httpd_response:send_status(Info::#mod{parsed_header::maybe_improper_list()},417,[32 | 77 | 97 | 100 | 101 | 104 | 108 | 110 | 111 | 116 | 119,...]) will never return since it differs in the 2nd argument from the success typing arguments: (#mod{socket_type::'ip_comm' | {'ssl',_},socket::port() | {'sslsocket',_,_}},100 | 301 | 304 | 400 | 401 | 403 | 404 | 412 | 414 | 416 | 500 | 501 | 503,any())
+httpd_request_handler.erl:401: The call httpd_response:send_status(Info::#mod{parsed_header::maybe_improper_list()},417,[32 | 77 | 97 | 100 | 101 | 104 | 108 | 110 | 111 | 116 | 119,...]) will never return since it differs in the 2nd argument from the success typing arguments: (#mod{socket_type::'ip_comm' | {'ssl',_},socket::port() | {'sslsocket',_,_}},100 | 301 | 304 | 400 | 401 | 403 | 404 | 412 | 414 | 416 | 500 | 501 | 503,any())
+httpd_request_handler.erl:489: The variable Other can never match since previous clauses completely covered the type {'error',_} | {'ok','http_eoh' | binary() | maybe_improper_list(any(),binary() | []) | {'http_error',binary() | string()} | {'http_request','DELETE' | 'GET' | 'HEAD' | 'OPTIONS' | 'POST' | 'PUT' | 'TRACE' | binary() | string(),'*' | binary() | string() | {'abs_path',binary() | [any()]} | {'scheme',binary() | [any()],binary() | [any()]} | {'absoluteURI','http' | 'https',binary() | [any()],'undefined' | non_neg_integer(),binary() | [any()]},{non_neg_integer(),non_neg_integer()}} | {'http_response',{non_neg_integer(),non_neg_integer()},integer(),binary() | string()} | {'http_header',integer(),atom() | binary() | string(),_,binary() | string()}}
+httpd_request_handler.erl:644: The call lists:reverse(Fields0::{'error',_} | {'ok',_}) will never return since it differs in the 1st argument from the success typing arguments: ([any()])
httpd_request_handler.erl:645: Function will never be called
+httpd_socket.erl:129: Call to missing or unexported function ssl:accept/2
+httpd_socket.erl:49: The pattern {'ok', _} can never match the type {'error',_}
httpd_sup.erl:63: The variable Else can never match since previous clauses completely covered the type {'error',_} | {'ok',[any()],_,_}
httpd_sup.erl:88: The pattern {'error', Reason} can never match the type {'ok',_,_}
httpd_sup.erl:92: The variable Else can never match since previous clauses completely covered the type {'ok',_,_}
@@ -38,17 +43,17 @@ mod_auth_plain.erl:100: The variable _ can never match since previous clauses co
mod_auth_plain.erl:159: The variable _ can never match since previous clauses completely covered the type [any()]
mod_auth_plain.erl:83: The variable O can never match since previous clauses completely covered the type [any()]
mod_cgi.erl:372: The pattern {'http_response', NewAccResponse} can never match the type 'ok'
-mod_dir.erl:101: The call lists:flatten(nonempty_improper_list(atom() | binary() | [any()] | char(),atom())) will never return since it differs in the 1st argument from the success typing arguments: ([any()])
+mod_dir.erl:101: The call lists:flatten(nonempty_improper_list(atom() | [any()] | char(),atom())) will never return since it differs in the 1st argument from the success typing arguments: ([any()])
mod_dir.erl:72: The pattern {'error', Reason} can never match the type {'ok',[[[any()] | char()],...]}
-mod_get.erl:135: The pattern <{'enfile', _}, _Info, Path> can never match the type <atom(),#mod{},atom() | binary() | [atom() | binary() | [any()] | char()]>
-mod_head.erl:80: The pattern <{'enfile', _}, _Info, Path> can never match the type <atom(),#mod{},atom() | binary() | [atom() | binary() | [atom() | binary() | [any()] | char()] | char()]>
+mod_get.erl:135: The pattern <{'enfile', _}, _Info, Path> can never match the type <atom(),#mod{},atom() | binary() | [atom() | [any()] | char()]>
+mod_head.erl:80: The pattern <{'enfile', _}, _Info, Path> can never match the type <atom(),#mod{},atom() | binary() | [atom() | [any()] | char()]>
mod_htaccess.erl:460: The pattern {'error', BadData} can never match the type {'ok',_}
-mod_include.erl:193: The pattern {_, Name, {[], []}} can never match the type {[any()],[any()],maybe_improper_list()}
-mod_include.erl:195: The pattern {_, Name, {PathInfo, []}} can never match the type {[any()],[any()],maybe_improper_list()}
-mod_include.erl:197: The pattern {_, Name, {PathInfo, QueryString}} can never match the type {[any()],[any()],maybe_improper_list()}
-mod_include.erl:201: The variable Gurka can never match since previous clauses completely covered the type {[any()],[any()],maybe_improper_list()}
-mod_include.erl:692: The pattern <{'read', Reason}, Info, Path> can never match the type <{'open',atom()},#mod{},atom() | binary() | [atom() | binary() | [atom() | binary() | [any()] | char()] | char()]>
-mod_include.erl:706: The pattern <{'enfile', _}, _Info, Path> can never match the type <atom(),#mod{},atom() | binary() | [atom() | binary() | [atom() | binary() | [any()] | char()] | char()]>
+mod_include.erl:193: The pattern {_, Name, {[], []}} can never match the type {[any()],[any()],string()}
+mod_include.erl:195: The pattern {_, Name, {PathInfo, []}} can never match the type {[any()],[any()],string()}
+mod_include.erl:197: The pattern {_, Name, {PathInfo, QueryString}} can never match the type {[any()],[any()],string()}
+mod_include.erl:201: The variable Gurka can never match since previous clauses completely covered the type {[any()],[any()],string()}
+mod_include.erl:692: The pattern <{'read', Reason}, Info, Path> can never match the type <{'open',atom()},#mod{},atom() | binary() | [atom() | [any()] | char()]>
+mod_include.erl:706: The pattern <{'enfile', _}, _Info, Path> can never match the type <atom(),#mod{},atom() | binary() | [atom() | [any()] | char()]>
mod_include.erl:716: Function read_error/3 will never be called
mod_include.erl:719: Function read_error/4 will never be called
mod_security_server.erl:386: The variable O can never match since previous clauses completely covered the type [any()]
diff --git a/lib/dialyzer/test/r9c_SUITE_data/results/mnesia b/lib/dialyzer/test/r9c_SUITE_data/results/mnesia
index e199581a0e..2be71ac7d7 100644
--- a/lib/dialyzer/test/r9c_SUITE_data/results/mnesia
+++ b/lib/dialyzer/test/r9c_SUITE_data/results/mnesia
@@ -6,6 +6,7 @@ mnesia_bup.erl:111: The created fun has no local return
mnesia_bup.erl:574: Function fallback_receiver/2 has no local return
mnesia_bup.erl:967: Function uninstall_fallback_master/2 has no local return
mnesia_checkpoint.erl:1014: The variable Error can never match since previous clauses completely covered the type {'ok',#checkpoint_args{nodes::[any()],retainers::[any(),...]}}
+mnesia_checkpoint.erl:894: The call sys:handle_system_msg(Msg::any(),From::any(),'no_parent','mnesia_checkpoint',[],Cp::#checkpoint_args{}) breaks the contract (Msg,From,Parent,Module,Debug,Misc) -> Void when is_subtype(Msg,term()), is_subtype(From,{pid(),Tag::_}), is_subtype(Parent,pid()), is_subtype(Module,module()), is_subtype(Debug,[dbg_opt()]), is_subtype(Misc,term()), is_subtype(Void,term())
mnesia_controller.erl:1666: The variable Tab can never match since previous clauses completely covered the type [any()]
mnesia_controller.erl:1679: The pattern {'stop', Reason, Reply, State2} can never match the type {'noreply',_} | {'reply',_,_} | {'stop','shutdown',#state{}}
mnesia_controller.erl:1685: The pattern {'noreply', State2, _Timeout} can never match the type {'reply',_,_}
@@ -15,6 +16,7 @@ mnesia_frag.erl:294: The call mnesia_frag:remote_collect(Ref::reference(),{'erro
mnesia_frag.erl:304: The call mnesia_frag:remote_collect(Ref::reference(),{'error',{'node_not_running',_}},[],OldSelectFun::fun(() -> [any()])) will never return since it differs in the 2nd argument from the success typing arguments: (reference(),'ok',[any()],fun(() -> [any()]))
mnesia_frag.erl:312: The call mnesia_frag:remote_collect(Ref::reference(),LocalRes::{'error',_},[],OldSelectFun::fun(() -> [any()])) will never return since it differs in the 2nd argument from the success typing arguments: (reference(),'ok',[any()],fun(() -> [any()]))
mnesia_index.erl:52: The call mnesia_lib:other_val(Var::{_,'commit_work' | 'index' | 'setorbag' | 'storage_type' | {'index',_}},_ReASoN_::any()) will never return since it differs in the 1st argument from the success typing arguments: ({_,'active_replicas' | 'where_to_read' | 'where_to_write'},any())
+mnesia_lib.erl:1028: The pattern {'EXIT', Reason} can never match the type [any()] | {'error',_}
mnesia_lib.erl:957: The pattern {'ok', {0, _}} can never match the type 'eof' | {'error',atom()} | {'ok',binary() | string()}
mnesia_lib.erl:959: The pattern {'ok', {_, Bin}} can never match the type 'eof' | {'error',atom()} | {'ok',binary() | string()}
mnesia_loader.erl:36: The call mnesia_lib:other_val(Var::{_,'access_mode' | 'cstruct' | 'db_nodes' | 'setorbag' | 'snmp' | 'storage_type'},Reason::any()) will never return since it differs in the 1st argument from the success typing arguments: ({_,'active_replicas' | 'where_to_read' | 'where_to_write'},any())
@@ -30,5 +32,6 @@ mnesia_schema.erl:1258: Guard test FromS::'disc_copies' | 'disc_only_copies' | '
mnesia_schema.erl:1639: The pattern {'false', 'mandatory'} can never match the type {'false','optional'}
mnesia_schema.erl:2434: The variable Reason can never match since previous clauses completely covered the type {'error',_} | {'ok',_}
mnesia_schema.erl:451: Guard test UseDirAnyway::'false' == 'true' can never succeed
+mnesia_text.erl:180: The variable T can never match since previous clauses completely covered the type {'error',{integer(),atom() | tuple(),_}} | {'ok',_}
mnesia_tm.erl:1522: Function commit_participant/5 has no local return
mnesia_tm.erl:2169: Function system_terminate/4 has no local return
diff --git a/lib/dialyzer/test/race_SUITE_data/results/extract_translations b/lib/dialyzer/test/race_SUITE_data/results/extract_translations
index f7d5abc6f5..62aa1aa511 100644
--- a/lib/dialyzer/test/race_SUITE_data/results/extract_translations
+++ b/lib/dialyzer/test/race_SUITE_data/results/extract_translations
@@ -1,5 +1,5 @@
-extract_translations.erl:140: The call ets:insert('files',{atom() | binary() | [atom() | binary() | [atom() | binary() | [any()] | char()] | char()]}) might have an unintended effect due to a possible race condition caused by its combination with the ets:lookup('files',File::atom() | binary() | [atom() | binary() | [atom() | binary() | [any()] | char()] | char()]) call in extract_translations.erl on line 135
+extract_translations.erl:140: The call ets:insert('files',{atom() | binary() | [atom() | [any()] | char()]}) might have an unintended effect due to a possible race condition caused by its combination with the ets:lookup('files',File::atom() | binary() | [atom() | [any()] | char()]) call in extract_translations.erl on line 135
extract_translations.erl:146: The call ets:insert('translations',{_,[]}) might have an unintended effect due to a possible race condition caused by its combination with the ets:lookup('translations',Str::any()) call in extract_translations.erl on line 126
-extract_translations.erl:152: The call ets:insert('files',{atom() | binary() | [atom() | binary() | [atom() | binary() | [any()] | char()] | char()]}) might have an unintended effect due to a possible race condition caused by its combination with the ets:lookup('files',File::atom() | binary() | [atom() | binary() | [atom() | binary() | [any()] | char()] | char()]) call in extract_translations.erl on line 148
+extract_translations.erl:152: The call ets:insert('files',{atom() | binary() | [atom() | [any()] | char()]}) might have an unintended effect due to a possible race condition caused by its combination with the ets:lookup('files',File::atom() | binary() | [atom() | [any()] | char()]) call in extract_translations.erl on line 148
extract_translations.erl:154: The call ets:insert('translations',{_,[]}) might have an unintended effect due to a possible race condition caused by its combination with the ets:lookup('translations',Str::any()) call in extract_translations.erl on line 126
diff --git a/lib/dialyzer/test/small_SUITE_data/results/common_eunit b/lib/dialyzer/test/small_SUITE_data/results/common_eunit
new file mode 100644
index 0000000000..bb5fd1c9ac
--- /dev/null
+++ b/lib/dialyzer/test/small_SUITE_data/results/common_eunit
@@ -0,0 +1,2 @@
+
+common_eunit.erl:57: The created fun has no local return
diff --git a/lib/dialyzer/test/small_SUITE_data/results/comparisons b/lib/dialyzer/test/small_SUITE_data/results/comparisons
new file mode 100644
index 0000000000..642585d25e
--- /dev/null
+++ b/lib/dialyzer/test/small_SUITE_data/results/comparisons
@@ -0,0 +1,153 @@
+
+comparisons.erl:100: The pattern 'true' can never match the type 'false'
+comparisons.erl:101: The pattern 'true' can never match the type 'false'
+comparisons.erl:102: The pattern 'false' can never match the type 'true'
+comparisons.erl:103: The pattern 'false' can never match the type 'true'
+comparisons.erl:104: The pattern 'true' can never match the type 'false'
+comparisons.erl:105: The pattern 'true' can never match the type 'false'
+comparisons.erl:107: The pattern 'true' can never match the type 'false'
+comparisons.erl:108: The pattern 'true' can never match the type 'false'
+comparisons.erl:109: The pattern 'false' can never match the type 'true'
+comparisons.erl:110: The pattern 'false' can never match the type 'true'
+comparisons.erl:111: The pattern 'true' can never match the type 'false'
+comparisons.erl:112: The pattern 'true' can never match the type 'false'
+comparisons.erl:113: The pattern 'false' can never match the type 'true'
+comparisons.erl:114: The pattern 'false' can never match the type 'true'
+comparisons.erl:115: The pattern 'true' can never match the type 'false'
+comparisons.erl:116: The pattern 'true' can never match the type 'false'
+comparisons.erl:117: The pattern 'false' can never match the type 'true'
+comparisons.erl:118: The pattern 'false' can never match the type 'true'
+comparisons.erl:123: The pattern 'false' can never match the type 'true'
+comparisons.erl:124: The pattern 'false' can never match the type 'true'
+comparisons.erl:125: The pattern 'true' can never match the type 'false'
+comparisons.erl:126: The pattern 'true' can never match the type 'false'
+comparisons.erl:127: The pattern 'false' can never match the type 'true'
+comparisons.erl:128: The pattern 'false' can never match the type 'true'
+comparisons.erl:129: The pattern 'true' can never match the type 'false'
+comparisons.erl:130: The pattern 'true' can never match the type 'false'
+comparisons.erl:132: The pattern 'true' can never match the type 'false'
+comparisons.erl:133: The pattern 'true' can never match the type 'false'
+comparisons.erl:134: The pattern 'false' can never match the type 'true'
+comparisons.erl:135: The pattern 'false' can never match the type 'true'
+comparisons.erl:136: The pattern 'true' can never match the type 'false'
+comparisons.erl:137: The pattern 'true' can never match the type 'false'
+comparisons.erl:138: The pattern 'false' can never match the type 'true'
+comparisons.erl:139: The pattern 'false' can never match the type 'true'
+comparisons.erl:140: The pattern 'true' can never match the type 'false'
+comparisons.erl:141: The pattern 'true' can never match the type 'false'
+comparisons.erl:142: The pattern 'false' can never match the type 'true'
+comparisons.erl:143: The pattern 'false' can never match the type 'true'
+comparisons.erl:144: The pattern 'true' can never match the type 'false'
+comparisons.erl:145: The pattern 'true' can never match the type 'false'
+comparisons.erl:146: The pattern 'false' can never match the type 'true'
+comparisons.erl:147: The pattern 'false' can never match the type 'true'
+comparisons.erl:152: The pattern 'false' can never match the type 'true'
+comparisons.erl:153: The pattern 'false' can never match the type 'true'
+comparisons.erl:154: The pattern 'true' can never match the type 'false'
+comparisons.erl:155: The pattern 'true' can never match the type 'false'
+comparisons.erl:157: The pattern 'true' can never match the type 'false'
+comparisons.erl:158: The pattern 'true' can never match the type 'false'
+comparisons.erl:159: The pattern 'false' can never match the type 'true'
+comparisons.erl:160: The pattern 'false' can never match the type 'true'
+comparisons.erl:161: The pattern 'true' can never match the type 'false'
+comparisons.erl:162: The pattern 'true' can never match the type 'false'
+comparisons.erl:163: The pattern 'false' can never match the type 'true'
+comparisons.erl:164: The pattern 'false' can never match the type 'true'
+comparisons.erl:165: The pattern 'true' can never match the type 'false'
+comparisons.erl:166: The pattern 'true' can never match the type 'false'
+comparisons.erl:167: The pattern 'false' can never match the type 'true'
+comparisons.erl:168: The pattern 'false' can never match the type 'true'
+comparisons.erl:169: The pattern 'true' can never match the type 'false'
+comparisons.erl:170: The pattern 'true' can never match the type 'false'
+comparisons.erl:171: The pattern 'false' can never match the type 'true'
+comparisons.erl:172: The pattern 'false' can never match the type 'true'
+comparisons.erl:173: The pattern 'true' can never match the type 'false'
+comparisons.erl:174: The pattern 'true' can never match the type 'false'
+comparisons.erl:175: The pattern 'false' can never match the type 'true'
+comparisons.erl:176: The pattern 'false' can never match the type 'true'
+comparisons.erl:186: The pattern 'false' can never match the type 'true'
+comparisons.erl:187: The pattern 'false' can never match the type 'true'
+comparisons.erl:188: The pattern 'true' can never match the type 'false'
+comparisons.erl:189: The pattern 'true' can never match the type 'false'
+comparisons.erl:190: The pattern 'false' can never match the type 'true'
+comparisons.erl:191: The pattern 'false' can never match the type 'true'
+comparisons.erl:192: The pattern 'true' can never match the type 'false'
+comparisons.erl:193: The pattern 'true' can never match the type 'false'
+comparisons.erl:203: The pattern 'false' can never match the type 'true'
+comparisons.erl:204: The pattern 'false' can never match the type 'true'
+comparisons.erl:205: The pattern 'true' can never match the type 'false'
+comparisons.erl:206: The pattern 'true' can never match the type 'false'
+comparisons.erl:208: The pattern 'true' can never match the type 'false'
+comparisons.erl:209: The pattern 'true' can never match the type 'false'
+comparisons.erl:210: The pattern 'false' can never match the type 'true'
+comparisons.erl:211: The pattern 'false' can never match the type 'true'
+comparisons.erl:221: The pattern 'true' can never match the type 'false'
+comparisons.erl:222: The pattern 'true' can never match the type 'false'
+comparisons.erl:223: The pattern 'false' can never match the type 'true'
+comparisons.erl:224: The pattern 'false' can never match the type 'true'
+comparisons.erl:225: The pattern 'true' can never match the type 'false'
+comparisons.erl:226: The pattern 'true' can never match the type 'false'
+comparisons.erl:227: The pattern 'false' can never match the type 'true'
+comparisons.erl:228: The pattern 'false' can never match the type 'true'
+comparisons.erl:242: The pattern 'false' can never match the type 'true'
+comparisons.erl:243: The pattern 'false' can never match the type 'true'
+comparisons.erl:244: The pattern 'true' can never match the type 'false'
+comparisons.erl:245: The pattern 'true' can never match the type 'false'
+comparisons.erl:246: The pattern 'false' can never match the type 'true'
+comparisons.erl:247: The pattern 'false' can never match the type 'true'
+comparisons.erl:248: The pattern 'true' can never match the type 'false'
+comparisons.erl:249: The pattern 'true' can never match the type 'false'
+comparisons.erl:251: The pattern 'true' can never match the type 'false'
+comparisons.erl:252: The pattern 'true' can never match the type 'false'
+comparisons.erl:253: The pattern 'false' can never match the type 'true'
+comparisons.erl:254: The pattern 'false' can never match the type 'true'
+comparisons.erl:263: The pattern 'false' can never match the type 'true'
+comparisons.erl:264: The pattern 'false' can never match the type 'true'
+comparisons.erl:265: The pattern 'true' can never match the type 'false'
+comparisons.erl:266: The pattern 'true' can never match the type 'false'
+comparisons.erl:268: The pattern 'true' can never match the type 'false'
+comparisons.erl:269: The pattern 'true' can never match the type 'false'
+comparisons.erl:270: The pattern 'false' can never match the type 'true'
+comparisons.erl:271: The pattern 'false' can never match the type 'true'
+comparisons.erl:272: The pattern 'true' can never match the type 'false'
+comparisons.erl:273: The pattern 'true' can never match the type 'false'
+comparisons.erl:274: The pattern 'false' can never match the type 'true'
+comparisons.erl:275: The pattern 'false' can never match the type 'true'
+comparisons.erl:293: The pattern 'false' can never match the type 'true'
+comparisons.erl:294: The pattern 'false' can never match the type 'true'
+comparisons.erl:295: The pattern 'true' can never match the type 'false'
+comparisons.erl:296: The pattern 'true' can never match the type 'false'
+comparisons.erl:311: The pattern 'true' can never match the type 'false'
+comparisons.erl:312: The pattern 'true' can never match the type 'false'
+comparisons.erl:313: The pattern 'false' can never match the type 'true'
+comparisons.erl:314: The pattern 'false' can never match the type 'true'
+comparisons.erl:44: The pattern 'false' can never match the type 'true'
+comparisons.erl:45: The pattern 'false' can never match the type 'true'
+comparisons.erl:46: The pattern 'true' can never match the type 'false'
+comparisons.erl:47: The pattern 'true' can never match the type 'false'
+comparisons.erl:48: The pattern 'false' can never match the type 'true'
+comparisons.erl:49: The pattern 'false' can never match the type 'true'
+comparisons.erl:50: The pattern 'true' can never match the type 'false'
+comparisons.erl:51: The pattern 'true' can never match the type 'false'
+comparisons.erl:52: The pattern 'false' can never match the type 'true'
+comparisons.erl:53: The pattern 'false' can never match the type 'true'
+comparisons.erl:54: The pattern 'true' can never match the type 'false'
+comparisons.erl:55: The pattern 'true' can never match the type 'false'
+comparisons.erl:69: The pattern 'false' can never match the type 'true'
+comparisons.erl:70: The pattern 'false' can never match the type 'true'
+comparisons.erl:71: The pattern 'true' can never match the type 'false'
+comparisons.erl:72: The pattern 'true' can never match the type 'false'
+comparisons.erl:73: The pattern 'false' can never match the type 'true'
+comparisons.erl:74: The pattern 'false' can never match the type 'true'
+comparisons.erl:75: The pattern 'true' can never match the type 'false'
+comparisons.erl:76: The pattern 'true' can never match the type 'false'
+comparisons.erl:77: The pattern 'false' can never match the type 'true'
+comparisons.erl:78: The pattern 'false' can never match the type 'true'
+comparisons.erl:79: The pattern 'true' can never match the type 'false'
+comparisons.erl:80: The pattern 'true' can never match the type 'false'
+comparisons.erl:94: The pattern 'false' can never match the type 'true'
+comparisons.erl:95: The pattern 'false' can never match the type 'true'
+comparisons.erl:96: The pattern 'true' can never match the type 'false'
+comparisons.erl:97: The pattern 'true' can never match the type 'false'
+comparisons.erl:98: The pattern 'false' can never match the type 'true'
+comparisons.erl:99: The pattern 'false' can never match the type 'true'
diff --git a/lib/dialyzer/test/small_SUITE_data/results/failing_funs b/lib/dialyzer/test/small_SUITE_data/results/failing_funs
new file mode 100644
index 0000000000..a1fb22cbc6
--- /dev/null
+++ b/lib/dialyzer/test/small_SUITE_data/results/failing_funs
@@ -0,0 +1,20 @@
+
+failing_funs.erl:101: The created fun has no local return
+failing_funs.erl:104: The created fun has no local return
+failing_funs.erl:127: The created fun has no local return
+failing_funs.erl:135: The created fun has no local return
+failing_funs.erl:138: The created fun has no local return
+failing_funs.erl:13: Function foo3/0 has no local return
+failing_funs.erl:13: The pattern 'b' can never match the type 'a'
+failing_funs.erl:161: The created fun has no local return
+failing_funs.erl:169: The created fun has no local return
+failing_funs.erl:172: The created fun has no local return
+failing_funs.erl:17: The pattern 'b' can never match the type 'a'
+failing_funs.erl:195: The created fun has no local return
+failing_funs.erl:203: The created fun has no local return
+failing_funs.erl:206: The created fun has no local return
+failing_funs.erl:229: The created fun has no local return
+failing_funs.erl:55: The created fun has no local return
+failing_funs.erl:62: The created fun has no local return
+failing_funs.erl:69: The created fun has no local return
+failing_funs.erl:76: The created fun has no local return
diff --git a/lib/dialyzer/test/small_SUITE_data/results/flatten b/lib/dialyzer/test/small_SUITE_data/results/flatten
index 4571214e49..8aa44dd002 100644
--- a/lib/dialyzer/test/small_SUITE_data/results/flatten
+++ b/lib/dialyzer/test/small_SUITE_data/results/flatten
@@ -1,2 +1,2 @@
-flatten.erl:17: The call lists:flatten(nonempty_improper_list(atom() | binary() | [any()] | char(),atom())) will never return since it differs in the 1st argument from the success typing arguments: ([any()])
+flatten.erl:17: The call lists:flatten(nonempty_improper_list(atom() | [any()] | char(),atom())) will never return since it differs in the 1st argument from the success typing arguments: ([any()])
diff --git a/lib/dialyzer/test/small_SUITE_data/results/my_sofs b/lib/dialyzer/test/small_SUITE_data/results/my_sofs
index bfee0bce0d..bc97c08d62 100644
--- a/lib/dialyzer/test/small_SUITE_data/results/my_sofs
+++ b/lib/dialyzer/test/small_SUITE_data/results/my_sofs
@@ -1,3 +1,3 @@
-my_sofs.erl:34: The pattern {'Set', _, _} can never match the type #OrdSet{}
-my_sofs.erl:54: The pattern {'Set', _, _} can never match the type #OrdSet{}
+my_sofs.erl:34: The pattern {'Set', _, _} can never match the type #'OrdSet'{}
+my_sofs.erl:54: The pattern {'Set', _, _} can never match the type #'OrdSet'{}
diff --git a/lib/dialyzer/test/small_SUITE_data/src/binary_lc_bug.erl b/lib/dialyzer/test/small_SUITE_data/src/binary_lc_bug.erl
new file mode 100644
index 0000000000..c1e82bfa59
--- /dev/null
+++ b/lib/dialyzer/test/small_SUITE_data/src/binary_lc_bug.erl
@@ -0,0 +1,8 @@
+-module(test).
+
+-export([bin_compr/0]).
+
+bin_compr() ->
+% [ 0 || {N, V} <- [{a, b}] ]. % Works ok
+ << <<>> || {A, B} <- [{a, b}] >>. % Complains
+% << <<>> || X <- [{a, b}] >>. % Works ok
diff --git a/lib/dialyzer/test/small_SUITE_data/src/codec_can.erl b/lib/dialyzer/test/small_SUITE_data/src/codec_can.erl
new file mode 100644
index 0000000000..8abf872b37
--- /dev/null
+++ b/lib/dialyzer/test/small_SUITE_data/src/codec_can.erl
@@ -0,0 +1,35 @@
+%%---------------------------------------------------------------------
+%% From: Peer Stritzinger
+%% Date: 1 May 2011
+%% Subject: Dialyzer v2.2.0 crash
+%%
+%% Binaries of the form <<_:N,_:_*M>> in specs resulted in a crash:
+%% dialyzer: Analysis failed with error: {{case_clause,8},
+%% [{erl_types,t_form_to_string,1},
+%% {erl_types,t_form_to_string,1},
+%% {dialyzer_contracts,contract_to_string_1,1},
+%% {dialyzer_contracts,extra_contract_warning,6},
+%% {dialyzer_contracts,picky_contract_check,7},
+%% because function erl_types:t_form_to_string/1 was not the inverse
+%% of erl_types:t_to_string/2.
+%%
+%% Fixed on the same date and send to OTP for inclusion.
+%%---------------------------------------------------------------------
+-module(codec_can).
+
+-export([recv/3, decode/1]).
+
+-record(can_pkt, {id, data :: binary(), timestamp}).
+
+-type can_pkt() :: #can_pkt{}.
+-type channel() :: atom() | pid() | {atom(),_}.
+
+-spec recv(<<_:64,_:_*8>>, fun((can_pkt()) -> R), channel()) -> R.
+recv(Packet, Fun, Chan) ->
+ #can_pkt{id = Can_id, data = Can_data} = P = decode(Packet),
+ Fun(P).
+
+-spec decode(<<_:64,_:_*8>>) -> #can_pkt{id::<<_:11>>,timestamp::char()}.
+decode(<<_:12, Len:4, Timestamp:16, 0:3, Id:11/bitstring, 0:18,
+ Data:Len/binary, _/binary>>) ->
+ #can_pkt{id = Id, data = Data, timestamp = Timestamp}.
diff --git a/lib/dialyzer/test/small_SUITE_data/src/common_eunit.erl b/lib/dialyzer/test/small_SUITE_data/src/common_eunit.erl
new file mode 100644
index 0000000000..bca390068e
--- /dev/null
+++ b/lib/dialyzer/test/small_SUITE_data/src/common_eunit.erl
@@ -0,0 +1,121 @@
+%%=====================================================================
+%% Program with an erroneous type declaration that caused dialyzer to
+%% go into an infinite loop. There are some comments that explain the
+%% symptoms and the culprit: the return of test_fun() is erroneous and
+%% its type should read
+%% fun((config()) -> test_rep() | [test_rep()])
+%% instead. But this should not throw dialyzer into an infinite loop.
+%% This concerned dialyzer in R14B02 (and probably prior).
+%%=====================================================================
+-module(common_eunit).
+
+-export([expand_cases/2]).
+
+-type test_name() :: atom() | {'group', atom()}.
+
+-type test_rep() :: {{atom(), atom(), arity()}, fun()}
+ | {'setup', fun(), fun()}
+ | {'setup', fun(), fun(), fun()}
+ | {atom(), test_rep()}
+ | {atom(), term(), test_rep()}.
+
+-type config() :: [proplists:property()].
+
+-type control() :: tuple() | atom().
+
+%% The combination of the following type and the (erroneous) spec for
+%% expand_cases/2 is the reason for the infinite loop in dialyzer.
+-type test_fun() :: fun((config()) -> test_rep()).
+
+%% If one comments out this spec the infinite loop disappears.
+-spec expand_cases(atom(), test_name() | [test_name()]) -> test_fun().
+expand_cases(Module, Cases) ->
+ if is_list(Cases) ->
+ TestFuns = [expand_case(Module, Case) || Case <- Cases],
+ fun(Config) -> [F(Config) || F <- TestFuns] end;
+ is_atom(Cases); is_tuple(Cases) ->
+ expand_cases(Module, [Cases])
+ end.
+
+-spec expand_case(atom(), test_name()) -> test_fun().
+expand_case(Module, CaseName) when is_atom(CaseName) ->
+ TestFun = fun(Config) ->
+ {{Module, CaseName, 1},
+ fun() -> apply(Module, CaseName, [Config]) end}
+ end,
+ setup_wrapper(Module, TestFun, {init_per_testcase, [CaseName]},
+ {end_per_testcase, [CaseName]});
+expand_case(Module, {group, GroupName}) ->
+ {Control, Cases} = group_specification(Module, GroupName),
+ TestFun = control_wrapper(Control, expand_cases(Module, Cases)),
+ setup_wrapper(Module, TestFun, {init_per_group, [GroupName]},
+ {end_per_group, [GroupName]}).
+
+-spec control_wrapper([control()], test_fun()) -> test_fun().
+control_wrapper([Control|T], TestFun0) ->
+ TestFun1 = control_wrapper(T, TestFun0),
+ fun(Config) ->
+ case Control of
+ parallel ->
+ {inparallel, TestFun1(Config)};
+ sequence ->
+ {inorder, TestFun1(Config)};
+ {timetrap, Time} ->
+ Seconds = case Time of
+ {hours, Hs} -> Hs * 60 * 60;
+ {minutes, Ms} -> Ms * 60;
+ {seconds, Ss} -> Ss;
+ MSs -> MSs / 1000
+ end,
+ {timeout, Seconds, TestFun1(Config)};
+ C when is_atom(C) ->
+ {C, TestFun1(Config)};
+ {C, Arg} ->
+ {C, Arg, TestFun1(Config)}
+ end
+ end;
+control_wrapper([], TestFun) ->
+ TestFun.
+
+-spec setup_wrapper(atom(), test_fun(), Callback, Callback) -> test_fun()
+ when Callback :: {atom(), list()}.
+setup_wrapper(Module, TestFun, {Setup, SA}, {Cleanup, CA}) ->
+ case erlang:function_exported(Module, Setup, length(SA) + 1) of
+ true ->
+ case erlang:function_exported(Module, Cleanup, length(CA) + 1) of
+ true ->
+ fun(Config0) ->
+ {setup,
+ fun() ->
+ apply(Module, Setup, SA ++ [Config0])
+ end,
+ fun(Config1) ->
+ apply(Module, Cleanup, CA ++ [Config1])
+ end,
+ TestFun}
+ end;
+ false ->
+ fun(Config) ->
+ {setup,
+ fun() ->
+ apply(Module, Setup, SA ++ [Config])
+ end,
+ TestFun}
+ end
+ end;
+ false ->
+ TestFun
+ end.
+
+-spec group_specification(atom(), atom()) -> {[control()], [test_name()]}.
+group_specification(Module, GroupName) ->
+ case lists:keyfind(GroupName, 1, Module:groups()) of
+ {_, Control, Cases} when is_list(Control), is_list(Cases) ->
+ {Control, Cases};
+ {_, Cases} when is_list(Cases) ->
+ {[], Cases};
+ false ->
+ exit({missing_group, GroupName});
+ _ ->
+ exit({bad_group_spec, GroupName})
+ end.
diff --git a/lib/dialyzer/test/small_SUITE_data/src/comparisons.erl b/lib/dialyzer/test/small_SUITE_data/src/comparisons.erl
new file mode 100644
index 0000000000..70e3cb6af4
--- /dev/null
+++ b/lib/dialyzer/test/small_SUITE_data/src/comparisons.erl
@@ -0,0 +1,322 @@
+-module(comparisons).
+
+-compile(export_all).
+
+-define(r, get(r)).
+
+integer() -> integer(?r).
+integer(X) when is_integer(X) -> X.
+
+mfloat() -> float(?r).
+mfloat(X) when is_float(X) -> X.
+
+atom() -> atom(?r).
+atom(X) when is_atom(X) -> X.
+
+tuple() -> tuple(?r).
+tuple(X) when is_tuple(X) -> X.
+
+list() -> list(?r).
+list(X) when is_list(X) -> X.
+
+i() -> integer().
+f() -> mfloat().
+n() -> case ?r of 1 -> i(); 2 -> f() end.
+a() -> atom().
+t() -> tuple().
+l() -> list().
+na() -> case ?r of 1 -> n(); 2 -> a() end.
+at() -> case ?r of 1 -> t(); 2 -> a() end.
+tl() -> case ?r of 1 -> t(); 2 -> l() end.
+
+test_i_ll_i() -> case i() < i() of true -> maybe; false -> maybe_too end.
+test_i_le_i() -> case i() =< i() of true -> maybe; false -> maybe_too end.
+test_i_gg_i() -> case i() > i() of true -> maybe; false -> maybe_too end.
+test_i_ge_i() -> case i() >= i() of true -> maybe; false -> maybe_too end.
+test_i_ll_f() -> case i() < f() of true -> maybe; false -> maybe_too end.
+test_i_le_f() -> case i() =< f() of true -> maybe; false -> maybe_too end.
+test_i_gg_f() -> case i() > f() of true -> maybe; false -> maybe_too end.
+test_i_ge_f() -> case i() >= f() of true -> maybe; false -> maybe_too end.
+test_i_ll_n() -> case i() < n() of true -> maybe; false -> maybe_too end.
+test_i_le_n() -> case i() =< n() of true -> maybe; false -> maybe_too end.
+test_i_gg_n() -> case i() > n() of true -> maybe; false -> maybe_too end.
+test_i_ge_n() -> case i() >= n() of true -> maybe; false -> maybe_too end.
+test_i_ll_a() -> case i() < a() of true -> always; false -> never end.
+test_i_le_a() -> case i() =< a() of true -> always; false -> never end.
+test_i_gg_a() -> case i() > a() of true -> never; false -> always end.
+test_i_ge_a() -> case i() >= a() of true -> never; false -> always end.
+test_i_ll_t() -> case i() < t() of true -> always; false -> never end.
+test_i_le_t() -> case i() =< t() of true -> always; false -> never end.
+test_i_gg_t() -> case i() > t() of true -> never; false -> always end.
+test_i_ge_t() -> case i() >= t() of true -> never; false -> always end.
+test_i_ll_l() -> case i() < l() of true -> always; false -> never end.
+test_i_le_l() -> case i() =< l() of true -> always; false -> never end.
+test_i_gg_l() -> case i() > l() of true -> never; false -> always end.
+test_i_ge_l() -> case i() >= l() of true -> never; false -> always end.
+
+test_f_ll_i() -> case f() < i() of true -> maybe; false -> maybe_too end.
+test_f_le_i() -> case f() =< i() of true -> maybe; false -> maybe_too end.
+test_f_gg_i() -> case f() > i() of true -> maybe; false -> maybe_too end.
+test_f_ge_i() -> case f() >= i() of true -> maybe; false -> maybe_too end.
+test_f_ll_f() -> case f() < f() of true -> maybe; false -> maybe_too end.
+test_f_le_f() -> case f() =< f() of true -> maybe; false -> maybe_too end.
+test_f_gg_f() -> case f() > f() of true -> maybe; false -> maybe_too end.
+test_f_ge_f() -> case f() >= f() of true -> maybe; false -> maybe_too end.
+test_f_ll_n() -> case f() < n() of true -> maybe; false -> maybe_too end.
+test_f_le_n() -> case f() =< n() of true -> maybe; false -> maybe_too end.
+test_f_gg_n() -> case f() > n() of true -> maybe; false -> maybe_too end.
+test_f_ge_n() -> case f() >= n() of true -> maybe; false -> maybe_too end.
+test_f_ll_a() -> case f() < a() of true -> always; false -> never end.
+test_f_le_a() -> case f() =< a() of true -> always; false -> never end.
+test_f_gg_a() -> case f() > a() of true -> never; false -> always end.
+test_f_ge_a() -> case f() >= a() of true -> never; false -> always end.
+test_f_ll_t() -> case f() < t() of true -> always; false -> never end.
+test_f_le_t() -> case f() =< t() of true -> always; false -> never end.
+test_f_gg_t() -> case f() > t() of true -> never; false -> always end.
+test_f_ge_t() -> case f() >= t() of true -> never; false -> always end.
+test_f_ll_l() -> case f() < l() of true -> always; false -> never end.
+test_f_le_l() -> case f() =< l() of true -> always; false -> never end.
+test_f_gg_l() -> case f() > l() of true -> never; false -> always end.
+test_f_ge_l() -> case f() >= l() of true -> never; false -> always end.
+
+test_n_ll_i() -> case n() < i() of true -> maybe; false -> maybe_too end.
+test_n_le_i() -> case n() =< i() of true -> maybe; false -> maybe_too end.
+test_n_gg_i() -> case n() > i() of true -> maybe; false -> maybe_too end.
+test_n_ge_i() -> case n() >= i() of true -> maybe; false -> maybe_too end.
+test_n_ll_f() -> case n() < f() of true -> maybe; false -> maybe_too end.
+test_n_le_f() -> case n() =< f() of true -> maybe; false -> maybe_too end.
+test_n_gg_f() -> case n() > f() of true -> maybe; false -> maybe_too end.
+test_n_ge_f() -> case n() >= f() of true -> maybe; false -> maybe_too end.
+test_n_ll_n() -> case n() < n() of true -> maybe; false -> maybe_too end.
+test_n_le_n() -> case n() =< n() of true -> maybe; false -> maybe_too end.
+test_n_gg_n() -> case n() > n() of true -> maybe; false -> maybe_too end.
+test_n_ge_n() -> case n() >= n() of true -> maybe; false -> maybe_too end.
+test_n_ll_a() -> case n() < a() of true -> always; false -> never end.
+test_n_le_a() -> case n() =< a() of true -> always; false -> never end.
+test_n_gg_a() -> case n() > a() of true -> never; false -> always end.
+test_n_ge_a() -> case n() >= a() of true -> never; false -> always end.
+test_n_ll_t() -> case n() < t() of true -> always; false -> never end.
+test_n_le_t() -> case n() =< t() of true -> always; false -> never end.
+test_n_gg_t() -> case n() > t() of true -> never; false -> always end.
+test_n_ge_t() -> case n() >= t() of true -> never; false -> always end.
+test_n_ll_l() -> case n() < l() of true -> always; false -> never end.
+test_n_le_l() -> case n() =< l() of true -> always; false -> never end.
+test_n_gg_l() -> case n() > l() of true -> never; false -> always end.
+test_n_ge_l() -> case n() >= l() of true -> never; false -> always end.
+
+test_a_ll_i() -> case a() < i() of true -> never; false -> always end.
+test_a_le_i() -> case a() =< i() of true -> never; false -> always end.
+test_a_gg_i() -> case a() > i() of true -> always; false -> never end.
+test_a_ge_i() -> case a() >= i() of true -> always; false -> never end.
+test_a_ll_f() -> case a() < f() of true -> never; false -> always end.
+test_a_le_f() -> case a() =< f() of true -> never; false -> always end.
+test_a_gg_f() -> case a() > f() of true -> always; false -> never end.
+test_a_ge_f() -> case a() >= f() of true -> always; false -> never end.
+test_a_ll_n() -> case a() < n() of true -> never; false -> always end.
+test_a_le_n() -> case a() =< n() of true -> never; false -> always end.
+test_a_gg_n() -> case a() > n() of true -> always; false -> never end.
+test_a_ge_n() -> case a() >= n() of true -> always; false -> never end.
+test_a_ll_a() -> case a() < a() of true -> maybe; false -> maybe_too end.
+test_a_le_a() -> case a() =< a() of true -> maybe; false -> maybe_too end.
+test_a_gg_a() -> case a() > a() of true -> maybe; false -> maybe_too end.
+test_a_ge_a() -> case a() >= a() of true -> maybe; false -> maybe_too end.
+test_a_ll_t() -> case a() < t() of true -> always; false -> never end.
+test_a_le_t() -> case a() =< t() of true -> always; false -> never end.
+test_a_gg_t() -> case a() > t() of true -> never; false -> always end.
+test_a_ge_t() -> case a() >= t() of true -> never; false -> always end.
+test_a_ll_l() -> case a() < l() of true -> always; false -> never end.
+test_a_le_l() -> case a() =< l() of true -> always; false -> never end.
+test_a_gg_l() -> case a() > l() of true -> never; false -> always end.
+test_a_ge_l() -> case a() >= l() of true -> never; false -> always end.
+
+test_t_ll_i() -> case t() < i() of true -> never; false -> always end.
+test_t_le_i() -> case t() =< i() of true -> never; false -> always end.
+test_t_gg_i() -> case t() > i() of true -> always; false -> never end.
+test_t_ge_i() -> case t() >= i() of true -> always; false -> never end.
+test_t_ll_f() -> case t() < f() of true -> never; false -> always end.
+test_t_le_f() -> case t() =< f() of true -> never; false -> always end.
+test_t_gg_f() -> case t() > f() of true -> always; false -> never end.
+test_t_ge_f() -> case t() >= f() of true -> always; false -> never end.
+test_t_ll_n() -> case t() < n() of true -> never; false -> always end.
+test_t_le_n() -> case t() =< n() of true -> never; false -> always end.
+test_t_gg_n() -> case t() > n() of true -> always; false -> never end.
+test_t_ge_n() -> case t() >= n() of true -> always; false -> never end.
+test_t_ll_a() -> case t() < a() of true -> never; false -> always end.
+test_t_le_a() -> case t() =< a() of true -> never; false -> always end.
+test_t_gg_a() -> case t() > a() of true -> always; false -> never end.
+test_t_ge_a() -> case t() >= a() of true -> always; false -> never end.
+test_t_ll_t() -> case t() < t() of true -> maybe; false -> maybe_too end.
+test_t_le_t() -> case t() =< t() of true -> maybe; false -> maybe_too end.
+test_t_gg_t() -> case t() > t() of true -> maybe; false -> maybe_too end.
+test_t_ge_t() -> case t() >= t() of true -> maybe; false -> maybe_too end.
+test_t_ll_l() -> case t() < l() of true -> always; false -> never end.
+test_t_le_l() -> case t() =< l() of true -> always; false -> never end.
+test_t_gg_l() -> case t() > l() of true -> never; false -> always end.
+test_t_ge_l() -> case t() >= l() of true -> never; false -> always end.
+
+test_l_ll_i() -> case l() < i() of true -> never; false -> always end.
+test_l_le_i() -> case l() =< i() of true -> never; false -> always end.
+test_l_gg_i() -> case l() > i() of true -> always; false -> never end.
+test_l_ge_i() -> case l() >= i() of true -> always; false -> never end.
+test_l_ll_f() -> case l() < f() of true -> never; false -> always end.
+test_l_le_f() -> case l() =< f() of true -> never; false -> always end.
+test_l_gg_f() -> case l() > f() of true -> always; false -> never end.
+test_l_ge_f() -> case l() >= f() of true -> always; false -> never end.
+test_l_ll_n() -> case l() < n() of true -> never; false -> always end.
+test_l_le_n() -> case l() =< n() of true -> never; false -> always end.
+test_l_gg_n() -> case l() > n() of true -> always; false -> never end.
+test_l_ge_n() -> case l() >= n() of true -> always; false -> never end.
+test_l_ll_a() -> case l() < a() of true -> never; false -> always end.
+test_l_le_a() -> case l() =< a() of true -> never; false -> always end.
+test_l_gg_a() -> case l() > a() of true -> always; false -> never end.
+test_l_ge_a() -> case l() >= a() of true -> always; false -> never end.
+test_l_ll_t() -> case l() < t() of true -> never; false -> always end.
+test_l_le_t() -> case l() =< t() of true -> never; false -> always end.
+test_l_gg_t() -> case l() > t() of true -> always; false -> never end.
+test_l_ge_t() -> case l() >= t() of true -> always; false -> never end.
+test_l_ll_l() -> case l() < l() of true -> maybe; false -> maybe_too end.
+test_l_le_l() -> case l() =< l() of true -> maybe; false -> maybe_too end.
+test_l_gg_l() -> case l() > l() of true -> maybe; false -> maybe_too end.
+test_l_ge_l() -> case l() >= l() of true -> maybe; false -> maybe_too end.
+
+test_n_ll_na() -> case n() < na() of true -> maybe; false -> maybe_too end.
+test_n_le_na() -> case n() =< na() of true -> maybe; false -> maybe_too end.
+test_n_gg_na() -> case n() > na() of true -> maybe; false -> maybe_too end.
+test_n_ge_na() -> case n() >= na() of true -> maybe; false -> maybe_too end.
+test_n_ll_at() -> case n() < at() of true -> always; false -> never end.
+test_n_le_at() -> case n() =< at() of true -> always; false -> never end.
+test_n_gg_at() -> case n() > at() of true -> never; false -> always end.
+test_n_ge_at() -> case n() >= at() of true -> never; false -> always end.
+test_n_ll_tl() -> case n() < tl() of true -> always; false -> never end.
+test_n_le_tl() -> case n() =< tl() of true -> always; false -> never end.
+test_n_gg_tl() -> case n() > tl() of true -> never; false -> always end.
+test_n_ge_tl() -> case n() >= tl() of true -> never; false -> always end.
+
+test_a_ll_na() -> case a() < na() of true -> maybe; false -> maybe_too end.
+test_a_le_na() -> case a() =< na() of true -> maybe; false -> maybe_too end.
+test_a_gg_na() -> case a() > na() of true -> maybe; false -> maybe_too end.
+test_a_ge_na() -> case a() >= na() of true -> maybe; false -> maybe_too end.
+test_a_ll_at() -> case a() < at() of true -> maybe; false -> maybe_too end.
+test_a_le_at() -> case a() =< at() of true -> maybe; false -> maybe_too end.
+test_a_gg_at() -> case a() > at() of true -> maybe; false -> maybe_too end.
+test_a_ge_at() -> case a() >= at() of true -> maybe; false -> maybe_too end.
+test_a_ll_tl() -> case a() < tl() of true -> always; false -> never end.
+test_a_le_tl() -> case a() =< tl() of true -> always; false -> never end.
+test_a_gg_tl() -> case a() > tl() of true -> never; false -> always end.
+test_a_ge_tl() -> case a() >= tl() of true -> never; false -> always end.
+
+test_t_ll_na() -> case t() < na() of true -> never; false -> always end.
+test_t_le_na() -> case t() =< na() of true -> never; false -> always end.
+test_t_gg_na() -> case t() > na() of true -> always; false -> never end.
+test_t_ge_na() -> case t() >= na() of true -> always; false -> never end.
+test_t_ll_at() -> case t() < at() of true -> maybe; false -> maybe_too end.
+test_t_le_at() -> case t() =< at() of true -> maybe; false -> maybe_too end.
+test_t_gg_at() -> case t() > at() of true -> maybe; false -> maybe_too end.
+test_t_ge_at() -> case t() >= at() of true -> maybe; false -> maybe_too end.
+test_t_ll_tl() -> case t() < tl() of true -> maybe; false -> maybe_too end.
+test_t_le_tl() -> case t() =< tl() of true -> maybe; false -> maybe_too end.
+test_t_gg_tl() -> case t() > tl() of true -> maybe; false -> maybe_too end.
+test_t_ge_tl() -> case t() >= tl() of true -> maybe; false -> maybe_too end.
+
+test_l_ll_na() -> case l() < na() of true -> never; false -> always end.
+test_l_le_na() -> case l() =< na() of true -> never; false -> always end.
+test_l_gg_na() -> case l() > na() of true -> always; false -> never end.
+test_l_ge_na() -> case l() >= na() of true -> always; false -> never end.
+test_l_ll_at() -> case l() < at() of true -> never; false -> always end.
+test_l_le_at() -> case l() =< at() of true -> never; false -> always end.
+test_l_gg_at() -> case l() > at() of true -> always; false -> never end.
+test_l_ge_at() -> case l() >= at() of true -> always; false -> never end.
+test_l_ll_tl() -> case l() < tl() of true -> maybe; false -> maybe_too end.
+test_l_le_tl() -> case l() =< tl() of true -> maybe; false -> maybe_too end.
+test_l_gg_tl() -> case l() > tl() of true -> maybe; false -> maybe_too end.
+test_l_ge_tl() -> case l() >= tl() of true -> maybe; false -> maybe_too end.
+
+test_na_ll_n() -> case na() < n() of true -> maybe; false -> maybe_too end.
+test_na_le_n() -> case na() =< n() of true -> maybe; false -> maybe_too end.
+test_na_gg_n() -> case na() > n() of true -> maybe; false -> maybe_too end.
+test_na_ge_n() -> case na() >= n() of true -> maybe; false -> maybe_too end.
+test_na_ll_a() -> case na() < a() of true -> maybe; false -> maybe_too end.
+test_na_le_a() -> case na() =< a() of true -> maybe; false -> maybe_too end.
+test_na_gg_a() -> case na() > a() of true -> maybe; false -> maybe_too end.
+test_na_ge_a() -> case na() >= a() of true -> maybe; false -> maybe_too end.
+test_na_ll_t() -> case na() < t() of true -> always; false -> never end.
+test_na_le_t() -> case na() =< t() of true -> always; false -> never end.
+test_na_gg_t() -> case na() > t() of true -> never; false -> always end.
+test_na_ge_t() -> case na() >= t() of true -> never; false -> always end.
+test_na_ll_l() -> case na() < l() of true -> always; false -> never end.
+test_na_le_l() -> case na() =< l() of true -> always; false -> never end.
+test_na_gg_l() -> case na() > l() of true -> never; false -> always end.
+test_na_ge_l() -> case na() >= l() of true -> never; false -> always end.
+
+test_at_ll_n() -> case at() < n() of true -> never; false -> always end.
+test_at_le_n() -> case at() =< n() of true -> never; false -> always end.
+test_at_gg_n() -> case at() > n() of true -> always; false -> never end.
+test_at_ge_n() -> case at() >= n() of true -> always; false -> never end.
+test_at_ll_a() -> case at() < a() of true -> maybe; false -> maybe_too end.
+test_at_le_a() -> case at() =< a() of true -> maybe; false -> maybe_too end.
+test_at_gg_a() -> case at() > a() of true -> maybe; false -> maybe_too end.
+test_at_ge_a() -> case at() >= a() of true -> maybe; false -> maybe_too end.
+test_at_ll_t() -> case at() < t() of true -> maybe; false -> maybe_too end.
+test_at_le_t() -> case at() =< t() of true -> maybe; false -> maybe_too end.
+test_at_gg_t() -> case at() > t() of true -> maybe; false -> maybe_too end.
+test_at_ge_t() -> case at() >= t() of true -> maybe; false -> maybe_too end.
+test_at_ll_l() -> case at() < l() of true -> always; false -> never end.
+test_at_le_l() -> case at() =< l() of true -> always; false -> never end.
+test_at_gg_l() -> case at() > l() of true -> never; false -> always end.
+test_at_ge_l() -> case at() >= l() of true -> never; false -> always end.
+
+test_tl_ll_n() -> case tl() < n() of true -> never; false -> always end.
+test_tl_le_n() -> case tl() =< n() of true -> never; false -> always end.
+test_tl_gg_n() -> case tl() > n() of true -> always; false -> never end.
+test_tl_ge_n() -> case tl() >= n() of true -> always; false -> never end.
+test_tl_ll_a() -> case tl() < a() of true -> never; false -> always end.
+test_tl_le_a() -> case tl() =< a() of true -> never; false -> always end.
+test_tl_gg_a() -> case tl() > a() of true -> always; false -> never end.
+test_tl_ge_a() -> case tl() >= a() of true -> always; false -> never end.
+test_tl_ll_t() -> case tl() < t() of true -> maybe; false -> maybe_too end.
+test_tl_le_t() -> case tl() =< t() of true -> maybe; false -> maybe_too end.
+test_tl_gg_t() -> case tl() > t() of true -> maybe; false -> maybe_too end.
+test_tl_ge_t() -> case tl() >= t() of true -> maybe; false -> maybe_too end.
+test_tl_ll_l() -> case tl() < l() of true -> maybe; false -> maybe_too end.
+test_tl_le_l() -> case tl() =< l() of true -> maybe; false -> maybe_too end.
+test_tl_gg_l() -> case tl() > l() of true -> maybe; false -> maybe_too end.
+test_tl_ge_l() -> case tl() >= l() of true -> maybe; false -> maybe_too end.
+
+test_na_ll_na() -> case na() < na() of true -> maybe; false -> maybe_too end.
+test_na_le_na() -> case na() =< na() of true -> maybe; false -> maybe_too end.
+test_na_gg_na() -> case na() > na() of true -> maybe; false -> maybe_too end.
+test_na_ge_na() -> case na() >= na() of true -> maybe; false -> maybe_too end.
+test_na_ll_at() -> case na() < at() of true -> maybe; false -> maybe_too end.
+test_na_le_at() -> case na() =< at() of true -> maybe; false -> maybe_too end.
+test_na_gg_at() -> case na() > at() of true -> maybe; false -> maybe_too end.
+test_na_ge_at() -> case na() >= at() of true -> maybe; false -> maybe_too end.
+test_na_ll_tl() -> case na() < tl() of true -> always; false -> never end.
+test_na_le_tl() -> case na() =< tl() of true -> always; false -> never end.
+test_na_gg_tl() -> case na() > tl() of true -> never; false -> always end.
+test_na_ge_tl() -> case na() >= tl() of true -> never; false -> always end.
+
+test_at_ll_na() -> case at() < na() of true -> maybe; false -> maybe_too end.
+test_at_le_na() -> case at() =< na() of true -> maybe; false -> maybe_too end.
+test_at_gg_na() -> case at() > na() of true -> maybe; false -> maybe_too end.
+test_at_ge_na() -> case at() >= na() of true -> maybe; false -> maybe_too end.
+test_at_ll_at() -> case at() < at() of true -> maybe; false -> maybe_too end.
+test_at_le_at() -> case at() =< at() of true -> maybe; false -> maybe_too end.
+test_at_gg_at() -> case at() > at() of true -> maybe; false -> maybe_too end.
+test_at_ge_at() -> case at() >= at() of true -> maybe; false -> maybe_too end.
+test_at_ll_tl() -> case at() < tl() of true -> maybe; false -> maybe_too end.
+test_at_le_tl() -> case at() =< tl() of true -> maybe; false -> maybe_too end.
+test_at_gg_tl() -> case at() > tl() of true -> maybe; false -> maybe_too end.
+test_at_ge_tl() -> case at() >= tl() of true -> maybe; false -> maybe_too end.
+
+test_tl_ll_na() -> case tl() < na() of true -> never; false -> always end.
+test_tl_le_na() -> case tl() =< na() of true -> never; false -> always end.
+test_tl_gg_na() -> case tl() > na() of true -> always; false -> never end.
+test_tl_ge_na() -> case tl() >= na() of true -> always; false -> never end.
+test_tl_ll_at() -> case tl() < at() of true -> maybe; false -> maybe_too end.
+test_tl_le_at() -> case tl() =< at() of true -> maybe; false -> maybe_too end.
+test_tl_gg_at() -> case tl() > at() of true -> maybe; false -> maybe_too end.
+test_tl_ge_at() -> case tl() >= at() of true -> maybe; false -> maybe_too end.
+test_tl_ll_tl() -> case tl() < tl() of true -> maybe; false -> maybe_too end.
+test_tl_le_tl() -> case tl() =< tl() of true -> maybe; false -> maybe_too end.
+test_tl_gg_tl() -> case tl() > tl() of true -> maybe; false -> maybe_too end.
+test_tl_ge_tl() -> case tl() >= tl() of true -> maybe; false -> maybe_too end.
diff --git a/lib/dialyzer/test/small_SUITE_data/src/failing_funs.erl b/lib/dialyzer/test/small_SUITE_data/src/failing_funs.erl
new file mode 100644
index 0000000000..1784c4a494
--- /dev/null
+++ b/lib/dialyzer/test/small_SUITE_data/src/failing_funs.erl
@@ -0,0 +1,250 @@
+-module(failing_funs).
+
+-compile(export_all).
+
+% Crashes with system call. No spec.
+foo1() -> halt().
+
+% Crashes with system call. With spec.
+-spec foo2() -> no_return().
+foo2() -> halt().
+
+% Crashes on its own. No spec.
+foo3() -> case a of b -> ok end.
+
+% Crashes on its own. With spec.
+-spec foo4() -> no_return().
+foo4() -> case a of b -> ok end.
+
+% Creates fun that crashes with system call. No spec.
+foo5() -> fun() -> halt() end.
+
+% Creates fun that crashes with system call. With spec.
+-spec foo6() -> fun(() -> no_return()).
+foo6() -> fun() -> halt() end.
+
+% Creates fun from named fun that will crash. Neither have spec.
+foo7() -> fun foo1/0.
+
+% Creates fun from named fun that will crash. Has spec.
+-spec foo8() -> fun(() -> no_return()).
+foo8() -> fun foo1/0.
+
+% Creates fun from named fun that will crash. Named has spec.
+foo9() -> fun foo2/0.
+
+% Creates fun from named fun that will crash. Both have specs.
+-spec foo10() -> fun(() -> no_return()).
+foo10() -> fun foo2/0.
+
+% Creates fun from named fun that will crash. Neither have spec.
+foo11() -> fun foo3/0.
+
+% Creates fun from named fun that will crash. Has spec.
+-spec foo12() -> fun(() -> no_return()).
+foo12() -> fun foo3/0.
+
+% Creates fun from named fun that will crash. Named has spec.
+foo13() -> fun foo4/0.
+
+% Creates fun from named fun that will crash. Both have specs.
+-spec foo14() -> fun(() -> no_return()).
+foo14() -> fun foo4/0.
+
+% Creates fun calling a named fun that will crash. Neither have spec.
+foo15() -> fun() -> foo1() end.
+
+% Creates fun calling a named fun that will crash. Has spec.
+-spec foo16() -> fun(() -> no_return()).
+foo16() -> fun() -> foo1() end.
+
+% Creates fun calling a named fun that will crash. Named has spec.
+foo17() -> fun() -> foo2() end.
+
+% Creates fun calling a named fun that will crash. Both have specs.
+-spec foo18() -> fun(() -> no_return()).
+foo18() -> fun() -> foo2() end.
+
+% Creates fun calling a named fun that will crash. Neither have spec.
+foo19() -> fun() -> foo3() end.
+
+% Creates fun calling a named fun that will crash. Has spec.
+-spec foo20() -> fun(() -> no_return()).
+foo20() -> fun() -> foo3() end.
+
+% Creates fun calling a named fun that will crash. Named has spec.
+foo21() -> fun() -> foo4() end.
+
+% Creates fun calling a named fun that will crash. Both have specs.
+-spec foo22() -> fun(() -> no_return()).
+foo22() -> fun() -> foo4() end.
+
+% Creates two funs with no local return and will return one or die. No spec.
+foo23() ->
+ Bomb = fun() -> halt() end,
+ case get(42) of
+ a -> Bomb();
+ b -> fun() -> halt() end
+ end.
+
+% Creates two funs with no local return and will return one or die. With spec.
+-spec foo24() -> fun(() -> no_return()).
+foo24() ->
+ Bomb = fun() -> halt() end,
+ case get(42) of
+ a -> Bomb();
+ b -> fun() -> halt() end
+ end.
+
+% Creates two funs with no local return and will return one or die. No spec.
+foo25() ->
+ Bomb = fun() -> foo1() end,
+ case get(42) of
+ a -> Bomb();
+ b -> fun() -> foo1() end
+ end.
+
+% Creates two funs with no local return and will return one or die. With spec.
+-spec foo26() -> fun(() -> no_return()).
+foo26() ->
+ Bomb = fun foo1/0,
+ case get(42) of
+ a -> Bomb();
+ b -> fun foo1/0
+ end.
+
+% Creates two funs with no local return and will return one or die. No spec.
+foo27() ->
+ Bomb = fun foo1/0,
+ case get(42) of
+ a -> Bomb();
+ b -> fun foo1/0
+ end.
+
+% Creates two funs with no local return and will return one or die. With spec.
+-spec foo28() -> fun(() -> no_return()).
+foo28() ->
+ Bomb = fun() -> foo1() end,
+ case get(42) of
+ a -> Bomb();
+ b -> fun() -> foo1() end
+ end.
+
+% Creates two funs with no local return and will return one or die. No spec.
+foo29() ->
+ Bomb = fun() -> foo2() end,
+ case get(42) of
+ a -> Bomb();
+ b -> fun() -> foo2() end
+ end.
+
+% Creates two funs with no local return and will return one or die. With spec.
+-spec foo30() -> fun(() -> no_return()).
+foo30() ->
+ Bomb = fun foo2/0,
+ case get(42) of
+ a -> Bomb();
+ b -> fun foo2/0
+ end.
+
+% Creates two funs with no local return and will return one or die. No spec.
+foo31() ->
+ Bomb = fun foo2/0,
+ case get(42) of
+ a -> Bomb();
+ b -> fun foo2/0
+ end.
+
+% Creates two funs with no local return and will return one or die. With spec.
+-spec foo32() -> fun(() -> no_return()).
+foo32() ->
+ Bomb = fun() -> foo2() end,
+ case get(42) of
+ a -> Bomb();
+ b -> fun() -> foo2() end
+ end.
+
+% Creates two funs with no local return and will return one or die. No spec.
+foo33() ->
+ Bomb = fun() -> foo3() end,
+ case get(42) of
+ a -> Bomb();
+ b -> fun() -> foo3() end
+ end.
+
+% Creates two funs with no local return and will return one or die. With spec.
+-spec foo34() -> fun(() -> no_return()).
+foo34() ->
+ Bomb = fun foo3/0,
+ case get(42) of
+ a -> Bomb();
+ b -> fun foo3/0
+ end.
+
+% Creates two funs with no local return and will return one or die. No spec.
+foo35() ->
+ Bomb = fun foo3/0,
+ case get(42) of
+ a -> Bomb();
+ b -> fun foo3/0
+ end.
+
+% Creates two funs with no local return and will return one or die. With spec.
+-spec foo36() -> fun(() -> no_return()).
+foo36() ->
+ Bomb = fun() -> foo3() end,
+ case get(42) of
+ a -> Bomb();
+ b -> fun() -> foo3() end
+ end.
+
+% Creates two funs with no local return and will return one or die. No spec.
+foo37() ->
+ Bomb = fun() -> foo4() end,
+ case get(42) of
+ a -> Bomb();
+ b -> fun() -> foo4() end
+ end.
+
+% Creates two funs with no local return and will return one or die. With spec.
+-spec foo38() -> fun(() -> no_return()).
+foo38() ->
+ Bomb = fun foo4/0,
+ case get(42) of
+ a -> Bomb();
+ b -> fun foo4/0
+ end.
+
+% Creates two funs with no local return and will return one or die. No spec.
+foo39() ->
+ Bomb = fun foo4/0,
+ case get(42) of
+ a -> Bomb();
+ b -> fun foo4/0
+ end.
+
+% Creates two funs with no local return and will return one or die. With spec.
+-spec foo40() -> fun(() -> no_return()).
+foo40() ->
+ Bomb = fun() -> foo4() end,
+ case get(42) of
+ a -> Bomb();
+ b -> fun() -> foo4() end
+ end.
+
+% Obtains two funs with no local return and will return one or die. No spec.
+foo41() ->
+ Bomb = foo5(),
+ case get(42) of
+ a -> Bomb();
+ b -> foo5()
+ end.
+
+% Obtains two funs with no local return and will return one or die. With spec.
+-spec foo42() -> fun(() -> no_return()).
+foo42() ->
+ Bomb = foo5(),
+ case get(42) of
+ a -> Bomb();
+ b -> foo5()
+ end.
diff --git a/lib/dialyzer/test/small_SUITE_data/src/file_open_encoding.erl b/lib/dialyzer/test/small_SUITE_data/src/file_open_encoding.erl
index 4f1268eba8..086df3464b 100644
--- a/lib/dialyzer/test/small_SUITE_data/src/file_open_encoding.erl
+++ b/lib/dialyzer/test/small_SUITE_data/src/file_open_encoding.erl
@@ -6,9 +6,7 @@
-export([parse/1]).
--type proplist() :: [{atom(), any()}].
-
--spec parse(string()) -> proplist().
+-spec parse(string()) -> proplists:proplist().
parse(FileName) ->
{ok, IoDevice} = file:open(FileName, [read, binary, {encoding, utf8}]),
do_parse(IoDevice, []).
diff --git a/lib/dialyzer/test/small_SUITE_data/src/list_to_bitstring.erl b/lib/dialyzer/test/small_SUITE_data/src/list_to_bitstring.erl
new file mode 100644
index 0000000000..109aa88f16
--- /dev/null
+++ b/lib/dialyzer/test/small_SUITE_data/src/list_to_bitstring.erl
@@ -0,0 +1,21 @@
+%%=====================================================================
+%% From: Ken Robinson
+%% Date: 28/04/2011, 17:26
+%%
+%% Program that produced bogus "Function has no local return" warnings
+%% due to erlang:list_to_bitstring/1 having erroneous hard coded type
+%% information, namely accepting iolist() instead of bitstrlist().
+%% Fixed 29/04/2011.
+%%=====================================================================
+
+-module(list_to_bitstring).
+
+-export([l2bs/0, l2bs_ok/0]).
+
+%% This function was producing a warning
+l2bs() ->
+ erlang:list_to_bitstring([<<42>>, <<42:13>>]).
+
+%% while this one was ok.
+l2bs_ok() ->
+ erlang:list_to_bitstring([<<42>>, <<42,42>>]).
diff --git a/lib/dialyzer/test/small_SUITE_data/src/no_return_bug.erl b/lib/dialyzer/test/small_SUITE_data/src/no_return_bug.erl
new file mode 100644
index 0000000000..5c24902590
--- /dev/null
+++ b/lib/dialyzer/test/small_SUITE_data/src/no_return_bug.erl
@@ -0,0 +1,42 @@
+%% Dialyzer couldn't infer that monitor_diskspace would go in an infinite loop
+%% instead of crashing due to the existence of list comprehensions that have a
+%% normal success typing. These were added to the monitor_diskspace's SCC and
+%% dialyzer_typesig didn't try to assign unit() to monitor_diskspace, as it
+%% required all the members of the SCC to return none().
+%%
+%% Testcase was submitted in erlang-questions mailing list by Prashanth Mundkur
+%% (http://erlang.org/pipermail/erlang-questions/2011-May/058063.html)
+
+-module(no_return_bug).
+-export([diskspace/1, monitor_diskspace/2, refresh_tags/1, monitor_launch/0]).
+
+-type diskinfo() :: {non_neg_integer(), non_neg_integer()}.
+
+-spec diskspace(nonempty_string()) -> {'ok', diskinfo()} | {'error', term()}.
+diskspace(Path) ->
+ case Path of
+ "a" -> {ok, {0,0}};
+ _ -> {error, error}
+ end.
+
+-spec monitor_diskspace(nonempty_string(),
+ [{diskinfo(), nonempty_string()}]) ->
+ no_return().
+monitor_diskspace(Root, Vols) ->
+ Df = fun(VolName) ->
+ diskspace(filename:join([Root, VolName]))
+ end,
+ NewVols = [{Space, VolName}
+ || {VolName, {ok, Space}}
+ <- [{VolName, Df(VolName)}
+ || {_OldSpace, VolName} <- Vols]],
+ monitor_diskspace(Root, NewVols).
+
+-spec refresh_tags(nonempty_string()) -> no_return().
+refresh_tags(Root) ->
+ {ok, _} = diskspace(Root),
+ refresh_tags(Root).
+
+monitor_launch() ->
+ spawn_link(fun() -> refresh_tags("abc") end),
+ spawn_link(fun() -> monitor_diskspace("root", [{{0,0}, "a"}]) end).
diff --git a/lib/dialyzer/test/small_SUITE_data/src/nowarnunused.erl b/lib/dialyzer/test/small_SUITE_data/src/nowarnunused.erl
new file mode 100644
index 0000000000..63daeee9e3
--- /dev/null
+++ b/lib/dialyzer/test/small_SUITE_data/src/nowarnunused.erl
@@ -0,0 +1,7 @@
+-module(nowarnunused).
+
+-compile({nowarn_unused_function, return_error/2}).
+
+-spec return_error(integer(), any()) -> no_return().
+return_error(Line, Message) ->
+ throw({error, {Line, ?MODULE, Message}}).
diff --git a/lib/dialyzer/test/small_SUITE_data/src/rebar_no_return.erl b/lib/dialyzer/test/small_SUITE_data/src/rebar_no_return.erl
new file mode 100644
index 0000000000..d3b504ae04
--- /dev/null
+++ b/lib/dialyzer/test/small_SUITE_data/src/rebar_no_return.erl
@@ -0,0 +1,19 @@
+-module(rebar_no_return).
+
+-export([t/0]).
+
+-spec t() -> no_return().
+t() ->
+ F = log_and_halt("baz"),
+ F("foo", 123).
+
+-spec log_and_halt(string()) -> fun((string(),integer()) -> no_return()).
+log_and_halt(Msg) ->
+ fun(_, _) ->
+ abort(Msg)
+ end.
+
+-spec abort(string()) -> no_return().
+abort(Msg) ->
+ io:format("~s~n", [Msg]),
+ halt(1).