@@ -25,6 +25,7 @@ let describe_internal_tag = function
25
25
| `Closed -> " @closed"
26
26
| `Hidden -> " @hidden"
27
27
| `Children_order _ -> " @children_order"
28
+ | `Short_title _ -> " @short_title"
28
29
29
30
let warn_unexpected_tag { Location. value; location } =
30
31
Error. raise_warning
@@ -54,48 +55,6 @@ let rec find_tags acc ~filter = function
54
55
warn_unexpected_tag hd;
55
56
find_tags acc ~filter tl)
56
57
57
- let handle_internal_tags (type a ) tags : a handle_internal_tags -> a = function
58
- | Expect_status -> (
59
- match
60
- find_tag
61
- ~filter: (function
62
- | (`Inline | `Open | `Closed ) as t -> Some t | _ -> None )
63
- tags
64
- with
65
- | Some (status , _ ) -> status
66
- | None -> `Default )
67
- | Expect_canonical -> (
68
- match
69
- find_tag ~filter: (function `Canonical p -> Some p | _ -> None ) tags
70
- with
71
- | Some (`Root _ , location ) ->
72
- warn_root_canonical location;
73
- None
74
- | Some ((`Dot _ as p ), _ ) -> Some p
75
- | None -> None )
76
- | Expect_page_tags ->
77
- let unparsed_lines =
78
- find_tags []
79
- ~filter: (function `Children_order _ as p -> Some p | _ -> None )
80
- tags
81
- in
82
- let lines =
83
- List. filter_map
84
- (function
85
- | `Children_order co , loc -> (
86
- match Frontmatter. parse_children_order loc co with
87
- | Ok co -> Some co
88
- | Error e ->
89
- Error. raise_warning e;
90
- None ))
91
- unparsed_lines
92
- in
93
- Frontmatter. of_lines lines |> Error. raise_warnings
94
- | Expect_none ->
95
- (* Will raise warnings. *)
96
- ignore (find_tag ~filter: (fun _ -> None ) tags);
97
- ()
98
-
99
58
(* Errors *)
100
59
let invalid_raw_markup_target : string -> Location.span -> Error.t =
101
60
Error. make ~suggestion: " try '{%html:...%}'."
@@ -138,6 +97,7 @@ let describe_element = function
138
97
| `Link (_ , _ ) -> " '{{:...} ...}' (external link)"
139
98
| `Heading (level , _ , _ ) ->
140
99
Printf. sprintf " '{%i ...}' (section heading)" level
100
+ | `Specific s -> s
141
101
142
102
(* End of errors *)
143
103
@@ -188,7 +148,8 @@ type surrounding =
188
148
| `Reference of
189
149
[ `Simple | `With_text ]
190
150
* string Location_ .with_location
191
- * Odoc_parser.Ast .inline_element Location_ .with_location list ]
151
+ * Odoc_parser.Ast .inline_element Location_ .with_location list
152
+ | `Specific of string ]
192
153
193
154
let rec non_link_inline_element :
194
155
surrounding :surrounding ->
@@ -524,12 +485,13 @@ let strip_internal_tags ast : internal_tags_removed with_location list * _ =
524
485
in
525
486
match tag with
526
487
| (`Inline | `Open | `Closed | `Hidden ) as tag -> next tag
527
- | `Children_order co ->
488
+ | (`Children_order _ | `Short_title _ ) as tag ->
489
+ let tag_name = describe_internal_tag tag in
528
490
if not start then
529
491
Error. raise_warning
530
- (Error. make " @children_order tag has to be before any content"
492
+ (Error. make " %s tag has to be before any content" tag_name
531
493
wloc.location);
532
- next ( `Children_order co)
494
+ next tag
533
495
| `Canonical { Location. value = s ; location = r_location } -> (
534
496
match
535
497
Error. raise_warnings (Reference. read_path_longident r_location s)
@@ -568,6 +530,54 @@ let append_alerts_to_comment alerts
568
530
in
569
531
comment @ (alerts : alerts :> Comment.docs )
570
532
533
+ let handle_internal_tags (type a ) tags : a handle_internal_tags -> a = function
534
+ | Expect_status -> (
535
+ match
536
+ find_tag
537
+ ~filter: (function
538
+ | (`Inline | `Open | `Closed ) as t -> Some t | _ -> None )
539
+ tags
540
+ with
541
+ | Some (status , _ ) -> status
542
+ | None -> `Default )
543
+ | Expect_canonical -> (
544
+ match
545
+ find_tag ~filter: (function `Canonical p -> Some p | _ -> None ) tags
546
+ with
547
+ | Some (`Root _ , location ) ->
548
+ warn_root_canonical location;
549
+ None
550
+ | Some ((`Dot _ as p ), _ ) -> Some p
551
+ | None -> None )
552
+ | Expect_page_tags ->
553
+ let unparsed_lines =
554
+ find_tags []
555
+ ~filter: (function
556
+ | (`Children_order _ | `Short_title _ ) as p -> Some p | _ -> None )
557
+ tags
558
+ in
559
+ let lines =
560
+ let do_ parse loc els =
561
+ let els = nestable_block_elements els in
562
+ match parse loc els with
563
+ | Ok res -> Some res
564
+ | Error e ->
565
+ Error. raise_warning e;
566
+ None
567
+ in
568
+ List. filter_map
569
+ (function
570
+ | `Children_order co , loc ->
571
+ do_ Frontmatter. parse_children_order loc co
572
+ | `Short_title t , loc -> do_ Frontmatter. parse_short_title loc t)
573
+ unparsed_lines
574
+ in
575
+ Frontmatter. of_lines lines |> Error. raise_warnings
576
+ | Expect_none ->
577
+ (* Will raise warnings. *)
578
+ ignore (find_tag ~filter: (fun _ -> None ) tags);
579
+ ()
580
+
571
581
let ast_to_comment ~internal_tags ~tags_allowed ~parent_of_sections
572
582
(ast : Ast.t ) alerts =
573
583
Error. catch_warnings (fun () ->
@@ -598,3 +608,11 @@ let parse_reference text =
598
608
}
599
609
in
600
610
Reference. parse location text
611
+
612
+ let non_link_inline_element :
613
+ context :string ->
614
+ Odoc_parser.Ast. inline_element with_location list ->
615
+ Comment. non_link_inline_element with_location list =
616
+ fun ~context elements ->
617
+ let surrounding = `Specific context in
618
+ non_link_inline_elements ~surrounding elements
0 commit comments