@@ -30,8 +30,9 @@ and signature ~f id acc (s : Signature.t) =
3030
3131and signature_item ~f id acc s_item =
3232 match s_item with
33- | Module (_ , m ) -> module_ ~f acc m
34- | ModuleType mt -> module_type ~f acc mt
33+ | Module (_ , m ) -> module_ ~f (m.id :> Paths.Identifier.LabelParent.t ) acc m
34+ | ModuleType mt ->
35+ module_type ~f (mt.id :> Paths.Identifier.LabelParent.t ) acc mt
3536 | ModuleSubstitution _ -> acc
3637 | ModuleTypeSubstitution _ -> acc
3738 | Open _ -> acc
@@ -40,17 +41,18 @@ and signature_item ~f id acc s_item =
4041 | TypExt te -> type_extension ~f acc te
4142 | Exception exc -> exception_ ~f acc exc
4243 | Value v -> value ~f acc v
43- | Class (_ , cl ) -> class_ ~f acc cl
44- | ClassType (_ , clt ) -> class_type ~f acc clt
44+ | Class (_ , cl ) -> class_ ~f (cl.id :> Paths.Identifier.LabelParent.t ) acc cl
45+ | ClassType (_ , clt ) ->
46+ class_type ~f (clt.id :> Paths.Identifier.LabelParent.t ) acc clt
4547 | Include i -> include_ ~f id acc i
4648 | Comment d -> docs ~f id acc d
4749
4850and docs ~f id acc d = f acc (Doc (id, d))
4951
5052and include_ ~f id acc inc = signature ~f id acc inc.expansion.content
5153
52- and class_type ~f acc ct =
53- (* This check is important because [is_hidden ] does not work on children of
54+ and class_type ~f id acc ct =
55+ (* This check is important because [is_internal ] does not work on children of
5456 internal items. This means that if [Fold] did not make this check here,
5557 it would be difficult to filter for internal items afterwards. This also
5658 applies to the same check in functions bellow. *)
@@ -59,8 +61,7 @@ and class_type ~f acc ct =
5961 let acc = f acc (ClassType ct) in
6062 match ct.expansion with
6163 | None -> acc
62- | Some cs ->
63- class_signature ~f (ct.id :> Paths.Identifier.LabelParent.t ) acc cs
64+ | Some cs -> class_signature ~f id acc cs
6465
6566and class_signature ~f id acc ct_expr =
6667 List. fold_left (class_signature_item ~f id) acc ct_expr.items
@@ -73,16 +74,13 @@ and class_signature_item ~f id acc item =
7374 | Inherit _ -> acc
7475 | Comment d -> docs ~f id acc d
7576
76- and class_ ~f acc cl =
77+ and class_ ~f id acc cl =
7778 if Paths.Identifier. is_hidden cl.id then acc
7879 else
7980 let acc = f acc (Class cl) in
8081 match cl.expansion with
8182 | None -> acc
82- | Some cl_signature ->
83- class_signature ~f
84- (cl.id :> Paths.Identifier.LabelParent.t )
85- acc cl_signature
83+ | Some cl_signature -> class_signature ~f id acc cl_signature
8684
8785and exception_ ~f acc exc =
8886 if Paths.Identifier. is_hidden exc.id then acc else f acc (Exception exc)
@@ -92,30 +90,25 @@ and type_extension ~f acc te = f acc (Extension te)
9290and value ~f acc v =
9391 if Paths.Identifier. is_hidden v.id then acc else f acc (Value v)
9492
95- and module_ ~f acc m =
93+ and module_ ~f id acc m =
9694 if Paths.Identifier. is_hidden m.id then acc
9795 else
9896 let acc = f acc (Module m) in
9997 match m.type_ with
10098 | Alias (_ , None) -> acc
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
99+ | Alias (_ , Some s_e ) -> simple_expansion ~f id acc s_e
100+ | ModuleType mte -> module_type_expr ~f id acc mte
105101
106102and type_decl ~f acc td =
107103 if Paths.Identifier. is_hidden td.id then acc else f acc (TypeDecl td)
108104
109- and module_type ~f acc mt =
105+ and module_type ~f id acc mt =
110106 if Paths.Identifier. is_hidden mt.id then acc
111107 else
112108 let acc = f acc (ModuleType mt) in
113109 match mt.expr with
114110 | None -> acc
115- | Some mt_expr ->
116- module_type_expr ~f
117- (mt.id :> Paths.Identifier.LabelParent.t )
118- acc mt_expr
111+ | Some mt_expr -> module_type_expr ~f id acc mt_expr
119112
120113and simple_expansion ~f id acc s_e =
121114 match s_e with
0 commit comments