@@ -64,7 +64,16 @@ module Cmd_arg = struct
64
64
let conv = Arg. conv ((fun s -> Ok (parse s)), pp)
65
65
end
66
66
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 =
68
77
let open Memo.O in
69
78
let + hints =
70
79
(* Good candidates for the "./x.exe" instead of "x.exe" error are
@@ -81,30 +90,25 @@ let not_found ~dir ~prog =
81
90
in
82
91
User_message. did_you_mean prog ~candidates
83
92
in
93
+ not_found ~hints ~prog
94
+ ;;
95
+
96
+ let program_not_built_yet prog =
84
97
User_error. raise
85
- ~hints
86
98
[ Pp. concat
87
99
~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
+ ]
89
106
]
90
107
;;
91
108
92
109
let build_prog ~no_rebuild ~prog p =
93
110
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
108
112
else
109
113
let open Memo.O in
110
114
let + () = Build_system. build_file p in
@@ -117,14 +121,14 @@ let get_path_and_build_if_necessary sctx ~no_rebuild ~dir ~prog =
117
121
| In_path ->
118
122
Super_context. resolve_program_memo sctx ~dir ~loc: None prog
119
123
>> = (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
121
125
| Ok p -> build_prog ~no_rebuild ~prog p)
122
126
| Relative_to_current_dir ->
123
127
let path = Path. relative_to_source_in_build_or_external ~dir prog in
124
128
Build_system. file_exists path
125
129
>> = (function
126
130
| true -> build_prog ~no_rebuild ~prog path
127
- | false -> not_found ~dir ~prog )
131
+ | false -> not_found_with_suggestions ~dir ~prog )
128
132
| Absolute ->
129
133
(match
130
134
let prog = Path. of_string prog in
@@ -137,7 +141,7 @@ let get_path_and_build_if_necessary sctx ~no_rebuild ~dir ~prog =
137
141
Option. some_if (Path. exists prog) prog)
138
142
with
139
143
| Some prog -> Memo. return prog
140
- | None -> not_found ~dir ~prog )
144
+ | None -> not_found_with_suggestions ~dir ~prog )
141
145
;;
142
146
143
147
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 () =
164
168
| exit_code -> on_exit exit_code
165
169
;;
166
170
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 =
178
248
match Common. watch common with
179
249
| Yes Passive ->
180
250
User_error. raise [ Pp. textf " passive watch mode is unsupported by exec" ]
@@ -209,4 +279,43 @@ let term : unit Term.t =
209
279
restore_cwd_and_execve (Common. root common) prog args env)
210
280
;;
211
281
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
+
212
321
let command = Cmd. v info term
0 commit comments