@@ -41,7 +41,7 @@ type doc_entry = Paragraph | Heading | CodeBlock | MathBlock | Verbatim
41
41
42
42
type value_entry = { value : Value .value ; type_ : TypeExpr .t }
43
43
44
- type extra =
44
+ type kind =
45
45
| TypeDecl of type_decl_entry
46
46
| Module
47
47
| Value of value_entry
@@ -61,13 +61,14 @@ module Html = Tyxml.Html
61
61
type t = {
62
62
id : Odoc_model.Paths.Identifier.Any .t ;
63
63
doc : Odoc_model.Comment .docs ;
64
- extra : extra ;
65
- html : Html_types .div Html .elt ;
64
+ kind : kind ;
66
65
}
67
66
68
- let entry ~id ~doc ~extra ~html =
67
+ type with_html = { entry : t ; html : [ `Code | `Div ] Tyxml.Html .elt list }
68
+
69
+ let entry ~id ~doc ~kind =
69
70
let id = (id :> Odoc_model.Paths.Identifier.Any.t ) in
70
- { id; extra ; doc; html }
71
+ { id; kind ; doc }
71
72
72
73
let varify_params =
73
74
List. mapi (fun i param ->
@@ -77,15 +78,6 @@ let varify_params =
77
78
78
79
let entry_of_constructor id_parent params (constructor : TypeDecl.Constructor.t )
79
80
=
80
- let html =
81
- Tyxml.Html. div ~a: []
82
- [
83
- Tyxml.Html. txt
84
- @@ Generator. constructor
85
- (constructor.id :> Identifier.t )
86
- constructor.args constructor.res;
87
- ]
88
- in
89
81
let args = constructor.args in
90
82
let res =
91
83
match constructor.res with
@@ -97,20 +89,11 @@ let entry_of_constructor id_parent params (constructor : TypeDecl.Constructor.t)
97
89
((id_parent :> Odoc_model.Paths.Identifier.Path.Type.t ), false ),
98
90
params )
99
91
in
100
- let extra = Constructor { args; res } in
101
- entry ~id: constructor.id ~doc: constructor.doc ~extra ~html
92
+ let kind = Constructor { args; res } in
93
+ entry ~id: constructor.id ~doc: constructor.doc ~kind
102
94
103
95
let entry_of_extension_constructor id_parent params
104
96
(constructor : Extension.Constructor.t ) =
105
- let html =
106
- Tyxml.Html. div ~a: []
107
- [
108
- Tyxml.Html. txt
109
- @@ Generator. constructor
110
- (constructor.id :> Identifier.t )
111
- constructor.args constructor.res;
112
- ]
113
- in
114
97
let args = constructor.args in
115
98
let res =
116
99
match constructor.res with
@@ -119,8 +102,8 @@ let entry_of_extension_constructor id_parent params
119
102
let params = varify_params params in
120
103
TypeExpr. Constr (id_parent, params)
121
104
in
122
- let extra = ExtensionConstructor { args; res } in
123
- entry ~id: constructor.id ~doc: constructor.doc ~extra ~html
105
+ let kind = ExtensionConstructor { args; res } in
106
+ entry ~id: constructor.id ~doc: constructor.doc ~kind
124
107
125
108
let entry_of_field id_parent params (field : TypeDecl.Field.t ) =
126
109
let params = varify_params params in
@@ -130,49 +113,42 @@ let entry_of_field id_parent params (field : TypeDecl.Field.t) =
130
113
((id_parent :> Odoc_model.Paths.Identifier.Path.Type.t ), false ),
131
114
params )
132
115
in
133
- let extra =
116
+ let kind =
134
117
Field { mutable_ = field.mutable_; type_ = field.type_; parent_type }
135
118
in
136
- let html = Html. div ~a: [] [] in
137
- entry ~id: field.id ~doc: field.doc ~extra ~html
119
+ entry ~id: field.id ~doc: field.doc ~kind
138
120
139
121
let rec entries_of_docs (d : Odoc_model.Comment.docs ) =
140
122
List. concat_map entries_of_doc d
141
123
142
124
and entries_of_doc d =
143
- let html = Html. div ~a: [] [] in
144
125
match d.value with
145
- | `Paragraph (lbl , _ ) ->
146
- [ entry ~id: lbl ~doc: [ d ] ~extra: (Doc Paragraph ) ~html ]
126
+ | `Paragraph (lbl , _ ) -> [ entry ~id: lbl ~doc: [ d ] ~kind: (Doc Paragraph ) ]
147
127
| `Tag _ -> []
148
128
| `List (_ , ds ) ->
149
129
List. concat_map entries_of_docs (ds :> Odoc_model.Comment.docs list )
150
- | `Heading (_ , lbl , _ ) ->
151
- [ entry ~id: lbl ~doc: [ d ] ~extra: (Doc Heading ) ~html ]
130
+ | `Heading (_ , lbl , _ ) -> [ entry ~id: lbl ~doc: [ d ] ~kind: (Doc Heading ) ]
152
131
| `Modules _ -> []
153
132
| `Code_block (lbl , _ , _ , o ) ->
154
133
let o =
155
134
match o with
156
135
| None -> []
157
136
| Some o -> entries_of_docs (o :> Odoc_model.Comment.docs )
158
137
in
159
- entry ~id: lbl ~doc: [ d ] ~extra: (Doc CodeBlock ) ~html :: o
160
- | `Verbatim (lbl , _ ) ->
161
- [ entry ~id: lbl ~doc: [ d ] ~extra: (Doc Verbatim ) ~html ]
162
- | `Math_block (lbl , _ ) ->
163
- [ entry ~id: lbl ~doc: [ d ] ~extra: (Doc MathBlock ) ~html ]
138
+ entry ~id: lbl ~doc: [ d ] ~kind: (Doc CodeBlock ) :: o
139
+ | `Verbatim (lbl , _ ) -> [ entry ~id: lbl ~doc: [ d ] ~kind: (Doc Verbatim ) ]
140
+ | `Math_block (lbl , _ ) -> [ entry ~id: lbl ~doc: [ d ] ~kind: (Doc MathBlock ) ]
164
141
| `Table _ -> []
165
142
166
143
let entries_of_item (x : Odoc_model.Fold.item ) =
167
- let html = Generator. html_of_entry x in
168
144
match x with
169
145
| CompilationUnit u -> (
170
146
match u.content with
171
- | Module m -> [ entry ~id: u.id ~doc: m.doc ~extra : Module ~html ]
147
+ | Module m -> [ entry ~id: u.id ~doc: m.doc ~kind : Module ]
172
148
| Pack _ -> [] )
173
149
| TypeDecl td ->
174
150
let txt = Render. text_of_typedecl td in
175
- let extra =
151
+ let kind =
176
152
TypeDecl
177
153
{
178
154
txt;
@@ -181,7 +157,7 @@ let entries_of_item (x : Odoc_model.Fold.item) =
181
157
representation = td.representation;
182
158
}
183
159
in
184
- let td_entry = entry ~id: td.id ~doc: td.doc ~extra ~html in
160
+ let td_entry = entry ~id: td.id ~doc: td.doc ~kind in
185
161
let subtype_entries =
186
162
match td.representation with
187
163
| None -> []
@@ -192,28 +168,28 @@ let entries_of_item (x : Odoc_model.Fold.item) =
192
168
| Some Extensible -> []
193
169
in
194
170
td_entry :: subtype_entries
195
- | Module m -> [ entry ~id: m.id ~doc: m.doc ~extra : Module ~html ]
171
+ | Module m -> [ entry ~id: m.id ~doc: m.doc ~kind : Module ]
196
172
| Value v ->
197
- let extra = Value { value = v.value; type_ = v.type_ } in
198
- [ entry ~id: v.id ~doc: v.doc ~extra ~html ]
173
+ let kind = Value { value = v.value; type_ = v.type_ } in
174
+ [ entry ~id: v.id ~doc: v.doc ~kind ]
199
175
| Exception exc ->
200
176
let res =
201
177
Option. value exc.res
202
178
~default: (TypeExpr. Constr (Odoc_model.Predefined. exn_path, [] ))
203
179
in
204
- let extra = Exception { args = exc.args; res } in
205
- [ entry ~id: exc.id ~doc: exc.doc ~extra ~html ]
180
+ let kind = Exception { args = exc.args; res } in
181
+ [ entry ~id: exc.id ~doc: exc.doc ~kind ]
206
182
| ClassType ct ->
207
- let extra = Class_type { virtual_ = ct.virtual_; params = ct.params } in
208
- [ entry ~id: ct.id ~doc: ct.doc ~extra ~html ]
183
+ let kind = Class_type { virtual_ = ct.virtual_; params = ct.params } in
184
+ [ entry ~id: ct.id ~doc: ct.doc ~kind ]
209
185
| Method m ->
210
- let extra =
186
+ let kind =
211
187
Method { virtual_ = m.virtual_; private_ = m.private_; type_ = m.type_ }
212
188
in
213
- [ entry ~id: m.id ~doc: m.doc ~extra ~html ]
189
+ [ entry ~id: m.id ~doc: m.doc ~kind ]
214
190
| Class cl ->
215
- let extra = Class { virtual_ = cl.virtual_; params = cl.params } in
216
- [ entry ~id: cl.id ~doc: cl.doc ~extra ~html ]
191
+ let kind = Class { virtual_ = cl.virtual_; params = cl.params } in
192
+ [ entry ~id: cl.id ~doc: cl.doc ~kind ]
217
193
| Extension te -> (
218
194
match te.constructors with
219
195
| [] -> []
@@ -222,21 +198,21 @@ let entries_of_item (x : Odoc_model.Fold.item) =
222
198
constructor for the url. Unfortunately, this breaks the uniqueness
223
199
of the ID in the search index... *)
224
200
let type_entry =
225
- let extra =
201
+ let kind =
226
202
TypeExtension
227
203
{
228
204
type_path = te.type_path;
229
205
type_params = te.type_params;
230
206
private_ = te.private_;
231
207
}
232
208
in
233
- entry ~id: c.id ~doc: te.doc ~extra ~html
209
+ entry ~id: c.id ~doc: te.doc ~kind
234
210
in
235
211
236
212
type_entry
237
213
:: List. map
238
214
(entry_of_extension_constructor te.type_path te.type_params)
239
215
te.constructors)
240
- | ModuleType mt -> [ entry ~id: mt.id ~doc: mt.doc ~extra : ModuleType ~html ]
216
+ | ModuleType mt -> [ entry ~id: mt.id ~doc: mt.doc ~kind : ModuleType ]
241
217
| Doc `Stop -> []
242
218
| Doc (`Docs d ) -> entries_of_docs d
0 commit comments