fix let a = ( *) 1 problem

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14012 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Hongbo Zhang 2013-08-18 02:26:00 +00:00
parent 70026195b6
commit 58d23575b7
4 changed files with 6 additions and 6 deletions

View File

@ -308,7 +308,7 @@ module Make (Token : Sig.Camlp4Token)
parse comment (in_comment c); COMMENT (buff_contents c) }
| "*)"
{ warn Comment_not_end (Loc.of_lexbuf lexbuf) ;
lexbuf.lex_curr_pos <- lexbuf.lex_curr_pos - 1;
c.lexbuf.lex_curr_pos <- c.lexbuf.lex_curr_pos - 1;
SYMBOL "*" }
| "<<" (quotchar* as beginning)
{ if quotations c

View File

@ -370,9 +370,9 @@ New syntax:\
parser
[ [: `((KEYWORD "(", _) as tok); xs :] ->
match xs with parser
[ [: `(KEYWORD ("or"|"mod"|"land"|"lor"|"lxor"|"lsl"|"lsr"|"asr" as i), _loc);
`(KEYWORD ")", _); xs :] ->
[: `(LIDENT i, _loc); infix_kwds_filter xs :]
[ [: `(KEYWORD ("or"|"mod"|"land"|"lor"|"lxor"|"lsl"|"lsr"|"asr"|"*" as i) , _loc);
`(KEYWORD ")" , _); xs :] ->
[: `(LIDENT i, _loc); infix_kwds_filter xs :]
| [: xs :] ->
[: `tok; infix_kwds_filter xs :] ]
| [: `x; xs :] -> [: `x; infix_kwds_filter xs :] ];

View File

@ -6464,7 +6464,7 @@ module Struct =
COMMENT (buff_contents c))
| 17 ->
(warn Comment_not_end (Loc.of_lexbuf lexbuf);
lexbuf.lex_curr_pos <- lexbuf.lex_curr_pos - 1;
c.lexbuf.lex_curr_pos <- c.lexbuf.lex_curr_pos - 1;
SYMBOL "*")
| 18 ->
let beginning =

View File

@ -683,7 +683,7 @@ New syntax:\
| Some
((KEYWORD
(("or" | "mod" | "land" | "lor" | "lxor" | "lsl" |
"lsr" | "asr"
"lsr" | "asr" | "*"
as i)),
_loc))
->