Skip to content

Commit 7ad9cd9

Browse files
committed
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
1 parent bfa1c0f commit 7ad9cd9

File tree

7 files changed

+25
-6
lines changed

7 files changed

+25
-6
lines changed

VERSION

+1-1
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
3.12.0+dev10 (2009-12-01)
1+
3.12.0+dev11 (2009-12-01)
22

33
# The version string is the first line of this file.
44
# It must be in the format described in stdlib/sys.mli

boot/ocamlc

2.53 KB
Binary file not shown.

boot/ocamldep

2.53 KB
Binary file not shown.

boot/ocamllex

1 Byte
Binary file not shown.

parsing/lexer.mll

+3-1
Original file line numberDiff line numberDiff line change
@@ -250,7 +250,8 @@ rule token = parse
250250
{ token lexbuf }
251251
| "_"
252252
{ UNDERSCORE }
253-
| "~" { TILDE }
253+
| "~"
254+
{ TILDE }
254255
| "~" lowercase identchar * ':'
255256
{ let s = Lexing.lexeme lexbuf in
256257
let name = String.sub s 1 (String.length s - 2) in
@@ -382,6 +383,7 @@ rule token = parse
382383
383384
| "!=" { INFIXOP0 "!=" }
384385
| "+" { PLUS }
386+
| "+." { PLUSDOT }
385387
| "-" { MINUS }
386388
| "-." { MINUSDOT }
387389

parsing/parser.mly

+18-2
Original file line numberDiff line numberDiff line change
@@ -98,6 +98,12 @@ let mkuminus name arg =
9898
| _ ->
9999
mkexp(Pexp_apply(mkoperator ("~" ^ name) 1, ["", arg]))
100100

101+
let mkuplus name arg =
102+
match name, arg.pexp_desc with
103+
| "+", desc -> mkexp desc
104+
| _ ->
105+
mkexp(Pexp_apply(mkoperator ("~" ^ name) 1, ["", arg]))
106+
101107
let rec mktailexp = function
102108
[] ->
103109
ghexp(Pexp_construct(Lident "[]", None, false))
@@ -281,6 +287,7 @@ let pat_of_label lbl =
281287
%token OR
282288
/* %token PARSER */
283289
%token PLUS
290+
%token PLUSDOT
284291
%token <string> PREFIXOP
285292
%token PRIVATE
286293
%token QUESTION
@@ -356,10 +363,10 @@ The precedences must be listed from low to high.
356363
%left INFIXOP0 EQUAL LESS GREATER /* expr (e OP e OP e) */
357364
%right INFIXOP1 /* expr (e OP e OP e) */
358365
%right COLONCOLON /* expr (e :: e :: e) */
359-
%left INFIXOP2 PLUS MINUS MINUSDOT /* expr (e OP e OP e) */
366+
%left INFIXOP2 PLUS PLUSDOT MINUS MINUSDOT /* expr (e OP e OP e) */
360367
%left INFIXOP3 STAR /* expr (e OP e OP e) */
361368
%right INFIXOP4 /* expr (e OP e OP e) */
362-
%nonassoc prec_unary_minus /* unary - */
369+
%nonassoc prec_unary_minus prec_unary_plus /* unary - */
363370
%nonassoc prec_constant_constructor /* cf. simple_expr (C versus C x) */
364371
%nonassoc prec_constr_appl /* above AS BAR COLONCOLON COMMA */
365372
%nonassoc below_SHARP
@@ -877,6 +884,8 @@ expr:
877884
{ mkinfix $1 $2 $3 }
878885
| expr PLUS expr
879886
{ mkinfix $1 "+" $3 }
887+
| expr PLUSDOT expr
888+
{ mkinfix $1 "+." $3 }
880889
| expr MINUS expr
881890
{ mkinfix $1 "-" $3 }
882891
| expr MINUSDOT expr
@@ -901,6 +910,8 @@ expr:
901910
{ mkinfix $1 ":=" $3 }
902911
| subtractive expr %prec prec_unary_minus
903912
{ mkuminus $1 $2 }
913+
| additive expr %prec prec_unary_plus
914+
{ mkuplus $1 $2 }
904915
| simple_expr DOT label_longident LESSMINUS expr
905916
{ mkexp(Pexp_setfield($1, $3, $5)) }
906917
| simple_expr DOT LPAREN seq_expr RPAREN LESSMINUS expr
@@ -1481,6 +1492,7 @@ operator:
14811492
| INFIXOP3 { $1 }
14821493
| INFIXOP4 { $1 }
14831494
| PLUS { "+" }
1495+
| PLUSDOT { "+." }
14841496
| MINUS { "-" }
14851497
| MINUSDOT { "-." }
14861498
| STAR { "*" }
@@ -1592,4 +1604,8 @@ subtractive:
15921604
| MINUS { "-" }
15931605
| MINUSDOT { "-." }
15941606
;
1607+
additive:
1608+
| PLUS { "+" }
1609+
| PLUSDOT { "+." }
1610+
;
15951611
%%

stdlib/printf.ml

+3-2
Original file line numberDiff line numberDiff line change
@@ -445,14 +445,15 @@ let format_float_lexeme =
445445

446446
let make_valid_float_lexeme s =
447447
(* Check if s is already a valid lexeme:
448-
in this case do nothing (we should still remove a leading +!),
448+
in this case do nothing (unless we got a leading '+' character that we
449+
should remove ?),
449450
otherwise turn s into a valid Caml lexeme. *)
450451
let l = String.length s in
451452
let rec valid_float_loop i =
452453
if i >= l then s ^ "." else
453454
match s.[i] with
454455
(* Sure, this is already a valid float lexeme. *)
455-
| '.' | 'e' | 'E' -> s
456+
| '.' | 'e' | 'E' -> s
456457
| _ -> valid_float_loop (i + 1) in
457458

458459
valid_float_loop 0 in

0 commit comments

Comments
 (0)