aboutsummaryrefslogtreecommitdiffstats
path: root/lib/hipe/cerl/erl_types.erl
diff options
context:
space:
mode:
Diffstat (limited to 'lib/hipe/cerl/erl_types.erl')
-rw-r--r--lib/hipe/cerl/erl_types.erl360
1 files changed, 214 insertions, 146 deletions
diff --git a/lib/hipe/cerl/erl_types.erl b/lib/hipe/cerl/erl_types.erl
index af34e355bb..32390045e3 100644
--- a/lib/hipe/cerl/erl_types.erl
+++ b/lib/hipe/cerl/erl_types.erl
@@ -228,7 +228,7 @@
-export([t_is_identifier/1]).
-endif.
--export_type([erl_type/0]).
+-export_type([erl_type/0, type_table/0, var_table/0]).
%%-define(DEBUG, true).
@@ -363,6 +363,15 @@
-type opaques() :: [erl_type()] | 'universe'.
+-type record_key() :: {'record', atom()}.
+-type type_key() :: {'type' | 'opaque', atom(), arity()}.
+-type record_value() :: orddict:orddict(). % XXX. To be refined
+-type type_value() :: {module(), erl_type(), atom()}.
+-type type_table() :: dict:dict(record_key(), record_value())
+ | dict:dict(type_key(), type_value()).
+
+-type var_table() :: dict:dict(atom(), erl_type()).
+
%%-----------------------------------------------------------------------------
%% Unions
%%
@@ -645,15 +654,16 @@ decorate_with_opaque(Type, ?opaque(Set2), Opaques) ->
end.
decoration([#opaque{struct = S} = Opaque|OpaqueTypes], Type, Opaques,
- NewOpaqueTypes, All) ->
+ NewOpaqueTypes0, All) ->
IsOpaque = is_opaque_type2(Opaque, Opaques),
I = t_inf(Type, S),
- case not IsOpaque orelse t_is_none(I = t_inf(Type, S)) of
- true -> decoration(OpaqueTypes, Type, Opaques, NewOpaqueTypes, All);
+ case not IsOpaque orelse t_is_none(I) of
+ true -> decoration(OpaqueTypes, Type, Opaques, NewOpaqueTypes0, All);
false ->
NewOpaque = Opaque#opaque{struct = decorate(I, S, Opaques)},
NewAll = All orelse t_is_equal(I, Type),
- decoration(OpaqueTypes, Type, Opaques, [NewOpaque|NewOpaqueTypes], NewAll)
+ NewOpaqueTypes = [NewOpaque|NewOpaqueTypes0],
+ decoration(OpaqueTypes, Type, Opaques, NewOpaqueTypes, NewAll)
end;
decoration([], _Type, _Opaques, NewOpaqueTypes, All) ->
{NewOpaqueTypes, All}.
@@ -722,7 +732,7 @@ decorate_tuples_in_sets([T1|Tuples], L2, Opaques, Acc) ->
decorate_tuples_in_sets([], _L, _Opaques, Acc) ->
lists:reverse(Acc).
--spec t_opaque_from_records(dict()) -> [erl_type()].
+-spec t_opaque_from_records(type_table()) -> [erl_type()].
t_opaque_from_records(RecDict) ->
OpaqueRecDict =
@@ -733,13 +743,14 @@ t_opaque_from_records(RecDict) ->
end
end, RecDict),
OpaqueTypeDict =
- dict:map(fun({opaque, Name, _Arity}, {Module, Type, ArgNames}) ->
- case ArgNames of
- [] ->
- t_opaque(Module, Name, [], t_from_form(Type, RecDict));
- _ ->
- throw({error,"Polymorphic opaque types not supported yet"})
- end
+ dict:map(fun({opaque, Name, _Arity}, {Module, _Type, ArgNames}) ->
+ %% Args = args_to_types(ArgNames),
+ %% List = lists:zip(ArgNames, Args),
+ %% TmpVarDict = dict:from_list(List),
+ %% Rep = t_from_form(Type, RecDict, TmpVarDict),
+ Rep = t_none(), % not used for anything right now
+ Args = [t_any() || _ <- ArgNames],
+ skip_opaque_alias(Rep, Module, Name, Args)
end, OpaqueRecDict),
[OpaqueType || {_Key, OpaqueType} <- dict:to_list(OpaqueTypeDict)].
@@ -796,7 +807,9 @@ t_is_remote(Type) ->
is_remote(?remote(_)) -> true;
is_remote(_) -> false.
--spec t_solve_remote(erl_type(), set(), dict()) -> erl_type().
+-type mod_records() :: dict:dict(module(), type_table()).
+
+-spec t_solve_remote(erl_type(), sets:set(mfa()), mod_records()) -> erl_type().
t_solve_remote(Type, ExpTypes, Records) ->
{RT, _RR} = t_solve_remote(Type, ExpTypes, Records, []),
@@ -833,8 +846,12 @@ t_solve_remote(?union(List), ET, R, C) ->
{t_sup(RL), RR};
t_solve_remote(T, _ET, _R, _C) -> {T, []}.
-t_solve_remote_type(#remote{mod = RemMod, name = Name, args = Args} = RemType,
+t_solve_remote_type(#remote{mod = RemMod, name = Name, args = Args0} = RemType,
ET, R, C) ->
+ Args = lists:map(fun(A) ->
+ {Arg, _} = t_solve_remote(A, ET, R, C),
+ Arg
+ end, Args0),
ArgsLen = length(Args),
case dict:find(RemMod, R) of
error ->
@@ -880,9 +897,7 @@ t_solve_remote_type(#remote{mod = RemMod, name = Name, args = Args} = RemType,
true -> t_limit(NewRep, ?REC_TYPE_LIMIT);
false -> NewRep
end,
- {t_from_form({opaque, -1, Name, {Mod, Args, RT1}},
- RemDict, TmpVarDict),
- RetRR};
+ {skip_opaque_alias(RT1, Mod, Name, Args), RetRR};
error ->
Msg = io_lib:format("Unable to find remote type ~w:~w()\n",
[RemMod, Name]),
@@ -1958,20 +1973,24 @@ t_timeout() ->
-spec t_array() -> erl_type().
t_array() ->
- t_opaque(array, array, [],
+ t_opaque(array, array, [t_any()],
t_tuple([t_atom('array'),
t_sup([t_atom('undefined'), t_non_neg_integer()]),
t_sup([t_atom('undefined'), t_non_neg_integer()]),
- t_any(), t_any()])).
+ t_any(),
+ t_any()])).
-spec t_dict() -> erl_type().
t_dict() ->
- t_opaque(dict, dict, [],
+ t_opaque(dict, dict, [t_any(), t_any()],
t_tuple([t_atom('dict'),
- t_non_neg_integer(), t_non_neg_integer(),
- t_non_neg_integer(), t_non_neg_integer(),
- t_non_neg_integer(), t_non_neg_integer(),
+ t_sup([t_atom('undefined'), t_non_neg_integer()]),
+ t_sup([t_atom('undefined'), t_non_neg_integer()]),
+ t_sup([t_atom('undefined'), t_non_neg_integer()]),
+ t_sup([t_atom('undefined'), t_non_neg_integer()]),
+ t_sup([t_atom('undefined'), t_non_neg_integer()]),
+ t_sup([t_atom('undefined'), t_non_neg_integer()]),
t_sup([t_atom('undefined'), t_tuple()]),
t_sup([t_atom('undefined'), t_tuple()])])).
@@ -2000,12 +2019,12 @@ t_gb_tree() ->
-spec t_queue() -> erl_type().
t_queue() ->
- t_opaque(queue, queue, [], t_tuple([t_list(), t_list()])).
+ t_opaque(queue, queue, [t_any()], t_tuple([t_list(), t_list()])).
-spec t_set() -> erl_type().
t_set() ->
- t_opaque(sets, set, [],
+ t_opaque(sets, set, [t_any()],
t_tuple([t_atom('set'), t_non_neg_integer(), t_non_neg_integer(),
t_pos_integer(), t_non_neg_integer(), t_non_neg_integer(),
t_non_neg_integer(),
@@ -2023,18 +2042,6 @@ all_opaque_builtins() ->
[t_array(), t_dict(), t_digraph(), t_gb_set(),
t_gb_tree(), t_queue(), t_set(), t_tid()].
--spec is_opaque_builtin(atom(), atom()) -> boolean().
-
-is_opaque_builtin(array, array) -> true;
-is_opaque_builtin(dict, dict) -> true;
-is_opaque_builtin(digraph, digraph) -> true;
-is_opaque_builtin(gb_sets, gb_set) -> true;
-is_opaque_builtin(gb_trees, gb_tree) -> true;
-is_opaque_builtin(queue, queue) -> true;
-is_opaque_builtin(sets, set) -> true;
-is_opaque_builtin(ets, tid) -> true;
-is_opaque_builtin(_, _) -> false.
-
%%------------------------------------
%% ?none is allowed in products. A product of size 1 is not a product.
@@ -2082,11 +2089,11 @@ t_has_var(?tuple(Elements, _, _)) ->
t_has_var_list(Elements);
t_has_var(?tuple_set(_) = T) ->
t_has_var_list(t_tuple_subtypes(T));
-%% t_has_var(?opaque(_)=T) ->
-%% %% "Polymorphic opaque types not supported yet"
-%% t_has_var(t_opaque_structure(T));
-%% t_has_var(?union(_) = U) ->
-%% exit(flat_format("Union happens in t_has_var/1 ~p\n",[U]));
+t_has_var(?opaque(Set)) ->
+ %% Assume variables in 'args' are also present i 'struct'
+ t_has_var_list([O#opaque.struct || O <- set_to_list(Set)]);
+t_has_var(?union(List)) ->
+ t_has_var_list(List);
t_has_var(_) -> false.
-spec t_has_var_list([erl_type()]) -> boolean().
@@ -2117,9 +2124,10 @@ t_collect_vars(?tuple(Types, _, _), Acc) ->
t_collect_vars(?tuple_set(_) = TS, Acc) ->
lists:foldl(fun(T, TmpAcc) -> t_collect_vars(T, TmpAcc) end, Acc,
t_tuple_subtypes(TS));
-%% t_collect_vars(?opaque(_)=T, Acc) ->
-%% %% "Polymorphic opaque types not supported yet"
-%% t_collect_vars(t_opaque_structure(T), Acc);
+t_collect_vars(?opaque(Set), Acc) ->
+ %% Assume variables in 'args' are also present i 'struct'
+ lists:foldl(fun(T, TmpAcc) -> t_collect_vars(T, TmpAcc) end, Acc,
+ [O#opaque.struct || O <- set_to_list(Set)]);
t_collect_vars(_, Acc) ->
Acc.
@@ -2442,8 +2450,8 @@ sup_opaque(List) ->
?opaque(ordsets:from_list(L)).
sup_opaq(L0) ->
- L1 = [{{Mod,Name}, T} ||
- #opaque{mod = Mod, name = Name}=T <- L0],
+ L1 = [{{Mod,Name,Args}, T} ||
+ #opaque{mod = Mod, name = Name, args = Args}=T <- L0],
F = family(L1),
[supl(Ts) || {_, Ts} <- F].
@@ -2809,31 +2817,35 @@ inf_collect(_T1, [], _Opaques, OpL) ->
OpL.
combine(S, T1, T2) ->
- #opaque{mod = Mod1, name = Name1} = T1,
- #opaque{mod = Mod2, name = Name2} = T2,
- case {Mod1, Name1} =:= {Mod2, Name2} of
- true -> [comb(Mod1, Name1, S, T1)];
- false -> [comb(Mod1, Name1, S, T1), comb(Mod2, Name2, S, T2)]
+ #opaque{mod = Mod1, name = Name1, args = Args1} = T1,
+ #opaque{mod = Mod2, name = Name2, args = Args2} = T2,
+ case is_same_type_name({Mod1, Name1, Args1}, {Mod2, Name2, Args2}) of
+ true -> [comb(Mod1, Name1, Args1, S, T1)];
+ false -> [comb(Mod1, Name1, Args1, S, T1), comb(Mod2, Name2, Args2, S, T2)]
end.
-comb(Mod, Name, S, T) ->
- case is_same_name(Mod, Name, S) of
+comb(Mod, Name, Args, S, T) ->
+ case is_same_name(Mod, Name, Args, S) of
true -> S;
false -> T#opaque{struct = S}
end.
-is_same_name(Mod, Name, ?opaque([#opaque{mod = Mod, name = Name}])) -> true;
-is_same_name(_Mod, _Name, _Opaque) -> false.
+is_same_name(Mod1, Name1, Args1,
+ ?opaque([#opaque{mod = Mod2, name = Name2, args = Args2}])) ->
+ is_same_type_name({Mod1, Name1, Args1}, {Mod2, Name2, Args2});
+is_same_name(_, _, _, _) -> false.
%% Combining two lists this way can be very time consuming...
+%% Note: two parameterized opaque types are not the same if their
+%% actual parameters differ
inf_opaque(Set1, Set2, Opaques) ->
List1 = inf_look_up(Set1, 1, Opaques),
List2 = inf_look_up(Set2, 2, Opaques),
List0 = [combine(Inf, T1, T2) ||
- {Is1, ModName1, T1} <- List1,
- {Is2, ModName2, T2} <- List2,
- not t_is_none(Inf = inf_opaque_types(Is1, ModName1, T1,
- Is2, ModName2, T2,
+ {Is1, ModNameArgs1, T1} <- List1,
+ {Is2, ModNameArgs2, T2} <- List2,
+ not t_is_none(Inf = inf_opaque_types(Is1, ModNameArgs1, T1,
+ Is2, ModNameArgs2, T2,
Opaques))],
List = lists:sort(lists:append(List0)),
sup_opaque(List).
@@ -2841,18 +2853,22 @@ inf_opaque(Set1, Set2, Opaques) ->
%% Optimization: do just one lookup.
inf_look_up(Set, Pos, Opaques) ->
[{Opaques =:= 'universe' orelse inf_is_opaque_type2(T, Pos, Opaques),
- {M, N}, T} ||
- #opaque{mod = M, name = N} = T <- set_to_list(Set)].
+ {M, N, Args}, T} ||
+ #opaque{mod = M, name = N, args = Args} = T <- set_to_list(Set)].
inf_is_opaque_type2(T, Pos, {match, Opaques}) ->
is_opaque_type2(T, Opaques) orelse throw(Pos);
inf_is_opaque_type2(T, _Pos, Opaques) ->
is_opaque_type2(T, Opaques).
-inf_opaque_types(IsOpaque1, ModName1, T1, IsOpaque2, ModName2, T2, Opaques) ->
+inf_opaque_types(IsOpaque1, ModNameArgs1, T1,
+ IsOpaque2, ModNameArgs2, T2, Opaques) ->
#opaque{struct = S1}=T1,
#opaque{struct = S2}=T2,
- case Opaques =:= 'universe' orelse ModName1 =:= ModName2 of
+ case
+ Opaques =:= 'universe' orelse
+ is_same_type_name(ModNameArgs1, ModNameArgs2)
+ of
true -> t_inf(S1, S2, Opaques);
false ->
case {IsOpaque1, IsOpaque2} of
@@ -3018,13 +3034,13 @@ findfirst(N1, N2, U1, B1, U2, B2) ->
%% to types. Hans Bolinder suggested the use of lists of Key-Value pairs for
%% this data structure and measurements showed a non-trivial speedup when using
%% them for operations within this module (e.g. in t_unify/2). However, there
-%% is code outside erl_types that still passes a dict() in the 2nd argument.
+%% is code outside erl_types that still passes a dict:dict() in the 2nd argument.
%% So, for the time being, this module provides a t_subst/2 function for these
%% external calls and a clone of it (t_subst_kv/2) which is used from all calls
%% from within this module. This code duplication needs to be eliminated at
%% some point.
--spec t_subst(erl_type(), dict()) -> erl_type().
+-spec t_subst(erl_type(), dict:dict(atom(), erl_type())) -> erl_type().
t_subst(T, Dict) ->
case t_has_var(T) of
@@ -3060,11 +3076,13 @@ t_subst_dict(?tuple(Elements, _Arity, _Tag), Dict) ->
t_tuple([t_subst_dict(E, Dict) || E <- Elements]);
t_subst_dict(?tuple_set(_) = TS, Dict) ->
t_sup([t_subst_dict(T, Dict) || T <- t_tuple_subtypes(TS)]);
-%% t_subst_dict(?opaque(Es), Dict) ->
-%% %% "Polymorphic opaque types not supported yet"
-%% List = [Opaque#opaque{struct = t_subst_dict(S, Dict)} ||
-%% Opaque = #opaque{struct = S} <- set_to_list(Es)],
-%% ?opaque(ordsets:from_list(List));
+t_subst_dict(?opaque(Es), Dict) ->
+ List = [Opaque#opaque{args = [t_subst_dict(Arg, Dict) || Arg <- Args],
+ struct = t_subst_dict(S, Dict)} ||
+ Opaque = #opaque{args = Args, struct = S} <- set_to_list(Es)],
+ ?opaque(ordsets:from_list(List));
+t_subst_dict(?union(List), Dict) ->
+ ?union([t_subst_dict(E, Dict) || E <- List]);
t_subst_dict(T, _Dict) ->
T.
@@ -3107,11 +3125,13 @@ t_subst_aux(?tuple(Elements, _Arity, _Tag), VarMap) ->
t_tuple([t_subst_aux(E, VarMap) || E <- Elements]);
t_subst_aux(?tuple_set(_) = TS, VarMap) ->
t_sup([t_subst_aux(T, VarMap) || T <- t_tuple_subtypes(TS)]);
-%% t_subst_aux(?opaque(Es), VarMap) ->
-%% %% "Polymorphic opaque types not supported yet"
-%% List = [Opaque#opaque{struct = t_subst_aux(S, VarMap)} ||
-%% Opaque = #opaque{struct = S} <- set_to_list(Es)],
-%% ?opaque(ordsets:from_list(List));
+t_subst_aux(?opaque(Es), VarMap) ->
+ List = [Opaque#opaque{args = [t_subst_aux(Arg, VarMap) || Arg <- Args],
+ struct = t_subst_aux(S, VarMap)} ||
+ Opaque = #opaque{args = Args, struct = S} <- set_to_list(Es)],
+ ?opaque(ordsets:from_list(List));
+t_subst_aux(?union(List), VarMap) ->
+ ?union([t_subst_aux(E, VarMap) || E <- List]);
t_subst_aux(T, _VarMap) ->
T.
@@ -3232,15 +3252,20 @@ unify_union(List) ->
is_opaque_type(?opaque(Elements), Opaques) ->
lists:any(fun(Opaque) -> is_opaque_type2(Opaque, Opaques) end, Elements).
-is_opaque_type2(#opaque{mod = Mod1, name = Name1}, Opaques) ->
+is_opaque_type2(#opaque{mod = Mod1, name = Name1, args = Args1}, Opaques) ->
F1 = fun(?opaque(Es)) ->
- F2 = fun(#opaque{mod = Mod, name = Name}) ->
- Mod1 =:= Mod andalso Name1 =:= Name
+ F2 = fun(#opaque{mod = Mod, name = Name, args = Args}) ->
+ is_type_name(Mod1, Name1, Args1, Mod, Name, Args)
end,
lists:any(F2, Es)
end,
lists:any(F1, Opaques).
+is_type_name(Mod, Name, Args1, Mod, Name, Args2) ->
+ length(Args1) =:= length(Args2);
+is_type_name(Mod1, Name1, Args1, Mod2, Name2, Args2) ->
+ is_same_type_name2(Mod1, Name1, Args1, Mod2, Name2, Args2).
+
%% Two functions since t_unify is not symmetric.
unify_tuple_set_and_tuple1(?tuple_set([{Arity, List}]),
?tuple(Elements2, Arity, _), VarMap) ->
@@ -3759,7 +3784,7 @@ t_limit_k(T, _K) -> T.
%%
%%============================================================================
--spec t_abstract_records(erl_type(), dict()) -> erl_type().
+-spec t_abstract_records(erl_type(), type_table()) -> erl_type().
t_abstract_records(?list(Contents, Termination, Size), RecDict) ->
case t_abstract_records(Contents, RecDict) of
@@ -3839,7 +3864,7 @@ t_map(Fun, T) ->
t_to_string(T) ->
t_to_string(T, dict:new()).
--spec t_to_string(erl_type(), dict()) -> string().
+-spec t_to_string(erl_type(), type_table()) -> string().
t_to_string(?any, _RecDict) ->
"any()";
@@ -3885,8 +3910,8 @@ t_to_string(?identifier(Set), _RecDict) ->
string:join([flat_format("~w()", [T]) || T <- set_to_list(Set)], " | ")
end;
t_to_string(?opaque(Set), RecDict) ->
- string:join([opaque_type(Mod, Name, S, RecDict) ||
- #opaque{mod = Mod, name = Name, struct = S}
+ string:join([opaque_type(Mod, Name, Args, S, RecDict) ||
+ #opaque{mod = Mod, name = Name, struct = S, args = Args}
<- set_to_list(Set)],
" | ");
t_to_string(?matchstate(Pres, Slots), RecDict) ->
@@ -4025,7 +4050,7 @@ record_fields_to_string([F|Fs], [{FName, _DefType}|FDefs], RecDict, Acc) ->
record_fields_to_string([], [], _RecDict, Acc) ->
lists:reverse(Acc).
--spec record_field_diffs_to_string(erl_type(), dict()) -> string().
+-spec record_field_diffs_to_string(erl_type(), type_table()) -> string().
record_field_diffs_to_string(?tuple([_|Fs], Arity, Tag), RecDict) ->
[TagAtom] = atom_vals(Tag),
@@ -4059,11 +4084,14 @@ union_sequence(Types, RecDict) ->
string:join(List, " | ").
-ifdef(DEBUG).
-opaque_type(Mod, Name, S, RecDict) ->
- opaque_name(Mod, Name, t_to_string(S, RecDict)).
+opaque_type(Mod, Name, _Args, S, RecDict) ->
+ ArgsString = comma_sequence(_Args, RecDict),
+ String = t_to_string(S, RecDict),
+ opaque_name(Mod, Name, ArgsString) ++ "[" ++ String ++ "]".
-else.
-opaque_type(Mod, Name, _S, _RecDict) ->
- opaque_name(Mod, Name, "").
+opaque_type(Mod, Name, Args, _S, RecDict) ->
+ ArgsString = comma_sequence(Args, RecDict),
+ opaque_name(Mod, Name, ArgsString).
-endif.
opaque_name(Mod, Name, Extra) ->
@@ -4071,11 +4099,16 @@ opaque_name(Mod, Name, Extra) ->
flat_format("~s(~s)", [S, Extra]).
mod_name(Mod, Name) ->
- case is_opaque_builtin(Mod, Name) of
+ case is_obsolete_opaque_builtin(Mod, Name) of
true -> flat_format("~w", [Name]);
false -> flat_format("~w:~w", [Mod, Name])
end.
+is_obsolete_opaque_builtin(digraph, digraph) -> true;
+is_obsolete_opaque_builtin(gb_sets, gb_set) -> true;
+is_obsolete_opaque_builtin(gb_trees, gb_tree) -> true;
+is_obsolete_opaque_builtin(_, _) -> false.
+
%%=============================================================================
%%
%% Build a type from parse forms.
@@ -4087,19 +4120,20 @@ mod_name(Mod, Name) ->
t_from_form(Form) ->
t_from_form(Form, dict:new()).
--spec t_from_form(parse_form(), dict()) -> erl_type().
+-spec t_from_form(parse_form(), type_table()) -> erl_type().
t_from_form(Form, RecDict) ->
t_from_form(Form, RecDict, dict:new()).
--spec t_from_form(parse_form(), dict(), dict()) -> erl_type().
+-spec t_from_form(parse_form(), type_table(), var_table()) -> erl_type().
t_from_form(Form, RecDict, VarDict) ->
{T, _R} = t_from_form(Form, [], RecDict, VarDict),
T.
--type type_names() :: [{'type' | 'opaque' | 'record', atom()}].
--spec t_from_form(parse_form(), type_names(), dict(), dict()) ->
+-type type_names() :: [type_key() | record_key()].
+
+-spec t_from_form(parse_form(), type_names(), type_table(), var_table()) ->
{erl_type(), type_names()}.
t_from_form({var, _L, '_'}, _TypeNames, _RecDict, _VarDict) ->
@@ -4138,8 +4172,8 @@ t_from_form({type, _L, any, []}, _TypeNames, _RecDict, _VarDict) ->
{t_any(), []};
t_from_form({type, _L, arity, []}, _TypeNames, _RecDict, _VarDict) ->
{t_arity(), []};
-t_from_form({type, _L, array, []}, _TypeNames, _RecDict, _VarDict) ->
- {t_array(), []};
+t_from_form({type, _L, array, []}, TypeNames, RecDict, VarDict) ->
+ builtin_type(array, t_array(), TypeNames, RecDict, VarDict);
t_from_form({type, _L, atom, []}, _TypeNames, _RecDict, _VarDict) ->
{t_atom(), []};
t_from_form({type, _L, binary, []}, _TypeNames, _RecDict, _VarDict) ->
@@ -4161,10 +4195,10 @@ t_from_form({type, _L, byte, []}, _TypeNames, _RecDict, _VarDict) ->
{t_byte(), []};
t_from_form({type, _L, char, []}, _TypeNames, _RecDict, _VarDict) ->
{t_char(), []};
-t_from_form({type, _L, dict, []}, _TypeNames, _RecDict, _VarDict) ->
- {t_dict(), []};
-t_from_form({type, _L, digraph, []}, _TypeNames, _RecDict, _VarDict) ->
- {t_digraph(), []};
+t_from_form({type, _L, dict, []}, TypeNames, RecDict, VarDict) ->
+ builtin_type(dict, t_dict(), TypeNames, RecDict, VarDict);
+t_from_form({type, _L, digraph, []}, TypeNames, RecDict, VarDict) ->
+ builtin_type(digraph, t_digraph(), TypeNames, RecDict, VarDict);
t_from_form({type, _L, float, []}, _TypeNames, _RecDict, _VarDict) ->
{t_float(), []};
t_from_form({type, _L, function, []}, _TypeNames, _RecDict, _VarDict) ->
@@ -4180,10 +4214,10 @@ t_from_form({type, _L, 'fun', [{type, _, product, Domain}, Range]},
{L, R1} = list_from_form(Domain, TypeNames, RecDict, VarDict),
{T, R2} = t_from_form(Range, TypeNames, RecDict, VarDict),
{t_fun(L, T), R1 ++ R2};
-t_from_form({type, _L, gb_set, []}, _TypeNames, _RecDict, _VarDict) ->
- {t_gb_set(), []};
-t_from_form({type, _L, gb_tree, []}, _TypeNames, _RecDict, _VarDict) ->
- {t_gb_tree(), []};
+t_from_form({type, _L, gb_set, []}, TypeNames, RecDict, VarDict) ->
+ builtin_type(gb_set, t_gb_set(), TypeNames, RecDict, VarDict);
+t_from_form({type, _L, gb_tree, []}, TypeNames, RecDict, VarDict) ->
+ builtin_type(gb_tree, t_gb_tree(), TypeNames, RecDict, VarDict);
t_from_form({type, _L, identifier, []}, _TypeNames, _RecDict, _VarDict) ->
{t_identifier(), []};
t_from_form({type, _L, integer, []}, _TypeNames, _RecDict, _VarDict) ->
@@ -4256,8 +4290,8 @@ t_from_form({type, _L, maybe_improper_list, [Content, Termination]},
t_from_form({type, _L, product, Elements}, TypeNames, RecDict, VarDict) ->
{L, R} = list_from_form(Elements, TypeNames, RecDict, VarDict),
{t_product(L), R};
-t_from_form({type, _L, queue, []}, _TypeNames, _RecDict, _VarDict) ->
- {t_queue(), []};
+t_from_form({type, _L, queue, []}, TypeNames, RecDict, VarDict) ->
+ builtin_type(queue, t_queue(), TypeNames, RecDict, VarDict);
t_from_form({type, _L, range, [From, To]} = Type,
_TypeNames, _RecDict, _VarDict) ->
case {erl_eval:partial_eval(From), erl_eval:partial_eval(To)} of
@@ -4269,14 +4303,14 @@ t_from_form({type, _L, record, [Name|Fields]}, TypeNames, RecDict, VarDict) ->
record_from_form(Name, Fields, TypeNames, RecDict, VarDict);
t_from_form({type, _L, reference, []}, _TypeNames, _RecDict, _VarDict) ->
{t_reference(), []};
-t_from_form({type, _L, set, []}, _TypeNames, _RecDict, _VarDict) ->
- {t_set(), []};
+t_from_form({type, _L, set, []}, TypeNames, RecDict, VarDict) ->
+ builtin_type(set, t_set(), TypeNames, RecDict, VarDict);
t_from_form({type, _L, string, []}, _TypeNames, _RecDict, _VarDict) ->
{t_string(), []};
t_from_form({type, _L, term, []}, _TypeNames, _RecDict, _VarDict) ->
{t_any(), []};
-t_from_form({type, _L, tid, []}, _TypeNames, _RecDict, _VarDict) ->
- {t_tid(), []};
+t_from_form({type, _L, tid, []}, TypeNames, RecDict, VarDict) ->
+ builtin_type(tid, t_tid(), TypeNames, RecDict, VarDict);
t_from_form({type, _L, timeout, []}, _TypeNames, _RecDict, _VarDict) ->
{t_timeout(), []};
t_from_form({type, _L, tuple, any}, _TypeNames, _RecDict, _VarDict) ->
@@ -4288,61 +4322,67 @@ t_from_form({type, _L, union, Args}, TypeNames, RecDict, VarDict) ->
{L, R} = list_from_form(Args, TypeNames, RecDict, VarDict),
{t_sup(L), R};
t_from_form({type, _L, Name, Args}, TypeNames, RecDict, VarDict) ->
+ type_from_form(Name, Args, TypeNames, RecDict, VarDict);
+t_from_form({opaque, _L, Name, {Mod, Args, Rep}}, _TypeNames,
+ _RecDict, _VarDict) ->
+ {t_opaque(Mod, Name, Args, Rep), []}.
+
+builtin_type(Name, Type, TypeNames, RecDict, VarDict) ->
+ case lookup_type(Name, 0, RecDict) of
+ {_, {_M, _T, _A}} ->
+ type_from_form(Name, [], TypeNames, RecDict, VarDict);
+ error ->
+ {Type, []}
+ end.
+
+type_from_form(Name, Args, TypeNames, RecDict, VarDict) ->
ArgsLen = length(Args),
+ ArgTypes = forms_to_types(Args, TypeNames, RecDict, VarDict),
case lookup_type(Name, ArgsLen, RecDict) of
{type, {_Module, Type, ArgNames}} ->
- case can_unfold_more({type, Name}, TypeNames) of
+ TypeName = {type, Name, ArgsLen},
+ case can_unfold_more(TypeName, TypeNames) of
true ->
- List = lists:zipwith(
- fun(ArgName, ArgType) ->
- {Ttemp, _R} = t_from_form(ArgType, TypeNames,
- RecDict, VarDict),
- {ArgName, Ttemp}
- end,
- ArgNames, Args),
+ List = lists:zip(ArgNames, ArgTypes),
TmpVarDict = dict:from_list(List),
- {T, R} = t_from_form(Type, [{type, Name}|TypeNames],
+ {T, R} = t_from_form(Type, [TypeName|TypeNames],
RecDict, TmpVarDict),
- case lists:member({type, Name}, R) of
+ case lists:member(TypeName, R) of
true -> {t_limit(T, ?REC_TYPE_LIMIT), R};
false -> {T, R}
end;
- false -> {t_any(), [{type, Name}]}
+ false -> {t_any(), [TypeName]}
end;
{opaque, {Module, Type, ArgNames}} ->
+ TypeName = {opaque, Name, ArgsLen},
{Rep, Rret} =
- case can_unfold_more({opaque, Name}, TypeNames) of
+ case can_unfold_more(TypeName, TypeNames) of
true ->
- List = lists:zipwith(
- fun(ArgName, ArgType) ->
- {Ttemp, _R} = t_from_form(ArgType, TypeNames,
- RecDict, VarDict),
- {ArgName, Ttemp}
- end,
- ArgNames, Args),
+ List = lists:zip(ArgNames, ArgTypes),
TmpVarDict = dict:from_list(List),
- {T, R} = t_from_form(Type, [{opaque, Name}|TypeNames],
+ {T, R} = t_from_form(Type, [TypeName|TypeNames],
RecDict, TmpVarDict),
- case lists:member({opaque, Name}, R) of
+ case lists:member(TypeName, R) of
true -> {t_limit(T, ?REC_TYPE_LIMIT), R};
false -> {T, R}
end;
- false -> {t_any(), [{opaque, Name}]}
+ false -> {t_any(), [TypeName]}
end,
- Tret = t_from_form({opaque, -1, Name, {Module, Args, Rep}},
- RecDict, VarDict),
- {Tret, Rret};
+ Args2 = [subst_all_vars_to_any(ArgType) || ArgType <- ArgTypes],
+ {skip_opaque_alias(Rep, Module, Name, Args2), Rret};
error ->
Msg = io_lib:format("Unable to find type ~w/~w\n", [Name, ArgsLen]),
throw({error, Msg})
- end;
-t_from_form({opaque, _L, Name, {Mod, Args, Rep}}, _TypeNames,
- _RecDict, _VarDict) ->
- case Args of
- [] -> {t_opaque(Mod, Name, Args, Rep), []};
- _ -> throw({error, "Polymorphic opaque types not supported yet"})
end.
+forms_to_types(Forms, TypeNames, RecDict, VarDict) ->
+ {Types, _} = list_from_form(Forms, TypeNames, RecDict, VarDict),
+ Types.
+
+skip_opaque_alias(?opaque(_) = T, _Mod, _Name, _Args) -> T;
+skip_opaque_alias(T, Module, Name, Args) ->
+ t_opaque(Module, Name, Args, T).
+
record_from_form({atom, _, Name}, ModFields, TypeNames, RecDict, VarDict) ->
case can_unfold_more({record, Name}, TypeNames) of
true ->
@@ -4403,8 +4443,10 @@ build_field_dict([], _TypeNames, _RecDict, _VarDict, Acc) ->
get_mod_record([{FieldName, DeclType}|Left1],
[{FieldName, ModType}|Left2], Acc) ->
- case t_is_var(ModType) orelse t_is_remote(ModType) orelse
- t_is_subtype(ModType, DeclType) of
+ ModTypeNoVars = subst_all_vars_to_any(ModType),
+ case
+ t_is_remote(ModTypeNoVars) orelse t_is_subtype(ModTypeNoVars, DeclType)
+ of
false -> {error, FieldName};
true -> get_mod_record(Left1, Left2, [{FieldName, ModType}|Acc])
end;
@@ -4561,7 +4603,7 @@ is_erl_type(?unit) -> true;
is_erl_type(#c{}) -> true;
is_erl_type(_) -> false.
--spec lookup_record(atom(), dict()) ->
+-spec lookup_record(atom(), type_table()) ->
'error' | {'ok', [{atom(), parse_form() | erl_type()}]}.
lookup_record(Tag, RecDict) when is_atom(Tag) ->
@@ -4576,7 +4618,8 @@ lookup_record(Tag, RecDict) when is_atom(Tag) ->
error
end.
--spec lookup_record(atom(), arity(), dict()) -> 'error' | {'ok', [{atom(), erl_type()}]}.
+-spec lookup_record(atom(), arity(), type_table()) ->
+ 'error' | {'ok', [{atom(), erl_type()}]}.
lookup_record(Tag, Arity, RecDict) when is_atom(Tag) ->
case dict:find({record, Tag}, RecDict) of
@@ -4595,7 +4638,8 @@ lookup_type(Name, Arity, RecDict) ->
{ok, Found} -> {type, Found}
end.
--spec type_is_defined('type' | 'opaque', atom(), arity(), dict()) -> boolean().
+-spec type_is_defined('type' | 'opaque', atom(), arity(), type_table()) ->
+ boolean().
type_is_defined(TypeOrOpaque, Name, Arity, RecDict) ->
dict:is_key({TypeOrOpaque, Name, Arity}, RecDict).
@@ -4627,6 +4671,30 @@ do_opaque(?union(List) = Type, Opaques, Pred) ->
do_opaque(Type, _Opaques, Pred) ->
Pred(Type).
+is_same_type_name(ModNameArgs, ModNameArgs) -> true;
+is_same_type_name({Mod, Name, Args1}, {Mod, Name, Args2}) ->
+ all_any(Args1) orelse all_any(Args2);
+is_same_type_name({Mod1, Name1, Args1}, {Mod2, Name2, Args2}) ->
+ is_same_type_name2(Mod1, Name1, Args1, Mod2, Name2, Args2).
+
+all_any([]) -> true;
+all_any([T|L]) ->
+ t_is_any(T) andalso all_any(L);
+all_any(_) -> false.
+
+%% Compatibility. In Erlang/OTP 17 the pre-defined opaque types
+%% digraph() and so on can be used, but there are also new types such
+%% as digraph:graph() with the exact same meaning. In Erlang/OTP R18.0
+%% all but the last clause can be removed.
+
+is_same_type_name2(digraph, digraph, [], digraph, graph, []) -> true;
+is_same_type_name2(digraph, graph, [], digraph, digraph, []) -> true;
+is_same_type_name2(gb_sets, gb_set, [], gb_sets, set, [_]) -> true;
+is_same_type_name2(gb_sets, set, [_], gb_sets, gb_set, []) -> true;
+is_same_type_name2(gb_trees, gb_tree, [], gb_trees, tree, [_, _]) -> true;
+is_same_type_name2(gb_trees, tree, [_, _], gb_trees, gb_tree, []) -> true;
+is_same_type_name2(_, _, _, _, _, _) -> false.
+
%% -----------------------------------
%% Set
%%