Skip to content

Commit

Permalink
fix: watch mode when PATH contains CWD
Browse files Browse the repository at this point in the history
On MacOS, PATH=.:PWD would add build paths to the list of directories
being watched. Fsevents only reports absolute paths, so we need to try
and convert them to build/source/external paths. On Linux, watching .
would produce relative (source paths), so this issue wouldn't occur.

Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg committed Mar 31, 2023
1 parent 2517bb4 commit 20c447e
Show file tree
Hide file tree
Showing 10 changed files with 60 additions and 95 deletions.
3 changes: 3 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,9 @@ Unreleased
`dune coq top` to obtain fast re-building of dependencies (with no checking
of proofs) prior to stepping into a file. (#7406, @rlepigre)

- Fix dune crashing on MacOS in watch mode whenever `$PATH` contains `$PWD`
(#7441, fixes #6907, @rgrinberg)

- Fix `dune install` when cross compiling (#7410, fixes #6191, @anmonteiro,
@rizo)

Expand Down
10 changes: 0 additions & 10 deletions otherlibs/stdune/src/copyfile_stubs.c
Original file line number Diff line number Diff line change
Expand Up @@ -50,20 +50,10 @@ CAMLprim value stdune_copyfile(value v_from, value v_to) {
CAMLreturn(Val_unit);
}

CAMLprim value stdune_is_darwin(value v_unit) {
CAMLparam1(v_unit);
CAMLreturn(Val_true);
}

#else

CAMLprim value stdune_copyfile(value v_from, value v_to) {
caml_failwith("copyfile: only on macos");
}

CAMLprim value stdune_is_darwin(value v_unit) {
CAMLparam1(v_unit);
CAMLreturn(Val_false);
}

#endif
2 changes: 1 addition & 1 deletion otherlibs/stdune/src/dune
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,6 @@
(re_export dune_filesystem_stubs))
(foreign_stubs
(language c)
(names wait3_stubs copyfile_stubs))
(names wait3_stubs platform_stubs copyfile_stubs))
(instrumentation
(backend bisect_ppx)))
8 changes: 3 additions & 5 deletions otherlibs/stdune/src/io.ml
Original file line number Diff line number Diff line change
Expand Up @@ -253,18 +253,16 @@ struct
it does COW when edited. It will also default back to regular copying if
it fails for w/e reason *)
external copyfile : string -> string -> unit = "stdune_copyfile"

external available : unit -> bool = "stdune_is_darwin"
end

let copy_file ?chmod ~src ~dst () =
Exn.protectx (setup_copy ?chmod ~src ~dst ()) ~finally:close_both
~f:(fun (ic, oc) -> copy_channels ic oc)

let copy_file =
match Copyfile.available () with
| false -> copy_file
| true -> (
match Platform.OS.value with
| Other -> copy_file
| Darwin -> (
fun ?chmod ~src ~dst () ->
let src = Path.to_string src in
let dst = Path.to_string dst in
Expand Down
19 changes: 19 additions & 0 deletions otherlibs/stdune/src/platform.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,19 @@
module OS = struct
type t =
| Darwin
| Other

let equal = Poly.equal

external is_darwin : unit -> bool = "stdune_is_darwin"

let to_dyn = function
| Darwin -> Dyn.variant "Darwin" []
| Other -> Dyn.variant "Other" []

let value = if is_darwin () then Darwin else Other
end

let assert_os what =
if not (OS.equal OS.value what) then
Code_error.raise "unexpected os" [ ("os", OS.(to_dyn value)) ]
9 changes: 9 additions & 0 deletions otherlibs/stdune/src/platform.mli
Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
module OS : sig
type t =
| Darwin
| Other

val value : t
end

val assert_os : OS.t -> unit
11 changes: 11 additions & 0 deletions otherlibs/stdune/src/platform_stubs.c
Original file line number Diff line number Diff line change
@@ -0,0 +1,11 @@
#include <caml/memory.h>
#include <caml/mlvalues.h>

CAMLprim value stdune_is_darwin(value v_unit) {
CAMLparam1(v_unit);
#if defined(__APPLE__)
CAMLreturn(Val_true);
#else
CAMLreturn(Val_false);
#endif
}
1 change: 1 addition & 0 deletions otherlibs/stdune/src/stdune.ml
Original file line number Diff line number Diff line change
Expand Up @@ -71,6 +71,7 @@ module Dune_filesystem_stubs = Dune_filesystem_stubs
module Predicate = Predicate
module Bytes_unit = Bytes_unit
module Dev_null = Dev_null
module Platform = Platform

module Unix_error = struct
include Dune_filesystem_stubs.Unix_error
Expand Down
13 changes: 9 additions & 4 deletions src/dune_engine/fs_memo.ml
Original file line number Diff line number Diff line change
Expand Up @@ -337,9 +337,14 @@ let invalidate_path_and_its_parent path =
directory should be added to or removed from the result. *)
let handle_fs_event ({ kind; path } : Dune_file_watcher.Fs_memo_event.t) :
Memo.Invalidation.t =
let path = Path.as_outside_build_dir_exn path in
match kind with
| File_changed -> Watcher.invalidate path
| Created | Deleted | Unknown -> invalidate_path_and_its_parent path
match Path.destruct_build_dir path with
| `Inside _ ->
(* This can occur on MacOS when [PATH=.:$PATH] for example *)
Platform.assert_os Darwin;
Memo.Invalidation.empty
| `Outside path -> (
match kind with
| File_changed -> Watcher.invalidate path
| Created | Deleted | Unknown -> invalidate_path_and_its_parent path)

let init = Watcher.init
79 changes: 4 additions & 75 deletions test/blackbox-tests/test-cases/watching/path-pwd.t
Original file line number Diff line number Diff line change
Expand Up @@ -19,84 +19,13 @@ Reproduce #6907
> EOF

$ build y
Error: { payload = Some [ [ "id"; [ "auto"; "0" ] ] ]
; message =
"connection terminated. this request will never receive a response"
; kind = Connection_dead
}
Success

$ touch x

$ build y
Timed out
Internal error, please report upstream including the contents of _build/log.
Description:
("as_outside_build_dir_exn", { path = In_build_dir ".sync/0" })
Raised at Stdune__Code_error.raise in file
"otherlibs/stdune/src/code_error.ml", line 11, characters 30-62
Called from Dune_engine__Fs_memo.handle_fs_event in file
"src/dune_engine/fs_memo.ml", line 289, characters 13-47
Called from
Dune_engine__Scheduler.Run_once.handle_invalidation_events.handle_event in
file "src/dune_engine/scheduler.ml", line 966, characters 26-55
Called from Stdlib__List.fold_left in file "list.ml", line 121, characters
24-34
Called from Dune_engine__Scheduler.Run_once.build_input_change in file
"src/dune_engine/scheduler.ml", line 1002, characters 23-56
Called from Fiber.run.loop in file "otherlibs/fiber/src/fiber.ml", line 15,
characters 51-60
Called from Dune_engine__Scheduler.Run_once.run in file
"src/dune_engine/scheduler.ml", line 1069, characters 10-50
Re-raised at Stdune__Exn.raise_with_backtrace in file
"otherlibs/stdune/src/exn.ml", line 36, characters 27-56
Called from Cmdliner_term.app.(fun) in file
"vendor/cmdliner/src/cmdliner_term.ml", line 24, characters 19-24
Called from Cmdliner_eval.run_parser in file
"vendor/cmdliner/src/cmdliner_eval.ml", line 34, characters 37-44
Called from Cmdliner_eval.eval_value in file
"vendor/cmdliner/src/cmdliner_eval.ml", line 202, characters 14-39
Called from Dune__exe__Main in file "bin/main.ml", line 97, characters 10-41

I must not crash. Uncertainty is the mind-killer. Exceptions are the
little-death that brings total obliteration. I will fully express my cases.
Execution will pass over me and through me. And when it has gone past, I
will unwind the stack along its path. Where the cases are handled there will
be nothing. Only I will remain.
exit 1
Success

$ stop_dune
Error: rpc server not running
Internal error, please report upstream including the contents of _build/log.
Description:
("as_outside_build_dir_exn", { path = In_build_dir ".sync/0" })
Raised at Stdune__Code_error.raise in file
"otherlibs/stdune/src/code_error.ml", line 11, characters 30-62
Called from Dune_engine__Fs_memo.handle_fs_event in file
"src/dune_engine/fs_memo.ml", line 289, characters 13-47
Called from
Dune_engine__Scheduler.Run_once.handle_invalidation_events.handle_event in
file "src/dune_engine/scheduler.ml", line 966, characters 26-55
Called from Stdlib__List.fold_left in file "list.ml", line 121, characters
24-34
Called from Dune_engine__Scheduler.Run_once.build_input_change in file
"src/dune_engine/scheduler.ml", line 1002, characters 23-56
Called from Fiber.run.loop in file "otherlibs/fiber/src/fiber.ml", line 15,
characters 51-60
Called from Dune_engine__Scheduler.Run_once.run in file
"src/dune_engine/scheduler.ml", line 1069, characters 10-50
Re-raised at Stdune__Exn.raise_with_backtrace in file
"otherlibs/stdune/src/exn.ml", line 36, characters 27-56
Called from Cmdliner_term.app.(fun) in file
"vendor/cmdliner/src/cmdliner_term.ml", line 24, characters 19-24
Called from Cmdliner_eval.run_parser in file
"vendor/cmdliner/src/cmdliner_eval.ml", line 34, characters 37-44
Called from Cmdliner_eval.eval_value in file
"vendor/cmdliner/src/cmdliner_eval.ml", line 202, characters 14-39
Called from Dune__exe__Main in file "bin/main.ml", line 97, characters 10-41

I must not crash. Uncertainty is the mind-killer. Exceptions are the
little-death that brings total obliteration. I will fully express my cases.
Execution will pass over me and through me. And when it has gone past, I
will unwind the stack along its path. Where the cases are handled there will
be nothing. Only I will remain.
exit 1
Success, waiting for filesystem changes...
Success, waiting for filesystem changes...

0 comments on commit 20c447e

Please sign in to comment.