aboutsummaryrefslogtreecommitdiffstats
path: root/lib
diff options
context:
space:
mode:
authorHans Bolinder <[email protected]>2014-04-09 09:28:46 +0200
committerHans Bolinder <[email protected]>2014-04-29 09:16:53 +0200
commit7ad783d431738c42fa9ce395fbc776916d927eb6 (patch)
tree065069662aa6a42d69596db105af0cc760b74cea /lib
parent847e7291b2800ebd7e188be6e88114fb1e8900ce (diff)
downloadotp-7ad783d431738c42fa9ce395fbc776916d927eb6.tar.gz
otp-7ad783d431738c42fa9ce395fbc776916d927eb6.tar.bz2
otp-7ad783d431738c42fa9ce395fbc776916d927eb6.zip
Allow more type names
product/_, union/_, range/2 as well as tuple/N (N > 0), map/N (N > 0), atom/1, integer/1, binary/2, record/_, and 'fun'/_ can now be used as type names.
Diffstat (limited to 'lib')
-rw-r--r--lib/edoc/src/edoc_specs.erl3
-rw-r--r--lib/hipe/cerl/erl_types.erl10
-rw-r--r--lib/stdlib/src/erl_internal.erl62
-rw-r--r--lib/stdlib/src/erl_lint.erl182
-rw-r--r--lib/stdlib/src/erl_parse.yrl16
-rw-r--r--lib/stdlib/src/erl_pp.erl3
-rw-r--r--lib/stdlib/test/erl_lint_SUITE.erl57
-rw-r--r--lib/stdlib/test/erl_pp_SUITE.erl1
8 files changed, 198 insertions, 136 deletions
diff --git a/lib/edoc/src/edoc_specs.erl b/lib/edoc/src/edoc_specs.erl
index 211a354c74..3c7e8bebfc 100644
--- a/lib/edoc/src/edoc_specs.erl
+++ b/lib/edoc/src/edoc_specs.erl
@@ -388,6 +388,9 @@ d2e({record_field,L,_Name}=F) ->
d2e({type,_,Name,Types0}) ->
Types = d2e(Types0),
typevar_anno(#t_type{name = #t_name{name = Name}, args = Types}, Types);
+d2e({user_type,_,Name,Types0}) ->
+ Types = d2e(Types0),
+ typevar_anno(#t_type{name = #t_name{name = Name}, args = Types}, Types);
d2e({var,_,'_'}) ->
#t_type{name = #t_name{name = ?TOP_TYPE}};
d2e({var,_,TypeName}) ->
diff --git a/lib/hipe/cerl/erl_types.erl b/lib/hipe/cerl/erl_types.erl
index 6065b79664..473a9eba4a 100644
--- a/lib/hipe/cerl/erl_types.erl
+++ b/lib/hipe/cerl/erl_types.erl
@@ -4350,7 +4350,10 @@ t_from_form({type, _L, tuple, Args}, TypeNames, RecDict, VarDict) ->
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({user_type, _L, Name, Args}, TypeNames, RecDict, VarDict) ->
+ type_from_form(Name, Args, TypeNames, RecDict, VarDict);
t_from_form({type, _L, Name, Args}, TypeNames, RecDict, VarDict) ->
+ %% Compatibility. Modules compiled before 18.0.
type_from_form(Name, Args, TypeNames, RecDict, VarDict);
t_from_form({opaque, _L, Name, {Mod, Args, Rep}}, _TypeNames,
_RecDict, _VarDict) ->
@@ -4588,9 +4591,12 @@ t_form_to_string({type, _L, Name, []} = T) ->
try t_to_string(t_from_form(T))
catch throw:{error, _} -> atom_to_string(Name) ++ "()"
end;
-t_form_to_string({type, _L, Name, List}) ->
+t_form_to_string({user_type, _L, Name, List}) ->
flat_format("~w(~s)",
- [Name, string:join(t_form_to_string_list(List), ",")]).
+ [Name, string:join(t_form_to_string_list(List), ",")]);
+t_form_to_string({type, L, Name, List}) ->
+ %% Compatibility. Modules compiled before 18.0.
+ t_form_to_string({user_type, L, Name, List}).
t_form_to_string_list(List) ->
t_form_to_string_list(List, []).
diff --git a/lib/stdlib/src/erl_internal.erl b/lib/stdlib/src/erl_internal.erl
index edfb097de0..5e6391da1f 100644
--- a/lib/stdlib/src/erl_internal.erl
+++ b/lib/stdlib/src/erl_internal.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1998-2013. All Rights Reserved.
+%% Copyright Ericsson AB 1998-2014. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -51,6 +51,8 @@
type_test/2,new_type_test/2,old_type_test/2,old_bif/2]).
-export([arith_op/2,bool_op/2,comp_op/2,list_op/2,send_op/2,op_type/2]).
+-export([is_type/2]).
+
%%---------------------------------------------------------------------------
%% Erlang builtin functions allowed in guards.
@@ -530,3 +532,61 @@ old_bif(unlink, 1) -> true;
old_bif(unregister, 1) -> true;
old_bif(whereis, 1) -> true;
old_bif(Name, A) when is_atom(Name), is_integer(A) -> false.
+
+-spec is_type(Name, NumberOfTypeVariables) -> boolean() when
+ Name :: atom(),
+ NumberOfTypeVariables :: non_neg_integer().
+%% Returns true if Name/NumberOfTypeVariables is a predefined type.
+
+is_type(any, 0) -> true;
+is_type(arity, 0) -> true;
+is_type(array, 0) -> true; % To be removed.
+is_type(atom, 0) -> true;
+is_type(binary, 0) -> true;
+is_type(bitstring, 0) -> true;
+is_type(bool, 0) -> true;
+is_type(boolean, 0) -> true;
+is_type(byte, 0) -> true;
+is_type(char, 0) -> true;
+is_type(dict, 0) -> true; % To be removed.
+is_type(digraph, 0) -> true; % To be removed.
+is_type(float, 0) -> true;
+is_type(function, 0) -> true;
+is_type(gb_set, 0) -> true; % To be removed.
+is_type(gb_tree, 0) -> true; % To be removed.
+is_type(identifier, 0) -> true;
+is_type(integer, 0) -> true;
+is_type(iodata, 0) -> true;
+is_type(iolist, 0) -> true;
+is_type(list, 0) -> true;
+is_type(list, 1) -> true;
+is_type(map, 0) -> true;
+is_type(maybe_improper_list, 0) -> true;
+is_type(maybe_improper_list, 2) -> true;
+is_type(mfa, 0) -> true;
+is_type(module, 0) -> true;
+is_type(neg_integer, 0) -> true;
+is_type(nil, 0) -> true;
+is_type(no_return, 0) -> true;
+is_type(node, 0) -> true;
+is_type(non_neg_integer, 0) -> true;
+is_type(none, 0) -> true;
+is_type(nonempty_improper_list, 2) -> true;
+is_type(nonempty_list, 0) -> true;
+is_type(nonempty_list, 1) -> true;
+is_type(nonempty_maybe_improper_list, 0) -> true;
+is_type(nonempty_maybe_improper_list, 2) -> true;
+is_type(nonempty_string, 0) -> true;
+is_type(number, 0) -> true;
+is_type(pid, 0) -> true;
+is_type(port, 0) -> true;
+is_type(pos_integer, 0) -> true;
+is_type(queue, 0) -> true; % To be removed.
+is_type(reference, 0) -> true;
+is_type(set, 0) -> true; % To be removed.
+is_type(string, 0) -> true;
+is_type(term, 0) -> true;
+is_type(tid, 0) -> true; % To be removed.
+is_type(timeout, 0) -> true;
+is_type(tuple, 0) -> true;
+is_type(_, _) -> false.
diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl
index 5deddf6bd1..3d33c3447b 100644
--- a/lib/stdlib/src/erl_lint.erl
+++ b/lib/stdlib/src/erl_lint.erl
@@ -340,14 +340,10 @@ 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; "
-%% "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; "
+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]);
+ [TypeName, gen_type_paren(Arity)]);
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)]);
@@ -1073,10 +1069,9 @@ check_undefined_types(#lint{usage=Usage,types=Def}=St0) ->
Used = Usage#usage.used_types,
UTAs = dict:fetch_keys(Used),
Undef = [{TA,dict:fetch(TA, Used)} ||
- {T,_}=TA <- UTAs,
+ TA <- UTAs,
not dict:is_key(TA, Def),
- not is_default_type(TA),
- not is_newly_introduced_var_arity_type(T)],
+ not is_default_type(TA)],
foldl(fun ({TA,L}, St) ->
add_error(L, {undefined_type,TA}, St)
end, St0, Undef).
@@ -2652,30 +2647,21 @@ type_def(Attr, Line, TypeName, ProtoType, Args, St0) ->
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
+ false ->
+ 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
+ case dict:is_key(TypePair, TypeDefs) 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;
+ add_error(Line, {redefine_type, TypePair}, St0);
false ->
St1 = case
Attr =:= opaque andalso
@@ -2712,7 +2698,7 @@ check_type({paren_type, _L, [Type]}, SeenVars, St) ->
check_type({remote_type, L, [{atom, _, Mod}, {atom, _, Name}, Args]},
SeenVars, #lint{module=CurrentMod} = St) ->
case Mod =:= CurrentMod of
- true -> check_type({type, L, Name, Args}, SeenVars, St);
+ true -> check_type({user_type, L, Name, Args}, SeenVars, St);
false ->
lists:foldl(fun(T, {AccSeenVars, AccSt}) ->
check_type(T, AccSeenVars, AccSt)
@@ -2746,7 +2732,10 @@ check_type({type, L, range, [From, To]}, SeenVars, St) ->
_ -> add_error(L, {type_syntax, range}, St)
end,
{SeenVars, St1};
-check_type({type, _L, map, any}, SeenVars, St) -> {SeenVars, St};
+check_type({type, L, map, any}, SeenVars, St) ->
+ %% To get usage right while map/0 is a newly_introduced_builtin_type.
+ St1 = used_type({map, 0}, L, St),
+ {SeenVars, St1};
check_type({type, _L, map, Pairs}, SeenVars, St) ->
lists:foldl(fun(Pair, {AccSeenVars, AccSt}) ->
check_type(Pair, AccSeenVars, AccSt)
@@ -2770,41 +2759,39 @@ check_type({type, L, record, [Name|Fields]}, SeenVars, St) ->
check_record_types(L, Atom, Fields, SeenVars, St1);
_ -> {SeenVars, add_error(L, {type_syntax, record}, St)}
end;
-check_type({type, _L, product, Args}, SeenVars, St) ->
+check_type({type, _L, Tag, Args}, SeenVars, St) when Tag =:= product;
+ Tag =:= union;
+ Tag =:= tuple ->
lists:foldl(fun(T, {AccSeenVars, AccSt}) ->
check_type(T, AccSeenVars, AccSt)
end, {SeenVars, St}, Args);
check_type({type, La, TypeName, Args}, SeenVars, St) ->
- #lint{usage=Usage, module = Module, types=Types} = St,
+ #lint{module = Module, types=Types} = St,
Arity = length(Args),
TypePair = {TypeName, Arity},
- St1 = case is_var_arity_type(TypeName) of
- true -> St;
- false ->
- Obsolete = (is_warn_enabled(deprecated_type, St)
- andalso obsolete_builtin_type(TypePair)),
- IsObsolete =
- case Obsolete of
- {deprecated, Repl, _} when element(1, Repl) =/= Module ->
- case dict:find(TypePair, Types) of
- {ok, _} -> false;
- error -> true
- end;
- _ -> false
- end,
- case IsObsolete of
- true ->
+ Obsolete = (is_warn_enabled(deprecated_type, St)
+ andalso obsolete_builtin_type(TypePair)),
+ St1 = case Obsolete of
+ {deprecated, Repl, _} when element(1, Repl) =/= Module ->
+ case dict:find(TypePair, Types) of
+ {ok, _} ->
+ used_type(TypePair, La, St);
+ error ->
{deprecated, Replacement, Rel} = Obsolete,
Tag = deprecated_builtin_type,
W = {Tag, TypePair, Replacement, Rel},
- add_warning(La, W, St);
- false ->
- OldUsed = Usage#usage.used_types,
- UsedTypes = dict:store(TypePair, La, OldUsed),
- St#lint{usage=Usage#usage{used_types=UsedTypes}}
- end
- end,
+ add_warning(La, W, St)
+ end;
+ _ -> St
+ end,
check_type({type, -1, product, Args}, SeenVars, St1);
+check_type({user_type, L, TypeName, Args}, SeenVars, St) ->
+ Arity = length(Args),
+ TypePair = {TypeName, Arity},
+ St1 = used_type(TypePair, L, St),
+ lists:foldl(fun(T, {AccSeenVars, AccSt}) ->
+ check_type(T, AccSeenVars, AccSt)
+ end, {SeenVars, St1}, Args);
check_type(I, SeenVars, St) ->
case erl_eval:partial_eval(I) of
{integer,_ILn,_Integer} -> {SeenVars, St};
@@ -2846,74 +2833,17 @@ check_record_types([{type, _, field_type, [{atom, AL, FName}, Type]}|Left],
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;
-is_var_arity_type(_) -> false.
-
-is_default_type({any, 0}) -> true;
-is_default_type({arity, 0}) -> true;
-is_default_type({array, 0}) -> true;
-is_default_type({atom, 0}) -> true;
-is_default_type({atom, 1}) -> true;
-is_default_type({binary, 0}) -> true;
-is_default_type({binary, 2}) -> true;
-is_default_type({bitstring, 0}) -> true;
-is_default_type({bool, 0}) -> true;
-is_default_type({boolean, 0}) -> true;
-is_default_type({byte, 0}) -> true;
-is_default_type({char, 0}) -> true;
-is_default_type({dict, 0}) -> true;
-is_default_type({digraph, 0}) -> true;
-is_default_type({float, 0}) -> true;
-is_default_type({'fun', 0}) -> true;
-is_default_type({'fun', 2}) -> true;
-is_default_type({function, 0}) -> true;
-is_default_type({gb_set, 0}) -> true;
-is_default_type({gb_tree, 0}) -> true;
-is_default_type({identifier, 0}) -> true;
-is_default_type({integer, 0}) -> true;
-is_default_type({integer, 1}) -> true;
-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({maybe_improper_list, 0}) -> true;
-is_default_type({maybe_improper_list, 2}) -> true;
-is_default_type({mfa, 0}) -> true;
-is_default_type({module, 0}) -> true;
-is_default_type({neg_integer, 0}) -> true;
-is_default_type({nil, 0}) -> true;
-is_default_type({no_return, 0}) -> true;
-is_default_type({node, 0}) -> true;
-is_default_type({non_neg_integer, 0}) -> true;
-is_default_type({none, 0}) -> true;
-is_default_type({nonempty_list, 0}) -> true;
-is_default_type({nonempty_list, 1}) -> true;
-is_default_type({nonempty_improper_list, 2}) -> true;
-is_default_type({nonempty_maybe_improper_list, 0}) -> true;
-is_default_type({nonempty_maybe_improper_list, 2}) -> true;
-is_default_type({nonempty_string, 0}) -> true;
-is_default_type({number, 0}) -> true;
-is_default_type({pid, 0}) -> true;
-is_default_type({port, 0}) -> true;
-is_default_type({pos_integer, 0}) -> true;
-is_default_type({queue, 0}) -> true;
-is_default_type({range, 2}) -> true;
-is_default_type({reference, 0}) -> true;
-is_default_type({set, 0}) -> true;
-is_default_type({string, 0}) -> true;
-is_default_type({term, 0}) -> true;
-is_default_type({timeout, 0}) -> true;
-is_default_type({var, 1}) -> true;
-is_default_type(_) -> 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.
+used_type(TypePair, L, St) ->
+ Usage = St#lint.usage,
+ OldUsed = Usage#usage.used_types,
+ UsedTypes = dict:store(TypePair, L, OldUsed),
+ St#lint{usage=Usage#usage{used_types=UsedTypes}}.
+
+is_default_type({Name, NumberOfTypeVariables}) ->
+ erl_internal:is_type(Name, NumberOfTypeVariables).
+
+is_newly_introduced_builtin_type({map, 0}) -> true;
+is_newly_introduced_builtin_type({Name, _}) when is_atom(Name) -> false.
is_obsolete_builtin_type(TypePair) ->
obsolete_builtin_type(TypePair) =/= no.
diff --git a/lib/stdlib/src/erl_parse.yrl b/lib/stdlib/src/erl_parse.yrl
index 1dc5fc52a7..3bb7a90c4f 100644
--- a/lib/stdlib/src/erl_parse.yrl
+++ b/lib/stdlib/src/erl_parse.yrl
@@ -146,8 +146,7 @@ type -> '(' top_type ')' : {paren_type, ?line('$2'), ['$2']}.
type -> var : '$1'.
type -> atom : '$1'.
type -> atom '(' ')' : build_gen_type('$1').
-type -> atom '(' top_types ')' : {type, ?line('$1'),
- normalise('$1'), '$3'}.
+type -> atom '(' top_types ')' : build_type('$1', '$3').
type -> atom ':' atom '(' ')' : {remote_type, ?line('$1'),
['$1', '$3', []]}.
type -> atom ':' atom '(' top_types ')' : {remote_type, ?line('$1'),
@@ -684,7 +683,8 @@ build_gen_type({atom, La, tuple}) ->
build_gen_type({atom, La, map}) ->
{type, La, map, any};
build_gen_type({atom, La, Name}) ->
- {type, La, Name, []}.
+ Tag = type_tag(Name, 0),
+ {Tag, La, Name, []}.
build_bin_type([{var, _, '_'}|Left], Int) ->
build_bin_type(Left, Int);
@@ -693,6 +693,16 @@ build_bin_type([], Int) ->
build_bin_type([{var, La, _}|_], _) ->
ret_err(La, "Bad binary type").
+build_type({atom, L, Name}, Types) ->
+ Tag = type_tag(Name, length(Types)),
+ {Tag, L, Name, Types}.
+
+type_tag(TypeName, NumberOfTypeVariables) ->
+ case erl_internal:is_type(TypeName, NumberOfTypeVariables) of
+ true -> type;
+ false -> user_type
+ end.
+
%% build_attribute(AttrName, AttrValue) ->
%% {attribute,Line,module,Module}
%% {attribute,Line,export,Exports}
diff --git a/lib/stdlib/src/erl_pp.erl b/lib/stdlib/src/erl_pp.erl
index 788dbb40b6..8337ecc4dd 100644
--- a/lib/stdlib/src/erl_pp.erl
+++ b/lib/stdlib/src/erl_pp.erl
@@ -285,6 +285,9 @@ ltype({type,_,'fun',[{type,_,any},_]}=FunType) ->
ltype({type,_Line,'fun',[{type,_,product,_},_]}=FunType) ->
[fun_type(['fun',$(], FunType),$)];
ltype({type,Line,T,Ts}) ->
+ %% Compatibility. Before 18.0.
+ simple_type({atom,Line,T}, Ts);
+ltype({user_type,Line,T,Ts}) ->
simple_type({atom,Line,T}, Ts);
ltype({remote_type,Line,[M,F,Ts]}) ->
simple_type({remote,Line,M,F}, Ts);
diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl
index 5506d3d166..580ff79584 100644
--- a/lib/stdlib/test/erl_lint_SUITE.erl
+++ b/lib/stdlib/test/erl_lint_SUITE.erl
@@ -63,7 +63,7 @@
too_many_arguments/1,
basic_errors/1,bin_syntax_errors/1,
predef/1,
- maps/1,maps_type/1
+ maps/1,maps_type/1,otp_11851/1
]).
% Default timetrap timeout (set in init_per_testcase).
@@ -92,7 +92,7 @@ all() ->
bif_clash, behaviour_basic, behaviour_multiple, otp_11861,
otp_7550, otp_8051, format_warn, {group, on_load},
too_many_arguments, basic_errors, bin_syntax_errors, predef,
- maps, maps_type].
+ maps, maps_type, otp_11851].
groups() ->
[{unused_vars_warn, [],
@@ -2649,7 +2649,9 @@ otp_11872(Config) when is_list(Config) ->
1.
">>,
{error,[{6,erl_lint,{undefined_type,{product,0}}}],
- [{8,erl_lint,{new_var_arity_type,map}}]} =
+ [{8,erl_lint,{new_builtin_type,{map,0}}},
+ {8,erl_lint,
+ {deprecated_builtin_type,{dict,0},{dict,dict,2}, "OTP 18.0"}}]} =
run_test2(Config, Ts, []),
ok.
@@ -3657,7 +3659,54 @@ maps_type(Config) when is_list(Config) ->
t(M) -> M.
">>,
[],
- {warnings,[{3,erl_lint,{new_var_arity_type,map}}]}}],
+ {warnings,[{3,erl_lint,{new_builtin_type,{map,0}}}]}}],
+ [] = run(Config, Ts),
+ ok.
+
+otp_11851(doc) ->
+ "OTP-11851: More atoms can be used as type names.";
+otp_11851(Config) when is_list(Config) ->
+ Ts = [
+ {otp_11851,
+ <<"
+ -type range(A, B) :: A | B.
+
+ -type union(A) :: A.
+
+ -type product() :: integer().
+
+ -type tuple(A) :: A.
+
+ -type map(A) :: A.
+
+ -type record() :: a | b.
+
+ -type integer(A) :: A.
+
+ -type atom(A) :: A.
+
+ -type binary(A, B) :: A | B.
+
+ -type 'fun'() :: integer().
+
+ -type 'fun'(X) :: X.
+
+ -type 'fun'(X, Y) :: X | Y.
+
+ -type all() :: range(atom(), integer()) | union(pid()) | product()
+ | tuple(reference()) | map(function()) | record()
+ | integer(atom()) | atom(integer())
+ | binary(pid(), tuple()) | 'fun'(port())
+ | 'fun'() | 'fun'(<<>>, 'none').
+
+ -spec t() -> all().
+
+ t() ->
+ a.
+ ">>,
+ [],
+ []}
+ ],
[] = run(Config, Ts),
ok.
diff --git a/lib/stdlib/test/erl_pp_SUITE.erl b/lib/stdlib/test/erl_pp_SUITE.erl
index d0892c6d79..12817943d0 100644
--- a/lib/stdlib/test/erl_pp_SUITE.erl
+++ b/lib/stdlib/test/erl_pp_SUITE.erl
@@ -874,6 +874,7 @@ type_examples() ->
{ex3,<<"-type paren() :: (ann2()). ">>},
{ex4,<<"-type t1() :: atom(). ">>},
{ex5,<<"-type t2() :: [t1()]. ">>},
+ {ex56,<<"-type integer(A) :: A. ">>},
{ex6,<<"-type t3(Atom) :: integer(Atom). ">>},
{ex7,<<"-type '\\'t::4'() :: t3('\\'foobar'). ">>},
{ex8,<<"-type t5() :: {t1(), t3(foo)}. ">>},