@@ -64,7 +64,16 @@ module Cmd_arg = struct
6464 let conv = Arg. conv ((fun s -> Ok (parse s)), pp)
6565end
6666
67- let not_found ~dir ~prog =
67+ let not_found ~hints ~prog =
68+ User_error. raise
69+ ~hints
70+ [ Pp. concat
71+ ~sep: Pp. space
72+ [ Pp. text " Program" ; User_message. command prog; Pp. text " not found!" ]
73+ ]
74+ ;;
75+
76+ let not_found_with_suggestions ~dir ~prog =
6877 let open Memo.O in
6978 let + hints =
7079 (* Good candidates for the "./x.exe" instead of "x.exe" error are
@@ -81,30 +90,25 @@ let not_found ~dir ~prog =
8190 in
8291 User_message. did_you_mean prog ~candidates
8392 in
93+ not_found ~hints ~prog
94+ ;;
95+
96+ let program_not_built_yet prog =
8497 User_error. raise
85- ~hints
8698 [ Pp. concat
8799 ~sep: Pp. space
88- [ Pp. text " Program" ; User_message. command prog; Pp. text " not found!" ]
100+ [ Pp. text " Program"
101+ ; User_message. command prog
102+ ; Pp. text " isn't built yet. You need to build it first or remove the"
103+ ; User_message. command " --no-build"
104+ ; Pp. text " option."
105+ ]
89106 ]
90107;;
91108
92109let build_prog ~no_rebuild ~prog p =
93110 if no_rebuild
94- then
95- if Path. exists p
96- then Memo. return p
97- else
98- User_error. raise
99- [ Pp. concat
100- ~sep: Pp. space
101- [ Pp. text " Program"
102- ; User_message. command prog
103- ; Pp. text " isn't built yet. You need to build it first or remove the"
104- ; User_message. command " --no-build"
105- ; Pp. text " option."
106- ]
107- ]
111+ then if Path. exists p then Memo. return p else program_not_built_yet prog
108112 else
109113 let open Memo.O in
110114 let + () = Build_system. build_file p in
@@ -117,14 +121,14 @@ let get_path_and_build_if_necessary sctx ~no_rebuild ~dir ~prog =
117121 | In_path ->
118122 Super_context. resolve_program_memo sctx ~dir ~loc: None prog
119123 >> = (function
120- | Error (_ : Action.Prog.Not_found.t ) -> not_found ~dir ~prog
124+ | Error (_ : Action.Prog.Not_found.t ) -> not_found_with_suggestions ~dir ~prog
121125 | Ok p -> build_prog ~no_rebuild ~prog p)
122126 | Relative_to_current_dir ->
123127 let path = Path. relative_to_source_in_build_or_external ~dir prog in
124128 Build_system. file_exists path
125129 >> = (function
126130 | true -> build_prog ~no_rebuild ~prog path
127- | false -> not_found ~dir ~prog )
131+ | false -> not_found_with_suggestions ~dir ~prog )
128132 | Absolute ->
129133 (match
130134 let prog = Path. of_string prog in
@@ -137,7 +141,7 @@ let get_path_and_build_if_necessary sctx ~no_rebuild ~dir ~prog =
137141 Option. some_if (Path. exists prog) prog)
138142 with
139143 | Some prog -> Memo. return prog
140- | None -> not_found ~dir ~prog )
144+ | None -> not_found_with_suggestions ~dir ~prog )
141145;;
142146
143147let step ~setup ~prog ~args ~common ~no_rebuild ~context ~on_exit () =
@@ -164,17 +168,69 @@ let step ~setup ~prog ~args ~common ~no_rebuild ~context ~on_exit () =
164168 | exit_code -> on_exit exit_code
165169;;
166170
167- let term : unit Term.t =
168- let + builder = Common.Builder. term
169- and + context = Common. context_arg ~doc: {| Run the command in this build context.| }
170- and + prog = Arg. (required & pos 0 (some Cmd_arg. conv) None (Arg. info [] ~docv: " PROG" ))
171- and + no_rebuild =
172- Arg. (value & flag & info [ " no-build" ] ~doc: " don't rebuild target before executing" )
173- and + args = Arg. (value & pos_right 0 Cmd_arg. conv [] (Arg. info [] ~docv: " ARGS" )) in
174- (* TODO we should make sure to finalize the current backend before exiting dune.
175- For watch mode, we should finalize the backend and then restart it in between
176- runs. *)
177- let common, config = Common. init builder in
171+ (* Similar to [get_path_and_build_if_necessary] but doesn't require the build
172+ system (ie. it sequences with [Fiber] rather than with [Memo]) and builds
173+ targets via an RPC server. Some functionality is not available but it can be
174+ run concurrently while a second Dune process holds the global build
175+ directory lock.
176+
177+ Returns the absolute path to the executable. *)
178+ let build_prog_via_rpc_if_necessary ~dir ~no_rebuild prog =
179+ match Filename. analyze_program_name prog with
180+ | In_path ->
181+ User_warning. emit
182+ [ Pp. textf
183+ " As this is not the main instance of Dune it is unable to locate the \
184+ executable %S within this project. Dune will attempt to resolve the \
185+ executable's name within your PATH only."
186+ prog
187+ ];
188+ let path = Env_path. path Env. initial in
189+ (match Bin. which ~path prog with
190+ | None -> not_found ~hints: [] ~prog
191+ | Some prog_path -> Fiber. return (Path. to_absolute_filename prog_path))
192+ | Relative_to_current_dir ->
193+ let open Fiber.O in
194+ let path = Path. relative_to_source_in_build_or_external ~dir prog in
195+ let + () =
196+ if no_rebuild
197+ then if Path. exists path then Fiber. return () else program_not_built_yet prog
198+ else (
199+ let target =
200+ Dune_lang.Dep_conf. File
201+ (Dune_lang.String_with_vars. make_text Loc. none (Path. to_string path))
202+ in
203+ Build_cmd. build_via_rpc_server ~print_on_success: false ~targets: [ target ])
204+ in
205+ Path. to_absolute_filename path
206+ | Absolute ->
207+ if Path. exists (Path. of_string prog)
208+ then Fiber. return prog
209+ else not_found ~hints: [] ~prog
210+ ;;
211+
212+ let exec_building_via_rpc_server ~common ~prog ~args ~no_rebuild =
213+ let open Fiber.O in
214+ let ensure_terminal : Cmd_arg.t -> _ = function
215+ | Terminal s -> s
216+ | Expandable (_ , raw ) ->
217+ (* Variables cannot be expanded without running the build system. *)
218+ User_error. raise
219+ [ Pp. textf
220+ " The term %S contains a variable but Dune is unable to expand variables when \
221+ building via RPC."
222+ raw
223+ ]
224+ in
225+ let context = Common. x common |> Option. value ~default: Context_name. default in
226+ let dir = Context_name. build_dir context in
227+ let prog = ensure_terminal prog in
228+ let args = List. map args ~f: ensure_terminal in
229+ let + prog = build_prog_via_rpc_if_necessary ~dir ~no_rebuild prog in
230+ restore_cwd_and_execve (Common. root common) prog args Env. initial
231+ ;;
232+
233+ let exec_building_directly ~common ~config ~context ~prog ~args ~no_rebuild =
178234 match Common. watch common with
179235 | Yes Passive ->
180236 User_error. raise [ Pp. textf " passive watch mode is unsupported by exec" ]
@@ -209,4 +265,40 @@ let term : unit Term.t =
209265 restore_cwd_and_execve (Common. root common) prog args env)
210266;;
211267
268+ let term : unit Term.t =
269+ let + builder = Common.Builder. term
270+ and + context = Common. context_arg ~doc: {| Run the command in this build context.| }
271+ and + prog = Arg. (required & pos 0 (some Cmd_arg. conv) None (Arg. info [] ~docv: " PROG" ))
272+ and + no_rebuild =
273+ Arg. (value & flag & info [ " no-build" ] ~doc: " don't rebuild target before executing" )
274+ and + args = Arg. (value & pos_right 0 Cmd_arg. conv [] (Arg. info [] ~docv: " ARGS" )) in
275+ (* TODO we should make sure to finalize the current backend before exiting dune.
276+ For watch mode, we should finalize the backend and then restart it in between
277+ runs. *)
278+ let common, config = Common. init builder in
279+ match Dune_util.Global_lock. lock ~timeout: None with
280+ | Error lock_held_by ->
281+ (match Common. watch common with
282+ | Yes _ ->
283+ User_error. raise
284+ [ Pp. textf
285+ " Another instance of dune%s has locked the _build directory. Refusing to \
286+ start a new watch server until no other instances of dune are running."
287+ (Dune_util.Global_lock.Lock_held_by. to_string_empty_if_unknown lock_held_by)
288+ ]
289+ | No ->
290+ if not (Common.Builder. equal builder Common.Builder. default)
291+ then
292+ User_warning. emit
293+ [ Pp. textf
294+ " Your build request is being forwarded to a running Dune instance%s. Note \
295+ that certain command line arguments may be ignored."
296+ (Dune_util.Global_lock.Lock_held_by. to_string_empty_if_unknown
297+ lock_held_by)
298+ ];
299+ Scheduler. go_without_rpc_server ~common ~config
300+ @@ fun () -> exec_building_via_rpc_server ~common ~prog ~args ~no_rebuild )
301+ | Ok () -> exec_building_directly ~common ~config ~context ~prog ~args ~no_rebuild
302+ ;;
303+
212304let command = Cmd. v info term
0 commit comments