aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src/erl_lint.erl
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/src/erl_lint.erl')
-rw-r--r--lib/stdlib/src/erl_lint.erl345
1 files changed, 225 insertions, 120 deletions
diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl
index 9f5be2da37..c4c94fbee4 100644
--- a/lib/stdlib/src/erl_lint.erl
+++ b/lib/stdlib/src/erl_lint.erl
@@ -80,13 +80,17 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) ->
-type fa() :: {atom(), arity()}. % function+arity
-type ta() :: {atom(), arity()}. % type+arity
+-record(typeinfo, {attr, line}).
+
%% Usage of records, functions, and imports. The variable table, which
%% is passed on as an argument, holds the usage of variables.
-record(usage, {
calls = dict:new(), %Who calls who
imported = [], %Actually imported functions
- used_records=sets:new() :: sets:set(),%Used record definitions
- used_types = dict:new() :: dict:dict()%Used type definitions
+ used_records = sets:new() %Used record definitions
+ :: sets:set(atom()),
+ used_types = dict:new() %Used type definitions
+ :: dict:dict(ta(), line())
}).
%% Define the lint state record.
@@ -95,13 +99,17 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) ->
-record(lint, {state=start :: 'start' | 'attribute' | 'function',
module=[], %Module
behaviour=[], %Behaviour
- exports=gb_sets:empty() :: gb_sets:set(),%Exports
- imports=[], %Imports
+ exports=gb_sets:empty() :: gb_sets:set(fa()),%Exports
+ imports=[] :: [fa()], %Imports, an orddict()
compile=[], %Compile flags
- records=dict:new() :: dict:dict(), %Record definitions
- locals=gb_sets:empty() :: gb_sets:set(),%All defined functions (prescanned)
- no_auto=gb_sets:empty() :: gb_sets:set() | 'all',%Functions explicitly not autoimported
- defined=gb_sets:empty() :: gb_sets:set(),%Defined fuctions
+ records=dict:new() %Record definitions
+ :: dict:dict(atom(), {line(),Fields :: term()}),
+ locals=gb_sets:empty() %All defined functions (prescanned)
+ :: gb_sets:set(fa()),
+ no_auto=gb_sets:empty() %Functions explicitly not autoimported
+ :: gb_sets:set(fa()) | 'all',
+ defined=gb_sets:empty() %Defined fuctions
+ :: gb_sets:set(fa()),
on_load=[] :: [fa()], %On-load function
on_load_line=0 :: line(), %Line for on_load
clashes=[], %Exported functions named as BIFs
@@ -116,12 +124,16 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) ->
%outside any fun or lc
xqlc= false :: boolean(), %true if qlc.hrl included
new = false :: boolean(), %Has user-defined 'new/N'
- called= [] :: [{fa(),line()}], %Called functions
+ called= [] :: [{fa(),line()}], %Called functions
usage = #usage{} :: #usage{},
- specs = dict:new() :: dict:dict(), %Type specifications
- callbacks = dict:new() :: dict:dict(), %Callback types
- types = dict:new() :: dict:dict(), %Type definitions
- exp_types=gb_sets:empty():: gb_sets:set()%Exported types
+ specs = dict:new() %Type specifications
+ :: dict:dict(mfa(), line()),
+ callbacks = dict:new() %Callback types
+ :: dict:dict(mfa(), line()),
+ types = dict:new() %Type definitions
+ :: dict:dict(ta(), #typeinfo{}),
+ exp_types=gb_sets:empty() %Exported types
+ :: gb_sets:set(ta())
}).
-type lint_state() :: #lint{}.
@@ -225,6 +237,8 @@ format_error({too_many_arguments,Arity}) ->
"maximum allowed is ~w", [Arity,?MAX_ARGUMENTS]);
%% --- patterns and guards ---
format_error(illegal_pattern) -> "illegal pattern";
+format_error(illegal_map_key) ->
+ "illegal map key";
format_error({illegal_map_key_variable,K}) ->
io_lib:format("illegal use of variable ~w in map",[K]);
format_error(illegal_bin_pattern) ->
@@ -317,10 +331,14 @@ format_error({undefined_type, {TypeName, Arity}}) ->
io_lib:format("type ~w~s undefined", [TypeName, gen_type_paren(Arity)]);
format_error({unused_type, {TypeName, Arity}}) ->
io_lib:format("type ~w~s is unused", [TypeName, gen_type_paren(Arity)]);
-format_error({new_builtin_type, {TypeName, Arity}}) ->
- io_lib:format("type ~w~s is a new builtin type; "
+%% format_error({new_builtin_type, {TypeName, Arity}}) ->
+%% io_lib:format("type ~w~s is a new builtin type; "
+%% "its (re)definition is allowed only until the next release",
+%% [TypeName, gen_type_paren(Arity)]);
+format_error({new_var_arity_type, TypeName}) ->
+ io_lib:format("type ~w is a new builtin type; "
"its (re)definition is allowed only until the next release",
- [TypeName, gen_type_paren(Arity)]);
+ [TypeName]);
format_error({builtin_type, {TypeName, Arity}}) ->
io_lib:format("type ~w~s is a builtin type; it cannot be redefined",
[TypeName, gen_type_paren(Arity)]);
@@ -344,10 +362,19 @@ format_error(spec_wrong_arity) ->
"spec has the wrong arity";
format_error(callback_wrong_arity) ->
"callback has the wrong arity";
-format_error({deprecated_type, {Name, Arity}, {Mod, NewName}, Rel}) ->
+format_error({deprecated_builtin_type, {Name, Arity},
+ Replacement, Rel}) ->
+ UseS = case Replacement of
+ {Mod, NewName} ->
+ io_lib:format("use ~w:~w/~w", [Mod, NewName, Arity]);
+ {Mod, NewName, NewArity} ->
+ io_lib:format("use ~w:~w/~w or preferably ~w:~w/~w",
+ [Mod, NewName, Arity,
+ Mod, NewName, NewArity])
+ end,
io_lib:format("type ~w/~w is deprecated and will be "
- "removed in ~s; use ~w:~w/~w",
- [Name, Arity, Rel, Mod, NewName, Arity]);
+ "removed in ~s; use ~s",
+ [Name, Arity, Rel, UseS]);
format_error({not_exported_opaque, {TypeName, Arity}}) ->
io_lib:format("opaque type ~w~s is not exported",
[TypeName, gen_type_paren(Arity)]);
@@ -499,6 +526,9 @@ start(File, Opts) ->
{deprecated_function,
bool_option(warn_deprecated_function, nowarn_deprecated_function,
true, Opts)},
+ {deprecated_type,
+ bool_option(warn_deprecated_type, nowarn_deprecated_type,
+ true, Opts)},
{obsolete_guard,
bool_option(warn_obsolete_guard, nowarn_obsolete_guard,
true, Opts)},
@@ -1156,7 +1186,7 @@ export_type(Line, ETs, #lint{usage = Usage, exp_types = ETs0} = St0) ->
add_error(Line, {bad_export_type, ETs}, St0)
end.
--spec exports(lint_state()) -> gb_sets:set().
+-spec exports(lint_state()) -> gb_sets:set(fa()).
exports(#lint{compile = Opts, defined = Defs, exports = Es}) ->
case lists:member(export_all, Opts) of
@@ -1373,18 +1403,20 @@ pattern({cons,_Line,H,T}, Vt, Old, Bvt, St0) ->
pattern({tuple,_Line,Ps}, Vt, Old, Bvt, St) ->
pattern_list(Ps, Vt, Old, Bvt, St);
pattern({map,_Line,Ps}, Vt, Old, Bvt, St) ->
- pattern_list(Ps, Vt, Old, Bvt, St);
-pattern({map_field_assoc,Line,_,_}, _, _, _, St) ->
- {[],[],add_error(Line, illegal_pattern, St)};
-pattern({map_field_exact,Line,KP,VP}, Vt, Old, Bvt0, St0) ->
- %% if the key pattern has variables we should fail
- case expr(KP,[],St0) of
- {[],_} ->
- pattern(VP, Vt, Old, Bvt0, St0);
- {[Var|_],_} ->
- %% found variables in key expression
- {Vt,Old,add_error(Line,{illegal_map_key_variable,element(1,Var)},St0)}
- end;
+ foldl(fun
+ ({map_field_assoc,L,_,_}, {Psvt,Bvt0,St0}) ->
+ {Psvt,Bvt0,add_error(L, illegal_pattern, St0)};
+ ({map_field_exact,L,KP,VP}, {Psvt,Bvt0,St0}) ->
+ case is_valid_map_key(KP, St0) of
+ true ->
+ {Pvt,Bvt1,St1} = pattern(VP, Vt, Old, Bvt, St0),
+ {vtmerge_pat(Pvt, Psvt),vtmerge_pat(Bvt0, Bvt1), St1};
+ false ->
+ {Psvt,Bvt0,add_error(L, illegal_map_key, St0)};
+ {false,variable,Var} ->
+ {Psvt,Bvt0,add_error(L, {illegal_map_key_variable,Var}, St0)}
+ end
+ end, {[],[],St}, Ps);
%%pattern({struct,_Line,_Tag,Ps}, Vt, Old, Bvt, St) ->
%% pattern_list(Ps, Vt, Old, Bvt, St);
pattern({record_index,Line,Name,Field}, _Vt, _Old, _Bvt, St) ->
@@ -1773,13 +1805,11 @@ gexpr({cons,_Line,H,T}, Vt, St) ->
gexpr({tuple,_Line,Es}, Vt, St) ->
gexpr_list(Es, Vt, St);
gexpr({map,_Line,Es}, Vt, St) ->
- gexpr_list(Es, Vt, St);
+ map_fields(Es, Vt, check_assoc_fields(Es, St), fun gexpr_list/3);
gexpr({map,_Line,Src,Es}, Vt, St) ->
- gexpr_list([Src|Es], Vt, St);
-gexpr({map_field_assoc,_Line,K,V}, Vt, St) ->
- gexpr_list([K,V], Vt, St);
-gexpr({map_field_exact,_Line,K,V}, Vt, St) ->
- gexpr_list([K,V], Vt, St);
+ {Svt,St1} = gexpr(Src, Vt, St),
+ {Fvt,St2} = map_fields(Es, Vt, St1, fun gexpr_list/3),
+ {vtmerge(Svt, Fvt),St2};
gexpr({record_index,Line,Name,Field}, _Vt, St) ->
check_record(Line, Name, St,
fun (Dfs, St1) -> record_field(Field, Name, Dfs, St1) end );
@@ -1852,6 +1882,10 @@ gexpr({op,Line,Op,A}, Vt, St0) ->
true -> {Avt,St1};
false -> {Avt,add_error(Line, illegal_guard_expr, St1)}
end;
+gexpr({op,_,'andalso',L,R}, Vt, St) ->
+ gexpr_list([L,R], Vt, St);
+gexpr({op,_,'orelse',L,R}, Vt, St) ->
+ gexpr_list([L,R], Vt, St);
gexpr({op,Line,Op,L,R}, Vt, St0) ->
{Avt,St1} = gexpr_list([L,R], Vt, St0),
case is_gexpr_op(Op, 2) of
@@ -1938,12 +1972,14 @@ is_gexpr({call,L,{tuple,Lt,[{atom,Lm,erlang},{atom,Lf,F}]},As}, RDs) ->
is_gexpr({call,L,{remote,Lt,{atom,Lm,erlang},{atom,Lf,F}},As}, RDs);
is_gexpr({op,_L,Op,A}, RDs) ->
is_gexpr_op(Op, 1) andalso is_gexpr(A, RDs);
+is_gexpr({op,_L,'andalso',A1,A2}, RDs) ->
+ is_gexpr_list([A1,A2], RDs);
+is_gexpr({op,_L,'orelse',A1,A2}, RDs) ->
+ is_gexpr_list([A1,A2], RDs);
is_gexpr({op,_L,Op,A1,A2}, RDs) ->
is_gexpr_op(Op, 2) andalso is_gexpr_list([A1,A2], RDs);
is_gexpr(_Other, _RDs) -> false.
-is_gexpr_op('andalso', 2) -> true;
-is_gexpr_op('orelse', 2) -> true;
is_gexpr_op(Op, A) ->
try erl_internal:op_type(Op, A) of
arith -> true;
@@ -1997,24 +2033,12 @@ expr({bc,_Line,E,Qs}, Vt, St) ->
handle_comprehension(E, Qs, Vt, St);
expr({tuple,_Line,Es}, Vt, St) ->
expr_list(Es, Vt, St);
-expr({map,Line,Es}, Vt, St) ->
- {Rvt,St1} = expr_list(Es,Vt,St),
- case is_valid_map_construction(Es) of
- true -> {Rvt,St1};
- false -> {[],add_error(Line,illegal_map_construction,St1)}
- end;
+expr({map,_Line,Es}, Vt, St) ->
+ map_fields(Es, Vt, check_assoc_fields(Es, St), fun expr_list/3);
expr({map,_Line,Src,Es}, Vt, St) ->
- expr_list([Src|Es], Vt, St);
-expr({map_field_assoc,Line,K,V}, Vt, St) ->
- case is_valid_map_key(K,St) of
- true -> expr_list([K,V], Vt, St);
- {false,Var} -> {[],add_error(Line,{illegal_map_key_variable,Var},St)}
- end;
-expr({map_field_exact,Line,K,V}, Vt, St) ->
- case is_valid_map_key(K,St) of
- true -> expr_list([K,V], Vt, St);
- {false,Var} -> {[],add_error(Line,{illegal_map_key_variable,Var},St)}
- end;
+ {Svt,St1} = expr(Src, Vt, St),
+ {Fvt,St2} = map_fields(Es, Vt, St1, fun expr_list/3),
+ {vtupdate(Svt, Fvt),St2};
expr({record_index,Line,Name,Field}, _Vt, St) ->
check_record(Line, Name, St,
fun (Dfs, St1) -> record_field(Field, Name, Dfs, St1) end);
@@ -2222,6 +2246,26 @@ record_expr(Line, Rec, Vt, St0) ->
St1 = warn_invalid_record(Line, Rec, St0),
expr(Rec, Vt, St1).
+check_assoc_fields([{map_field_exact,Line,_,_}|Fs], St) ->
+ check_assoc_fields(Fs, add_error(Line, illegal_map_construction, St));
+check_assoc_fields([{map_field_assoc,_,_,_}|Fs], St) ->
+ check_assoc_fields(Fs, St);
+check_assoc_fields([], St) ->
+ St.
+
+map_fields([{Tag,Line,K,V}|Fs], Vt, St, F) when Tag =:= map_field_assoc;
+ Tag =:= map_field_exact ->
+ St1 = case is_valid_map_key(K, St) of
+ true -> St;
+ false -> add_error(Line, illegal_map_key, St);
+ {false,variable,Var} -> add_error(Line, {illegal_map_key_variable,Var}, St)
+ end,
+ {Pvt,St2} = F([K,V], Vt, St1),
+ {Vts,St3} = map_fields(Fs, Vt, St2, F),
+ {vtupdate(Pvt, Vts),St3};
+map_fields([], Vt, St, _) ->
+ {Vt,St}.
+
%% warn_invalid_record(Line, Record, State0) -> State
%% Adds warning if the record is invalid.
@@ -2274,18 +2318,64 @@ is_valid_call(Call) ->
_ -> true
end.
-%% check_map_construction
-%% Only #{ K => V }, i.e. assoc is a valid construction
-is_valid_map_construction([{map_field_assoc,_,_,_}|Es]) ->
- is_valid_map_construction(Es);
-is_valid_map_construction([]) -> true;
-is_valid_map_construction(_) -> false.
+%% is_valid_map_key(K,St) -> true | false | {false, Var::atom()}
+%% check for value expression without variables
is_valid_map_key(K,St) ->
case expr(K,[],St) of
- {[],_} -> true;
+ {[],_} ->
+ is_valid_map_key_value(K);
{[Var|_],_} ->
- {false,element(1,Var)}
+ {false,variable,element(1,Var)}
+ end.
+
+is_valid_map_key_value(K) ->
+ case K of
+ {char,_,_} -> true;
+ {integer,_,_} -> true;
+ {float,_,_} -> true;
+ {string,_,_} -> true;
+ {nil,_} -> true;
+ {atom,_,_} -> true;
+ {cons,_,H,T} ->
+ is_valid_map_key_value(H) andalso
+ is_valid_map_key_value(T);
+ {tuple,_,Es} ->
+ foldl(fun(E,B) ->
+ B andalso is_valid_map_key_value(E)
+ end,true,Es);
+ {map,_,Arg,Ps} ->
+ % only check for value expressions to be valid
+ % invalid map expressions are later checked in
+ % core and kernel
+ is_valid_map_key_value(Arg) andalso foldl(fun
+ ({Tag,_,Ke,Ve},B) when Tag =:= map_field_assoc;
+ Tag =:= map_field_exact ->
+ B andalso is_valid_map_key_value(Ke)
+ andalso is_valid_map_key_value(Ve)
+ end,true,Ps);
+ {map,_,Ps} ->
+ foldl(fun
+ ({Tag,_,Ke,Ve},B) when Tag =:= map_field_assoc;
+ Tag =:= map_field_exact ->
+ B andalso is_valid_map_key_value(Ke)
+ andalso is_valid_map_key_value(Ve)
+ end, true, Ps);
+ {record,_,_,Fs} ->
+ foldl(fun
+ ({record_field,_,Ke,Ve},B) ->
+ B andalso is_valid_map_key_value(Ke)
+ andalso is_valid_map_key_value(Ve)
+ end,true,Fs);
+ {bin,_,Es} ->
+ % only check for value expressions to be valid
+ % invalid binary expressions are later checked in
+ % core and kernel
+ foldl(fun
+ ({bin_element,_,E,_,_},B) ->
+ B andalso is_valid_map_key_value(E)
+ end,true,Es);
+ _ -> false
end.
%% record_def(Line, RecordName, [RecField], State) -> State.
@@ -2500,8 +2590,6 @@ find_field(_F, []) -> error.
%% Attr :: 'type' | 'opaque'
%% Checks that a type definition is valid.
--record(typeinfo, {attr, line}).
-
type_def(_Attr, _Line, {record, _RecName}, Fields, [], St0) ->
%% The record field names and such are checked in the record format.
%% We only need to check the types.
@@ -2518,32 +2606,46 @@ type_def(Attr, Line, TypeName, ProtoType, Args, St0) ->
CheckType = {type, -1, product, [ProtoType|Args]},
check_type(CheckType, St#lint{types=NewDefs})
end,
- case (dict:is_key(TypePair, TypeDefs) orelse is_var_arity_type(TypeName)) of
- true ->
- case is_default_type(TypePair) of
- true ->
- case is_newly_introduced_builtin_type(TypePair) of
- %% allow some types just for bootstrapping
- true ->
- Warn = {new_builtin_type, TypePair},
- St1 = add_warning(Line, Warn, St0),
- StoreType(St1);
- false ->
- add_error(Line, {builtin_type, TypePair}, St0)
- end;
- false -> add_error(Line, {redefine_type, TypePair}, St0)
- end;
- false ->
- St1 = case
- Attr =:= opaque andalso
- is_underspecified(ProtoType, Arity)
- of
- true ->
- Warn = {underspecified_opaque, TypePair},
- add_warning(Line, Warn, St0);
- false -> St0
- end,
- StoreType(St1)
+ case is_default_type(TypePair) of
+ true ->
+ case is_obsolete_builtin_type(TypePair) of
+ true -> StoreType(St0);
+ false -> add_error(Line, {builtin_type, TypePair}, St0)
+%% case is_newly_introduced_builtin_type(TypePair) of
+%% %% allow some types just for bootstrapping
+%% true ->
+%% Warn = {new_builtin_type, TypePair},
+%% St1 = add_warning(Line, Warn, St0),
+%% StoreType(St1);
+%% false ->
+%% add_error(Line, {builtin_type, TypePair}, St0)
+%% end
+ end;
+ false ->
+ case
+ dict:is_key(TypePair, TypeDefs) orelse
+ is_var_arity_type(TypeName)
+ of
+ true ->
+ case is_newly_introduced_var_arity_type(TypeName) of
+ true ->
+ Warn = {new_var_arity_type, TypeName},
+ add_warning(Line, Warn, St0);
+ false ->
+ add_error(Line, {redefine_type, TypePair}, St0)
+ end;
+ false ->
+ St1 = case
+ Attr =:= opaque andalso
+ is_underspecified(ProtoType, Arity)
+ of
+ true ->
+ Warn = {underspecified_opaque, TypePair},
+ add_warning(Line, Warn, St0);
+ false -> St0
+ end,
+ StoreType(St1)
+ end
end.
is_underspecified({type,_,term,[]}, 0) -> true;
@@ -2637,10 +2739,11 @@ check_type({type, La, TypeName, Args}, SeenVars, St) ->
St1 = case is_var_arity_type(TypeName) of
true -> St;
false ->
- Obsolete = obsolete_type(TypePair),
+ Obsolete = (is_warn_enabled(deprecated_type, St)
+ andalso obsolete_builtin_type(TypePair)),
IsObsolete =
case Obsolete of
- {deprecated, {M, _}, _} when M =/= Module ->
+ {deprecated, Repl, _} when element(1, Repl) =/= Module ->
case dict:find(TypePair, Types) of
{ok, _} -> false;
error -> true
@@ -2650,7 +2753,8 @@ check_type({type, La, TypeName, Args}, SeenVars, St) ->
case IsObsolete of
true ->
{deprecated, Replacement, Rel} = Obsolete,
- W = {deprecated_type, TypePair, Replacement, Rel},
+ Tag = deprecated_builtin_type,
+ W = {Tag, TypePair, Replacement, Rel},
add_warning(La, W, St);
false ->
OldUsed = Usage#usage.used_types,
@@ -2701,6 +2805,7 @@ check_record_types([], _Name, _DefFields, SeenVars, St, _SeenFields) ->
{SeenVars, St}.
is_var_arity_type(tuple) -> true;
+is_var_arity_type(map) -> true;
is_var_arity_type(product) -> true;
is_var_arity_type(union) -> true;
is_var_arity_type(record) -> true;
@@ -2733,7 +2838,6 @@ is_default_type({iodata, 0}) -> true;
is_default_type({iolist, 0}) -> true;
is_default_type({list, 0}) -> true;
is_default_type({list, 1}) -> true;
-is_default_type({map, 0}) -> true;
is_default_type({maybe_improper_list, 0}) -> true;
is_default_type({maybe_improper_list, 2}) -> true;
is_default_type({mfa, 0}) -> true;
@@ -2764,31 +2868,32 @@ is_default_type({timeout, 0}) -> true;
is_default_type({var, 1}) -> true;
is_default_type(_) -> false.
-%% R13
-is_newly_introduced_builtin_type({arity, 0}) -> true;
-is_newly_introduced_builtin_type({array, 0}) -> true; % opaque
-is_newly_introduced_builtin_type({bitstring, 0}) -> true;
-is_newly_introduced_builtin_type({dict, 0}) -> true; % opaque
-is_newly_introduced_builtin_type({digraph, 0}) -> true; % opaque
-is_newly_introduced_builtin_type({gb_set, 0}) -> true; % opaque
-is_newly_introduced_builtin_type({gb_tree, 0}) -> true; % opaque
-is_newly_introduced_builtin_type({iodata, 0}) -> true;
-is_newly_introduced_builtin_type({queue, 0}) -> true; % opaque
-is_newly_introduced_builtin_type({set, 0}) -> true; % opaque
-%% R13B01
-is_newly_introduced_builtin_type({boolean, 0}) -> true;
-is_newly_introduced_builtin_type({Name, _}) when is_atom(Name) -> false.
+is_newly_introduced_var_arity_type(map) -> true;
+is_newly_introduced_var_arity_type(_) -> false.
+
+%% is_newly_introduced_builtin_type({Name, _}) when is_atom(Name) -> false.
+
+is_obsolete_builtin_type(TypePair) ->
+ obsolete_builtin_type(TypePair) =/= no.
%% Obsolete in OTP 17.0.
-obsolete_type({array, 0}) -> {deprecated, {array, array}, "OTP 18.0"};
-obsolete_type({dict, 0}) -> {deprecated, {dict, dict}, "OTP 18.0"};
-obsolete_type({digraph, 0}) -> {deprecated, {digraph, graph}, "OTP 18.0"};
-obsolete_type({gb_set, 0}) -> {deprecated, {gb_sets, set}, "OTP 18.0"};
-obsolete_type({gb_tree, 0}) -> {deprecated, {gb_trees, tree}, "OTP 18.0"};
-obsolete_type({queue, 0}) -> {deprecated, {queue, queue}, "OTP 18.0"};
-obsolete_type({set, 0}) -> {deprecated, {sets, set}, "OTP 18.0"};
-obsolete_type({tid, 0}) -> {deprecated, {ets, tid}, "OTP 18.0"};
-obsolete_type({Name, _}) when is_atom(Name) -> no.
+obsolete_builtin_type({array, 0}) ->
+ {deprecated, {array, array, 1}, "OTP 18.0"};
+obsolete_builtin_type({dict, 0}) ->
+ {deprecated, {dict, dict, 2}, "OTP 18.0"};
+obsolete_builtin_type({digraph, 0}) ->
+ {deprecated, {digraph, graph}, "OTP 18.0"};
+obsolete_builtin_type({gb_set, 0}) ->
+ {deprecated, {gb_sets, set, 1}, "OTP 18.0"};
+obsolete_builtin_type({gb_tree, 0}) ->
+ {deprecated, {gb_trees, tree, 2}, "OTP 18.0"};
+obsolete_builtin_type({queue, 0}) ->
+ {deprecated, {queue, queue, 1}, "OTP 18.0"};
+obsolete_builtin_type({set, 0}) ->
+ {deprecated, {sets, set, 1}, "OTP 18.0"};
+obsolete_builtin_type({tid, 0}) ->
+ {deprecated, {ets, tid}, "OTP 18.0"};
+obsolete_builtin_type({Name, A}) when is_atom(Name), is_integer(A) -> no.
%% spec_decl(Line, Fun, Types, State) -> State.