Skip to content
Closed
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
8 changes: 4 additions & 4 deletions bin/build.ml
Original file line number Diff line number Diff line change
Expand Up @@ -144,9 +144,9 @@ let run_build_command ~(common : Common.t) ~config ~request =
;;

let build_via_rpc_server ~print_on_success ~targets builder lock_held_by =
Rpc.Rpc_common.wrap_build_outcome_exn
Rpc.Common.wrap_build_outcome_exn
~print_on_success
(Rpc.Group.Build.build ~wait:true builder lock_held_by)
(Rpc.Build.build ~wait:true builder lock_held_by)
targets
()
;;
Expand Down Expand Up @@ -203,10 +203,10 @@ let build =
an RPC server in the background to schedule the fiber which will
perform the RPC call.
*)
Rpc.Rpc_common.run_via_rpc
Rpc.Common.run_via_rpc
~common
~config
(Rpc.Group.Build.build ~wait:true builder lock_held_by)
(Rpc.Build.build ~wait:true builder lock_held_by)
targets
| Ok () ->
let request setup =
Expand Down
6 changes: 3 additions & 3 deletions bin/diagnostics.ml
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@ open Import

let exec () =
let open Fiber.O in
let where = Rpc.Rpc_common.active_server_exn () in
let where = Rpc.Common.active_server_exn () in
let module Client = Dune_rpc_client.Client in
let+ errors =
let* connect = Client.Connection.connect_exn where in
Expand All @@ -22,7 +22,7 @@ let exec () =
| Ok errors ->
List.iter errors ~f:(fun err ->
Console.print_user_message (Dune_rpc.Diagnostic.to_user_message err))
| Error e -> Rpc.Rpc_common.raise_rpc_error e
| Error e -> Rpc.Common.raise_rpc_error e
;;

let info =
Expand All @@ -32,7 +32,7 @@ let info =

let term =
let+ (builder : Common.Builder.t) = Common.Builder.term in
Rpc.Rpc_common.client_term builder exec
Rpc.Common.client_term builder exec
;;

let command = Cmd.v info term
4 changes: 2 additions & 2 deletions bin/fmt.ml
Original file line number Diff line number Diff line change
Expand Up @@ -44,10 +44,10 @@ let run_fmt_command ~common ~config ~preview builder =
| Ok () -> Scheduler.go_with_rpc_server ~common ~config once
| Error lock_held_by ->
(* The --preview flag is being ignored by the RPC server, warn the user. *)
if preview then Rpc.Rpc_common.warn_ignore_arguments lock_held_by;
if preview then Rpc.Common.warn_ignore_arguments lock_held_by;
let response =
Scheduler.go_without_rpc_server ~common ~config (fun () ->
Rpc.Rpc_common.fire_request
Rpc.Common.fire_request
~name:"format"
~wait:true
~warn_forwarding:false
Expand Down
4 changes: 2 additions & 2 deletions bin/promotion.ml
Original file line number Diff line number Diff line change
Expand Up @@ -62,10 +62,10 @@ module Apply = struct
let+ () = Fiber.return () in
Diff_promotion.promote_files_registered_in_last_run files_to_promote)
| Error lock_held_by ->
Rpc.Rpc_common.run_via_rpc
Rpc.Common.run_via_rpc
~common
~config
(Rpc.Rpc_common.fire_request
(Rpc.Common.fire_request
~name:"promote_many"
~wait:true
~lock_held_by
Expand Down
8 changes: 4 additions & 4 deletions bin/rpc/rpc_build.ml → bin/rpc/build.ml
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ let build ~wait builder lock_held_by targets =
let sexp = Dune_lang.Dep_conf.encode target in
Dune_lang.to_string sexp)
in
Rpc_common.fire_request
Common.fire_request
~name:"build"
~wait
~lock_held_by
Expand All @@ -18,13 +18,13 @@ let build ~wait builder lock_held_by targets =
let term =
let name_ = Arg.info [] ~docv:"TARGET" in
let+ (builder : Common.Builder.t) = Common.Builder.term
and+ wait = Rpc_common.wait_term
and+ wait = Common.wait_term
and+ targets = Arg.(value & pos_all string [] name_) in
Rpc_common.client_term builder
Common.client_term builder
@@ fun () ->
let open Fiber.O in
let+ response =
Rpc_common.fire_request ~name:"build" ~wait builder Dune_rpc_impl.Decl.build targets
Common.fire_request ~name:"build" ~wait builder Dune_rpc_impl.Decl.build targets
in
match response with
| Error (error : Dune_rpc.Response.Error.t) ->
Expand Down
File renamed without changes.
File renamed without changes.
File renamed without changes.
4 changes: 1 addition & 3 deletions bin/rpc/group.ml
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,4 @@ let info =
Cmd.info "rpc" ~doc ~man
;;

let group = Cmd.group info [ Rpc_status.cmd; Rpc_build.cmd; Rpc_ping.cmd ]

module Build = Rpc_build
let group = Cmd.group info [ Status.cmd; Build.cmd; Ping.cmd ]
2 changes: 0 additions & 2 deletions bin/rpc/group.mli
Original file line number Diff line number Diff line change
@@ -1,4 +1,2 @@
(** dune rpc command group *)
val group : unit Cmdliner.Cmd.t

module Build = Rpc_build
8 changes: 4 additions & 4 deletions bin/rpc/rpc_ping.ml → bin/rpc/ping.ml
Original file line number Diff line number Diff line change
Expand Up @@ -11,19 +11,19 @@ let info =

let term =
let+ (builder : Common.Builder.t) = Common.Builder.term
and+ wait = Rpc_common.wait_term in
Rpc_common.client_term builder
and+ wait = Common.wait_term in
Common.client_term builder
@@ fun () ->
let open Fiber.O in
Rpc_common.fire_request
Common.fire_request
~name:"ping_cmd"
~wait
builder
Dune_rpc_private.Procedures.Public.ping
()
>>| function
| Ok () -> Console.print [ Pp.text "Server appears to be responding normally" ]
| Error e -> Rpc_common.raise_rpc_error e
| Error e -> Common.raise_rpc_error e
;;

let cmd = Cmd.v info term
File renamed without changes.
8 changes: 4 additions & 4 deletions bin/rpc/rpc.ml
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
module Group = Group
module Rpc_build = Rpc_build
module Rpc_common = Rpc_common
module Rpc_ping = Rpc_ping
module Rpc_status = Rpc_status
module Build = Build
module Common = Common
module Ping = Ping
module Status = Status
4 changes: 2 additions & 2 deletions bin/rpc/rpc_status.ml → bin/rpc/status.ml
Original file line number Diff line number Diff line change
Expand Up @@ -103,7 +103,7 @@ let term =
"Show all running Dune instances together with their root, pids and number \
of clients.")
in
Rpc_common.client_term builder
Common.client_term builder
@@ fun () ->
let open Fiber.O in
if all
Expand All @@ -112,7 +112,7 @@ let term =
let+ statuses = Fiber.parallel_map ~f:get_status dunes in
print_statuses statuses
else (
let where = Rpc_common.active_server_exn () in
let where = Common.active_server_exn () in
Console.print
[ Pp.textf "Server is listening on %s" (Dune_rpc.Where.to_string where)
; Pp.text "Connected clients (including this one):"
Expand Down
File renamed without changes.
4 changes: 2 additions & 2 deletions bin/runtest.ml
Original file line number Diff line number Diff line change
Expand Up @@ -51,9 +51,9 @@ let runtest_term =
Scheduler.go_without_rpc_server
~common
~config
(Rpc.Rpc_common.wrap_build_outcome_exn
(Rpc.Common.wrap_build_outcome_exn
~print_on_success:true
(Rpc.Rpc_common.fire_request
(Rpc.Common.fire_request
~name:"runtest"
~wait:false
~lock_held_by
Expand Down
4 changes: 2 additions & 2 deletions bin/shutdown.ml
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ let send_shutdown cli =

let exec () =
let open Fiber.O in
let where = Rpc.Rpc_common.active_server_exn () in
let where = Rpc.Common.active_server_exn () in
let* conn = Client.Connection.connect_exn where in
Dune_rpc_impl.Client.client
conn
Expand All @@ -31,7 +31,7 @@ let info =

let term =
let+ builder = Common.Builder.term in
Rpc.Rpc_common.client_term builder exec
Rpc.Common.client_term builder exec
;;

let command = Cmd.v info term
2 changes: 1 addition & 1 deletion src/dune_rules/modules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -405,7 +405,7 @@ module Group = struct
(* TODO this happens with "side" modules like menhir mock modules *)
acc
| Some (Module _) -> acc
| Some (Group g) -> loop (g :: acc) g.modules ps)
| Some (Group g) -> loop (acc @ [ g ]) g.modules ps)
in
fun acc modules m -> loop acc modules (Module.path m)
;;
Expand Down
Loading