@@ -25,7 +25,7 @@ type kind =
25
25
{ pid : Pid .t
26
26
; wait_for_watches_established : unit -> unit
27
27
}
28
- | Fsevents of Fsevents .t
28
+ | Fsevents of Fsevents .t Nonempty_list .t
29
29
| Inotify of Inotify_lib .t
30
30
31
31
type t =
@@ -171,8 +171,11 @@ let shutdown t =
171
171
| Fsevents fsevents ->
172
172
`Thunk
173
173
(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;
176
179
Fsevents.RunLoop. stop runloop)
177
180
178
181
let buffer_capacity = 65536
@@ -218,7 +221,11 @@ module Buffer = struct
218
221
end
219
222
220
223
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
222
229
fun () -> Lazy. force path
223
230
224
231
let special_file_for_inotify_sync_absolute =
@@ -299,10 +306,12 @@ let select_watcher_backend () =
299
306
fswatch_backend ()
300
307
301
308
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"
303
311
304
312
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;
306
315
emit_sync ()
307
316
308
317
let spawn_external_watcher ~root ~backend =
@@ -425,16 +434,39 @@ let create_inotifylib ~scheduler =
425
434
let create_fsevents ~(scheduler : Scheduler.t ) =
426
435
prepare_sync () ;
427
436
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
428
463
let fsevents =
429
464
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 ->
431
466
scheduler.thread_safe_send_emit_events_job (fun () ->
432
467
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
437
468
let action = Fsevents.Event. action event in
469
+ let path = path event in
438
470
if is_special_file_for_inotify_sync path then
439
471
match action with
440
472
| Unknown
@@ -463,19 +495,20 @@ let create_fsevents ~(scheduler : Scheduler.t) =
463
495
scheduler.spawn_thread (fun () ->
464
496
let runloop = Fsevents.RunLoop. in_current_thread () in
465
497
Fsevents. start fsevents runloop;
498
+ Fsevents. start fsevents_special runloop;
466
499
match Fsevents.RunLoop. run_current_thread runloop with
467
500
| Ok () -> ()
468
501
| Error exn ->
469
502
Code_error. raise " fsevents callback raised" [ (" exn" , Exn. to_dyn exn ) ]);
470
503
Fsevents. set_exclusion_paths fsevents
471
504
~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 }
479
512
480
513
let create_external ~root ~debounce_interval ~scheduler ~backend =
481
514
match debounce_interval with
0 commit comments