Skip to content

Commit bd340fb

Browse files
import_type in edoc
1 parent d1e27c1 commit bd340fb

File tree

4 files changed

+110
-88
lines changed

4 files changed

+110
-88
lines changed

lib/edoc/src/edoc.hrl

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -51,7 +51,8 @@
5151
attributes = [],
5252
records = [],
5353
encoding = latin1,
54-
file}).
54+
file,
55+
imported_types = #{}}).
5556

5657
-record(env, {module = [],
5758
root = "",

lib/edoc/src/edoc_extract.erl

Lines changed: 19 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -132,7 +132,8 @@ source1(Tree, File0, Env, Opts, TypeDocs) ->
132132
Env1 = Env#env{module = Name,
133133
root = ""},
134134
Env2 = add_macro_defs(module_macros(Env1), Opts, Env1),
135-
Entries1 = get_tags([Header, Footer | Entries], Env2, File, TypeDocs),
135+
Imp = Module#module.imported_types,
136+
Entries1 = get_tags([Header, Footer | Entries], Env2, File, TypeDocs, Imp),
136137
Entries2 = edoc_specs:add_type_data(Entries1, Opts, File, Module),
137138
edoc_tags:check_types(Entries2, Opts, File),
138139
Data = edoc_data:module(Module, Entries2, Env2, Opts),
@@ -211,7 +212,8 @@ header(Tree, File0, Env, _Opts) ->
211212
warning(File, "documentation before function definitions is ignored by @headerfile", []);
212213
true -> ok
213214
end,
214-
[Entry] = get_tags([Footer#entry{name = header}], Env, File),
215+
Imp = #{},
216+
[Entry] = get_tags([Footer#entry{name = header}], Env, File, Imp),
215217
Entry#entry.data.
216218

217219
%% NEW-OPTIONS: def
@@ -323,14 +325,16 @@ get_module_info(Forms, File) ->
323325
Attributes = ordsets:from_list(get_list_keyval(attributes, L)),
324326
Records = get_list_keyval(records, L),
325327
Encoding = edoc_lib:read_encoding(File, []),
328+
ImportedTypes = #{T => M || {import_type, {M, Ts}} <- Attributes, T <- Ts},
326329
#module{name = Name,
327330
parameters = Vars,
328331
functions = Functions,
329332
exports = ordsets:intersection(Exports, Functions),
330333
attributes = Attributes,
331334
records = Records,
332335
encoding = Encoding,
333-
file = File}.
336+
file = File,
337+
imported_types = ImportedTypes}.
334338

335339
get_list_keyval(Key, L) ->
336340
case lists:keyfind(Key, 1, L) of
@@ -622,32 +626,32 @@ capitalize(Cs) -> Cs.
622626
% footer :: sets:set(atom()),
623627
% function :: sets:set(atom())}.
624628

625-
get_tags(Es, Env, File) ->
626-
get_tags(Es, Env, File, dict:new()).
629+
get_tags(Es, Env, File, Imp) ->
630+
get_tags(Es, Env, File, dict:new(), Imp).
627631

628-
get_tags(Es, Env, File, TypeDocs) ->
632+
get_tags(Es, Env, File, TypeDocs, Imp) ->
629633
%% Cache this stuff for quick lookups.
630634
Tags = #tags{names = sets:from_list(edoc_tags:tag_names()),
631635
single = sets:from_list(edoc_tags:tags(single)),
632636
module = sets:from_list(edoc_tags:tags(module)),
633637
footer = sets:from_list(edoc_tags:tags(footer)),
634638
function = sets:from_list(edoc_tags:tags(function))},
635639
How = dict:from_list(edoc_tags:tag_parsers()),
636-
get_tags(Es, Tags, Env, How, File, TypeDocs).
640+
get_tags(Es, Tags, Env, How, File, TypeDocs, Imp).
637641

638642
get_tags([#entry{name = Name, data = {Cs,Cbs,Specs,Types,Records}} = E | Es],
639-
Tags, Env, How, File, TypeDocs) ->
643+
Tags, Env, How, File, TypeDocs, Imp) ->
640644
Where = {File, Name},
641645
Ts0 = scan_tags(Cs),
642646
{Ts1,Specs1} = select_spec(Ts0, Where, Specs),
643647
Ts2 = check_tags(Ts1, Tags, Where),
644648
Ts3 = edoc_macros:expand_tags(Ts2, Env, Where),
645649
Ts4 = edoc_tags:parse_tags(Ts3, How, Env, Where),
646-
Ts = selected_specs(Specs1, Ts4),
647-
ETypes = [edoc_specs:type(Type, TypeDocs) || Type <- Types ++ Records],
650+
Ts = selected_specs(Specs1, Ts4, Imp),
651+
ETypes = [edoc_specs:type(Type, TypeDocs, Imp) || Type <- Types ++ Records],
648652
Callbacks = get_callbacks(Name, Cbs, TypeDocs),
649-
[E#entry{data = Ts ++ ETypes ++ Callbacks} | get_tags(Es, Tags, Env, How, File, TypeDocs)];
650-
get_tags([], _, _, _, _, _) ->
653+
[E#entry{data = Ts ++ ETypes ++ Callbacks} | get_tags(Es, Tags, Env, How, File, TypeDocs, Imp)];
654+
get_tags([], _, _, _, _, _, _) ->
651655
[].
652656

653657
get_callbacks(_EntryName, CbForms, TypeDocs) ->
@@ -713,10 +717,10 @@ skip_specs(Ts) ->
713717
[ T || T = #tag{name = N} <- Ts, N /= spec ].
714718

715719
%% If a `-spec' attribute is present, it takes precedence over `@spec' tags.
716-
selected_specs([], Ts) ->
720+
selected_specs([], Ts, _) ->
717721
Ts;
718-
selected_specs([F], Ts) ->
719-
[edoc_specs:spec(F) | skip_specs(Ts)].
722+
selected_specs([F], Ts, Imp) ->
723+
[edoc_specs:spec(F, Imp) | skip_specs(Ts)].
720724

721725
%% Macros for modules
722726

lib/edoc/src/edoc_specs.erl

Lines changed: 75 additions & 70 deletions
Original file line numberDiff line numberDiff line change
@@ -21,27 +21,30 @@
2121

2222
-module(edoc_specs).
2323

24-
-export([type/2, spec/1, dummy_spec/1, docs/2]).
24+
-export([type/3, spec/2, dummy_spec/1, docs/2]).
2525

2626
-export([add_type_data/4, tag/1, is_tag/1]).
2727

2828
-include("edoc.hrl").
2929
-include("edoc_types.hrl").
3030

3131
-type syntaxTree() :: erl_syntax:syntaxTree().
32+
-type imported_types() :: #{{atom(), arity()} => module()}.
3233

3334
-define(TOP_TYPE, term).
3435

3536
%%
3637
%% Exported functions
3738
%%
3839

39-
-spec type(Form::syntaxTree(), TypeDocs::dict:dict()) -> #tag{}.
40+
-spec type(Form::syntaxTree(),
41+
TypeDocs::dict:dict(),
42+
Imp::imported_types()) -> #tag{}.
4043

4144
%% @doc Convert an Erlang type to EDoc representation.
4245
%% TypeDocs is a dict of {Name, Doc}.
4346
%% Note: #t_typedef.name is set to {record, R} for record types.
44-
type(Form, TypeDocs) ->
47+
type(Form, TypeDocs, Imp) ->
4548
{Name, Data0} = analyze_type_attribute(Form),
4649
{TypeName, Type, Args, Doc} =
4750
case Data0 of
@@ -64,19 +67,19 @@ type(Form, TypeDocs) ->
6467
#tag{name = type, line = get_line(element(2, Type)),
6568
origin = code,
6669
data = {#t_typedef{name = TypeName,
67-
args = d2e(Args),
68-
type = d2e(opaque2abstr(Name, Type))},
70+
args = d2e(Args, Imp),
71+
type = d2e(opaque2abstr(Name, Type), Imp)},
6972
Doc},
7073
form = Form}.
7174

72-
-spec spec(Form::syntaxTree()) -> #tag{}.
75+
-spec spec(Form::syntaxTree(), Imp::imported_types()) -> #tag{}.
7376

7477
%% @doc Convert an Erlang spec to EDoc representation.
75-
spec(Form) ->
78+
spec(Form, Imp) ->
7679
{Name, _Arity, TypeSpecs} = get_spec(Form),
7780
#tag{name = spec, line = get_line(element(2, lists:nth(1, TypeSpecs))),
7881
origin = code,
79-
data = [aspec(d2e(TypeSpec), Name) || TypeSpec <- TypeSpecs],
82+
data = [aspec(d2e(TypeSpec, Imp), Name) || TypeSpec <- TypeSpecs],
8083
form = Form}.
8184

8285
-spec dummy_spec(Form::syntaxTree()) -> #tag{}.
@@ -329,133 +332,135 @@ arg_name([A | As], Default) ->
329332
is_name(A) ->
330333
is_atom(A).
331334

332-
d2e(T) ->
333-
d2e(T, 0).
335+
d2e(T, Imp) ->
336+
d2e(T, 0, Imp).
334337

335-
d2e({ann_type,_,[V, T0]}, Prec) ->
338+
d2e({ann_type,_,[V, T0]}, Prec, Imp) ->
336339
%% Note: the -spec/-type syntax allows annotations everywhere, but
337340
%% EDoc does not. The fact that the annotation is added to the
338341
%% type here does not necessarily mean that it will be used by the
339342
%% layout module.
340343
{_L,P,R} = erl_parse:type_inop_prec('::'),
341-
T1 = d2e(T0, R),
344+
T1 = d2e(T0, R, Imp),
342345
T = ?add_t_ann(T1, element(3, V)),
343346
maybe_paren(P, Prec, T); % the only necessary call to maybe_paren()
344-
d2e({remote_type,_,[{atom,_,M},{atom,_,F},Ts0]}, _Prec) ->
345-
Ts = d2e(Ts0),
347+
d2e({remote_type,_,[{atom,_,M},{atom,_,F},Ts0]}, _Prec, Imp) ->
348+
Ts = d2e(Ts0, Imp),
346349
typevar_anno(#t_type{name = #t_name{module = M, name = F}, args = Ts}, Ts);
347-
d2e({type,_,'fun',[{type,_,product,As0},Ran0]}, _Prec) ->
348-
Ts = [Ran|As] = d2e([Ran0|As0]),
350+
d2e({type,_,'fun',[{type,_,product,As0},Ran0]}, _Prec, Imp) ->
351+
Ts = [Ran|As] = d2e([Ran0|As0], Imp),
349352
%% Assume that the linter has checked type variables.
350353
typevar_anno(#t_fun{args = As, range = Ran}, Ts);
351-
d2e({type,_,'fun',[A0={type,_,any},Ran0]}, _Prec) ->
352-
Ts = [A, Ran] = d2e([A0, Ran0]),
354+
d2e({type,_,'fun',[A0={type,_,any},Ran0]}, _Prec, Imp) ->
355+
Ts = [A, Ran] = d2e([A0, Ran0], Imp),
353356
typevar_anno(#t_fun{args = [A], range = Ran}, Ts);
354-
d2e({type,_,'fun',[]}, _Prec) ->
357+
d2e({type,_,'fun',[]}, _Prec, _Imp) ->
355358
#t_type{name = #t_name{name = function}, args = []};
356-
d2e({type,_,any}, _Prec) ->
359+
d2e({type,_,any}, _Prec, _Imp) ->
357360
#t_var{name = '...'}; % Kludge... not a type variable!
358-
d2e({type,_,nil,[]}, _Prec) ->
361+
d2e({type,_,nil,[]}, _Prec, _Imp) ->
359362
#t_nil{};
360-
d2e({paren_type,_,[T]}, Prec) ->
361-
d2e(T, Prec);
362-
d2e({type,_,list,[T0]}, _Prec) ->
363-
T = d2e(T0),
363+
d2e({paren_type,_,[T]}, Prec, Imp) ->
364+
d2e(T, Prec, Imp);
365+
d2e({type,_,list,[T0]}, _Prec, Imp) ->
366+
T = d2e(T0, Imp),
364367
typevar_anno(#t_list{type = T}, [T]);
365-
d2e({type,_,nonempty_list,[T0]}, _Prec) ->
366-
T = d2e(T0),
368+
d2e({type,_,nonempty_list,[T0]}, _Prec, Imp) ->
369+
T = d2e(T0, Imp),
367370
typevar_anno(#t_nonempty_list{type = T}, [T]);
368-
d2e({type,_,bounded_fun,[T,Gs]}, _Prec) ->
369-
[F0|Defs] = d2e([T|Gs]),
371+
d2e({type,_,bounded_fun,[T,Gs]}, _Prec, Imp) ->
372+
[F0|Defs] = d2e([T|Gs], Imp),
370373
F = ?set_t_ann(F0, lists:keydelete(type_variables, 1, ?t_ann(F0))),
371374
%% Assume that the linter has checked type variables.
372375
#t_spec{type = typevar_anno(F, [F0]), defs = Defs};
373-
d2e({type,_,range,[V1,V2]}, Prec) ->
376+
d2e({type,_,range,[V1,V2]}, Prec, _Imp) ->
374377
{_L,P,_R} = erl_parse:type_inop_prec('..'),
375378
{integer,_,I1} = erl_eval:partial_eval(V1),
376379
{integer,_,I2} = erl_eval:partial_eval(V2),
377380
T0 = #t_integer_range{from = I1, to = I2},
378381
maybe_paren(P, Prec, T0);
379-
d2e({type,_,constraint,[Sub,Ts0]}, _Prec) ->
382+
d2e({type,_,constraint,[Sub,Ts0]}, _Prec, Imp) ->
380383
case {Sub,Ts0} of
381384
{{atom,_,is_subtype},[{var,_,N},T0]} ->
382-
Ts = [T] = d2e([T0]),
385+
Ts = [T] = d2e([T0], Imp),
383386
#t_def{name = #t_var{name = N}, type = typevar_anno(T, Ts)};
384387
{{atom,_,is_subtype},[ST0,T0]} ->
385388
%% Should not happen.
386-
Ts = [ST,T] = d2e([ST0,T0]),
389+
Ts = [ST,T] = d2e([ST0,T0], Imp),
387390
#t_def{name = ST, type = typevar_anno(T, Ts)};
388391
_ ->
389392
throw_error(get_line(element(2, Sub)), "cannot handle guard", [])
390393
end;
391-
d2e({type,_,union,Ts0}, Prec) ->
394+
d2e({type,_,union,Ts0}, Prec, Imp) ->
392395
{_L,P,R} = erl_parse:type_inop_prec('|'),
393-
Ts = d2e(Ts0, R),
396+
Ts = d2e(Ts0, R, Imp),
394397
T = maybe_paren(P, Prec, #t_union{types = Ts}),
395398
typevar_anno(T, Ts);
396-
d2e({type,_,tuple,any}, _Prec) ->
399+
d2e({type,_,tuple,any}, _Prec, _Imp) ->
397400
#t_type{name = #t_name{name = tuple}, args = []};
398-
d2e({type,_,binary,[Base,Unit]}, _Prec) ->
401+
d2e({type,_,binary,[Base,Unit]}, _Prec, _Imp) ->
399402
{integer,_,B} = erl_eval:partial_eval(Base),
400403
{integer,_,U} = erl_eval:partial_eval(Unit),
401404
#t_binary{base_size = B, unit_size = U};
402-
d2e({type,_,map,any}, _Prec) ->
405+
d2e({type,_,map,any}, _Prec, _Imp) ->
403406
#t_type{name = #t_name{name = map}, args = []};
404-
d2e({type,_,map,Es}, _Prec) ->
405-
#t_map{types = d2e(Es) };
406-
d2e({type,_,map_field_assoc,[K,V]}, Prec) ->
407-
T = #t_map_field{assoc_type = assoc, k_type = d2e(K), v_type=d2e(V) },
407+
d2e({type,_,map,Es}, _Prec, Imp) ->
408+
#t_map{types = d2e(Es, Imp) };
409+
d2e({type,_,map_field_assoc,[K,V]}, Prec, Imp) ->
410+
T = #t_map_field{assoc_type = assoc, k_type = d2e(K, Imp), v_type=d2e(V, Imp) },
408411
{P,_R} = erl_parse:type_preop_prec('#'),
409412
maybe_paren(P, Prec, T);
410-
d2e({type,_,map_field_exact,[K,V]}, Prec) ->
411-
T = #t_map_field{assoc_type = exact, k_type = d2e(K), v_type=d2e(V) },
413+
d2e({type,_,map_field_exact,[K,V]}, Prec, Imp) ->
414+
T = #t_map_field{assoc_type = exact, k_type = d2e(K, Imp), v_type=d2e(V, Imp) },
412415
{P,_R} = erl_parse:type_preop_prec('#'),
413416
maybe_paren(P, Prec, T);
414-
d2e({type,_,tuple,Ts0}, _Prec) ->
415-
Ts = d2e(Ts0),
417+
d2e({type,_,tuple,Ts0}, _Prec, Imp) ->
418+
Ts = d2e(Ts0, Imp),
416419
typevar_anno(#t_tuple{types = Ts}, Ts);
417-
d2e({type,_,record,[Name|Fs0]}, Prec) ->
420+
d2e({type,_,record,[Name|Fs0]}, Prec, Imp) ->
418421
Atom = #t_atom{val = element(3, Name)},
419-
Fs = d2e(Fs0),
422+
Fs = d2e(Fs0, Imp),
420423
{P,_R} = erl_parse:type_preop_prec('#'),
421424
T = maybe_paren(P, Prec, #t_record{name = Atom, fields = Fs}),
422425
typevar_anno(T, Fs);
423-
d2e({type,_,field_type,[Name,Type0]}, Prec) ->
426+
d2e({type,_,field_type,[Name,Type0]}, Prec, Imp) ->
424427
{_L,P,R} = erl_parse:type_inop_prec('::'),
425-
Type = maybe_paren(P, Prec, d2e(Type0, R)),
428+
Type = maybe_paren(P, Prec, d2e(Type0, R, Imp)),
426429
T = #t_field{name = #t_atom{val = element(3, Name)}, type = Type},
427430
typevar_anno(T, [Type]);
428-
d2e({typed_record_field,{record_field,L,Name},Type}, Prec) ->
429-
d2e({type,L,field_type,[Name,Type]}, Prec);
430-
d2e({typed_record_field,{record_field,L,Name,_E},Type}, Prec) ->
431-
d2e({type,L,field_type,[Name,Type]}, Prec);
432-
d2e({record_field,L,_Name,_E}=F, Prec) ->
433-
d2e({typed_record_field,F,{type,L,any,[]}}, Prec); % Maybe skip...
434-
d2e({record_field,L,_Name}=F, Prec) ->
435-
d2e({typed_record_field,F,{type,L,any,[]}}, Prec); % Maybe skip...
436-
d2e({type,_,Name,Types0}, _Prec) ->
437-
Types = d2e(Types0),
431+
d2e({typed_record_field,{record_field,L,Name},Type}, Prec, Imp) ->
432+
d2e({type,L,field_type,[Name,Type]}, Prec, Imp);
433+
d2e({typed_record_field,{record_field,L,Name,_E},Type}, Prec, Imp) ->
434+
d2e({type,L,field_type,[Name,Type]}, Prec, Imp);
435+
d2e({record_field,L,_Name,_E}=F, Prec, Imp) ->
436+
d2e({typed_record_field,F,{type,L,any,[]}}, Prec, Imp); % Maybe skip...
437+
d2e({record_field,L,_Name}=F, Prec, Imp) ->
438+
d2e({typed_record_field,F,{type,L,any,[]}}, Prec, Imp); % Maybe skip...
439+
d2e({type,_,Name,Types0}, _Prec, Imp) ->
440+
Types = d2e(Types0, Imp),
438441
typevar_anno(#t_type{name = #t_name{name = Name}, args = Types}, Types);
439-
d2e({user_type,_,Name,Types0}, _Prec) ->
440-
Types = d2e(Types0),
441-
typevar_anno(#t_type{name = #t_name{name = Name}, args = Types}, Types);
442-
d2e({var,_,'_'}, _Prec) ->
442+
d2e({user_type,_,Name,Types0}, _Prec, Imp) ->
443+
Arity = length(Types0),
444+
Mod = maps:get({Name, Arity}, Imp, []),
445+
Types = d2e(Types0, Imp),
446+
typevar_anno(#t_type{name = #t_name{module = Mod, name = Name}, args = Types}, Types);
447+
d2e({var,_,'_'}, _Prec, _Imp) ->
443448
#t_type{name = #t_name{name = ?TOP_TYPE}};
444-
d2e({var,_,TypeName}, _Prec) ->
449+
d2e({var,_,TypeName}, _Prec, _Imp) ->
445450
TypeVar = ordsets:from_list([TypeName]),
446451
T = #t_var{name = TypeName},
447452
%% Annotate type variables with the name of the variable.
448453
%% Doing so will stop edoc_layout (and possibly other layout modules)
449454
%% from using the argument name from the source or to invent a new name.
450455
T1 = ?add_t_ann(T, {type_variables, TypeVar}),
451456
?add_t_ann(T1, TypeName);
452-
d2e(L, Prec) when is_list(L) ->
453-
[d2e(T, Prec) || T <- L];
454-
d2e({atom,_,A}, _Prec) ->
457+
d2e(L, Prec, Imp) when is_list(L) ->
458+
[d2e(T, Prec, Imp) || T <- L];
459+
d2e({atom,_,A}, _Prec, _Imp) ->
455460
#t_atom{val = A};
456-
d2e(undefined = U, _Prec) -> % opaque
461+
d2e(undefined = U, _Prec, _Imp) -> % opaque
457462
U;
458-
d2e(Expr, _Prec) ->
463+
d2e(Expr, _Prec, _Imp) ->
459464
{integer,_,I} = erl_eval:partial_eval(Expr),
460465
#t_integer{val = I}.
461466

lib/edoc/test/edoc_SUITE.erl

Lines changed: 14 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -25,13 +25,13 @@
2525
%% Test cases
2626
-export([app/1,appup/1,build_std/1,build_map_module/1,otp_12008/1,
2727
build_app/1, otp_14285/1, infer_module_app_test/1,
28-
module_with_feature/1]).
28+
module_with_feature/1, module_with_import_type/1]).
2929

3030
suite() -> [{ct_hooks,[ts_install_cth]}].
3131

3232
all() ->
3333
[app,appup,build_std,build_map_module,otp_12008, build_app, otp_14285,
34-
infer_module_app_test, module_with_feature].
34+
infer_module_app_test, module_with_feature, module_with_import_type].
3535

3636
groups() ->
3737
[].
@@ -170,3 +170,15 @@ module_with_feature(Config) ->
170170
PreprocessOpts = [{preprocess, true}, {dir, PrivDir}],
171171
ok = edoc:files([Source], PreprocessOpts),
172172
ok.
173+
174+
module_with_import_type(Config) ->
175+
DataDir = ?config(data_dir, Config),
176+
PrivDir = ?config(priv_dir, Config),
177+
F1 = filename:join(DataDir, "export_type.erl"),
178+
F2 = filename:join(DataDir, "import_type.erl"),
179+
ok = edoc:files([F1, F2], [{dir, PrivDir}]),
180+
ImportTypeHtmlFile = filename:join(PrivDir, "import_type.html"),
181+
true = filelib:is_regular(ImportTypeHtmlFile),
182+
{ok, Html} = file:read_file(ImportTypeHtmlFile),
183+
{_, _} = binary:match(Html, <<"export_type:my_binary()">>),
184+
ok.

0 commit comments

Comments
 (0)