File tree Expand file tree Collapse file tree 4 files changed +16
-6
lines changed Expand file tree Collapse file tree 4 files changed +16
-6
lines changed Original file line number Diff line number Diff line change @@ -68,7 +68,7 @@ module Apply = struct
6868 ~config
6969 lock_held_by
7070 (Rpc_common. fire_request
71- ~name: " promote_but_better "
71+ ~name: " promote_but_different "
7272 ~wait: true
7373 Dune_rpc_impl.Decl. promote)
7474 files_to_promote
Original file line number Diff line number Diff line change @@ -21,9 +21,7 @@ val client_term : Common.Builder.t -> (unit -> 'a Fiber.t) -> 'a
2121(* * Cmdliner argument for a wait flag. *)
2222val wait_term : bool Cmdliner.Term .t
2323
24- val establish_client_session : wait :bool -> Dune_rpc_client.Client.Connection .t Fiber .t
25-
26- (* * Send a request to the RPC server.
24+ (* * Send a request to the RPC server. If [wait], it will poll forever until a server is listening.
2725 Should be scheduled by a scheduler that does not come with a RPC server on its own. *)
2826val fire_request
2927 : name:string
Original file line number Diff line number Diff line change @@ -93,11 +93,19 @@ module Build = struct
9393end
9494
9595module Promote = struct
96+ let on_missing fn =
97+ User_warning. emit
98+ [ Pp. paragraphf
99+ " Nothing to promote for %s."
100+ (Stdune.Path.Source. to_string_maybe_quoted fn)
101+ ]
102+ ;;
103+
96104 let sexp =
97105 let open Conv in
98106 let to_ = function
99107 | [] -> Promote.Diff_promotion. All
100- | paths -> These (List. map ~f: Stdune.Path.Source. of_string paths, ignore )
108+ | paths -> These (List. map ~f: Stdune.Path.Source. of_string paths, on_missing )
101109 in
102110 let from = function
103111 | Promote.Diff_promotion. All -> []
@@ -113,7 +121,9 @@ module Promote = struct
113121 ~version: 1
114122 ;;
115123
116- let decl = Decl.Request. make ~method_: " promote_but_better" ~generations: [ v1 ]
124+ (* Due to conflict with `Dune_rpc_private.Procedures.Public.promote`,
125+ this has to be named something other than "promote". *)
126+ let decl = Decl.Request. make ~method_: " promote_but_different" ~generations: [ v1 ]
117127end
118128
119129let build = Build. decl
Original file line number Diff line number Diff line change @@ -396,6 +396,8 @@ let handler (t : _ t Fdecl.t) handle : 'build_arg Dune_rpc_server.Handler.t =
396396 in
397397 Handler. implement_request rpc Decl. promote f
398398 in
399+ (* The two handlers above and below implement the same thing: 'promote',
400+ but in two slightly different ways. Maybe one should be removed/deprecated? *)
399401 let () =
400402 let f _ path =
401403 let files = For_handlers. source_path_of_string path in
You can’t perform that action at this time.
0 commit comments