Skip to content
Merged
Show file tree
Hide file tree
Changes from 8 commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
4 changes: 4 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -32,6 +32,10 @@ Tags:
### Changed
- Style: Adjusted line height in the TOC to improve readability (@sorawee, #1045)

### Fixed
- Warn and exit when table(s) is not closed (@lubegasimon, #1050)
- Hint when list(s) is not closed (@lubegasimon, #1050)

# 2.3.0

### Added
Expand Down
7 changes: 7 additions & 0 deletions src/parser/parse_error.ml
Original file line number Diff line number Diff line change
Expand Up @@ -81,3 +81,10 @@ let truncated_code_block_meta : Loc.span -> Warning.t =

let truncated_code_block : Loc.span -> Warning.t =
Warning.make ~suggestion:"add ']}'." "Missing end of code block."

let end_not_allowed :
?suggestion:string -> what:string -> in_what:string -> Loc.span -> Warning.t
=
fun ?suggestion ~what ~in_what ->
Warning.make ?suggestion "%s is not allowed in %s." (capitalize_ascii what)
in_what
30 changes: 24 additions & 6 deletions src/parser/syntax.ml
Original file line number Diff line number Diff line change
Expand Up @@ -118,13 +118,22 @@ module Table = struct
end

module Reader = struct
let until_rbrace input acc =
let until_rbrace_or_eof input acc =
let rec consume () =
let next_token = peek input in
match next_token.value with
| `Right_brace ->
junk input;
`End (acc, next_token.location)
| `End ->
Parse_error.end_not_allowed next_token.location
~what:(Token.describe `End) ~in_what:"table"
~suggestion:
"try to add '}' at the end of table content ('{t ...' or '{table \
...' )."
|> add_warning input;
junk input;
`End (acc, next_token.location)
| `Space _ | `Single_newline _ | `Blank_line _ ->
junk input;
consume ()
Expand Down Expand Up @@ -1227,8 +1236,10 @@ and explicit_list_items :
let next_token = peek input in
match next_token.value with
| `End ->
Parse_error.not_allowed next_token.location ~what:(Token.describe `End)
Parse_error.end_not_allowed next_token.location
~what:(Token.describe `End)
~in_what:(Token.describe parent_markup)
~suggestion:"try to add '}' at the end of the list content."
|> add_warning input;
(List.rev acc, next_token.location)
| `Right_brace ->
Expand Down Expand Up @@ -1275,8 +1286,9 @@ and explicit_list_items :
(match token_after_list_item.value with
| `Right_brace -> junk input
| `End ->
Parse_error.not_allowed token_after_list_item.location
Parse_error.end_not_allowed token_after_list_item.location
~what:(Token.describe `End) ~in_what:(Token.describe token)
~suggestion:"try to add '}' at the end of the list content."
|> add_warning input);

let acc = content :: acc in
Expand Down Expand Up @@ -1310,7 +1322,7 @@ and explicit_list_items :
which is consumed. *)
and light_table ~parent_markup ~parent_markup_location input =
let rec consume_rows acc ~last_loc =
Reader.until_rbrace input acc >>> fun next_token ->
Reader.until_rbrace_or_eof input acc >>> fun next_token ->
match next_token.Loc.value with
| `Bar | #token_that_always_begins_an_inline_element -> (
let next, row, last_loc =
Expand Down Expand Up @@ -1340,6 +1352,12 @@ and light_table_row ~parent_markup ~last_loc input =
let return row cell = List.rev (push_cells row cell) in
let next_token = peek input in
match next_token.value with
| `End ->
Parse_error.end_not_allowed next_token.location
~what:(Token.describe `End) ~in_what:"table"
|> add_warning input;
junk input;
(`Stop, return acc_row acc_cell, next_token.location)
| `Right_brace ->
junk input;
(`Stop, return acc_row acc_cell, next_token.location)
Expand Down Expand Up @@ -1385,7 +1403,7 @@ and light_table_row ~parent_markup ~last_loc input =
which is consumed. *)
and heavy_table ~parent_markup ~parent_markup_location input =
let rec consume_rows acc ~last_loc =
Reader.until_rbrace input acc >>> fun next_token ->
Reader.until_rbrace_or_eof input acc >>> fun next_token ->
match next_token.Loc.value with
| `Begin_table_row as token ->
junk input;
Expand All @@ -1411,7 +1429,7 @@ and heavy_table ~parent_markup ~parent_markup_location input =
which is consumed. *)
and heavy_table_row ~parent_markup input =
let rec consume_cell_items acc =
Reader.until_rbrace input acc >>> fun next_token ->
Reader.until_rbrace_or_eof input acc >>> fun next_token ->
match next_token.Loc.value with
| `Begin_table_cell kind as token ->
junk input;
Expand Down
21 changes: 14 additions & 7 deletions src/parser/test/test.ml
Original file line number Diff line number Diff line change
Expand Up @@ -3533,7 +3533,8 @@ let%expect_test _ =
((output (((f.ml (1 0) (1 3)) (unordered heavy ()))))
(warnings
( "File \"f.ml\", line 1, characters 3-3:\
\nEnd of text is not allowed in '{ul ...}' (bulleted list)."
\nEnd of text is not allowed in '{ul ...}' (bulleted list).\
\nSuggestion: try to add '}' at the end of the list content."
"File \"f.ml\", line 1, characters 0-3:\
\n'{ul ...}' (bulleted list) should not be empty."))) |}]

Expand Down Expand Up @@ -3567,9 +3568,11 @@ 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 11-11:\
\nEnd of text is not allowed in '{li ...}' (list item)."
\nEnd of text is not allowed in '{li ...}' (list item).\
\nSuggestion: try to add '}' at the end of the list content."
"File \"f.ml\", line 1, characters 11-11:\
\nEnd of text is not allowed in '{ul ...}' (bulleted list)."))) |}]
\nEnd of text is not allowed in '{ul ...}' (bulleted list).\
\nSuggestion: try to add '}' at the end of the list content."))) |}]

let unterminated_left_curly_brace =
test "{ul {- foo";
Expand All @@ -3581,9 +3584,11 @@ let%expect_test _ =
((((f.ml (1 7) (1 10)) (paragraph (((f.ml (1 7) (1 10)) (word foo)))))))))))
(warnings
( "File \"f.ml\", line 1, characters 10-10:\
\nEnd of text is not allowed in '{- ...}' (list item)."
\nEnd of text is not allowed in '{- ...}' (list item).\
\nSuggestion: try to add '}' at the end of the list content."
"File \"f.ml\", line 1, characters 10-10:\
\nEnd of text is not allowed in '{ul ...}' (bulleted list)."))) |}]
\nEnd of text is not allowed in '{ul ...}' (bulleted list).\
\nSuggestion: try to add '}' at the end of the list content."))) |}]

let empty_li_styntax =
test "{ul {li }}";
Expand Down Expand Up @@ -5083,7 +5088,8 @@ let%expect_test _ =
\n']}' is not allowed in '{ul ...}' (bulleted list).\
\nSuggestion: move ']}' into a list item, '{li ...}' or '{- ...}'."
"File \"f.ml\", line 1, characters 6-6:\
\nEnd of text is not allowed in '{ul ...}' (bulleted list)."
\nEnd of text is not allowed in '{ul ...}' (bulleted list).\
\nSuggestion: try to add '}' at the end of the list content."
"File \"f.ml\", line 1, characters 0-3:\
\n'{ul ...}' (bulleted list) should not be empty."))) |}]

Expand All @@ -5096,7 +5102,8 @@ let%expect_test _ =
( "File \"f.ml\", line 1, characters 4-7:\
\n'{li ...}' (list item) should not be empty."
"File \"f.ml\", line 1, characters 11-11:\
\nEnd of text is not allowed in '{ul ...}' (bulleted list)."))) |}]
\nEnd of text is not allowed in '{ul ...}' (bulleted list).\
\nSuggestion: try to add '}' at the end of the list content."))) |}]

let right_bracket_in_heading =
test "{2 ]}";
Expand Down
24 changes: 24 additions & 0 deletions src/parser/test/test_tables.ml
Original file line number Diff line number Diff line change
Expand Up @@ -82,6 +82,18 @@ let%expect_test _ =
(align "no alignment")))))
(warnings ())) |}]

let unclosed_table =
test "{table {tr {td}}";
[%expect
{|
((output
(((f.ml (1 0) (1 16))
(table (syntax heavy) (grid ((row ((data ()))))) (align "no alignment")))))
(warnings
( "File \"f.ml\", line 1, characters 16-16:\
\nEnd of text is not allowed in table.\
\nSuggestion: try to add '}' at the end of table content ('{t ...' or '{table ...' )."))) |}]

let complex_table =
test
{|
Expand Down Expand Up @@ -190,6 +202,18 @@ let%expect_test _ =
(table (syntax light) (grid ()) (align "no alignment")))))
(warnings ())) |}]

let unclosed_table =
test "{t ";
[%expect
{|
((output
(((f.ml (1 0) (1 3))
(table (syntax light) (grid ()) (align "no alignment")))))
(warnings
( "File \"f.ml\", line 1, characters 2-3:\
\nEnd of text is not allowed in table.\
\nSuggestion: try to add '}' at the end of table content ('{t ...' or '{table ...' )."))) |}]

let simple =
test {|
{t
Expand Down
8 changes: 4 additions & 4 deletions test/model/semantics/test.ml
Original file line number Diff line number Diff line change
Expand Up @@ -885,25 +885,25 @@ let%expect_test _ =
test "{ul {li foo @author Bar}}";
[%expect
{|
{"value":[{"`List":["`Unordered",[[{"`Paragraph":[{"`Word":"foo"},"`Space"]},{"`Paragraph":[{"`Word":"@author"},"`Space",{"`Word":" Bar}}"}]}]]]}],"warnings":["File \"f.ml\", line 1, characters 12-25:\n'@author' is not allowed in '{li ...}' (list item).\nSuggestion: move '@author' outside of any other markup.","File \"f.ml\", line 1, characters 25-25:\nEnd of text is not allowed in '{li ...}' (list item).","File \"f.ml\", line 1, characters 25-25:\nEnd of text is not allowed in '{ul ...}' (bulleted list)."]} |}]
{"value":[{"`List":["`Unordered",[[{"`Paragraph":[{"`Word":"foo"},"`Space"]},{"`Paragraph":[{"`Word":"@author"},"`Space",{"`Word":" Bar}}"}]}]]]}],"warnings":["File \"f.ml\", line 1, characters 12-25:\n'@author' is not allowed in '{li ...}' (list item).\nSuggestion: move '@author' outside of any other markup.","File \"f.ml\", line 1, characters 25-25:\nEnd of text is not allowed in '{li ...}' (list item).\nSuggestion: try to add '}' at the end of the list content.","File \"f.ml\", line 1, characters 25-25:\nEnd of text is not allowed in '{ul ...}' (bulleted list).\nSuggestion: try to add '}' at the end of the list content."]} |}]

let in_list_item_at_start =
test "{ul {li @author Foo}}";
[%expect
{|
{"value":[{"`List":["`Unordered",[[{"`Paragraph":[{"`Word":"@author"},"`Space",{"`Word":" Foo}}"}]}]]]}],"warnings":["File \"f.ml\", line 1, characters 8-21:\n'@author' is not allowed in '{li ...}' (list item).\nSuggestion: move '@author' outside of any other markup.","File \"f.ml\", line 1, characters 21-21:\nEnd of text is not allowed in '{li ...}' (list item).","File \"f.ml\", line 1, characters 21-21:\nEnd of text is not allowed in '{ul ...}' (bulleted list)."]} |}]
{"value":[{"`List":["`Unordered",[[{"`Paragraph":[{"`Word":"@author"},"`Space",{"`Word":" Foo}}"}]}]]]}],"warnings":["File \"f.ml\", line 1, characters 8-21:\n'@author' is not allowed in '{li ...}' (list item).\nSuggestion: move '@author' outside of any other markup.","File \"f.ml\", line 1, characters 21-21:\nEnd of text is not allowed in '{li ...}' (list item).\nSuggestion: try to add '}' at the end of the list content.","File \"f.ml\", line 1, characters 21-21:\nEnd of text is not allowed in '{ul ...}' (bulleted list).\nSuggestion: try to add '}' at the end of the list content."]} |}]

let in_list_item_on_new_line =
test "{ul {li foo\n@author Bar}}";
[%expect
{|
{"value":[{"`List":["`Unordered",[[{"`Paragraph":[{"`Word":"foo"}]},{"`Paragraph":[{"`Word":"@author"},"`Space",{"`Word":" Bar}}"}]}]]]}],"warnings":["File \"f.ml\", line 2, characters 0-13:\n'@author' is not allowed in '{li ...}' (list item).\nSuggestion: move '@author' outside of any other markup.","File \"f.ml\", line 2, characters 13-13:\nEnd of text is not allowed in '{li ...}' (list item).","File \"f.ml\", line 2, characters 13-13:\nEnd of text is not allowed in '{ul ...}' (bulleted list)."]} |}]
{"value":[{"`List":["`Unordered",[[{"`Paragraph":[{"`Word":"foo"}]},{"`Paragraph":[{"`Word":"@author"},"`Space",{"`Word":" Bar}}"}]}]]]}],"warnings":["File \"f.ml\", line 2, characters 0-13:\n'@author' is not allowed in '{li ...}' (list item).\nSuggestion: move '@author' outside of any other markup.","File \"f.ml\", line 2, characters 13-13:\nEnd of text is not allowed in '{li ...}' (list item).\nSuggestion: try to add '}' at the end of the list content.","File \"f.ml\", line 2, characters 13-13:\nEnd of text is not allowed in '{ul ...}' (bulleted list).\nSuggestion: try to add '}' at the end of the list content."]} |}]

let in_list =
test "{ul @author Foo}";
[%expect
{|
{"value":[{"`List":["`Unordered",[]]}],"warnings":["File \"f.ml\", line 1, characters 4-16:\n'@author' is not allowed in '{ul ...}' (bulleted list).\nSuggestion: move '@author' outside the list.","File \"f.ml\", line 1, characters 16-16:\nEnd of text is not allowed in '{ul ...}' (bulleted list).","File \"f.ml\", line 1, characters 0-3:\n'{ul ...}' (bulleted list) should not be empty."]} |}]
{"value":[{"`List":["`Unordered",[]]}],"warnings":["File \"f.ml\", line 1, characters 4-16:\n'@author' is not allowed in '{ul ...}' (bulleted list).\nSuggestion: move '@author' outside the list.","File \"f.ml\", line 1, characters 16-16:\nEnd of text is not allowed in '{ul ...}' (bulleted list).\nSuggestion: try to add '}' at the end of the list content.","File \"f.ml\", line 1, characters 0-3:\n'{ul ...}' (bulleted list) should not be empty."]} |}]

let in_code_block =
test "{[@author Foo]}";
Expand Down