Skip to content

Commit

Permalink
Display a clear error on empty character literals ''
Browse files Browse the repository at this point in the history
Before:
> # '';;
> Error: Syntax error

After:
> # '';;
> Error: Illegal empty character literal ''
> Hint: Did you mean ' ' or a type variable 'a?

Before, this input would get correctly lexed into QUOTE QUOTE and then
fail in the parser with a generic "Syntax error" message. (Even if we
had better error messages in the parser, here the parser-level error
would not be very illuminating as ' is never the start of a valid
expression or structure item).

Fixes ocaml#10196.
  • Loading branch information
gasche committed Feb 4, 2021
1 parent d14b3ec commit 908c5f2
Show file tree
Hide file tree
Showing 3 changed files with 12 additions and 0 deletions.
4 changes: 4 additions & 0 deletions Changes
Expand Up @@ -83,6 +83,10 @@ Working version
the source code than the point explicitly shown in the error message.
(François Pottier, review by Gabriel Scherer and Frédéric Bour.)

- #10196, #10197: better error message on empty character literals ''.
(Gabriel Scherer, review by David Allsopp and Florian Angeletti,
report by Robin Björklin)

### Internal/compiler-libs changes:

- #9650, #9651: keep refactoring the pattern-matching compiler
Expand Down
1 change: 1 addition & 0 deletions parsing/lexer.mli
Expand Up @@ -31,6 +31,7 @@ type error =
| Unterminated_comment of Location.t
| Unterminated_string
| Unterminated_string_in_comment of Location.t * Location.t
| Empty_character_literal
| Keyword_as_label of string
| Invalid_literal of string
| Invalid_directive of string * string option
Expand Down
7 changes: 7 additions & 0 deletions parsing/lexer.mll
Expand Up @@ -27,6 +27,7 @@ type error =
| Unterminated_comment of Location.t
| Unterminated_string
| Unterminated_string_in_comment of Location.t * Location.t
| Empty_character_literal
| Keyword_as_label of string
| Invalid_literal of string
| Invalid_directive of string * string option
Expand Down Expand Up @@ -300,6 +301,10 @@ let prepare_error loc = function
Location.errorf ~loc
"This comment contains an unterminated string literal"
~sub:[Location.msg ~loc:literal_loc "String literal begins here"]
| Empty_character_literal ->
Location.errorf ~loc
"Illegal empty character literal ''\n\
Hint: Did you mean ' ' or a type variable 'a?"
| Keyword_as_label kwd ->
Location.errorf ~loc
"`%s' is a keyword, it cannot be used as label name" kwd
Expand Down Expand Up @@ -459,6 +464,8 @@ rule token = parse
{ CHAR(char_for_hexadecimal_code lexbuf 3) }
| "\'" ("\\" _ as esc)
{ error lexbuf (Illegal_escape (esc, None)) }
| "\'\'"
{ error lexbuf Empty_character_literal }
| "(*"
{ let s, loc = wrap_comment_lexer comment lexbuf in
COMMENT (s, loc) }
Expand Down

0 comments on commit 908c5f2

Please sign in to comment.