Skip to content

Commit 935d15d

Browse files
committed
Remove sections_allowed as it was not used (apart from in a test)
1 parent 9094191 commit 935d15d

File tree

5 files changed

+464
-491
lines changed

5 files changed

+464
-491
lines changed

src/loader/doc_attr.ml

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -114,7 +114,7 @@ let pad_loc loc =
114114
{ loc.Location.loc_start with pos_cnum = loc.loc_start.pos_cnum + 3 }
115115

116116
let ast_to_comment ~internal_tags parent ast_docs alerts =
117-
Odoc_model.Semantics.ast_to_comment ~internal_tags ~sections_allowed:`All
117+
Odoc_model.Semantics.ast_to_comment ~internal_tags
118118
~tags_allowed:true ~parent_of_sections:parent ast_docs alerts
119119
|> Error.raise_warnings
120120

@@ -150,7 +150,6 @@ let attached_no_tag parent attrs =
150150
let read_string ~tags_allowed internal_tags parent location str =
151151
Odoc_model.Semantics.parse_comment
152152
~internal_tags
153-
~sections_allowed:`All
154153
~tags_allowed
155154
~containing_definition:parent
156155
~location

src/markdown/odoc_md.ml

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -13,8 +13,7 @@ let parse id input_s =
1313
Doc_of_md.parse_comment ~location ~text:str ()
1414
in
1515
let (content, ()), semantics_warnings =
16-
Semantics.ast_to_comment ~internal_tags:Expect_none ~sections_allowed:`All
17-
~tags_allowed:false
16+
Semantics.ast_to_comment ~internal_tags:Expect_none ~tags_allowed:false
1817
~parent_of_sections:(id :> Paths.Identifier.LabelParent.t)
1918
content []
2019
|> Error.unpack_warnings

src/model/semantics.ml

Lines changed: 28 additions & 50 deletions
Original file line numberDiff line numberDiff line change
@@ -105,12 +105,6 @@ let default_raw_markup_target_not_supported : Location.span -> Error.t =
105105
Error.make ~suggestion:"try '{%html:...%}'."
106106
"'{%%...%%}' (raw markup) needs a target language."
107107

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-
114108
let bad_heading_level : int -> Location.span -> Error.t =
115109
Error.make "'%d': bad heading level (0-5 allowed)."
116110

@@ -162,7 +156,6 @@ type alerts =
162156
[ `Tag of [ `Alert of string * string option ] ] Location_.with_location list
163157

164158
type status = {
165-
sections_allowed : sections_allowed;
166159
tags_allowed : bool;
167160
parent_of_sections : Paths.Identifier.LabelParent.t;
168161
}
@@ -453,42 +446,27 @@ let section_heading :
453446
in
454447
(top_heading_level, element)
455448
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'
492470

493471
let validate_first_page_heading status ast_element =
494472
match status.parent_of_sections.iv with
@@ -511,7 +489,7 @@ let top_level_block_elements status ast_elements =
511489
| [] -> List.rev comment_elements_acc
512490
| ast_element :: ast_elements -> (
513491
(* 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
515493
validate_first_page_heading status ast_element;
516494

517495
match ast_element with
@@ -600,23 +578,23 @@ let append_alerts_to_comment alerts
600578
in
601579
comment @ (alerts : alerts :> Comment.docs)
602580

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 =
605583
Error.catch_warnings (fun () ->
606-
let status = { sections_allowed; tags_allowed; parent_of_sections } in
584+
let status = { tags_allowed; parent_of_sections } in
607585
let ast, tags = strip_internal_tags ast in
608586
let elts =
609587
top_level_block_elements status ast |> append_alerts_to_comment alerts
610588
in
611589
(elts, handle_internal_tags tags internal_tags))
612590

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 =
615593
Error.catch_warnings (fun () ->
616594
let ast =
617595
Odoc_parser.parse_comment ~location ~text |> Error.raise_parser_warnings
618596
in
619-
ast_to_comment ~internal_tags ~sections_allowed ~tags_allowed
597+
ast_to_comment ~internal_tags ~tags_allowed
620598
~parent_of_sections:containing_definition ast []
621599
|> Error.raise_warnings)
622600

src/model/semantics.mli

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -13,7 +13,6 @@ type alerts =
1313

1414
val ast_to_comment :
1515
internal_tags:'tags handle_internal_tags ->
16-
sections_allowed:sections_allowed ->
1716
tags_allowed:bool ->
1817
parent_of_sections:Paths.Identifier.LabelParent.t ->
1918
Odoc_parser.Ast.t ->
@@ -22,7 +21,6 @@ val ast_to_comment :
2221

2322
val parse_comment :
2423
internal_tags:'tags handle_internal_tags ->
25-
sections_allowed:sections_allowed ->
2624
tags_allowed:bool ->
2725
containing_definition:Paths.Identifier.LabelParent.t ->
2826
location:Lexing.position ->

0 commit comments

Comments
 (0)