Skip to content

Commit 409b10e

Browse files
committed
Parser: Fixes following PR review
1 parent c6e9ba7 commit 409b10e

File tree

2 files changed

+27
-28
lines changed

2 files changed

+27
-28
lines changed

src/parser/lexer.mll

Lines changed: 9 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -400,10 +400,6 @@ and token input = parse
400400
| `Eof ->
401401
warning input ~start_offset Parse_error.truncated_code_block_meta;
402402
emit_truncated_code_block ()
403-
| `Invalid_char c ->
404-
warning input ~start_offset
405-
(Parse_error.language_tag_invalid_char lang_tag_ c);
406-
code_block_with_metadata []
407403
}
408404

409405
| "{@" horizontal_space* '['
@@ -767,13 +763,13 @@ and string input = parse
767763
and code_block_metadata_atom input = parse
768764
| '"'
769765
{
770-
let start_offset = Lexing.lexeme_start input.lexbuf + 1 in
766+
let start_offset = Lexing.lexeme_start input.lexbuf in
771767
Buffer.clear string_buffer;
772768
let s = string input lexbuf in
773-
with_location_adjustments ~start_offset ~adjust_end_by:"\"" (fun _ -> Loc.at) input s }
769+
with_location_adjustments ~start_offset (fun _ -> Loc.at) input s }
774770
| (tag_unquoted_atom as value)
775771
{ with_location_adjustments (fun _ -> Loc.at) input value }
776-
| (_ as c)
772+
| ('=' as c)
777773
{ warning input (Parse_error.code_block_tag_invalid_char c);
778774
with_location_adjustments (fun _ -> Loc.at) input "" }
779775

@@ -794,9 +790,12 @@ and code_block_metadata_tail input tag acc = parse
794790
| None ->
795791
warning input (Parse_error.code_block_tag_invalid_char '=');
796792
code_block_metadata_tail input None acc lexbuf }
797-
| (_ # space_char # '[' # '=' as c) [^ '[']* '['
798-
{ warning input (Parse_error.code_block_tag_invalid_char c);
799-
`Ok (List.rev acc)}
793+
| (_ # space_char # '[' # '=' as c) (_ # space_char # '[')*
794+
{
795+
let start_offset = Lexing.lexeme_start input.lexbuf in
796+
let end_offset = start_offset + 1 in
797+
warning input ~start_offset ~end_offset (Parse_error.code_block_tag_invalid_char c);
798+
code_block_metadata_tail input None acc lexbuf }
800799
| eof
801800
{ `Eof }
802801

src/parser/test/test.ml

Lines changed: 18 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -3241,7 +3241,7 @@ let%expect_test _ =
32413241
(warnings
32423242
( "File \"f.ml\", line 1, characters 8-9:\
32433243
\nInvalid character in code block metadata tag '='."
3244-
"File \"f.ml\", line 1, characters 9-14:\
3244+
"File \"f.ml\", line 1, characters 9-10:\
32453245
\nInvalid character in code block metadata tag 'f'.")))
32463246
|}]
32473247

@@ -3267,7 +3267,7 @@ let%expect_test _ =
32673267
(((f.ml (1 0) (1 30))
32683268
(code_block
32693269
(((f.ml (1 2) (1 7)) ocaml)
3270-
((binding ((f.ml (1 9) (1 13)) A) ((f.ml (1 15) (1 20)) hello))))
3270+
((binding ((f.ml (1 8) (1 14)) A) ((f.ml (1 15) (1 20)) hello))))
32713271
((f.ml (1 22) (1 28)) " code ")))))
32723272
(warnings ()))
32733273
|}]
@@ -3281,7 +3281,7 @@ let%expect_test _ =
32813281
(code_block (((f.ml (1 2) (1 7)) ocaml) ())
32823282
((f.ml (1 12) (1 18)) " code ")))))
32833283
(warnings
3284-
( "File \"f.ml\", line 1, characters 7-12:\
3284+
( "File \"f.ml\", line 1, characters 7-8:\
32853285
\nInvalid character in code block metadata tag ','.")))
32863286
|}]
32873287

@@ -3484,13 +3484,13 @@ let%expect_test _ =
34843484
(((f.ml (1 2) (1 7)) ocaml)
34853485
((binding ((f.ml (1 8) (1 11)) env) ((f.ml (1 12) (1 14)) f1))
34863486
(binding ((f.ml (1 15) (1 22)) version) ((f.ml (1 23) (1 27)) 4.06))
3487-
(tag ((f.ml (1 29) (1 51)) "tag with several words"))
3488-
(binding ((f.ml (1 54) (1 66)) "binding with")
3487+
(tag ((f.ml (1 28) (1 52)) "tag with several words"))
3488+
(binding ((f.ml (1 53) (1 67)) "binding with")
34893489
((f.ml (1 68) (1 78)) singleword))
34903490
(binding ((f.ml (1 79) (1 83)) also)
3491-
((f.ml (1 85) (1 95)) "other case"))
3492-
(binding ((f.ml (1 98) (1 112)) "everything has")
3493-
((f.ml (1 115) (1 129)) "multiple words"))))
3491+
((f.ml (1 84) (1 96)) "other case"))
3492+
(binding ((f.ml (1 97) (1 113)) "everything has")
3493+
((f.ml (1 114) (1 130)) "multiple words"))))
34943494
((f.ml (1 132) (1 135)) foo)))))
34953495
(warnings ()))
34963496
|}]
@@ -3515,13 +3515,13 @@ let%expect_test _ =
35153515
((binding ((f.ml (2 9) (2 12)) env) ((f.ml (2 13) (2 15)) f1))
35163516
(binding ((f.ml (3 9) (3 16)) version) ((f.ml (3 17) (3 21)) 4.06))
35173517
(tag ((f.ml (4 9) (4 19)) single_tag))
3518-
(tag ((f.ml (5 10) (5 32)) "tag with several words"))
3519-
(binding ((f.ml (6 10) (6 22)) "binding with")
3518+
(tag ((f.ml (5 9) (5 33)) "tag with several words"))
3519+
(binding ((f.ml (6 9) (6 23)) "binding with")
35203520
((f.ml (6 24) (6 34)) singleword))
35213521
(binding ((f.ml (7 9) (7 13)) also)
3522-
((f.ml (7 15) (7 25)) "other case"))
3523-
(binding ((f.ml (8 10) (8 24)) "everything has")
3524-
((f.ml (8 27) (8 41)) "multiple words"))))
3522+
((f.ml (7 14) (7 26)) "other case"))
3523+
(binding ((f.ml (8 9) (8 25)) "everything has")
3524+
((f.ml (8 26) (8 42)) "multiple words"))))
35253525
((f.ml (9 10) (9 13)) foo)))))
35263526
(warnings ()))
35273527
|}]
@@ -3534,7 +3534,7 @@ let%expect_test _ =
35343534
(((f.ml (1 0) (1 24))
35353535
(code_block
35363536
(((f.ml (1 2) (1 7)) ocaml)
3537-
((binding ((f.ml (1 9) (1 11)) "\"") ((f.ml (1 14) (1 16)) "\""))))
3537+
((binding ((f.ml (1 8) (1 12)) "\"") ((f.ml (1 13) (1 17)) "\""))))
35383538
((f.ml (1 19) (1 22)) foo)))))
35393539
(warnings ()))
35403540
|}]
@@ -3547,7 +3547,7 @@ let%expect_test _ =
35473547
(((f.ml (1 0) (1 20))
35483548
(code_block (((f.ml (1 2) (1 7)) ocaml) ()) ((f.ml (1 15) (1 18)) foo)))))
35493549
(warnings
3550-
( "File \"f.ml\", line 1, characters 9-15:\
3550+
( "File \"f.ml\", line 1, characters 9-10:\
35513551
\nInvalid character in code block metadata tag '\"'.")))
35523552
|}]
35533553

@@ -3558,7 +3558,7 @@ let%expect_test _ =
35583558
((output
35593559
(((f.ml (1 0) (1 19))
35603560
(code_block
3561-
(((f.ml (1 2) (1 7)) ocaml) ((tag ((f.ml (1 9) (1 11)) "\\"))))
3561+
(((f.ml (1 2) (1 7)) ocaml) ((tag ((f.ml (1 8) (1 12)) "\\"))))
35623562
((f.ml (1 14) (1 17)) foo)))))
35633563
(warnings ()))
35643564
|}]
@@ -3571,7 +3571,7 @@ let%expect_test _ =
35713571
((output
35723572
(((f.ml (2 5) (2 28))
35733573
(code_block
3574-
(((f.ml (2 7) (2 12)) ocaml) ((tag ((f.ml (2 14) (2 20)) "a\bc"))))
3574+
(((f.ml (2 7) (2 12)) ocaml) ((tag ((f.ml (2 13) (2 21)) "a\bc"))))
35753575
((f.ml (2 23) (2 26)) foo)))))
35763576
(warnings
35773577
( "File \"f.ml\", line 2, characters 14-16:\
@@ -3591,7 +3591,7 @@ let%expect_test _ =
35913591
(((f.ml (2 5) (2 37))
35923592
(code_block
35933593
(((f.ml (2 7) (2 12)) ocaml)
3594-
((binding ((f.ml (2 14) (2 20)) "a\bc") ((f.ml (2 23) (2 29)) xyz))))
3594+
((binding ((f.ml (2 13) (2 21)) "a\bc") ((f.ml (2 22) (2 30)) xyz))))
35953595
((f.ml (2 32) (2 35)) foo)))))
35963596
(warnings
35973597
( "File \"f.ml\", line 2, characters 14-16:\

0 commit comments

Comments
 (0)