Skip to content

Commit

Permalink
fix: remove file watcher workaround
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg committed Feb 8, 2022
1 parent bc77bfc commit dba7c8f
Show file tree
Hide file tree
Showing 4 changed files with 13 additions and 57 deletions.
40 changes: 2 additions & 38 deletions src/dune_engine/fs_memo.ml
Original file line number Diff line number Diff line change
Expand Up @@ -56,42 +56,6 @@ end = struct
it shouldn't be a problem. *)
let state = ref (Waiting_for_file_watcher [])

(* CR-someday aalekseyev: For [watch_path] to work correctly we need to ensure
that the parent directory of [path] exists. That's certainly not guaranteed
by the [Fs_memo] API, so we should do something to make it more robust, but
I believe that is masked by the fact that we usually (always?) look at the
source directory before looking for files in that directory.
It might seem that the [`Does_not_exist] "fall back to the containing dir"
trick used below can be extended to fall back all the way to the root, but
it can't be because watching the root is not sufficient to receive events
for creation of "root/a/b/c" -- for that we need to watch "root/a/b". *)
let watch_path watcher path =
match Dune_file_watcher.add_watch watcher path with
| Ok () -> ()
| Error `Does_not_exist -> (
(* If we're at the root of the workspace (or the Unix root) then we can't
get [`Does_not_exist] because Dune can't start without a workspace and
the Unix root always exists. Hence, the [_exn] below can't raise,
except if the user deletes the workspace directory under our feet, in
which case all bets are off. *)
let containing_dir = Path.parent_exn path in
(* If the [path] is absent, we need to wait for it to be created by
watching the parent. We still try to add a watch for the [path] itself
after that succeeds, in case the [path] was created already before we
started watching its parent. *)
(match Dune_file_watcher.add_watch watcher containing_dir with
| Ok () -> ()
| Error `Does_not_exist ->
Log.info
[ Pp.textf "Attempted to add watch to non-existent directory %s."
(Path.to_string containing_dir)
]);
match Dune_file_watcher.add_watch watcher path with
| Error `Does_not_exist
| Ok () ->
())

let watch_or_record_path ~accessed_path ~path_to_watch =
match !state with
| Waiting_for_file_watcher watch_records ->
Expand All @@ -100,7 +64,7 @@ end = struct
({ accessed_path; path_to_watch } :: watch_records)
| No_file_watcher -> ()
| File_watcher dune_file_watcher ->
watch_path dune_file_watcher path_to_watch
Dune_file_watcher.add_watch dune_file_watcher path_to_watch

(* This comment applies to both memoization tables below.
Expand Down Expand Up @@ -201,7 +165,7 @@ end = struct
state := File_watcher watcher;
Memo.Invalidation.map_reduce watch_records
~f:(fun { accessed_path; path_to_watch } ->
watch_path watcher path_to_watch;
Dune_file_watcher.add_watch watcher path_to_watch;
invalidate accessed_path))
end

Expand Down
16 changes: 7 additions & 9 deletions src/dune_file_watcher/dune_file_watcher.ml
Original file line number Diff line number Diff line change
Expand Up @@ -670,7 +670,7 @@ let add_watch t path =
match t.kind with
| Fsevents f -> (
match path with
| Path.In_source_tree _ -> (* already watched by source watcher *) Ok ()
| Path.In_source_tree _ -> (* already watched by source watcher *) ()
| In_build_dir _ ->
Code_error.raise "attempted to watch a directory in build" []
| External ext -> (
Expand All @@ -690,26 +690,25 @@ let add_watch t path =
loop ext
in
match ext with
| None -> Ok ()
| Some ext ->
| None -> ()
| Some ext -> (
let watch =
lazy
(fsevents ~latency:f.latency f.scheduler ~paths:[ path ]
fsevents_standard_event)
in
(match Watch_trie.add f.external_ ext watch with
match Watch_trie.add f.external_ ext watch with
| Watch_trie.Under_existing_node -> ()
| Inserted { new_t; removed } ->
let watch = Lazy.force watch in
Fsevents.start watch f.runloop;
List.iter removed ~f:(fun (_, fs) -> Fsevents.stop fs);
f.external_ <- new_t);
Ok ()))
f.external_ <- new_t)))
| Fswatch _ ->
(* Here we assume that the path is already being watched because the coarse
file watchers are expected to watch all the source files from the
start *)
Ok ()
()
| Inotify { inotify; awaiting_creation; mutex } ->
Mutex.lock mutex;
let rec loop p =
Expand All @@ -725,7 +724,6 @@ let add_watch t path =
| Some p -> loop p)
in
loop path;
Mutex.unlock mutex;
Ok ()
Mutex.unlock mutex

let emit_sync = Fs_sync.emit
2 changes: 1 addition & 1 deletion src/dune_file_watcher/dune_file_watcher.mli
Original file line number Diff line number Diff line change
Expand Up @@ -73,7 +73,7 @@ val wait_for_initial_watches_established_blocking : t -> unit
far. *)
val emit_sync : t -> Sync_id.t

val add_watch : t -> Path.t -> (unit, [ `Does_not_exist ]) result
val add_watch : t -> Path.t -> unit

module For_tests : sig
val should_exclude : string -> bool
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -32,9 +32,7 @@ let%expect_test _ =
| Watcher_terminated -> assert false)))
in
let print_events n = print_events ~try_to_get_events ~expected:n in
(match Dune_file_watcher.add_watch watcher (Path.of_string ".") with
| Error _ -> assert false
| Ok () -> ());
Dune_file_watcher.add_watch watcher (Path.of_string ".");
Dune_file_watcher.wait_for_initial_watches_established_blocking watcher;
Stdio.Out_channel.write_all "x" ~data:"x";
print_events 2;
Expand All @@ -52,9 +50,7 @@ let%expect_test _ =
{ path = In_source_tree "y"; kind = "Created" }
|}];
let (_ : _) = Fpath.mkdir_p "d/w" in
(match Dune_file_watcher.add_watch watcher (Path.of_string "d/w") with
| Error _ -> assert false
| Ok () -> ());
Dune_file_watcher.add_watch watcher (Path.of_string "d/w");
Stdio.Out_channel.write_all "d/w/x" ~data:"x";
print_events 3;
[%expect
Expand All @@ -70,9 +66,7 @@ let%expect_test _ =
{ path = In_source_tree "d/w/y"; kind = "Created" }
{ path = In_source_tree "d/w/y"; kind = "File_changed" }
|}];
(match Dune_file_watcher.add_watch watcher (Path.of_string "e/1/2") with
| Error _ -> assert false
| Ok () -> ());
Dune_file_watcher.add_watch watcher (Path.of_string "e/1/2");
let (_ : _) = Fpath.mkdir_p "e/1" in
Stdio.Out_channel.write_all "e/1/2" ~data:"z";
print_events 3;
Expand Down

0 comments on commit dba7c8f

Please sign in to comment.