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

ocaml / odoc / 2860

26 Feb 2025 10:42AM UTC coverage: 73.427% (+0.06%) from 73.368%
2860

Pull #1321

github

web-flow
Merge 5bdc6f16b into b8c8d99e8
Pull Request #1321: Remove unneeded code and unify "utils" modules

56 of 77 new or added lines in 12 files covered. (72.73%)

1 existing line in 1 file now uncovered.

10257 of 13969 relevant lines covered (73.43%)

9954.81 hits per line

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

82.9
/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
      | Ok target ->
434✔
196
          let content = non_link_inline_elements ~surrounding:value content in
197
          Location.at location (`Reference (target, content))
434✔
198
      | 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
      Location.at location (`Code_block (lang_tag, content, outputs))
232
  | { value = `Math_block s; location } -> Location.at location (`Math_block s)
1✔
233
  | { value = `Verbatim _; _ } as element -> element
17✔
234
  | { value = `Modules modules; location } ->
9✔
235
      let modules =
236
        List.fold_left
237
          (fun acc { Location.value; location } ->
238
            match
30✔
239
              Error.raise_warnings (Reference.read_mod_longident location value)
30✔
240
            with
241
            | Ok r ->
30✔
242
                { Comment.module_reference = r; module_synopsis = None } :: acc
NEW
243
            | Error error ->
×
244
                Error.raise_warning error;
245
                acc)
×
246
          [] modules
247
        |> List.rev
9✔
248
      in
249
      Location.at location (`Modules modules)
9✔
250
  | { value = `List (kind, _syntax, items); location } ->
49✔
251
      `List (kind, List.map nestable_block_elements items)
49✔
252
      |> Location.at location
253
  | { value = `Table ((grid, align), (`Heavy | `Light)); location } ->
2✔
254
      let data =
255
        List.map
256
          (List.map (fun (cell, cell_type) ->
5✔
257
               (nestable_block_elements cell, cell_type)))
32✔
258
          grid
259
      in
260
      `Table { Comment.data; align } |> Location.at location
5✔
261
  | { value = `Media (_, { value = `Link href; _ }, content, m); location } ->
7✔
262
      `Media (`Link href, m, content) |> Location.at location
263
  | {
6✔
264
   value =
265
     `Media
266
       (kind, { value = `Reference href; location = href_location }, content, m);
267
   location;
268
  } -> (
269
      let fallback error =
270
        Error.raise_warning error;
×
271
        let placeholder =
×
272
          match kind with
273
          | `Simple -> `Code_span href
×
274
          | `With_text ->
×
275
              `Styled (`Emphasis, [ `Word content |> Location.at location ])
×
276
        in
277
        `Paragraph (inline_elements [ placeholder |> Location.at location ])
×
278
        |> Location.at location
279
      in
280
      match Error.raise_warnings (Reference.parse_asset href_location href) with
6✔
281
      | Ok target ->
6✔
282
          `Media (`Reference target, m, content) |> Location.at location
NEW
283
      | Error error -> fallback error)
×
284

285
and nestable_block_elements elements = List.map nestable_block_element elements
197✔
286

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

320
(* When the user does not give a section heading a label (anchor), we generate
321
   one from the text in the heading. This is the common case. This involves
322
   simply scanning the AST for words, lowercasing them, and joining them with
323
   hyphens.
324

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

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

374
let section_heading :
375
    status ->
376
    top_heading_level:int option ->
377
    Location.span ->
378
    [ `Heading of _ ] ->
379
    int option * Comment.block_element with_location =
380
 fun status ~top_heading_level location heading ->
381
  let (`Heading (level, label, content)) = heading in
309✔
382

383
  let text = inline_elements content in
384

385
  let heading_label_explicit, label =
309✔
386
    match label with
387
    | Some label -> (true, label)
49✔
388
    | None -> (false, generate_heading_label text)
260✔
389
  in
390
  let label =
391
    Paths.Identifier.Mk.label
392
      (status.parent_of_sections, Names.LabelName.make_std label)
309✔
393
  in
394

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

425
let validate_first_page_heading status ast_element =
426
  match status.parent_of_sections.iv with
585✔
427
  | `Page (_, name) | `LeafPage (_, name) -> (
73✔
428
      match ast_element with
429
      | { Location.value = `Heading (_, _, _); _ } -> ()
148✔
430
      | _invalid_ast_element ->
437✔
431
          let filename = Names.PageName.to_string name ^ ".mld" in
437✔
432
          Error.raise_warning (page_heading_required filename))
437✔
433
  | _not_a_page -> ()
×
434

435
let top_level_block_elements status ast_elements =
436
  let rec traverse :
3,832✔
437
      top_heading_level:int option ->
438
      Comment.block_element with_location list ->
439
      internal_tags_removed with_location list ->
440
      Comment.block_element with_location list =
441
   fun ~top_heading_level comment_elements_acc ast_elements ->
442
    match ast_elements with
5,281✔
443
    | [] -> List.rev comment_elements_acc
3,832✔
444
    | ast_element :: ast_elements -> (
1,449✔
445
        (* The first [ast_element] in pages must be a title or section heading. *)
446
        if top_heading_level = None then
447
          validate_first_page_heading status ast_element;
585✔
448

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

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

520
(** Append alerts at the end of the comment. Tags are favoured in case of alerts
521
    of the same name. *)
522
let append_alerts_to_comment alerts
523
    (comment : Comment.block_element with_location list) =
524
  let alerts =
3,832✔
525
    List.filter
526
      (fun alert ->
527
        let (`Tag alert) = alert.Location_.value in
8✔
528
        List.for_all
529
          (fun elem ->
530
            match (elem.Location_.value, alert) with
1✔
531
            | `Tag (`Deprecated _), `Alert ("deprecated", _) -> false
1✔
532
            | _ -> true)
×
533
          comment)
534
      alerts
535
  in
536
  comment @ (alerts :> Comment.elements)
3,832✔
537

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

592
let ast_to_comment ~internal_tags ~tags_allowed ~parent_of_sections
593
    (ast : Ast.t) alerts =
594
  Error.catch_warnings (fun () ->
3,832✔
595
      let status = { tags_allowed; parent_of_sections } in
3,832✔
596
      let ast, tags = strip_internal_tags ast in
597
      let elts =
3,832✔
598
        top_level_block_elements status ast |> append_alerts_to_comment alerts
3,832✔
599
      in
600
      (elts, handle_internal_tags tags internal_tags))
3,832✔
601

602
let parse_comment ~internal_tags ~tags_allowed ~containing_definition ~location
603
    ~text =
604
  Error.catch_warnings (fun () ->
716✔
605
      let ast =
716✔
606
        Odoc_parser.parse_comment ~location ~text |> Error.raise_parser_warnings
607
      in
608
      ast_to_comment ~internal_tags ~tags_allowed
716✔
609
        ~parent_of_sections:containing_definition ast []
610
      |> Error.raise_warnings)
716✔
611

612
let parse_reference text =
613
  let location =
37✔
614
    Location_.
615
      {
616
        file = "";
617
        start = { line = 0; column = 0 };
618
        end_ = { line = 0; column = String.length text };
37✔
619
      }
620
  in
621
  Reference.parse location text
622

623
let non_link_inline_element :
624
    context:string ->
625
    Odoc_parser.Ast.inline_element with_location list ->
626
    Comment.non_link_inline_element with_location list =
627
 fun ~context elements ->
628
  let surrounding = `Specific context in
×
629
  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