@@ -105,12 +105,6 @@ let default_raw_markup_target_not_supported : Location.span -> Error.t =
105
105
Error. make ~suggestion: " try '{%html:...%}'."
106
106
" '{%%...%%}' (raw markup) needs a target language."
107
107
108
- let headings_not_allowed : Location.span -> Error.t =
109
- Error. make " Headings not allowed in this comment."
110
-
111
- let titles_not_allowed : Location.span -> Error.t =
112
- Error. make " Title-level headings {0 ...} are only allowed in pages."
113
-
114
108
let bad_heading_level : int -> Location.span -> Error.t =
115
109
Error. make " '%d': bad heading level (0-5 allowed)."
116
110
@@ -162,7 +156,6 @@ type alerts =
162
156
[ `Tag of [ `Alert of string * string option ] ] Location_ .with_location list
163
157
164
158
type status = {
165
- sections_allowed : sections_allowed ;
166
159
tags_allowed : bool ;
167
160
parent_of_sections : Paths.Identifier.LabelParent .t ;
168
161
}
@@ -453,42 +446,27 @@ let section_heading :
453
446
in
454
447
(top_heading_level, element)
455
448
in
456
-
457
- match (status.sections_allowed, level) with
458
- | `None , _any_level ->
459
- Error. raise_warning (headings_not_allowed location);
460
- let text = (text :> Comment.inline_element with_location list ) in
461
- let element =
462
- Location. at location
463
- (`Paragraph [ Location. at location (`Styled (`Bold , text)) ])
464
- in
465
- (top_heading_level, element)
466
- | `No_titles , 0 ->
467
- Error. raise_warning (titles_not_allowed location);
468
- mk_heading `Title
469
- | _ , level ->
470
- let level' =
471
- match level with
472
- | 0 -> `Title
473
- | 1 -> `Section
474
- | 2 -> `Subsection
475
- | 3 -> `Subsubsection
476
- | 4 -> `Paragraph
477
- | 5 -> `Subparagraph
478
- | _ ->
479
- Error. raise_warning (bad_heading_level level location);
480
- (* Implicitly promote to level-5. *)
481
- `Subparagraph
482
- in
483
- (match top_heading_level with
484
- | Some top_level
485
- when status.sections_allowed = `All && level < = top_level && level < = 5
486
- ->
487
- Error. raise_warning
488
- (heading_level_should_be_lower_than_top_level level top_level
489
- location)
490
- | _ -> () );
491
- mk_heading level'
449
+ let level' =
450
+ match level with
451
+ | 0 -> `Title
452
+ | 1 -> `Section
453
+ | 2 -> `Subsection
454
+ | 3 -> `Subsubsection
455
+ | 4 -> `Paragraph
456
+ | 5 -> `Subparagraph
457
+ | _ ->
458
+ Error. raise_warning (bad_heading_level level location);
459
+ (* Implicitly promote to level-5. *)
460
+ `Subparagraph
461
+ in
462
+ let () =
463
+ match top_heading_level with
464
+ | Some top_level when level < = top_level && level < = 5 ->
465
+ Error. raise_warning
466
+ (heading_level_should_be_lower_than_top_level level top_level location)
467
+ | _ -> ()
468
+ in
469
+ mk_heading level'
492
470
493
471
let validate_first_page_heading status ast_element =
494
472
match status.parent_of_sections.iv with
@@ -511,7 +489,7 @@ let top_level_block_elements status ast_elements =
511
489
| [] -> List. rev comment_elements_acc
512
490
| ast_element :: ast_elements -> (
513
491
(* The first [ast_element] in pages must be a title or section heading. *)
514
- if status.sections_allowed = `All && top_heading_level = None then
492
+ if top_heading_level = None then
515
493
validate_first_page_heading status ast_element;
516
494
517
495
match ast_element with
@@ -600,23 +578,23 @@ let append_alerts_to_comment alerts
600
578
in
601
579
comment @ (alerts : alerts :> Comment.docs )
602
580
603
- let ast_to_comment ~internal_tags ~sections_allowed ~ tags_allowed
604
- ~ parent_of_sections (ast : Ast.t ) alerts =
581
+ let ast_to_comment ~internal_tags ~tags_allowed ~ parent_of_sections
582
+ (ast : Ast.t ) alerts =
605
583
Error. catch_warnings (fun () ->
606
- let status = { sections_allowed; tags_allowed; parent_of_sections } in
584
+ let status = { tags_allowed; parent_of_sections } in
607
585
let ast, tags = strip_internal_tags ast in
608
586
let elts =
609
587
top_level_block_elements status ast |> append_alerts_to_comment alerts
610
588
in
611
589
(elts, handle_internal_tags tags internal_tags))
612
590
613
- let parse_comment ~internal_tags ~sections_allowed ~ tags_allowed
614
- ~containing_definition ~ location ~ text =
591
+ let parse_comment ~internal_tags ~tags_allowed ~ containing_definition ~ location
592
+ ~text =
615
593
Error. catch_warnings (fun () ->
616
594
let ast =
617
595
Odoc_parser. parse_comment ~location ~text |> Error. raise_parser_warnings
618
596
in
619
- ast_to_comment ~internal_tags ~sections_allowed ~ tags_allowed
597
+ ast_to_comment ~internal_tags ~tags_allowed
620
598
~parent_of_sections: containing_definition ast []
621
599
|> Error. raise_warnings)
622
600
0 commit comments