To deal with printf output for %F format, adding a unary + operator.

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@9454 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Pierre Weis 2009-12-07 16:40:39 +00:00
parent bfa1c0f2ec
commit 7ad9cd975b
7 changed files with 25 additions and 6 deletions

View File

@ -1,4 +1,4 @@
3.12.0+dev10 (2009-12-01)
3.12.0+dev11 (2009-12-01)
# The version string is the first line of this file.
# It must be in the format described in stdlib/sys.mli

Binary file not shown.

Binary file not shown.

Binary file not shown.

View File

@ -250,7 +250,8 @@ rule token = parse
{ token lexbuf }
| "_"
{ UNDERSCORE }
| "~" { TILDE }
| "~"
{ TILDE }
| "~" lowercase identchar * ':'
{ let s = Lexing.lexeme lexbuf in
let name = String.sub s 1 (String.length s - 2) in
@ -382,6 +383,7 @@ rule token = parse
| "!=" { INFIXOP0 "!=" }
| "+" { PLUS }
| "+." { PLUSDOT }
| "-" { MINUS }
| "-." { MINUSDOT }

View File

@ -98,6 +98,12 @@ let mkuminus name arg =
| _ ->
mkexp(Pexp_apply(mkoperator ("~" ^ name) 1, ["", arg]))
let mkuplus name arg =
match name, arg.pexp_desc with
| "+", desc -> mkexp desc
| _ ->
mkexp(Pexp_apply(mkoperator ("~" ^ name) 1, ["", arg]))
let rec mktailexp = function
[] ->
ghexp(Pexp_construct(Lident "[]", None, false))
@ -281,6 +287,7 @@ let pat_of_label lbl =
%token OR
/* %token PARSER */
%token PLUS
%token PLUSDOT
%token <string> PREFIXOP
%token PRIVATE
%token QUESTION
@ -356,10 +363,10 @@ The precedences must be listed from low to high.
%left INFIXOP0 EQUAL LESS GREATER /* expr (e OP e OP e) */
%right INFIXOP1 /* expr (e OP e OP e) */
%right COLONCOLON /* expr (e :: e :: e) */
%left INFIXOP2 PLUS MINUS MINUSDOT /* expr (e OP e OP e) */
%left INFIXOP2 PLUS PLUSDOT MINUS MINUSDOT /* expr (e OP e OP e) */
%left INFIXOP3 STAR /* expr (e OP e OP e) */
%right INFIXOP4 /* expr (e OP e OP e) */
%nonassoc prec_unary_minus /* unary - */
%nonassoc prec_unary_minus prec_unary_plus /* unary - */
%nonassoc prec_constant_constructor /* cf. simple_expr (C versus C x) */
%nonassoc prec_constr_appl /* above AS BAR COLONCOLON COMMA */
%nonassoc below_SHARP
@ -877,6 +884,8 @@ expr:
{ mkinfix $1 $2 $3 }
| expr PLUS expr
{ mkinfix $1 "+" $3 }
| expr PLUSDOT expr
{ mkinfix $1 "+." $3 }
| expr MINUS expr
{ mkinfix $1 "-" $3 }
| expr MINUSDOT expr
@ -901,6 +910,8 @@ expr:
{ mkinfix $1 ":=" $3 }
| subtractive expr %prec prec_unary_minus
{ mkuminus $1 $2 }
| additive expr %prec prec_unary_plus
{ mkuplus $1 $2 }
| simple_expr DOT label_longident LESSMINUS expr
{ mkexp(Pexp_setfield($1, $3, $5)) }
| simple_expr DOT LPAREN seq_expr RPAREN LESSMINUS expr
@ -1481,6 +1492,7 @@ operator:
| INFIXOP3 { $1 }
| INFIXOP4 { $1 }
| PLUS { "+" }
| PLUSDOT { "+." }
| MINUS { "-" }
| MINUSDOT { "-." }
| STAR { "*" }
@ -1592,4 +1604,8 @@ subtractive:
| MINUS { "-" }
| MINUSDOT { "-." }
;
additive:
| PLUS { "+" }
| PLUSDOT { "+." }
;
%%

View File

@ -445,14 +445,15 @@ let format_float_lexeme =
let make_valid_float_lexeme s =
(* Check if s is already a valid lexeme:
in this case do nothing (we should still remove a leading +!),
in this case do nothing (unless we got a leading '+' character that we
should remove ?),
otherwise turn s into a valid Caml lexeme. *)
let l = String.length s in
let rec valid_float_loop i =
if i >= l then s ^ "." else
match s.[i] with
(* Sure, this is already a valid float lexeme. *)
| '.' | 'e' | 'E' -> s
| '.' | 'e' | 'E' -> s
| _ -> valid_float_loop (i + 1) in
valid_float_loop 0 in