Skip to content

Commit 53257f5

Browse files
committed
fix(fsevents): better sync file handling
We move the sync file to _build/.sync. This is done to be able to setup a private watch for it and ignore the _build directory. This is good for fsevents as it allows us to drop watching the possibly massive build directory. Signed-off-by: Rudi Grinberg <me@rgrinberg.com>
1 parent a29390d commit 53257f5

File tree

1 file changed

+51
-18
lines changed

1 file changed

+51
-18
lines changed

src/dune_file_watcher/dune_file_watcher.ml

+51-18
Original file line numberDiff line numberDiff line change
@@ -25,7 +25,7 @@ type kind =
2525
{ pid : Pid.t
2626
; wait_for_watches_established : unit -> unit
2727
}
28-
| Fsevents of Fsevents.t
28+
| Fsevents of Fsevents.t Nonempty_list.t
2929
| Inotify of Inotify_lib.t
3030

3131
type t =
@@ -171,8 +171,11 @@ let shutdown t =
171171
| Fsevents fsevents ->
172172
`Thunk
173173
(fun () ->
174-
let runloop = Option.value_exn (Fsevents.runloop fsevents) in
175-
Fsevents.stop fsevents;
174+
let fsevents = Nonempty_list.to_list fsevents in
175+
let runloop =
176+
List.hd fsevents |> Fsevents.runloop |> Option.value_exn
177+
in
178+
List.iter fsevents ~f:Fsevents.stop;
176179
Fsevents.RunLoop.stop runloop)
177180

178181
let buffer_capacity = 65536
@@ -218,7 +221,11 @@ module Buffer = struct
218221
end
219222

220223
let special_file_for_inotify_sync =
221-
let path = lazy (Path.Build.relative Path.Build.root "dune-inotify-sync") in
224+
let path =
225+
lazy
226+
(let dir = Path.Build.relative Path.Build.root ".sync" in
227+
Path.Build.relative dir "dune-inotify-sync")
228+
in
222229
fun () -> Lazy.force path
223230

224231
let special_file_for_inotify_sync_absolute =
@@ -299,10 +306,12 @@ let select_watcher_backend () =
299306
fswatch_backend ()
300307

301308
let emit_sync () =
302-
Io.write_file (Path.build (special_file_for_inotify_sync ())) "z"
309+
let path = Path.build (special_file_for_inotify_sync ()) in
310+
Io.write_file path "z"
303311

304312
let prepare_sync () =
305-
Path.mkdir_p (Path.parent_exn (Path.build (special_file_for_inotify_sync ())));
313+
let dir = Path.parent_exn (Path.build (special_file_for_inotify_sync ())) in
314+
Path.mkdir_p dir;
306315
emit_sync ()
307316

308317
let spawn_external_watcher ~root ~backend =
@@ -425,16 +434,39 @@ let create_inotifylib ~scheduler =
425434
let create_fsevents ~(scheduler : Scheduler.t) =
426435
prepare_sync ();
427436
let ignored_files = Table.create (module String) 64 in
437+
let latency = 0.2 in
438+
let path event =
439+
Fsevents.Event.path event |> Path.of_string
440+
|> Path.Expert.try_localize_external
441+
in
442+
let fsevents_special =
443+
Fsevents.create
444+
~paths:
445+
[ special_file_for_inotify_sync ()
446+
|> Path.Build.parent_exn |> Path.build |> Path.to_absolute_filename
447+
]
448+
~latency
449+
~f:(fun events ->
450+
scheduler.thread_safe_send_emit_events_job (fun () ->
451+
List.filter_map events ~f:(fun event ->
452+
let action = Fsevents.Event.action event in
453+
if is_special_file_for_inotify_sync (path event) then
454+
match action with
455+
| Unknown
456+
| Create
457+
| Modify ->
458+
Some Event.Sync
459+
| Remove -> None
460+
else
461+
None)))
462+
in
428463
let fsevents =
429464
let paths = [ Path.to_string Path.root ] in
430-
Fsevents.create ~paths ~latency:0.2 ~f:(fun events ->
465+
Fsevents.create ~paths ~latency ~f:(fun events ->
431466
scheduler.thread_safe_send_emit_events_job (fun () ->
432467
List.filter_map events ~f:(fun event ->
433-
let path =
434-
Fsevents.Event.path event |> Path.of_string
435-
|> Path.Expert.try_localize_external
436-
in
437468
let action = Fsevents.Event.action event in
469+
let path = path event in
438470
if is_special_file_for_inotify_sync path then
439471
match action with
440472
| Unknown
@@ -463,19 +495,20 @@ let create_fsevents ~(scheduler : Scheduler.t) =
463495
scheduler.spawn_thread (fun () ->
464496
let runloop = Fsevents.RunLoop.in_current_thread () in
465497
Fsevents.start fsevents runloop;
498+
Fsevents.start fsevents_special runloop;
466499
match Fsevents.RunLoop.run_current_thread runloop with
467500
| Ok () -> ()
468501
| Error exn ->
469502
Code_error.raise "fsevents callback raised" [ ("exn", Exn.to_dyn exn) ]);
470503
Fsevents.set_exclusion_paths fsevents
471504
~paths:
472-
((* For now, we don't ignore the build directroy because we want to
473-
receive events from the special event sync event *)
474-
[ "_esy"; "_opam"; ".git"; ".hg" ]
475-
|> List.rev_map ~f:(fun base ->
476-
let path = Path.relative (Path.source Path.Source.root) base in
477-
Path.to_absolute_filename path));
478-
{ kind = Fsevents fsevents; ignored_files }
505+
(Path.(build Build.root)
506+
:: ([ "_esy"; "_opam"; ".git"; ".hg" ]
507+
|> List.rev_map ~f:(fun base ->
508+
let path = Path.relative (Path.source Path.Source.root) base in
509+
path))
510+
|> List.rev_map ~f:Path.to_absolute_filename);
511+
{ kind = Fsevents [ fsevents; fsevents_special ]; ignored_files }
479512

480513
let create_external ~root ~debounce_interval ~scheduler ~backend =
481514
match debounce_interval with

0 commit comments

Comments
 (0)