PR#6816: lexer raise for literal number followed by alphanum

(Hugo Heuzard)

The following were previously accepted and are now (rightly) rejected:
  (fun x y -> x,y) 0O56789;;
  (fun x y z t a b -> x,y,z,t,a,b) 0b0l0l0O10l0O6789l0e2;;

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@16003 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Gabriel Scherer 2015-04-12 10:31:14 +00:00
parent 3376907929
commit bbb896f4b1
2 changed files with 6 additions and 0 deletions

View File

@ -24,6 +24,7 @@ type error =
| Unterminated_string_in_comment of Location.t * Location.t
| Keyword_as_label of string
| Literal_overflow of string
| Invalid_literal of string
;;
exception Error of error * Location.t

View File

@ -25,6 +25,7 @@ type error =
| Unterminated_string_in_comment of Location.t * Location.t
| Keyword_as_label of string
| Literal_overflow of string
| Invalid_literal of string
;;
exception Error of error * Location.t;;
@ -248,6 +249,8 @@ let report_error ppf = function
| Literal_overflow ty ->
fprintf ppf "Integer literal exceeds the range of representable \
integers of type %s" ty
| Invalid_literal s ->
fprintf ppf "Invalid literal %s" s
let () =
Location.register_error_of_exn
@ -350,6 +353,8 @@ rule token = parse
NATIVEINT (cvt_nativeint_literal (Lexing.lexeme lexbuf))
with Failure _ ->
raise (Error(Literal_overflow "nativeint", Location.curr lexbuf)) }
| (float_literal | int_literal) identchar+
{ raise (Error(Invalid_literal (Lexing.lexeme lexbuf), Location.curr lexbuf)) }
| "\""
{ reset_string_buffer();
is_in_string := true;