amelioration message d'erreur illegal character

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@2721 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Damien Doligez 1999-12-30 17:09:37 +00:00
parent 0991853b80
commit 50606c59fc
3 changed files with 7 additions and 7 deletions

View File

@ -17,7 +17,7 @@
val token: Lexing.lexbuf -> Parser.token
type error =
| Illegal_character
| Illegal_character of char
| Unterminated_comment
| Unterminated_string
| Unterminated_string_in_comment

View File

@ -19,7 +19,7 @@ open Misc
open Parser
type error =
| Illegal_character
| Illegal_character of char
| Unterminated_comment
| Unterminated_string
| Unterminated_string_in_comment
@ -151,8 +151,8 @@ let comment_start_pos = ref [];;
open Formatmsg
let report_error = function
Illegal_character ->
print_string "Illegal character"
Illegal_character c ->
printf "Illegal character (%s)" (Char.escaped c)
| Unterminated_comment ->
print_string "Comment not terminated"
| Unterminated_string ->
@ -304,7 +304,7 @@ rule token = parse
{ INFIXOP3(Lexing.lexeme lexbuf) }
| eof { EOF }
| _
{ raise (Error(Illegal_character,
{ raise (Error(Illegal_character ((Lexing.lexeme lexbuf).[0]),
Lexing.lexeme_start lexbuf, Lexing.lexeme_end lexbuf)) }
and comment = parse

View File

@ -27,7 +27,7 @@ let rec skip_phrase lexbuf =
| Lexer.Error (Lexer.Unterminated_comment, _, _) -> ()
| Lexer.Error (Lexer.Unterminated_string, _, _) -> ()
| Lexer.Error (Lexer.Unterminated_string_in_comment, _, _) -> ()
| Lexer.Error (Lexer.Illegal_character,_,_) -> skip_phrase lexbuf
| Lexer.Error (Lexer.Illegal_character _,_,_) -> skip_phrase lexbuf
;;
let maybe_skip_phrase lexbuf =
@ -45,7 +45,7 @@ let wrap parsing_fun lexbuf =
| Lexer.Error(Lexer.Unterminated_comment, _, _) as err -> raise err
| Lexer.Error(Lexer.Unterminated_string, _, _) as err -> raise err
| Lexer.Error(Lexer.Unterminated_string_in_comment, _, _) as err -> raise err
| Lexer.Error(Lexer.Illegal_character, _, _) as err ->
| Lexer.Error(Lexer.Illegal_character _, _, _) as err ->
if !Location.input_name = "" then skip_phrase lexbuf;
raise err
| Syntaxerr.Error _ as err ->