Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
16 changes: 7 additions & 9 deletions bin/build.ml
Original file line number Diff line number Diff line change
Expand Up @@ -143,14 +143,6 @@ let run_build_command ~(common : Common.t) ~config ~request =
~request
;;

let build_via_rpc_server ~print_on_success ~targets builder lock_held_by =
Rpc.Rpc_common.wrap_build_outcome_exn
~print_on_success
(Rpc.Group.Build.build ~wait:true builder lock_held_by)
targets
()
;;

let build =
let doc = "Build the given targets, or the default ones if none are given." in
let man =
Expand Down Expand Up @@ -203,10 +195,16 @@ let build =
an RPC server in the background to schedule the fiber which will
perform the RPC call.
*)
let targets = Rpc.Rpc_common.prepare_targets targets in
Rpc.Rpc_common.run_via_rpc
~common
~config
(Rpc.Group.Build.build ~wait:true builder lock_held_by)
(Rpc.Rpc_common.fire_request
~name:"build"
~wait:true
~lock_held_by
builder
Dune_rpc_impl.Decl.build)
targets
| Ok () ->
let request setup =
Expand Down
12 changes: 0 additions & 12 deletions bin/build.mli
Original file line number Diff line number Diff line change
@@ -1,17 +1,5 @@
open Import

(** Connect to an RPC server (waiting for the server to start if necessary) and
then send a request to the server to build the specified targets. If the
build fails then a diagnostic error message is printed. If
[print_on_success] is true then this function will also print a message
after the build succeeds. *)
val build_via_rpc_server
: print_on_success:bool
-> targets:Dune_lang.Dep_conf.t list
-> Common.Builder.t
-> Dune_util.Global_lock.Lock_held_by.t
-> unit Fiber.t

val run_build_system
: common:Common.t
-> request:(Dune_rules.Main.build_system -> unit Action_builder.t)
Expand Down
14 changes: 10 additions & 4 deletions bin/exec.ml
Original file line number Diff line number Diff line change
Expand Up @@ -225,11 +225,17 @@ let build_prog_via_rpc_if_necessary ~dir ~no_rebuild builder lock_held_by prog =
Dune_lang.Dep_conf.File
(Dune_lang.String_with_vars.make_text Loc.none (Path.to_string path))
in
Build.build_via_rpc_server
let targets = Rpc.Rpc_common.prepare_targets [ target ] in
Rpc.Rpc_common.wrap_build_outcome_exn
~print_on_success:false
~targets:[ target ]
builder
lock_held_by)
(Rpc.Rpc_common.fire_request
~name:"build"
~wait:true
~lock_held_by
builder
Dune_rpc_impl.Decl.build)
targets
())
in
Path.to_absolute_filename path
| Absolute ->
Expand Down
15 changes: 0 additions & 15 deletions bin/rpc/rpc_build.ml
Original file line number Diff line number Diff line change
@@ -1,20 +1,5 @@
open Import

let build ~wait builder lock_held_by targets =
let targets =
List.map targets ~f:(fun target ->
let sexp = Dune_lang.Dep_conf.encode target in
Dune_lang.to_string sexp)
in
Rpc_common.fire_request
~name:"build"
~wait
~lock_held_by
builder
Dune_rpc_impl.Decl.build
targets
;;

let term =
let name_ = Arg.info [] ~docv:"TARGET" in
let+ (builder : Common.Builder.t) = Common.Builder.term
Expand Down
11 changes: 0 additions & 11 deletions bin/rpc/rpc_build.mli
Original file line number Diff line number Diff line change
@@ -1,15 +1,4 @@
open! Import

(** Sends a command to an RPC server to build the specified targets and wait
for the build to complete or fail. If [wait] is true then wait until an RPC
server is running before making the request. Otherwise if no RPC server is
running then raise a [User_error]. *)
val build
: wait:bool
-> Common.Builder.t
-> Dune_util.Global_lock.Lock_held_by.t
-> Dune_lang.Dep_conf.t list
-> (Dune_rpc.Build_outcome_with_diagnostics.t, Dune_rpc.Response.Error.t) result Fiber.t

(** dune rpc build command *)
val cmd : unit Cmdliner.Cmd.t
6 changes: 6 additions & 0 deletions bin/rpc/rpc_common.ml
Original file line number Diff line number Diff line change
Expand Up @@ -75,6 +75,12 @@ let establish_client_session ~wait =
if wait then establish_connection_with_retry () else establish_connection_exn ()
;;

let prepare_targets targets =
List.map targets ~f:(fun target ->
let sexp = Dune_lang.Dep_conf.encode target in
Dune_lang.to_string sexp)
;;

let warn_ignore_arguments lock_held_by =
User_warning.emit
[ Pp.paragraphf
Expand Down
4 changes: 4 additions & 0 deletions bin/rpc/rpc_common.mli
Original file line number Diff line number Diff line change
Expand Up @@ -21,6 +21,10 @@ val client_term : Common.Builder.t -> (unit -> 'a Fiber.t) -> 'a
(** Cmdliner argument for a wait flag. *)
val wait_term : bool Cmdliner.Term.t

(** Encode the targets as [Dune_lang.t], and then as strings suitable to
be sent via RPC. *)
val prepare_targets : Dune_lang.Dep_conf.t list -> string list

(** Send a request to the RPC server. If [wait], it will poll forever until a server is listening.
Should be scheduled by a scheduler that does not come with a RPC server on its own.

Expand Down
14 changes: 10 additions & 4 deletions bin/tools/tools_common.ml
Original file line number Diff line number Diff line change
Expand Up @@ -35,11 +35,17 @@ let build_dev_tool_directly common dev_tool =

let build_dev_tool_via_rpc builder lock_held_by dev_tool =
let target = dev_tool_build_target dev_tool in
Build.build_via_rpc_server
let targets = Rpc.Rpc_common.prepare_targets [ target ] in
Rpc.Rpc_common.wrap_build_outcome_exn
~print_on_success:false
~targets:[ target ]
builder
lock_held_by
(Rpc.Rpc_common.fire_request
~name:"build"
~wait:true
~lock_held_by
builder
Dune_rpc_impl.Decl.build)
targets
()
;;

let lock_and_build_dev_tool ~common ~config builder dev_tool =
Expand Down
Loading