1 (***********************************************************************)
5 (* Xavier Leroy and Pierre Weis, projet Cristal, INRIA Rocquencourt *)
7 (* Copyright 1996 Institut National de Recherche en Informatique et *)
8 (* en Automatique. All rights reserved. This file is distributed *)
9 (* under the terms of the GNU Library General Public License, with *)
10 (* the special exception on linking described in file ../LICENSE. *)
12 (***********************************************************************)
16 (** Formatted output functions. *)
18 val fprintf
: out_channel
-> ('a
, out_channel
, unit) format
-> 'a
19 (** [fprintf outchan format arg1 ... argN] formats the arguments
20 [arg1] to [argN] according to the format string [format], and
21 outputs the resulting string on the channel [outchan].
23 The format is a character string which contains two types of
24 objects: plain characters, which are simply copied to the output
25 channel, and conversion specifications, each of which causes
26 conversion and printing of arguments.
28 Conversion specifications have the following form:
30 [% \[flags\] \[width\] \[.precision\] type]
32 In short, a conversion specification consists in the [%] character,
33 followed by optional modifiers and a type which is made of one or
34 two characters. The types and their meanings are:
36 - [d], [i], [n], [l], [L], or [N]: convert an integer argument to
38 - [u]: convert an integer argument to unsigned decimal.
39 - [x]: convert an integer argument to unsigned hexadecimal,
40 using lowercase letters.
41 - [X]: convert an integer argument to unsigned hexadecimal,
42 using uppercase letters.
43 - [o]: convert an integer argument to unsigned octal.
44 - [s]: insert a string argument.
45 - [S]: insert a string argument in Caml syntax (double quotes, escapes).
46 - [c]: insert a character argument.
47 - [C]: insert a character argument in Caml syntax (single quotes, escapes).
48 - [f]: convert a floating-point argument to decimal notation,
49 in the style [dddd.ddd].
50 - [F]: convert a floating-point argument to Caml syntax ([dddd.]
51 or [dddd.ddd] or [d.ddd e+-dd]).
52 - [e] or [E]: convert a floating-point argument to decimal notation,
53 in the style [d.ddd e+-dd] (mantissa and exponent).
54 - [g] or [G]: convert a floating-point argument to decimal notation,
55 in style [f] or [e], [E] (whichever is more compact).
56 - [B]: convert a boolean argument to the string [true] or [false]
57 - [b]: convert a boolean argument (for backward compatibility; do not
59 - [ld], [li], [lu], [lx], [lX], [lo]: convert an [int32] argument to
60 the format specified by the second letter (decimal, hexadecimal, etc).
61 - [nd], [ni], [nu], [nx], [nX], [no]: convert a [nativeint] argument to
62 the format specified by the second letter.
63 - [Ld], [Li], [Lu], [Lx], [LX], [Lo]: convert an [int64] argument to
64 the format specified by the second letter.
65 - [a]: user-defined printer. Takes two arguments and applies the
66 first one to [outchan] (the current output channel) and to the
67 second argument. The first argument must therefore have type
68 [out_channel -> 'b -> unit] and the second ['b].
69 The output produced by the function is inserted in the output of
70 [fprintf] at the current point.
71 - [t]: same as [%a], but takes only one argument (with type
72 [out_channel -> unit]) and apply it to [outchan].
73 - [\{ fmt %\}]: convert a format string argument. The argument must
74 have the same type as the internal format string [fmt].
75 - [( fmt %)]: format string substitution. Takes a format string
76 argument and substitutes it to the internal format string [fmt]
77 to print following arguments. The argument must have the same
79 - [!]: take no argument and flush the output.
80 - [%]: take no argument and output one [%] character.
82 The optional [flags] are:
83 - [-]: left-justify the output (default is right justification).
84 - [0]: for numerical conversions, pad with zeroes instead of spaces.
85 - [+]: for numerical conversions, prefix number with a [+] sign if positive.
86 - space: for numerical conversions, prefix number with a space if positive.
87 - [#]: request an alternate formatting style for numbers.
89 The optional [width] is an integer indicating the minimal
90 width of the result. For instance, [%6d] prints an integer,
91 prefixing it with spaces to fill at least 6 characters.
93 The optional [precision] is a dot [.] followed by an integer
94 indicating how many digits follow the decimal point in the [%f],
95 [%e], and [%E] conversions. For instance, [%.4f] prints a [float] with
98 The integer in a [width] or [precision] can also be specified as
99 [*], in which case an extra integer argument is taken to specify
100 the corresponding [width] or [precision]. This integer argument
101 precedes immediately the argument to print.
102 For instance, [%.*f] prints a [float] with as many fractional
103 digits as the value of the argument given before the float. *)
105 val printf
: ('a
, out_channel
, unit) format
-> 'a
106 (** Same as {!Printf.fprintf}, but output on [stdout]. *)
108 val eprintf
: ('a
, out_channel
, unit) format
-> 'a
109 (** Same as {!Printf.fprintf}, but output on [stderr]. *)
111 val ifprintf
: 'a
-> ('b
, 'a
, unit) format
-> 'b
112 (** Same as {!Printf.fprintf}, but does not print anything.
113 Useful to ignore some material when conditionally printing. *)
115 val sprintf
: ('a
, unit, string) format
-> 'a
116 (** Same as {!Printf.fprintf}, but instead of printing on an output channel,
117 return a string containing the result of formatting the arguments. *)
119 val bprintf
: Buffer.t
-> ('a
, Buffer.t
, unit) format
-> 'a
120 (** Same as {!Printf.fprintf}, but instead of printing on an output channel,
121 append the formatted arguments to the given extensible buffer
122 (see module {!Buffer}). *)
124 (** Formatted output functions with continuations. *)
125 val kfprintf
: (out_channel
-> 'a
) -> out_channel
->
126 ('b
, out_channel
, unit, 'a
) format4
-> 'b
;;
127 (** Same as [fprintf], but instead of returning immediately,
128 passes the out channel to its first argument at the end of printing. *)
130 val ksprintf
: (string -> 'a
) -> ('b
, unit, string, 'a
) format4
-> 'b
;;
131 (** Same as [sprintf] above, but instead of returning the string,
132 passes it to the first argument. *)
134 val kbprintf
: (Buffer.t
-> 'a
) -> Buffer.t
->
135 ('b
, Buffer.t
, unit, 'a
) format4
-> 'b
;;
136 (** Same as [bprintf], but instead of returning immediately,
137 passes the buffer to its first argument at the end of printing. *)
139 val kprintf
: (string -> 'a
) -> ('b
, unit, string, 'a
) format4
-> 'b
;;
140 (** A deprecated synonym for [ksprintf]. *)
144 (* For system use only. Don't call directly. *)
146 module CamlinternalPr
: sig
151 val index_of_int
: int -> index
;;
152 external int_of_index
: index
-> int = "%identity";;
153 external unsafe_index_of_int
: int -> index
= "%identity";;
155 val succ_index
: index
-> index
;;
157 val sub
: ('a
, 'b
, 'c
, 'd
, 'e
, 'f
) format6
-> index
-> int -> string;;
158 val to_string
: ('a
, 'b
, 'c
, 'd
, 'e
, 'f
) format6
-> string;;
159 external length
: ('a
, 'b
, 'c
, 'd
, 'e
, 'f
) format6
-> int
161 external get
: ('a
, 'b
, 'c
, 'd
, 'e
, 'f
) format6
-> int -> char
162 = "%string_safe_get";;
163 external unsafe_to_string
: ('a
, 'b
, 'c
, 'd
, 'e
, 'f
) format6
-> string
165 external unsafe_get
: ('a
, 'b
, 'c
, 'd
, 'e
, 'f
) format6
-> int -> char
166 = "%string_unsafe_get";;
173 mutable ac_rglr
: int;
174 mutable ac_skip
: int;
175 mutable ac_rdrs
: int;
178 val ac_of_format
: ('a
, 'b
, 'c
, 'd
, 'e
, 'f
) format6
-> ac
;;
181 (('a
, 'b
, 'c
, 'd
, 'e
, 'f
) format6
-> int) ->
182 (('a
, 'b
, 'c
, 'd
, 'e
, 'f
) format6
-> int -> char
-> int) ->
183 char
-> ('a
, 'b
, 'c
, 'd
, 'e
, 'f
) format6
-> int -> int
185 val summarize_format_type
: ('a
, 'b
, 'c
, 'd
, 'e
, 'f
) format6
-> string
187 val scan_format
: ('a
, 'b
, 'c
, 'd
, 'e
, 'f
) format6
->
191 (Sformat.index
-> string -> int -> 'h
) ->
192 (Sformat.index
-> 'i
-> 'j
-> int -> 'h
) ->
193 (Sformat.index
-> 'k
-> int -> 'h
) ->
194 (Sformat.index
-> int -> 'h
) ->
195 (Sformat.index
-> ('l
, 'm
, 'n
, 'o
, 'p
, 'q
) format6
-> int -> 'h
) -> 'h
198 (('a
, 'b
, 'c
, 'd
, 'e
, 'f
) format6
-> Obj.t array
-> 'g
) ->
199 ('a
, 'b
, 'c
, 'd
, 'e
, 'f
) format6
-> 'g