Skip to content

Commit

Permalink
_
Browse files Browse the repository at this point in the history
  • Loading branch information
rgrinberg committed Mar 3, 2023
1 parent 923e6cf commit fc62d95
Show file tree
Hide file tree
Showing 2 changed files with 4 additions and 13 deletions.
8 changes: 4 additions & 4 deletions otherlibs/stdune/src/ansi_color.ml
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,7 @@ end = struct

let write_to_buffer buf c =
Buffer.add_string buf "38;5;";
Buffer.add_string buf (int_of_char c |> string_of_int)
int_of_char c |> Int.to_string |> Buffer.add_string buf
end

module RGB24 : sig
Expand Down Expand Up @@ -54,11 +54,11 @@ end = struct

let write_to_buffer buf t =
Buffer.add_string buf "38;2;";
Buffer.add_string buf (string_of_int (red t));
red t |> Int.to_string |> Buffer.add_string buf;
Buffer.add_char buf ';';
Buffer.add_string buf (string_of_int (green t));
green t |> Int.to_string |> Buffer.add_string buf;
Buffer.add_char buf ';';
Buffer.add_string buf (string_of_int (blue t))
blue t |> Int.to_string |> Buffer.add_string buf
end

module Style = struct
Expand Down
9 changes: 0 additions & 9 deletions otherlibs/stdune/src/ansi_color.mli
Original file line number Diff line number Diff line change
Expand Up @@ -2,10 +2,6 @@ module RGB8 : sig
(** 8 bit RGB color *)
type t

(** [RGB8.of_int rgb] creates an [RGB8.t] value from an [int] value. The value
is masked by [0xFF] leaving only the last 8 bits. *)
val of_int : int -> t

(** [RGB8.to_int t] returns the [int] value of [t] as an 8 bit integer. *)
val to_int : t -> int
end
Expand All @@ -22,11 +18,6 @@ module RGB24 : sig

(** [RGB24.blue t] returns the blue component of [t] *)
val blue : t -> int

(** [RGB24.create ~r ~g ~b] creates an [RGB24.t] value from [int] values for
red, green and blue. These values are masked by [0xFF] leaving only the
last 8 bits. *)
val create : r:int -> g:int -> b:int -> t
end

module Style : sig
Expand Down

0 comments on commit fc62d95

Please sign in to comment.