update ocaml299to3

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@6143 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Jacques Garrigue 2004-03-10 08:56:01 +00:00
parent 151cc41991
commit f455882521
2 changed files with 12 additions and 5 deletions

View File

@ -19,10 +19,14 @@ dumpobj.cmx: ../parsing/asttypes.cmi ../bytecomp/bytesections.cmx \
../utils/config.cmx ../bytecomp/emitcode.cmx ../typing/ident.cmx \
../bytecomp/instruct.cmx ../bytecomp/lambda.cmx ../bytecomp/opcodes.cmx \
opnames.cmx ../utils/tbl.cmx
lexer299.cmo: ../parsing/location.cmi ../utils/misc.cmi ../utils/warnings.cmi
lexer299.cmx: ../parsing/location.cmx ../utils/misc.cmx ../utils/warnings.cmx
lexer301.cmo: ../parsing/location.cmi ../utils/misc.cmi ../utils/warnings.cmi
lexer301.cmx: ../parsing/location.cmx ../utils/misc.cmx ../utils/warnings.cmx
objinfo.cmo: ../utils/config.cmi ../bytecomp/emitcode.cmi
objinfo.cmx: ../utils/config.cmx ../bytecomp/emitcode.cmx
ocaml299to3.cmo: lexer299.cmo
ocaml299to3.cmx: lexer299.cmx
ocamlcp.cmo: ../driver/main_args.cmi
ocamlcp.cmx: ../driver/main_args.cmx
ocamldep.cmo: ../utils/clflags.cmo ../utils/config.cmi depend.cmi \

View File

@ -15,6 +15,7 @@
(* The lexer definition *)
{
open Lexing
open Misc
type token =
@ -277,7 +278,9 @@ rule token = parse
{ UNDERSCORE }
| lowercase identchar * ':' [ ^ ':' '=' '>']
{ let s = Lexing.lexeme lexbuf in
lexbuf.Lexing.lex_curr_pos <- lexbuf.Lexing.lex_curr_pos - 1;
lexbuf.lex_curr_pos <- lexbuf.lex_curr_pos - 1;
lexbuf.lex_curr_p <-
{lexbuf.lex_curr_p with pos_cnum = lexbuf.lex_curr_p.pos_cnum - 1};
LABEL (String.sub s 0 (String.length s - 2)) }
(*
| lowercase identchar * ':'
@ -320,8 +323,8 @@ rule token = parse
comment lexbuf;
token lexbuf }
| "(*)"
{ let loc = { Location.loc_start = Lexing.lexeme_start lexbuf;
Location.loc_end = Lexing.lexeme_end lexbuf - 1;
{ let loc = { Location.loc_start = Lexing.lexeme_start_p lexbuf;
Location.loc_end = Lexing.lexeme_end_p lexbuf;
Location.loc_ghost = false }
and warn = Warnings.Comment "the start of a comment"
in
@ -331,8 +334,8 @@ rule token = parse
token lexbuf
}
| "*)"
{ let loc = { Location.loc_start = Lexing.lexeme_start lexbuf;
Location.loc_end = Lexing.lexeme_end lexbuf;
{ let loc = { Location.loc_start = Lexing.lexeme_start_p lexbuf;
Location.loc_end = Lexing.lexeme_end_p lexbuf;
Location.loc_ghost = false }
and warn = Warnings.Comment "not the end of a comment"
in