21
21
22
22
-module (edoc_specs ).
23
23
24
- -export ([type /2 , spec /1 , dummy_spec /1 , docs /2 ]).
24
+ -export ([type /3 , spec /2 , dummy_spec /1 , docs /2 ]).
25
25
26
26
-export ([add_type_data /4 , tag /1 , is_tag /1 ]).
27
27
28
28
-include (" edoc.hrl" ).
29
29
-include (" edoc_types.hrl" ).
30
30
31
31
-type syntaxTree () :: erl_syntax :syntaxTree ().
32
+ -type imported_types () :: #{{atom (), arity ()} => module ()}.
32
33
33
34
-define (TOP_TYPE , term ).
34
35
35
36
% %
36
37
% % Exported functions
37
38
% %
38
39
39
- -spec type (Form :: syntaxTree (), TypeDocs :: dict :dict ()) -> # tag {}.
40
+ -spec type (Form :: syntaxTree (),
41
+ TypeDocs :: dict :dict (),
42
+ Imp :: imported_types ()) -> # tag {}.
40
43
41
44
% % @doc Convert an Erlang type to EDoc representation.
42
45
% % TypeDocs is a dict of {Name, Doc}.
43
46
% % Note: #t_typedef.name is set to {record, R} for record types.
44
- type (Form , TypeDocs ) ->
47
+ type (Form , TypeDocs , Imp ) ->
45
48
{Name , Data0 } = analyze_type_attribute (Form ),
46
49
{TypeName , Type , Args , Doc } =
47
50
case Data0 of
@@ -64,19 +67,19 @@ type(Form, TypeDocs) ->
64
67
# tag {name = type , line = get_line (element (2 , Type )),
65
68
origin = code ,
66
69
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 )},
69
72
Doc },
70
73
form = Form }.
71
74
72
- -spec spec (Form :: syntaxTree ()) -> # tag {}.
75
+ -spec spec (Form :: syntaxTree (), Imp :: imported_types () ) -> # tag {}.
73
76
74
77
% % @doc Convert an Erlang spec to EDoc representation.
75
- spec (Form ) ->
78
+ spec (Form , Imp ) ->
76
79
{Name , _Arity , TypeSpecs } = get_spec (Form ),
77
80
# tag {name = spec , line = get_line (element (2 , lists :nth (1 , TypeSpecs ))),
78
81
origin = code ,
79
- data = [aspec (d2e (TypeSpec ), Name ) || TypeSpec <- TypeSpecs ],
82
+ data = [aspec (d2e (TypeSpec , Imp ), Name ) || TypeSpec <- TypeSpecs ],
80
83
form = Form }.
81
84
82
85
-spec dummy_spec (Form :: syntaxTree ()) -> # tag {}.
@@ -329,133 +332,135 @@ arg_name([A | As], Default) ->
329
332
is_name (A ) ->
330
333
is_atom (A ).
331
334
332
- d2e (T ) ->
333
- d2e (T , 0 ).
335
+ d2e (T , Imp ) ->
336
+ d2e (T , 0 , Imp ).
334
337
335
- d2e ({ann_type ,_ ,[V , T0 ]}, Prec ) ->
338
+ d2e ({ann_type ,_ ,[V , T0 ]}, Prec , Imp ) ->
336
339
% % Note: the -spec/-type syntax allows annotations everywhere, but
337
340
% % EDoc does not. The fact that the annotation is added to the
338
341
% % type here does not necessarily mean that it will be used by the
339
342
% % layout module.
340
343
{_L ,P ,R } = erl_parse :type_inop_prec ('::' ),
341
- T1 = d2e (T0 , R ),
344
+ T1 = d2e (T0 , R , Imp ),
342
345
T = ? add_t_ann (T1 , element (3 , V )),
343
346
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 ),
346
349
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 ),
349
352
% % Assume that the linter has checked type variables.
350
353
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 ),
353
356
typevar_anno (# t_fun {args = [A ], range = Ran }, Ts );
354
- d2e ({type ,_ ,'fun' ,[]}, _Prec ) ->
357
+ d2e ({type ,_ ,'fun' ,[]}, _Prec , _Imp ) ->
355
358
# t_type {name = # t_name {name = function }, args = []};
356
- d2e ({type ,_ ,any }, _Prec ) ->
359
+ d2e ({type ,_ ,any }, _Prec , _Imp ) ->
357
360
# t_var {name = '...' }; % Kludge... not a type variable!
358
- d2e ({type ,_ ,nil ,[]}, _Prec ) ->
361
+ d2e ({type ,_ ,nil ,[]}, _Prec , _Imp ) ->
359
362
# 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 ),
364
367
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 ),
367
370
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 ),
370
373
F = ? set_t_ann (F0 , lists :keydelete (type_variables , 1 , ? t_ann (F0 ))),
371
374
% % Assume that the linter has checked type variables.
372
375
# t_spec {type = typevar_anno (F , [F0 ]), defs = Defs };
373
- d2e ({type ,_ ,range ,[V1 ,V2 ]}, Prec ) ->
376
+ d2e ({type ,_ ,range ,[V1 ,V2 ]}, Prec , _Imp ) ->
374
377
{_L ,P ,_R } = erl_parse :type_inop_prec ('..' ),
375
378
{integer ,_ ,I1 } = erl_eval :partial_eval (V1 ),
376
379
{integer ,_ ,I2 } = erl_eval :partial_eval (V2 ),
377
380
T0 = # t_integer_range {from = I1 , to = I2 },
378
381
maybe_paren (P , Prec , T0 );
379
- d2e ({type ,_ ,constraint ,[Sub ,Ts0 ]}, _Prec ) ->
382
+ d2e ({type ,_ ,constraint ,[Sub ,Ts0 ]}, _Prec , Imp ) ->
380
383
case {Sub ,Ts0 } of
381
384
{{atom ,_ ,is_subtype },[{var ,_ ,N },T0 ]} ->
382
- Ts = [T ] = d2e ([T0 ]),
385
+ Ts = [T ] = d2e ([T0 ], Imp ),
383
386
# t_def {name = # t_var {name = N }, type = typevar_anno (T , Ts )};
384
387
{{atom ,_ ,is_subtype },[ST0 ,T0 ]} ->
385
388
% % Should not happen.
386
- Ts = [ST ,T ] = d2e ([ST0 ,T0 ]),
389
+ Ts = [ST ,T ] = d2e ([ST0 ,T0 ], Imp ),
387
390
# t_def {name = ST , type = typevar_anno (T , Ts )};
388
391
_ ->
389
392
throw_error (get_line (element (2 , Sub )), " cannot handle guard" , [])
390
393
end ;
391
- d2e ({type ,_ ,union ,Ts0 }, Prec ) ->
394
+ d2e ({type ,_ ,union ,Ts0 }, Prec , Imp ) ->
392
395
{_L ,P ,R } = erl_parse :type_inop_prec ('|' ),
393
- Ts = d2e (Ts0 , R ),
396
+ Ts = d2e (Ts0 , R , Imp ),
394
397
T = maybe_paren (P , Prec , # t_union {types = Ts }),
395
398
typevar_anno (T , Ts );
396
- d2e ({type ,_ ,tuple ,any }, _Prec ) ->
399
+ d2e ({type ,_ ,tuple ,any }, _Prec , _Imp ) ->
397
400
# t_type {name = # t_name {name = tuple }, args = []};
398
- d2e ({type ,_ ,binary ,[Base ,Unit ]}, _Prec ) ->
401
+ d2e ({type ,_ ,binary ,[Base ,Unit ]}, _Prec , _Imp ) ->
399
402
{integer ,_ ,B } = erl_eval :partial_eval (Base ),
400
403
{integer ,_ ,U } = erl_eval :partial_eval (Unit ),
401
404
# t_binary {base_size = B , unit_size = U };
402
- d2e ({type ,_ ,map ,any }, _Prec ) ->
405
+ d2e ({type ,_ ,map ,any }, _Prec , _Imp ) ->
403
406
# 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 ) },
408
411
{P ,_R } = erl_parse :type_preop_prec ('#' ),
409
412
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 ) },
412
415
{P ,_R } = erl_parse :type_preop_prec ('#' ),
413
416
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 ),
416
419
typevar_anno (# t_tuple {types = Ts }, Ts );
417
- d2e ({type ,_ ,record ,[Name |Fs0 ]}, Prec ) ->
420
+ d2e ({type ,_ ,record ,[Name |Fs0 ]}, Prec , Imp ) ->
418
421
Atom = # t_atom {val = element (3 , Name )},
419
- Fs = d2e (Fs0 ),
422
+ Fs = d2e (Fs0 , Imp ),
420
423
{P ,_R } = erl_parse :type_preop_prec ('#' ),
421
424
T = maybe_paren (P , Prec , # t_record {name = Atom , fields = Fs }),
422
425
typevar_anno (T , Fs );
423
- d2e ({type ,_ ,field_type ,[Name ,Type0 ]}, Prec ) ->
426
+ d2e ({type ,_ ,field_type ,[Name ,Type0 ]}, Prec , Imp ) ->
424
427
{_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 )),
426
429
T = # t_field {name = # t_atom {val = element (3 , Name )}, type = Type },
427
430
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 ),
438
441
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 ) ->
443
448
# t_type {name = # t_name {name = ? TOP_TYPE }};
444
- d2e ({var ,_ ,TypeName }, _Prec ) ->
449
+ d2e ({var ,_ ,TypeName }, _Prec , _Imp ) ->
445
450
TypeVar = ordsets :from_list ([TypeName ]),
446
451
T = # t_var {name = TypeName },
447
452
% % Annotate type variables with the name of the variable.
448
453
% % Doing so will stop edoc_layout (and possibly other layout modules)
449
454
% % from using the argument name from the source or to invent a new name.
450
455
T1 = ? add_t_ann (T , {type_variables , TypeVar }),
451
456
? 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 ) ->
455
460
# t_atom {val = A };
456
- d2e (undefined = U , _Prec ) -> % opaque
461
+ d2e (undefined = U , _Prec , _Imp ) -> % opaque
457
462
U ;
458
- d2e (Expr , _Prec ) ->
463
+ d2e (Expr , _Prec , _Imp ) ->
459
464
{integer ,_ ,I } = erl_eval :partial_eval (Expr ),
460
465
# t_integer {val = I }.
461
466
0 commit comments