summaryrefslogtreecommitdiffstats
path: root/stdlib
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib')
-rw-r--r--stdlib/format.ml35
-rw-r--r--stdlib/format.mli21
2 files changed, 56 insertions, 0 deletions
diff --git a/stdlib/format.ml b/stdlib/format.ml
index fc2df5128..02222932e 100644
--- a/stdlib/format.ml
+++ b/stdlib/format.ml
@@ -747,6 +747,41 @@ let pp_set_tab state () =
enqueue_advance state elem
;;
+
+(* Convenience functions *)
+
+(* To format a list *)
+let rec pp_print_list ?(pp_sep = pp_print_cut) pp_v ppf = function
+ | [] -> ()
+ | [v] -> pp_v ppf v
+ | v :: vs ->
+ pp_v ppf v;
+ pp_sep ppf ();
+ pp_print_list ~pp_sep pp_v ppf vs
+
+(* To format free-flowing text *)
+let pp_print_text ppf s =
+ let len = String.length s in
+ let left = ref 0 in
+ let right = ref 0 in
+ let flush () =
+ pp_print_string ppf (String.sub s !left (!right - !left));
+ incr right; left := !right;
+ in
+ while (!right <> len) do
+ match s.[!right] with
+ | '\n' ->
+ flush ();
+ pp_force_newline ppf ()
+ | ' ' ->
+ flush (); pp_print_space ppf ()
+ (* there is no specific support for '\t'
+ as it is unclear what a right semantics would be *)
+ | _ -> incr right
+ done;
+ if !left <> len then flush ()
+
+
(**************************************************************
Procedures to control the pretty-printers
diff --git a/stdlib/format.mli b/stdlib/format.mli
index 2df4779c2..1d8662bc6 100644
--- a/stdlib/format.mli
+++ b/stdlib/format.mli
@@ -564,6 +564,27 @@ val pp_get_formatter_out_functions :
evaluation of these primitives. For instance,
[print_string] is equal to [pp_print_string std_formatter]. *)
+(** {6 Convenience formatting functions.} *)
+
+val pp_print_list:
+ ?pp_sep:(formatter -> unit -> unit) ->
+ (formatter -> 'a -> unit) -> (formatter -> 'a list -> unit)
+(** [pp_print_list ?pp_sep pp_v ppf l] prints the list [l]. [pp_v] is
+ used on the elements of [l] and each element is separated by
+ a call to [pp_sep] (defaults to {!pp_print_cut}). Does nothing on
+ empty lists.
+
+ @since 4.02
+*)
+
+val pp_print_text : formatter -> string -> unit
+(** [pp_print_text ppf s] prints [s] with spaces and newlines
+ respectively printed with {!pp_print_space} and
+ {!pp_force_newline}.
+
+ @since 4.02
+*)
+
(** {6 [printf] like functions for pretty-printing.} *)
val fprintf : formatter -> ('a, formatter, unit) format -> 'a;;