summaryrefslogtreecommitdiffstats
path: root/stdlib
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib')
-rw-r--r--stdlib/format.ml5
-rw-r--r--stdlib/format.mli13
2 files changed, 12 insertions, 6 deletions
diff --git a/stdlib/format.ml b/stdlib/format.ml
index 1fcc96995..37c6af8fa 100644
--- a/stdlib/format.ml
+++ b/stdlib/format.ml
@@ -1077,8 +1077,8 @@ let implode_rev s0 = function
(* [mkprintf] is the printf-like function generator: given the
- [to_s] flag that tells if we are printing into a string,
- the [get_out] function that has to be called to get a [ppf] function to
- output onto.
- It generates a [kprintf] function that takes as arguments a [k]
+ output onto,
+ it generates a [kprintf] function that takes as arguments a [k]
continuation function to be called at the end of formatting,
and a printing format string to print the rest of the arguments
according to the format string.
@@ -1313,6 +1313,7 @@ let mkprintf to_s get_out =
let kfprintf k ppf = mkprintf false (fun _ -> ppf) k;;
let ifprintf ppf = Tformat.kapr (fun _ -> Obj.magic ignore);;
+let ikfprintf k ppf = Tformat.kapr (fun _ _ -> Obj.magic (k ppf));;
let fprintf ppf = kfprintf ignore ppf;;
let printf fmt = fprintf std_formatter fmt;;
diff --git a/stdlib/format.mli b/stdlib/format.mli
index bab557f8b..1d4088ad6 100644
--- a/stdlib/format.mli
+++ b/stdlib/format.mli
@@ -640,16 +640,16 @@ val fprintf : out_channel -> ('a, out_channel, unit) format -> 'a;;
It prints [x = 1] within a pretty-printing box.
*)
+val ifprintf : out_channel -> ('a, out_channel, unit) format -> 'a;;
+(** Same as [fprintf] above, but does not print anything.
+ Useful to ignore some material when conditionally printing. *)
+
val printf : ('a, out_channel, unit) format -> 'a;;
(** Same as [fprintf] above, but output on [std_formatter]. *)
val eprintf : ('a, out_channel, unit) format -> 'a;;
(** Same as [fprintf] above, but output on [err_formatter]. *)
-val ifprintf : out_channel -> ('a, out_channel, unit) format -> 'a;;
-(** Same as [fprintf] above, but does not print anything.
- Useful to ignore some material when conditionally printing. *)
-
val sprintf : ('a, unit, string) format -> 'a;;
(** Same as [printf] above, but instead of printing on a formatter,
returns a string containing the result of formatting the arguments.
@@ -678,6 +678,11 @@ val kfprintf : (out_channel -> 'a) -> out_channel ->
(** Same as [fprintf] above, but instead of returning immediately,
passes the formatter to its first argument at the end of printing. *)
+val ikfprintf : (out_channel -> 'a) -> out_channel ->
+ ('b, out_channel, unit, 'a) format4 -> 'b;;
+(** Same as [kfprintf] above, but does not print anything.
+ Useful to ignore some material when conditionally printing. *)
+
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. *)