Skip to content

Commit

Permalink
Apply rgrinberg suggestions from PR
Browse files Browse the repository at this point in the history
Signed-off-by: Jonah Beckford <71855677+jonahbeckford@users.noreply.github.com>
  • Loading branch information
jonahbeckford committed Mar 14, 2023
1 parent b3fe080 commit f6f921c
Show file tree
Hide file tree
Showing 3 changed files with 5 additions and 5 deletions.
6 changes: 3 additions & 3 deletions src/dune_file_watcher/dune_file_watcher.ml
Original file line number Diff line number Diff line change
Expand Up @@ -153,7 +153,7 @@ module Re = Dune_re
let exclude_regex watch_exclusions =
Re.compile (Re.alt (List.map watch_exclusions ~f:Re.Posix.re))

let should_exclude path watch_exclusions =
let should_exclude path ~watch_exclusions =
Re.execp (exclude_regex watch_exclusions) path

module For_tests = struct
Expand All @@ -163,7 +163,7 @@ end
let process_inotify_event (event : Async_inotify_for_dune.Async_inotify.Event.t)
watch_exclusions : Event.t list =
let create_event_unless_excluded ~kind ~path =
match should_exclude path watch_exclusions with
match should_exclude path ~watch_exclusions with
| true -> []
| false ->
let path = Path.of_string path in
Expand Down Expand Up @@ -598,7 +598,7 @@ let fswatch_win_callback ~(scheduler : Scheduler.t) ~sync_table
String.concat ~sep:"/"
(String.split_on_char ~sep:'\\' (String.lowercase_ascii filename))
in
if not (should_exclude normalized_filename watch_exclusions) then
if not (should_exclude normalized_filename ~watch_exclusions) then
scheduler.thread_safe_send_emit_events_job (fun () ->
let kind =
match Fswatch_win.Event.action event with
Expand Down
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 @@ -80,5 +80,5 @@ val emit_sync : t -> Sync_id.t
val add_watch : t -> Path.t -> (unit, [ `Does_not_exist ]) result

module For_tests : sig
val should_exclude : string -> string list -> bool
val should_exclude : string -> watch_exclusions:string list -> bool
end
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@ let printf = Printf.printf
let test string =
printf "should_exclude(%s) = %b\n" string
(Dune_file_watcher.For_tests.should_exclude string
Dune_config.standard_watch_exclusions)
~watch_exclusions:Dune_config.standard_watch_exclusions)

let%expect_test _ =
test "file.ml";
Expand Down

0 comments on commit f6f921c

Please sign in to comment.