summaryrefslogtreecommitdiffstats
path: root/stdlib/printf.ml
diff options
context:
space:
mode:
authorPierre Weis <Pierre.Weis@inria.fr>2013-03-19 08:06:06 +0000
committerPierre Weis <Pierre.Weis@inria.fr>2013-03-19 08:06:06 +0000
commita2c500f8bc8ef98a33fa55689eb81f2bbd968b93 (patch)
tree0aa03384b09058d314e576d8d87501d899d6ed31 /stdlib/printf.ml
parent559521f1253830ff97916a62715c4ee86e28cc1c (diff)
Details.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@13413 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/printf.ml')
-rw-r--r--stdlib/printf.ml24
1 files changed, 12 insertions, 12 deletions
diff --git a/stdlib/printf.ml b/stdlib/printf.ml
index 1797b8e80..ad24c873a 100644
--- a/stdlib/printf.ml
+++ b/stdlib/printf.ml
@@ -149,21 +149,21 @@ let extract_format fmt start stop widths =
;;
let extract_format_int conv fmt start stop widths =
- let sfmt = extract_format fmt start stop widths in
- match conv with
- | 'n' | 'N' ->
- sfmt.[String.length sfmt - 1] <- 'u';
- sfmt
- | _ -> sfmt
+ let sfmt = extract_format fmt start stop widths in
+ match conv with
+ | 'n' | 'N' ->
+ sfmt.[String.length sfmt - 1] <- 'u';
+ sfmt
+ | _ -> sfmt
;;
let extract_format_float conv fmt start stop widths =
- let sfmt = extract_format fmt start stop widths in
- match conv with
- | 'F' ->
- sfmt.[String.length sfmt - 1] <- 'g';
- sfmt
- | _ -> sfmt
+ let sfmt = extract_format fmt start stop widths in
+ match conv with
+ | 'F' ->
+ sfmt.[String.length sfmt - 1] <- 'g';
+ sfmt
+ | _ -> sfmt
;;
(* Returns the position of the next character following the meta format