Merge pull request #9865 from raphael-proust/pp_print_seq

Stdlib.Format: add pp_print_seq
master
Florian Angeletti 2020-09-14 16:52:11 +02:00 committed by GitHub
commit bc4d260de7
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
6 changed files with 75 additions and 0 deletions

View File

@ -146,6 +146,9 @@ Working version
### Standard library:
- #9865: add Format.pp_print_seq
(Raphaël Proust, review by Nicolás Ojeda Bär)
- #9781: add injectivity annotations to parameterized abstract types
(Jeremy Yallop, review by Nicolás Ojeda Bär)

View File

@ -263,6 +263,7 @@ stdlib__format.cmo : \
stdlib__string.cmi \
stdlib.cmi \
stdlib__stack.cmi \
stdlib__seq.cmi \
stdlib__queue.cmi \
stdlib__list.cmi \
stdlib__int.cmi \
@ -274,6 +275,7 @@ stdlib__format.cmx : \
stdlib__string.cmx \
stdlib.cmx \
stdlib__stack.cmx \
stdlib__seq.cmx \
stdlib__queue.cmx \
stdlib__list.cmx \
stdlib__int.cmx \
@ -283,6 +285,7 @@ stdlib__format.cmx : \
stdlib__format.cmi
stdlib__format.cmi : \
stdlib.cmi \
stdlib__seq.cmi \
stdlib__buffer.cmi
stdlib__fun.cmo : \
stdlib__printexc.cmi \

View File

@ -1191,6 +1191,22 @@ let rec pp_print_list ?(pp_sep = pp_print_cut) pp_v ppf = function
pp_sep ppf ();
pp_print_list ~pp_sep pp_v ppf vs
(* To format a sequence *)
let rec pp_print_seq_in ~pp_sep pp_v ppf seq =
match seq () with
| Seq.Nil -> ()
| Seq.Cons (v, seq) ->
pp_sep ppf ();
pp_v ppf v;
pp_print_seq_in ~pp_sep pp_v ppf seq
let pp_print_seq ?(pp_sep = pp_print_cut) pp_v ppf seq =
match seq () with
| Seq.Nil -> ()
| Seq.Cons (v, seq) ->
pp_v ppf v;
pp_print_seq_in ~pp_sep pp_v ppf seq
(* To format free-flowing text *)
let pp_print_text ppf s =
let len = String.length s in

View File

@ -1084,6 +1084,19 @@ val pp_print_list:
@since 4.02.0
*)
val pp_print_seq:
?pp_sep:(formatter -> unit -> unit) ->
(formatter -> 'a -> unit) -> (formatter -> 'a Seq.t -> unit)
(** [pp_print_seq ?pp_sep pp_v ppf s] prints items of sequence [s],
using [pp_v] to print each item, and calling [pp_sep]
between items ([pp_sep] defaults to {!pp_print_cut}.
Does nothing on empty sequences.
This function does not terminate on infinite sequences.
@since 4.12
*)
val pp_print_text : formatter -> string -> unit
(** [pp_print_text ppf s] prints [s] with spaces and newlines respectively
printed using {!pp_print_space} and {!pp_force_newline}.

View File

@ -0,0 +1,33 @@
(* TEST
include testing
*)
(*
A test file for the Format module.
*)
open Testing;;
open Format;;
let say s = Printf.printf s;;
let pp_print_intseq = pp_print_seq ~pp_sep:(fun fmt () -> pp_print_char fmt ' ') pp_print_int;;
try
say "empty\n%!";
test (asprintf "%a%!" pp_print_intseq Seq.empty = "");
say "\nmisc\n%!";
test (asprintf "%a" pp_print_intseq (List.to_seq [0]) = "0");
test (asprintf "%a" pp_print_intseq (List.to_seq [0;1;2]) = "0 1 2");
test (asprintf "%a" pp_print_intseq (List.to_seq [0;0]) = "0 0");
say "\nend of tests\n%!";
with e ->
say "unexpected exception: %s\n%!" (Printexc.to_string e);
test false;
;;

View File

@ -0,0 +1,7 @@
empty
0
misc
1 2 3
end of tests
All tests succeeded.