• Home
  • Features
  • Pricing
  • Docs
  • Announcements
  • Sign In

ocaml / odoc / 2891

05 Mar 2025 12:43PM UTC coverage: 73.363% (+0.01%) from 73.353%
2891

push

github

jonludlam
Add docstrings for distinguishing codeblock content and raw content

10262 of 13988 relevant lines covered (73.36%)

9948.16 hits per line

Source File
Press 'n' to go to next uncovered line, 'b' for previous

83.33
/src/model/semantics.ml
1
open Odoc_utils
2

3
module Location = Location_
4
module Ast = Odoc_parser.Ast
5

6
type internal_tags_removed =
7
  [ `Tag of Ast.ocamldoc_tag
8
  | `Heading of Ast.heading
9
  | `Media of
10
    Ast.reference_kind * Ast.media_href Ast.with_location * string * Ast.media
11
  | Ast.nestable_block_element ]
12
(** {!Ast.block_element} without internal tags. *)
13

14
type _ handle_internal_tags =
15
  | Expect_status :
16
      [ `Default | `Inline | `Open | `Closed ] handle_internal_tags
17
  | Expect_canonical : Reference.path option handle_internal_tags
18
  | Expect_none : unit handle_internal_tags
19
  | Expect_page_tags : Frontmatter.t handle_internal_tags
20

21
let describe_internal_tag = function
22
  | `Canonical _ -> "@canonical"
8✔
23
  | `Inline -> "@inline"
2✔
24
  | `Open -> "@open"
×
25
  | `Closed -> "@closed"
×
26
  | `Hidden -> "@hidden"
×
27
  | `Children_order _ -> "@children_order"
8✔
28
  | `Toc_status _ -> "@toc_status"
×
29
  | `Short_title _ -> "@short_title"
8✔
30
  | `Order_category _ -> "@order_category"
×
31

32
let warn_unexpected_tag { Location.value; location } =
33
  Error.raise_warning
10✔
34
  @@ Error.make "Unexpected tag '%s' at this location."
10✔
35
       (describe_internal_tag value)
10✔
36
       location
37

38
let warn_root_canonical location =
39
  Error.raise_warning
2✔
40
  @@ Error.make "Canonical paths must contain a dot, eg. X.Y." location
2✔
41

42
let rec find_tag ~filter = function
43
  | [] -> None
3,578✔
44
  | hd :: tl -> (
173✔
45
      match filter hd.Location.value with
46
      | Some x -> Some (x, hd.location)
163✔
47
      | None ->
10✔
48
          warn_unexpected_tag hd;
49
          find_tag ~filter tl)
10✔
50

51
let rec find_tags acc ~filter = function
52
  | [] -> List.rev acc
91✔
53
  | hd :: tl -> (
16✔
54
      match filter hd.Location.value with
55
      | Some x -> find_tags ((x, hd.location) :: acc) ~filter tl
16✔
56
      | None ->
×
57
          warn_unexpected_tag hd;
58
          find_tags acc ~filter tl)
×
59

60
(* Errors *)
61
let invalid_raw_markup_target : string -> Location.span -> Error.t =
62
  Error.make ~suggestion:"try '{%html:...%}'."
1,220✔
63
    "'{%%%s:': bad raw markup target."
64

65
let default_raw_markup_target_not_supported : Location.span -> Error.t =
66
  Error.make ~suggestion:"try '{%html:...%}'."
1,220✔
67
    "'{%%...%%}' (raw markup) needs a target language."
68

69
let bad_heading_level : int -> Location.span -> Error.t =
70
  Error.make "'%d': bad heading level (0-5 allowed)."
1,220✔
71

72
let heading_level_should_be_lower_than_top_level :
73
    int -> int -> Location.span -> Error.t =
74
 fun this_heading_level top_heading_level ->
75
  Error.make "%s: heading level should be lower than top heading level '%d'."
10✔
76
    (Printf.sprintf "'{%i'" this_heading_level)
10✔
77
    top_heading_level
78

79
let page_heading_required : string -> Error.t =
80
  Error.filename_only "Pages (.mld files) should start with a heading."
1,220✔
81

82
let tags_not_allowed : Location.span -> Error.t =
83
  Error.make "Tags are not allowed in pages."
1,220✔
84

85
let not_allowed :
86
    ?suggestion:string ->
87
    what:string ->
88
    in_what:string ->
89
    Location.span ->
90
    Error.t =
91
 fun ?suggestion ~what ~in_what ->
92
  Error.make ?suggestion "%s is not allowed in %s."
×
93
    (Astring.String.Ascii.capitalize what)
×
94
    in_what
95

96
let describe_element = function
97
  | `Reference (`Simple, _, _) -> "'{!...}' (cross-reference)"
×
98
  | `Reference (`With_text, _, _) -> "'{{!...} ...}' (cross-reference)"
×
99
  | `Link (_, _) -> "'{{:...} ...}' (external link)"
×
100
  | `Heading (level, _, _) ->
×
101
      Printf.sprintf "'{%i ...}' (section heading)" level
102
  | `Specific s -> s
×
103

104
(* End of errors *)
105

106
type 'a with_location = 'a Location.with_location
107

108
type ast_leaf_inline_element =
109
  [ `Space of string
110
  | `Word of string
111
  | `Code_span of string
112
  | `Math_span of string
113
  | `Raw_markup of string option * string ]
114

115
type sections_allowed = [ `All | `No_titles | `None ]
116

117
type alerts =
118
  [ `Tag of [ `Alert of string * string option ] ] Location_.with_location list
119

120
type status = {
121
  tags_allowed : bool;
122
  parent_of_sections : Paths.Identifier.LabelParent.t;
123
}
124

125
let leaf_inline_element :
126
    ast_leaf_inline_element with_location ->
127
    Comment.leaf_inline_element with_location =
128
 fun element ->
129
  match element with
7,842✔
130
  | { value = `Word _ | `Code_span _ | `Math_span _; _ } as element -> element
3✔
131
  | { value = `Space _; _ } -> Location.same element `Space
3,318✔
132
  | { value = `Raw_markup (target, s); location } -> (
24✔
133
      match target with
134
      | Some invalid_target
21✔
135
        when String.trim invalid_target = ""
3✔
136
             || String.exists
18✔
137
                  (function '%' | '}' -> true | _ -> false)
1✔
138
                  invalid_target ->
4✔
139
          Error.raise_warning
7✔
140
            (invalid_raw_markup_target invalid_target location);
7✔
141

142
          Location.same element (`Code_span s)
7✔
143
      | None ->
3✔
144
          Error.raise_warning (default_raw_markup_target_not_supported location);
3✔
145
          Location.same element (`Code_span s)
3✔
146
      | Some target -> Location.same element (`Raw_markup (target, s)))
14✔
147

148
type surrounding =
149
  [ `Link of
150
    string * Odoc_parser.Ast.inline_element Location_.with_location list
151
  | `Reference of
152
    [ `Simple | `With_text ]
153
    * string Location_.with_location
154
    * Odoc_parser.Ast.inline_element Location_.with_location list
155
  | `Specific of string ]
156

157
let rec non_link_inline_element :
158
    surrounding:surrounding ->
159
    Odoc_parser.Ast.inline_element with_location ->
160
    Comment.non_link_inline_element with_location =
161
 fun ~surrounding element ->
162
  match element with
112✔
163
  | { value = #ast_leaf_inline_element; _ } as element ->
100✔
164
      (leaf_inline_element element
165
        :> Comment.non_link_inline_element with_location)
166
  | { value = `Styled (style, content); _ } ->
12✔
167
      `Styled (style, non_link_inline_elements ~surrounding content)
12✔
168
      |> Location.same element
169
  | ( { value = `Reference (_, _, content); _ }
×
170
    | { value = `Link (_, content); _ } ) as element ->
×
171
      not_allowed
172
        ~what:(describe_element element.value)
×
173
        ~in_what:(describe_element surrounding)
×
174
        element.location
175
      |> Error.raise_warning;
×
176

177
      `Styled (`Emphasis, non_link_inline_elements ~surrounding content)
×
178
      |> Location.same element
179

180
and non_link_inline_elements ~surrounding elements =
181
  List.map (non_link_inline_element ~surrounding) elements
467✔
182

183
let rec inline_element :
184
    Odoc_parser.Ast.inline_element with_location ->
185
    Comment.inline_element with_location =
186
 fun element ->
187
  match element with
8,453✔
188
  | { value = #ast_leaf_inline_element; _ } as element ->
7,742✔
189
      (leaf_inline_element element :> Comment.inline_element with_location)
190
  | { value = `Styled (style, content); location } ->
67✔
191
      `Styled (style, inline_elements content) |> Location.at location
67✔
192
  | { value = `Reference (kind, target, content) as value; location } -> (
623✔
193
      let { Location.value = target; location = target_location } = target in
194
      match Error.raise_warnings (Reference.parse target_location target) with
623✔
195
      | Result.Ok target ->
434✔
196
          let content = non_link_inline_elements ~surrounding:value content in
197
          Location.at location (`Reference (target, content))
434✔
198
      | Result.Error error ->
189✔
199
          Error.raise_warning error;
200
          let placeholder =
189✔
201
            match kind with
202
            | `Simple -> `Code_span target
188✔
203
            | `With_text -> `Styled (`Emphasis, content)
1✔
204
          in
205
          inline_element (Location.at location placeholder))
189✔
206
  | { value = `Link (target, content) as value; location } ->
21✔
207
      `Link (target, non_link_inline_elements ~surrounding:value content)
21✔
208
      |> Location.at location
209

210
and inline_elements elements = List.map inline_element elements
1,534✔
211

212
let rec nestable_block_element :
213
    Odoc_parser.Ast.nestable_block_element with_location ->
214
    Comment.nestable_block_element with_location =
215
 fun element ->
216
  match element with
1,269✔
217
  | { value = `Paragraph content; location } ->
1,158✔
218
      Location.at location (`Paragraph (inline_elements content))
1,158✔
219
  | { value = `Code_block { meta; delimiter = _; content; output }; location }
17✔
220
    ->
221
      let lang_tag =
222
        match meta with
223
        | Some { language = { Location.value; _ }; _ } -> Some value
×
224
        | None -> None
17✔
225
      in
226
      let outputs =
227
        match output with
228
        | None -> None
17✔
229
        | Some l -> Some (List.map nestable_block_element l)
×
230
      in
231
      let trimmed_content, warnings =
232
        Odoc_parser.codeblock_content location content.value
233
      in
234
      let warnings = List.map Error.t_of_parser_t warnings in
17✔
235
      List.iter (Error.raise_warning ~non_fatal:true) warnings;
17✔
236
      let content = Location.at content.location trimmed_content in
17✔
237
      Location.at location (`Code_block (lang_tag, content, outputs))
17✔
238
  | { value = `Math_block s; location } -> Location.at location (`Math_block s)
1✔
239
  | { value = `Verbatim v; location } ->
17✔
240
      let v, warnings = Odoc_parser.codeblock_content location v in
241
      let warnings = List.map Error.t_of_parser_t warnings in
17✔
242
      List.iter (Error.raise_warning ~non_fatal:true) warnings;
17✔
243
      Location.at location (`Verbatim v)
17✔
244
  | { value = `Modules modules; location } ->
9✔
245
      let modules =
246
        List.fold_left
247
          (fun acc { Location.value; location } ->
248
            match
30✔
249
              Error.raise_warnings (Reference.read_mod_longident location value)
30✔
250
            with
251
            | Result.Ok r ->
30✔
252
                { Comment.module_reference = r; module_synopsis = None } :: acc
253
            | Result.Error error ->
×
254
                Error.raise_warning error;
255
                acc)
×
256
          [] modules
257
        |> List.rev
9✔
258
      in
259
      Location.at location (`Modules modules)
9✔
260
  | { value = `List (kind, _syntax, items); location } ->
49✔
261
      `List (kind, List.map nestable_block_elements items)
49✔
262
      |> Location.at location
263
  | { value = `Table ((grid, align), (`Heavy | `Light)); location } ->
2✔
264
      let data =
265
        List.map
266
          (List.map (fun (cell, cell_type) ->
5✔
267
               (nestable_block_elements cell, cell_type)))
32✔
268
          grid
269
      in
270
      `Table { Comment.data; align } |> Location.at location
5✔
271
  | { value = `Media (_, { value = `Link href; _ }, content, m); location } ->
7✔
272
      `Media (`Link href, m, content) |> Location.at location
273
  | {
6✔
274
   value =
275
     `Media
276
       (kind, { value = `Reference href; location = href_location }, content, m);
277
   location;
278
  } -> (
279
      let fallback error =
280
        Error.raise_warning error;
×
281
        let placeholder =
×
282
          match kind with
283
          | `Simple -> `Code_span href
×
284
          | `With_text ->
×
285
              `Styled (`Emphasis, [ `Word content |> Location.at location ])
×
286
        in
287
        `Paragraph (inline_elements [ placeholder |> Location.at location ])
×
288
        |> Location.at location
289
      in
290
      match Error.raise_warnings (Reference.parse_asset href_location href) with
6✔
291
      | Result.Ok target ->
6✔
292
          `Media (`Reference target, m, content) |> Location.at location
293
      | Result.Error error -> fallback error)
×
294

295
and nestable_block_elements elements = List.map nestable_block_element elements
197✔
296

297
let tag :
298
    location:Location.span ->
299
    status ->
300
    Ast.ocamldoc_tag ->
301
    ( Comment.block_element with_location,
302
      internal_tags_removed with_location )
303
    Result.result =
304
 fun ~location status tag ->
305
  if not status.tags_allowed then
74✔
306
    (* Trigger a warning but do not remove the tag. Avoid turning tags into
307
       text that would render the same. *)
308
    Error.raise_warning (tags_not_allowed location);
1✔
309
  let ok t = Result.Ok (Location.at location (`Tag t)) in
74✔
310
  match tag with
311
  | (`Author _ | `Since _ | `Version _) as tag -> ok tag
2✔
312
  | `Deprecated content -> ok (`Deprecated (nestable_block_elements content))
4✔
313
  | `Param (name, content) ->
5✔
314
      ok (`Param (name, nestable_block_elements content))
5✔
315
  | `Raise (name, content) -> (
8✔
316
      match Error.raise_warnings (Reference.parse location name) with
8✔
317
      (* TODO: location for just name *)
318
      | Result.Ok target ->
4✔
319
          ok (`Raise (`Reference (target, []), nestable_block_elements content))
4✔
320
      | Result.Error error ->
4✔
321
          Error.raise_warning error;
322
          let placeholder = `Code_span name in
4✔
323
          ok (`Raise (placeholder, nestable_block_elements content)))
4✔
324
  | `Return content -> ok (`Return (nestable_block_elements content))
3✔
325
  | `See (kind, target, content) ->
7✔
326
      ok (`See (kind, target, nestable_block_elements content))
7✔
327
  | `Before (version, content) ->
6✔
328
      ok (`Before (version, nestable_block_elements content))
6✔
329

330
(* When the user does not give a section heading a label (anchor), we generate
331
   one from the text in the heading. This is the common case. This involves
332
   simply scanning the AST for words, lowercasing them, and joining them with
333
   hyphens.
334

335
   This must be done in the parser (i.e. early, not at HTML/other output
336
   generation time), so that the cross-referencer can see these anchors. *)
337
let generate_heading_label : Comment.inline_element with_location list -> string
338
    =
339
 fun content ->
340
  (* Code spans can contain spaces, so we need to replace them with hyphens. We
341
     also lowercase all the letters, for consistency with the rest of this
342
     procedure. *)
343
  let replace_spaces_with_hyphens_and_lowercase s =
260✔
344
    let result = Bytes.create (String.length s) in
12✔
345
    s
12✔
346
    |> String.iteri (fun index c ->
347
           let c =
65✔
348
             match c with
349
             | ' ' | '\t' | '\r' | '\n' -> '-'
×
350
             | _ -> Astring.Char.Ascii.lowercase c
56✔
351
           in
352
           Bytes.set result index c);
353
    Bytes.unsafe_to_string result
12✔
354
  in
355

356
  let strip_locs li = List.map (fun ele -> ele.Location.value) li in
11✔
357
  (* Perhaps this should be done using a [Buffer.t]; we can switch to that as
358
     needed. *)
359
  let rec scan_inline_elements anchor = function
360
    | [] -> anchor
271✔
361
    | element :: more ->
630✔
362
        let anchor =
363
          match (element : Comment.inline_element) with
364
          | `Space -> anchor ^ "-"
183✔
365
          | `Word w -> anchor ^ Astring.String.Ascii.lowercase w
424✔
366
          | `Code_span c | `Math_span c ->
×
367
              anchor ^ replace_spaces_with_hyphens_and_lowercase c
12✔
368
          | `Raw_markup _ ->
×
369
              (* TODO Perhaps having raw markup in a section heading should be an
370
                 error? *)
371
              anchor
372
          | `Styled (_, content) ->
5✔
373
              content |> strip_locs |> scan_inline_elements anchor
5✔
374
          | `Reference (_, content) | `Link (_, content) ->
3✔
375
              content |> strip_locs
376
              |> List.map (fun (ele : Comment.non_link_inline_element) ->
6✔
377
                     (ele :> Comment.inline_element))
6✔
378
              |> scan_inline_elements anchor
6✔
379
        in
380
        scan_inline_elements anchor more
381
  in
382
  content |> List.map (fun ele -> ele.Location.value) |> scan_inline_elements ""
260✔
383

384
let section_heading :
385
    status ->
386
    top_heading_level:int option ->
387
    Location.span ->
388
    [ `Heading of _ ] ->
389
    int option * Comment.block_element with_location =
390
 fun status ~top_heading_level location heading ->
391
  let (`Heading (level, label, content)) = heading in
309✔
392

393
  let text = inline_elements content in
394

395
  let heading_label_explicit, label =
309✔
396
    match label with
397
    | Some label -> (true, label)
49✔
398
    | None -> (false, generate_heading_label text)
260✔
399
  in
400
  let label =
401
    Paths.Identifier.Mk.label
402
      (status.parent_of_sections, Names.LabelName.make_std label)
309✔
403
  in
404

405
  let mk_heading heading_level =
309✔
406
    let attrs = { Comment.heading_level; heading_label_explicit } in
309✔
407
    let element = Location.at location (`Heading (attrs, label, text)) in
408
    let top_heading_level =
309✔
409
      match top_heading_level with None -> Some level | some -> some
148✔
410
    in
411
    (top_heading_level, element)
412
  in
413
  let level' =
414
    match level with
415
    | 0 -> `Title
102✔
416
    | 1 -> `Section
113✔
417
    | 2 -> `Subsection
59✔
418
    | 3 -> `Subsubsection
19✔
419
    | 4 -> `Paragraph
3✔
420
    | 5 -> `Subparagraph
2✔
421
    | _ ->
11✔
422
        Error.raise_warning (bad_heading_level level location);
11✔
423
        (* Implicitly promote to level-5. *)
424
        `Subparagraph
11✔
425
  in
426
  let () =
427
    match top_heading_level with
428
    | Some top_level when level <= top_level && level <= 5 ->
11✔
429
        Error.raise_warning
10✔
430
          (heading_level_should_be_lower_than_top_level level top_level location)
10✔
431
    | _ -> ()
299✔
432
  in
433
  mk_heading level'
434

435
let validate_first_page_heading status ast_element =
436
  match status.parent_of_sections.iv with
585✔
437
  | `Page (_, name) | `LeafPage (_, name) -> (
73✔
438
      match ast_element with
439
      | { Location.value = `Heading (_, _, _); _ } -> ()
148✔
440
      | _invalid_ast_element ->
437✔
441
          let filename = Names.PageName.to_string name ^ ".mld" in
437✔
442
          Error.raise_warning (page_heading_required filename))
437✔
443
  | _not_a_page -> ()
×
444

445
let top_level_block_elements status ast_elements =
446
  let rec traverse :
3,832✔
447
      top_heading_level:int option ->
448
      Comment.block_element with_location list ->
449
      internal_tags_removed with_location list ->
450
      Comment.block_element with_location list =
451
   fun ~top_heading_level comment_elements_acc ast_elements ->
452
    match ast_elements with
5,281✔
453
    | [] -> List.rev comment_elements_acc
3,832✔
454
    | ast_element :: ast_elements -> (
1,449✔
455
        (* The first [ast_element] in pages must be a title or section heading. *)
456
        if top_heading_level = None then
457
          validate_first_page_heading status ast_element;
585✔
458

459
        match ast_element with
1,449✔
460
        | { value = #Odoc_parser.Ast.nestable_block_element; _ } as element ->
1,066✔
461
            let element = nestable_block_element element in
462
            let element = (element :> Comment.block_element with_location) in
1,066✔
463
            traverse ~top_heading_level
464
              (element :: comment_elements_acc)
465
              ast_elements
466
        | { value = `Tag the_tag; location } -> (
74✔
467
            match tag ~location status the_tag with
468
            | Result.Ok element ->
74✔
469
                traverse ~top_heading_level
470
                  (element :: comment_elements_acc)
471
                  ast_elements
472
            | Result.Error placeholder ->
×
473
                traverse ~top_heading_level comment_elements_acc
474
                  (placeholder :: ast_elements))
475
        | { value = `Heading _ as heading; _ } ->
309✔
476
            let top_heading_level, element =
477
              section_heading status ~top_heading_level
478
                ast_element.Location.location heading
479
            in
480
            traverse ~top_heading_level
309✔
481
              (element :: comment_elements_acc)
482
              ast_elements)
483
  in
484
  let top_heading_level =
485
    (* Non-page documents have a generated title. *)
486
    match status.parent_of_sections.iv with
487
    | `Page _ | `LeafPage _ -> None
73✔
488
    | _parent_with_generated_title -> Some 0
3,263✔
489
  in
490
  traverse ~top_heading_level [] ast_elements
491

492
let strip_internal_tags ast : internal_tags_removed with_location list * _ =
493
  let rec loop ~start tags ast' = function
3,832✔
494
    | ({ Location.value = `Tag (#Ast.internal_tag as tag); _ } as wloc) :: tl
194✔
495
      -> (
496
        let next tag =
497
          loop ~start ({ wloc with value = tag } :: tags) ast' tl
192✔
498
        in
499
        match tag with
500
        | (`Inline | `Open | `Closed | `Hidden) as tag -> next tag
×
501
        | ( `Children_order _ | `Short_title _ | `Toc_status _
×
502
          | `Order_category _ ) as tag ->
×
503
            let tag_name = describe_internal_tag tag in
504
            if not start then
16✔
505
              Error.raise_warning
1✔
506
                (Error.make "%s tag has to be before any content" tag_name
1✔
507
                   wloc.location);
508
            next tag
16✔
509
        | `Canonical { Location.value = s; location = r_location } -> (
160✔
510
            match
511
              Error.raise_warnings (Reference.read_path_longident r_location s)
160✔
512
            with
513
            | Result.Ok path -> next (`Canonical path)
158✔
514
            | Result.Error e ->
2✔
515
                Error.raise_warning e;
516
                loop ~start tags ast' tl))
2✔
517
    | ({
1,449✔
518
         value =
519
           ( `Tag #Ast.ocamldoc_tag
74✔
520
           | `Heading _ | `Media _
6✔
521
           | #Ast.nestable_block_element );
1,060✔
522
         _;
523
       } as hd)
524
      :: tl ->
525
        loop ~start:false tags (hd :: ast') tl
526
    | [] -> (List.rev ast', List.rev tags)
3,832✔
527
  in
528
  loop ~start:true [] [] ast
529

530
(** Append alerts at the end of the comment. Tags are favoured in case of alerts
531
    of the same name. *)
532
let append_alerts_to_comment alerts
533
    (comment : Comment.block_element with_location list) =
534
  let alerts =
3,832✔
535
    List.filter
536
      (fun alert ->
537
        let (`Tag alert) = alert.Location_.value in
8✔
538
        List.for_all
539
          (fun elem ->
540
            match (elem.Location_.value, alert) with
1✔
541
            | `Tag (`Deprecated _), `Alert ("deprecated", _) -> false
1✔
542
            | _ -> true)
×
543
          comment)
544
      alerts
545
  in
546
  comment @ (alerts :> Comment.elements)
3,832✔
547

548
let handle_internal_tags (type a) tags : a handle_internal_tags -> a = function
3,832✔
549
  | Expect_status -> (
90✔
550
      match
551
        find_tag
552
          ~filter:(function
553
            | (`Inline | `Open | `Closed) as t -> Some t | _ -> None)
1✔
554
          tags
555
      with
556
      | Some (status, _) -> status
13✔
557
      | None -> `Default)
77✔
558
  | Expect_canonical -> (
2,207✔
559
      match
560
        find_tag ~filter:(function `Canonical p -> Some p | _ -> None) tags
1✔
561
      with
562
      | Some (`Root _, location) ->
2✔
563
          warn_root_canonical location;
564
          None
2✔
565
      | Some ((`Dot _ as p), _) -> Some p
148✔
566
      | None -> None)
2,057✔
567
  | Expect_page_tags ->
91✔
568
      let unparsed_lines =
569
        find_tags []
570
          ~filter:(function
571
            | ( `Children_order _ | `Toc_status _ | `Short_title _
×
572
              | `Order_category _ ) as p ->
×
573
                Some p
574
            | _ -> None)
×
575
          tags
576
      in
577
      let lines =
91✔
578
        let do_ parse loc els =
579
          let els = nestable_block_elements els in
16✔
580
          match parse loc els with
16✔
581
          | Ok res -> Some res
13✔
582
          | Error e ->
3✔
583
              Error.raise_warning e;
584
              None
3✔
585
        in
586
        List.filter_map
91✔
587
          (function
588
            | `Children_order co, loc ->
8✔
589
                do_ Frontmatter.parse_children_order loc co
590
            | `Toc_status co, loc -> do_ Frontmatter.parse_toc_status loc co
×
591
            | `Short_title t, loc -> do_ Frontmatter.parse_short_title loc t
8✔
592
            | `Order_category t, loc ->
×
593
                do_ Frontmatter.parse_order_category loc t)
594
          unparsed_lines
595
      in
596
      Frontmatter.of_lines lines |> Error.raise_warnings
91✔
597
  | Expect_none ->
1,444✔
598
      (* Will raise warnings. *)
599
      ignore (find_tag ~filter:(fun _ -> None) tags);
8✔
600
      ()
601

602
let ast_to_comment ~internal_tags ~tags_allowed ~parent_of_sections
603
    (ast : Ast.t) alerts =
604
  Error.catch_warnings (fun () ->
3,832✔
605
      let status = { tags_allowed; parent_of_sections } in
3,832✔
606
      let ast, tags = strip_internal_tags ast in
607
      let elts =
3,832✔
608
        top_level_block_elements status ast |> append_alerts_to_comment alerts
3,832✔
609
      in
610
      (elts, handle_internal_tags tags internal_tags))
3,832✔
611

612
let parse_comment ~internal_tags ~tags_allowed ~containing_definition ~location
613
    ~text =
614
  Error.catch_warnings (fun () ->
716✔
615
      let ast =
716✔
616
        Odoc_parser.parse_comment ~location ~text |> Error.raise_parser_warnings
617
      in
618
      ast_to_comment ~internal_tags ~tags_allowed
716✔
619
        ~parent_of_sections:containing_definition ast []
620
      |> Error.raise_warnings)
716✔
621

622
let parse_reference text =
623
  let location =
37✔
624
    Location_.
625
      {
626
        file = "";
627
        start = { line = 0; column = 0 };
628
        end_ = { line = 0; column = String.length text };
37✔
629
      }
630
  in
631
  Reference.parse location text
632

633
let non_link_inline_element :
634
    context:string ->
635
    Odoc_parser.Ast.inline_element with_location list ->
636
    Comment.non_link_inline_element with_location list =
637
 fun ~context elements ->
638
  let surrounding = `Specific context in
×
639
  non_link_inline_elements ~surrounding elements
STATUS · Troubleshooting · Open an Issue · Sales · Support · CAREERS · ENTERPRISE · START FREE · SCHEDULE DEMO
ANNOUNCEMENTS · TWITTER · TOS & SLA · Supported CI Services · What's a CI service? · Automated Testing

© 2026 Coveralls, Inc