diff --git a/CHANGES.md b/CHANGES.md index 82a9adbd47..34b822db82 100644 --- a/CHANGES.md +++ b/CHANGES.md @@ -49,6 +49,7 @@ `{delim@lang[ code ]delim[ result ]}` - Output file paths and labels in the man and latex backends changed to avoid name clashes (@Julow, #1191) +- Change the scoping and placement rules for tags. Fixed #1138. (@panglesd, #1239) ### Fixed diff --git a/doc/ocamldoc_differences.mld b/doc/ocamldoc_differences.mld index 5992517b37..eb2a1f7a9a 100644 --- a/doc/ocamldoc_differences.mld +++ b/doc/ocamldoc_differences.mld @@ -15,6 +15,7 @@ The following describes the changes between what [odoc] understands and what’s - Heading levels are more restrictive. In the manual, it suggests any whole number is acceptable. In [odoc], similarly to the HTML spec, we allow headings from 1-5. Heading level [0] is for the title of [.mld] files. [odoc] emits a warning for heading levels outside this range and caps them. +- Tags are restricted in scope and do not need to be put at the end of the docstring. {3 Omissions} - Comments describing class inheritance are not rendered ({{:https://github.com/ocaml/odoc/issues/574}GitHub issue}). diff --git a/doc/odoc_for_authors.mld b/doc/odoc_for_authors.mld index e595d76de5..9d9bb04ed2 100644 --- a/doc/odoc_for_authors.mld +++ b/doc/odoc_for_authors.mld @@ -485,8 +485,7 @@ the {{!page-driver}driver}. {2:tags Tags} Tags are used to provide specific information for individual elements, such -as author, version, parameters, etc. Tags start with an [@] symbol, appear -at the end of documentation comments, and are not allowed elsewhere. +as author, version, parameters, etc. Tags start with an [@] symbol. They should appear on their own lines with nothing but whitespace before them. There are three types of tags. Those with: @@ -522,8 +521,8 @@ i.e., there shouldn't be any [odoc] markup. {3 Block Tags} These tags have a block of potentially marked-up text associated with them, -and occasionally some more data too. The block of text concludes with the end -of the comment or by another tag. They are: +and occasionally some more data too. The block of text is implicitly ended by a +new line, a heading or another tag. - [@deprecated ] - marks the element as deprecated. [text] should describe when the element was deprecated, what to use as a replacement, and possibly diff --git a/src/parser/syntax.ml b/src/parser/syntax.ml index 8d8c490400..c8a77a5700 100644 --- a/src/parser/syntax.ml +++ b/src/parser/syntax.ml @@ -576,11 +576,12 @@ let _check_subset : stopped_implicitly -> Token.t = fun t -> (t :> Token.t) - The type of token that the block parser stops at. See discussion above. *) type ('block, 'stops_at_which_tokens) context = | Top_level : (Ast.block_element, stops_at_delimiters) context - | In_shorthand_list : (Ast.nestable_block_element, stopped_implicitly) context + | In_implicitly_ended : + [ `Tag | `Shorthand_list ] + -> (Ast.nestable_block_element, stopped_implicitly) context | In_explicit_list : (Ast.nestable_block_element, stops_at_delimiters) context | In_table_cell : (Ast.nestable_block_element, stops_at_delimiters) context | In_code_results : (Ast.nestable_block_element, code_stop) context - | In_tag : (Ast.nestable_block_element, Token.t) context (* This is a no-op. It is needed to prove to the type system that nestable block elements are acceptable block elements in all contexts. *) @@ -592,11 +593,10 @@ let accepted_in_all_contexts : fun context block -> match context with | Top_level -> (block :> Ast.block_element) - | In_shorthand_list -> block + | In_implicitly_ended (`Tag | `Shorthand_list) -> block | In_explicit_list -> block | In_table_cell -> block | In_code_results -> block - | In_tag -> block (* Converts a tag to a series of words. This is used in error recovery, when a tag cannot be generated. *) @@ -638,13 +638,12 @@ let rec block_element_list : * where_in_line = fun context ~parent_markup input -> let rec consume_block_elements : - parsed_a_tag:bool -> where_in_line -> block with_location list -> block with_location list * stops_at_which_tokens with_location * where_in_line = - fun ~parsed_a_tag where_in_line acc -> + fun where_in_line acc -> let describe token = match token with | #token_that_always_begins_an_inline_element -> "paragraph" @@ -657,16 +656,6 @@ let rec block_element_list : |> add_warning input in - let warn_if_after_tags { Loc.location; value = token } = - if parsed_a_tag then - let suggestion = - Printf.sprintf "move %s before any tags." (Token.describe token) - in - Parse_error.not_allowed ~what:(describe token) - ~in_what:"the tags section" ~suggestion location - |> add_warning input - in - let warn_because_not_at_top_level { Loc.location; value = token } = let suggestion = Printf.sprintf "move %s outside of any other markup." @@ -683,9 +672,9 @@ let rec block_element_list : | { value = `End; _ } as next_token -> ( match context with | Top_level -> (List.rev acc, next_token, where_in_line) - | In_shorthand_list -> (List.rev acc, next_token, where_in_line) + | In_implicitly_ended (`Tag | `Shorthand_list) -> + (List.rev acc, next_token, where_in_line) | In_explicit_list -> (List.rev acc, next_token, where_in_line) - | In_tag -> (List.rev acc, next_token, where_in_line) | In_table_cell -> (List.rev acc, next_token, where_in_line) | In_code_results -> (List.rev acc, next_token, where_in_line)) | { value = `Right_brace; _ } as next_token -> ( @@ -694,37 +683,39 @@ let rec block_element_list : possible values of [context]. *) match context with | Top_level -> (List.rev acc, next_token, where_in_line) - | In_shorthand_list -> (List.rev acc, next_token, where_in_line) + | In_implicitly_ended (`Tag | `Shorthand_list) -> + (List.rev acc, next_token, where_in_line) | In_explicit_list -> (List.rev acc, next_token, where_in_line) | In_table_cell -> (List.rev acc, next_token, where_in_line) - | In_tag -> (List.rev acc, next_token, where_in_line) | In_code_results -> junk input; - consume_block_elements ~parsed_a_tag where_in_line acc) + consume_block_elements where_in_line acc) | { value = `Right_code_delimiter; _ } as next_token -> ( match context with | In_code_results -> (List.rev acc, next_token, where_in_line) | _ -> junk input; - consume_block_elements ~parsed_a_tag where_in_line acc) + consume_block_elements where_in_line acc) (* Whitespace. This can terminate some kinds of block elements. It is also necessary to track it to interpret [`Minus] and [`Plus] correctly, as well as to ensure that all block elements begin on their own line. *) | { value = `Space _; _ } -> junk input; - consume_block_elements ~parsed_a_tag where_in_line acc + consume_block_elements where_in_line acc | { value = `Single_newline _; _ } -> junk input; - consume_block_elements ~parsed_a_tag `At_start_of_line acc + consume_block_elements `At_start_of_line acc | { value = `Blank_line _; _ } as next_token -> ( match context with - (* Blank lines terminate shorthand lists ([- foo]). They also terminate - paragraphs, but the paragraph parser is aware of that internally. *) - | In_shorthand_list -> (List.rev acc, next_token, where_in_line) + (* Blank lines terminate shorthand lists ([- foo]) and tags. They also + terminate paragraphs, but the paragraph parser is aware of that + internally. *) + | In_implicitly_ended (`Tag | `Shorthand_list) -> + (List.rev acc, next_token, where_in_line) (* Otherwise, blank lines are pretty much like single newlines. *) | _ -> junk input; - consume_block_elements ~parsed_a_tag `At_start_of_line acc) + consume_block_elements `At_start_of_line acc) (* Explicit list items ([{li ...}] and [{- ...}]) can never appear directly in block content. They can only appear inside [{ul ...}] and [{ol ...}]. So, catch those. *) @@ -740,7 +731,7 @@ let rec block_element_list : |> add_warning input; junk input; - consume_block_elements ~parsed_a_tag where_in_line acc + consume_block_elements where_in_line acc (* Table rows ([{tr ...}]) can never appear directly in block content. They can only appear inside [{table ...}]. *) | { value = `Begin_table_row as token; location } -> @@ -753,7 +744,7 @@ let rec block_element_list : ~suggestion location |> add_warning input; junk input; - consume_block_elements ~parsed_a_tag where_in_line acc + consume_block_elements where_in_line acc (* Table cells ([{th ...}] and [{td ...}]) can never appear directly in block content. They can only appear inside [{tr ...}]. *) | { value = `Begin_table_cell _ as token; location } -> @@ -766,9 +757,8 @@ let rec block_element_list : ~suggestion location |> add_warning input; junk input; - consume_block_elements ~parsed_a_tag where_in_line acc - (* Tags. These can appear at the top level only. Also, once one tag is seen, - the only top-level elements allowed are more tags. *) + consume_block_elements where_in_line acc + (* Tags. These can appear at the top level only. *) | { value = `Tag tag as token; location } as next_token -> ( let recover_when_not_at_top_level context = warn_because_not_at_top_level next_token; @@ -779,8 +769,7 @@ let rec block_element_list : |> accepted_in_all_contexts context |> Loc.at location in - consume_block_elements ~parsed_a_tag `At_start_of_line - (paragraph :: acc) + consume_block_elements `At_start_of_line (paragraph :: acc) in match context with @@ -789,15 +778,11 @@ let rec block_element_list : (* If a tag starts at the beginning of a line, it terminates the preceding tag and/or the current shorthand list. In this case, return to the caller, and let the caller decide how to interpret the tag token. *) - | In_shorthand_list -> + | In_implicitly_ended (`Tag | `Shorthand_list) -> if where_in_line = `At_start_of_line then (List.rev acc, next_token, where_in_line) else recover_when_not_at_top_level context | In_table_cell -> recover_when_not_at_top_level context - | In_tag -> - if where_in_line = `At_start_of_line then - (List.rev acc, next_token, where_in_line) - else recover_when_not_at_top_level context | In_code_results -> recover_when_not_at_top_level context (* If this is the top-level call to [block_element_list], parse the tag. *) @@ -831,11 +816,11 @@ let rec block_element_list : in let tag = Loc.at location (`Tag tag) in - consume_block_elements ~parsed_a_tag:true `After_text - (tag :: acc) + consume_block_elements `After_text (tag :: acc) | (`Deprecated | `Return) as tag -> let content, _stream_head, where_in_line = - block_element_list In_tag ~parent_markup:token input + block_element_list (In_implicitly_ended `Tag) + ~parent_markup:token input in let tag = match tag with @@ -846,11 +831,11 @@ let rec block_element_list : location :: List.map Loc.location content |> Loc.span in let tag = Loc.at location (`Tag tag) in - consume_block_elements ~parsed_a_tag:true where_in_line - (tag :: acc) + consume_block_elements where_in_line (tag :: acc) | (`Param _ | `Raise _ | `Before _) as tag -> let content, _stream_head, where_in_line = - block_element_list In_tag ~parent_markup:token input + block_element_list (In_implicitly_ended `Tag) + ~parent_markup:token input in let tag = match tag with @@ -862,34 +847,30 @@ let rec block_element_list : location :: List.map Loc.location content |> Loc.span in let tag = Loc.at location (`Tag tag) in - consume_block_elements ~parsed_a_tag:true where_in_line - (tag :: acc) + consume_block_elements where_in_line (tag :: acc) | `See (kind, target) -> let content, _next_token, where_in_line = - block_element_list In_tag ~parent_markup:token input + block_element_list (In_implicitly_ended `Tag) + ~parent_markup:token input in let location = location :: List.map Loc.location content |> Loc.span in let tag = `Tag (`See (kind, target, content)) in let tag = Loc.at location tag in - consume_block_elements ~parsed_a_tag:true where_in_line - (tag :: acc) + consume_block_elements where_in_line (tag :: acc) | (`Inline | `Open | `Closed | `Hidden) as tag -> let tag = Loc.at location (`Tag tag) in - consume_block_elements ~parsed_a_tag:true `After_text - (tag :: acc))) + consume_block_elements `After_text (tag :: acc))) | ( { value = #token_that_always_begins_an_inline_element; _ } | { value = `Bar; _ } ) as next_token -> - warn_if_after_tags next_token; warn_if_after_text next_token; let block = paragraph input in let block = Loc.map (accepted_in_all_contexts context) block in let acc = block :: acc in - consume_block_elements ~parsed_a_tag `After_text acc + consume_block_elements `After_text acc | { value = `Verbatim s as token; location } as next_token -> - warn_if_after_tags next_token; warn_if_after_text next_token; if s = "" then Parse_error.should_not_be_empty ~what:(Token.describe token) location @@ -899,9 +880,8 @@ let rec block_element_list : let block = accepted_in_all_contexts context token in let block = Loc.at location block in let acc = block :: acc in - consume_block_elements ~parsed_a_tag `After_text acc + consume_block_elements `After_text acc | { value = `Math_block s as token; location } as next_token -> - warn_if_after_tags next_token; warn_if_after_text next_token; if s = "" then Parse_error.should_not_be_empty ~what:(Token.describe token) location @@ -911,14 +891,13 @@ let rec block_element_list : let block = accepted_in_all_contexts context token in let block = Loc.at location block in let acc = block :: acc in - consume_block_elements ~parsed_a_tag `After_text acc + consume_block_elements `After_text acc | { value = `Code_block (meta, delim, { value = s; location = v_loc }, has_outputs) as token; location; } as next_token -> - warn_if_after_tags next_token; warn_if_after_text next_token; junk input; let delimiter = if delim = "" then None else Some delim in @@ -958,9 +937,8 @@ let rec block_element_list : in let block = Loc.at location block in let acc = block :: acc in - consume_block_elements ~parsed_a_tag `After_text acc + consume_block_elements `After_text acc | { value = `Modules s as token; location } as next_token -> - warn_if_after_tags next_token; warn_if_after_text next_token; junk input; @@ -999,9 +977,8 @@ let rec block_element_list : let block = accepted_in_all_contexts context (`Modules modules) in let block = Loc.at location block in let acc = block :: acc in - consume_block_elements ~parsed_a_tag `After_text acc + consume_block_elements `After_text acc | { value = `Begin_list kind as token; location } as next_token -> - warn_if_after_tags next_token; warn_if_after_text next_token; junk input; @@ -1018,10 +995,9 @@ let rec block_element_list : let block = accepted_in_all_contexts context block in let block = Loc.at location block in let acc = block :: acc in - consume_block_elements ~parsed_a_tag `After_text acc + consume_block_elements `After_text acc | { value = (`Begin_table_light | `Begin_table_heavy) as token; location } as next_token -> - warn_if_after_tags next_token; warn_if_after_text next_token; junk input; let block, brace_location = @@ -1037,7 +1013,7 @@ let rec block_element_list : let block = accepted_in_all_contexts context (`Table block) in let block = Loc.at location block in let acc = block :: acc in - consume_block_elements ~parsed_a_tag `After_text acc + consume_block_elements `After_text acc | { value = (`Minus | `Plus) as token; location } as next_token -> ( (match where_in_line with | `After_text | `After_shorthand_bullet -> @@ -1046,10 +1022,9 @@ let rec block_element_list : |> add_warning input | _ -> ()); - warn_if_after_tags next_token; - match context with - | In_shorthand_list -> (List.rev acc, next_token, where_in_line) + | In_implicitly_ended `Shorthand_list -> + (List.rev acc, next_token, where_in_line) | _ -> let items, where_in_line = shorthand_list_items next_token where_in_line input @@ -1064,11 +1039,9 @@ let rec block_element_list : let block = accepted_in_all_contexts context block in let block = Loc.at location block in let acc = block :: acc in - consume_block_elements ~parsed_a_tag where_in_line acc) + consume_block_elements where_in_line acc) | { value = `Begin_section_heading (level, label) as token; location } as next_token -> ( - warn_if_after_tags next_token; - let recover_when_not_at_top_level context = warn_because_not_at_top_level next_token; junk input; @@ -1083,18 +1056,16 @@ let rec block_element_list : |> accepted_in_all_contexts context |> Loc.at location in - consume_block_elements ~parsed_a_tag `At_start_of_line - (paragraph :: acc) + consume_block_elements `At_start_of_line (paragraph :: acc) in match context with - | In_shorthand_list -> + | In_implicitly_ended (`Tag | `Shorthand_list) -> if where_in_line = `At_start_of_line then (List.rev acc, next_token, where_in_line) else recover_when_not_at_top_level context | In_explicit_list -> recover_when_not_at_top_level context | In_table_cell -> recover_when_not_at_top_level context - | In_tag -> recover_when_not_at_top_level context | In_code_results -> recover_when_not_at_top_level context | Top_level -> if where_in_line <> `At_start_of_line then @@ -1127,7 +1098,7 @@ let rec block_element_list : let heading = `Heading (level, label, content) in let heading = Loc.at location heading in let acc = heading :: acc in - consume_block_elements ~parsed_a_tag `After_text acc) + consume_block_elements `After_text acc) | { value = `Begin_paragraph_style _ as token; location } -> junk input; let content, brace_location = @@ -1146,13 +1117,11 @@ let rec block_element_list : |> accepted_in_all_contexts context |> Loc.at location in - consume_block_elements ~parsed_a_tag `At_start_of_line (paragraph :: acc) + consume_block_elements `At_start_of_line (paragraph :: acc) | { - location; - value = `Media_with_replacement_text (href, media, content) as token; - } as next_token -> - warn_if_after_tags next_token; - + location; + value = `Media_with_replacement_text (href, media, content) as token; + } -> junk input; let r_location = @@ -1181,10 +1150,8 @@ let rec block_element_list : let block = accepted_in_all_contexts context block in let block = Loc.at location block in let acc = block :: acc in - consume_block_elements ~parsed_a_tag `After_text acc - | { location; value = `Simple_media (href, media) } as next_token -> - warn_if_after_tags next_token; - + consume_block_elements `After_text acc + | { location; value = `Simple_media (href, media) } -> junk input; let r_location = @@ -1198,20 +1165,20 @@ let rec block_element_list : let block = accepted_in_all_contexts context block in let block = Loc.at location block in let acc = block :: acc in - consume_block_elements ~parsed_a_tag `After_text acc + consume_block_elements `After_text acc in let where_in_line = match context with | Top_level -> `At_start_of_line - | In_shorthand_list -> `After_shorthand_bullet + | In_implicitly_ended `Shorthand_list -> `After_shorthand_bullet | In_explicit_list -> `After_explicit_list_bullet | In_table_cell -> `After_table_cell | In_code_results -> `After_tag - | In_tag -> `After_tag + | In_implicitly_ended `Tag -> `After_tag in - consume_block_elements ~parsed_a_tag:false where_in_line [] + consume_block_elements where_in_line [] (* {3 Lists} *) @@ -1248,7 +1215,8 @@ and shorthand_list_items : junk input; let content, stream_head, where_in_line = - block_element_list In_shorthand_list ~parent_markup:bullet input + block_element_list (In_implicitly_ended `Shorthand_list) + ~parent_markup:bullet input in if content = [] then Parse_error.should_not_be_empty ~what:(Token.describe bullet) diff --git a/src/parser/test/test.ml b/src/parser/test/test.ml index 175828dc67..af6be5d40a 100644 --- a/src/parser/test/test.ml +++ b/src/parser/test/test.ml @@ -4051,10 +4051,10 @@ let%expect_test _ = [%expect {| ((output - (((f.ml (1 0) (3 3)) + (((f.ml (1 0) (1 15)) (@deprecated - ((f.ml (1 12) (1 15)) (paragraph (((f.ml (1 12) (1 15)) (word foo))))) - ((f.ml (3 0) (3 3)) (paragraph (((f.ml (3 0) (3 3)) (word bar))))))))) + ((f.ml (1 12) (1 15)) (paragraph (((f.ml (1 12) (1 15)) (word foo))))))) + ((f.ml (3 0) (3 3)) (paragraph (((f.ml (3 0) (3 3)) (word bar))))))) (warnings ())) |}] let whitespace_only = @@ -4087,9 +4087,8 @@ let%expect_test _ = [%expect {| ((output - (((f.ml (1 0) (3 3)) - (@deprecated - ((f.ml (3 0) (3 3)) (paragraph (((f.ml (3 0) (3 3)) (word foo))))))))) + (((f.ml (1 0) (1 11)) (@deprecated)) + ((f.ml (3 0) (3 3)) (paragraph (((f.ml (3 0) (3 3)) (word foo))))))) (warnings ())) |}] let extra_whitespace = @@ -4194,6 +4193,38 @@ let%expect_test _ = (paragraph (((f.ml (1 14) (1 17)) (word foo))))))))))))) (warnings ())) |}] + let with_shorthand_list_double_item = + test "@deprecated - foo\n- bar"; + [%expect + {| + ((output + (((f.ml (1 0) (2 5)) + (@deprecated + ((f.ml (1 12) (2 5)) + (unordered light + ((((f.ml (1 14) (1 17)) + (paragraph (((f.ml (1 14) (1 17)) (word foo)))))) + (((f.ml (2 2) (2 5)) (paragraph (((f.ml (2 2) (2 5)) (word bar))))))))))))) + (warnings ())) |}] + + let double_implicitly_ended = + test "@deprecated - foo\n- bar\n\nNew paragraph"; + [%expect + {| + ((output + (((f.ml (1 0) (2 5)) + (@deprecated + ((f.ml (1 12) (2 5)) + (unordered light + ((((f.ml (1 14) (1 17)) + (paragraph (((f.ml (1 14) (1 17)) (word foo)))))) + (((f.ml (2 2) (2 5)) (paragraph (((f.ml (2 2) (2 5)) (word bar))))))))))) + ((f.ml (4 0) (4 13)) + (paragraph + (((f.ml (4 0) (4 3)) (word New)) ((f.ml (4 3) (4 4)) space) + ((f.ml (4 4) (4 13)) (word paragraph))))))) + (warnings ())) |}] + let with_shorthand_list_after_newline = test "@deprecated\n- foo"; [%expect @@ -4233,14 +4264,11 @@ let%expect_test _ = [%expect {| ((output - (((f.ml (1 0) (2 7)) + (((f.ml (1 0) (1 15)) (@deprecated - ((f.ml (1 12) (1 15)) (paragraph (((f.ml (1 12) (1 15)) (word foo))))) - ((f.ml (2 0) (2 7)) (paragraph (((f.ml (2 3) (2 6)) (word Bar))))))))) - (warnings - ( "File \"f.ml\", line 2, characters 0-2:\ - \n'{2 ...}' (section heading) is not allowed in '@deprecated'.\ - \nSuggestion: move '{2' outside of any other markup."))) |}] + ((f.ml (1 12) (1 15)) (paragraph (((f.ml (1 12) (1 15)) (word foo))))))) + ((f.ml (2 0) (2 7)) (2 (label ()) (((f.ml (2 3) (2 6)) (word Bar))))))) + (warnings ())) |}] end in () @@ -4322,10 +4350,10 @@ let%expect_test _ = [%expect {| ((output - (((f.ml (1 0) (3 3)) + (((f.ml (1 0) (1 14)) (@param foo - ((f.ml (1 11) (1 14)) (paragraph (((f.ml (1 11) (1 14)) (word bar))))) - ((f.ml (3 0) (3 3)) (paragraph (((f.ml (3 0) (3 3)) (word baz))))))))) + ((f.ml (1 11) (1 14)) (paragraph (((f.ml (1 11) (1 14)) (word bar))))))) + ((f.ml (3 0) (3 3)) (paragraph (((f.ml (3 0) (3 3)) (word baz))))))) (warnings ())) |}] let two = @@ -4826,9 +4854,6 @@ let%expect_test _ = ((f.ml (1 8) (1 11)) (paragraph (((f.ml (1 8) (1 11)) (word foo))))))) (warnings ( "File \"f.ml\", line 1, characters 8-11:\ - \nParagraph is not allowed in the tags section.\ - \nSuggestion: move 'foo' before any tags." - "File \"f.ml\", line 1, characters 8-11:\ \nParagraph should begin on its own line."))) |}] let followed_by_paragraph = @@ -4838,10 +4863,7 @@ let%expect_test _ = ((output (((f.ml (1 0) (1 7)) @inline) ((f.ml (2 0) (2 3)) (paragraph (((f.ml (2 0) (2 3)) (word foo))))))) - (warnings - ( "File \"f.ml\", line 2, characters 0-3:\ - \nParagraph is not allowed in the tags section.\ - \nSuggestion: move 'foo' before any tags."))) |}] + (warnings ())) |}] let followed_by_tag = test "@inline\n@deprecated"; @@ -4861,10 +4883,7 @@ let%expect_test _ = ((((f.ml (1 10) (1 13)) (paragraph (((f.ml (1 10) (1 13)) (word foo))))))))))) (warnings ( "File \"f.ml\", line 1, characters 8-9:\ - \n'-' (bulleted list item) should begin on its own line." - "File \"f.ml\", line 1, characters 8-9:\ - \n'-' (bulleted list item) is not allowed in the tags section.\ - \nSuggestion: move '-' (bulleted list item) before any tags."))) |}] + \n'-' (bulleted list item) should begin on its own line."))) |}] end in () @@ -4897,9 +4916,6 @@ let%expect_test _ = ((f.ml (1 6) (1 9)) (paragraph (((f.ml (1 6) (1 9)) (word foo))))))) (warnings ( "File \"f.ml\", line 1, characters 6-9:\ - \nParagraph is not allowed in the tags section.\ - \nSuggestion: move 'foo' before any tags." - "File \"f.ml\", line 1, characters 6-9:\ \nParagraph should begin on its own line."))) |}] let followed_by_paragraph = @@ -4909,10 +4925,7 @@ let%expect_test _ = ((output (((f.ml (1 0) (1 5)) @open) ((f.ml (2 0) (2 3)) (paragraph (((f.ml (2 0) (2 3)) (word foo))))))) - (warnings - ( "File \"f.ml\", line 2, characters 0-3:\ - \nParagraph is not allowed in the tags section.\ - \nSuggestion: move 'foo' before any tags."))) |}] + (warnings ())) |}] let followed_by_tag = test "@open\n@deprecated"; @@ -4932,10 +4945,7 @@ let%expect_test _ = ((((f.ml (1 8) (1 11)) (paragraph (((f.ml (1 8) (1 11)) (word foo))))))))))) (warnings ( "File \"f.ml\", line 1, characters 6-7:\ - \n'-' (bulleted list item) should begin on its own line." - "File \"f.ml\", line 1, characters 6-7:\ - \n'-' (bulleted list item) is not allowed in the tags section.\ - \nSuggestion: move '-' (bulleted list item) before any tags."))) |}] + \n'-' (bulleted list item) should begin on its own line."))) |}] end in () @@ -4969,9 +4979,6 @@ let%expect_test _ = ((f.ml (1 8) (1 11)) (paragraph (((f.ml (1 8) (1 11)) (word foo))))))) (warnings ( "File \"f.ml\", line 1, characters 8-11:\ - \nParagraph is not allowed in the tags section.\ - \nSuggestion: move 'foo' before any tags." - "File \"f.ml\", line 1, characters 8-11:\ \nParagraph should begin on its own line."))) |}] let followed_by_paragraph = @@ -4981,10 +4988,7 @@ let%expect_test _ = ((output (((f.ml (1 0) (1 7)) @closed) ((f.ml (2 0) (2 3)) (paragraph (((f.ml (2 0) (2 3)) (word foo))))))) - (warnings - ( "File \"f.ml\", line 2, characters 0-3:\ - \nParagraph is not allowed in the tags section.\ - \nSuggestion: move 'foo' before any tags."))) |}] + (warnings ())) |}] let followed_by_tag = test "@closed\n@deprecated"; @@ -5004,10 +5008,7 @@ let%expect_test _ = ((((f.ml (1 10) (1 13)) (paragraph (((f.ml (1 10) (1 13)) (word foo))))))))))) (warnings ( "File \"f.ml\", line 1, characters 8-9:\ - \n'-' (bulleted list item) should begin on its own line." - "File \"f.ml\", line 1, characters 8-9:\ - \n'-' (bulleted list item) is not allowed in the tags section.\ - \nSuggestion: move '-' (bulleted list item) before any tags."))) |}] + \n'-' (bulleted list item) should begin on its own line."))) |}] end in () @@ -5041,9 +5042,6 @@ let%expect_test _ = ((f.ml (1 8) (1 11)) (paragraph (((f.ml (1 8) (1 11)) (word foo))))))) (warnings ( "File \"f.ml\", line 1, characters 8-11:\ - \nParagraph is not allowed in the tags section.\ - \nSuggestion: move 'foo' before any tags." - "File \"f.ml\", line 1, characters 8-11:\ \nParagraph should begin on its own line."))) |}] let followed_by_paragraph = @@ -5053,10 +5051,7 @@ let%expect_test _ = ((output (((f.ml (1 0) (1 7)) @hidden) ((f.ml (2 0) (2 3)) (paragraph (((f.ml (2 0) (2 3)) (word foo))))))) - (warnings - ( "File \"f.ml\", line 2, characters 0-3:\ - \nParagraph is not allowed in the tags section.\ - \nSuggestion: move 'foo' before any tags."))) |}] + (warnings ())) |}] let followed_by_tag = test "@hidden\n@deprecated"; @@ -5076,10 +5071,7 @@ let%expect_test _ = ((((f.ml (1 10) (1 13)) (paragraph (((f.ml (1 10) (1 13)) (word foo))))))))))) (warnings ( "File \"f.ml\", line 1, characters 8-9:\ - \n'-' (bulleted list item) should begin on its own line." - "File \"f.ml\", line 1, characters 8-9:\ - \n'-' (bulleted list item) is not allowed in the tags section.\ - \nSuggestion: move '-' (bulleted list item) before any tags."))) |}] + \n'-' (bulleted list item) should begin on its own line."))) |}] end in () diff --git a/test/model/semantics/test.ml b/test/model/semantics/test.ml index b3dcd83878..532a6333b6 100644 --- a/test/model/semantics/test.ml +++ b/test/model/semantics/test.ml @@ -759,49 +759,49 @@ let%expect_test _ = test "@author Foo\nbar"; [%expect {| - {"value":[{"`Tag":{"`Author":"Foo"}},{"`Paragraph":[{"`Word":"bar"}]}],"warnings":["File \"f.ml\", line 2, characters 0-3:\nParagraph is not allowed in the tags section.\nSuggestion: move 'bar' before any tags."]} |}] + {"value":[{"`Tag":{"`Author":"Foo"}},{"`Paragraph":[{"`Word":"bar"}]}],"warnings":[]} |}] let followed_by_code_span = test "@author Foo\n[bar]"; [%expect {| - {"value":[{"`Tag":{"`Author":"Foo"}},{"`Paragraph":[{"`Code_span":"bar"}]}],"warnings":["File \"f.ml\", line 2, characters 0-5:\nParagraph is not allowed in the tags section.\nSuggestion: move '[...]' (code) before any tags."]} |}] + {"value":[{"`Tag":{"`Author":"Foo"}},{"`Paragraph":[{"`Code_span":"bar"}]}],"warnings":[]} |}] let followed_by_code_block = test "@author Foo\n{[bar]}"; [%expect {| - {"value":[{"`Tag":{"`Author":"Foo"}},{"`Code_block":["None","bar"]}],"warnings":["File \"f.ml\", line 2, characters 0-7:\n'{[...]}' (code block) is not allowed in the tags section.\nSuggestion: move '{[...]}' (code block) before any tags."]} |}] + {"value":[{"`Tag":{"`Author":"Foo"}},{"`Code_block":["None","bar"]}],"warnings":[]} |}] let followed_by_verbatim = test "@author Foo\n{v bar v}"; [%expect {| - {"value":[{"`Tag":{"`Author":"Foo"}},{"`Verbatim":"bar"}],"warnings":["File \"f.ml\", line 2, characters 0-9:\n'{v ... v}' (verbatim text) is not allowed in the tags section.\nSuggestion: move '{v ... v}' (verbatim text) before any tags."]} |}] + {"value":[{"`Tag":{"`Author":"Foo"}},{"`Verbatim":"bar"}],"warnings":[]} |}] let followed_by_modules = test "@author foo\n{!modules:Foo}"; [%expect {| - {"value":[{"`Tag":{"`Author":"foo"}},{"`Modules":[[{"`Root":["Foo","`TUnknown"]},"None"]]}],"warnings":["File \"f.ml\", line 2, characters 0-14:\n'{!modules ...}' is not allowed in the tags section.\nSuggestion: move '{!modules ...}' before any tags."]} |}] + {"value":[{"`Tag":{"`Author":"foo"}},{"`Modules":[[{"`Root":["Foo","`TUnknown"]},"None"]]}],"warnings":[]} |}] let followed_by_list = test "@author Foo\n{ul {li bar}}"; [%expect {| - {"value":[{"`Tag":{"`Author":"Foo"}},{"`List":["`Unordered",[[{"`Paragraph":[{"`Word":"bar"}]}]]]}],"warnings":["File \"f.ml\", line 2, characters 0-3:\n'{ul ...}' (bulleted list) is not allowed in the tags section.\nSuggestion: move '{ul ...}' (bulleted list) before any tags."]} |}] + {"value":[{"`Tag":{"`Author":"Foo"}},{"`List":["`Unordered",[[{"`Paragraph":[{"`Word":"bar"}]}]]]}],"warnings":[]} |}] let followed_by_shorthand_list = test "@author Foo\n- bar"; [%expect {| - {"value":[{"`Tag":{"`Author":"Foo"}},{"`List":["`Unordered",[[{"`Paragraph":[{"`Word":"bar"}]}]]]}],"warnings":["File \"f.ml\", line 2, characters 0-1:\n'-' (bulleted list item) is not allowed in the tags section.\nSuggestion: move '-' (bulleted list item) before any tags."]} |}] + {"value":[{"`Tag":{"`Author":"Foo"}},{"`List":["`Unordered",[[{"`Paragraph":[{"`Word":"bar"}]}]]]}],"warnings":[]} |}] let followed_by_section_heading = test "@author Foo\n{2 Bar}"; [%expect {| - {"value":[{"`Tag":{"`Author":"Foo"}},{"`Heading":[{"heading_level":"`Subsection","heading_label_explicit":"false"},{"`Label":[{"`Page":["None","f.ml"]},"bar"]},[{"`Word":"Bar"}]]}],"warnings":["File \"f.ml\", line 2, characters 0-2:\n'{2 ...}' (section heading) is not allowed in the tags section.\nSuggestion: move '{2 ...}' (section heading) before any tags."]} |}] + {"value":[{"`Tag":{"`Author":"Foo"}},{"`Heading":[{"heading_level":"`Subsection","heading_label_explicit":"false"},{"`Label":[{"`Page":["None","f.ml"]},"bar"]},[{"`Word":"Bar"}]]}],"warnings":[]} |}] let followed_by_author = test "@author Foo\n@author Bar";