Skip to content

Commit 09a0dbe

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 15bddb5 commit 09a0dbe

File tree

3 files changed

+160
-25
lines changed

3 files changed

+160
-25
lines changed

bin/exec.ml

Lines changed: 103 additions & 25 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,6 +168,68 @@ let step ~setup ~prog ~args ~common ~no_rebuild ~context ~on_exit () =
164168
| exit_code -> on_exit exit_code
165169
;;
166170

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 = function
215+
| Cmd_arg.Terminal s -> s
216+
| Expandable (_, raw) ->
217+
(* Pforms cannot be expanded without running the build system. *)
218+
User_error.raise
219+
[ Pp.textf
220+
"The term %S contains a pform variable but Dune is unable to expand pform \
221+
variables when 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+
167233
let term : unit Term.t =
168234
let+ builder = Common.Builder.term
169235
and+ context = Common.context_arg ~doc:{|Run the command in this build context.|}
@@ -189,11 +255,23 @@ let term : unit Term.t =
189255
let* () = Fiber.return @@ Scheduler.maybe_clear_screen ~details_hum:[] config in
190256
build @@ step ~setup ~prog ~args ~common ~no_rebuild ~context ~on_exit
191257
| No ->
192-
Scheduler.go_with_rpc_server ~common ~config
193-
@@ fun () ->
194-
let open Fiber.O in
195-
let* setup = Import.Main.setup () in
196-
build_exn @@ step ~setup ~prog ~args ~common ~no_rebuild ~context ~on_exit:exit
258+
(match Dune_util.Global_lock.lock ~timeout:None with
259+
| Error lock_held_by ->
260+
User_warning.emit
261+
[ Dune_util.Global_lock.Lock_held_by.message lock_held_by
262+
; Pp.text
263+
"While one instance of Dune is already running, subsequent invocations of \
264+
Dune will run with reduced functionality and some command-line arguments \
265+
will be ignored."
266+
];
267+
Scheduler.go_without_rpc_server ~common ~config
268+
@@ fun () -> exec_building_via_rpc_server ~common ~prog ~args ~no_rebuild
269+
| Ok () ->
270+
Scheduler.go_with_rpc_server ~common ~config
271+
@@ fun () ->
272+
let open Fiber.O in
273+
let* setup = Import.Main.setup () in
274+
build_exn @@ step ~setup ~prog ~args ~common ~no_rebuild ~context ~on_exit:exit)
197275
;;
198276

199277
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)
Lines changed: 55 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,55 @@
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 "Hello, World!"' > 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+
14+
Demonstrate handling the --no-build option:
15+
$ dune exec --no-build ./foo.exe 2>&1 | sed 's/pid: [0-9]*/pid: PID/g'
16+
Warning: A running dune (pid: PID) instance has locked the build
17+
directory. If this is not the case, please delete "_build/.lock".
18+
While one instance of Dune is already running, subsequent invocations of Dune
19+
will run with reduced functionality and some command-line arguments will be
20+
ignored.
21+
Error: Program './foo.exe' isn't built yet. You need to build it first or
22+
remove the '--no-build' option.
23+
24+
Demonstrate running an executable from the current project:
25+
$ dune exec ./foo.exe 2>&1 | sed 's/pid: [0-9]*/pid: PID/g'
26+
Warning: A running dune (pid: PID) instance has locked the build
27+
directory. If this is not the case, please delete "_build/.lock".
28+
While one instance of Dune is already running, subsequent invocations of Dune
29+
will run with reduced functionality and some command-line arguments will be
30+
ignored.
31+
Hello, World!
32+
33+
Demonstrate running an executable from PATH:
34+
$ dune exec echo "Hello, World!" 2>&1 | sed 's/pid: [0-9]*/pid: PID/g'
35+
Warning: A running dune (pid: PID) instance has locked the build
36+
directory. If this is not the case, please delete "_build/.lock".
37+
While one instance of Dune is already running, subsequent invocations of Dune
38+
will run with reduced functionality and some command-line arguments will be
39+
ignored.
40+
Warning: As this is not the main instance of Dune it is unable to locate the
41+
executable "echo" within this project. Dune will attempt to resolve the
42+
executable's name within your PATH only.
43+
Hello, World!
44+
45+
Demonstrate running an executable via an absolute path:
46+
$ dune exec $(which echo) "Hello, World!" 2>&1 | sed 's/pid: [0-9]*/pid: PID/g'
47+
Warning: A running dune (pid: PID) instance has locked the build
48+
directory. If this is not the case, please delete "_build/.lock".
49+
While one instance of Dune is already running, subsequent invocations of Dune
50+
will run with reduced functionality and some command-line arguments will be
51+
ignored.
52+
Hello, World!
53+
54+
$ dune shutdown
55+
$ wait

0 commit comments

Comments
 (0)