Skip to content

Commit

Permalink
rpc: serialize user message styles
Browse files Browse the repository at this point in the history
Signed-off-by: Ali Caglayan <alizter@gmail.com>
  • Loading branch information
Alizter committed Sep 7, 2023
1 parent 0566d5c commit 6c5860b
Show file tree
Hide file tree
Showing 13 changed files with 771 additions and 138 deletions.
2 changes: 2 additions & 0 deletions doc/changes/8516.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
- RPC message styles are now serialised meaning that RPC diagnostics keep their Ansi
styling. (#8516, fixes #6921, @Alizter)
2 changes: 2 additions & 0 deletions otherlibs/dune-rpc/dune_rpc.ml
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,8 @@ module V1 = struct
module Message = Message
module Where = Where
module Registry = Registry
module Ansi_color = Ansi_color
module User_message = User_message
include Public

module Client = struct
Expand Down
108 changes: 108 additions & 0 deletions otherlibs/dune-rpc/dune_rpc.mli
Original file line number Diff line number Diff line change
Expand Up @@ -86,6 +86,112 @@ module V1 : sig
val to_string_absolute : t -> string
end

module Ansi_color : sig
module RGB8 : sig
(** 8-bit RGB color *)
type t

(** [of_int i] creates an 8-bit color from the least significant 8 bits of [i]. *)
val of_int : int -> t

(** [to_int t] returns the 8-bit color as an integer in the range [0, 255]. *)
val to_int : t -> int
end

module RGB24 : sig
(** 24-bit RGB color (true color) *)
type t

(** [make ~red ~green ~blue] creates a 24-bit color from the given RGB
components. Each color component should be in the range [0, 255]. *)
val make : red:int -> green:int -> blue:int -> t

(** [red t] returns the red component of the 24-bit color [t]. *)
val red : t -> int

(** [green t] returns the green component of the 24-bit color [t]. *)
val green : t -> int

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

(** [of_int i] creates a 24-bit color from the least significant 24 bits of [i].
Each color components consists of 8 bits. *)
val of_int : int -> t

(** [to_int t] returns the 24-bit color as an integer in the range [0, 0xFFFFFF].
Each color components consists of 8 bits. *)
val to_int : t -> int
end

module Style : sig
(** Ansi Terminal Styles *)
type t =
[ `Fg_default
| `Fg_black
| `Fg_red
| `Fg_green
| `Fg_yellow
| `Fg_blue
| `Fg_magenta
| `Fg_cyan
| `Fg_white
| `Fg_bright_black
| `Fg_bright_red
| `Fg_bright_green
| `Fg_bright_yellow
| `Fg_bright_blue
| `Fg_bright_magenta
| `Fg_bright_cyan
| `Fg_bright_white
| `Fg_8_bit_color of RGB8.t
| `Fg_24_bit_color of RGB24.t
| `Bg_default
| `Bg_black
| `Bg_red
| `Bg_green
| `Bg_yellow
| `Bg_blue
| `Bg_magenta
| `Bg_cyan
| `Bg_white
| `Bg_bright_black
| `Bg_bright_red
| `Bg_bright_green
| `Bg_bright_yellow
| `Bg_bright_blue
| `Bg_bright_magenta
| `Bg_bright_cyan
| `Bg_bright_white
| `Bg_8_bit_color of RGB8.t
| `Bg_24_bit_color of RGB24.t
| `Bold
| `Dim
| `Italic
| `Underline
]
end
end

module User_message : sig
(** User Message Styles *)
module Style : sig
type t =
| Loc
| Error
| Warning
| Kwd
| Id
| Prompt
| Hint
| Details
| Ok
| Debug
| Success
| Ansi_styles of Ansi_color.Style.t list
end
end

module Target : sig
type t =
| Path of string
Expand Down Expand Up @@ -121,6 +227,7 @@ module V1 : sig

val loc : t -> Loc.t
val message : t -> unit Pp.t
val message_with_style : t -> User_message.Style.t Pp.t
end

type t
Expand All @@ -129,6 +236,7 @@ module V1 : sig
val loc : t -> Loc.t option
val id : t -> Id.t
val message : t -> unit Pp.t
val message_with_style : t -> User_message.Style.t Pp.t
val severity : t -> severity option
val promotion : t -> Promotion.t list

Expand Down
Loading

0 comments on commit 6c5860b

Please sign in to comment.