Disallow .~ in extended indexing operators. (#2106)

Disallow .~ in the lexer to preserve MetaOCaml compatibility.
master
yallop 2018-10-22 22:33:00 +09:00 committed by Damien Doligez
parent ef76e6e630
commit 20f4c6ced3
5 changed files with 21 additions and 4 deletions

View File

@ -15,6 +15,11 @@ Working version
- GPR#1892: Allow shadowing of items coming from an include
(Thomas Refis, review by Gabriel Radanne)
* GPR#2106: .~ is now a reserved keyword, and is no longer available
for use in extended indexing operators
(Jeremy Yallop, review by Gabriel Scherer, Florian Angeletti, and
Damien Doligez)
### Type system:
- GPR#1826: allow expanding a type to a private abbreviation instead of

View File

@ -280,9 +280,9 @@ The following character sequences are also keywords:
%
\begin{alltt}
" != # & && ' ( ) * + , -"
" -. -> . .. : :: := :> ; ;; <"
" <- = > >] >} ? [ [< [> [| ]"
" _ ` { {< | |] || } ~"
" -. -> . .. .~ : :: := :> ; ;;"
" < <- = > >] >} ? [ [< [> [|"
" ] _ ` { {< | |] || } ~"
\end{alltt}
%
Note that the following identifiers are keywords of the Camlp4

View File

@ -27,6 +27,7 @@ val skip_hash_bang: Lexing.lexbuf -> unit
type error =
| Illegal_character of char
| Illegal_escape of string * string option
| Reserved_sequence of string * string option
| Unterminated_comment of Location.t
| Unterminated_string
| Unterminated_string_in_comment of Location.t * Location.t

View File

@ -23,6 +23,7 @@ open Parser
type error =
| Illegal_character of char
| Illegal_escape of string * string option
| Reserved_sequence of string * string option
| Unterminated_comment of Location.t
| Unterminated_string
| Unterminated_string_in_comment of Location.t * Location.t
@ -263,6 +264,12 @@ let prepare_error loc = function
(fun ppf -> match explanation with
| None -> ()
| Some expl -> fprintf ppf ": %s" expl)
| Reserved_sequence (s, explanation) ->
Location.errorf ~loc
"Reserved character sequence: %s%t" s
(fun ppf -> match explanation with
| None -> ()
| Some expl -> fprintf ppf " %s" expl)
| Unterminated_comment _ ->
Location.errorf ~loc "Comment not terminated"
| Unterminated_string ->
@ -305,7 +312,7 @@ let identchar_latin1 =
let symbolchar =
['!' '$' '%' '&' '*' '+' '-' '.' '/' ':' '<' '=' '>' '?' '@' '^' '|' '~']
let dotsymbolchar =
['!' '$' '%' '&' '*' '+' '-' '/' ':' '=' '>' '?' '@' '^' '|' '~']
['!' '$' '%' '&' '*' '+' '-' '/' ':' '=' '>' '?' '@' '^' '|']
let decimal_literal =
['0'-'9'] ['0'-'9' '_']*
let hex_digit =
@ -343,6 +350,9 @@ rule token = parse
{ UNDERSCORE }
| "~"
{ TILDE }
| ".~"
{ error lexbuf
(Reserved_sequence (".~", Some "is reserved for use in MetaOCaml")) }
| "~" (lowercase identchar * as name) ':'
{ check_label_name lexbuf name;
LABEL name }

View File

@ -30,6 +30,7 @@ let rec skip_phrase lexbuf =
| _ -> skip_phrase lexbuf
| exception (Lexer.Error (Lexer.Unterminated_comment _, _)
| Lexer.Error (Lexer.Unterminated_string, _)
| Lexer.Error (Lexer.Reserved_sequence _, _)
| Lexer.Error (Lexer.Unterminated_string_in_comment _, _)
| Lexer.Error (Lexer.Illegal_character _, _)) ->
skip_phrase lexbuf