Skip to content

Commit

Permalink
Share exclude patterns
Browse files Browse the repository at this point in the history
Signed-off-by: nojebar <[email protected]>
  • Loading branch information
nojb committed Feb 11, 2023
1 parent f02fefa commit 78ed4b2
Showing 1 changed file with 4 additions and 24 deletions.
28 changes: 4 additions & 24 deletions src/dune_file_watcher/dune_file_watcher.ml
Original file line number Diff line number Diff line change
Expand Up @@ -160,6 +160,9 @@ let exclude_patterns =
; {|/#[^#]*#$|}
; {|^4913$|} (* https://github.com/neovim/neovim/issues/3460 *)
; {|/4913$|}
; {|/.git|}
; {|/.hg|}
; {|:/windows|}
]

module Re = Dune_re
Expand Down Expand Up @@ -588,29 +591,6 @@ let create_fsevents ?(latency = 0.2) ~(scheduler : Scheduler.t) () =
; sync_table
}

let fswatch_win_exclude_patterns =
Re.compile
(Re.alt
[ Re.str "/_opam"
; Re.str "/_esy"
; Re.str
"/.#" (* Such files can be created by Emacs and also Dune itself. *)
; Re.seq [ Re.char '~'; Re.eos ]
; Re.str "/#"
; Re.str "/4913" (* https://github.com/neovim/neovim/issues/3460 *)
; Re.str "/.git"
; Re.str "/.hg"
; Re.str ":/windows"
])

let fswatch_win_should_exclude path =
let path =
String.concat ~sep:"/"
(String.split_on_char ~sep:'\\'
(String.lowercase_ascii (Path.to_string path)))
in
Re.execp fswatch_win_exclude_patterns path

let fswatch_win_callback ~(scheduler : Scheduler.t) ~sync_table event =
let dir = Fswatch_win.Event.directory event in
let filename = Filename.concat dir (Fswatch_win.Event.path event) in
Expand All @@ -628,7 +608,7 @@ let fswatch_win_callback ~(scheduler : Scheduler.t) ~sync_table event =
scheduler.thread_safe_send_emit_events_job (fun () -> [ Sync id ]))
| Removed | Renamed_new | Renamed_old -> ())
| path ->
if not (fswatch_win_should_exclude path) then
if not (should_exclude filename) then
scheduler.thread_safe_send_emit_events_job (fun () ->
let kind =
match Fswatch_win.Event.action event with
Expand Down

0 comments on commit 78ed4b2

Please sign in to comment.