Skip to content

Commit df92865

Browse files
authored
Warn when a list or table is not closed (#1050)
1 parent 71cd0b2 commit df92865

File tree

6 files changed

+68
-18
lines changed

6 files changed

+68
-18
lines changed

CHANGES.md

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -35,6 +35,10 @@ Tags:
3535
### Changed
3636
- Style: Adjusted line height in the TOC to improve readability (@sorawee, #1045)
3737

38+
### Fixed
39+
- Warn and exit when table(s) is not closed (@lubegasimon, #1050)
40+
- Hint when list(s) is not closed (@lubegasimon, #1050)
41+
3842
# 2.3.0
3943

4044
### Added

src/parser/parse_error.ml

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -81,3 +81,8 @@ let truncated_code_block_meta : Loc.span -> Warning.t =
8181

8282
let truncated_code_block : Loc.span -> Warning.t =
8383
Warning.make ~suggestion:"add ']}'." "Missing end of code block."
84+
85+
let end_not_allowed : in_what:string -> Loc.span -> Warning.t =
86+
fun ~in_what ->
87+
Warning.make ~suggestion:"add '}'." "End of text is not allowed in %s."
88+
in_what

src/parser/syntax.ml

Lines changed: 17 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -118,13 +118,18 @@ module Table = struct
118118
end
119119

120120
module Reader = struct
121-
let until_rbrace input acc =
121+
let until_rbrace_or_eof input acc =
122122
let rec consume () =
123123
let next_token = peek input in
124124
match next_token.value with
125125
| `Right_brace ->
126126
junk input;
127127
`End (acc, next_token.location)
128+
| `End ->
129+
Parse_error.end_not_allowed next_token.location ~in_what:"table"
130+
|> add_warning input;
131+
junk input;
132+
`End (acc, next_token.location)
128133
| `Space _ | `Single_newline _ | `Blank_line _ ->
129134
junk input;
130135
consume ()
@@ -1227,7 +1232,7 @@ and explicit_list_items :
12271232
let next_token = peek input in
12281233
match next_token.value with
12291234
| `End ->
1230-
Parse_error.not_allowed next_token.location ~what:(Token.describe `End)
1235+
Parse_error.end_not_allowed next_token.location
12311236
~in_what:(Token.describe parent_markup)
12321237
|> add_warning input;
12331238
(List.rev acc, next_token.location)
@@ -1275,8 +1280,8 @@ and explicit_list_items :
12751280
(match token_after_list_item.value with
12761281
| `Right_brace -> junk input
12771282
| `End ->
1278-
Parse_error.not_allowed token_after_list_item.location
1279-
~what:(Token.describe `End) ~in_what:(Token.describe token)
1283+
Parse_error.end_not_allowed token_after_list_item.location
1284+
~in_what:(Token.describe token)
12801285
|> add_warning input);
12811286

12821287
let acc = content :: acc in
@@ -1310,7 +1315,7 @@ and explicit_list_items :
13101315
which is consumed. *)
13111316
and light_table ~parent_markup ~parent_markup_location input =
13121317
let rec consume_rows acc ~last_loc =
1313-
Reader.until_rbrace input acc >>> fun next_token ->
1318+
Reader.until_rbrace_or_eof input acc >>> fun next_token ->
13141319
match next_token.Loc.value with
13151320
| `Bar | #token_that_always_begins_an_inline_element -> (
13161321
let next, row, last_loc =
@@ -1340,6 +1345,11 @@ and light_table_row ~parent_markup ~last_loc input =
13401345
let return row cell = List.rev (push_cells row cell) in
13411346
let next_token = peek input in
13421347
match next_token.value with
1348+
| `End ->
1349+
Parse_error.end_not_allowed next_token.location ~in_what:"table"
1350+
|> add_warning input;
1351+
junk input;
1352+
(`Stop, return acc_row acc_cell, next_token.location)
13431353
| `Right_brace ->
13441354
junk input;
13451355
(`Stop, return acc_row acc_cell, next_token.location)
@@ -1385,7 +1395,7 @@ and light_table_row ~parent_markup ~last_loc input =
13851395
which is consumed. *)
13861396
and heavy_table ~parent_markup ~parent_markup_location input =
13871397
let rec consume_rows acc ~last_loc =
1388-
Reader.until_rbrace input acc >>> fun next_token ->
1398+
Reader.until_rbrace_or_eof input acc >>> fun next_token ->
13891399
match next_token.Loc.value with
13901400
| `Begin_table_row as token ->
13911401
junk input;
@@ -1411,7 +1421,7 @@ and heavy_table ~parent_markup ~parent_markup_location input =
14111421
which is consumed. *)
14121422
and heavy_table_row ~parent_markup input =
14131423
let rec consume_cell_items acc =
1414-
Reader.until_rbrace input acc >>> fun next_token ->
1424+
Reader.until_rbrace_or_eof input acc >>> fun next_token ->
14151425
match next_token.Loc.value with
14161426
| `Begin_table_cell kind as token ->
14171427
junk input;

src/parser/test/test.ml

Lines changed: 14 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -3533,7 +3533,8 @@ let%expect_test _ =
35333533
((output (((f.ml (1 0) (1 3)) (unordered heavy ()))))
35343534
(warnings
35353535
( "File \"f.ml\", line 1, characters 3-3:\
3536-
\nEnd of text is not allowed in '{ul ...}' (bulleted list)."
3536+
\nEnd of text is not allowed in '{ul ...}' (bulleted list).\
3537+
\nSuggestion: add '}'."
35373538
"File \"f.ml\", line 1, characters 0-3:\
35383539
\n'{ul ...}' (bulleted list) should not be empty."))) |}]
35393540

@@ -3567,9 +3568,11 @@ let%expect_test _ =
35673568
((((f.ml (1 8) (1 11)) (paragraph (((f.ml (1 8) (1 11)) (word foo)))))))))))
35683569
(warnings
35693570
( "File \"f.ml\", line 1, characters 11-11:\
3570-
\nEnd of text is not allowed in '{li ...}' (list item)."
3571+
\nEnd of text is not allowed in '{li ...}' (list item).\
3572+
\nSuggestion: add '}'."
35713573
"File \"f.ml\", line 1, characters 11-11:\
3572-
\nEnd of text is not allowed in '{ul ...}' (bulleted list)."))) |}]
3574+
\nEnd of text is not allowed in '{ul ...}' (bulleted list).\
3575+
\nSuggestion: add '}'."))) |}]
35733576

35743577
let unterminated_left_curly_brace =
35753578
test "{ul {- foo";
@@ -3581,9 +3584,11 @@ let%expect_test _ =
35813584
((((f.ml (1 7) (1 10)) (paragraph (((f.ml (1 7) (1 10)) (word foo)))))))))))
35823585
(warnings
35833586
( "File \"f.ml\", line 1, characters 10-10:\
3584-
\nEnd of text is not allowed in '{- ...}' (list item)."
3587+
\nEnd of text is not allowed in '{- ...}' (list item).\
3588+
\nSuggestion: add '}'."
35853589
"File \"f.ml\", line 1, characters 10-10:\
3586-
\nEnd of text is not allowed in '{ul ...}' (bulleted list)."))) |}]
3590+
\nEnd of text is not allowed in '{ul ...}' (bulleted list).\
3591+
\nSuggestion: add '}'."))) |}]
35873592

35883593
let empty_li_styntax =
35893594
test "{ul {li }}";
@@ -5083,7 +5088,8 @@ let%expect_test _ =
50835088
\n']}' is not allowed in '{ul ...}' (bulleted list).\
50845089
\nSuggestion: move ']}' into a list item, '{li ...}' or '{- ...}'."
50855090
"File \"f.ml\", line 1, characters 6-6:\
5086-
\nEnd of text is not allowed in '{ul ...}' (bulleted list)."
5091+
\nEnd of text is not allowed in '{ul ...}' (bulleted list).\
5092+
\nSuggestion: add '}'."
50875093
"File \"f.ml\", line 1, characters 0-3:\
50885094
\n'{ul ...}' (bulleted list) should not be empty."))) |}]
50895095

@@ -5096,7 +5102,8 @@ let%expect_test _ =
50965102
( "File \"f.ml\", line 1, characters 4-7:\
50975103
\n'{li ...}' (list item) should not be empty."
50985104
"File \"f.ml\", line 1, characters 11-11:\
5099-
\nEnd of text is not allowed in '{ul ...}' (bulleted list)."))) |}]
5105+
\nEnd of text is not allowed in '{ul ...}' (bulleted list).\
5106+
\nSuggestion: add '}'."))) |}]
51005107

51015108
let right_bracket_in_heading =
51025109
test "{2 ]}";

src/parser/test/test_tables.ml

Lines changed: 24 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -82,6 +82,18 @@ let%expect_test _ =
8282
(align "no alignment")))))
8383
(warnings ())) |}]
8484

85+
let unclosed_table =
86+
test "{table {tr {td}}";
87+
[%expect
88+
{|
89+
((output
90+
(((f.ml (1 0) (1 16))
91+
(table (syntax heavy) (grid ((row ((data ()))))) (align "no alignment")))))
92+
(warnings
93+
( "File \"f.ml\", line 1, characters 16-16:\
94+
\nEnd of text is not allowed in table.\
95+
\nSuggestion: add '}'."))) |}]
96+
8597
let complex_table =
8698
test
8799
{|
@@ -190,6 +202,18 @@ let%expect_test _ =
190202
(table (syntax light) (grid ()) (align "no alignment")))))
191203
(warnings ())) |}]
192204

205+
let unclosed_table =
206+
test "{t ";
207+
[%expect
208+
{|
209+
((output
210+
(((f.ml (1 0) (1 3))
211+
(table (syntax light) (grid ()) (align "no alignment")))))
212+
(warnings
213+
( "File \"f.ml\", line 1, characters 2-3:\
214+
\nEnd of text is not allowed in table.\
215+
\nSuggestion: add '}'."))) |}]
216+
193217
let simple =
194218
test {|
195219
{t

test/model/semantics/test.ml

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -885,25 +885,25 @@ let%expect_test _ =
885885
test "{ul {li foo @author Bar}}";
886886
[%expect
887887
{|
888-
{"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)."]} |}]
888+
{"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: add '}'.","File \"f.ml\", line 1, characters 25-25:\nEnd of text is not allowed in '{ul ...}' (bulleted list).\nSuggestion: add '}'."]} |}]
889889

890890
let in_list_item_at_start =
891891
test "{ul {li @author Foo}}";
892892
[%expect
893893
{|
894-
{"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)."]} |}]
894+
{"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: add '}'.","File \"f.ml\", line 1, characters 21-21:\nEnd of text is not allowed in '{ul ...}' (bulleted list).\nSuggestion: add '}'."]} |}]
895895

896896
let in_list_item_on_new_line =
897897
test "{ul {li foo\n@author Bar}}";
898898
[%expect
899899
{|
900-
{"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)."]} |}]
900+
{"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: add '}'.","File \"f.ml\", line 2, characters 13-13:\nEnd of text is not allowed in '{ul ...}' (bulleted list).\nSuggestion: add '}'."]} |}]
901901

902902
let in_list =
903903
test "{ul @author Foo}";
904904
[%expect
905905
{|
906-
{"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."]} |}]
906+
{"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: add '}'.","File \"f.ml\", line 1, characters 0-3:\n'{ul ...}' (bulleted list) should not be empty."]} |}]
907907

908908
let in_code_block =
909909
test "{[@author Foo]}";

0 commit comments

Comments
 (0)