aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--bootstrap/lib/stdlib/ebin/erl_parse.beambin82864 -> 82984 bytes
-rw-r--r--erts/doc/src/absform.xml4
-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
-rw-r--r--lib/hipe/cerl/erl_types.erl903
-rw-r--r--lib/stdlib/doc/src/erl_id_trans.xml3
-rw-r--r--lib/stdlib/doc/src/erl_parse.xml8
-rw-r--r--lib/stdlib/src/erl_expand_records.erl5
-rw-r--r--lib/stdlib/src/erl_lint.erl8
-rw-r--r--lib/stdlib/src/erl_parse.yrl36
-rw-r--r--lib/stdlib/src/erl_pp.erl4
-rw-r--r--lib/stdlib/src/lib.erl2
-rw-r--r--lib/stdlib/src/ms_transform.erl7
-rw-r--r--lib/stdlib/src/proplists.erl5
-rw-r--r--lib/stdlib/src/qlc.erl7
-rw-r--r--lib/stdlib/src/qlc_pt.erl18
-rw-r--r--lib/stdlib/src/sofs.erl3
-rw-r--r--lib/syntax_tools/src/Makefile2
-rw-r--r--lib/syntax_tools/src/erl_recomment.erl8
-rw-r--r--lib/syntax_tools/src/erl_syntax.erl9
22 files changed, 774 insertions, 565 deletions
diff --git a/bootstrap/lib/stdlib/ebin/erl_parse.beam b/bootstrap/lib/stdlib/ebin/erl_parse.beam
index 9b04739d58..3baf38cc72 100644
--- a/bootstrap/lib/stdlib/ebin/erl_parse.beam
+++ b/bootstrap/lib/stdlib/ebin/erl_parse.beam
Binary files differ
diff --git a/erts/doc/src/absform.xml b/erts/doc/src/absform.xml
index bfabb7f042..0b04f8f70e 100644
--- a/erts/doc/src/absform.xml
+++ b/erts/doc/src/absform.xml
@@ -152,9 +152,11 @@
<list type="bulleted">
<item>If L is an atom literal, then
Rep(L) = <c>{atom,LINE,L}</c>.</item>
+ <item>If L is a character literal, then
+ Rep(L) = <c>{char,LINE,L}</c>.</item>
<item>If L is a float literal, then
Rep(L) = <c>{float,LINE,L}</c>.</item>
- <item>If L is an integer or character literal, then
+ <item>If L is an integer literal, then
Rep(L) = <c>{integer,LINE,L}</c>.</item>
<item>If L is a string literal consisting of the characters
<c>C_1</c>, ..., <c>C_k</c>, then
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}.
diff --git a/lib/hipe/cerl/erl_types.erl b/lib/hipe/cerl/erl_types.erl
index 705fc73613..7826dada9d 100644
--- a/lib/hipe/cerl/erl_types.erl
+++ b/lib/hipe/cerl/erl_types.erl
@@ -80,11 +80,9 @@
t_float/0,
t_var_names/1,
t_form_to_string/1,
- t_from_form/4,
- t_from_form/5,
+ t_from_form/6,
t_from_form_without_remote/3,
- t_check_record_fields/4,
- t_check_record_fields/5,
+ t_check_record_fields/6,
t_from_range/2,
t_from_range_unsafe/2,
t_from_term/1,
@@ -221,6 +219,7 @@
is_erl_type/1,
atom_to_string/1,
var_table__new/0,
+ cache__new/0,
map_pairwise_merge/3
]).
@@ -237,7 +236,7 @@
-export([t_is_identifier/1]).
-endif.
--export_type([erl_type/0, opaques/0, type_table/0, var_table/0]).
+-export_type([erl_type/0, opaques/0, type_table/0, var_table/0, cache/0]).
%%-define(DEBUG, true).
@@ -328,7 +327,7 @@
%% Auxiliary types and convenient macros
%%
--type parse_form() :: erl_parse:abstract_expr().
+-type parse_form() :: erl_parse:abstract_type().
-type rng_elem() :: 'pos_inf' | 'neg_inf' | integer().
-record(int_set, {set :: [integer()]}).
@@ -375,9 +374,11 @@
-type opaques() :: [erl_type()] | 'universe'.
-type record_key() :: {'record', atom()}.
--type type_key() :: {'type' | 'opaque', atom(), arity()}.
+-type type_key() :: {'type' | 'opaque', mfa()}.
-type record_value() :: [{atom(), erl_parse:abstract_expr(), erl_type()}].
--type type_value() :: {module(), erl_type(), atom()}.
+-type type_value() :: {{module(), {file:name(), erl_anno:line()},
+ erl_parse:abstract_type(), ArgNames :: [atom()]},
+ erl_type()}.
-type type_table() :: dict:dict(record_key() | type_key(),
record_value() | type_value()).
@@ -757,8 +758,8 @@ t_opaque_from_records(RecDict) ->
{{Module, _FileLine, _Form, ArgNames}, _Type}) ->
%% Args = args_to_types(ArgNames),
%% List = lists:zip(ArgNames, Args),
- %% TmpVarDict = dict:from_list(List),
- %% Rep = t_from_form(Type, RecDict, TmpVarDict),
+ %% TmpVarTab = maps:to_list(List),
+ %% Rep = t_from_form(Type, RecDict, TmpVarTab),
Rep = t_any(), % not used for anything right now
Args = [t_any() || _ <- ArgNames],
t_opaque(Module, Name, Args, Rep)
@@ -1769,7 +1770,8 @@ mapdict_insert(E={_,_,_}, T) -> [E|T].
t_map_mandatoriness(), erl_type())
-> t_map_pair() | false),
erl_type(), erl_type()) -> t_map_dict().
-map_pairwise_merge(F, ?map(APairs, ADefK, ADefV), ?map(BPairs, BDefK, BDefV)) ->
+map_pairwise_merge(F, ?map(APairs, ADefK, ADefV),
+ ?map(BPairs, BDefK, BDefV)) ->
map_pairwise_merge(F, APairs, ADefK, ADefV, BPairs, BDefK, BDefV).
map_pairwise_merge(_, [], _, _, [], _, _) -> [];
@@ -4413,33 +4415,30 @@ mod_name(Mod, Name) ->
-type type_names() :: [type_key() | record_key()].
--type mta() :: {module(), atom(), arity()}.
--type mra() :: {module(), atom(), arity()}.
--type site() :: {'type', mta()} | {'spec', mfa()} | {'record', mra()}.
+-type mta() :: {module(), atom(), arity()}.
+-type mra() :: {module(), atom(), arity()}.
+-type site() :: {'type', mta()} | {'spec', mfa()} | {'record', mra()}.
+-type cache_key() :: {module(), atom(), expand_depth(),
+ [erl_type()], type_names()}.
+-opaque cache() :: #{cache_key() => {erl_type(), expand_limit()}}.
--spec t_from_form(parse_form(), sets:set(mfa()),
- site(), mod_records()) -> erl_type().
+-spec t_from_form(parse_form(), sets:set(mfa()), site(), mod_records(),
+ var_table(), cache()) -> {erl_type(), cache()}.
-t_from_form(Form, ExpTypes, Site, RecDict) ->
- t_from_form(Form, ExpTypes, Site, RecDict, maps:new()).
-
--spec t_from_form(parse_form(), sets:set(mfa()),
- site(), mod_records(), var_table()) -> erl_type().
-
-t_from_form(Form, ExpTypes, Site, RecDict, VarDict) ->
- {T, _} = t_from_form1(Form, ExpTypes, Site, RecDict, VarDict),
- T.
+t_from_form(Form, ExpTypes, Site, RecDict, VarTab, Cache) ->
+ t_from_form1(Form, ExpTypes, Site, RecDict, VarTab, Cache).
%% Replace external types with with none().
-spec t_from_form_without_remote(parse_form(), site(), type_table()) ->
- erl_type().
+ {erl_type(), cache()}.
t_from_form_without_remote(Form, Site, TypeTable) ->
Module = site_module(Site),
RecDict = dict:from_list([{Module, TypeTable}]),
ExpTypes = replace_by_none,
- {T, _} = t_from_form1(Form, ExpTypes, Site, RecDict, maps:new()),
- T.
+ VarTab = var_table__new(),
+ Cache = cache__new(),
+ t_from_form1(Form, ExpTypes, Site, RecDict, VarTab, Cache).
%% REC_TYPE_LIMIT is used for limiting the depth of recursive types.
%% EXPAND_LIMIT is used for limiting the size of types by
@@ -4452,34 +4451,53 @@ t_from_form_without_remote(Form, Site, TypeTable) ->
-type expand_depth() :: integer().
+-record(from_form, {site :: site(),
+ xtypes :: sets:set(mfa()) | 'replace_by_none',
+ mrecs :: mod_records(),
+ vtab :: var_table(),
+ tnames :: type_names()}).
+
-spec t_from_form1(parse_form(), sets:set(mfa()) | 'replace_by_none',
- site(), mod_records(), var_table()) ->
- {erl_type(), expand_limit()}.
+ site(), mod_records(), var_table(), cache()) ->
+ {erl_type(), cache()}.
-t_from_form1(Form, ET, Site, MR, V) ->
+t_from_form1(Form, ET, Site, MR, V, C) ->
TypeNames = initial_typenames(Site),
- t_from_form1(Form, TypeNames, ET, Site, MR, V, ?EXPAND_DEPTH).
+ State = #from_form{site = Site,
+ xtypes = ET,
+ mrecs = MR,
+ vtab = V,
+ tnames = TypeNames},
+ L = ?EXPAND_LIMIT,
+ {T1, L1, C1} = from_form(Form, State, ?EXPAND_DEPTH, L, C),
+ if
+ L1 =< 0 ->
+ from_form_loop(Form, State, 1, L, C1);
+ true ->
+ {T1, C1}
+ end.
initial_typenames({type, _MTA}=Site) -> [Site];
initial_typenames({spec, _MFA}) -> [];
initial_typenames({record, _MRA}) -> [].
-t_from_form1(Form, TypeNames, ET, Site, MR, V, D) ->
- L = ?EXPAND_LIMIT,
- {T, L1} = t_from_form(Form, TypeNames, ET, Site, MR, V, D, L),
+from_form_loop(Form, State, D, Limit, C) ->
+ {T1, L1, C1} = from_form(Form, State, D, Limit, C),
+ Delta = Limit - L1,
if
- L1 =< 0, D > 1 ->
- D1 = D div 2,
- t_from_form1(Form, TypeNames, ET, Site, MR, V, D1);
+ %% Save some time by assuming next depth will exceed the limit.
+ Delta * 8 > Limit ->
+ {T1, C1};
true ->
- {T, L1}
+ D1 = D + 1,
+ from_form_loop(Form, State, D1, Limit, C1)
end.
--spec t_from_form(parse_form(), type_names(),
- sets:set(mfa()) | 'replace_by_none',
- site(), mod_records(), var_table(),
- expand_depth(), expand_limit())
- -> {erl_type(), expand_limit()}.
+-spec from_form(parse_form(),
+ #from_form{},
+ expand_depth(),
+ expand_limit(),
+ cache()) -> {erl_type(), expand_limit(), cache()}.
%% If there is something wrong with parse_form()
%% throw({error, io_lib:chars()} is called;
@@ -4489,330 +4507,336 @@ t_from_form1(Form, TypeNames, ET, Site, MR, V, D) ->
%%
%% It is assumed that site_module(S) can be found in MR.
-t_from_form(_, _TypeNames, _ET, _S, _MR, _V, D, L) when D =< 0 ; L =< 0 ->
- {t_any(), L};
-t_from_form({var, _L, '_'}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_any(), L};
-t_from_form({var, _L, Name}, _TypeNames, _ET, _S, _MR, V, _D, L) ->
+from_form(_, _S, D, L, C) when D =< 0 ; L =< 0 ->
+ {t_any(), L, C};
+from_form({var, _L, '_'}, _S, _D, L, C) ->
+ {t_any(), L, C};
+from_form({var, _L, Name}, S, _D, L, C) ->
+ V = S#from_form.vtab,
case maps:find(Name, V) of
- error -> {t_var(Name), L};
- {ok, Val} -> {Val, L}
+ error -> {t_var(Name), L, C};
+ {ok, Val} -> {Val, L, C}
end;
-t_from_form({ann_type, _L, [_Var, Type]}, TypeNames, ET, S, MR, V, D, L) ->
- t_from_form(Type, TypeNames, ET, S, MR, V, D, L);
-t_from_form({paren_type, _L, [Type]}, TypeNames, ET, S, MR, V, D, L) ->
- t_from_form(Type, TypeNames, ET, S, MR, V, D, L);
-t_from_form({remote_type, _L, [{atom, _, Module}, {atom, _, Type}, Args]},
- TypeNames, ET, S, MR, V, D, L) ->
- remote_from_form(Module, Type, Args, TypeNames, ET, S, MR, V, D, L);
-t_from_form({atom, _L, Atom}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_atom(Atom), L};
-t_from_form({integer, _L, Int}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_integer(Int), L};
-t_from_form({op, _L, _Op, _Arg} = Op, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
+from_form({ann_type, _L, [_Var, Type]}, S, D, L, C) ->
+ from_form(Type, S, D, L, C);
+from_form({paren_type, _L, [Type]}, S, D, L, C) ->
+ from_form(Type, S, D, L, C);
+from_form({remote_type, _L, [{atom, _, Module}, {atom, _, Type}, Args]},
+ S, D, L, C) ->
+ remote_from_form(Module, Type, Args, S, D, L, C);
+from_form({atom, _L, Atom}, _S, _D, L, C) ->
+ {t_atom(Atom), L, C};
+from_form({integer, _L, Int}, _S, _D, L, C) ->
+ {t_integer(Int), L, C};
+from_form({op, _L, _Op, _Arg} = Op, _S, _D, L, C) ->
case erl_eval:partial_eval(Op) of
{integer, _, Val} ->
- {t_integer(Val), L};
+ {t_integer(Val), L, C};
_ -> throw({error, io_lib:format("Unable to evaluate type ~w\n", [Op])})
end;
-t_from_form({op, _L, _Op, _Arg1, _Arg2} = Op, _TypeNames,
- _ET, _S, _MR, _V, _D, L) ->
+from_form({op, _L, _Op, _Arg1, _Arg2} = Op, _S, _D, L, C) ->
case erl_eval:partial_eval(Op) of
{integer, _, Val} ->
- {t_integer(Val), L};
+ {t_integer(Val), L, C};
_ -> throw({error, io_lib:format("Unable to evaluate type ~w\n", [Op])})
end;
-t_from_form({type, _L, any, []}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_any(), L};
-t_from_form({type, _L, arity, []}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_arity(), L};
-t_from_form({type, _L, atom, []}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_atom(), L};
-t_from_form({type, _L, binary, []}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_binary(), L};
-t_from_form({type, _L, binary, [Base, Unit]} = Type,
- _TypeNames, _ET, _S, _MR, _V, _D, L) ->
+from_form({type, _L, any, []}, _S, _D, L, C) ->
+ {t_any(), L, C};
+from_form({type, _L, arity, []}, _S, _D, L, C) ->
+ {t_arity(), L, C};
+from_form({type, _L, atom, []}, _S, _D, L, C) ->
+ {t_atom(), L, C};
+from_form({type, _L, binary, []}, _S, _D, L, C) ->
+ {t_binary(), L, C};
+from_form({type, _L, binary, [Base, Unit]} = Type, _S, _D, L, C) ->
case {erl_eval:partial_eval(Base), erl_eval:partial_eval(Unit)} of
{{integer, _, B}, {integer, _, U}} when B >= 0, U >= 0 ->
- {t_bitstr(U, B), L};
+ {t_bitstr(U, B), L, C};
_ -> throw({error, io_lib:format("Unable to evaluate type ~w\n", [Type])})
end;
-t_from_form({type, _L, bitstring, []}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_bitstr(), L};
-t_from_form({type, _L, bool, []}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_boolean(), L}; % XXX: Temporarily
-t_from_form({type, _L, boolean, []}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_boolean(), L};
-t_from_form({type, _L, byte, []}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_byte(), L};
-t_from_form({type, _L, char, []}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_char(), L};
-t_from_form({type, _L, float, []}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_float(), L};
-t_from_form({type, _L, function, []}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_fun(), L};
-t_from_form({type, _L, 'fun', []}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_fun(), L};
-t_from_form({type, _L, 'fun', [{type, _, any}, Range]}, TypeNames,
- ET, S, MR, V, D, L) ->
- {T, L1} = t_from_form(Range, TypeNames, ET, S, MR, V, D - 1, L - 1),
- {t_fun(T), L1};
-t_from_form({type, _L, 'fun', [{type, _, product, Domain}, Range]},
- TypeNames, ET, S, MR, V, D, L) ->
- {Dom1, L1} = list_from_form(Domain, TypeNames, ET, S, MR, V, D, L),
- {Ran1, L2} = t_from_form(Range, TypeNames, ET, S, MR, V, D, L1),
- {t_fun(Dom1, Ran1), L2};
-t_from_form({type, _L, identifier, []}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_identifier(), L};
-t_from_form({type, _L, integer, []}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_integer(), L};
-t_from_form({type, _L, iodata, []}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_iodata(), L};
-t_from_form({type, _L, iolist, []}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_iolist(), L};
-t_from_form({type, _L, list, []}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_list(), L};
-t_from_form({type, _L, list, [Type]}, TypeNames, ET, S, MR, V, D, L) ->
- {T, L1} = t_from_form(Type, TypeNames, ET, S, MR, V, D - 1, L - 1),
- {t_list(T), L1};
-t_from_form({type, _L, map, any}, TypeNames, ET, S, MR, V, D, L) ->
- builtin_type(map, t_map(), TypeNames, ET, S, MR, V, D, L);
-t_from_form({type, _L, map, List}, TypeNames, ET, S, MR, V, D, L) ->
- {Pairs1, L5} =
- fun PairsFromForm(_, L1) when L1 =< 0 -> {[{?any,?opt,?any}], L1};
- PairsFromForm([], L1) -> {[], L1};
- PairsFromForm([{type, _, Oper, [KF, VF]}|T], L1) ->
- {Key, L2} = t_from_form(KF, TypeNames, ET, S, MR, V, D - 1, L1),
- {Val, L3} = t_from_form(VF, TypeNames, ET, S, MR, V, D - 1, L2),
- {Pairs0, L4} = PairsFromForm(T, L3 - 1),
+from_form({type, _L, bitstring, []}, _S, _D, L, C) ->
+ {t_bitstr(), L, C};
+from_form({type, _L, bool, []}, _S, _D, L, C) ->
+ {t_boolean(), L, C}; % XXX: Temporarily
+from_form({type, _L, boolean, []}, _S, _D, L, C) ->
+ {t_boolean(), L, C};
+from_form({type, _L, byte, []}, _S, _D, L, C) ->
+ {t_byte(), L, C};
+from_form({type, _L, char, []}, _S, _D, L, C) ->
+ {t_char(), L, C};
+from_form({type, _L, float, []}, _S, _D, L, C) ->
+ {t_float(), L, C};
+from_form({type, _L, function, []}, _S, _D, L, C) ->
+ {t_fun(), L, C};
+from_form({type, _L, 'fun', []}, _S, _D, L, C) ->
+ {t_fun(), L, C};
+from_form({type, _L, 'fun', [{type, _, any}, Range]}, S, D, L, C) ->
+ {T, L1, C1} = from_form(Range, S, D - 1, L - 1, C),
+ {t_fun(T), L1, C1};
+from_form({type, _L, 'fun', [{type, _, product, Domain}, Range]},
+ S, D, L, C) ->
+ {Dom1, L1, C1} = list_from_form(Domain, S, D, L, C),
+ {Ran1, L2, C2} = from_form(Range, S, D, L1, C1),
+ {t_fun(Dom1, Ran1), L2, C2};
+from_form({type, _L, identifier, []}, _S, _D, L, C) ->
+ {t_identifier(), L, C};
+from_form({type, _L, integer, []}, _S, _D, L, C) ->
+ {t_integer(), L, C};
+from_form({type, _L, iodata, []}, _S, _D, L, C) ->
+ {t_iodata(), L, C};
+from_form({type, _L, iolist, []}, _S, _D, L, C) ->
+ {t_iolist(), L, C};
+from_form({type, _L, list, []}, _S, _D, L, C) ->
+ {t_list(), L, C};
+from_form({type, _L, list, [Type]}, S, D, L, C) ->
+ {T, L1, C1} = from_form(Type, S, D - 1, L - 1, C),
+ {t_list(T), L1, C1};
+from_form({type, _L, map, any}, S, D, L, C) ->
+ builtin_type(map, t_map(), S, D, L, C);
+from_form({type, _L, map, List}, S, D0, L, C) ->
+ {Pairs1, L5, C5} =
+ fun PairsFromForm(_, L1, C1) when L1 =< 0 -> {[{?any,?opt,?any}], L1, C1};
+ PairsFromForm([], L1, C1) -> {[], L1, C1};
+ PairsFromForm([{type, _, Oper, [KF, VF]}|T], L1, C1) ->
+ D = D0 - 1,
+ {Key, L2, C2} = from_form(KF, S, D, L1, C1),
+ {Val, L3, C3} = from_form(VF, S, D, L2, C2),
+ {Pairs0, L4, C4} = PairsFromForm(T, L3 - 1, C3),
case Oper of
- map_field_assoc -> {[{Key,?opt, Val}|Pairs0], L4};
- map_field_exact -> {[{Key,?mand,Val}|Pairs0], L4}
+ map_field_assoc -> {[{Key,?opt, Val}|Pairs0], L4, C4};
+ map_field_exact -> {[{Key,?mand,Val}|Pairs0], L4, C4}
end
- end(List, L),
+ end(List, L, C),
try
{Pairs, DefK, DefV} = map_from_form(Pairs1, [], [], [], ?none, ?none),
- {t_map(Pairs, DefK, DefV), L5}
- catch none -> {t_none(), L5}
+ {t_map(Pairs, DefK, DefV), L5, C5}
+ catch none -> {t_none(), L5, C5}
end;
-t_from_form({type, _L, mfa, []}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_mfa(), L};
-t_from_form({type, _L, module, []}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_module(), L};
-t_from_form({type, _L, nil, []}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_nil(), L};
-t_from_form({type, _L, neg_integer, []}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_neg_integer(), L};
-t_from_form({type, _L, non_neg_integer, []}, _TypeNames, _ET, _S, _MR,
- _V, _D, L) ->
- {t_non_neg_integer(), L};
-t_from_form({type, _L, no_return, []}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_unit(), L};
-t_from_form({type, _L, node, []}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_node(), L};
-t_from_form({type, _L, none, []}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_none(), L};
-t_from_form({type, _L, nonempty_list, []}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_nonempty_list(), L};
-t_from_form({type, _L, nonempty_list, [Type]}, TypeNames, ET, S, MR, V, D, L) ->
- {T, L1} = t_from_form(Type, TypeNames, ET, S, MR, V, D, L - 1),
- {t_nonempty_list(T), L1};
-t_from_form({type, _L, nonempty_improper_list, [Cont, Term]}, TypeNames,
- ET, S, MR, V, D, L) ->
- {T1, L1} = t_from_form(Cont, TypeNames, ET, S, MR, V, D, L - 1),
- {T2, L2} = t_from_form(Term, TypeNames, ET, S, MR, V, D, L1),
- {t_cons(T1, T2), L2};
-t_from_form({type, _L, nonempty_maybe_improper_list, []}, _TypeNames,
- _ET, _S, _MR, _V, _D, L) ->
- {t_cons(?any, ?any), L};
-t_from_form({type, _L, nonempty_maybe_improper_list, [Cont, Term]},
- TypeNames, ET, S, MR, V, D, L) ->
- {T1, L1} = t_from_form(Cont, TypeNames, ET, S, MR, V, D, L - 1),
- {T2, L2} = t_from_form(Term, TypeNames, ET, S, MR, V, D, L1),
- {t_cons(T1, T2), L2};
-t_from_form({type, _L, nonempty_string, []}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_nonempty_string(), L};
-t_from_form({type, _L, number, []}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_number(), L};
-t_from_form({type, _L, pid, []}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_pid(), L};
-t_from_form({type, _L, port, []}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_port(), L};
-t_from_form({type, _L, pos_integer, []}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_pos_integer(), L};
-t_from_form({type, _L, maybe_improper_list, []}, _TypeNames,
- _ET, _S, _MR, _V, _D, L) ->
- {t_maybe_improper_list(), L};
-t_from_form({type, _L, maybe_improper_list, [Content, Termination]},
- TypeNames, ET, S, MR, V, D, L) ->
- {T1, L1} = t_from_form(Content, TypeNames, ET, S, MR, V, D, L - 1),
- {T2, L2} = t_from_form(Termination, TypeNames, ET, S, MR, V, D, L1),
- {t_maybe_improper_list(T1, T2), L2};
-t_from_form({type, _L, product, Elements}, TypeNames, ET, S, MR, V, D, L) ->
- {Lst, L1} = list_from_form(Elements, TypeNames, ET, S, MR, V, D - 1, L),
- {t_product(Lst), L1};
-t_from_form({type, _L, range, [From, To]} = Type,
- _TypeNames, _ET, _S, _MR, _V, _D, L) ->
+from_form({type, _L, mfa, []}, _S, _D, L, C) ->
+ {t_mfa(), L, C};
+from_form({type, _L, module, []}, _S, _D, L, C) ->
+ {t_module(), L, C};
+from_form({type, _L, nil, []}, _S, _D, L, C) ->
+ {t_nil(), L, C};
+from_form({type, _L, neg_integer, []}, _S, _D, L, C) ->
+ {t_neg_integer(), L, C};
+from_form({type, _L, non_neg_integer, []}, _S, _D, L, C) ->
+ {t_non_neg_integer(), L, C};
+from_form({type, _L, no_return, []}, _S, _D, L, C) ->
+ {t_unit(), L, C};
+from_form({type, _L, node, []}, _S, _D, L, C) ->
+ {t_node(), L, C};
+from_form({type, _L, none, []}, _S, _D, L, C) ->
+ {t_none(), L, C};
+from_form({type, _L, nonempty_list, []}, _S, _D, L, C) ->
+ {t_nonempty_list(), L, C};
+from_form({type, _L, nonempty_list, [Type]}, S, D, L, C) ->
+ {T, L1, C1} = from_form(Type, S, D, L - 1, C),
+ {t_nonempty_list(T), L1, C1};
+from_form({type, _L, nonempty_improper_list, [Cont, Term]}, S, D, L, C) ->
+ {T1, L1, C1} = from_form(Cont, S, D, L - 1, C),
+ {T2, L2, C2} = from_form(Term, S, D, L1, C1),
+ {t_cons(T1, T2), L2, C2};
+from_form({type, _L, nonempty_maybe_improper_list, []}, _S, _D, L, C) ->
+ {t_cons(?any, ?any), L, C};
+from_form({type, _L, nonempty_maybe_improper_list, [Cont, Term]},
+ S, D, L, C) ->
+ {T1, L1, C1} = from_form(Cont, S, D, L - 1, C),
+ {T2, L2, C2} = from_form(Term, S, D, L1, C1),
+ {t_cons(T1, T2), L2, C2};
+from_form({type, _L, nonempty_string, []}, _S, _D, L, C) ->
+ {t_nonempty_string(), L, C};
+from_form({type, _L, number, []}, _S, _D, L, C) ->
+ {t_number(), L, C};
+from_form({type, _L, pid, []}, _S, _D, L, C) ->
+ {t_pid(), L, C};
+from_form({type, _L, port, []}, _S, _D, L, C) ->
+ {t_port(), L, C};
+from_form({type, _L, pos_integer, []}, _S, _D, L, C) ->
+ {t_pos_integer(), L, C};
+from_form({type, _L, maybe_improper_list, []}, _S, _D, L, C) ->
+ {t_maybe_improper_list(), L, C};
+from_form({type, _L, maybe_improper_list, [Content, Termination]},
+ S, D, L, C) ->
+ {T1, L1, C1} = from_form(Content, S, D, L - 1, C),
+ {T2, L2, C2} = from_form(Termination, S, D, L1, C1),
+ {t_maybe_improper_list(T1, T2), L2, C2};
+from_form({type, _L, product, Elements}, S, D, L, C) ->
+ {Lst, L1, C1} = list_from_form(Elements, S, D - 1, L, C),
+ {t_product(Lst), L1, C1};
+from_form({type, _L, range, [From, To]} = Type, _S, _D, L, C) ->
case {erl_eval:partial_eval(From), erl_eval:partial_eval(To)} of
{{integer, _, FromVal}, {integer, _, ToVal}} ->
- {t_from_range(FromVal, ToVal), L};
+ {t_from_range(FromVal, ToVal), L, C};
_ -> throw({error, io_lib:format("Unable to evaluate type ~w\n", [Type])})
end;
-t_from_form({type, _L, record, [Name|Fields]}, TypeNames, ET, S, MR, V, D, L) ->
- record_from_form(Name, Fields, TypeNames, ET, S, MR, V, D, L);
-t_from_form({type, _L, reference, []}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_reference(), L};
-t_from_form({type, _L, string, []}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_string(), L};
-t_from_form({type, _L, term, []}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_any(), L};
-t_from_form({type, _L, timeout, []}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_timeout(), L};
-t_from_form({type, _L, tuple, any}, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {t_tuple(), L};
-t_from_form({type, _L, tuple, Args}, TypeNames, ET, S, MR, V, D, L) ->
- {Lst, L1} = list_from_form(Args, TypeNames, ET, S, MR, V, D - 1, L),
- {t_tuple(Lst), L1};
-t_from_form({type, _L, union, Args}, TypeNames, ET, S, MR, V, D, L) ->
- {Lst, L1} = list_from_form(Args, TypeNames, ET, S, MR, V, D, L),
- {t_sup(Lst), L1};
-t_from_form({user_type, _L, Name, Args}, TypeNames, ET, S, MR, V, D, L) ->
- type_from_form(Name, Args, TypeNames, ET, S, MR, V, D, L);
-t_from_form({type, _L, Name, Args}, TypeNames, ET, S, MR, V, D, L) ->
+from_form({type, _L, record, [Name|Fields]}, S, D, L, C) ->
+ record_from_form(Name, Fields, S, D, L, C);
+from_form({type, _L, reference, []}, _S, _D, L, C) ->
+ {t_reference(), L, C};
+from_form({type, _L, string, []}, _S, _D, L, C) ->
+ {t_string(), L, C};
+from_form({type, _L, term, []}, _S, _D, L, C) ->
+ {t_any(), L, C};
+from_form({type, _L, timeout, []}, _S, _D, L, C) ->
+ {t_timeout(), L, C};
+from_form({type, _L, tuple, any}, _S, _D, L, C) ->
+ {t_tuple(), L, C};
+from_form({type, _L, tuple, Args}, S, D, L, C) ->
+ {Lst, L1, C1} = list_from_form(Args, S, D - 1, L, C),
+ {t_tuple(Lst), L1, C1};
+from_form({type, _L, union, Args}, S, D, L, C) ->
+ {Lst, L1, C1} = list_from_form(Args, S, D, L, C),
+ {t_sup(Lst), L1, C1};
+from_form({user_type, _L, Name, Args}, S, D, L, C) ->
+ type_from_form(Name, Args, S, D, L, C);
+from_form({type, _L, Name, Args}, S, D, L, C) ->
%% Compatibility: modules compiled before Erlang/OTP 18.0.
- type_from_form(Name, Args, TypeNames, ET, S, MR, V, D, L);
-t_from_form({opaque, _L, Name, {Mod, Args, Rep}}, _TypeNames,
- _ET, _S, _MR, _V, _D, L) ->
+ type_from_form(Name, Args, S, D, L, C);
+from_form({opaque, _L, Name, {Mod, Args, Rep}}, _S, _D, L, C) ->
%% XXX. To be removed.
- {t_opaque(Mod, Name, Args, Rep), L}.
+ {t_opaque(Mod, Name, Args, Rep), L, C}.
-builtin_type(Name, Type, TypeNames, ET, Site, MR, V, D, L) ->
+builtin_type(Name, Type, S, D, L, C) ->
+ #from_form{site = Site, mrecs = MR} = S,
M = site_module(Site),
case dict:find(M, MR) of
{ok, R} ->
case lookup_type(Name, 0, R) of
{_, {{_M, _FL, _F, _A}, _T}} ->
- type_from_form(Name, [], TypeNames, ET, Site, MR, V, D, L);
+ type_from_form(Name, [], S, D, L, C);
error ->
- {Type, L}
+ {Type, L, C}
end;
error ->
- {Type, L}
+ {Type, L, C}
end.
-type_from_form(Name, Args, TypeNames, ET, Site0, MR, V, D, L) ->
+type_from_form(Name, Args, S, D, L, C) ->
+ #from_form{site = Site, mrecs = MR, tnames = TypeNames} = S,
ArgsLen = length(Args),
- Module = site_module(Site0),
- {ok, R} = dict:find(Module, MR),
+ Module = site_module(Site),
TypeName = {type, {Module, Name, ArgsLen}},
+ case can_unfold_more(TypeName, TypeNames) of
+ true ->
+ {ok, R} = dict:find(Module, MR),
+ type_from_form1(Name, Args, ArgsLen, R, TypeName, TypeNames,
+ S, D, L, C);
+ false ->
+ {t_any(), L, C}
+ end.
+
+type_from_form1(Name, Args, ArgsLen, R, TypeName, TypeNames, S, D, L, C) ->
case lookup_type(Name, ArgsLen, R) of
- {type, {{Module, _FileName, Form, ArgNames}, _Type}} ->
- case can_unfold_more(TypeName, TypeNames) of
- true ->
- NewTypeNames = [TypeName|TypeNames],
- {ArgTypes, L1} =
- list_from_form(Args, TypeNames, ET, Site0, MR, V, D, L),
- List = lists:zip(ArgNames, ArgTypes),
- TmpV = maps:from_list(List),
- Site = TypeName,
- t_from_form(Form, NewTypeNames, ET, Site, MR, TmpV, D, L1);
- false ->
- {t_any(), L}
- end;
- {opaque, {{Module, _FileName, Form, ArgNames}, Type}} ->
- case can_unfold_more(TypeName, TypeNames) of
- true ->
- NewTypeNames = [TypeName|TypeNames],
- {ArgTypes, L1} =
- list_from_form(Args, NewTypeNames, ET, Site0, MR, V, D, L),
+ {Tag, {{Module, _FileName, Form, ArgNames}, Type}} ->
+ NewTypeNames = [TypeName|TypeNames],
+ S1 = S#from_form{tnames = NewTypeNames},
+ {ArgTypes, L1, C1} = list_from_form(Args, S1, D, L, C),
+ CKey = cache_key(Module, Name, ArgTypes, TypeNames, D),
+ case cache_find(CKey, C) of
+ {CachedType, DeltaL} ->
+ {CachedType, L1 - DeltaL, C};
+ error ->
List = lists:zip(ArgNames, ArgTypes),
TmpV = maps:from_list(List),
- Site = TypeName,
- {Rep, L2} =
- t_from_form(Form, NewTypeNames, ET, Site, MR, TmpV, D, L1),
- Rep1 = choose_opaque_type(Rep, Type),
- Rep2 = case cannot_have_opaque(Rep1, TypeName, TypeNames) of
- true -> Rep1;
- false ->
- ArgTypes2 = subst_all_vars_to_any_list(ArgTypes),
- t_opaque(Module, Name, ArgTypes2, Rep1)
- end,
- {Rep2, L2};
- false -> {t_any(), L}
+ S2 = S1#from_form{site = TypeName, vtab = TmpV},
+ Fun = fun(DD, LL) -> from_form(Form, S2, DD, LL, C1) end,
+ {NewType, L3, C3} =
+ case Tag of
+ type ->
+ recur_limit(Fun, D, L1, TypeName, TypeNames);
+ opaque ->
+ {Rep, L2, C2} = recur_limit(Fun, D, L1, TypeName, TypeNames),
+ Rep1 = choose_opaque_type(Rep, Type),
+ Rep2 = case cannot_have_opaque(Rep1, TypeName, TypeNames) of
+ true -> Rep1;
+ false ->
+ ArgTypes2 = subst_all_vars_to_any_list(ArgTypes),
+ t_opaque(Module, Name, ArgTypes2, Rep1)
+ end,
+ {Rep2, L2, C2}
+ end,
+ C4 = cache_put(CKey, NewType, L1 - L3, C3),
+ {NewType, L3, C4}
end;
error ->
- Msg = io_lib:format("Unable to find type ~w/~w\n", [Name, ArgsLen]),
+ Msg = io_lib:format("Unable to find type ~w/~w\n",
+ [Name, ArgsLen]),
throw({error, Msg})
end.
-remote_from_form(RemMod, Name, Args, TypeNames, ET, S, MR, V, D, L) ->
+remote_from_form(RemMod, Name, Args, S, D, L, C) ->
+ #from_form{xtypes = ET, mrecs = MR, tnames = TypeNames} = S,
if
ET =:= replace_by_none ->
- {t_none(), L};
+ {t_none(), L, C};
true ->
ArgsLen = length(Args),
MFA = {RemMod, Name, ArgsLen},
case dict:find(RemMod, MR) of
error ->
self() ! {self(), ext_types, MFA},
- {t_any(), L};
+ {t_any(), L, C};
{ok, RemDict} ->
- RemType = {type, MFA},
case sets:is_element(MFA, ET) of
true ->
- case lookup_type(Name, ArgsLen, RemDict) of
- {type, {{_Mod, _FileLine, Form, ArgNames}, _Type}} ->
- case can_unfold_more(RemType, TypeNames) of
- true ->
- NewTypeNames = [RemType|TypeNames],
- {ArgTypes, L1} = list_from_form(Args, TypeNames,
- ET, S, MR, V, D, L),
- List = lists:zip(ArgNames, ArgTypes),
- TmpVarDict = maps:from_list(List),
- Site = RemType,
- t_from_form(Form, NewTypeNames, ET,
- Site, MR, TmpVarDict, D, L1);
- false ->
- {t_any(), L}
- end;
- {opaque, {{Mod, _FileLine, Form, ArgNames}, Type}} ->
- case can_unfold_more(RemType, TypeNames) of
- true ->
- NewTypeNames = [RemType|TypeNames],
- {ArgTypes, L1} = list_from_form(Args, NewTypeNames,
- ET, S, MR, V, D, L),
- List = lists:zip(ArgNames, ArgTypes),
- TmpVarDict = maps:from_list(List),
- Site = RemType,
- {NewRep, L2} =
- t_from_form(Form, NewTypeNames, ET, Site, MR,
- TmpVarDict, D, L1),
- NewRep1 = choose_opaque_type(NewRep, Type),
- NewRep2 =
- case
- cannot_have_opaque(NewRep1, RemType, TypeNames)
- of
- true -> NewRep1;
- false ->
- ArgTypes2 = subst_all_vars_to_any_list(ArgTypes),
- t_opaque(Mod, Name, ArgTypes2, NewRep1)
- end,
- {NewRep2, L2};
- false ->
- {t_any(), L}
- end;
- error ->
- Msg = io_lib:format("Unable to find remote type ~w:~w()\n",
- [RemMod, Name]),
- throw({error, Msg})
+ RemType = {type, MFA},
+ case can_unfold_more(RemType, TypeNames) of
+ true ->
+ remote_from_form1(RemMod, Name, Args, ArgsLen, RemDict,
+ RemType, TypeNames, S, D, L, C);
+ false ->
+ {t_any(), L, C}
end;
false ->
self() ! {self(), ext_types, {RemMod, Name, ArgsLen}},
- {t_any(), L}
+ {t_any(), L, C}
end
end
end.
+remote_from_form1(RemMod, Name, Args, ArgsLen, RemDict, RemType, TypeNames,
+ S, D, L, C) ->
+ case lookup_type(Name, ArgsLen, RemDict) of
+ {Tag, {{Mod, _FileLine, Form, ArgNames}, Type}} ->
+ NewTypeNames = [RemType|TypeNames],
+ S1 = S#from_form{tnames = NewTypeNames},
+ {ArgTypes, L1, C1} = list_from_form(Args, S1, D, L, C),
+ CKey = cache_key(RemMod, Name, ArgTypes, TypeNames, D),
+ %% case error of
+ case cache_find(CKey, C) of
+ {CachedType, DeltaL} ->
+ {CachedType, L - DeltaL, C};
+ error ->
+ List = lists:zip(ArgNames, ArgTypes),
+ TmpVarTab = maps:from_list(List),
+ S2 = S1#from_form{site = RemType, vtab = TmpVarTab},
+ Fun = fun(DD, LL) -> from_form(Form, S2, DD, LL, C1) end,
+ {NewType, L3, C3} =
+ case Tag of
+ type ->
+ recur_limit(Fun, D, L1, RemType, TypeNames);
+ opaque ->
+ {NewRep, L2, C2} = recur_limit(Fun, D, L1, RemType, TypeNames),
+ NewRep1 = choose_opaque_type(NewRep, Type),
+ NewRep2 =
+ case cannot_have_opaque(NewRep1, RemType, TypeNames) of
+ true -> NewRep1;
+ false ->
+ ArgTypes2 = subst_all_vars_to_any_list(ArgTypes),
+ t_opaque(Mod, Name, ArgTypes2, NewRep1)
+ end,
+ {NewRep2, L2, C2}
+ end,
+ C4 = cache_put(CKey, NewType, L1 - L3, C3),
+ {NewType, L3, C4}
+ end;
+ error ->
+ Msg = io_lib:format("Unable to find remote type ~w:~w()\n",
+ [RemMod, Name]),
+ throw({error, Msg})
+ end.
+
subst_all_vars_to_any_list(Types) ->
[subst_all_vars_to_any(Type) || Type <- Types].
@@ -4835,63 +4859,67 @@ choose_opaque_type(Type, DeclType) ->
false -> DeclType
end.
-record_from_form({atom, _, Name}, ModFields, TypeNames, ET, S, MR, V, D, L) ->
- case can_unfold_more({record, Name}, TypeNames) of
+record_from_form({atom, _, Name}, ModFields, S, D0, L0, C) ->
+ #from_form{site = Site, mrecs = MR, tnames = TypeNames} = S,
+ RecordType = {record, Name},
+ case can_unfold_more(RecordType, TypeNames) of
true ->
- M = site_module(S),
+ M = site_module(Site),
{ok, R} = dict:find(M, MR),
case lookup_record(Name, R) of
{ok, DeclFields} ->
- NewTypeNames = [{record, Name}|TypeNames],
- S1 = {record, {M, Name, length(DeclFields)}},
- {GetModRec, L1} = get_mod_record(ModFields, DeclFields,
- NewTypeNames, ET, S1, MR, V, D, L),
- case GetModRec of
- {error, FieldName} ->
- throw({error, io_lib:format("Illegal declaration of #~w{~w}\n",
- [Name, FieldName])});
- {ok, NewFields} ->
- {NewFields1, L2} =
- fields_from_form(NewFields, NewTypeNames, ET, S1, MR,
- maps:new(), D, L1),
- Rec = t_tuple(
- [t_atom(Name)|[Type
- || {_FieldName, Type} <- NewFields1]]),
- {Rec, L2}
- end;
+ NewTypeNames = [RecordType|TypeNames],
+ Site1 = {record, {M, Name, length(DeclFields)}},
+ S1 = S#from_form{site = Site1, tnames = NewTypeNames},
+ Fun = fun(D, L) ->
+ {GetModRec, L1, C1} =
+ get_mod_record(ModFields, DeclFields, S1, D, L, C),
+ case GetModRec of
+ {error, FieldName} ->
+ throw({error,
+ io_lib:format("Illegal declaration of #~w{~w}\n",
+ [Name, FieldName])});
+ {ok, NewFields} ->
+ S2 = S1#from_form{vtab = var_table__new()},
+ {NewFields1, L2, C2} =
+ fields_from_form(NewFields, S2, D, L1, C1),
+ Rec = t_tuple(
+ [t_atom(Name)|[Type
+ || {_FieldName, Type} <- NewFields1]]),
+ {Rec, L2, C2}
+ end
+ end,
+ recur_limit(Fun, D0, L0, RecordType, TypeNames);
error ->
throw({error, io_lib:format("Unknown record #~w{}\n", [Name])})
end;
false ->
- {t_any(), L}
+ {t_any(), L0, C}
end.
-get_mod_record([], DeclFields, _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {{ok, DeclFields}, L};
-get_mod_record(ModFields, DeclFields, TypeNames, ET, S, MR, V, D, L) ->
+get_mod_record([], DeclFields, _S, _D, L, C) ->
+ {{ok, DeclFields}, L, C};
+get_mod_record(ModFields, DeclFields, S, D, L, C) ->
DeclFieldsDict = lists:keysort(1, DeclFields),
- {ModFieldsDict, L1} =
- build_field_dict(ModFields, TypeNames, ET, S, MR, V, D, L),
+ {ModFieldsDict, L1, C1} = build_field_dict(ModFields, S, D, L, C),
case get_mod_record_types(DeclFieldsDict, ModFieldsDict, []) of
- {error, _FieldName} = Error -> {Error, L1};
+ {error, _FieldName} = Error -> {Error, L1, C1};
{ok, FinalKeyDict} ->
Fields = [lists:keyfind(FieldName, 1, FinalKeyDict)
|| {FieldName, _, _} <- DeclFields],
- {{ok, Fields}, L1}
+ {{ok, Fields}, L1, C1}
end.
-build_field_dict(FieldTypes, TypeNames, ET, S, MR, V, D, L) ->
- build_field_dict(FieldTypes, TypeNames, ET, S, MR, V, D, L, []).
+build_field_dict(FieldTypes, S, D, L, C) ->
+ build_field_dict(FieldTypes, S, D, L, C, []).
build_field_dict([{type, _, field_type, [{atom, _, Name}, Type]}|Left],
- TypeNames, ET, S, MR, V, D, L, Acc) ->
- {T, L1} = t_from_form(Type, TypeNames, ET, S, MR, V, D, L - 1),
+ S, D, L, C, Acc) ->
+ {T, L1, C1} = from_form(Type, S, D, L - 1, C),
NewAcc = [{Name, Type, T}|Acc],
- {Dict, L2} =
- build_field_dict(Left, TypeNames, ET, S, MR, V, D, L1, NewAcc),
- {Dict, L2};
-build_field_dict([], _TypeNames, _ET, _S, _MR, _V, _D, L, Acc) ->
- {lists:keysort(1, Acc), L}.
+ build_field_dict(Left, S, D, L1, C1, NewAcc);
+build_field_dict([], _S, _D, L, C, Acc) ->
+ {lists:keysort(1, Acc), L, C}.
get_mod_record_types([{FieldName, _Abstr, _DeclType}|Left1],
[{FieldName, TypeForm, ModType}|Left2],
@@ -4909,20 +4937,19 @@ get_mod_record_types(_, [{FieldName2, _FormType, _ModType}|_], _Acc) ->
%% It is important to create a limited version of the record type
%% since nested record types can otherwise easily result in huge
%% terms.
-fields_from_form([], _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {[], L};
-fields_from_form([{Name, Abstr, _Type}|Tail], TypeNames, ET, S, MR,
- V, D, L) ->
- {T, L1} = t_from_form(Abstr, TypeNames, ET, S, MR, V, D, L),
- {F, L2} = fields_from_form(Tail, TypeNames, ET, S, MR, V, D, L1),
- {[{Name, T}|F], L2}.
-
-list_from_form([], _TypeNames, _ET, _S, _MR, _V, _D, L) ->
- {[], L};
-list_from_form([H|Tail], TypeNames, ET, S, MR, V, D, L) ->
- {H1, L1} = t_from_form(H, TypeNames, ET, S, MR, V, D, L - 1),
- {T1, L2} = list_from_form(Tail, TypeNames, ET, S, MR, V, D, L1),
- {[H1|T1], L2}.
+fields_from_form([], _S, _D, L, C) ->
+ {[], L, C};
+fields_from_form([{Name, Abstr, _Type}|Tail], S, D, L, C) ->
+ {T, L1, C1} = from_form(Abstr, S, D, L, C),
+ {F, L2, C2} = fields_from_form(Tail, S, D, L1, C1),
+ {[{Name, T}|F], L2, C2}.
+
+list_from_form([], _S, _D, L, C) ->
+ {[], L, C};
+list_from_form([H|Tail], S, D, L, C) ->
+ {H1, L1, C1} = from_form(H, S, D, L - 1, C),
+ {T1, L2, C2} = list_from_form(Tail, S, D, L1, C1),
+ {[H1|T1], L2, C2}.
%% Sorts, combines non-singleton pairs, and applies precendence and
%% mandatoriness rules.
@@ -4968,80 +4995,140 @@ promote_to_mand(MKs, [E={K,_,V}|T]) ->
false -> E
end|promote_to_mand(MKs, T)].
--spec t_check_record_fields(parse_form(), sets:set(mfa()), site(),
- mod_records()) -> ok.
+-define(RECUR_EXPAND_LIMIT, 10).
+-define(RECUR_EXPAND_DEPTH, 2).
-t_check_record_fields(Form, ExpTypes, Site, RecDict) ->
- t_check_record_fields(Form, ExpTypes, Site, RecDict, maps:new()).
+%% If more of the limited resources is spent on the non-recursive
+%% forms, more warnings are found. And the analysis is also a bit
+%% faster.
+%%
+%% Setting REC_TYPE_LIMIT to 1 would work also work well.
+
+recur_limit(Fun, D, L, _, _) when L =< ?RECUR_EXPAND_DEPTH,
+ D =< ?RECUR_EXPAND_LIMIT ->
+ Fun(D, L);
+recur_limit(Fun, D, L, TypeName, TypeNames) ->
+ case is_recursive(TypeName, TypeNames) of
+ true ->
+ {T, L1, C1} = Fun(?RECUR_EXPAND_DEPTH, ?RECUR_EXPAND_LIMIT),
+ {T, L - L1, C1};
+ false ->
+ Fun(D, L)
+ end.
-spec t_check_record_fields(parse_form(), sets:set(mfa()), site(),
- mod_records(), var_table()) -> ok.
+ mod_records(), var_table(), cache()) -> cache().
+
+t_check_record_fields(Form, ExpTypes, Site, RecDict, VarTable, Cache) ->
+ State = #from_form{site = Site,
+ xtypes = ExpTypes,
+ mrecs = RecDict,
+ vtab = VarTable,
+ tnames = []},
+ check_record_fields(Form, State, Cache).
+
+-spec check_record_fields(parse_form(), #from_form{}, cache()) -> cache().
%% If there is something wrong with parse_form()
%% throw({error, io_lib:chars()} is called.
-t_check_record_fields({var, _L, _}, _ET, _S, _MR, _V) -> ok;
-t_check_record_fields({ann_type, _L, [_Var, Type]}, ET, S, MR, V) ->
- t_check_record_fields(Type, ET, S, MR, V);
-t_check_record_fields({paren_type, _L, [Type]}, ET, S, MR, V) ->
- t_check_record_fields(Type, ET, S, MR, V);
-t_check_record_fields({remote_type, _L, [{atom, _, _}, {atom, _, _}, Args]},
- ET, S, MR, V) ->
- list_check_record_fields(Args, ET, S, MR, V);
-t_check_record_fields({atom, _L, _}, _ET, _S, _MR, _V) -> ok;
-t_check_record_fields({integer, _L, _}, _ET, _S, _MR, _V) -> ok;
-t_check_record_fields({op, _L, _Op, _Arg}, _ET, _S, _MR, _V) -> ok;
-t_check_record_fields({op, _L, _Op, _Arg1, _Arg2}, _ET, _S, _MR, _V) -> ok;
-t_check_record_fields({type, _L, tuple, any}, _ET, _S, _MR, _V) -> ok;
-t_check_record_fields({type, _L, map, any}, _ET, _S, _MR, _V) -> ok;
-t_check_record_fields({type, _L, binary, [_Base, _Unit]}, _ET, _S, _MR, _V) ->
- ok;
-t_check_record_fields({type, _L, 'fun', [{type, _, any}, Range]},
- ET, S, MR, V) ->
- t_check_record_fields(Range, ET, S, MR, V);
-t_check_record_fields({type, _L, range, [_From, _To]}, _ET, _S, _MR, _V) ->
- ok;
-t_check_record_fields({type, _L, record, [Name|Fields]}, ET, S, MR, V) ->
- check_record(Name, Fields, ET, S, MR, V);
-t_check_record_fields({type, _L, _, Args}, ET, S, MR, V) ->
- list_check_record_fields(Args, ET, S, MR, V);
-t_check_record_fields({user_type, _L, _Name, Args}, ET, S, MR, V) ->
- list_check_record_fields(Args, ET, S, MR, V).
-
-check_record({atom, _, Name}, ModFields, ET, Site, MR, V) ->
+check_record_fields({var, _L, _}, _S, C) -> C;
+check_record_fields({ann_type, _L, [_Var, Type]}, S, C) ->
+ check_record_fields(Type, S, C);
+check_record_fields({paren_type, _L, [Type]}, S, C) ->
+ check_record_fields(Type, S, C);
+check_record_fields({remote_type, _L, [{atom, _, _}, {atom, _, _}, Args]},
+ S, C) ->
+ list_check_record_fields(Args, S, C);
+check_record_fields({atom, _L, _}, _S, C) -> C;
+check_record_fields({integer, _L, _}, _S, C) -> C;
+check_record_fields({op, _L, _Op, _Arg}, _S, C) -> C;
+check_record_fields({op, _L, _Op, _Arg1, _Arg2}, _S, C) -> C;
+check_record_fields({type, _L, tuple, any}, _S, C) -> C;
+check_record_fields({type, _L, map, any}, _S, C) -> C;
+check_record_fields({type, _L, binary, [_Base, _Unit]}, _S, C) -> C;
+check_record_fields({type, _L, 'fun', [{type, _, any}, Range]}, S, C) ->
+ check_record_fields(Range, S, C);
+check_record_fields({type, _L, range, [_From, _To]}, _S, C) -> C;
+check_record_fields({type, _L, record, [Name|Fields]}, S, C) ->
+ check_record(Name, Fields, S, C);
+check_record_fields({type, _L, _, Args}, S, C) ->
+ list_check_record_fields(Args, S, C);
+check_record_fields({user_type, _L, _Name, Args}, S, C) ->
+ list_check_record_fields(Args, S, C).
+
+check_record({atom, _, Name}, ModFields, S, C) ->
+ #from_form{site = Site, mrecs = MR} = S,
M = site_module(Site),
{ok, R} = dict:find(M, MR),
{ok, DeclFields} = lookup_record(Name, R),
- case check_fields(Name, ModFields, DeclFields, ET, Site, MR, V) of
+ case check_fields(Name, ModFields, DeclFields, S, C) of
{error, FieldName} ->
throw({error, io_lib:format("Illegal declaration of #~w{~w}\n",
[Name, FieldName])});
- ok -> ok
+ C1 -> C1
end.
check_fields(RecName, [{type, _, field_type, [{atom, _, Name}, Abstr]}|Left],
- DeclFields, ET, Site0, MR, V) ->
+ DeclFields, S, C) ->
+ #from_form{site = Site0, xtypes = ET, mrecs = MR, vtab = V} = S,
M = site_module(Site0),
Site = {record, {M, RecName, length(DeclFields)}},
- Type = t_from_form(Abstr, ET, Site, MR, V),
+ {Type, C1} = t_from_form(Abstr, ET, Site, MR, V, C),
{Name, _, DeclType} = lists:keyfind(Name, 1, DeclFields),
TypeNoVars = subst_all_vars_to_any(Type),
case t_is_subtype(TypeNoVars, DeclType) of
false -> {error, Name};
- true -> check_fields(RecName, Left, DeclFields, ET, Site0, MR, V)
+ true -> check_fields(RecName, Left, DeclFields, S, C1)
end;
-check_fields(_RecName, [], _Decl, _ET, _Site, _MR, _V) ->
- ok.
+check_fields(_RecName, [], _Decl, _S, C) ->
+ C.
-list_check_record_fields([], _ET, _S, _MR, _V) ->
- ok;
-list_check_record_fields([H|Tail], ET, S, MR, V) ->
- ok = t_check_record_fields(H, ET, S, MR, V),
- list_check_record_fields(Tail, ET, S, MR, V).
+list_check_record_fields([], _S, C) ->
+ C;
+list_check_record_fields([H|Tail], S, C) ->
+ C1 = check_record_fields(H, S, C),
+ list_check_record_fields(Tail, S, C1).
site_module({_, {Module, _, _}}) ->
Module.
+-spec cache__new() -> cache().
+
+cache__new() ->
+ maps:new().
+
+-spec cache_key(module(), atom(), [erl_type()],
+ type_names(), expand_depth()) -> cache_key().
+
+%% If TypeNames is left out from the key, the cache is smaller, and
+%% the form-to-type translation is faster. But it would be a shame if,
+%% for example, any() is used, where a more complex type should be
+%% used. There is also a slight risk of creating unnecessarily big
+%% types.
+
+cache_key(Module, Name, ArgTypes, TypeNames, D) ->
+ {Module, Name, D, ArgTypes, TypeNames}.
+
+-spec cache_find(cache_key(), cache()) ->
+ {erl_type(), expand_limit()} | 'error'.
+
+cache_find(Key, Cache) ->
+ case maps:find(Key, Cache) of
+ {ok, Value} ->
+ Value;
+ error ->
+ error
+ end.
+
+-spec cache_put(cache_key(), erl_type(), expand_limit(), cache()) -> cache().
+
+cache_put(_Key, _Type, DeltaL, Cache) when DeltaL < 0 ->
+ %% The type is truncated; do not reuse it.
+ Cache;
+cache_put(Key, Type, DeltaL, Cache) ->
+ maps:put(Key, {Type, DeltaL}, Cache).
+
-spec t_var_names([erl_type()]) -> [atom()].
t_var_names([{var, _, Name}|L]) when L =/= '_' ->
@@ -5140,10 +5227,15 @@ t_form_to_string({type, _L, Name, []} = T) ->
M = mod,
D0 = dict:new(),
MR = dict:from_list([{M, D0}]),
- S = {type, {M,Name,0}},
- V = #{},
- {T1, _} =
- t_from_form(T, [], sets:new(), S, MR, V, _Deep=1000, _ALot=100000),
+ Site = {type, {M,Name,0}},
+ V = var_table__new(),
+ C = cache__new(),
+ State = #from_form{site = Site,
+ xtypes = sets:new(),
+ mrecs = MR,
+ vtab = V,
+ tnames = []},
+ {T1, _, _} = from_form(T, State, _Deep=1000, _ALot=1000000, C),
t_to_string(T1)
catch throw:{error, _} -> atom_to_string(Name) ++ "()"
end;
@@ -5219,6 +5311,7 @@ lookup_record(Tag, Arity, RecDict) when is_atom(Tag) ->
error -> error
end.
+-spec lookup_type(_, _, _) -> {'type' | 'opaque', type_value()} | 'error'.
lookup_type(Name, Arity, RecDict) ->
case dict:find({type, Name, Arity}, RecDict) of
error ->
diff --git a/lib/stdlib/doc/src/erl_id_trans.xml b/lib/stdlib/doc/src/erl_id_trans.xml
index 153bd4148e..649490f8b3 100644
--- a/lib/stdlib/doc/src/erl_id_trans.xml
+++ b/lib/stdlib/doc/src/erl_id_trans.xml
@@ -49,7 +49,8 @@
<name>parse_transform(Forms, Options) -> Forms</name>
<fsummary>Transform Erlang forms</fsummary>
<type>
- <v>Forms = [<seealso marker="erl_parse#type-abstract_form">erl_parse:abstract_form()</seealso>]</v>
+ <v>Forms = [<seealso marker="erl_parse#type-abstract_form">erl_parse:abstract_form()</seealso>
+ | <seealso marker="erl_parse#type-form_info">erl_parse:form_info()</seealso>]</v>
<v>Options = [<seealso marker="compile#type-option">compile:option()</seealso>]</v>
</type>
<desc>
diff --git a/lib/stdlib/doc/src/erl_parse.xml b/lib/stdlib/doc/src/erl_parse.xml
index 32fce16d68..771ccc2dc6 100644
--- a/lib/stdlib/doc/src/erl_parse.xml
+++ b/lib/stdlib/doc/src/erl_parse.xml
@@ -73,6 +73,14 @@
<name name="error_info"></name>
</datatype>
<datatype>
+ <name name="form_info"></name>
+ <desc><p>Tuples <c>{error, error_info()}</c> and <c>{warning,
+ error_info()}</c>, denoting syntactically incorrect forms and
+ warnings, and <c>{eof, line()}</c>, denoting an end-of-stream
+ encountered before a complete form had been parsed.</p>
+ </desc>
+ </datatype>
+ <datatype>
<name name="token"></name>
</datatype>
</datatypes>
diff --git a/lib/stdlib/src/erl_expand_records.erl b/lib/stdlib/src/erl_expand_records.erl
index 9c0a7fb7d5..ebcbc54ab1 100644
--- a/lib/stdlib/src/erl_expand_records.erl
+++ b/lib/stdlib/src/erl_expand_records.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2005-2015. All Rights Reserved.
+%% Copyright Ericsson AB 2005-2016. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
@@ -37,8 +37,9 @@
checked_ra=[] % successfully accessed records
}).
--spec(module(AbsForms, CompileOptions) -> AbsForms when
+-spec(module(AbsForms, CompileOptions) -> AbsForms2 when
AbsForms :: [erl_parse:abstract_form()],
+ AbsForms2 :: [erl_parse:abstract_form()],
CompileOptions :: [compile:option()]).
%% Is is assumed that Fs is a valid list of forms. It should pass
diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl
index 2508f96b91..e9332ce069 100644
--- a/lib/stdlib/src/erl_lint.erl
+++ b/lib/stdlib/src/erl_lint.erl
@@ -99,7 +99,7 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) ->
module='', %Module
behaviour=[], %Behaviour
exports=gb_sets:empty() :: gb_sets:set(fa()),%Exports
- imports=[] :: [fa()], %Imports, an orddict()
+ imports=[] :: orddict:orddict(fa(), module()),%Imports
compile=[], %Compile flags
records=dict:new() %Record definitions
:: dict:dict(atom(), {line(),Fields :: term()}),
@@ -467,7 +467,7 @@ used_vars(Exprs, BindingsList) ->
%% really all ordsets!
-spec(module(AbsForms) -> {ok, Warnings} | {error, Errors, Warnings} when
- AbsForms :: [erl_parse:abstract_form()],
+ AbsForms :: [erl_parse:abstract_form() | erl_parse:form_info()],
Warnings :: [{file:filename(),[ErrorInfo]}],
Errors :: [{FileName2 :: file:filename(),[ErrorInfo]}],
ErrorInfo :: error_info()).
@@ -479,7 +479,7 @@ module(Forms) ->
-spec(module(AbsForms, FileName) ->
{ok, Warnings} | {error, Errors, Warnings} when
- AbsForms :: [erl_parse:abstract_form()],
+ AbsForms :: [erl_parse:abstract_form() | erl_parse:form_info()],
FileName :: atom() | string(),
Warnings :: [{file:filename(),[ErrorInfo]}],
Errors :: [{FileName2 :: file:filename(),[ErrorInfo]}],
@@ -492,7 +492,7 @@ module(Forms, FileName) ->
-spec(module(AbsForms, FileName, CompileOptions) ->
{ok, Warnings} | {error, Errors, Warnings} when
- AbsForms :: [erl_parse:abstract_form()],
+ AbsForms :: [erl_parse:abstract_form() | erl_parse:form_info()],
FileName :: atom() | string(),
CompileOptions :: [compile:option()],
Warnings :: [{file:filename(),[ErrorInfo]}],
diff --git a/lib/stdlib/src/erl_parse.yrl b/lib/stdlib/src/erl_parse.yrl
index 1de09aae62..85b2816451 100644
--- a/lib/stdlib/src/erl_parse.yrl
+++ b/lib/stdlib/src/erl_parse.yrl
@@ -531,7 +531,7 @@ Erlang code.
-compile([{hipe,[{regalloc,linear_scan}]}]).
-export_type([abstract_clause/0, abstract_expr/0, abstract_form/0,
- abstract_type/0, error_info/0]).
+ abstract_type/0, form_info/0, error_info/0]).
%% Start of Abstract Format
@@ -543,7 +543,6 @@ Erlang code.
| af_export()
| af_import()
| af_export_type()
- | af_optional_callbacks()
| af_compile()
| af_file()
| af_record_decl()
@@ -570,9 +569,6 @@ Erlang code.
-type af_ta_list() :: [{type_name(), arity()}].
--type af_optional_callbacks() ::
- {'attribute', anno(), 'optional_callbacks', af_fa_list()}.
-
-type af_compile() :: {'attribute', anno(), 'compile', any()}.
-type af_file() :: {'attribute', anno(), 'file', {string(), anno()}}.
@@ -864,16 +860,22 @@ Erlang code.
| af_unary_op(af_singleton_integer_type())
| af_binary_op(af_singleton_integer_type()).
--type af_literal() :: af_atom() | af_integer() | af_float() | af_string().
+-type af_literal() :: af_atom()
+ | af_character()
+ | af_float()
+ | af_integer()
+ | af_string().
-type af_atom() :: af_lit_atom(atom()).
-type af_lit_atom(A) :: {'atom', anno(), A}.
--type af_integer() :: {'integer', anno(), non_neg_integer()}.
+-type af_character() :: {'char', anno(), char()}.
-type af_float() :: {'float', anno(), float()}.
+-type af_integer() :: {'integer', anno(), non_neg_integer()}.
+
-type af_string() :: {'string', anno(), string()}.
-type af_match(T) :: {'match', anno(), af_pattern(), T}.
@@ -941,6 +943,10 @@ Erlang code.
-type type_name() :: atom().
+-type form_info() :: {'eof', erl_anno:line()}
+ | {'error', erl_scan:error_info() | error_info()}
+ | {'warning', erl_scan:error_info() | error_info()}.
+
%% End of Abstract Format
%% XXX. To be refined.
@@ -1500,8 +1506,9 @@ type_preop_prec('#') -> {700,800}.
| abstract_type().
-spec map_anno(Fun, Abstr) -> NewAbstr when
- Fun :: fun((Anno) -> Anno),
+ Fun :: fun((Anno) -> NewAnno),
Anno :: erl_anno:anno(),
+ NewAnno :: erl_anno:anno(),
Abstr :: erl_parse_tree(),
NewAbstr :: erl_parse_tree().
@@ -1510,14 +1517,14 @@ map_anno(F0, Abstr) ->
{NewAbstr, []} = modify_anno1(Abstr, [], F),
NewAbstr.
--spec fold_anno(Fun, Acc0, Abstr) -> NewAbstr when
+-spec fold_anno(Fun, Acc0, Abstr) -> Acc1 when
Fun :: fun((Anno, AccIn) -> AccOut),
Anno :: erl_anno:anno(),
Acc0 :: term(),
+ Acc1 :: term(),
AccIn :: term(),
AccOut :: term(),
- Abstr :: erl_parse_tree(),
- NewAbstr :: erl_parse_tree().
+ Abstr :: erl_parse_tree().
fold_anno(F0, Acc0, Abstr) ->
F = fun(A, Acc) -> {A, F0(A, Acc)} end,
@@ -1525,8 +1532,9 @@ fold_anno(F0, Acc0, Abstr) ->
NewAcc.
-spec mapfold_anno(Fun, Acc0, Abstr) -> {NewAbstr, Acc1} when
- Fun :: fun((Anno, AccIn) -> {Anno, AccOut}),
+ Fun :: fun((Anno, AccIn) -> {NewAnno, AccOut}),
Anno :: erl_anno:anno(),
+ NewAnno :: erl_anno:anno(),
Acc0 :: term(),
Acc1 :: term(),
AccIn :: term(),
@@ -1542,7 +1550,9 @@ mapfold_anno(F, Acc0, Abstr) ->
Abstr :: erl_parse_tree().
new_anno(Term) ->
- map_anno(fun erl_anno:new/1, Term).
+ F = fun(L, Acc) -> {erl_anno:new(L), Acc} end,
+ {NewAbstr, []} = modify_anno1(Term, [], F),
+ NewAbstr.
-spec anno_to_term(Abstr) -> term() when
Abstr :: erl_parse_tree().
diff --git a/lib/stdlib/src/erl_pp.erl b/lib/stdlib/src/erl_pp.erl
index 4009300a32..016962f538 100644
--- a/lib/stdlib/src/erl_pp.erl
+++ b/lib/stdlib/src/erl_pp.erl
@@ -70,13 +70,13 @@
%%%
-spec(form(Form) -> io_lib:chars() when
- Form :: erl_parse:abstract_form()).
+ Form :: erl_parse:abstract_form() | erl_parse:form_info()).
form(Thing) ->
form(Thing, none).
-spec(form(Form, Options) -> io_lib:chars() when
- Form :: erl_parse:abstract_form(),
+ Form :: erl_parse:abstract_form() | erl_parse:form_info(),
Options :: options()).
form(Thing, Options) ->
diff --git a/lib/stdlib/src/lib.erl b/lib/stdlib/src/lib.erl
index 6fba63a895..56654097d9 100644
--- a/lib/stdlib/src/lib.erl
+++ b/lib/stdlib/src/lib.erl
@@ -73,7 +73,7 @@ nonl([H|T]) -> [H|nonl(T)].
send(To, Msg) -> To ! Msg.
--spec sendw(To, Msg) -> Msg when
+-spec sendw(To, Msg) -> term() when
To :: pid() | atom() | {atom(), node()},
Msg :: term().
diff --git a/lib/stdlib/src/ms_transform.erl b/lib/stdlib/src/ms_transform.erl
index 24b5fde1db..c0eea652e7 100644
--- a/lib/stdlib/src/ms_transform.erl
+++ b/lib/stdlib/src/ms_transform.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2002-2015. All Rights Reserved.
+%% Copyright Ericsson AB 2002-2016. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
@@ -224,8 +224,9 @@ transform_from_shell(Dialect, Clauses, BoundEnvironment) ->
%% Called when translating during compiling
%%
--spec parse_transform(Forms, Options) -> Forms when
- Forms :: [erl_parse:abstract_form()],
+-spec parse_transform(Forms, Options) -> Forms2 when
+ Forms :: [erl_parse:abstract_form() | erl_parse:form_info()],
+ Forms2 :: [erl_parse:abstract_form() | erl_parse:form_info()],
Options :: term().
parse_transform(Forms, _Options) ->
diff --git a/lib/stdlib/src/proplists.erl b/lib/stdlib/src/proplists.erl
index 8e99ec0ed9..5356467b19 100644
--- a/lib/stdlib/src/proplists.erl
+++ b/lib/stdlib/src/proplists.erl
@@ -438,8 +438,9 @@ substitute_aliases_1([], P) ->
%% @see normalize/2
-spec substitute_negations(Negations, ListIn) -> ListOut when
- Negations :: [{Key, Key}],
- Key :: term(),
+ Negations :: [{Key1, Key2}],
+ Key1 :: term(),
+ Key2 :: term(),
ListIn :: [term()],
ListOut :: [term()].
diff --git a/lib/stdlib/src/qlc.erl b/lib/stdlib/src/qlc.erl
index b396ba7057..f3665824f2 100644
--- a/lib/stdlib/src/qlc.erl
+++ b/lib/stdlib/src/qlc.erl
@@ -734,10 +734,11 @@ table(TraverseFun, Options) when is_function(TraverseFun) ->
table(T1, T2) ->
erlang:error(badarg, [T1, T2]).
--spec(transform_from_evaluator(LC, Bs) -> Expr when
+-spec(transform_from_evaluator(LC, Bs) -> Return when
LC :: abstract_expr(),
- Expr :: abstract_expr(),
- Bs :: erl_eval:binding_struct()).
+ Bs :: erl_eval:binding_struct(),
+ Return :: {ok, abstract_expr()}
+ | {not_ok, {error, module(), Reason :: term()}}).
transform_from_evaluator(LC, Bs0) ->
qlc_pt:transform_from_evaluator(LC, Bs0).
diff --git a/lib/stdlib/src/qlc_pt.erl b/lib/stdlib/src/qlc_pt.erl
index e4b9768b12..0db63b81f4 100644
--- a/lib/stdlib/src/qlc_pt.erl
+++ b/lib/stdlib/src/qlc_pt.erl
@@ -67,8 +67,8 @@
%%%
-spec(parse_transform(Forms, Options) -> Forms2 when
- Forms :: [erl_parse:abstract_form()],
- Forms2 :: [erl_parse:abstract_form()],
+ Forms :: [erl_parse:abstract_form() | erl_parse:form_info()],
+ Forms2 :: [erl_parse:abstract_form() | erl_parse:form_info()],
Options :: [Option],
Option :: type_checker | compile:option()).
@@ -117,19 +117,21 @@ parse_transform(Forms0, Options) ->
true = ets:delete(NodeInfo)
end.
--spec(transform_from_evaluator(LC, Bs) -> Expr when
+-spec(transform_from_evaluator(LC, Bs) -> Return when
LC :: erl_parse:abstract_expr(),
- Expr :: erl_parse:abstract_expr(),
- Bs :: erl_eval:binding_struct()).
+ Bs :: erl_eval:binding_struct(),
+ Return :: {ok, erl_parse:abstract_expr()}
+ | {not_ok, {error, module(), Reason :: term()}}).
transform_from_evaluator(LC, Bindings) ->
?DEBUG("qlc Parse Transform (Evaluator Version)~n", []),
transform_expression(LC, Bindings, false).
--spec(transform_expression(LC, Bs) -> Expr when
+-spec(transform_expression(LC, Bs) -> Return when
LC :: erl_parse:abstract_expr(),
- Expr :: erl_parse:abstract_expr(),
- Bs :: erl_eval:binding_struct()).
+ Bs :: erl_eval:binding_struct(),
+ Return :: {ok, erl_parse:abstract_expr()}
+ | {not_ok, [{error, Reason :: term()}]}).
transform_expression(LC, Bindings) ->
transform_expression(LC, Bindings, true).
diff --git a/lib/stdlib/src/sofs.erl b/lib/stdlib/src/sofs.erl
index b18df2ad09..c244e06ca4 100644
--- a/lib/stdlib/src/sofs.erl
+++ b/lib/stdlib/src/sofs.erl
@@ -621,6 +621,9 @@ canonical_relation(Sets) when ?IS_SET(Sets) ->
%%% Functions on binary relations only.
%%%
+-spec(rel2fam(BinRel) -> Family when
+ Family :: family(),
+ BinRel :: binary_relation()).
rel2fam(R) ->
relation_to_family(R).
diff --git a/lib/syntax_tools/src/Makefile b/lib/syntax_tools/src/Makefile
index 2e91adf8af..8325db45a8 100644
--- a/lib/syntax_tools/src/Makefile
+++ b/lib/syntax_tools/src/Makefile
@@ -29,7 +29,7 @@ ERL_COMPILE_FLAGS += -pa $(EBIN) -pa ./ -I$(INCLUDE)
ifeq ($(NATIVE_LIBS_ENABLED),yes)
ERL_COMPILE_FLAGS += +native
endif
-ERL_COMPILE_FLAGS += +nowarn_shadow_vars +warn_unused_import -Werror # +warn_missing_spec +warn_untyped_record
+ERL_COMPILE_FLAGS += +nowarn_shadow_vars +warn_unused_import #-Werror # +warn_missing_spec +warn_untyped_record
SOURCES=erl_syntax.erl erl_prettypr.erl erl_syntax_lib.erl \
erl_comment_scan.erl erl_recomment.erl erl_tidy.erl \
diff --git a/lib/syntax_tools/src/erl_recomment.erl b/lib/syntax_tools/src/erl_recomment.erl
index 5ce533285d..c1141b2bc6 100644
--- a/lib/syntax_tools/src/erl_recomment.erl
+++ b/lib/syntax_tools/src/erl_recomment.erl
@@ -601,16 +601,16 @@ expand_comment(C) ->
-record(leaf, {min = 0 :: integer(),
max = 0 :: integer(),
- precomments = [] :: [erl_syntax:syntaxTree()],
- postcomments = [] :: [erl_syntax:syntaxTree()],
+ precomments = [] :: [erl_comment_scan:comment()],
+ postcomments = [] :: [erl_comment_scan:comment()],
value :: erl_syntax:syntaxTree()}).
-record(tree, {min = 0 :: integer(),
max = 0 :: integer(),
type :: atom(),
attrs :: erl_syntax:syntaxTreeAttributes(),
- precomments = [] :: [erl_syntax:syntaxTree()],
- postcomments = [] :: [erl_syntax:syntaxTree()],
+ precomments = [] :: [erl_comment_scan:comment()],
+ postcomments = [] :: [erl_comment_scan:comment()],
subtrees = [] :: [extendedSyntaxTree()]}).
diff --git a/lib/syntax_tools/src/erl_syntax.erl b/lib/syntax_tools/src/erl_syntax.erl
index f4cda814fc..ee42e56172 100644
--- a/lib/syntax_tools/src/erl_syntax.erl
+++ b/lib/syntax_tools/src/erl_syntax.erl
@@ -443,7 +443,14 @@
-type syntaxTree() :: #tree{} | #wrapper{} | erl_parse().
--type erl_parse() :: erl_parse:abstract_form() | erl_parse:abstract_expr().
+-type erl_parse() :: erl_parse:abstract_clause()
+ | erl_parse:abstract_expr()
+ | erl_parse:abstract_form()
+ | erl_parse:abstract_type()
+ | erl_parse:form_info()
+ %% To shut up Dialyzer:
+ | {bin_element, _, _, _, _}.
+
%% The representation built by the Erlang standard library parser
%% `erl_parse'. This is a subset of the {@link syntaxTree()} type.