Module Printf


module Printf: sig .. end
Formatted output functions.

val fprintf : out_channel ->
('a, out_channel, unit) format -> 'a
fprintf outchan format arg1 ... argN formats the arguments arg1 to argN according to the format string format, and outputs the resulting string on the channel outchan.

The format is a character string which contains two types of objects: plain characters, which are simply copied to the output channel, and conversion specifications, each of which causes conversion and printing of arguments.

Conversion specifications have the following form:

% [flags] [width] [.precision] type

In short, a conversion specification consists in the % character, followed by optional modifiers and a type which is made of one or two characters. The types and their meanings are:

The optional flags are: The optional width is an integer indicating the minimal width of the result. For instance, %6d prints an integer, prefixing it with spaces to fill at least 6 characters.

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.

The integer in a width or precision can also be specified as *, in which case an extra integer argument is taken to specify the corresponding width or precision. This integer argument precedes immediately the argument to print. For instance, %.*f prints a float with as many fractional digits as the value of the argument given before the float.

val printf : ('a, out_channel, unit) format -> 'a
Same as Printf.fprintf, but output on stdout.
val eprintf : ('a, out_channel, unit) format -> 'a
Same as Printf.fprintf, but output on stderr.
val ifprintf : 'a -> ('b, 'a, unit) format -> 'b
Same as Printf.fprintf, but does not print anything. Useful to ignore some material when conditionally printing.
Since 3.10.0
val sprintf : ('a, unit, string) format -> 'a
Same as Printf.fprintf, but instead of printing on an output channel, return a string containing the result of formatting the arguments.
val bprintf : Buffer.t -> ('a, Buffer.t, unit) format -> 'a
Same as Printf.fprintf, but instead of printing on an output channel, append the formatted arguments to the given extensible buffer (see module Buffer).

Formatted output functions with continuations.
val kfprintf : (out_channel -> 'a) ->
out_channel ->
('b, out_channel, unit, 'a) format4 -> 'b
Same as fprintf, but instead of returning immediately, passes the out channel to its first argument at the end of printing.
Since 3.09.0
val ksprintf : (string -> 'a) -> ('b, unit, string, 'a) format4 -> 'b
Same as sprintf above, but instead of returning the string, passes it to the first argument.
Since 3.09.0
val kbprintf : (Buffer.t -> 'a) ->
Buffer.t -> ('b, Buffer.t, unit, 'a) format4 -> 'b
Same as bprintf, but instead of returning immediately, passes the buffer to its first argument at the end of printing.
Since 3.10.0
val kprintf : (string -> 'a) -> ('b, unit, string, 'a) format4 -> 'b
A deprecated synonym for ksprintf.