val fprintf : Stdlib.out_channel -> ('a, Stdlib.out_channel, unit) Stdlib.format -> 'afprintf outchan format arg1 ... argNformats the argumentsarg1toargNaccording to the format stringformat, and outputs the resulting string on the channeloutchan.The format string 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] typeIn 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:
d,i: convert an integer argument to signed decimal.u,n,l,L, orN: convert an integer argument to unsigned decimal. Warning:n,l,L, andNare used forscanf, and should not be used forprintf.x: convert an integer argument to unsigned hexadecimal, using lowercase letters.X: convert an integer argument to unsigned hexadecimal, using uppercase letters.o: convert an integer argument to unsigned octal.s: insert a string argument.S: convert a string argument to OCaml syntax (double quotes, escapes).c: insert a character argument.C: convert a character argument to OCaml syntax (single quotes, escapes).f: convert a floating-point argument to decimal notation, in the styledddd.ddd.F: convert a floating-point argument to OCaml syntax (dddd.ordddd.dddord.ddd e+-dd).eorE: convert a floating-point argument to decimal notation, in the styled.ddd e+-dd(mantissa and exponent).gorG: convert a floating-point argument to decimal notation, in stylefore,E(whichever is more compact). Moreover, any trailing zeros are removed from the fractional part of the result and the decimal-point character is removed if there is no fractional part remaining.horH: convert a floating-point argument to hexadecimal notation, in the style0xh.hhhh p+-dd(hexadecimal mantissa, exponent in decimal and denotes a power of 2).B: convert a boolean argument to the stringtrueorfalseb: convert a boolean argument (deprecated; do not use in new programs).ld,li,lu,lx,lX,lo: convert anint32argument to the format specified by the second letter (decimal, hexadecimal, etc).nd,ni,nu,nx,nX,no: convert anativeintargument to the format specified by the second letter.Ld,Li,Lu,Lx,LX,Lo: convert anint64argument to the format specified by the second letter.a: user-defined printer. Take two arguments and apply the first one tooutchan(the current output channel) and to the second argument. The first argument must therefore have typeout_channel -> 'b -> unitand the second'b. The output produced by the function is inserted in the output offprintfat the current point.t: same as%a, but take only one argument (with typeout_channel -> unit) and apply it tooutchan.\{ fmt %\}: convert a format string argument to its type digest. The argument must have the same type as the internal format stringfmt.( fmt %): format string substitution. Take a format string argument and substitute it to the internal format stringfmtto print following arguments. The argument must have the same type as the internal format stringfmt.!: take no argument and flush the output.%: take no argument and output one%character.\@: take no argument and output one\@character.,: take no argument and output nothing: a no-op delimiter for conversion specifications.
The optional
flagsare:-: left-justify the output (default is right justification).0: for numerical conversions, pad with zeroes instead of spaces.+: for signed numerical conversions, prefix number with a+sign if positive.- space: for signed numerical conversions, prefix number with a space if positive.
#: request an alternate formatting style for the integer types (x,X,o,lx,lX,lo,Lx,LX,Lo,d,i,u,ld,li,lu,Ld,Li,Lu,nd,ni,nu).
The optional
widthis an integer indicating the minimal width of the result. For instance,%6dprints an integer, prefixing it with spaces to fill at least 6 characters.The optional
precisionis a dot.followed by an integer indicating how many digits follow the decimal point in the%f,%e,%E,%h, and%Hconversions or the maximum number of significant digits to appear for the%F,%gand%Gconversions. For instance,%.4fprints afloatwith 4 fractional digits.The integer in a
widthorprecisioncan also be specified as*, in which case an extra integer argument is taken to specify the correspondingwidthorprecision. This integer argument precedes immediately the argument to print. For instance,%.*fprints afloatwith as many fractional digits as the value of the argument given before the float.
val printf : ('a, Stdlib.out_channel, unit) Stdlib.format -> 'aSame as
Printf.fprintf, but output onstdout.
val eprintf : ('a, Stdlib.out_channel, unit) Stdlib.format -> 'aSame as
Printf.fprintf, but output onstderr.
val sprintf : ('a, unit, string) Stdlib.format -> 'aSame as
Printf.fprintf, but instead of printing on an output channel, return a string containing the result of formatting the arguments.
val bprintf : Stdlib.Buffer.t -> ('a, Stdlib.Buffer.t, unit) Stdlib.format -> 'aSame as
Printf.fprintf, but instead of printing on an output channel, append the formatted arguments to the given extensible buffer (see moduleBuffer).
val ifprintf : 'b -> ('a, 'b, 'c, unit) Stdlib.format4 -> 'aSame as
Printf.fprintf, but does not print anything. Useful to ignore some material when conditionally printing.- since
- 3.10.0
val kfprintf : (Stdlib.out_channel -> 'd) -> Stdlib.out_channel -> ('a, Stdlib.out_channel, unit, 'd) Stdlib.format4 -> 'aSame 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 ikfprintf : ('b -> 'd) -> 'b -> ('a, 'b, 'c, 'd) Stdlib.format4 -> 'aSame as
kfprintfabove, but does not print anything. Useful to ignore some material when conditionally printing.- since
- 4.01.0
val ksprintf : (string -> 'd) -> ('a, unit, string, 'd) Stdlib.format4 -> 'aSame as
sprintfabove, but instead of returning the string, passes it to the first argument.- since
- 3.09.0
val kbprintf : (Stdlib.Buffer.t -> 'd) -> Stdlib.Buffer.t -> ('a, Stdlib.Buffer.t, unit, 'd) Stdlib.format4 -> 'aSame 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 -> 'b) -> ('a, unit, string, 'b) Stdlib.format4 -> 'aA deprecated synonym for
ksprintf.