@@ -191,17 +191,16 @@ type surrounding =
191
191
* Odoc_parser.Ast .inline_element Location_ .with_location list ]
192
192
193
193
let rec non_link_inline_element :
194
- status ->
195
194
surrounding :surrounding ->
196
195
Odoc_parser.Ast. inline_element with_location ->
197
196
Comment. non_link_inline_element with_location =
198
- fun status ~surrounding element ->
197
+ fun ~surrounding element ->
199
198
match element with
200
199
| { value = #ast_leaf_inline_element ; _ } as element ->
201
200
(leaf_inline_element element
202
201
:> Comment. non_link_inline_element with_location)
203
202
| { value = `Styled (style , content ); _ } ->
204
- `Styled (style, non_link_inline_elements status ~surrounding content)
203
+ `Styled (style, non_link_inline_elements ~surrounding content)
205
204
|> Location. same element
206
205
| ( { value = `Reference (_, _, content); _ }
207
206
| { value = `Link (_ , content ); _ } ) as element ->
@@ -211,29 +210,26 @@ let rec non_link_inline_element :
211
210
element.location
212
211
|> Error. raise_warning;
213
212
214
- `Styled (`Emphasis , non_link_inline_elements status ~surrounding content)
213
+ `Styled (`Emphasis , non_link_inline_elements ~surrounding content)
215
214
|> Location. same element
216
215
217
- and non_link_inline_elements status ~surrounding elements =
218
- List. map (non_link_inline_element status ~surrounding ) elements
216
+ and non_link_inline_elements ~surrounding elements =
217
+ List. map (non_link_inline_element ~surrounding ) elements
219
218
220
219
let rec inline_element :
221
- status ->
222
220
Odoc_parser.Ast. inline_element with_location ->
223
221
Comment. inline_element with_location =
224
- fun status element ->
222
+ fun element ->
225
223
match element with
226
224
| { value = #ast_leaf_inline_element ; _ } as element ->
227
225
(leaf_inline_element element :> Comment.inline_element with_location )
228
226
| { value = `Styled (style , content ); location } ->
229
- `Styled (style, inline_elements status content) |> Location. at location
227
+ `Styled (style, inline_elements content) |> Location. at location
230
228
| { value = `Reference (kind , target , content ) as value ; location } -> (
231
229
let { Location. value = target; location = target_location } = target in
232
230
match Error. raise_warnings (Reference. parse target_location target) with
233
231
| Result. Ok target ->
234
- let content =
235
- non_link_inline_elements status ~surrounding: value content
236
- in
232
+ let content = non_link_inline_elements ~surrounding: value content in
237
233
Location. at location (`Reference (target, content))
238
234
| Result. Error error ->
239
235
Error. raise_warning error;
@@ -242,21 +238,20 @@ let rec inline_element :
242
238
| `Simple -> `Code_span target
243
239
| `With_text -> `Styled (`Emphasis , content)
244
240
in
245
- inline_element status (Location. at location placeholder))
241
+ inline_element (Location. at location placeholder))
246
242
| { value = `Link (target , content ) as value ; location } ->
247
- `Link (target, non_link_inline_elements status ~surrounding: value content)
243
+ `Link (target, non_link_inline_elements ~surrounding: value content)
248
244
|> Location. at location
249
245
250
- and inline_elements status elements = List. map ( inline_element status) elements
246
+ and inline_elements elements = List. map inline_element elements
251
247
252
248
let rec nestable_block_element :
253
- status ->
254
249
Odoc_parser.Ast. nestable_block_element with_location ->
255
250
Comment. nestable_block_element with_location =
256
- fun status element ->
251
+ fun element ->
257
252
match element with
258
253
| { value = `Paragraph content ; location } ->
259
- Location. at location (`Paragraph (inline_elements status content))
254
+ Location. at location (`Paragraph (inline_elements content))
260
255
| { value = `Code_block { meta; delimiter = _; content; output }; location }
261
256
->
262
257
let lang_tag =
@@ -267,7 +262,7 @@ let rec nestable_block_element :
267
262
let outputs =
268
263
match output with
269
264
| None -> None
270
- | Some l -> Some (List. map ( nestable_block_element status) l)
265
+ | Some l -> Some (List. map nestable_block_element l)
271
266
in
272
267
Location. at location (`Code_block (lang_tag, content, outputs))
273
268
| { value = `Math_block s ; location } -> Location. at location (`Math_block s)
@@ -289,13 +284,13 @@ let rec nestable_block_element :
289
284
in
290
285
Location. at location (`Modules modules)
291
286
| { value = `List (kind , _syntax , items ); location } ->
292
- `List (kind, List. map ( nestable_block_elements status) items)
287
+ `List (kind, List. map nestable_block_elements items)
293
288
|> Location. at location
294
289
| { value = `Table ((grid , align ), (`Heavy | `Light )); location } ->
295
290
let data =
296
291
List. map
297
292
(List. map (fun (cell , cell_type ) ->
298
- (nestable_block_elements status cell, cell_type)))
293
+ (nestable_block_elements cell, cell_type)))
299
294
grid
300
295
in
301
296
`Table { Comment. data; align } |> Location. at location
@@ -315,17 +310,15 @@ let rec nestable_block_element :
315
310
| `With_text ->
316
311
`Styled (`Emphasis , [ `Word content |> Location. at location ])
317
312
in
318
- `Paragraph
319
- (inline_elements status [ placeholder |> Location. at location ])
313
+ `Paragraph (inline_elements [ placeholder |> Location. at location ])
320
314
|> Location. at location
321
315
in
322
316
match Error. raise_warnings (Reference. parse_asset href_location href) with
323
317
| Result. Ok target ->
324
318
`Media (`Reference target, m, content) |> Location. at location
325
319
| Result. Error error -> fallback error)
326
320
327
- and nestable_block_elements status elements =
328
- List. map (nestable_block_element status) elements
321
+ and nestable_block_elements elements = List. map nestable_block_element elements
329
322
330
323
let tag :
331
324
location :Location. span ->
@@ -342,26 +335,23 @@ let tag :
342
335
let ok t = Result. Ok (Location. at location (`Tag t)) in
343
336
match tag with
344
337
| (`Author _ | `Since _ | `Version _ ) as tag -> ok tag
345
- | `Deprecated content ->
346
- ok (`Deprecated (nestable_block_elements status content))
338
+ | `Deprecated content -> ok (`Deprecated (nestable_block_elements content))
347
339
| `Param (name , content ) ->
348
- ok (`Param (name, nestable_block_elements status content))
340
+ ok (`Param (name, nestable_block_elements content))
349
341
| `Raise (name , content ) -> (
350
342
match Error. raise_warnings (Reference. parse location name) with
351
343
(* TODO: location for just name * )
352
344
| Result. Ok target ->
353
- ok
354
- (`Raise
355
- (`Reference (target, [] ), nestable_block_elements status content))
345
+ ok (`Raise (`Reference (target, [] ), nestable_block_elements content))
356
346
| Result. Error error ->
357
347
Error. raise_warning error;
358
348
let placeholder = `Code_span name in
359
- ok (`Raise (placeholder, nestable_block_elements status content)))
360
- | `Return content -> ok (`Return (nestable_block_elements status content))
349
+ ok (`Raise (placeholder, nestable_block_elements content)))
350
+ | `Return content -> ok (`Return (nestable_block_elements content))
361
351
| `See (kind , target , content ) ->
362
- ok (`See (kind, target, nestable_block_elements status content))
352
+ ok (`See (kind, target, nestable_block_elements content))
363
353
| `Before (version , content ) ->
364
- ok (`Before (version, nestable_block_elements status content))
354
+ ok (`Before (version, nestable_block_elements content))
365
355
366
356
(* When the user does not give a section heading a label (anchor), we generate
367
357
one from the text in the heading. This is the common case. This involves
@@ -426,7 +416,7 @@ let section_heading :
426
416
fun status ~top_heading_level location heading ->
427
417
let (`Heading (level, label, content)) = heading in
428
418
429
- let text = inline_elements status content in
419
+ let text = inline_elements content in
430
420
431
421
let heading_label_explicit, label =
432
422
match label with
@@ -494,7 +484,7 @@ let top_level_block_elements status ast_elements =
494
484
495
485
match ast_element with
496
486
| { value = #Odoc_parser.Ast. nestable_block_element ; _ } as element ->
497
- let element = nestable_block_element status element in
487
+ let element = nestable_block_element element in
498
488
let element = (element :> Comment.block_element with_location ) in
499
489
traverse ~top_heading_level
500
490
(element :: comment_elements_acc)
0 commit comments