Skip to content

Commit 58c3497

Browse files
committed
Fix wrong id being given to doc comments
Standalone documentation comments currently do not have an id. This id was carried as the accumulator of the field, which yielded wrong results! Signed-off-by: Paul-Elliot <peada@free.fr>
1 parent 9624fc1 commit 58c3497

File tree

6 files changed

+121
-86
lines changed

6 files changed

+121
-86
lines changed

src/model/fold.ml

Lines changed: 47 additions & 29 deletions
Original file line numberDiff line numberDiff line change
@@ -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

1616
let 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

2022
and 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

4852
and 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

6976
and 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

7787
and 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

94106
and 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

125140
and 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

src/model/fold.mli

Lines changed: 51 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -17,23 +17,54 @@ type item =
1717
| Class of Class.t
1818
| Extension of Extension.t
1919
| ModuleType of ModuleType.t
20-
| Doc of Comment.docs_or_stop
20+
| Doc of Paths.Identifier.LabelParent.t * Comment.docs_or_stop
2121

22-
(** Bellow are the folding functions. For items that may contain
22+
(** Below are the folding functions. For items that may contain
2323
others, such as [signature], it folds recursively on the
24-
sub-items. It does not recurse into internal items. *)
24+
sub-items. It does not recurse into internal items.
25+
26+
The LabelParent identifier is used to give an id to the doc entries. *)
2527

2628
val unit : f:('a -> item -> 'a) -> 'a -> Compilation_unit.t -> 'a
2729
val page : f:('a -> item -> 'a) -> 'a -> Page.t -> 'a
2830

29-
val signature : f:('a -> item -> 'a) -> 'a -> Signature.t -> 'a
30-
val signature_item : f:('a -> item -> 'a) -> 'a -> Signature.item -> 'a
31-
val docs : f:('a -> item -> 'a) -> 'a -> Comment.docs_or_stop -> 'a
32-
val include_ : f:('a -> item -> 'a) -> 'a -> Include.t -> 'a
31+
val signature :
32+
f:('a -> item -> 'a) ->
33+
Paths.Identifier.LabelParent.t ->
34+
'a ->
35+
Signature.t ->
36+
'a
37+
val signature_item :
38+
f:('a -> item -> 'a) ->
39+
Paths.Identifier.LabelParent.t ->
40+
'a ->
41+
Signature.item ->
42+
'a
43+
val docs :
44+
f:('a -> item -> 'a) ->
45+
Paths.Identifier.LabelParent.t ->
46+
'a ->
47+
Comment.docs_or_stop ->
48+
'a
49+
val include_ :
50+
f:('a -> item -> 'a) ->
51+
Paths.Identifier.LabelParent.t ->
52+
'a ->
53+
Include.t ->
54+
'a
3355
val class_type : f:('a -> item -> 'a) -> 'a -> ClassType.t -> 'a
34-
val class_signature : f:('a -> item -> 'a) -> 'a -> ClassSignature.t -> 'a
56+
val class_signature :
57+
f:('a -> item -> 'a) ->
58+
Paths.Identifier.LabelParent.t ->
59+
'a ->
60+
ClassSignature.t ->
61+
'a
3562
val class_signature_item :
36-
f:('a -> item -> 'a) -> 'a -> ClassSignature.item -> 'a
63+
f:('a -> item -> 'a) ->
64+
Paths.Identifier.LabelParent.t ->
65+
'a ->
66+
ClassSignature.item ->
67+
'a
3768
val class_ : f:('a -> item -> 'a) -> 'a -> Class.t -> 'a
3869
val exception_ : f:('a -> item -> 'a) -> 'a -> Exception.t -> 'a
3970
val type_extension : f:('a -> item -> 'a) -> 'a -> Extension.t -> 'a
@@ -42,6 +73,15 @@ val module_ : f:('a -> item -> 'a) -> 'a -> Module.t -> 'a
4273
val type_decl : f:('a -> item -> 'a) -> 'a -> TypeDecl.t -> 'a
4374
val module_type : f:('a -> item -> 'a) -> 'a -> ModuleType.t -> 'a
4475
val simple_expansion :
45-
f:('a -> item -> 'a) -> 'a -> ModuleType.simple_expansion -> 'a
46-
val module_type_expr : f:('a -> item -> 'a) -> 'a -> ModuleType.expr -> 'a
76+
f:('a -> item -> 'a) ->
77+
Paths.Identifier.LabelParent.t ->
78+
'a ->
79+
ModuleType.simple_expansion ->
80+
'a
81+
val module_type_expr :
82+
f:('a -> item -> 'a) ->
83+
Paths.Identifier.LabelParent.t ->
84+
'a ->
85+
ModuleType.expr ->
86+
'a
4787
val functor_parameter : f:('a -> item -> 'a) -> 'a -> FunctorParameter.t -> 'a

src/search/entry.ml

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -146,7 +146,7 @@ and entries_of_doc id d =
146146
| `Math_block _ -> [ entry ~id ~doc:[ d ] ~kind:(Doc MathBlock) ]
147147
| `Table _ -> []
148148

149-
let entries_of_item id (x : Odoc_model.Fold.item) =
149+
let entries_of_item (x : Odoc_model.Fold.item) =
150150
match x with
151151
| CompilationUnit u -> (
152152
match u.content with
@@ -219,5 +219,5 @@ let entries_of_item id (x : Odoc_model.Fold.item) =
219219
(entry_of_extension_constructor te.type_path te.type_params)
220220
te.constructors)
221221
| ModuleType mt -> [ entry ~id:mt.id ~doc:mt.doc ~kind:ModuleType ]
222-
| Doc `Stop -> []
223-
| Doc (`Docs d) -> entries_of_docs id d
222+
| Doc (_, `Stop) -> []
223+
| Doc (id, `Docs d) -> entries_of_docs id d

src/search/entry.mli

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -61,5 +61,4 @@ type t = {
6161
kind : kind;
6262
}
6363

64-
val entries_of_item :
65-
Odoc_model.Paths.Identifier.Any.t -> Odoc_model.Fold.item -> t list
64+
val entries_of_item : Odoc_model.Fold.item -> t list

src/search/json_index/json_search.ml

Lines changed: 5 additions & 27 deletions
Original file line numberDiff line numberDiff line change
@@ -193,42 +193,20 @@ let output_json ppf first entries =
193193
first entries
194194

195195
let unit ppf u =
196-
let f (first, id) i =
197-
let entries = Entry.entries_of_item id i in
196+
let f first i =
197+
let entries = Entry.entries_of_item i in
198198
let entries =
199199
List.map (fun entry -> (entry, Html.of_entry entry)) entries
200200
in
201-
let id =
202-
match i with
203-
| CompilationUnit u -> (u.id :> Odoc_model.Paths.Identifier.t)
204-
| TypeDecl _ -> id
205-
| Module m -> (m.id :> Odoc_model.Paths.Identifier.t)
206-
| Value _ -> id
207-
| Exception _ -> id
208-
| ClassType ct -> (ct.id :> Odoc_model.Paths.Identifier.t)
209-
| Method _ -> id
210-
| Class c -> (c.id :> Odoc_model.Paths.Identifier.t)
211-
| Extension _ -> id
212-
| ModuleType mt -> (mt.id :> Odoc_model.Paths.Identifier.t)
213-
| Doc _ -> id
214-
in
215201
let first = output_json ppf first entries in
216-
(first, id)
217-
in
218-
let _first =
219-
Odoc_model.Fold.unit ~f
220-
( true,
221-
(u.Odoc_model.Lang.Compilation_unit.id :> Odoc_model.Paths.Identifier.t)
222-
)
223-
u
202+
first
224203
in
204+
let _first = Odoc_model.Fold.unit ~f true u in
225205
()
226206

227207
let page ppf (page : Odoc_model.Lang.Page.t) =
228208
let f first i =
229-
let entries =
230-
Entry.entries_of_item (page.name :> Odoc_model.Paths.Identifier.t) i
231-
in
209+
let entries = Entry.entries_of_item i in
232210
let entries =
233211
List.map (fun entry -> (entry, Html.of_entry entry)) entries
234212
in

0 commit comments

Comments
 (0)