Skip to content

Commit

Permalink
Fix exec -w for relative paths with --root argument
Browse files Browse the repository at this point in the history
Passing --root to `dune build` and `dune exec` causes relative paths
to files to be resolved relative to the workspace root rather than the
working directory (in addition to its main function of explicitly
setting the workspace root directory). This was not implemented
correctly for exec watch mode, where relative paths would be resolved
relative to the working directory instead.

There was already a test for this which was failing, however the test
is disabled in CI as it is known to be flaky.

Signed-off-by: Stephen Sherratt <[email protected]>
  • Loading branch information
gridbugs committed Oct 1, 2024
1 parent 63fac22 commit d361ee4
Show file tree
Hide file tree
Showing 4 changed files with 30 additions and 20 deletions.
26 changes: 15 additions & 11 deletions bin/exec.ml
Original file line number Diff line number Diff line change
Expand Up @@ -77,22 +77,26 @@ module Command_to_exec = struct

(* Helper function to spawn a new process running a command in an
environment, returning the new process' pid *)
let spawn_process path ~args ~env =
let spawn_process (common : Common.t) path ~args ~env =
let pid =
let path = Path.to_string path in
let prog = string_path_relative_to_specified_root common (Path.to_string path) in
let env = Env.to_unix env |> Spawn.Env.of_list in
let argv = path :: args in
let argv = prog :: args in
let cwd = Spawn.Working_dir.Path Fpath.initial_cwd in
Spawn.spawn ~prog:path ~env ~cwd ~argv ()
Spawn.spawn ~prog ~env ~cwd ~argv ()
in
Pid.of_int pid
;;

(* Run the command, first (re)building the program which the command is
invoking *)
let build_and_run_in_child_process { get_path_and_build_if_necessary; prog; args; env } =
let build_and_run_in_child_process
common
{ get_path_and_build_if_necessary; prog; args; env }
=
get_path_and_build_if_necessary prog
|> Fiber.map ~f:(Result.map ~f:(spawn_process ~args ~env))
|> Fiber.map
~f:(Result.map ~f:(fun exe_path -> spawn_process common ~args ~env exe_path))
;;
end

Expand Down Expand Up @@ -139,18 +143,18 @@ module Watch = struct

(* Kills the currently running process, then runs the given command after
(re)building the program which it will invoke *)
let run state ~command_to_exec =
let run common state ~command_to_exec =
let open Fiber.O in
let* () = Fiber.return () in
let* () = kill_currently_running_process state in
let* command_to_exec = command_to_exec () in
Command_to_exec.build_and_run_in_child_process command_to_exec
Command_to_exec.build_and_run_in_child_process common command_to_exec
>>| Result.map ~f:(fun pid -> state.currently_running_pid := Some pid)
;;

let loop ~command_to_exec =
let loop common ~command_to_exec =
let state = init_state () in
Scheduler.Run.poll (run state ~command_to_exec)
Scheduler.Run.poll (run common state ~command_to_exec)
;;
end

Expand Down Expand Up @@ -322,7 +326,7 @@ module Exec_context = struct
; env
}
in
Watch.loop ~command_to_exec
Watch.loop common ~command_to_exec
;;
end

Expand Down
18 changes: 10 additions & 8 deletions bin/import.ml
Original file line number Diff line number Diff line change
Expand Up @@ -237,14 +237,16 @@ module Scheduler = struct
;;
end

let restore_cwd_and_execve (common : Common.t) prog argv env =
let prog =
if Filename.is_relative prog
then (
let root = Common.root common in
Filename.concat root.dir prog)
else prog
in
let string_path_relative_to_specified_root (common : Common.t) path =
if Filename.is_relative path
then (
let root = Common.root common in
Filename.concat root.dir path)
else path
;;

let restore_cwd_and_execve common prog argv env =
let prog = string_path_relative_to_specified_root common prog in
Proc.restore_cwd_and_execve prog argv ~env
;;

Expand Down
2 changes: 2 additions & 0 deletions doc/changes/10982.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
- Fix exec -w for relative paths with --root argument (#10982,
@gridbugs)
Original file line number Diff line number Diff line change
Expand Up @@ -22,8 +22,10 @@ Perform the same test above but first enter the "bin" directory.
Success, waiting for filesystem changes...
foo
Leaving directory '..'
$ PID=$!
$ cd ..
$ wait
$ ../wait-for-file.sh $DONE_FLAG
$ kill $PID

Test that the behaviour is the same when not running with "--watch"
$ cd bin && dune exec --root .. ./bin/main.exe
Expand Down

0 comments on commit d361ee4

Please sign in to comment.