Skip to content

Commit

Permalink
Enforce precision in printf %F
Browse files Browse the repository at this point in the history
  • Loading branch information
proux01 committed Feb 23, 2019
1 parent 64603e7 commit 7088cf8
Show file tree
Hide file tree
Showing 2 changed files with 12 additions and 7 deletions.
15 changes: 10 additions & 5 deletions stdlib/camlinternalFormat.ml
Expand Up @@ -221,6 +221,9 @@ let default_float_precision = -6
necessary". For the other FP formats, we take the absolute value
of the precision, hence 6 digits by default. *)

(* Default precision for OCaml float printing (%F). *)
let default_ocaml_float_precision = 12

(******************************************************************************)
(* Externals *)

Expand Down Expand Up @@ -1408,9 +1411,8 @@ let format_of_iconvn = function

(* Generate the format_float first argument form a float_conv. *)
let format_of_fconv fconv prec =
if fconv = Float_F then "%.12g" else
let prec = abs prec in
let symb = char_of_fconv fconv in
let symb = if fconv = Float_F then 'g' else char_of_fconv fconv in
let buf = buffer_create 16 in
buffer_add_char buf '%';
bprint_fconv_flag buf fconv;
Expand Down Expand Up @@ -1730,10 +1732,13 @@ and make_float_padding_precision : type x y a b c d e f .
((b, c) acc -> f) -> (b, c) acc ->
(a, b, c, d, e, f) fmt ->
(x, y) padding -> (y, float -> a) precision -> float_conv -> x =
let default_float_precision fconv =
if fconv = Float_F then default_ocaml_float_precision
else default_float_precision in
fun k acc fmt pad prec fconv -> match pad, prec with
| No_padding, No_precision ->
fun x ->
let str = convert_float fconv default_float_precision x in
let str = convert_float fconv (default_float_precision fconv) x in
make_printf k (Acc_data_string (acc, str)) fmt
| No_padding, Lit_precision p ->
fun x ->
Expand All @@ -1745,7 +1750,7 @@ and make_float_padding_precision : type x y a b c d e f .
make_printf k (Acc_data_string (acc, str)) fmt
| Lit_padding (padty, w), No_precision ->
fun x ->
let str = convert_float fconv default_float_precision x in
let str = convert_float fconv (default_float_precision fconv) x in
let str' = fix_padding padty w str in
make_printf k (Acc_data_string (acc, str')) fmt
| Lit_padding (padty, w), Lit_precision p ->
Expand All @@ -1758,7 +1763,7 @@ and make_float_padding_precision : type x y a b c d e f .
make_printf k (Acc_data_string (acc, str)) fmt
| Arg_padding padty, No_precision ->
fun w x ->
let str = convert_float fconv default_float_precision x in
let str = convert_float fconv (default_float_precision fconv) x in
let str' = fix_padding padty w str in
make_printf k (Acc_data_string (acc, str')) fmt
| Arg_padding padty, Lit_precision p ->
Expand Down
4 changes: 2 additions & 2 deletions stdlib/printf.mli
Expand Up @@ -110,8 +110,8 @@ val fprintf : out_channel -> ('a, out_channel, unit) format -> 'a
The optional [precision] is a dot [.] followed by an integer
indicating how many digits follow the decimal point in the [%f],
[%e], and [%E] conversions. For instance, [%.4f] prints a [float] with
4 fractional digits.
[%F], [%e], [%E], [%g], [%G], [%h], and [%H] conversions.
For instance, [%.4f] prints a [float] with 4 fractional digits.
The integer in a [width] or [precision] can also be specified as
[*], in which case an extra integer argument is taken to specify
Expand Down

0 comments on commit 7088cf8

Please sign in to comment.