Skip to content

Commit

Permalink
Fix
Browse files Browse the repository at this point in the history
Signed-off-by: nojebar <[email protected]>
  • Loading branch information
nojb committed Feb 8, 2023
1 parent a7602ba commit a0d4b97
Show file tree
Hide file tree
Showing 4 changed files with 10 additions and 11 deletions.
1 change: 0 additions & 1 deletion .ocamlformat
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
version=0.21.0
profile=conventional
ocaml-version=4.08.0
break-separators=before
Expand Down
12 changes: 8 additions & 4 deletions src/dune_file_watcher/dune_file_watcher.ml
Original file line number Diff line number Diff line change
Expand Up @@ -210,7 +210,8 @@ let shutdown t =
Fsevents.stop fsevents.sync;
Watch_trie.to_list fsevents.external_
|> List.iter ~f:(fun (_, fs) -> Fsevents.stop fs))
| Fswatch_win _t -> `Thunk (fun () -> ()) (* TODO: clean up resources. *)
| Fswatch_win _t -> `Thunk (fun () -> ())
(* TODO: clean up resources. *)

let buffer_capacity = 65536

Expand Down Expand Up @@ -608,7 +609,11 @@ 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 (should_exclude filename) then
let normalized_filename =
String.concat ~sep:"/"
(String.split_on_char ~sep:'\\' (String.lowercase_ascii filename))
in
if not (should_exclude normalized_filename) then
scheduler.thread_safe_send_emit_events_job (fun () ->
let kind =
match Fswatch_win.Event.action event with
Expand Down Expand Up @@ -663,8 +668,7 @@ let parent_directory ext =
match Path.External.parent p with
| None ->
User_warning.emit
[ Pp.textf "Refusing to watch %s" (Path.External.to_string ext)
];
[ Pp.textf "Refusing to watch %s" (Path.External.to_string ext) ];
None
| Some ext -> loop ext
in
Expand Down
2 changes: 1 addition & 1 deletion src/fswatch_win/fswatch_win.ml
Original file line number Diff line number Diff line change
Expand Up @@ -59,6 +59,6 @@ let wait t =
(function
| { Event.action = Modified; path; directory } -> (
try not (Sys.is_directory (Filename.concat directory path))
with Sys_error _ -> false)
with Sys_error _ -> true)
| _ -> true)
(get_events t.fsenv)
6 changes: 1 addition & 5 deletions src/fswatch_win/fswatch_win_stubs.c
Original file line number Diff line number Diff line change
Expand Up @@ -245,9 +245,6 @@ static DWORD WINAPI watch_thread(LPVOID param) {
}
}

#define FILE_OPEN_FLAGS \
(FILE_SHARE_READ | FILE_SHARE_WRITE | FILE_SHARE_DELETE)

value fswatch_win_add(value v_fsenv, value v_path) {
CAMLparam2(v_fsenv, v_path);
static HANDLE thread = NULL;
Expand All @@ -262,8 +259,7 @@ value fswatch_win_add(value v_fsenv, value v_path) {

path = caml_stat_strdup_to_utf16(String_val(v_path));
dir_handle =
CreateFileW(path, FILE_LIST_DIRECTORY,
FILE_SHARE_READ | FILE_SHARE_WRITE | FILE_SHARE_DELETE,
CreateFileW(path, FILE_LIST_DIRECTORY, FILE_SHARE_READ | FILE_SHARE_DELETE,
NULL, OPEN_EXISTING,
FILE_FLAG_BACKUP_SEMANTICS | FILE_FLAG_OVERLAPPED, NULL);
caml_stat_free(path);
Expand Down

0 comments on commit a0d4b97

Please sign in to comment.