Skip to content

Commit c236cb6

Browse files
committed
Add fire_notification to rpc_common, to simplify shutdown.
Signed-off-by: Ambre Austen Suhamy <[email protected]>
1 parent 569e150 commit c236cb6

File tree

3 files changed

+62
-39
lines changed

3 files changed

+62
-39
lines changed

bin/rpc/rpc_common.ml

Lines changed: 40 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -39,6 +39,18 @@ let request_exn client request arg =
3939
| Error e -> raise (Dune_rpc.Version_error.E e)
4040
;;
4141

42+
let notify_exn client notification arg =
43+
let open Fiber.O in
44+
let* res =
45+
Client.Versioned.prepare_notification
46+
client
47+
(Dune_rpc.Decl.Notification.witness notification)
48+
in
49+
match res with
50+
| Ok decl -> Client.notification client decl arg
51+
| Error e -> raise (Dune_rpc.Version_error.E e)
52+
;;
53+
4254
let client_term builder f =
4355
let builder = Common.Builder.forbid_builds builder in
4456
let builder = Common.Builder.disable_log_file builder in
@@ -97,6 +109,17 @@ let warn_ignore_arguments lock_held_by =
97109
]
98110
;;
99111

112+
let should_warn ~warn_forwarding builder =
113+
warn_forwarding && not (Common.Builder.equal builder Common.Builder.default)
114+
;;
115+
116+
let send_request ~f connection name =
117+
Dune_rpc_impl.Client.client
118+
connection
119+
(Dune_rpc.Initialize.Request.create ~id:(Dune_rpc.Id.make (Sexp.Atom name)))
120+
~f
121+
;;
122+
100123
let fire_request
101124
~name
102125
~wait
@@ -108,12 +131,23 @@ let fire_request
108131
=
109132
let open Fiber.O in
110133
let* connection = establish_client_session ~wait in
111-
if warn_forwarding && not (Common.Builder.equal builder Common.Builder.default)
112-
then warn_ignore_arguments lock_held_by;
113-
Dune_rpc_impl.Client.client
114-
connection
115-
(Dune_rpc.Initialize.Request.create ~id:(Dune_rpc.Id.make (Sexp.Atom name)))
116-
~f:(fun client -> request_exn client request arg)
134+
if should_warn ~warn_forwarding builder then warn_ignore_arguments lock_held_by;
135+
send_request connection name ~f:(fun client -> request_exn client request arg)
136+
;;
137+
138+
let fire_notification
139+
~name
140+
~wait
141+
?(warn_forwarding = true)
142+
?(lock_held_by = Dune_util.Global_lock.Lock_held_by.Unknown)
143+
builder
144+
notification
145+
arg
146+
=
147+
let open Fiber.O in
148+
let* connection = establish_client_session ~wait in
149+
if should_warn ~warn_forwarding builder then warn_ignore_arguments lock_held_by;
150+
send_request connection name ~f:(fun client -> notify_exn client notification arg)
117151
;;
118152

119153
let wrap_build_outcome_exn ~print_on_success build_outcome =

bin/rpc/rpc_common.mli

Lines changed: 15 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -7,14 +7,6 @@ val active_server_exn : unit -> Dune_rpc.Where.t
77
(** Raise an RPC response error. *)
88
val raise_rpc_error : Dune_rpc.Response.Error.t -> 'a
99

10-
(** Make a request and raise an exception if the preparation for the request
11-
fails in any way. Returns an [Error] if the response errors. *)
12-
val request_exn
13-
: Dune_rpc_client.Client.t
14-
-> ('a, 'b) Dune_rpc.Decl.request
15-
-> 'a
16-
-> 'b Fiber.t
17-
1810
(** Cmdliner term for a generic RPC client. *)
1911
val client_term : Common.Builder.t -> (unit -> 'a Fiber.t) -> 'a
2012

@@ -40,6 +32,21 @@ val fire_request
4032
-> 'a
4133
-> 'b Fiber.t
4234

35+
(** Send a notification to the RPC server. If [wait], it will poll forever until a server is listening.
36+
Should be scheduled by a scheduler that does not come with a RPC server on its own.
37+
38+
[warn_forwarding] defaults to true, warns the user that since a RPC server is running, some arguments are ignored.
39+
[lock_held_by] defaults to [Unknown], is only used to allow error messages to print the PID. *)
40+
val fire_notification
41+
: name:string
42+
-> wait:bool
43+
-> ?warn_forwarding:bool
44+
-> ?lock_held_by:Dune_util.Global_lock.Lock_held_by.t
45+
-> Common.Builder.t
46+
-> 'a Dune_rpc.Decl.notification
47+
-> 'a
48+
-> unit Fiber.t
49+
4350
val wrap_build_outcome_exn
4451
: print_on_success:bool
4552
-> Dune_rpc.Build_outcome_with_diagnostics.t

bin/shutdown.ml

Lines changed: 7 additions & 25 deletions
Original file line numberDiff line numberDiff line change
@@ -1,28 +1,4 @@
11
open Import
2-
module Client = Dune_rpc_client.Client
3-
4-
let send_shutdown cli =
5-
let open Fiber.O in
6-
let* decl =
7-
Client.Versioned.prepare_notification
8-
cli
9-
Dune_rpc_private.Public.Notification.shutdown
10-
in
11-
match decl with
12-
| Ok decl -> Client.notification cli decl ()
13-
| Error e -> raise (Dune_rpc_private.Version_error.E e)
14-
;;
15-
16-
let exec () =
17-
let open Fiber.O in
18-
let where = Rpc.Rpc_common.active_server_exn () in
19-
let* conn = Client.Connection.connect_exn where in
20-
Dune_rpc_impl.Client.client
21-
conn
22-
~f:send_shutdown
23-
(Dune_rpc_private.Initialize.Request.create
24-
~id:(Dune_rpc_private.Id.make (Sexp.Atom "shutdown_cmd")))
25-
;;
262

273
let info =
284
let doc = "Cancel and shutdown any builds in the current workspace." in
@@ -31,7 +7,13 @@ let info =
317

328
let term =
339
let+ builder = Common.Builder.term in
34-
Rpc.Rpc_common.client_term builder exec
10+
Rpc.Rpc_common.client_term
11+
builder
12+
(Rpc.Rpc_common.fire_notification
13+
~name:"shutdown_cmd"
14+
~wait:false
15+
builder
16+
Dune_rpc_private.Procedures.Public.shutdown)
3517
;;
3618

3719
let command = Cmd.v info term

0 commit comments

Comments
 (0)