Skip to content

Commit

Permalink
Only clear known cache directories
Browse files Browse the repository at this point in the history
Signed-off-by: Nicolás Ojeda Bär <n.oje.bar@gmail.com>
  • Loading branch information
nojb committed Oct 24, 2023
1 parent 675c61c commit 8cfc7a4
Show file tree
Hide file tree
Showing 4 changed files with 22 additions and 3 deletions.
2 changes: 1 addition & 1 deletion bin/cache.ml
Original file line number Diff line number Diff line change
Expand Up @@ -93,7 +93,7 @@ let clear =
let man = [ `P "Remove any traces of the Dune cache." ] in
Cmd.info "clear" ~doc ~man
in
Cmd.v info @@ Term.(const Dune_cache.clear $ const ())
Cmd.v info @@ Term.(const Dune_cache_storage.clear $ const ())
;;

let command =
Expand Down
2 changes: 0 additions & 2 deletions src/dune_cache/dune_cache.ml
Original file line number Diff line number Diff line change
@@ -1,5 +1,3 @@
module Config = Config
module Local = Local
module Trimmer = Trimmer

let clear () = Stdune.Path.rm_rf ~allow_external:true Dune_cache_storage.Layout.root_dir
19 changes: 19 additions & 0 deletions src/dune_cache_storage/dune_cache_storage.ml
Original file line number Diff line number Diff line change
Expand Up @@ -338,3 +338,22 @@ let with_temp_file ?(prefix = "dune") ~suffix f =
let with_temp_dir ?(prefix = "dune") ~suffix f =
Fiber_util.Temp.with_temp_dir ~parent_dir:Layout.temp_dir ~prefix ~suffix ~f
;;

let clear () =
let rm_rf path = Path.rm_rf ~allow_external:true path in
let rmdir path =
try Path.rmdir path with
| Unix.Unix_error ((ENOENT | ENOTEMPTY), _, _) -> ()
in
let rm_rf_all versions dir =
List.iter versions ~f:(fun version ->
let dir = dir version in
rm_rf dir;
Option.iter ~f:rmdir (Path.parent dir))
in
rm_rf_all Version.Metadata.all Layout.Versioned.metadata_storage_dir;
rm_rf_all Version.File.all Layout.Versioned.file_storage_dir;
rm_rf_all Version.Value.all Layout.Versioned.value_storage_dir;
rm_rf Layout.temp_dir;
Path.rmdir Layout.root_dir
;;
2 changes: 2 additions & 0 deletions src/dune_cache_storage/dune_cache_storage.mli
Original file line number Diff line number Diff line change
Expand Up @@ -138,3 +138,5 @@ module Raw_value : sig
-> content_digest:Digest.t
-> Util.Write_result.t
end

val clear : unit -> unit

0 comments on commit 8cfc7a4

Please sign in to comment.