summaryrefslogtreecommitdiffstats
path: root/stdlib/printf.ml
diff options
context:
space:
mode:
authorPierre Weis <Pierre.Weis@inria.fr>2009-12-07 16:40:39 +0000
committerPierre Weis <Pierre.Weis@inria.fr>2009-12-07 16:40:39 +0000
commit7ad9cd975bc5fdbbf6d050fa167a289e58a63d59 (patch)
treede2966d3d35e3295c70db65622304aad7612d822 /stdlib/printf.ml
parentbfa1c0f2ecd21f6fe85ac0355eb57f3b75ed0844 (diff)
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
Diffstat (limited to 'stdlib/printf.ml')
-rw-r--r--stdlib/printf.ml5
1 files changed, 3 insertions, 2 deletions
diff --git a/stdlib/printf.ml b/stdlib/printf.ml
index 6121daf3f..2d2ea5e35 100644
--- a/stdlib/printf.ml
+++ b/stdlib/printf.ml
@@ -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