Skip to content

Commit

Permalink
Move Path.rm_rf to Fpath
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg committed Apr 22, 2021
1 parent 261790f commit 0f31294
Show file tree
Hide file tree
Showing 3 changed files with 32 additions and 24 deletions.
26 changes: 26 additions & 0 deletions otherlibs/stdune-unstable/fpath.ml
Original file line number Diff line number Diff line change
Expand Up @@ -90,3 +90,29 @@ let unlink =
let unlink_no_err t =
try unlink t with
| _ -> ()

let rec clear_dir dir =
match Dune_filesystem_stubs.read_directory_with_kinds dir with
| Error ENOENT -> ()
| Error error ->
raise
(Unix.Unix_error
(error, dir, "Stdune.Path.rm_rf: read_directory_with_kinds"))
| Ok listing ->
List.iter listing ~f:(fun (fn, kind) ->
let fn = Filename.concat dir fn in
match kind with
| Unix.S_DIR -> rm_rf_dir fn
| _ -> unlink fn)

and rm_rf_dir path =
clear_dir path;
Unix.rmdir path

let rm_rf ?(allow_external = false) fn =
if (not allow_external) && not (Filename.is_relative fn) then
Code_error.raise "Path.rm_rf called on external dir" [ ("fn", String fn) ];
match Unix.lstat fn with
| exception Unix.Unix_error (ENOENT, _, _) -> ()
| { Unix.st_kind = S_DIR; _ } -> rm_rf_dir fn
| _ -> unlink fn
4 changes: 4 additions & 0 deletions otherlibs/stdune-unstable/fpath.mli
Original file line number Diff line number Diff line change
Expand Up @@ -26,3 +26,7 @@ val unlink : string -> unit
val unlink_no_err : string -> unit

val initial_cwd : string

val clear_dir : string -> unit

val rm_rf : ?allow_external:bool -> string -> unit
26 changes: 2 additions & 24 deletions otherlibs/stdune-unstable/path.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1142,34 +1142,12 @@ let insert_after_build_dir_exn =
| External _ ->
error a b

let rec clear_dir dir =
match Dune_filesystem_stubs.read_directory_with_kinds dir with
| Error ENOENT -> ()
| Error error ->
raise
(Unix.Unix_error
(error, dir, "Stdune.Path.rm_rf: read_directory_with_kinds"))
| Ok listing ->
List.iter listing ~f:(fun (fn, kind) ->
let fn = Filename.concat dir fn in
match kind with
| Unix.S_DIR -> rm_rf_dir fn
| _ -> Fpath.unlink fn)

and rm_rf_dir path =
clear_dir path;
Unix.rmdir path
let clear_dir dir = Fpath.clear_dir (to_string dir)

let rm_rf ?(allow_external = false) t =
if (not allow_external) && not (is_managed t) then
Code_error.raise "Path.rm_rf called on external dir" [ ("t", to_dyn t) ];
let fn = to_string t in
match Unix.lstat fn with
| exception Unix.Unix_error (ENOENT, _, _) -> ()
| { Unix.st_kind = S_DIR; _ } -> rm_rf_dir fn
| _ -> Fpath.unlink fn

let clear_dir dir = clear_dir (to_string dir)
Fpath.rm_rf ~allow_external (to_string t)

let mkdir_p ?perms = function
| External s -> External.mkdir_p s ?perms
Expand Down

0 comments on commit 0f31294

Please sign in to comment.