Skip to content

Commit b5ef6e4

Browse files
committed
Pass the documentation along with module expansions
Previously, when resolving module aliases, the documentation of the target module was inserted in the signature as a Comment.
1 parent f030bb3 commit b5ef6e4

File tree

14 files changed

+113
-57
lines changed

14 files changed

+113
-57
lines changed

src/document/generator.ml

Lines changed: 8 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1217,15 +1217,18 @@ module Make (Syntax : SYNTAX) = struct
12171217
let modname = Paths.Identifier.name t.id in
12181218
let expansion =
12191219
match t.type_ with
1220-
| Alias (_, Some e) -> Some (simple_expansion e)
1220+
| Alias (_, Some e) -> Some (simple_expansion e.a_expansion, e.a_doc)
12211221
| Alias (_, None) -> None
1222-
| ModuleType e -> expansion_of_module_type_expr e
1222+
| ModuleType e -> (
1223+
match expansion_of_module_type_expr e with
1224+
| Some e -> Some (e, t.doc)
1225+
| None -> None )
12231226
in
12241227
let modname, status, expansion =
12251228
match expansion with
12261229
| None -> (O.documentedSrc (O.txt modname), `Default, None)
1227-
| Some items ->
1228-
let doc = Comment.standalone t.doc in
1230+
| Some (items, expansion_doc) ->
1231+
let doc = Comment.standalone expansion_doc in
12291232
let status =
12301233
match t.type_ with
12311234
| ModuleType (Signature _) -> `Inline
@@ -1269,7 +1272,7 @@ module Make (Syntax : SYNTAX) = struct
12691272
++ Syntax.Mod.open_tag ++ O.txt " ... " ++ Syntax.Mod.close_tag
12701273
in
12711274
match md with
1272-
| Alias (_, Some se) -> simple_expansion_in_decl base se
1275+
| Alias (_, Some se) -> simple_expansion_in_decl base se.a_expansion
12731276
| Alias (p, _) when not Paths.Path.(is_hidden (p :> t)) ->
12741277
O.txt " = " ++ mdexpr md
12751278
| Alias _ -> sig_dotdotdot

src/document/targets.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -55,7 +55,7 @@ and module_ (t : Odoc_model.Lang.Module.t) =
5555
let url = Url.Path.from_identifier t.id in
5656
let subpages =
5757
match t.type_ with
58-
| Alias (_, Some e) -> simple_expansion e
58+
| Alias (_, Some e) -> simple_expansion e.a_expansion
5959
| Alias (_, None) -> []
6060
| ModuleType expr -> module_type_expr expr
6161
in

src/model/lang.ml

Lines changed: 6 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -19,8 +19,13 @@ open Paths
1919
(** {3 Modules} *)
2020

2121
module rec Module : sig
22+
type alias_expansion = {
23+
a_doc : Comment.docs;
24+
a_expansion : ModuleType.simple_expansion;
25+
}
26+
2227
type decl =
23-
| Alias of (Path.Module.t * ModuleType.simple_expansion option)
28+
| Alias of (Path.Module.t * alias_expansion option)
2429
| ModuleType of ModuleType.expr
2530

2631
type t = {

src/model_desc/lang_desc.ml

Lines changed: 9 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -18,9 +18,17 @@ let rec module_decl =
1818
C
1919
( "Alias",
2020
((x :> Paths.Path.t), y),
21-
Pair (path, Option simple_expansion) )
21+
Pair (path, Option module_alias_expansion) )
2222
| ModuleType x -> C ("ModuleType", x, moduletype_expr))
2323

24+
and module_alias_expansion =
25+
let open Lang.Module in
26+
Record
27+
[
28+
F ("a_doc", (fun t -> t.a_doc), docs);
29+
F ("a_expansion", (fun t -> t.a_expansion), simple_expansion);
30+
]
31+
2432
and module_t =
2533
let open Lang.Module in
2634
Record

src/xref2/compile.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -320,7 +320,7 @@ and include_ : Env.t -> Include.t -> Include.t =
320320
match decl with
321321
| Alias p ->
322322
Expand_tools.aux_expansion_of_module_alias env ~strengthen:true p
323-
>>= Expand_tools.assert_not_functor
323+
>>= fun (expansion, _doc) -> Expand_tools.assert_not_functor expansion
324324
| ModuleType mty ->
325325
Expand_tools.aux_expansion_of_u_module_type_expr env mty
326326
with

src/xref2/component.ml

Lines changed: 13 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -71,8 +71,13 @@ module Opt = struct
7171
end
7272

7373
module rec Module : sig
74+
type alias_expansion = {
75+
a_doc : CComment.docs;
76+
a_expansion : ModuleType.simple_expansion;
77+
}
78+
7479
type decl =
75-
| Alias of Cpath.module_ * ModuleType.simple_expansion option
80+
| Alias of Cpath.module_ * alias_expansion option
7681
| ModuleType of ModuleType.expr
7782

7883
type t = {
@@ -1887,10 +1892,16 @@ module Of_Lang = struct
18871892
match m with
18881893
| Odoc_model.Lang.Module.Alias (p, e) ->
18891894
Module.Alias
1890-
(module_path ident_map p, option simple_expansion ident_map e)
1895+
(module_path ident_map p, option module_alias_expansion ident_map e)
18911896
| Odoc_model.Lang.Module.ModuleType s ->
18921897
Module.ModuleType (module_type_expr ident_map s)
18931898

1899+
and module_alias_expansion ident_map e =
1900+
{
1901+
Module.a_doc = docs ident_map e.a_doc;
1902+
a_expansion = simple_expansion ident_map e.a_expansion;
1903+
}
1904+
18941905
and include_decl ident_map m =
18951906
match m with
18961907
| Odoc_model.Lang.Include.Alias p -> Include.Alias (module_path ident_map p)

src/xref2/component.mli

Lines changed: 6 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -61,8 +61,13 @@ end
6161
*)
6262

6363
module rec Module : sig
64+
type alias_expansion = {
65+
a_doc : CComment.docs;
66+
a_expansion : ModuleType.simple_expansion;
67+
}
68+
6469
type decl =
65-
| Alias of Cpath.module_ * ModuleType.simple_expansion option
70+
| Alias of Cpath.module_ * alias_expansion option
6671
| ModuleType of ModuleType.expr
6772

6873
type t = {

src/xref2/expand_tools.ml

Lines changed: 21 additions & 30 deletions
Original file line numberDiff line numberDiff line change
@@ -33,13 +33,14 @@ let rec aux_expansion_of_module :
3333
Component.Module.t ->
3434
(expansion, signature_of_module_error) Result.result =
3535
let open Component.Module in
36-
fun env ~strengthen m -> aux_expansion_of_module_decl env ~strengthen m.type_
37-
38-
and aux_expansion_of_module_decl env ~strengthen ty =
39-
let open Component.Module in
40-
match ty with
41-
| Alias (path, _) -> aux_expansion_of_module_alias env ~strengthen path
42-
| ModuleType expr -> aux_expansion_of_module_type_expr env expr
36+
fun env ~strengthen m ->
37+
match m.type_ with
38+
| Alias (path, _) ->
39+
aux_expansion_of_module_alias env ~strengthen path
40+
>>= fun (expansion, _doc) -> Ok expansion
41+
| ModuleType expr ->
42+
(* TODO: Should [expr] be [ModuleType.t] ? (eg. include the [doc] field) *)
43+
aux_expansion_of_module_type_expr env expr
4344

4445
and aux_expansion_of_module_alias env ~strengthen path =
4546
(* Format.eprintf "aux_expansion_of_module_alias (strengthen=%b, path=%a)\n%!"
@@ -56,28 +57,14 @@ and aux_expansion_of_module_alias env ~strengthen path =
5657
&& not (Cpath.is_resolved_module_hidden ~weak_canonical_test:true p)
5758
in
5859
let m = Component.Delayed.get m in
59-
match (aux_expansion_of_module env ~strengthen:true m, m.doc) with
60-
| (Error _ as e), _ -> e
61-
| Ok (Signature sg), [] ->
62-
(* Format.eprintf "Maybe strenthening now...\n%!"; *)
63-
let sg' =
64-
if strengthen then
65-
Strengthen.signature ?canonical:m.canonical (`Resolved p) sg
66-
else sg
67-
in
68-
Ok (Signature sg')
69-
| Ok (Signature sg), docs ->
70-
(* Format.eprintf "Maybe strenthening now...\n%!"; *)
60+
match aux_expansion_of_module env ~strengthen:true m with
61+
| Error _ as e -> e
62+
| Ok (Signature sg) when strengthen ->
7163
let sg' =
72-
if strengthen then
73-
Strengthen.signature ?canonical:m.canonical (`Resolved p) sg
74-
else sg
64+
Strengthen.signature ?canonical:m.canonical (`Resolved p) sg
7565
in
76-
(* Format.eprintf "Before:\n%a\n\n%!After\n%a\n\n%!"
77-
Component.Fmt.signature sg
78-
Component.Fmt.signature sg'; *)
79-
Ok (Signature { sg' with items = Comment (`Docs docs) :: sg'.items })
80-
| Ok (Functor _ as x), _ -> Ok x )
66+
Ok (Signature sg', m.doc)
67+
| Ok x -> Ok (x, m.doc) )
8168
| Error e -> Error (`UnresolvedPath (`Module (path, e)))
8269

8370
(* We need to reresolve fragments in expansions as the root of the fragment
@@ -99,7 +86,10 @@ and aux_expansion_of_module_type_type_of_desc env t :
9986
match t with
10087
| Component.ModuleType.ModPath p ->
10188
aux_expansion_of_module_alias env ~strengthen:false p
102-
| StructInclude p -> aux_expansion_of_module_alias env ~strengthen:true p
89+
>>= fun (expansion, _doc) -> Ok expansion
90+
| StructInclude p ->
91+
aux_expansion_of_module_alias env ~strengthen:true p
92+
>>= fun (expansion, _doc) -> Ok expansion
10393

10494
and assert_not_functor = function Signature sg -> Ok sg | _ -> assert false
10595

@@ -211,8 +201,9 @@ let expansion_of_u_module_type_expr env id expr =
211201
let expansion_of_module_alias env id path =
212202
let open Paths.Identifier in
213203
aux_expansion_of_module_alias ~strengthen:false env path
214-
>>= handle_expansion env (id : Module.t :> Signature.t)
215-
>>= fun (env, r) -> Ok (env, false, r)
204+
>>= fun (expansion, doc) ->
205+
handle_expansion env (id : Module.t :> Signature.t) expansion
206+
>>= fun (env, r) -> Ok (env, false, r, doc)
216207

217208
let expansion_of_module_type_of_desc env id t_desc =
218209
aux_expansion_of_module_type_type_of_desc env t_desc

src/xref2/lang_of.ml

Lines changed: 12 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -670,9 +670,20 @@ and module_decl :
670670
match d with
671671
| Component.Module.Alias (p, s) ->
672672
Odoc_model.Lang.Module.Alias
673-
(Path.module_ map p, Opt.map (simple_expansion map identifier) s)
673+
(Path.module_ map p, Opt.map (module_alias_expansion map identifier) s)
674674
| ModuleType mty -> ModuleType (module_type_expr map identifier mty)
675675

676+
and module_alias_expansion :
677+
maps ->
678+
Identifier.Signature.t ->
679+
Component.Module.alias_expansion ->
680+
Lang.Module.alias_expansion =
681+
fun map identifier t ->
682+
{
683+
a_doc = docs (identifier :> Identifier.LabelParent.t) t.a_doc;
684+
a_expansion = simple_expansion map identifier t.a_expansion;
685+
}
686+
676687
and mty_substitution map identifier = function
677688
| Component.ModuleType.ModuleEq (frag, decl) ->
678689
Odoc_model.Lang.ModuleType.ModuleEq

src/xref2/link.ml

Lines changed: 18 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -375,8 +375,7 @@ and extract_doc : Module.decl -> Comment.docs * Module.decl =
375375
| e -> ([], e)
376376
in
377377
function
378-
| Alias (p, expansion) -> (
379-
match map_expansion expansion with d, e -> (d, Alias (p, e)) )
378+
| Alias (_, Some e) as alias -> (e.a_doc, alias)
380379
| ModuleType (Path { p_path; p_expansion }) -> (
381380
match map_expansion p_expansion with
382381
| d, e -> (d, ModuleType (Path { p_path; p_expansion = e })) )
@@ -398,7 +397,7 @@ and module_ : Env.t -> Module.t -> Module.t =
398397
let type_ = module_decl env sg_id m.type_ in
399398
let type_ =
400399
match type_ with
401-
| Alias (`Resolved p, e) ->
400+
| Alias (`Resolved p, _) ->
402401
let hidden_alias =
403402
Paths.Path.is_hidden (`Resolved (p :> Paths.Path.Resolved.t))
404403
in
@@ -412,11 +411,13 @@ and module_ : Env.t -> Module.t -> Module.t =
412411
match
413412
Expand_tools.expansion_of_module_alias env m.id (`Resolved cp)
414413
with
415-
| Ok (_, _, e) ->
414+
| Ok (_, _, e, doc) ->
416415
let le = Lang_of.(simple_expansion empty sg_id e) in
417-
Alias (`Resolved p, Some (simple_expansion env sg_id le))
418-
| Error _ -> Alias (`Resolved p, e)
419-
else Alias (`Resolved p, e)
416+
let a_doc = Lang_of.docs (sg_id :> Id.LabelParent.t) doc
417+
and a_expansion = simple_expansion env sg_id le in
418+
Alias (`Resolved p, Some { a_doc; a_expansion })
419+
| Error _ -> type_
420+
else type_
420421
| Alias _ -> type_
421422
| ModuleType mty -> ModuleType mty
422423
in
@@ -432,7 +433,16 @@ and module_decl : Env.t -> Id.Signature.t -> Module.decl -> Module.decl =
432433
match decl with
433434
| ModuleType expr -> ModuleType (module_type_expr env id expr)
434435
| Alias (p, e) ->
435-
Alias (module_path env p, Opt.map (simple_expansion env id) e)
436+
Alias (module_path env p, Opt.map (module_alias_expansion env id) e)
437+
438+
and module_alias_expansion :
439+
Env.t -> Id.Signature.t -> Module.alias_expansion -> Module.alias_expansion
440+
=
441+
fun env id e ->
442+
{
443+
a_doc = comment_docs env e.a_doc;
444+
a_expansion = simple_expansion env id e.a_expansion;
445+
}
436446

437447
and include_decl : Env.t -> Id.Signature.t -> Include.decl -> Include.decl =
438448
fun env id decl ->

0 commit comments

Comments
 (0)