Skip to content

Commit

Permalink
Remove readonly attribute on Windows before unlink
Browse files Browse the repository at this point in the history
The legacy DOS readonly attribute is a tedious difference on Windows,
because a user may have permission to delete a file, but unlink fails
because the attribute is set.

Signed-off-by: David Allsopp <[email protected]>
  • Loading branch information
dra27 committed Sep 6, 2017
1 parent ee63bca commit 395872a
Show file tree
Hide file tree
Showing 2 changed files with 20 additions and 3 deletions.
1 change: 1 addition & 0 deletions src/action.ml
Original file line number Diff line number Diff line change
Expand Up @@ -560,6 +560,7 @@ let rec exec t ~ectx ~dir ~env_extra ~stdout_to ~stderr_to =
match Unix.readlink dst with
| target ->
if target <> src then begin
(* @@DRA Win32 remove read-only attribute needed when symlinking enabled *)
Unix.unlink dst;
Unix.symlink src dst
end
Expand Down
22 changes: 19 additions & 3 deletions src/path.ml
Original file line number Diff line number Diff line change
Expand Up @@ -373,8 +373,24 @@ let exists t = Sys.file_exists (to_string t)
let readdir t = Sys.readdir (to_string t) |> Array.to_list
let is_directory t = Sys.is_directory (to_string t)
let rmdir t = Unix.rmdir (to_string t)
let unlink t = Unix.unlink (to_string t)
let unlink_no_err t = try Unix.unlink (to_string t) with _ -> ()
let win32_unlink fn =
try
Unix.unlink fn
with Unix.Unix_error (Unix.EACCES, _, _) as e ->
(* Try removing the read-only attribute *)
try
Unix.chmod fn 0o666;
Unix.unlink fn
with _ ->
raise e
let unlink_operation =
if Sys.win32 then
win32_unlink
else
Unix.unlink
let unlink t =
unlink_operation (to_string t)
let unlink_no_err t = try unlink t with _ -> ()

let extend_basename t ~suffix = t ^ suffix

Expand Down Expand Up @@ -403,7 +419,7 @@ let rm_rf =
let fn = Filename.concat dir fn in
match Unix.lstat fn with
| { st_kind = S_DIR; _ } -> loop fn
| _ -> Unix.unlink fn);
| _ -> unlink_operation fn);
Unix.rmdir dir
in
fun t ->
Expand Down

0 comments on commit 395872a

Please sign in to comment.