Skip to content

Commit 4bcb45d

Browse files
committed
Allow dune exec while watch server is running
This change allows a limited version of `dune exec` to run at the same time as dune is running in watch mode. This allows users to run example programs without needing to stop their watch server. This works by sending messages to the RPC server to build the executable if necessary. Signed-off-by: Stephen Sherratt <[email protected]>
1 parent 03eb21f commit 4bcb45d

File tree

5 files changed

+196
-34
lines changed

5 files changed

+196
-34
lines changed

bin/build_cmd.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -221,7 +221,7 @@ let build =
221221
[ Pp.textf
222222
"Your build request is being forwarded to a running Dune instance%s so \
223223
most command-line arguments will be ignored."
224-
(match (lock_held_by : Dune_util.Global_lock.Lock_held_by.t) with
224+
(match lock_held_by with
225225
| Unknown -> ""
226226
| Pid_from_lockfile pid -> sprintf " (pid: %d)" pid)
227227
];

bin/exec.ml

Lines changed: 140 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -64,7 +64,16 @@ module Cmd_arg = struct
6464
let conv = Arg.conv ((fun s -> Ok (parse s)), pp)
6565
end
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

92109
let 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

143147
let step ~setup ~prog ~args ~common ~no_rebuild ~context ~on_exit () =
@@ -164,17 +168,83 @@ 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+
(* This case is reached if [dune exec] is passed the name of an
182+
executable (rather than a path to an executable). When dune is running
183+
directly, dune will try to resolve the executbale name within the public
184+
executables defined in the current project and its dependencies, and
185+
only if no executable with the given name is found will dune then
186+
resolve the name within the $PATH variable instead. Looking up an
187+
executable's name within the current project requires running the
188+
build system, but running the build system is not allowed while
189+
another dune instance holds the global build directory lock. In this
190+
case dune will only resolve the executable's name within $PATH.
191+
Because this behaviour is different from the default, print a warning
192+
so users are hopefully less surprised.
193+
*)
194+
User_warning.emit
195+
[ Pp.textf
196+
"As this is not the main instance of Dune it is unable to locate the \
197+
executable %S within this project. Dune will attempt to resolve the \
198+
executable's name within your PATH only."
199+
prog
200+
];
201+
let path = Env_path.path Env.initial in
202+
(match Bin.which ~path prog with
203+
| None -> not_found ~hints:[] ~prog
204+
| Some prog_path -> Fiber.return (Path.to_absolute_filename prog_path))
205+
| Relative_to_current_dir ->
206+
let open Fiber.O in
207+
let path = Path.relative_to_source_in_build_or_external ~dir prog in
208+
let+ () =
209+
if no_rebuild
210+
then if Path.exists path then Fiber.return () else program_not_built_yet prog
211+
else (
212+
let target =
213+
Dune_lang.Dep_conf.File
214+
(Dune_lang.String_with_vars.make_text Loc.none (Path.to_string path))
215+
in
216+
Build_cmd.build_via_rpc_server ~print_on_success:false ~targets:[ target ])
217+
in
218+
Path.to_absolute_filename path
219+
| Absolute ->
220+
if Path.exists (Path.of_string prog)
221+
then Fiber.return prog
222+
else not_found ~hints:[] ~prog
223+
;;
224+
225+
let exec_building_via_rpc_server ~common ~prog ~args ~no_rebuild =
226+
let open Fiber.O in
227+
let ensure_terminal v =
228+
match (v : Cmd_arg.t) with
229+
| Terminal s -> s
230+
| Expandable (_, raw) ->
231+
(* Variables cannot be expanded without running the build system. *)
232+
User_error.raise
233+
[ Pp.textf
234+
"The term %S contains a variable but Dune is unable to expand variables when \
235+
building via RPC."
236+
raw
237+
]
238+
in
239+
let context = Common.x common |> Option.value ~default:Context_name.default in
240+
let dir = Context_name.build_dir context in
241+
let prog = ensure_terminal prog in
242+
let args = List.map args ~f:ensure_terminal in
243+
let+ prog = build_prog_via_rpc_if_necessary ~dir ~no_rebuild prog in
244+
restore_cwd_and_execve (Common.root common) prog args Env.initial
245+
;;
246+
247+
let exec_building_directly ~common ~config ~context ~prog ~args ~no_rebuild =
178248
match Common.watch common with
179249
| Yes Passive ->
180250
User_error.raise [ Pp.textf "passive watch mode is unsupported by exec" ]
@@ -209,4 +279,43 @@ let term : unit Term.t =
209279
restore_cwd_and_execve (Common.root common) prog args env)
210280
;;
211281

282+
let term : unit Term.t =
283+
let+ builder = Common.Builder.term
284+
and+ context = Common.context_arg ~doc:{|Run the command in this build context.|}
285+
and+ prog = Arg.(required & pos 0 (some Cmd_arg.conv) None (Arg.info [] ~docv:"PROG"))
286+
and+ no_rebuild =
287+
Arg.(value & flag & info [ "no-build" ] ~doc:"don't rebuild target before executing")
288+
and+ args = Arg.(value & pos_right 0 Cmd_arg.conv [] (Arg.info [] ~docv:"ARGS")) in
289+
(* TODO we should make sure to finalize the current backend before exiting dune.
290+
For watch mode, we should finalize the backend and then restart it in between
291+
runs. *)
292+
let common, config = Common.init builder in
293+
match Dune_util.Global_lock.lock ~timeout:None with
294+
| Error lock_held_by ->
295+
(match Common.watch common with
296+
| Yes _ ->
297+
User_error.raise
298+
[ Pp.textf
299+
"Another instance of dune%s has locked the _build directory. Refusing to \
300+
start a new watch server until no other instances of dune are running."
301+
(match lock_held_by with
302+
| Unknown -> ""
303+
| Pid_from_lockfile pid -> sprintf " (pid: %d)" pid)
304+
]
305+
| No ->
306+
if not (Common.Builder.equal builder Common.Builder.default)
307+
then
308+
User_warning.emit
309+
[ Pp.textf
310+
"Your build request is being forwarded to a running Dune instance%s. Note \
311+
that certain command line arguments may be ignored."
312+
(match lock_held_by with
313+
| Unknown -> ""
314+
| Pid_from_lockfile pid -> sprintf " (pid: %d)" pid)
315+
];
316+
Scheduler.go_without_rpc_server ~common ~config
317+
@@ fun () -> exec_building_via_rpc_server ~common ~prog ~args ~no_rebuild)
318+
| Ok () -> exec_building_directly ~common ~config ~context ~prog ~args ~no_rebuild
319+
;;
320+
212321
let command = Cmd.v info term

doc/changes/11840.md

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,2 @@
1+
- Allow `dune exec` to run concurrently with another instance of dune in watch
2+
mode (#11840, @gridbugs)

test/blackbox-tests/test-cases/watching/dune

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -17,8 +17,9 @@
1717
(applies_to what-dune-watches)
1818
(deps %{bin:strace}))
1919

20-
;; this test sometimes gets stuck and times out
20+
;; These tests sometimes get stuck and time out:
2121

2222
(cram
23-
(applies_to watching-eager-concurrent-build-command)
23+
(applies_to watching-eager-concurrent-build-command
24+
watching-eager-concurrent-exec-command)
2425
(enabled_if false))
Lines changed: 50 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,50 @@
1+
Demonstrate running "dune exec" concurrently with an eager rpc server.
2+
3+
$ echo '(lang dune 3.18)' > dune-project
4+
$ echo '(executable (name foo))' > dune
5+
$ echo 'let () = print_endline "foo"' > foo.ml
6+
$ touch README.md
7+
8+
Just watch the readme file so we don't accidentally build foo.exe before
9+
testing the --no-build option:
10+
$ dune build README.md --watch &
11+
Success, waiting for filesystem changes...
12+
Success, waiting for filesystem changes...
13+
Success, waiting for filesystem changes...
14+
15+
Demonstrate handling the --no-build option:
16+
$ dune exec --no-build ./foo.exe
17+
Error: Program './foo.exe' isn't built yet. You need to build it first or
18+
remove the '--no-build' option.
19+
[1]
20+
21+
Demonstrate running an executable from the current project:
22+
$ dune exec ./foo.exe
23+
foo
24+
25+
Demonstrate running an executable from PATH:
26+
$ dune exec echo "bar"
27+
Warning: As this is not the main instance of Dune it is unable to locate the
28+
executable "echo" within this project. Dune will attempt to resolve the
29+
executable's name within your PATH only.
30+
bar
31+
32+
Demonstrate printing a warning if arguments are passed that would be ignored
33+
due to how Dune builds via RPC:
34+
$ dune exec --force ./foo.exe 2>&1 | sed 's/pid: [0-9]*/pid: PID/g'
35+
Warning: Your build request is being forwarded to a running Dune instance
36+
(pid: PID). Note that certain command line arguments may be ignored.
37+
foo
38+
39+
Demonstrate trying to run exec in watch mode while another watch server is running:
40+
$ dune exec ./foo.exe --watch 2>&1 | sed 's/pid: [0-9]*/pid: PID/g'
41+
Error: Another instance of dune (pid: PID) has locked the _build
42+
directory. Refusing to start a new watch server until no other instances of
43+
dune are running.
44+
45+
Demonstrate running an executable via an absolute path:
46+
$ dune exec $(which echo) "baz"
47+
baz
48+
49+
$ dune shutdown
50+
$ wait

0 commit comments

Comments
 (0)