summaryrefslogtreecommitdiffstats
path: root/stdlib/camlinternalFormat.ml
diff options
context:
space:
mode:
authorGabriel Scherer <gabriel.scherer@gmail.com>2014-05-12 15:38:14 +0000
committerGabriel Scherer <gabriel.scherer@gmail.com>2014-05-12 15:38:14 +0000
commit11fdab809df9dd9773d100013dee9e41d9fa8404 (patch)
tree6a3a2cffad9c204374d1e1a1ea277ca2b58dbaa6 /stdlib/camlinternalFormat.ml
parent8f7b47a1370884e3683f727dbcb5e8ce2be61110 (diff)
accept and ignore '+' and '-' before precision integers
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14830 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/camlinternalFormat.ml')
-rw-r--r--stdlib/camlinternalFormat.ml17
1 files changed, 14 insertions, 3 deletions
diff --git a/stdlib/camlinternalFormat.ml b/stdlib/camlinternalFormat.ml
index 1c35d7809..acaf16b76 100644
--- a/stdlib/camlinternalFormat.ml
+++ b/stdlib/camlinternalFormat.ml
@@ -1421,11 +1421,22 @@ let fmt_ebb_of_string str =
(_, _, e, f) fmt_ebb =
fun pct_ind str_ind end_ind plus sharp space ign pad ->
if str_ind = end_ind then unexpected_end_of_format end_ind;
- match str.[str_ind] with
- | '0' .. '9' ->
+ let parse_literal str_ind =
let new_ind, prec = parse_positive str_ind end_ind 0 in
parse_conversion pct_ind (new_ind + 1) end_ind plus sharp space ign pad
- (Lit_precision prec) str.[new_ind]
+ (Lit_precision prec) str.[new_ind] in
+ match str.[str_ind] with
+ | '0' .. '9' -> parse_literal str_ind
+ | ('+' | '-') when legacy_behavior ->
+ (* Legacy mode would accept and ignore '+' or '-' before the
+ integer describing the desired precision; not that this
+ cannot happen for padding width, as '+' and '-' already have
+ a semantics there.
+
+ That said, the idea (supported by this tweak) that width and
+ precision literals are "integer literals" in the OCaml sense is
+ still blatantly wrong, as 123_456 or 0xFF are rejected. *)
+ parse_literal (str_ind + 1)
| '*' ->
parse_after_precision pct_ind (str_ind + 1) end_ind plus sharp space ign
pad Arg_precision