Skip to content

Commit 79afcd2

Browse files
committed
Delete redundant functions build_via_rpc
Signed-off-by: Ambre Austen Suhamy <[email protected]>
1 parent 2b0fa16 commit 79afcd2

File tree

8 files changed

+37
-55
lines changed

8 files changed

+37
-55
lines changed

bin/build.ml

Lines changed: 7 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -143,14 +143,6 @@ let run_build_command ~(common : Common.t) ~config ~request =
143143
~request
144144
;;
145145

146-
let build_via_rpc_server ~print_on_success ~targets builder lock_held_by =
147-
Rpc.Rpc_common.wrap_build_outcome_exn
148-
~print_on_success
149-
(Rpc.Group.Build.build ~wait:true builder lock_held_by)
150-
targets
151-
()
152-
;;
153-
154146
let build =
155147
let doc = "Build the given targets, or the default ones if none are given." in
156148
let man =
@@ -203,10 +195,16 @@ let build =
203195
an RPC server in the background to schedule the fiber which will
204196
perform the RPC call.
205197
*)
198+
let targets = Rpc.Rpc_common.prepare_targets targets in
206199
Rpc.Rpc_common.run_via_rpc
207200
~common
208201
~config
209-
(Rpc.Group.Build.build ~wait:true builder lock_held_by)
202+
(Rpc.Rpc_common.fire_request
203+
~name:"build"
204+
~wait:true
205+
~lock_held_by
206+
builder
207+
Dune_rpc_impl.Decl.build)
210208
targets
211209
| Ok () ->
212210
let request setup =

bin/build.mli

Lines changed: 0 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -1,17 +1,5 @@
11
open Import
22

3-
(** Connect to an RPC server (waiting for the server to start if necessary) and
4-
then send a request to the server to build the specified targets. If the
5-
build fails then a diagnostic error message is printed. If
6-
[print_on_success] is true then this function will also print a message
7-
after the build succeeds. *)
8-
val build_via_rpc_server
9-
: print_on_success:bool
10-
-> targets:Dune_lang.Dep_conf.t list
11-
-> Common.Builder.t
12-
-> Dune_util.Global_lock.Lock_held_by.t
13-
-> unit Fiber.t
14-
153
val run_build_system
164
: common:Common.t
175
-> request:(Dune_rules.Main.build_system -> unit Action_builder.t)

bin/exec.ml

Lines changed: 10 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -225,11 +225,17 @@ let build_prog_via_rpc_if_necessary ~dir ~no_rebuild builder lock_held_by prog =
225225
Dune_lang.Dep_conf.File
226226
(Dune_lang.String_with_vars.make_text Loc.none (Path.to_string path))
227227
in
228-
Build.build_via_rpc_server
228+
let targets = Rpc.Rpc_common.prepare_targets [ target ] in
229+
Rpc.Rpc_common.wrap_build_outcome_exn
229230
~print_on_success:false
230-
~targets:[ target ]
231-
builder
232-
lock_held_by)
231+
(Rpc.Rpc_common.fire_request
232+
~name:"build"
233+
~wait:true
234+
~lock_held_by
235+
builder
236+
Dune_rpc_impl.Decl.build)
237+
targets
238+
())
233239
in
234240
Path.to_absolute_filename path
235241
| Absolute ->

bin/rpc/rpc_build.ml

Lines changed: 0 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -1,20 +1,5 @@
11
open Import
22

3-
let build ~wait builder lock_held_by targets =
4-
let targets =
5-
List.map targets ~f:(fun target ->
6-
let sexp = Dune_lang.Dep_conf.encode target in
7-
Dune_lang.to_string sexp)
8-
in
9-
Rpc_common.fire_request
10-
~name:"build"
11-
~wait
12-
~lock_held_by
13-
builder
14-
Dune_rpc_impl.Decl.build
15-
targets
16-
;;
17-
183
let term =
194
let name_ = Arg.info [] ~docv:"TARGET" in
205
let+ (builder : Common.Builder.t) = Common.Builder.term

bin/rpc/rpc_build.mli

Lines changed: 0 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -1,15 +1,4 @@
11
open! Import
22

3-
(** Sends a command to an RPC server to build the specified targets and wait
4-
for the build to complete or fail. If [wait] is true then wait until an RPC
5-
server is running before making the request. Otherwise if no RPC server is
6-
running then raise a [User_error]. *)
7-
val build
8-
: wait:bool
9-
-> Common.Builder.t
10-
-> Dune_util.Global_lock.Lock_held_by.t
11-
-> Dune_lang.Dep_conf.t list
12-
-> (Dune_rpc.Build_outcome_with_diagnostics.t, Dune_rpc.Response.Error.t) result Fiber.t
13-
143
(** dune rpc build command *)
154
val cmd : unit Cmdliner.Cmd.t

bin/rpc/rpc_common.ml

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -75,6 +75,12 @@ let establish_client_session ~wait =
7575
if wait then establish_connection_with_retry () else establish_connection_exn ()
7676
;;
7777

78+
let prepare_targets targets =
79+
List.map targets ~f:(fun target ->
80+
let sexp = Dune_lang.Dep_conf.encode target in
81+
Dune_lang.to_string sexp)
82+
;;
83+
7884
let warn_ignore_arguments lock_held_by =
7985
User_warning.emit
8086
[ Pp.paragraphf

bin/rpc/rpc_common.mli

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -21,6 +21,10 @@ val client_term : Common.Builder.t -> (unit -> 'a Fiber.t) -> 'a
2121
(** Cmdliner argument for a wait flag. *)
2222
val wait_term : bool Cmdliner.Term.t
2323

24+
(** Encode the targets as [Dune_lang.t], and then as strings suitable to
25+
be sent via RPC. *)
26+
val prepare_targets : Dune_lang.Dep_conf.t list -> string list
27+
2428
(** Send a request to the RPC server. If [wait], it will poll forever until a server is listening.
2529
Should be scheduled by a scheduler that does not come with a RPC server on its own.
2630

bin/tools/tools_common.ml

Lines changed: 10 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -35,11 +35,17 @@ let build_dev_tool_directly common dev_tool =
3535

3636
let build_dev_tool_via_rpc builder lock_held_by dev_tool =
3737
let target = dev_tool_build_target dev_tool in
38-
Build.build_via_rpc_server
38+
let targets = Rpc.Rpc_common.prepare_targets [ target ] in
39+
Rpc.Rpc_common.wrap_build_outcome_exn
3940
~print_on_success:false
40-
~targets:[ target ]
41-
builder
42-
lock_held_by
41+
(Rpc.Rpc_common.fire_request
42+
~name:"build"
43+
~wait:true
44+
~lock_held_by
45+
builder
46+
Dune_rpc_impl.Decl.build)
47+
targets
48+
()
4349
;;
4450

4551
let lock_and_build_dev_tool ~common ~config builder dev_tool =

0 commit comments

Comments
 (0)