Skip to content

Commit

Permalink
test: serialize and reserialize RPC error messages
Browse files Browse the repository at this point in the history
We demonstrate a bug with how error messages are serialized. Currently
there are two "Error:" prefixes after serializing and deserializing.
This is because the prefix hasn't been stripped in the initial
serialization. We should strip the prefix since the severity information
is recorded elsewhere in the diagnostic data.

Signed-off-by: Ali Caglayan <alizter@gmail.com>
  • Loading branch information
Alizter committed Aug 19, 2023
1 parent 2bb0a0f commit 692876c
Show file tree
Hide file tree
Showing 5 changed files with 46 additions and 0 deletions.
9 changes: 9 additions & 0 deletions src/dune_engine/build_system.ml
Original file line number Diff line number Diff line change
Expand Up @@ -92,6 +92,15 @@ module Error = struct
| Diagnostic d -> `Diagnostic d.diagnostic
;;

module For_tests = struct
let make ~id ~description () =
match description with
| `Exn exn -> Exn { id; exn }
| `Diagnostic diagnostic ->
Diagnostic { id; diagnostic; dir = None; promotion = None }
;;
end

module Set : sig
type error := t

Expand Down
13 changes: 13 additions & 0 deletions src/dune_engine/build_system.mli
Original file line number Diff line number Diff line change
Expand Up @@ -88,6 +88,7 @@ module Error : sig

module Map : Map.S with type key = t

val gen : unit -> t
val compare : t -> t -> Ordering.t
val to_int : t -> int
val to_dyn : t -> Dyn.t
Expand Down Expand Up @@ -126,6 +127,18 @@ module Error : sig
val current : t -> error Id.Map.t
val empty : t
end

module For_tests : sig
(** Internal helpers for testing purposes. Do not use. *)

(** Construct an [Error.t] *)
val make
: id:Id.t
-> description:
[ `Exn of Exn_with_backtrace.t | `Diagnostic of Compound_user_error.t ]
-> unit
-> t
end
end

(** The current set of active errors. *)
Expand Down
6 changes: 6 additions & 0 deletions src/dune_rpc_impl/dune_rpc_impl.ml
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,12 @@ module Private = Dune_rpc_client.Private
module Watch_mode_config = Watch_mode_config
module Where = Dune_rpc_client.Where

module Diagnostics = struct
module For_tests = struct
let diagnostic_of_error = Diagnostics.diagnostic_of_error
end
end

module Poll_active =
Dune_rpc_private.Registry.Poll
(Fiber)
Expand Down
2 changes: 2 additions & 0 deletions test/expect-tests/dune_rpc/dune
Original file line number Diff line number Diff line change
Expand Up @@ -5,10 +5,12 @@
(libraries
ocaml_config
dune_util
dune_console
dune_rpc_private
dune_rpc_server
dune_rpc_impl
dune_rpc_client
dune_engine
stdune
test_scheduler
csexp
Expand Down
16 changes: 16 additions & 0 deletions test/expect-tests/dune_rpc/dune_rpc_tests.ml
Original file line number Diff line number Diff line change
Expand Up @@ -925,3 +925,19 @@ let%expect_test "print digests for all public RPCs" =
Request: Sexp
Response: 33528f248084297d123a6ebd4c3ddee0 |}]
;;

let%expect_test "serialize and then deserialize error messages" =
let id = Dune_engine.Build_system.Error.Id.gen () in
let main = User_error.make [ Pp.verbatim "Oh no!" ] in
Dune_console.print_user_message main;
let description =
`Diagnostic (Dune_engine.Compound_user_error.make ~main ~related:[])
in
Dune_engine.Build_system.Error.For_tests.make ~id ~description ()
|> Dune_rpc_impl.Diagnostics.For_tests.diagnostic_of_error
|> Dune_rpc_private.Diagnostic.to_user_message
|> Dune_console.print_user_message;
[%expect {|
Error: Oh no!
Error: Error: Oh no! |}]
;;

0 comments on commit 692876c

Please sign in to comment.