@@ -11,20 +11,24 @@ type item =
1111 | Class of Class .t
1212 | Extension of Extension .t
1313 | ModuleType of ModuleType .t
14- | Doc of Comment .docs_or_stop
14+ | Doc of Paths.Identifier.LabelParent .t * Comment .docs_or_stop
1515
1616let rec unit ~f acc u =
1717 let acc = f acc (CompilationUnit u) in
18- match u.content with Module m -> signature ~f acc m | Pack _ -> acc
18+ match u.content with
19+ | Module m -> signature ~f (u.id :> Paths.Identifier.LabelParent.t ) acc m
20+ | Pack _ -> acc
1921
2022and page ~f acc p =
2123 let open Page in
22- docs ~f acc (`Docs p.content)
24+ docs ~f (p.name :> Paths.Identifier.LabelParent.t ) acc (`Docs p.content)
2325
24- and signature ~f acc (s : Signature.t ) =
25- List. fold_left (signature_item ~f ) acc s.items
26+ and signature ~f id acc (s : Signature.t ) =
27+ List. fold_left
28+ (signature_item ~f (id :> Paths.Identifier.LabelParent.t ))
29+ acc s.items
2630
27- and signature_item ~f acc s_item =
31+ and signature_item ~f id acc s_item =
2832 match s_item with
2933 | Module (_ , m ) -> module_ ~f acc m
3034 | ModuleType mt -> module_type ~f acc mt
@@ -38,12 +42,12 @@ and signature_item ~f acc s_item =
3842 | Value v -> value ~f acc v
3943 | Class (_ , cl ) -> class_ ~f acc cl
4044 | ClassType (_ , clt ) -> class_type ~f acc clt
41- | Include i -> include_ ~f acc i
42- | Comment d -> docs ~f acc d
45+ | Include i -> include_ ~f id acc i
46+ | Comment d -> docs ~f id acc d
4347
44- and docs ~f acc d = f acc (Doc d )
48+ and docs ~f id acc d = f acc (Doc (id, d) )
4549
46- and include_ ~f acc inc = signature ~f acc inc.expansion.content
50+ and include_ ~f id acc inc = signature ~f id acc inc.expansion.content
4751
4852and class_type ~f acc ct =
4953 (* This check is important because [is_internal] does not work on children of
@@ -53,26 +57,32 @@ and class_type ~f acc ct =
5357 if Paths.Identifier. is_internal ct.id then acc
5458 else
5559 let acc = f acc (ClassType ct) in
56- match ct.expansion with None -> acc | Some cs -> class_signature ~f acc cs
60+ match ct.expansion with
61+ | None -> acc
62+ | Some cs ->
63+ class_signature ~f (ct.id :> Paths.Identifier.LabelParent.t ) acc cs
5764
58- and class_signature ~f acc ct_expr =
59- List. fold_left (class_signature_item ~f ) acc ct_expr.items
65+ and class_signature ~f id acc ct_expr =
66+ List. fold_left (class_signature_item ~f id ) acc ct_expr.items
6067
61- and class_signature_item ~f acc item =
68+ and class_signature_item ~f id acc item =
6269 match item with
6370 | Method m -> f acc (Method m)
6471 | InstanceVariable _ -> acc
6572 | Constraint _ -> acc
6673 | Inherit _ -> acc
67- | Comment d -> docs ~f acc d
74+ | Comment d -> docs ~f id acc d
6875
6976and class_ ~f acc cl =
7077 if Paths.Identifier. is_internal cl.id then acc
7178 else
7279 let acc = f acc (Class cl) in
7380 match cl.expansion with
7481 | None -> acc
75- | Some cl_signature -> class_signature ~f acc cl_signature
82+ | Some cl_signature ->
83+ class_signature ~f
84+ (cl.id :> Paths.Identifier.LabelParent.t )
85+ acc cl_signature
7686
7787and exception_ ~f acc exc =
7888 if Paths.Identifier. is_internal exc.id then acc else f acc (Exception exc)
@@ -88,8 +98,10 @@ and module_ ~f acc m =
8898 let acc = f acc (Module m) in
8999 match m.type_ with
90100 | Alias (_ , None) -> acc
91- | Alias (_ , Some s_e ) -> simple_expansion ~f acc s_e
92- | ModuleType mte -> module_type_expr ~f acc mte
101+ | Alias (_ , Some s_e ) ->
102+ simple_expansion ~f (m.id :> Paths.Identifier.LabelParent.t ) acc s_e
103+ | ModuleType mte ->
104+ module_type_expr ~f (m.id :> Paths.Identifier.LabelParent.t ) acc mte
93105
94106and type_decl ~f acc td =
95107 if Paths.Identifier. is_internal td.id then acc else f acc (TypeDecl td)
@@ -100,27 +112,33 @@ and module_type ~f acc mt =
100112 let acc = f acc (ModuleType mt) in
101113 match mt.expr with
102114 | None -> acc
103- | Some mt_expr -> module_type_expr ~f acc mt_expr
115+ | Some mt_expr ->
116+ module_type_expr ~f
117+ (mt.id :> Paths.Identifier.LabelParent.t )
118+ acc mt_expr
104119
105- and simple_expansion ~f acc s_e =
120+ and simple_expansion ~f id acc s_e =
106121 match s_e with
107- | Signature sg -> signature ~f acc sg
122+ | Signature sg -> signature ~f id acc sg
108123 | Functor (p , s_e ) ->
109124 let acc = functor_parameter ~f acc p in
110- simple_expansion ~f acc s_e
125+ simple_expansion ~f id acc s_e
111126
112- and module_type_expr ~f acc mte =
127+ and module_type_expr ~f id acc mte =
113128 match mte with
114- | Signature s -> signature ~f acc s
129+ | Signature s -> signature ~f id acc s
115130 | Functor (fp , mt_expr ) ->
116131 let acc = functor_parameter ~f acc fp in
117- module_type_expr ~f acc mt_expr
118- | With { w_expansion = Some sg ; _ } -> simple_expansion ~f acc sg
119- | TypeOf { t_expansion = Some sg ; _ } -> simple_expansion ~f acc sg
120- | Path { p_expansion = Some sg ; _ } -> simple_expansion ~f acc sg
132+ module_type_expr ~f id acc mt_expr
133+ | With { w_expansion = Some sg ; _ } -> simple_expansion ~f id acc sg
134+ | TypeOf { t_expansion = Some sg ; _ } -> simple_expansion ~f id acc sg
135+ | Path { p_expansion = Some sg ; _ } -> simple_expansion ~f id acc sg
121136 | Path { p_expansion = None ; _ } -> acc
122137 | With { w_expansion = None ; _ } -> acc
123138 | TypeOf { t_expansion = None ; _ } -> acc
124139
125140and functor_parameter ~f acc fp =
126- match fp with Unit -> acc | Named n -> module_type_expr ~f acc n.expr
141+ match fp with
142+ | Unit -> acc
143+ | Named n ->
144+ module_type_expr ~f (n.id :> Paths.Identifier.LabelParent.t ) acc n.expr
0 commit comments