Skip to content

Commit 66a0766

Browse files
committed
Remove redundant function run_via_rpc
Signed-off-by: Ambre Austen Suhamy <[email protected]>
1 parent a677f99 commit 66a0766

File tree

10 files changed

+80
-115
lines changed

10 files changed

+80
-115
lines changed

bin/build.ml

Lines changed: 10 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -196,16 +196,16 @@ let build =
196196
perform the RPC call.
197197
*)
198198
let targets = Rpc.Rpc_common.prepare_targets targets in
199-
Rpc.Rpc_common.run_via_rpc
200-
~common
201-
~config
202-
(Rpc.Rpc_common.fire_request
203-
~name:"build"
204-
~wait:true
205-
~lock_held_by
206-
builder
207-
Dune_rpc_impl.Decl.build)
208-
targets
199+
Scheduler.go_without_rpc_server ~common ~config (fun () ->
200+
let open Fiber.O in
201+
Rpc.Rpc_common.fire_request
202+
~name:"build"
203+
~wait:true
204+
~lock_held_by
205+
builder
206+
Dune_rpc_impl.Decl.build
207+
targets
208+
>>| Rpc.Rpc_common.wrap_build_outcome_exn ~print_on_success:true)
209209
| Ok () ->
210210
let request setup =
211211
Target.interpret_targets (Common.root common) config setup targets

bin/exec.ml

Lines changed: 8 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -226,16 +226,15 @@ let build_prog_via_rpc_if_necessary ~dir ~no_rebuild builder lock_held_by prog =
226226
(Dune_lang.String_with_vars.make_text Loc.none (Path.to_string path))
227227
in
228228
let targets = Rpc.Rpc_common.prepare_targets [ target ] in
229-
Rpc.Rpc_common.wrap_build_outcome_exn
230-
~print_on_success:false
231-
(Rpc.Rpc_common.fire_request
232-
~name:"build"
233-
~wait:true
234-
~lock_held_by
235-
builder
236-
Dune_rpc_impl.Decl.build)
229+
let open Fiber.O in
230+
Rpc.Rpc_common.fire_request
231+
~name:"build"
232+
~wait:true
233+
~lock_held_by
234+
builder
235+
Dune_rpc_impl.Decl.build
237236
targets
238-
())
237+
>>| Rpc.Rpc_common.wrap_build_outcome_exn ~print_on_success:false)
239238
in
240239
Path.to_absolute_filename path
241240
| Absolute ->

bin/fmt.ml

Lines changed: 9 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -45,25 +45,15 @@ let run_fmt_command ~common ~config ~preview builder =
4545
| Error lock_held_by ->
4646
(* The --preview flag is being ignored by the RPC server, warn the user. *)
4747
if preview then Rpc.Rpc_common.warn_ignore_arguments lock_held_by;
48-
let response =
49-
Scheduler.go_without_rpc_server ~common ~config (fun () ->
50-
Rpc.Rpc_common.fire_request
51-
~name:"format"
52-
~wait:true
53-
~warn_forwarding:false
54-
~lock_held_by
55-
builder
56-
Dune_rpc.Procedures.Public.format
57-
())
58-
in
59-
(match response with
60-
| Ok () -> ()
61-
| Error error ->
62-
User_error.raise
63-
[ Pp.paragraphf
64-
"Error: %s\n%!"
65-
(Dyn.to_string (Dune_rpc.Response.Error.to_dyn error))
66-
])
48+
Scheduler.go_without_rpc_server ~common ~config (fun () ->
49+
Rpc.Rpc_common.fire_request
50+
~name:"format"
51+
~wait:true
52+
~warn_forwarding:false
53+
~lock_held_by
54+
builder
55+
Dune_rpc.Procedures.Public.format
56+
())
6757
;;
6858

6959
let command =

bin/promotion.ml

Lines changed: 10 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -62,16 +62,16 @@ module Apply = struct
6262
let+ () = Fiber.return () in
6363
Diff_promotion.promote_files_registered_in_last_run files_to_promote)
6464
| Error lock_held_by ->
65-
Rpc.Rpc_common.run_via_rpc
66-
~common
67-
~config
68-
(Rpc.Rpc_common.fire_request
69-
~name:"promote_many"
70-
~wait:true
71-
~lock_held_by
72-
builder
73-
Dune_rpc_private.Procedures.Public.promote_many)
74-
files_to_promote
65+
Scheduler.go_without_rpc_server ~common ~config (fun () ->
66+
let open Fiber.O in
67+
Rpc.Rpc_common.fire_request
68+
~name:"promote_many"
69+
~wait:true
70+
~lock_held_by
71+
builder
72+
Dune_rpc_private.Procedures.Public.promote_many
73+
files_to_promote
74+
>>| Rpc.Rpc_common.wrap_build_outcome_exn ~print_on_success:true)
7575
;;
7676

7777
let command = Cmd.v info term

bin/rpc/rpc_build.ml

Lines changed: 2 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -12,10 +12,8 @@ let term =
1212
Rpc_common.fire_request ~name:"build" ~wait builder Dune_rpc_impl.Decl.build targets
1313
in
1414
match response with
15-
| Error (error : Dune_rpc.Response.Error.t) ->
16-
Printf.eprintf "Error: %s\n%!" (Dyn.to_string (Dune_rpc.Response.Error.to_dyn error))
17-
| Ok Success -> print_endline "Success"
18-
| Ok (Failure _) -> print_endline "Failure"
15+
| Success -> print_endline "Success"
16+
| Failure _ -> print_endline "Failure"
1917
;;
2018

2119
let info =

bin/rpc/rpc_common.ml

Lines changed: 11 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -21,17 +21,22 @@ let raise_rpc_error (e : Rpc_error.t) =
2121
User_error.raise
2222
[ Pp.paragraph "Server returned error: "
2323
; Pp.paragraphf "%s (error kind: %s)" e.message (interpret_kind e.kind)
24+
(* CR-soon ElectreAAS: Should we be printing the payload? *)
2425
]
2526
;;
2627

27-
let request_exn client request n =
28+
let request_exn client request arg =
2829
let open Fiber.O in
2930
let* decl =
3031
Client.Versioned.prepare_request client (Dune_rpc.Decl.Request.witness request)
3132
in
3233
match decl with
34+
| Ok decl ->
35+
Client.request client decl arg
36+
>>| (function
37+
| Ok response -> response
38+
| Error e -> raise_rpc_error e)
3339
| Error e -> raise (Dune_rpc.Version_error.E e)
34-
| Ok decl -> Client.request client decl n
3540
;;
3641

3742
let client_term builder f =
@@ -111,15 +116,12 @@ let fire_request
111116
~f:(fun client -> request_exn client request arg)
112117
;;
113118

114-
let wrap_build_outcome_exn ~print_on_success f args () =
115-
let open Fiber.O in
116-
let+ response = f args in
117-
match response with
118-
| Error (error : Rpc_error.t) -> raise_rpc_error error
119-
| Ok Dune_rpc.Build_outcome_with_diagnostics.Success ->
119+
let wrap_build_outcome_exn ~print_on_success build_outcome =
120+
match build_outcome with
121+
| Dune_rpc.Build_outcome_with_diagnostics.Success ->
120122
if print_on_success
121123
then Console.print [ Pp.text "Success" |> Pp.tag User_message.Style.Success ]
122-
| Ok (Failure errors) ->
124+
| Failure errors ->
123125
let error_msg =
124126
match List.length errors with
125127
| 0 ->
@@ -133,10 +135,3 @@ let wrap_build_outcome_exn ~print_on_success f args () =
133135
Console.print_user_message main);
134136
User_error.raise [ error_msg |> Pp.tag User_message.Style.Error ]
135137
;;
136-
137-
let run_via_rpc ~common ~config f args =
138-
Scheduler.go_without_rpc_server
139-
~common
140-
~config
141-
(wrap_build_outcome_exn ~print_on_success:true f args)
142-
;;

bin/rpc/rpc_common.mli

Lines changed: 3 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -13,7 +13,7 @@ val request_exn
1313
: Dune_rpc_client.Client.t
1414
-> ('a, 'b) Dune_rpc.Decl.request
1515
-> 'a
16-
-> ('b, Dune_rpc.Response.Error.t) result Fiber.t
16+
-> 'b Fiber.t
1717

1818
(** Cmdliner term for a generic RPC client. *)
1919
val client_term : Common.Builder.t -> (unit -> 'a Fiber.t) -> 'a
@@ -38,26 +38,12 @@ val fire_request
3838
-> Common.Builder.t
3939
-> ('a, 'b) Dune_rpc.Decl.request
4040
-> 'a
41-
-> ('b, Dune_rpc.Response.Error.t) result Fiber.t
41+
-> 'b Fiber.t
4242

4343
val wrap_build_outcome_exn
4444
: print_on_success:bool
45-
-> ('a
46-
-> (Dune_rpc.Build_outcome_with_diagnostics.t, Dune_rpc.Response.Error.t) result
47-
Fiber.t)
48-
-> 'a
45+
-> Dune_rpc.Build_outcome_with_diagnostics.t
4946
-> unit
50-
-> unit Fiber.t
5147

5248
(** Warn the user that since a RPC server is running, some arguments are ignored. *)
5349
val warn_ignore_arguments : Dune_util.Global_lock.Lock_held_by.t -> unit
54-
55-
(** Schedule a fiber to run via RPC, wrapping any errors. *)
56-
val run_via_rpc
57-
: common:Common.t
58-
-> config:Dune_config_file.Dune_config.t
59-
-> ('a
60-
-> (Dune_rpc.Build_outcome_with_diagnostics.t, Dune_rpc.Response.Error.t) result
61-
Fiber.t)
62-
-> 'a
63-
-> unit

bin/rpc/rpc_ping.ml

Lines changed: 9 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -15,15 +15,15 @@ let term =
1515
Rpc_common.client_term builder
1616
@@ fun () ->
1717
let open Fiber.O in
18-
Rpc_common.fire_request
19-
~name:"ping_cmd"
20-
~wait
21-
builder
22-
Dune_rpc_private.Procedures.Public.ping
23-
()
24-
>>| function
25-
| Ok () -> Console.print [ Pp.text "Server appears to be responding normally" ]
26-
| Error e -> Rpc_common.raise_rpc_error e
18+
let+ () =
19+
Rpc_common.fire_request
20+
~name:"ping_cmd"
21+
~wait
22+
builder
23+
Dune_rpc_private.Procedures.Public.ping
24+
()
25+
in
26+
Console.print [ Pp.text "Server appears to be responding normally" ]
2727
;;
2828

2929
let cmd = Cmd.v info term

bin/runtest.ml

Lines changed: 10 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -48,18 +48,16 @@ let runtest_term =
4848
~dir_or_cram_test_paths
4949
~to_cwd:(Common.root common).to_cwd)
5050
| Error lock_held_by ->
51-
Scheduler.go_without_rpc_server
52-
~common
53-
~config
54-
(Rpc.Rpc_common.wrap_build_outcome_exn
55-
~print_on_success:true
56-
(Rpc.Rpc_common.fire_request
57-
~name:"runtest"
58-
~wait:false
59-
~lock_held_by
60-
builder
61-
Dune_rpc.Procedures.Public.runtest)
62-
dir_or_cram_test_paths)
51+
Scheduler.go_without_rpc_server ~common ~config (fun () ->
52+
let open Fiber.O in
53+
Rpc.Rpc_common.fire_request
54+
~name:"runtest"
55+
~wait:false
56+
~lock_held_by
57+
builder
58+
Dune_rpc.Procedures.Public.runtest
59+
dir_or_cram_test_paths
60+
>>| Rpc.Rpc_common.wrap_build_outcome_exn ~print_on_success:true)
6361
;;
6462

6563
let commands =

bin/tools/tools_common.ml

Lines changed: 8 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -36,16 +36,15 @@ let build_dev_tool_directly common dev_tool =
3636
let build_dev_tool_via_rpc builder lock_held_by dev_tool =
3737
let target = dev_tool_build_target dev_tool in
3838
let targets = Rpc.Rpc_common.prepare_targets [ target ] in
39-
Rpc.Rpc_common.wrap_build_outcome_exn
40-
~print_on_success:false
41-
(Rpc.Rpc_common.fire_request
42-
~name:"build"
43-
~wait:true
44-
~lock_held_by
45-
builder
46-
Dune_rpc_impl.Decl.build)
39+
let open Fiber.O in
40+
Rpc.Rpc_common.fire_request
41+
~name:"build"
42+
~wait:true
43+
~lock_held_by
44+
builder
45+
Dune_rpc_impl.Decl.build
4746
targets
48-
()
47+
>>| Rpc.Rpc_common.wrap_build_outcome_exn ~print_on_success:false
4948
;;
5049

5150
let lock_and_build_dev_tool ~common ~config builder dev_tool =

0 commit comments

Comments
 (0)