Skip to content

Commit

Permalink
warn when a table is unclosed
Browse files Browse the repository at this point in the history
  • Loading branch information
lubegasimon committed Nov 30, 2023
1 parent a60e987 commit 3a5f9af
Show file tree
Hide file tree
Showing 2 changed files with 16 additions and 4 deletions.
4 changes: 4 additions & 0 deletions src/parser/parse_error.ml
Original file line number Diff line number Diff line change
Expand Up @@ -81,3 +81,7 @@ 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 unclosed_table : Loc.span -> Warning.t =
Warning.make ~suggestion:"try to add '}' at the end of table content."
"Unclosed table '{t ...' or '{table ...'"
16 changes: 12 additions & 4 deletions src/parser/syntax.ml
Original file line number Diff line number Diff line change
Expand Up @@ -118,13 +118,17 @@ 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.unclosed_table next_token.location |> add_warning input;
junk input;
`End (acc, next_token.location)
| `Space _ | `Single_newline _ | `Blank_line _ ->
junk input;
consume ()
Expand Down Expand Up @@ -1310,7 +1314,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 +1344,10 @@ 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.unclosed_table next_token.location |> 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 +1393,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 +1419,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

0 comments on commit 3a5f9af

Please sign in to comment.