aboutsummaryrefslogtreecommitdiffstats
path: root/lib/dialyzer
diff options
context:
space:
mode:
authorHans Bolinder <[email protected]>2016-06-10 10:32:04 +0200
committerHans Bolinder <[email protected]>2016-06-10 10:32:04 +0200
commit7dd54b5a89d382689562ea19e7ff96daf5b65290 (patch)
treedcdab1be7b8aa4f155951a2ab22c164ff133c9d5 /lib/dialyzer
parent599b3cd3d802f09a9f921f44e72418e7d7ad1a06 (diff)
parent0d1c055fd82fa71ca4db08d7827de4d20d2f1241 (diff)
downloadotp-7dd54b5a89d382689562ea19e7ff96daf5b65290.tar.gz
otp-7dd54b5a89d382689562ea19e7ff96daf5b65290.tar.bz2
otp-7dd54b5a89d382689562ea19e7ff96daf5b65290.zip
Merge branch 'hasse/dialyzer/improve_from_form/OTP-13547'
* hasse/dialyzer/improve_from_form/OTP-13547: Update primary bootstrap stdlib: Correct types and specs dialyzer: Minor adjustments dialyzer: Suppress unmatched_return for send/2 dialyzer: Improve the translation of forms to types dialyzer: Use a cache when translating forms to types dialyzer: Prepare erl_types:t_from_form() for a cache dialyzer: Optimize erl_types:t_form_form() dialyzer: Correct types syntax_tools: Correct types erts: Correct character repr in doc of the abstract format stdlib: Correct types and specs
Diffstat (limited to 'lib/dialyzer')
-rw-r--r--lib/dialyzer/src/dialyzer_contracts.erl161
-rw-r--r--lib/dialyzer/src/dialyzer_dataflow.erl13
-rw-r--r--lib/dialyzer/src/dialyzer_utils.erl122
-rw-r--r--lib/dialyzer/test/unmatched_returns_SUITE_data/src/send.erl11
4 files changed, 193 insertions, 114 deletions
diff --git a/lib/dialyzer/src/dialyzer_contracts.erl b/lib/dialyzer/src/dialyzer_contracts.erl
index 272ad10e90..976a2b8955 100644
--- a/lib/dialyzer/src/dialyzer_contracts.erl
+++ b/lib/dialyzer/src/dialyzer_contracts.erl
@@ -53,7 +53,9 @@
%% to expand records and/or remote types that they might contain.
%%-----------------------------------------------------------------------
--type tmp_contract_fun() :: fun((sets:set(mfa()), types()) -> contract_pair()).
+-type cache() :: ets:tid().
+-type tmp_contract_fun() ::
+ fun((sets:set(mfa()), types(), cache()) -> contract_pair()).
-record(tmp_contract, {contract_funs = [] :: [tmp_contract_fun()],
forms = [] :: [{_, _}]}).
@@ -153,19 +155,30 @@ process_contract_remote_types(CodeServer) ->
ExpTypes = dialyzer_codeserver:get_exported_types(CodeServer),
RecordDict = dialyzer_codeserver:get_records(CodeServer),
ContractFun =
- fun({_M, _F, _A}, {File, #tmp_contract{contract_funs = CFuns, forms = Forms}, Xtra}) ->
- NewCs = [CFun(ExpTypes, RecordDict) || CFun <- CFuns],
- Args = general_domain(NewCs),
- {File, #contract{contracts = NewCs, args = Args, forms = Forms}, Xtra}
+ 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, RecordDict, 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, ContractDict) ->
- dict:map(ContractFun, ContractDict)
+ fun({ModuleName, ContractDict}, C3) ->
+ {NewContractList, C4} =
+ lists:mapfoldl(ContractFun, C3, dict:to_list(ContractDict)),
+ {{ModuleName, dict:from_list(NewContractList)}, C4}
end,
- NewContractDict = dict:map(ModuleFun, TmpContractDict),
- NewCallbackDict = dict:map(ModuleFun, TmpCallbackDict),
+ Cache = erl_types:cache__new(),
+ {NewContractList, C5} =
+ lists:mapfoldl(ModuleFun, Cache, dict:to_list(TmpContractDict)),
+ {NewCallbackList, _C6} =
+ lists:mapfoldl(ModuleFun, C5, dict:to_list(TmpCallbackDict)),
+ NewContractDict = dict:from_list(NewContractList),
+ NewCallbackDict = dict:from_list(NewCallbackList),
dialyzer_codeserver:finalize_contracts(NewContractDict, NewCallbackDict,
- CodeServer).
+ CodeServer).
-type opaques_fun() :: fun((module()) -> [erl_types:erl_type()]).
@@ -431,19 +444,19 @@ contract_from_form(Forms, MFA, RecDict, FileLine) ->
contract_from_form([{type, _, 'fun', [_, _]} = Form | Left], MFA, RecDict,
FileLine, TypeAcc, FormAcc) ->
TypeFun =
- fun(ExpTypes, AllRecords) ->
- NewType =
+ fun(ExpTypes, AllRecords, Cache) ->
+ {NewType, NewCache} =
try
- from_form_with_check(Form, ExpTypes, MFA, AllRecords)
+ from_form_with_check(Form, ExpTypes, MFA, AllRecords, Cache)
catch
throw:{error, Msg} ->
{File, Line} = FileLine,
NewMsg = io_lib:format("~s:~p: ~s", [filename:basename(File),
- Line, Msg]),
+ Line, Msg]),
throw({error, NewMsg})
end,
NewTypeNoVars = erl_types:subst_all_vars_to_any(NewType),
- {NewTypeNoVars, []}
+ {{NewTypeNoVars, []}, NewCache}
end,
NewTypeAcc = [TypeFun | TypeAcc],
NewFormAcc = [{Form, []} | FormAcc],
@@ -452,13 +465,15 @@ contract_from_form([{type, _L1, bounded_fun,
[{type, _L2, 'fun', [_, _]} = Form, Constr]}| Left],
MFA, RecDict, FileLine, TypeAcc, FormAcc) ->
TypeFun =
- fun(ExpTypes, AllRecords) ->
- {Constr1, VarDict} =
- process_constraints(Constr, MFA, RecDict, ExpTypes, AllRecords),
- NewType = from_form_with_check(Form, ExpTypes, MFA, AllRecords,
- VarDict),
+ fun(ExpTypes, AllRecords, Cache) ->
+ {Constr1, VarTable, Cache1} =
+ process_constraints(Constr, MFA, RecDict, ExpTypes, AllRecords,
+ Cache),
+ {NewType, NewCache} =
+ from_form_with_check(Form, ExpTypes, MFA, AllRecords,
+ VarTable, Cache1),
NewTypeNoVars = erl_types:subst_all_vars_to_any(NewType),
- {NewTypeNoVars, Constr1}
+ {{NewTypeNoVars, Constr1}, NewCache}
end,
NewTypeAcc = [TypeFun | TypeAcc],
NewFormAcc = [{Form, Constr} | FormAcc],
@@ -466,74 +481,91 @@ contract_from_form([{type, _L1, bounded_fun,
contract_from_form([], _MFA, _RecDict, _FileLine, TypeAcc, FormAcc) ->
{lists:reverse(TypeAcc), lists:reverse(FormAcc)}.
-process_constraints(Constrs, MFA, RecDict, ExpTypes, AllRecords) ->
- Init0 = initialize_constraints(Constrs, MFA, RecDict, ExpTypes, AllRecords),
+process_constraints(Constrs, MFA, RecDict, ExpTypes, AllRecords, Cache) ->
+ {Init0, NewCache} = initialize_constraints(Constrs, MFA, RecDict, ExpTypes,
+ AllRecords, Cache),
Init = remove_cycles(Init0),
- constraints_fixpoint(Init, MFA, RecDict, ExpTypes, AllRecords).
+ constraints_fixpoint(Init, MFA, RecDict, ExpTypes, AllRecords, NewCache).
-initialize_constraints(Constrs, MFA, RecDict, ExpTypes, AllRecords) ->
- initialize_constraints(Constrs, MFA, RecDict, ExpTypes, AllRecords, []).
+initialize_constraints(Constrs, MFA, RecDict, ExpTypes, AllRecords, Cache) ->
+ initialize_constraints(Constrs, MFA, RecDict, ExpTypes, AllRecords,
+ Cache, []).
-initialize_constraints([], _MFA, _RecDict, _ExpTypes, _AllRecords, Acc) ->
- Acc;
-initialize_constraints([Constr|Rest], MFA, RecDict, ExpTypes, AllRecords, Acc) ->
+initialize_constraints([], _MFA, _RecDict, _ExpTypes, _AllRecords,
+ Cache, Acc) ->
+ {Acc, Cache};
+initialize_constraints([Constr|Rest], MFA, RecDict, ExpTypes, AllRecords,
+ Cache, Acc) ->
case Constr of
{type, _, constraint, [{atom, _, is_subtype}, [Type1, Type2]]} ->
VarTable = erl_types:var_table__new(),
- T1 = final_form(Type1, ExpTypes, MFA, AllRecords, VarTable),
+ {T1, NewCache} =
+ final_form(Type1, ExpTypes, MFA, AllRecords, VarTable, Cache),
Entry = {T1, Type2},
- initialize_constraints(Rest, MFA, RecDict, ExpTypes, AllRecords, [Entry|Acc]);
+ initialize_constraints(Rest, MFA, RecDict, ExpTypes, AllRecords,
+ NewCache, [Entry|Acc]);
{type, _, constraint, [{atom,_,Name}, List]} ->
N = length(List),
throw({error,
io_lib:format("Unsupported type guard ~w/~w\n", [Name, N])})
end.
-constraints_fixpoint(Constrs, MFA, RecDict, ExpTypes, AllRecords) ->
+constraints_fixpoint(Constrs, MFA, RecDict, ExpTypes, AllRecords, Cache) ->
VarTable = erl_types:var_table__new(),
- VarDict =
- constraints_to_dict(Constrs, MFA, RecDict, ExpTypes, AllRecords, VarTable),
- constraints_fixpoint(VarDict, MFA, Constrs, RecDict, ExpTypes, AllRecords).
-
-constraints_fixpoint(OldVarDict, MFA, Constrs, RecDict, ExpTypes, AllRecords) ->
- NewVarDict =
- constraints_to_dict(Constrs, MFA, RecDict, ExpTypes, AllRecords, OldVarDict),
- case NewVarDict of
- OldVarDict ->
+ {VarTab, NewCache} =
+ constraints_to_dict(Constrs, MFA, RecDict, ExpTypes, AllRecords,
+ VarTable, Cache),
+ constraints_fixpoint(VarTab, MFA, Constrs, RecDict, ExpTypes,
+ AllRecords, NewCache).
+
+constraints_fixpoint(OldVarTab, MFA, Constrs, RecDict, ExpTypes,
+ AllRecords, Cache) ->
+ {NewVarTab, NewCache} =
+ constraints_to_dict(Constrs, MFA, RecDict, ExpTypes, AllRecords,
+ OldVarTab, Cache),
+ case NewVarTab of
+ OldVarTab ->
Fun =
fun(Key, Value, Acc) ->
[{subtype, erl_types:t_var(Key), Value}|Acc]
end,
- FinalConstrs = maps:fold(Fun, [], NewVarDict),
- {FinalConstrs, NewVarDict};
+ FinalConstrs = maps:fold(Fun, [], NewVarTab),
+ {FinalConstrs, NewVarTab, NewCache};
_Other ->
- constraints_fixpoint(NewVarDict, MFA, Constrs, RecDict, ExpTypes, AllRecords)
+ constraints_fixpoint(NewVarTab, MFA, Constrs, RecDict, ExpTypes,
+ AllRecords, NewCache)
end.
-final_form(Form, ExpTypes, MFA, AllRecords, VarDict) ->
- from_form_with_check(Form, ExpTypes, MFA, AllRecords, VarDict).
+final_form(Form, ExpTypes, MFA, AllRecords, VarTable, Cache) ->
+ from_form_with_check(Form, ExpTypes, MFA, AllRecords, VarTable, Cache).
-from_form_with_check(Form, ExpTypes, MFA, AllRecords) ->
+from_form_with_check(Form, ExpTypes, MFA, AllRecords, Cache) ->
VarTable = erl_types:var_table__new(),
- from_form_with_check(Form, ExpTypes, MFA, AllRecords, VarTable).
+ from_form_with_check(Form, ExpTypes, MFA, AllRecords, VarTable, Cache).
-from_form_with_check(Form, ExpTypes, MFA, AllRecords, VarDict) ->
+from_form_with_check(Form, ExpTypes, MFA, AllRecords, VarTable, Cache) ->
Site = {spec, MFA},
- erl_types:t_check_record_fields(Form, ExpTypes, Site, AllRecords, VarDict),
- erl_types:t_from_form(Form, ExpTypes, Site, AllRecords, VarDict).
-
-constraints_to_dict(Constrs, MFA, RecDict, ExpTypes, AllRecords, VarDict) ->
- Subtypes =
- constraints_to_subs(Constrs, MFA, RecDict, ExpTypes, AllRecords, VarDict, []),
- insert_constraints(Subtypes).
-
-constraints_to_subs([], _MFA, _RecDict, _ExpTypes, _AllRecords, _VarDict, Acc) ->
- Acc;
-constraints_to_subs([C|Rest], MFA, RecDict, ExpTypes, AllRecords, VarDict, Acc) ->
- {T1, Form2} = C,
- T2 = final_form(Form2, ExpTypes, MFA, AllRecords, VarDict),
+ C1 = erl_types:t_check_record_fields(Form, ExpTypes, Site, AllRecords,
+ VarTable, Cache),
+ erl_types:t_from_form(Form, ExpTypes, Site, AllRecords, VarTable, C1).
+
+constraints_to_dict(Constrs, MFA, RecDict, ExpTypes, AllRecords,
+ VarTab, Cache) ->
+ {Subtypes, NewCache} =
+ constraints_to_subs(Constrs, MFA, RecDict, ExpTypes, AllRecords,
+ VarTab, Cache, []),
+ {insert_constraints(Subtypes), NewCache}.
+
+constraints_to_subs([], _MFA, _RecDict, _ExpTypes, _AllRecords,
+ _VarTab, Cache, Acc) ->
+ {Acc, Cache};
+constraints_to_subs([{T1, Form2}|Rest], MFA, RecDict, ExpTypes, AllRecords,
+ VarTab, Cache, Acc) ->
+ {T2, NewCache} =
+ final_form(Form2, ExpTypes, MFA, AllRecords, VarTab, Cache),
NewAcc = [{subtype, T1, T2}|Acc],
- constraints_to_subs(Rest, MFA, RecDict, ExpTypes, AllRecords, VarDict, NewAcc).
+ constraints_to_subs(Rest, MFA, RecDict, ExpTypes, AllRecords,
+ VarTab, NewCache, NewAcc).
%% Replaces variables with '_' when necessary to break up cycles among
%% the constraints.
@@ -647,6 +679,7 @@ get_invalid_contract_warnings_funs([{MFA, {FileLine, Contract, _Xtra}}|Left],
{value, {Ret, Args}} ->
Sig = erl_types:t_fun(Args, Ret),
{M, _F, _A} = MFA,
+ %% io:format("MFA ~p~n", [MFA]),
Opaques = FindOpaques(M),
{File, Line} = FileLine,
WarningInfo = {File, Line, MFA},
@@ -795,7 +828,7 @@ is_remote_types_related(Contract, CSig, Sig, MFA, RecDict) ->
t_from_forms_without_remote([{FType, []}], MFA, RecDict) ->
Site = {spec, MFA},
- Type1 = erl_types:t_from_form_without_remote(FType, Site, RecDict),
+ {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) ->
%% 'When' constraints
diff --git a/lib/dialyzer/src/dialyzer_dataflow.erl b/lib/dialyzer/src/dialyzer_dataflow.erl
index 3349b12932..9399789464 100644
--- a/lib/dialyzer/src/dialyzer_dataflow.erl
+++ b/lib/dialyzer/src/dialyzer_dataflow.erl
@@ -522,7 +522,7 @@ handle_apply_or_call([{TypeOfApply, {Fun, Sig, Contr, LocalRet}}|Left],
?debug("RetWithoutLocal: ~s\n", [erl_types:t_to_string(RetWithoutLocal)]),
?debug("BifRet: ~s\n", [erl_types:t_to_string(BifRange(NewArgTypes))]),
?debug("SigRange: ~s\n", [erl_types:t_to_string(SigRange)]),
- ?debug("ContrRet: ~s\n", [erl_types:t_to_string(CRange(NewArgTypes))]),
+ ?debug("ContrRet: ~s\n", [erl_types:t_to_string(ContrRet)]),
?debug("LocalRet: ~s\n", [erl_types:t_to_string(LocalRet)]),
State1 =
@@ -2954,11 +2954,15 @@ is_call_to_send(Tree) ->
Arity = cerl:call_arity(Tree),
cerl:is_c_atom(Mod)
andalso cerl:is_c_atom(Name)
- andalso (cerl:atom_val(Name) =:= '!')
+ andalso is_send(cerl:atom_val(Name))
andalso (cerl:atom_val(Mod) =:= erlang)
andalso (Arity =:= 2)
end.
+is_send('!') -> true;
+is_send(send) -> true;
+is_send(_) -> false.
+
is_lc_simple_list(Tree, TreeType, State) ->
Opaques = State#state.opaques,
Ann = cerl:get_ann(Tree),
@@ -3067,7 +3071,10 @@ state__add_warning(#state{warnings = Warnings, warning_mode = true} = State,
false ->
WarningInfo = {get_file(Ann), get_line(Ann), State#state.curr_fun},
Warn = {Tag, WarningInfo, Msg},
- ?debug("MSG ~s\n", [dialyzer:format_warning(Warn)]),
+ case Tag of
+ ?WARN_CONTRACT_RANGE -> ok;
+ _ -> ?debug("MSG ~s\n", [dialyzer:format_warning(Warn)])
+ end,
State#state{warnings = [Warn|Warnings]}
end
end.
diff --git a/lib/dialyzer/src/dialyzer_utils.erl b/lib/dialyzer/src/dialyzer_utils.erl
index d37701f03b..76a5cf3d0b 100644
--- a/lib/dialyzer/src/dialyzer_utils.erl
+++ b/lib/dialyzer/src/dialyzer_utils.erl
@@ -194,15 +194,18 @@ get_core_from_abstract_code(AbstrCode, Opts) ->
%%
%% ============================================================================
+-type type_table() :: erl_types:type_table().
+-type mod_records() :: dict:dict(module(), type_table()).
+
-spec get_record_and_type_info(abstract_code()) ->
- {'ok', dict:dict()} | {'error', string()}.
+ {'ok', type_table()} | {'error', string()}.
get_record_and_type_info(AbstractCode) ->
Module = get_module(AbstractCode),
get_record_and_type_info(AbstractCode, Module, dict:new()).
--spec get_record_and_type_info(abstract_code(), module(), dict:dict()) ->
- {'ok', dict:dict()} | {'error', string()}.
+-spec get_record_and_type_info(abstract_code(), module(), type_table()) ->
+ {'ok', type_table()} | {'error', string()}.
get_record_and_type_info(AbstractCode, Module, RecDict) ->
get_record_and_type_info(AbstractCode, Module, RecDict, "nofile").
@@ -299,92 +302,117 @@ get_record_fields([], _RecDict, Acc) ->
process_record_remote_types(CServer) ->
TempRecords = dialyzer_codeserver:get_temp_records(CServer),
ExpTypes = dialyzer_codeserver:get_exported_types(CServer),
- TempRecords1 = process_opaque_types0(TempRecords, ExpTypes),
+ Cache = erl_types:cache__new(),
+ {TempRecords1, Cache1} =
+ process_opaque_types0(TempRecords, ExpTypes, Cache),
+ %% A cache (not the field type cache) is used for speeding things up a bit.
+ VarTable = erl_types:var_table__new(),
ModuleFun =
- fun(Module, Record) ->
+ fun({Module, Record}, C0) ->
RecordFun =
- fun(Key, Value) ->
+ fun({Key, Value}, C2) ->
case Key of
{record, Name} ->
FieldFun =
- fun(Arity, Fields) ->
+ fun({Arity, Fields}, C4) ->
Site = {record, {Module, Name, Arity}},
- [{FieldName, Field,
- erl_types:t_from_form(Field,
- ExpTypes,
- Site,
- TempRecords1)}
- || {FieldName, Field, _} <- Fields]
+ {Fields1, C7} =
+ lists:mapfoldl(fun({FieldName, Field, _}, C5) ->
+ {FieldT, C6} =
+ erl_types:t_from_form
+ (Field, ExpTypes, Site,
+ TempRecords1, VarTable,
+ C5),
+ {{FieldName, Field, FieldT}, C6}
+ end, C4, Fields),
+ {{Arity, Fields1}, C7}
end,
{FileLine, Fields} = Value,
- {FileLine, orddict:map(FieldFun, Fields)};
- _Other -> Value
+ {FieldsList, C3} =
+ lists:mapfoldl(FieldFun, C2, orddict:to_list(Fields)),
+ {{Key, {FileLine, orddict:from_list(FieldsList)}}, C3};
+ _Other -> {{Key, Value}, C2}
end
end,
- dict:map(RecordFun, Record)
+ {RecordList, C1} =
+ lists:mapfoldl(RecordFun, C0, dict:to_list(Record)),
+ {{Module, dict:from_list(RecordList)}, C1}
end,
- NewRecords = dict:map(ModuleFun, TempRecords1),
- ok = check_record_fields(NewRecords, ExpTypes),
+ {NewRecordsList, C1} =
+ lists:mapfoldl(ModuleFun, Cache1, dict:to_list(TempRecords1)),
+ NewRecords = dict:from_list(NewRecordsList),
+ _C8 = check_record_fields(NewRecords, ExpTypes, C1),
dialyzer_codeserver:finalize_records(NewRecords, CServer).
%% erl_types:t_from_form() substitutes the declaration of opaque types
%% for the expanded type in some cases. To make sure the initial type,
%% any(), is not used, the expansion is done twice.
%% XXX: Recursive opaque types are not handled well.
-process_opaque_types0(TempRecords0, TempExpTypes) ->
- TempRecords1 = process_opaque_types(TempRecords0, TempExpTypes),
- process_opaque_types(TempRecords1, TempExpTypes).
+process_opaque_types0(TempRecords0, TempExpTypes, Cache) ->
+ {TempRecords1, NewCache} =
+ process_opaque_types(TempRecords0, TempExpTypes, Cache),
+ process_opaque_types(TempRecords1, TempExpTypes, NewCache).
-process_opaque_types(TempRecords, TempExpTypes) ->
+process_opaque_types(TempRecords, TempExpTypes, Cache) ->
+ VarTable = erl_types:var_table__new(),
ModuleFun =
- fun(Module, Record) ->
+ fun({Module, Record}, C0) ->
RecordFun =
- fun(Key, Value) ->
+ fun({Key, Value}, C2) ->
case Key of
{opaque, Name, NArgs} ->
{{_Module, _FileLine, Form, _ArgNames}=F, _Type} = Value,
Site = {type, {Module, Name, NArgs}},
- Type = erl_types:t_from_form(Form, TempExpTypes, Site,
- TempRecords),
- {F, Type};
- _Other -> Value
+ {Type, C3} =
+ erl_types:t_from_form(Form, TempExpTypes, Site,
+ TempRecords, VarTable, C2),
+ {{Key, {F, Type}}, C3};
+ _Other -> {{Key, Value}, C2}
end
end,
- dict:map(RecordFun, Record)
+ {RecordList, C1} =
+ lists:mapfoldl(RecordFun, C0, dict:to_list(Record)),
+ {{Module, dict:from_list(RecordList)}, C1}
+ %% dict:map(RecordFun, Record)
end,
- dict:map(ModuleFun, TempRecords).
+ {TempRecordList, NewCache} =
+ lists:mapfoldl(ModuleFun, Cache, dict:to_list(TempRecords)),
+ {dict:from_list(TempRecordList), NewCache}.
+ %% dict:map(ModuleFun, TempRecords).
-check_record_fields(Records, TempExpTypes) ->
+check_record_fields(Records, TempExpTypes, Cache) ->
+ VarTable = erl_types:var_table__new(),
CheckFun =
- fun({Module, Element}) ->
- CheckForm = fun(Form, Site) ->
- erl_types:t_check_record_fields(Form, TempExpTypes,
- Site, Records)
+ fun({Module, Element}, C0) ->
+ CheckForm = fun(Form, Site, C1) ->
+ erl_types:t_check_record_fields(Form, TempExpTypes,
+ Site, Records,
+ VarTable, C1)
end,
ElemFun =
- fun({Key, Value}) ->
+ fun({Key, Value}, C2) ->
case Key of
{record, Name} ->
FieldFun =
- fun({Arity, Fields}) ->
+ fun({Arity, Fields}, C3) ->
Site = {record, {Module, Name, Arity}},
- _ = [ok = CheckForm(Field, Site) ||
- {_, Field, _} <- Fields],
- ok
+ lists:foldl(fun({_, Field, _}, C4) ->
+ CheckForm(Field, Site, C4)
+ end, C3, Fields)
end,
{FileLine, Fields} = Value,
- Fun = fun() -> lists:foreach(FieldFun, Fields) end,
+ Fun = fun() -> lists:foldl(FieldFun, C2, Fields) end,
msg_with_position(Fun, FileLine);
{_OpaqueOrType, Name, NArgs} ->
Site = {type, {Module, Name, NArgs}},
{{_Module, FileLine, Form, _ArgNames}, _Type} = Value,
- Fun = fun() -> ok = CheckForm(Form, Site) end,
+ Fun = fun() -> CheckForm(Form, Site, C2) end,
msg_with_position(Fun, FileLine)
end
end,
- lists:foreach(ElemFun, dict:to_list(Element))
+ lists:foldl(ElemFun, C0, dict:to_list(Element))
end,
- lists:foreach(CheckFun, dict:to_list(Records)).
+ lists:foldl(CheckFun, Cache, dict:to_list(Records)).
msg_with_position(Fun, FileLine) ->
try Fun()
@@ -396,7 +424,7 @@ msg_with_position(Fun, FileLine) ->
throw({error, NewMsg})
end.
--spec merge_records(dict:dict(), dict:dict()) -> dict:dict().
+-spec merge_records(mod_records(), mod_records()) -> mod_records().
merge_records(NewRecords, OldRecords) ->
dict:merge(fun(_Key, NewVal, _OldVal) -> NewVal end, NewRecords, OldRecords).
@@ -410,7 +438,7 @@ merge_records(NewRecords, OldRecords) ->
-type spec_dict() :: dict:dict().
-type callback_dict() :: dict:dict().
--spec get_spec_info(module(), abstract_code(), dict:dict()) ->
+-spec get_spec_info(module(), abstract_code(), type_table()) ->
{'ok', spec_dict(), callback_dict()} | {'error', string()}.
get_spec_info(ModName, AbstractCode, RecordsDict) ->
@@ -676,7 +704,7 @@ format_errors([]) ->
format_sig(Type) ->
format_sig(Type, dict:new()).
--spec format_sig(erl_types:erl_type(), dict:dict()) -> string().
+-spec format_sig(erl_types:erl_type(), type_table()) -> string().
format_sig(Type, RecDict) ->
"fun(" ++ Sig = lists:flatten(erl_types:t_to_string(Type, RecDict)),
diff --git a/lib/dialyzer/test/unmatched_returns_SUITE_data/src/send.erl b/lib/dialyzer/test/unmatched_returns_SUITE_data/src/send.erl
new file mode 100644
index 0000000000..4d681b5cc7
--- /dev/null
+++ b/lib/dialyzer/test/unmatched_returns_SUITE_data/src/send.erl
@@ -0,0 +1,11 @@
+-module(send).
+
+-export([s/0]).
+
+s() ->
+ self() ! n(), % no warning
+ erlang:send(self(), n()), % no warning
+ ok.
+
+n() ->
+ {1, 1}.