aboutsummaryrefslogtreecommitdiffstats
path: root/lib/dialyzer/src
diff options
context:
space:
mode:
Diffstat (limited to 'lib/dialyzer/src')
-rw-r--r--lib/dialyzer/src/dialyzer.erl4
-rw-r--r--lib/dialyzer/src/dialyzer_cl.erl2
-rw-r--r--lib/dialyzer/src/dialyzer_cl_parse.erl4
-rw-r--r--lib/dialyzer/src/dialyzer_codeserver.erl8
-rw-r--r--lib/dialyzer/src/dialyzer_contracts.erl227
-rw-r--r--lib/dialyzer/src/dialyzer_dataflow.erl45
-rw-r--r--lib/dialyzer/src/dialyzer_gui_wx.erl4
-rw-r--r--lib/dialyzer/src/dialyzer_plt.erl20
-rw-r--r--lib/dialyzer/src/dialyzer_races.erl66
-rw-r--r--lib/dialyzer/src/dialyzer_typesig.erl10
-rw-r--r--lib/dialyzer/src/dialyzer_utils.erl123
-rw-r--r--lib/dialyzer/src/typer.erl6
12 files changed, 272 insertions, 247 deletions
diff --git a/lib/dialyzer/src/dialyzer.erl b/lib/dialyzer/src/dialyzer.erl
index 1538174d4a..185c8c9ae6 100644
--- a/lib/dialyzer/src/dialyzer.erl
+++ b/lib/dialyzer/src/dialyzer.erl
@@ -409,6 +409,10 @@ message_to_string({extra_range, [M, F, A, ExtraRanges, SigRange]}) ->
io_lib:format("The specification for ~w:~tw/~w states that the function"
" might also return ~ts but the inferred return is ~ts\n",
[M, F, A, ExtraRanges, SigRange]);
+message_to_string({missing_range, [M, F, A, ExtraRanges, ContrRange]}) ->
+ io_lib:format("The success typing for ~w:~tw/~w implies that the function"
+ " might also return ~ts but the specification return is ~ts\n",
+ [M, F, A, ExtraRanges, ContrRange]);
message_to_string({overlapping_contract, [M, F, A]}) ->
io_lib:format("Overloaded contract for ~w:~tw/~w has overlapping domains;"
" such contracts are currently unsupported and are simply ignored\n",
diff --git a/lib/dialyzer/src/dialyzer_cl.erl b/lib/dialyzer/src/dialyzer_cl.erl
index 0617be6435..1e06d6e974 100644
--- a/lib/dialyzer/src/dialyzer_cl.erl
+++ b/lib/dialyzer/src/dialyzer_cl.erl
@@ -672,7 +672,7 @@ failed_anal_msg(Reason, LogCache) ->
%%
format_log_cache(LogCache) ->
Str = lists:append(lists:reverse(LogCache)),
- string:join(string:tokens(Str, "\n"), "\n ").
+ lists:join("\n ", string:lexemes(Str, "\n")).
-spec store_warnings(#cl_state{}, [raw_warning()]) -> #cl_state{}.
diff --git a/lib/dialyzer/src/dialyzer_cl_parse.erl b/lib/dialyzer/src/dialyzer_cl_parse.erl
index 80c10183cf..f21eaed087 100644
--- a/lib/dialyzer/src/dialyzer_cl_parse.erl
+++ b/lib/dialyzer/src/dialyzer_cl_parse.erl
@@ -41,8 +41,8 @@ start() ->
Ret
catch
throw:{dialyzer_cl_parse_error, Msg} -> {error, Msg};
- _:R ->
- Msg = io_lib:format("~tp\n~tp\n", [R, erlang:get_stacktrace()]),
+ _:R:S ->
+ Msg = io_lib:format("~tp\n~tp\n", [R, S]),
{error, lists:flatten(Msg)}
end.
diff --git a/lib/dialyzer/src/dialyzer_codeserver.erl b/lib/dialyzer/src/dialyzer_codeserver.erl
index 5587cf2bdf..c4e3c322e5 100644
--- a/lib/dialyzer/src/dialyzer_codeserver.erl
+++ b/lib/dialyzer/src/dialyzer_codeserver.erl
@@ -347,13 +347,11 @@ get_file_contract(Key, ContDict) ->
lookup_mfa_contract(MFA, #codeserver{contracts = ContDict}) ->
ets_dict_find(MFA, ContDict).
--spec lookup_meta_info(module() | mfa(), codeserver()) -> meta_info().
+-spec lookup_meta_info(module() | mfa(), codeserver()) ->
+ {'ok', meta_info()} | 'error'.
lookup_meta_info(MorMFA, #codeserver{fun_meta_info = FunMetaInfo}) ->
- case ets_dict_find(MorMFA, FunMetaInfo) of
- error -> [];
- {ok, PropList} -> PropList
- end.
+ ets_dict_find(MorMFA, FunMetaInfo).
-spec get_contracts(codeserver()) ->
dict:dict(mfa(), dialyzer_contracts:file_contract()).
diff --git a/lib/dialyzer/src/dialyzer_contracts.erl b/lib/dialyzer/src/dialyzer_contracts.erl
index e72c1aecfc..9c36d745c3 100644
--- a/lib/dialyzer/src/dialyzer_contracts.erl
+++ b/lib/dialyzer/src/dialyzer_contracts.erl
@@ -25,7 +25,7 @@
%% get_contract_signature/1,
is_overloaded/1,
process_contract_remote_types/1,
- store_tmp_contract/5]).
+ store_tmp_contract/6]).
-export_type([file_contract/0, plt_contracts/0]).
@@ -146,18 +146,18 @@ process_contract_remote_types(CodeServer) ->
Mods = dialyzer_codeserver:all_temp_modules(CodeServer),
RecordTable = dialyzer_codeserver:get_records_table(CodeServer),
ExpTypes = dialyzer_codeserver:get_exported_types(CodeServer),
- ContractFun =
- fun({{_M, _F, _A}=MFA, {File, TmpContract, Xtra}}, C0) ->
- #tmp_contract{contract_funs = CFuns, forms = Forms} = TmpContract,
- {NewCs, C2} = lists:mapfoldl(fun(CFun, C1) ->
- CFun(ExpTypes, RecordTable, C1)
- end, C0, CFuns),
- Args = general_domain(NewCs),
- Contract = #contract{contracts = NewCs, args = Args, forms = Forms},
- {{MFA, {File, Contract, Xtra}}, C2}
- end,
ModuleFun =
fun(ModuleName) ->
+ ContractFun =
+ fun({MFA, {File, TmpContract, Xtra}}, C0) ->
+ #tmp_contract{contract_funs = CFuns, forms = Forms} = TmpContract,
+ {NewCs, C2} = lists:mapfoldl(fun(CFun, C1) ->
+ CFun(ExpTypes, RecordTable, C1)
+ end, C0, CFuns),
+ Args = general_domain(NewCs),
+ Contract = #contract{contracts = NewCs, args = Args, forms = Forms},
+ {{MFA, {File, Contract, Xtra}}, C2}
+ end,
Cache = erl_types:cache__new(),
{ContractMap, CallbackMap} =
dialyzer_codeserver:get_temp_contracts(ModuleName, CodeServer),
@@ -197,6 +197,12 @@ check_contracts(Contracts, Callgraph, FunTypes, ModOpaques) ->
false ->
[{MFA, Contract}|NewContracts]
end;
+ {range_warnings, _} ->
+ %% do not treat extra range, either in contract or
+ %% in success typing, as an error in this check
+ %% since that prevents discovering other actual
+ %% errors
+ [{MFA, Contract}|NewContracts];
{error, _Error} -> NewContracts
end;
error -> NewContracts
@@ -206,14 +212,26 @@ check_contracts(Contracts, Callgraph, FunTypes, ModOpaques) ->
end,
orddict:from_list(lists:foldl(FoldFun, [], orddict:to_list(FunTypes))).
+-type check_contract_return() ::
+ 'ok'
+ | {'error',
+ 'invalid_contract'
+ | {'opaque_mismatch', erl_types:erl_type()}
+ | {'overlapping_contract', [module() | atom() | byte()]}
+ | string()}
+ | {'range_warnings',
+ [{'error', {'extra_range' | 'missing_range',
+ erl_types:erl_type(),
+ erl_types:erl_type()}}]}.
+
%% Checks all components of a contract
--spec check_contract(#contract{}, erl_types:erl_type()) -> 'ok' | {'error', term()}.
+-spec check_contract(#contract{}, erl_types:erl_type()) -> check_contract_return().
check_contract(Contract, SuccType) ->
check_contract(Contract, SuccType, 'universe').
-spec check_contract(#contract{}, erl_types:erl_type(), erl_types:opaques()) ->
- 'ok' | {'error', term()}.
+ check_contract_return().
check_contract(#contract{contracts = Contracts}, SuccType, Opaques) ->
try
@@ -286,15 +304,23 @@ check_contract_inf_list([], _SuccType, _Opaques, OM) ->
check_extraneous([], _SuccType) -> ok;
check_extraneous([C|Cs], SuccType) ->
case check_extraneous_1(C, SuccType) of
- ok -> check_extraneous(Cs, SuccType);
- Error -> Error
+ {error, invalid_contract} = Error ->
+ Error;
+ {error, {extra_range, _, _}} = Error ->
+ {range_warnings, [Error | check_missing(C, SuccType)]};
+ ok ->
+ case check_missing(C, SuccType) of
+ [] -> check_extraneous(Cs, SuccType);
+ ErrorL -> {range_warnings, ErrorL}
+ end
end.
check_extraneous_1(Contract, SuccType) ->
CRng = erl_types:t_fun_range(Contract),
CRngs = erl_types:t_elements(CRng),
STRng = erl_types:t_fun_range(SuccType),
- ?debug("CR = ~tp\nSR = ~tp\n", [CRngs, STRng]),
+ ?debug("\nCR = ~ts\nSR = ~ts\n", [erl_types:t_to_string(CRng),
+ erl_types:t_to_string(STRng)]),
case [CR || CR <- CRngs,
erl_types:t_is_none(erl_types:t_inf(CR, STRng))] of
[] ->
@@ -337,6 +363,18 @@ map_part(Type) ->
is_empty_map(Type) ->
erl_types:t_is_equal(Type, erl_types:t_from_term(#{})).
+check_missing(Contract, SuccType) ->
+ CRng = erl_types:t_fun_range(Contract),
+ STRng = erl_types:t_fun_range(SuccType),
+ STRngs = erl_types:t_elements(STRng),
+ ?debug("\nCR = ~ts\nSR = ~ts\n", [erl_types:t_to_string(CRng),
+ erl_types:t_to_string(STRng)]),
+ case [STR || STR <- STRngs,
+ erl_types:t_is_none(erl_types:t_inf(STR, CRng))] of
+ [] -> [];
+ STRs -> [{error, {missing_range, erl_types:t_sup(STRs), CRng}}]
+ end.
+
%% This is the heart of the "range function"
-spec process_contracts([contract_pair()], [erl_types:erl_type()]) ->
erl_types:erl_type().
@@ -436,26 +474,29 @@ insert_constraints([], Map) -> Map.
-type spec_data() :: {TypeSpec :: [_], Xtra:: [_]}.
--spec store_tmp_contract(mfa(), file_line(), spec_data(), contracts(), types()) ->
- contracts().
+-spec store_tmp_contract(module(), mfa(), file_line(), spec_data(),
+ contracts(), types()) -> contracts().
-store_tmp_contract(MFA, FileLine, {TypeSpec, Xtra}, SpecMap, RecordsDict) ->
+store_tmp_contract(Module, MFA, FileLine, {TypeSpec, Xtra}, SpecMap,
+ RecordsDict) ->
%% io:format("contract from form: ~tp\n", [TypeSpec]),
- TmpContract = contract_from_form(TypeSpec, MFA, RecordsDict, FileLine),
+ TmpContract = contract_from_form(TypeSpec, Module, MFA, RecordsDict, FileLine),
%% io:format("contract: ~tp\n", [TmpContract]),
maps:put(MFA, {FileLine, TmpContract, Xtra}, SpecMap).
-contract_from_form(Forms, MFA, RecDict, FileLine) ->
- {CFuns, Forms1} = contract_from_form(Forms, MFA, RecDict, FileLine, [], []),
+contract_from_form(Forms, Module, MFA, RecDict, FileLine) ->
+ {CFuns, Forms1} =
+ contract_from_form(Forms, Module, MFA, RecDict, FileLine, [], []),
#tmp_contract{contract_funs = CFuns, forms = Forms1}.
-contract_from_form([{type, _, 'fun', [_, _]} = Form | Left], MFA, RecDict,
- FileLine, TypeAcc, FormAcc) ->
+contract_from_form([{type, _, 'fun', [_, _]} = Form | Left], Module, MFA,
+ RecDict, FileLine, TypeAcc, FormAcc) ->
TypeFun =
fun(ExpTypes, RecordTable, Cache) ->
{NewType, NewCache} =
try
- from_form_with_check(Form, ExpTypes, MFA, RecordTable, Cache)
+ from_form_with_check(Form, ExpTypes, Module, MFA, RecordTable,
+ Cache)
catch
throw:{error, Msg} ->
{File, Line} = FileLine,
@@ -468,68 +509,74 @@ contract_from_form([{type, _, 'fun', [_, _]} = Form | Left], MFA, RecDict,
end,
NewTypeAcc = [TypeFun | TypeAcc],
NewFormAcc = [{Form, []} | FormAcc],
- contract_from_form(Left, MFA, RecDict, FileLine, NewTypeAcc, NewFormAcc);
+ contract_from_form(Left, Module, MFA, RecDict, FileLine, NewTypeAcc,
+ NewFormAcc);
contract_from_form([{type, _L1, bounded_fun,
[{type, _L2, 'fun', [_, _]} = Form, Constr]}| Left],
- MFA, RecDict, FileLine, TypeAcc, FormAcc) ->
+ Module, MFA, RecDict, FileLine, TypeAcc, FormAcc) ->
TypeFun =
fun(ExpTypes, RecordTable, Cache) ->
{Constr1, VarTable, Cache1} =
- process_constraints(Constr, MFA, RecDict, ExpTypes, RecordTable,
- Cache),
+ process_constraints(Constr, Module, MFA, RecDict, ExpTypes,
+ RecordTable, Cache),
{NewType, NewCache} =
- from_form_with_check(Form, ExpTypes, MFA, RecordTable,
+ from_form_with_check(Form, ExpTypes, Module, MFA, RecordTable,
VarTable, Cache1),
NewTypeNoVars = erl_types:subst_all_vars_to_any(NewType),
{{NewTypeNoVars, Constr1}, NewCache}
end,
NewTypeAcc = [TypeFun | TypeAcc],
NewFormAcc = [{Form, Constr} | FormAcc],
- contract_from_form(Left, MFA, RecDict, FileLine, NewTypeAcc, NewFormAcc);
-contract_from_form([], _MFA, _RecDict, _FileLine, TypeAcc, FormAcc) ->
+ contract_from_form(Left, Module, MFA, RecDict, FileLine, NewTypeAcc,
+ NewFormAcc);
+contract_from_form([], _Mod, _MFA, _RecDict, _FileLine, TypeAcc, FormAcc) ->
{lists:reverse(TypeAcc), lists:reverse(FormAcc)}.
-process_constraints(Constrs, MFA, RecDict, ExpTypes, RecordTable, Cache) ->
- {Init0, NewCache} = initialize_constraints(Constrs, MFA, RecDict, ExpTypes,
- RecordTable, Cache),
+process_constraints(Constrs, Module, MFA, RecDict, ExpTypes, RecordTable,
+ Cache) ->
+ {Init0, NewCache} = initialize_constraints(Constrs, Module, MFA, RecDict,
+ ExpTypes, RecordTable, Cache),
Init = remove_cycles(Init0),
- constraints_fixpoint(Init, MFA, RecDict, ExpTypes, RecordTable, NewCache).
+ constraints_fixpoint(Init, Module, MFA, RecDict, ExpTypes, RecordTable,
+ NewCache).
-initialize_constraints(Constrs, MFA, RecDict, ExpTypes, RecordTable, Cache) ->
- initialize_constraints(Constrs, MFA, RecDict, ExpTypes, RecordTable,
+initialize_constraints(Constrs, Module, MFA, RecDict, ExpTypes, RecordTable,
+ Cache) ->
+ initialize_constraints(Constrs, Module, MFA, RecDict, ExpTypes, RecordTable,
Cache, []).
-initialize_constraints([], _MFA, _RecDict, _ExpTypes, _RecordTable,
+initialize_constraints([], _Module, _MFA, _RecDict, _ExpTypes, _RecordTable,
Cache, Acc) ->
{Acc, Cache};
-initialize_constraints([Constr|Rest], MFA, RecDict, ExpTypes, RecordTable,
- Cache, Acc) ->
+initialize_constraints([Constr|Rest], Module, MFA, RecDict, ExpTypes,
+ RecordTable, Cache, Acc) ->
case Constr of
{type, _, constraint, [{atom, _, is_subtype}, [Type1, Type2]]} ->
VarTable = erl_types:var_table__new(),
{T1, NewCache} =
- final_form(Type1, ExpTypes, MFA, RecordTable, VarTable, Cache),
+ final_form(Type1, ExpTypes, Module, MFA, RecordTable, VarTable, Cache),
Entry = {T1, Type2},
- initialize_constraints(Rest, MFA, RecDict, ExpTypes, RecordTable,
- NewCache, [Entry|Acc]);
+ initialize_constraints(Rest, Module, MFA, RecDict, ExpTypes,
+ RecordTable, NewCache, [Entry|Acc]);
{type, _, constraint, [{atom,_,Name}, List]} ->
N = length(List),
throw({error,
io_lib:format("Unsupported type guard ~tw/~w\n", [Name, N])})
end.
-constraints_fixpoint(Constrs, MFA, RecDict, ExpTypes, RecordTable, Cache) ->
+constraints_fixpoint(Constrs, Module, MFA, RecDict, ExpTypes, RecordTable,
+ Cache) ->
VarTable = erl_types:var_table__new(),
{VarTab, NewCache} =
- constraints_to_dict(Constrs, MFA, RecDict, ExpTypes, RecordTable,
+ constraints_to_dict(Constrs, Module, MFA, RecDict, ExpTypes, RecordTable,
VarTable, Cache),
- constraints_fixpoint(VarTab, MFA, Constrs, RecDict, ExpTypes,
+ constraints_fixpoint(VarTab, Module, MFA, Constrs, RecDict, ExpTypes,
RecordTable, NewCache).
-constraints_fixpoint(OldVarTab, MFA, Constrs, RecDict, ExpTypes,
+constraints_fixpoint(OldVarTab, Module, MFA, Constrs, RecDict, ExpTypes,
RecordTable, Cache) ->
{NewVarTab, NewCache} =
- constraints_to_dict(Constrs, MFA, RecDict, ExpTypes, RecordTable,
+ constraints_to_dict(Constrs, Module, MFA, RecDict, ExpTypes, RecordTable,
OldVarTab, Cache),
case NewVarTab of
OldVarTab ->
@@ -540,19 +587,23 @@ constraints_fixpoint(OldVarTab, MFA, Constrs, RecDict, ExpTypes,
FinalConstrs = maps:fold(Fun, [], NewVarTab),
{FinalConstrs, NewVarTab, NewCache};
_Other ->
- constraints_fixpoint(NewVarTab, MFA, Constrs, RecDict, ExpTypes,
+ constraints_fixpoint(NewVarTab, Module, MFA, Constrs, RecDict, ExpTypes,
RecordTable, NewCache)
end.
-final_form(Form, ExpTypes, MFA, RecordTable, VarTable, Cache) ->
- from_form_with_check(Form, ExpTypes, MFA, RecordTable, VarTable, Cache).
+final_form(Form, ExpTypes, Module, MFA, RecordTable, VarTable, Cache) ->
+ from_form_with_check(Form, ExpTypes, Module, MFA, RecordTable, VarTable,
+ Cache).
-from_form_with_check(Form, ExpTypes, MFA, RecordTable, Cache) ->
+from_form_with_check(Form, ExpTypes, Module, MFA, RecordTable, Cache) ->
VarTable = erl_types:var_table__new(),
- from_form_with_check(Form, ExpTypes, MFA, RecordTable, VarTable, Cache).
+ from_form_with_check(Form, ExpTypes, Module, MFA, RecordTable, VarTable,
+ Cache).
-from_form_with_check(Form, ExpTypes, MFA, RecordTable, VarTable, Cache) ->
- Site = {spec, MFA},
+from_form_with_check(Form, ExpTypes, Module, MFA, RecordTable, VarTable,
+ Cache) ->
+ {_, F, A} = MFA,
+ Site = {spec, {Module, F, A}},
C1 = erl_types:t_check_record_fields(Form, ExpTypes, Site, RecordTable,
VarTable, Cache),
%% The check costs some time, and with the assumption that contracts
@@ -560,22 +611,22 @@ from_form_with_check(Form, ExpTypes, MFA, RecordTable, VarTable, Cache) ->
%% erl_types:t_from_form_check_remote(Form, ExpTypes, MFA, RecordTable),
erl_types:t_from_form(Form, ExpTypes, Site, RecordTable, VarTable, C1).
-constraints_to_dict(Constrs, MFA, RecDict, ExpTypes, RecordTable,
+constraints_to_dict(Constrs, Module, MFA, RecDict, ExpTypes, RecordTable,
VarTab, Cache) ->
{Subtypes, NewCache} =
- constraints_to_subs(Constrs, MFA, RecDict, ExpTypes, RecordTable,
+ constraints_to_subs(Constrs, Module, MFA, RecDict, ExpTypes, RecordTable,
VarTab, Cache, []),
{insert_constraints(Subtypes), NewCache}.
-constraints_to_subs([], _MFA, _RecDict, _ExpTypes, _RecordTable,
+constraints_to_subs([], _Module, _MFA, _RecDict, _ExpTypes, _RecordTable,
_VarTab, Cache, Acc) ->
{Acc, Cache};
-constraints_to_subs([{T1, Form2}|Rest], MFA, RecDict, ExpTypes, RecordTable,
- VarTab, Cache, Acc) ->
+constraints_to_subs([{T1, Form2}|Rest], Module, MFA, RecDict, ExpTypes,
+ RecordTable, VarTab, Cache, Acc) ->
{T2, NewCache} =
- final_form(Form2, ExpTypes, MFA, RecordTable, VarTab, Cache),
+ final_form(Form2, ExpTypes, Module, MFA, RecordTable, VarTab, Cache),
NewAcc = [{subtype, T1, T2}|Acc],
- constraints_to_subs(Rest, MFA, RecDict, ExpTypes, RecordTable,
+ constraints_to_subs(Rest, Module, MFA, RecDict, ExpTypes, RecordTable,
VarTab, NewCache, NewAcc).
%% Replaces variables with '_' when necessary to break up cycles among
@@ -708,22 +759,30 @@ get_invalid_contract_warnings_funs([{MFA, {FileLine, Contract, _Xtra}}|Left],
[W|Acc];
{error, {overlapping_contract, []}} ->
[overlapping_contract_warning(MFA, WarningInfo)|Acc];
- {error, {extra_range, ExtraRanges, STRange}} ->
- Warn =
- case t_from_forms_without_remote(Contract#contract.forms,
- MFA, RecDict) of
- {ok, NoRemoteType} ->
- CRet = erl_types:t_fun_range(NoRemoteType),
- erl_types:t_is_subtype(ExtraRanges, CRet);
- unsupported ->
- true
- end,
- case Warn of
- true ->
- [extra_range_warning(MFA, WarningInfo, ExtraRanges, STRange)|Acc];
- false ->
- Acc
- end;
+ {range_warnings, Errors} ->
+ Fun =
+ fun({error, {extra_range, ExtraRanges, STRange}}, Acc0) ->
+ Warn =
+ case t_from_forms_without_remote(Contract#contract.forms,
+ MFA, RecDict) of
+ {ok, NoRemoteType} ->
+ CRet = erl_types:t_fun_range(NoRemoteType),
+ erl_types:t_is_subtype(ExtraRanges, CRet);
+ unsupported ->
+ true
+ end,
+ case Warn of
+ true ->
+ [extra_range_warning(MFA, WarningInfo,
+ ExtraRanges, STRange)|Acc0];
+ false ->
+ Acc0
+ end;
+ ({error, {missing_range, ExtraRanges, CRange}}, Acc0) ->
+ [missing_range_warning(MFA, WarningInfo,
+ ExtraRanges, CRange)|Acc0]
+ end,
+ lists:foldl(Fun, Acc, Errors);
{error, Msg} ->
[{?WARN_CONTRACT_SYNTAX, WarningInfo, Msg}|Acc];
ok ->
@@ -741,6 +800,9 @@ get_invalid_contract_warnings_funs([{MFA, {FileLine, Contract, _Xtra}}|Left],
{error, _} ->
[invalid_contract_warning(MFA, WarningInfo, BifSig, RecDict)
|Acc];
+ {range_warnings, _} ->
+ picky_contract_check(CSig, BifSig, MFA, WarningInfo,
+ Contract, RecDict, Acc);
ok ->
picky_contract_check(CSig, BifSig, MFA, WarningInfo,
Contract, RecDict, Acc)
@@ -774,6 +836,12 @@ extra_range_warning({M, F, A}, WarningInfo, ExtraRanges, STRange) ->
{?WARN_CONTRACT_SUPERTYPE, WarningInfo,
{extra_range, [M, F, A, ERangesStr, STRangeStr]}}.
+missing_range_warning({M, F, A}, WarningInfo, ExtraRanges, CRange) ->
+ ERangesStr = erl_types:t_to_string(ExtraRanges),
+ CRangeStr = erl_types:t_to_string(CRange),
+ {?WARN_CONTRACT_SUBTYPE, WarningInfo,
+ {missing_range, [M, F, A, ERangesStr, CRangeStr]}}.
+
picky_contract_check(CSig0, Sig0, MFA, WarningInfo, Contract, RecDict, Acc) ->
CSig = erl_types:t_abstract_records(CSig0, RecDict),
Sig = erl_types:t_abstract_records(Sig0, RecDict),
@@ -843,6 +911,7 @@ is_remote_types_related(Contract, CSig, Sig, MFA, RecDict) ->
t_from_forms_without_remote([{FType, []}], MFA, RecDict) ->
Site = {spec, MFA},
+ %% FIXME
Type1 = erl_types:t_from_form_without_remote(FType, Site, RecDict),
{ok, erl_types:subst_all_vars_to_any(Type1)};
t_from_forms_without_remote([{_FType, _Constrs}], _MFA, _RecDict) ->
diff --git a/lib/dialyzer/src/dialyzer_dataflow.erl b/lib/dialyzer/src/dialyzer_dataflow.erl
index ea3523a965..45b4abb253 100644
--- a/lib/dialyzer/src/dialyzer_dataflow.erl
+++ b/lib/dialyzer/src/dialyzer_dataflow.erl
@@ -102,6 +102,8 @@
| 'undefined', % race
fun_homes :: dict:dict(label(), mfa())
| 'undefined', % race
+ reachable_funs :: sets:set(label())
+ | 'undefined', % race
plt :: dialyzer_plt:plt()
| 'undefined', % race
opaques :: [type()]
@@ -269,9 +271,11 @@ traverse(Tree, Map, State) ->
case state__warning_mode(State) of
true -> {State, Map, Type};
false ->
- State2 = state__add_work(get_label(Tree), State),
+ FunLbl = get_label(Tree),
+ State2 = state__add_work(FunLbl, State),
State3 = state__update_fun_env(Tree, Map, State2),
- {State3, Map, Type}
+ State4 = state__add_reachable(FunLbl, State3),
+ {State4, Map, Type}
end;
'let' ->
handle_let(Tree, Map, State);
@@ -299,6 +303,7 @@ traverse(Tree, Map, State) ->
match_fail -> t_none();
raise -> t_none();
bs_init_writable -> t_from_term(<<>>);
+ build_stacktrace -> erl_bif_types:type(erlang, build_stacktrace, 0);
Other -> erlang:error({'Unsupported primop', Other})
end,
{State, Map, Type};
@@ -3038,25 +3043,35 @@ state__new(Callgraph, Codeserver, Tree, Plt, Module, Records) ->
{TreeMap, FunHomes} = build_tree_map(Tree, Callgraph),
Funs = dict:fetch_keys(TreeMap),
FunTab = init_fun_tab(Funs, dict:new(), TreeMap, Callgraph, Plt),
- ExportedFuns =
- [Fun || Fun <- Funs--[top], dialyzer_callgraph:is_escaping(Fun, Callgraph)],
- Work = init_work(ExportedFuns),
+ ExportedFunctions =
+ [Fun ||
+ Fun <- Funs--[top],
+ dialyzer_callgraph:is_escaping(Fun, Callgraph),
+ dialyzer_callgraph:lookup_name(Fun, Callgraph) =/= error
+ ],
+ Work = init_work(ExportedFunctions),
Env = lists:foldl(fun(Fun, Env) -> dict:store(Fun, map__new(), Env) end,
dict:new(), Funs),
#state{callgraph = Callgraph, codeserver = Codeserver,
envs = Env, fun_tab = FunTab, fun_homes = FunHomes, opaques = Opaques,
plt = Plt, races = dialyzer_races:new(), records = Records,
warning_mode = false, warnings = [], work = Work, tree_map = TreeMap,
- module = Module}.
+ module = Module, reachable_funs = sets:new()}.
state__warning_mode(#state{warning_mode = WM}) ->
WM.
state__set_warning_mode(#state{tree_map = TreeMap, fun_tab = FunTab,
- races = Races} = State) ->
+ races = Races, callgraph = Callgraph,
+ reachable_funs = ReachableFuns} = State) ->
?debug("==========\nStarting warning pass\n==========\n", []),
Funs = dict:fetch_keys(TreeMap),
- State#state{work = init_work([top|Funs--[top]]),
+ Work =
+ [Fun ||
+ Fun <- Funs--[top],
+ dialyzer_callgraph:lookup_name(Fun, Callgraph) =/= error orelse
+ sets:is_element(Fun, ReachableFuns)],
+ State#state{work = init_work(Work),
fun_tab = FunTab, warning_mode = true,
races = dialyzer_races:put_race_analysis(true, Races)}.
@@ -3148,7 +3163,8 @@ state__get_race_warnings(#state{races = Races} = State) ->
State1#state{races = Races1}.
state__get_warnings(#state{tree_map = TreeMap, fun_tab = FunTab,
- callgraph = Callgraph, plt = Plt} = State) ->
+ callgraph = Callgraph, plt = Plt,
+ reachable_funs = ReachableFuns} = State) ->
FoldFun =
fun({top, _}, AccState) -> AccState;
({FunLbl, Fun}, AccState) ->
@@ -3183,7 +3199,12 @@ state__get_warnings(#state{tree_map = TreeMap, fun_tab = FunTab,
GenRet = dialyzer_contracts:get_contract_return(C),
not t_is_unit(GenRet)
end,
- case Warn of
+ %% Do not output warnings for unreachable funs.
+ case
+ Warn andalso
+ (dialyzer_callgraph:lookup_name(FunLbl, Callgraph) =/= error
+ orelse sets:is_element(FunLbl, ReachableFuns))
+ of
true ->
case classify_returns(Fun) of
no_match ->
@@ -3254,6 +3275,10 @@ state__get_args_and_status(Tree, #state{fun_tab = FunTab}) ->
{ok, {ArgTypes, _}} -> {ArgTypes, true}
end.
+state__add_reachable(FunLbl, #state{reachable_funs = ReachableFuns}=State) ->
+ NewReachableFuns = sets:add_element(FunLbl, ReachableFuns),
+ State#state{reachable_funs = NewReachableFuns}.
+
build_tree_map(Tree, Callgraph) ->
Fun =
fun(T, {Dict, Homes, FunLbls} = Acc) ->
diff --git a/lib/dialyzer/src/dialyzer_gui_wx.erl b/lib/dialyzer/src/dialyzer_gui_wx.erl
index b4b1872c12..b8414b7d8b 100644
--- a/lib/dialyzer/src/dialyzer_gui_wx.erl
+++ b/lib/dialyzer/src/dialyzer_gui_wx.erl
@@ -475,7 +475,7 @@ gui_loop(#gui_state{backend_pid = BackendPid, doc_plt = DocPlt,
gui_loop(State);
{BackendPid, ext_types, ExtTypes} ->
Map = fun({M,F,A}) -> io_lib:format("~tp:~tp/~p",[M,F,A]) end,
- ExtTypeString = string:join(lists:map(Map, ExtTypes), "\n"),
+ ExtTypeString = lists:join("\n", lists:map(Map, ExtTypes)),
Msg = io_lib:format("The following remote types are being used "
"but information about them is not available.\n"
"The analysis might get more precise by including "
@@ -638,7 +638,7 @@ output_sms(#gui_state{frame = Frame}, Title, Message, Type) ->
free_editor(#gui_state{gui = Wx, frame = Frame}, Title, Contents0) ->
Contents = lists:flatten(Contents0),
- Tokens = string:tokens(Contents, "\n"),
+ Tokens = string:lexemes(Contents, "\n"),
NofLines = length(Tokens),
LongestLine = lists:max([length(X) || X <- Tokens]),
Height0 = NofLines * 25 + 80,
diff --git a/lib/dialyzer/src/dialyzer_plt.erl b/lib/dialyzer/src/dialyzer_plt.erl
index 95c8b5ebce..2af4534396 100644
--- a/lib/dialyzer/src/dialyzer_plt.erl
+++ b/lib/dialyzer/src/dialyzer_plt.erl
@@ -531,17 +531,19 @@ compute_md5_from_files(Files) ->
lists:keysort(1, [{F, compute_md5_from_file(F)} || F <- Files]).
compute_md5_from_file(File) ->
- case filelib:is_regular(File) of
- false ->
+ case beam_lib:all_chunks(File) of
+ {ok, _, Chunks} ->
+ %% We cannot use beam_lib:md5 because it does not consider
+ %% the debug_info chunk, where typespecs are likely stored.
+ %% So we consider almost all chunks except the useless ones.
+ Filtered = [[ID, Chunk] || {ID, Chunk} <- Chunks, ID =/= "CInf", ID =/= "Docs"],
+ erlang:md5(lists:sort(Filtered));
+ {error, beam_lib, {file_error, _, enoent}} ->
Msg = io_lib:format("Not a regular file: ~ts\n", [File]),
throw({dialyzer_error, Msg});
- true ->
- case dialyzer_utils:get_core_from_beam(File) of
- {error, Error} ->
- throw({dialyzer_error, Error});
- {ok, Core} ->
- erlang:md5(term_to_binary(Core))
- end
+ {error, beam_lib, _} ->
+ Msg = io_lib:format("Could not compute MD5 for .beam: ~ts\n", [File]),
+ throw({dialyzer_error, Msg})
end.
init_diff_list(RemoveFiles, AddFiles) ->
diff --git a/lib/dialyzer/src/dialyzer_races.erl b/lib/dialyzer/src/dialyzer_races.erl
index 7fe64c3e11..7602faa21d 100644
--- a/lib/dialyzer/src/dialyzer_races.erl
+++ b/lib/dialyzer/src/dialyzer_races.erl
@@ -1270,8 +1270,8 @@ filter_named_tables(NamesList) ->
[] -> [];
[Head|Tail] ->
NewHead =
- case string:rstr(Head, "()") of
- 0 -> [Head];
+ case string:find(Head, "()", trailing) of
+ nomatch -> [Head];
_Other -> []
end,
NewHead ++ filter_named_tables(Tail)
@@ -1558,8 +1558,8 @@ any_args(StrList) ->
case StrList of
[] -> false;
[Head|Tail] ->
- case string:rstr(Head, "()") of
- 0 -> any_args(Tail);
+ case string:find(Head, "()", trailing) of
+ nomatch -> any_args(Tail);
_Other -> true
end
end.
@@ -1765,10 +1765,8 @@ ets_list_args(MaybeList) ->
end.
ets_list_argtypes(ListStr) ->
- ListStr1 = string:strip(ListStr, left, $[),
- ListStr2 = string:strip(ListStr1, right, $]),
- ListStr3 = string:strip(ListStr2, right, $.),
- string:strip(ListStr3, right, $,).
+ ListStr1 = string:trim(ListStr, leading, "$["),
+ string:trim(ListStr1, trailing, "$]$.$,").
ets_tuple_args(MaybeTuple) ->
case is_tuple(MaybeTuple) of
@@ -1810,7 +1808,7 @@ ets_tuple_argtypes2_helper(TupleStr, ElemStr, NestingLevel) ->
{[H|ElemStr], NestingLevel, false}
end,
case Return of
- true -> string:tokens(NewElemStr, " |");
+ true -> string:lexemes(NewElemStr, " |");
false ->
ets_tuple_argtypes2_helper(T, NewElemStr, NewNestingLevel)
end
@@ -1889,44 +1887,44 @@ format_args_2(StrArgList, Call) ->
case Call of
whereis ->
lists_key_replace(2, StrArgList,
- string:tokens(lists:nth(2, StrArgList), " |"));
+ string:lexemes(lists:nth(2, StrArgList), " |"));
register ->
lists_key_replace(2, StrArgList,
- string:tokens(lists:nth(2, StrArgList), " |"));
+ string:lexemes(lists:nth(2, StrArgList), " |"));
unregister ->
lists_key_replace(2, StrArgList,
- string:tokens(lists:nth(2, StrArgList), " |"));
+ string:lexemes(lists:nth(2, StrArgList), " |"));
ets_new ->
StrArgList1 = lists_key_replace(2, StrArgList,
- string:tokens(lists:nth(2, StrArgList), " |")),
+ string:lexemes(lists:nth(2, StrArgList), " |")),
lists_key_replace(4, StrArgList1,
- string:tokens(ets_list_argtypes(lists:nth(4, StrArgList1)), " |"));
+ string:lexemes(ets_list_argtypes(lists:nth(4, StrArgList1)), " |"));
ets_lookup ->
StrArgList1 = lists_key_replace(2, StrArgList,
- string:tokens(lists:nth(2, StrArgList), " |")),
+ string:lexemes(lists:nth(2, StrArgList), " |")),
lists_key_replace(4, StrArgList1,
- string:tokens(lists:nth(4, StrArgList1), " |"));
+ string:lexemes(lists:nth(4, StrArgList1), " |"));
ets_insert ->
StrArgList1 = lists_key_replace(2, StrArgList,
- string:tokens(lists:nth(2, StrArgList), " |")),
+ string:lexemes(lists:nth(2, StrArgList), " |")),
lists_key_replace(4, StrArgList1,
ets_tuple_argtypes2(
ets_tuple_argtypes1(lists:nth(4, StrArgList1), [], [], 0),
[]));
mnesia_dirty_read1 ->
lists_key_replace(2, StrArgList,
- [mnesia_tuple_argtypes(T) || T <- string:tokens(
+ [mnesia_tuple_argtypes(T) || T <- string:lexemes(
lists:nth(2, StrArgList), " |")]);
mnesia_dirty_read2 ->
lists_key_replace(2, StrArgList,
- string:tokens(lists:nth(2, StrArgList), " |"));
+ string:lexemes(lists:nth(2, StrArgList), " |"));
mnesia_dirty_write1 ->
lists_key_replace(2, StrArgList,
- [mnesia_record_tab(R) || R <- string:tokens(
+ [mnesia_record_tab(R) || R <- string:lexemes(
lists:nth(2, StrArgList), " |")]);
mnesia_dirty_write2 ->
lists_key_replace(2, StrArgList,
- string:tokens(lists:nth(2, StrArgList), " |"));
+ string:lexemes(lists:nth(2, StrArgList), " |"));
function_call -> StrArgList
end.
@@ -1943,18 +1941,16 @@ format_type(Type, State) ->
erl_types:t_to_string(Type, R).
mnesia_record_tab(RecordStr) ->
- case string:str(RecordStr, "#") =:= 1 of
- true ->
- "'" ++
- string:sub_string(RecordStr, 2, string:str(RecordStr, "{") - 1) ++
- "'";
- false -> RecordStr
+ case erl_scan:string(RecordStr) of
+ {ok, [{'#', _}, {atom, _, Name}|_], _} ->
+ io_lib:write_string(atom_to_list(Name), $');
+ _ -> RecordStr
end.
mnesia_tuple_argtypes(TupleStr) ->
- TupleStr1 = string:strip(TupleStr, left, ${),
- [TupleStr2|_T] = string:tokens(TupleStr1, " ,"),
- lists:flatten(string:tokens(TupleStr2, " |")).
+ TupleStr1 = string:trim(TupleStr, leading, "${"),
+ [TupleStr2|_T] = string:lexemes(TupleStr1, " ,"),
+ lists:flatten(string:lexemes(TupleStr2, " |")).
-spec race_var_map(var_to_map1(), var_to_map2(), dict:dict(), op()) ->
dict:dict().
@@ -2237,7 +2233,7 @@ var_type_analysis(FunDefArgs, FunCallTypes, WarnVarArgs, RaceWarnTag,
case lists_key_member_lists(Vars, FunVarArgs) of
0 -> [Vars, WVA2, WVA3, WVA4];
N when is_integer(N) ->
- NewWVA2 = string:tokens(lists:nth(N + 1, FunVarArgs), " |"),
+ NewWVA2 = string:lexemes(lists:nth(N + 1, FunVarArgs), " |"),
[Vars, NewWVA2, WVA3, WVA4]
end;
?WARN_WHEREIS_UNREGISTER ->
@@ -2246,7 +2242,7 @@ var_type_analysis(FunDefArgs, FunCallTypes, WarnVarArgs, RaceWarnTag,
case lists_key_member_lists(Vars, FunVarArgs) of
0 -> [Vars, WVA2];
N when is_integer(N) ->
- NewWVA2 = string:tokens(lists:nth(N + 1, FunVarArgs), " |"),
+ NewWVA2 = string:lexemes(lists:nth(N + 1, FunVarArgs), " |"),
[Vars, NewWVA2]
end;
?WARN_ETS_LOOKUP_INSERT ->
@@ -2256,7 +2252,7 @@ var_type_analysis(FunDefArgs, FunCallTypes, WarnVarArgs, RaceWarnTag,
case lists_key_member_lists(Vars1, FunVarArgs) of
0 -> [Vars1, WVA2];
N1 when is_integer(N1) ->
- NewWVA2 = string:tokens(lists:nth(N1 + 1, FunVarArgs), " |"),
+ NewWVA2 = string:lexemes(lists:nth(N1 + 1, FunVarArgs), " |"),
[Vars1, NewWVA2]
end,
Vars2 =
@@ -2286,10 +2282,10 @@ var_type_analysis(FunDefArgs, FunCallTypes, WarnVarArgs, RaceWarnTag,
NewWVA2 =
case Arity of
1 ->
- [mnesia_record_tab(R) || R <- string:tokens(
+ [mnesia_record_tab(R) || R <- string:lexemes(
lists:nth(2, FunVarArgs), " |")];
2 ->
- string:tokens(lists:nth(N + 1, FunVarArgs), " |")
+ string:lexemes(lists:nth(N + 1, FunVarArgs), " |")
end,
[Vars, NewWVA2|T]
end
diff --git a/lib/dialyzer/src/dialyzer_typesig.erl b/lib/dialyzer/src/dialyzer_typesig.erl
index d03326ec97..dede475f98 100644
--- a/lib/dialyzer/src/dialyzer_typesig.erl
+++ b/lib/dialyzer/src/dialyzer_typesig.erl
@@ -418,6 +418,11 @@ traverse(Tree, DefinedVars, State) ->
match_fail -> throw(error);
raise -> throw(error);
bs_init_writable -> {State, t_from_term(<<>>)};
+ build_stacktrace ->
+ V = mk_var(Tree),
+ Type = erl_bif_types:type(erlang, build_stacktrace, 0),
+ State1 = state__store_conj(V, sub, Type, State),
+ {State1, V};
Other -> erlang:error({'Unsupported primop', Other})
end;
'receive' ->
@@ -1895,9 +1900,8 @@ solver(Solver, SolveFun) ->
?debug("Solver ~w returned unexpected result:\n ~P\n",
[Solver, _R, 60]),
throw(error)
- catch E:R ->
- io:format("Solver ~w failed: ~w:~p\n ~tp\n",
- [Solver, E, R, erlang:get_stacktrace()]),
+ catch E:R:S ->
+ io:format("Solver ~w failed: ~w:~p\n ~tp\n", [Solver, E, R, S]),
throw(error)
end.
diff --git a/lib/dialyzer/src/dialyzer_utils.erl b/lib/dialyzer/src/dialyzer_utils.erl
index 9b8fbc67eb..310301ee0b 100644
--- a/lib/dialyzer/src/dialyzer_utils.erl
+++ b/lib/dialyzer/src/dialyzer_utils.erl
@@ -120,92 +120,10 @@ get_core_from_beam(File, Opts) ->
{error, " Could not get Core Erlang code for: " ++ File ++ "\n"}
end;
_ ->
- deprecated_get_core_from_beam(File, Opts)
+ {error, " Could not get Core Erlang code for: " ++ File ++ "\n" ++
+ " Recompile with +debug_info or analyze starting from source code"}
end.
-deprecated_get_core_from_beam(File, Opts) ->
- case get_abstract_code_from_beam(File) of
- error ->
- {error, " Could not get abstract code for: " ++ File ++ "\n" ++
- " Recompile with +debug_info or analyze starting from source code"};
- {ok, AbstrCode} ->
- case get_compile_options_from_beam(File) of
- error ->
- {error, " Could not get compile options for: " ++ File ++ "\n" ++
- " Recompile or analyze starting from source code"};
- {ok, CompOpts} ->
- case get_core_from_abstract_code(AbstrCode, Opts ++ CompOpts) of
- error ->
- {error, " Could not get core Erlang code for: " ++ File};
- {ok, _} = Core ->
- Core
- end
- end
- end.
-
-get_abstract_code_from_beam(File) ->
- case beam_lib:chunks(File, [abstract_code]) of
- {ok, {_, List}} ->
- case lists:keyfind(abstract_code, 1, List) of
- {abstract_code, {raw_abstract_v1, Abstr}} -> {ok, Abstr};
- _ -> error
- end;
- _ ->
- %% No or unsuitable abstract code.
- error
- end.
-
-get_compile_options_from_beam(File) ->
- case beam_lib:chunks(File, [compile_info]) of
- {ok, {_, List}} ->
- case lists:keyfind(compile_info, 1, List) of
- {compile_info, CompInfo} -> compile_info_to_options(CompInfo);
- _ -> error
- end;
- _ ->
- %% No or unsuitable compile info.
- error
- end.
-
-compile_info_to_options(CompInfo) ->
- case lists:keyfind(options, 1, CompInfo) of
- {options, CompOpts} -> {ok, CompOpts};
- _ -> error
- end.
-
-get_core_from_abstract_code(AbstrCode, Opts) ->
- %% We do not want the parse_transforms around since we already
- %% performed them. In some cases we end up in trouble when
- %% performing them again.
- AbstrCode1 = cleanup_parse_transforms(AbstrCode),
- %% Remove parse_transforms (and other options) from compile options.
- Opts2 = cleanup_compile_options(Opts),
- try compile:noenv_forms(AbstrCode1, Opts2 ++ src_compiler_opts()) of
- {ok, _, Core} -> {ok, Core};
- _What -> error
- catch
- error:_ -> error
- end.
-
-cleanup_parse_transforms([{attribute, _, compile, {parse_transform, _}}|Left]) ->
- cleanup_parse_transforms(Left);
-cleanup_parse_transforms([Other|Left]) ->
- [Other|cleanup_parse_transforms(Left)];
-cleanup_parse_transforms([]) ->
- [].
-
-cleanup_compile_options(Opts) ->
- lists:filter(fun keep_compile_option/1, Opts).
-
-%% Using abstract, not asm or core.
-keep_compile_option(from_asm) -> false;
-keep_compile_option(from_core) -> false;
-%% The parse transform will already have been applied, may cause
-%% problems if it is re-applied.
-keep_compile_option({parse_transform, _}) -> false;
-keep_compile_option(warnings_as_errors) -> false;
-keep_compile_option(_) -> true.
-
%% ============================================================================
%%
%% Typed Records
@@ -532,8 +450,9 @@ get_spec_info([{Contract, Ln, [{Id, TypeSpec}]}|Left],
error ->
SpecData = {TypeSpec, Xtra},
NewActiveMap =
- dialyzer_contracts:store_tmp_contract(MFA, {File, Ln}, SpecData,
- ActiveMap, RecordsMap),
+ dialyzer_contracts:store_tmp_contract(ModName, MFA, {File, Ln},
+ SpecData, ActiveMap,
+ RecordsMap),
{NewSpecMap, NewCallbackMap} =
case Contract of
spec -> {NewActiveMap, CallbackMap};
@@ -681,24 +600,32 @@ collect_attribute([], _Tag, _File) ->
-spec is_suppressed_fun(mfa(), codeserver()) -> boolean().
is_suppressed_fun(MFA, CodeServer) ->
- lookup_fun_property(MFA, nowarn_function, CodeServer).
+ lookup_fun_property(MFA, nowarn_function, CodeServer, false).
-spec is_suppressed_tag(mfa() | module(), dial_warn_tag(), codeserver()) ->
boolean().
is_suppressed_tag(MorMFA, Tag, Codeserver) ->
- not lookup_fun_property(MorMFA, Tag, Codeserver).
-
-lookup_fun_property({M, _F, _A}=MFA, Property, CodeServer) ->
- MFAPropList = dialyzer_codeserver:lookup_meta_info(MFA, CodeServer),
- case proplists:get_value(Property, MFAPropList, no) of
- mod -> false; % suppressed in function
- func -> true; % requested in function
- no -> lookup_fun_property(M, Property, CodeServer)
+ not lookup_fun_property(MorMFA, Tag, Codeserver, true).
+
+lookup_fun_property({M, _F, _A}=MFA, Property, CodeServer, NoInfoReturn) ->
+ case dialyzer_codeserver:lookup_meta_info(MFA, CodeServer) of
+ error ->
+ lookup_fun_property(M, Property, CodeServer, NoInfoReturn);
+ {ok, MFAPropList} ->
+ case proplists:get_value(Property, MFAPropList, no) of
+ mod -> false; % suppressed in function
+ func -> true; % requested in function
+ no -> lookup_fun_property(M, Property, CodeServer, NoInfoReturn)
+ end
end;
-lookup_fun_property(M, Property, CodeServer) when is_atom(M) ->
- MPropList = dialyzer_codeserver:lookup_meta_info(M, CodeServer),
- proplists:is_defined(Property, MPropList).
+lookup_fun_property(M, Property, CodeServer, NoInfoReturn) when is_atom(M) ->
+ case dialyzer_codeserver:lookup_meta_info(M, CodeServer) of
+ error ->
+ NoInfoReturn;
+ {ok, MPropList} ->
+ proplists:is_defined(Property, MPropList)
+ end.
%% ============================================================================
%%
diff --git a/lib/dialyzer/src/typer.erl b/lib/dialyzer/src/typer.erl
index 16b9c8a94a..4b99f5f72e 100644
--- a/lib/dialyzer/src/typer.erl
+++ b/lib/dialyzer/src/typer.erl
@@ -164,9 +164,9 @@ get_type_info(#analysis{callgraph = CallGraph,
CodeServer),
Analysis#analysis{callgraph = StrippedCallGraph, trust_plt = NewPlt}
catch
- error:What ->
+ error:What:Stacktrace ->
fatal_error(io_lib:format("Analysis failed with message: ~tp",
- [{What, erlang:get_stacktrace()}]));
+ [{What, Stacktrace}]));
throw:{dialyzer_succ_typing_error, Msg} ->
fatal_error(io_lib:format("Analysis failed with message: ~ts", [Msg]))
end.
@@ -401,7 +401,7 @@ get_type({{M, F, A} = MFA, Range, Arg}, CodeServer, Records) ->
Sig = erl_types:t_fun(Arg, Range),
case dialyzer_contracts:check_contract(Contract, Sig) of
ok -> {{F, A}, {contract, Contract}};
- {error, {extra_range, _, _}} ->
+ {range_warnings, _} ->
{{F, A}, {contract, Contract}};
{error, {overlapping_contract, []}} ->
{{F, A}, {contract, Contract}};