Skip to content

Commit 0a1e51c

Browse files
committed
Improve ansi colors tests
show how our pp'd value is outputted Signed-off-by: Rudi Grinberg <[email protected]>
1 parent 3bdde29 commit 0a1e51c

File tree

2 files changed

+17
-4
lines changed

2 files changed

+17
-4
lines changed

otherlibs/stdune-unstable/ansi_color.mli

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -81,6 +81,9 @@ module Style : sig
8181
val escape_sequence : t list -> string
8282
end
8383

84+
val make_printer :
85+
bool Lazy.t -> Format.formatter -> (Style.t list Pp.t -> unit) Staged.t
86+
8487
(** Print to [Format.std_formatter] *)
8588
val print : Style.t list Pp.t -> unit
8689

test/expect-tests/stdune/ansi_color_tests.ml

Lines changed: 14 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -32,11 +32,21 @@ let%expect_test "reproduce #2664" =
3232
for i = 1 to 20 do
3333
f (string_of_int i)
3434
done;
35-
let pp =
36-
Buffer.contents b |> Ansi_color.parse
37-
|> dyn_of_pp (Dyn.Encoder.list Ansi_color.Style.to_dyn)
38-
|> Dyn.pp
35+
let string_with_ansi_colors = Buffer.contents b in
36+
let pp = Ansi_color.parse string_with_ansi_colors in
37+
let ansi_colors_from_pp =
38+
let b = Buffer.create 16 in
39+
let ppf = Format.formatter_of_buffer b in
40+
Staged.unstage (Ansi_color.make_printer (lazy true) ppf) pp;
41+
Buffer.contents b
3942
in
43+
printfn "Original : %S" string_with_ansi_colors;
44+
printfn "From PP : %S" ansi_colors_from_pp;
45+
[%expect
46+
{|
47+
Original : "\027[34m1\027[39m\027[34m2\027[39m\027[34m3\027[39m\027[34m4\027[39m\027[34m5\027[39m\027[34m6\027[39m\027[34m7\027[39m\027[34m8\027[39m\027[34m9\027[39m\027[34m10\027[39m\027[34m11\027[39m\027[34m12\027[39m\027[34m13\027[39m\027[34m14\027[39m\027[34m15\027[39m\027[34m16\027[39m\027[34m17\027[39m\027[34m18\027[39m\027[34m19\027[39m\027[34m20\027[39m"
48+
From PP : "\027[34m1\027[0m\027[34m2\027[0m\027[34m3\027[0m\027[34m4\027[0m\027[34m5\027[0m\027[34m6\027[0m\027[34m7\027[0m\027[34m8\027[0m\027[34m9\027[0m\027[34m10\027[0m\027[34m11\027[0m\027[34m12\027[0m\027[34m13\027[0m\027[34m14\027[0m\027[34m15\027[0m\027[34m16\027[0m\027[34m17\027[0m\027[34m18\027[0m\027[34m19\027[0m\027[34m20\027[0m" |}];
49+
let pp = dyn_of_pp (Dyn.Encoder.list Ansi_color.Style.to_dyn) pp |> Dyn.pp in
4050
Format.printf "%a@.%!" Pp.to_fmt pp;
4151
[%expect
4252
{|

0 commit comments

Comments
 (0)