Skip to content

Commit

Permalink
Proposed changes
Browse files Browse the repository at this point in the history
  • Loading branch information
dra27 authored and rjbou committed Mar 24, 2022
1 parent 1685264 commit 32226ed
Showing 1 changed file with 20 additions and 20 deletions.
40 changes: 20 additions & 20 deletions src/core/opamSystem.ml
Original file line number Diff line number Diff line change
Expand Up @@ -132,9 +132,13 @@ let remove_file file =
if
try ignore (Unix.lstat file); true with Unix.Unix_error _ -> false
then (
log "rm %s" file;
try
log "rm %s" file;
Unix.unlink file
try Unix.unlink file
with Unix.Unix_error(EACCES, _, _) when Sys.win32 ->
(* Attempt to remove the read-only bit on Windows *)
Unix.chmod file 0o666;
Unix.unlink file
with Unix.Unix_error _ as e ->
internal_error "Cannot remove %s (%s)." file (Printexc.to_string e)
)
Expand Down Expand Up @@ -180,31 +184,27 @@ let setup_copy ?(chmod = fun x -> x) ~src ~dst () =
(Unix.fstat (Unix.descr_of_in_channel ic)).st_perm |> chmod
in
let () =
(*
Windows, at least with Microsoft (MSVC) runtime library,
will give "Permission denied" if `dst` is -r-xr-xr-x (MSYS2)
or -r-x------+ (Cygwin), and then you write to the file (ex.
`open_out_gen [Open_trunc]`; `Unix.unlink`; etc.). So on
Windows always chmod the file first if we are not delegating
to MSYS2 or Cygwin executables.
*)
try if Sys.win32 || Unix.((lstat dst).st_kind <> S_REG) then
if Sys.win32 then Unix.chmod dst 0o640 else ();
remove_file dst
try if Unix.((lstat dst).st_kind <> S_REG) then
remove_file dst
with Unix.Unix_error(ENOENT, _, _) -> ()
in
let oc =
open_out_gen
[ Open_wronly; Open_creat; Open_trunc; Open_binary ]
perm dst
let fd =
let flags = Unix.[ O_WRONLY; O_CREAT; O_TRUNC ] in
try Unix.openfile dst flags perm
with Unix.Unix_error(EACCES, _, _) when Sys.win32 ->
(* Attempt to remove the read-only bit on Windows *)
begin
try Unix.chmod dst 0o666
with Unix.Unix_error(_, _, _) -> ()
end;
Unix.openfile dst flags perm
in
let fd = Unix.descr_of_out_channel oc in
try
if Unix.((fstat fd).st_perm) <> perm then
Unix.fchmod fd perm;
(ic, oc)
(ic, Unix.out_channel_of_descr fd)
with exn ->
OpamStd.Exn.finalise exn (fun () -> close_out oc)
OpamStd.Exn.finalise exn (fun () -> Unix.close fd)
with exn ->
OpamStd.Exn.finalise exn (fun () -> close_in ic)
Expand Down

0 comments on commit 32226ed

Please sign in to comment.