Skip to content

Commit

Permalink
Enable dune cache by default (#10710)
Browse files Browse the repository at this point in the history
* Added feature flag to enable dune cache by default
  • Loading branch information
ElectreAAS authored Aug 26, 2024
1 parent 5d05171 commit 5607dd9
Show file tree
Hide file tree
Showing 27 changed files with 123 additions and 30 deletions.
36 changes: 35 additions & 1 deletion bin/common.ml
Original file line number Diff line number Diff line change
Expand Up @@ -583,6 +583,7 @@ module Builder = struct
; file_watcher : Dune_engine.Scheduler.Run.file_watcher
; workspace_config : Dune_rules.Workspace.Clflags.t
; cache_debug_flags : Dune_engine.Cache_debug_flags.t
; cache_rules_default : bool
; report_errors_config : Dune_engine.Report_errors_config.t
; separate_error_messages : bool
; stop_on_first_error : bool
Expand Down Expand Up @@ -932,6 +933,20 @@ module Builder = struct
useful for Dune developers to make Dune tests of the digest cache more \
reproducible.")
and+ cache_debug_flags = cache_debug_flags_term
and+ cache_rules_default =
let default =
Dune_lang.Toggle.of_bool !Dune_engine.Clflags.can_go_in_shared_cache_default
in
let doc =
Printf.sprintf
"Enable or disable caching rules (%s). Default is `%s'."
(Arg.doc_alts_enum Config.Toggle.all)
(Config.Toggle.to_string default)
in
Arg.(
value
& opt (enum Config.Toggle.all) default
& info [ "cache-rules" ] ~docs ~env:(Cmd.Env.info ~doc "DUNE_CACHE_RULES") ~doc)
and+ report_errors_config =
Arg.(
value
Expand Down Expand Up @@ -1008,6 +1023,7 @@ module Builder = struct
; config_from_config_file
}
; cache_debug_flags
; cache_rules_default = Dune_lang.Toggle.enabled cache_rules_default
; report_errors_config
; separate_error_messages
; stop_on_first_error
Expand Down Expand Up @@ -1163,6 +1179,23 @@ let build (builder : Builder.t) =
{ builder; root; rpc; stats }
;;

let maybe_init_cache (cache_config : Dune_cache.Config.t) =
match cache_config with
| Disabled -> cache_config
| Enabled _ ->
(match Dune_cache_storage.Layout.create_cache_directories () with
| Ok () -> cache_config
| Error (path, exn) ->
User_warning.emit
~hints:
[ Pp.textf "Make sure the directory %s can be created" (Path.to_string path) ]
[ Pp.textf
"Cache directories could not be created: %s; disabling cache"
(Unix.error_message exn)
];
Disabled)
;;

let init (builder : Builder.t) =
let c = build builder in
if c.root.dir <> Filename.current_dir_name then Sys.chdir c.root.dir;
Expand Down Expand Up @@ -1216,7 +1249,7 @@ let init (builder : Builder.t) =
Dune_rules.Main.init
~stats:c.stats
~sandboxing_preference:config.sandboxing_preference
~cache_config
~cache_config:(maybe_init_cache cache_config)
~cache_debug_flags:c.builder.cache_debug_flags
();
Only_packages.Clflags.set c.builder.only_packages;
Expand All @@ -1241,6 +1274,7 @@ let init (builder : Builder.t) =
Dune_rules.Clflags.ignore_lock_dir := c.builder.ignore_lock_dir;
Dune_rules.Clflags.on_missing_dune_project_file
:= if c.builder.require_dune_project_file then Error else Warn;
Dune_engine.Clflags.can_go_in_shared_cache_default := c.builder.cache_rules_default;
Log.info
[ Pp.textf
"Workspace root: %s"
Expand Down
8 changes: 5 additions & 3 deletions src/dune_cache_storage/layout.ml
Original file line number Diff line number Diff line change
Expand Up @@ -82,7 +82,9 @@ let value_storage_dir = Versioned.value_storage_dir Version.Value.current
let value_path = Versioned.value_path Version.Value.current

let create_cache_directories () =
List.iter
[ temp_dir; metadata_storage_dir; file_storage_dir; value_storage_dir ]
~f:(fun path -> ignore (Fpath.mkdir_p (Path.to_string path) : Fpath.mkdir_p_result))
[ temp_dir; metadata_storage_dir; file_storage_dir; value_storage_dir ]
|> Result.List.iter ~f:(fun path ->
match Fpath.mkdir_p (Path.to_string path) with
| Already_exists | Created -> Ok ()
| exception Unix.Unix_error (e, _, _) -> Error (path, e))
;;
7 changes: 5 additions & 2 deletions src/dune_cache_storage/layout.mli
Original file line number Diff line number Diff line change
Expand Up @@ -12,8 +12,11 @@ open Import
val root_dir : Path.t

(** Create a few subdirectories in [root_dir]. We expose this function because
we don't want to modify the file system when the cache is disabled. *)
val create_cache_directories : unit -> unit
we don't want to modify the file system when the cache is disabled.
Returns whether creation has succeeded or in the case of error which directory
could not be created. *)
val create_cache_directories : unit -> (unit, Path.t * Unix.error) result

(** This directory stores metadata files, one per each historically executed
build rule or output-producing action. (While this is a convenient mental
Expand Down
4 changes: 2 additions & 2 deletions src/dune_config_file/dune_config_file.ml
Original file line number Diff line number Diff line change
Expand Up @@ -289,9 +289,9 @@ module Dune_config = struct
; concurrency = (if Execution_env.inside_dune then Fixed 1 else Auto)
; terminal_persistence = Clear_on_rebuild
; sandboxing_preference = []
; cache_enabled = `Disabled
; cache_enabled = `Enabled
; cache_reproducibility_check = Skip
; cache_storage_mode = None
; cache_storage_mode = Some (Dune_cache_storage.Mode.default ())
; action_stdout_on_success = Print
; action_stderr_on_success = Print
; experimental = []
Expand Down
2 changes: 1 addition & 1 deletion src/dune_engine/action.ml
Original file line number Diff line number Diff line change
Expand Up @@ -336,7 +336,7 @@ module Full = struct
let make
?(env = Env.empty)
?(locks = [])
?(can_go_in_shared_cache = true)
?(can_go_in_shared_cache = !Clflags.can_go_in_shared_cache_default)
?(sandbox = Sandbox_config.default)
action
=
Expand Down
3 changes: 2 additions & 1 deletion src/dune_engine/action.mli
Original file line number Diff line number Diff line change
Expand Up @@ -152,7 +152,8 @@ module Full : sig
val make
: ?env:Env.t (** default [Env.empty] *)
-> ?locks:Path.t list (** default [[]] *)
-> ?can_go_in_shared_cache:bool (** default [true] *)
-> ?can_go_in_shared_cache:bool
(** default [!Clflags.can_fo_in_shared_cache_default] *)
-> ?sandbox:Sandbox_config.t (** default [Sandbox_config.default] *)
-> action
-> t
Expand Down
5 changes: 0 additions & 5 deletions src/dune_engine/build_config.ml
Original file line number Diff line number Diff line change
Expand Up @@ -106,11 +106,6 @@ let set
contexts
~f:(fun ((ctx : Build_context.t), ctx_type) -> ctx.name, (ctx, ctx_type)))
in
let () =
match (cache_config : Dune_cache.Config.t) with
| Disabled -> ()
| Enabled _ -> Dune_cache_storage.Layout.create_cache_directories ()
in
Fdecl.set
t
{ contexts
Expand Down
1 change: 1 addition & 0 deletions src/dune_engine/clflags.ml
Original file line number Diff line number Diff line change
Expand Up @@ -19,3 +19,4 @@ let promote = ref None
let force = ref false
let always_show_command_line = ref false
let display = ref Display.Quiet
let can_go_in_shared_cache_default = ref false
3 changes: 3 additions & 0 deletions src/dune_engine/clflags.mli
Original file line number Diff line number Diff line change
Expand Up @@ -34,3 +34,6 @@ val always_show_command_line : bool ref

(** The display mode *)
val display : Display.t ref

(** Whether actions are cacheable by default, default [false] *)
val can_go_in_shared_cache_default : bool ref
1 change: 1 addition & 0 deletions src/dune_rules/dune
Original file line number Diff line number Diff line change
Expand Up @@ -33,6 +33,7 @@
build_path_prefix_map
dune_engine
dune_vcs
dune_cache_storage
dune_config
dune_config_file
dune_findlib
Expand Down
2 changes: 1 addition & 1 deletion src/dune_rules/simple_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -63,7 +63,7 @@ let add_user_rule
sctx
~dir
~(rule : Rule_conf.t)
~(action : _ Action_builder.With_targets.t)
~(action : Action.Full.t Action_builder.With_targets.t)
~expander
=
let action =
Expand Down
35 changes: 35 additions & 0 deletions test/blackbox-tests/test-cases/default-cache.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,35 @@
The dune cache should be enabled by default

$ echo "(lang dune 3.17)" > dune-project

$ cat > dune << EOF
> (library
> (name foo))
> EOF

$ cat > foo.ml << EOF
> let f x y = x + y
> EOF

Set up cache directory

$ export DUNE_CACHE_ROOT=$(pwd)/dune_test_cache
$ mkdir $DUNE_CACHE_ROOT
$ DUNE_CACHE=disabled dune build
$ ls $DUNE_CACHE_ROOT

We have not written anything to the cache yet.

Change source files to force a recompilation

$ cat > foo.ml << EOF
> let f x y = x - y
> EOF
$ dune build
$ ls $DUNE_CACHE_ROOT | sort
files
meta
temp
values

Cache has been written to!
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@ This checks what happens when a file available in the cache is used in a directo

$ export DUNE_CACHE_ROOT=$PWD/.cache
$ export DUNE_CACHE=enabled
$ export DUNE_CACHE_RULES=enabled
$ . ./helpers.sh

$ cat > dune-project << EOF
Expand Down
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
We create 2 directory targets which share a whole subdirectory.

$ export DUNE_CACHE_ROOT=$PWD/.cache
$ export DUNE_CACHE_RULES=enabled
$ export DUNE_CACHE=enabled
$ . ./helpers.sh

Expand Down
1 change: 1 addition & 0 deletions test/blackbox-tests/test-cases/directory-targets/cache.t
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
We test that directory targets can go in the shared cache. See #8067.

$ export DUNE_CACHE_ROOT=$PWD/.cache
$ export DUNE_CACHE_RULES=enabled
$ export DUNE_CACHE=enabled

In project a, we create a rule with a directory target. The script that creates
Expand Down
1 change: 1 addition & 0 deletions test/blackbox-tests/test-cases/dune-cache/config.t
Original file line number Diff line number Diff line change
Expand Up @@ -26,6 +26,7 @@ Check that old cache configuration format works fine with an old language
Test that DUNE_CACHE_ROOT can be used to control the cache location

$ export DUNE_CACHE_ROOT=$PWD/.cache
$ export DUNE_CACHE_RULES=enabled

Build succeeds and the 'copy' mode is respected

Expand Down
1 change: 1 addition & 0 deletions test/blackbox-tests/test-cases/dune-cache/dedup.t
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@ Test deduplication of build artifacts when using Dune cache with hard links.

$ export DUNE_CACHE=enabled
$ export DUNE_CACHE_ROOT=$PWD/.cache
$ export DUNE_CACHE_RULES=enabled

$ cat > dune-project <<EOF
> (lang dune 2.1)
Expand Down
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
Check that Dune cache can cope with missing file/metadata entries.

$ export DUNE_CACHE_ROOT=$PWD/.cache
$ export DUNE_CACHE_RULES=enabled

$ cat > config <<EOF
> (lang dune 2.1)
Expand Down
1 change: 1 addition & 0 deletions test/blackbox-tests/test-cases/dune-cache/mode-copy.t
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@ variable, and via the [DUNE_CACHE_ROOT] variable. Here we test the former.

$ export XDG_RUNTIME_DIR=$PWD/.xdg-runtime
$ export XDG_CACHE_HOME=$PWD/.xdg-cache
$ export DUNE_CACHE_RULES=enabled

$ cat > config <<EOF
> (lang dune 3.0)
Expand Down
1 change: 1 addition & 0 deletions test/blackbox-tests/test-cases/dune-cache/mode-hardlink.t
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@ variable, and via the [DUNE_CACHE_ROOT] variable. Here we test the former.

$ export XDG_RUNTIME_DIR=$PWD/.xdg-runtime
$ export XDG_CACHE_HOME=$PWD/.xdg-cache
$ export DUNE_CACHE_RULES=enabled

$ cat > config <<EOF
> (lang dune 2.1)
Expand Down
22 changes: 15 additions & 7 deletions test/blackbox-tests/test-cases/dune-cache/readonly-fs.t
Original file line number Diff line number Diff line change
Expand Up @@ -17,16 +17,24 @@ where Dune is supposed to store the cache:
$ export DUNE_CACHE_ROOT=$(pwd)/readonly/cache-dir

$ dune build
Error:
mkdir($TESTCASE_ROOT/readonly/cache-dir): Permission denied
[1]
Warning: Cache directories could not be created: Permission denied; disabling
cache
Hint: Make sure the directory
$TESTCASE_ROOT/readonly/cache-dir/temp
can be created

Likewise, this should also happen if the location is set via XDG variables.

$ unset DUNE_CACHE_ROOT
$ export XDG_CACHE_HOME=$(pwd)/readonly/xdg-cache-dir
$ export DUNE_CONFIG__SKIP_LINE_BREAK=enabled

$ dune build
Error:
mkdir($TESTCASE_ROOT/readonly/xdg-cache-dir): Permission denied
[1]
$ dune build 2>&1 | sed 's/created: .*;/created: $REASON:/'
Warning: Cache directories could not be created: $REASON: disabling cache
Hint: Make sure the directory $TESTCASE_ROOT/readonly/xdg-cache-dir/dune/db/temp can be created

$ HOME=/homeless-shelter
$ unset XDG_CACHE_HOME
$ dune build 2>&1 | sed 's/created: .*;/created: $REASON:/'
Warning: Cache directories could not be created: $REASON: disabling cache
Hint: Make sure the directory /homeless-shelter/.cache/dune/db/temp can be created
1 change: 1 addition & 0 deletions test/blackbox-tests/test-cases/dune-cache/repro-check.t
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
Test reproducibility check

$ export DUNE_CACHE_ROOT=$PWD/.cache
$ export DUNE_CACHE_RULES=enabled
$ cat > config <<EOF
> (lang dune 3.0)
> (cache enabled)
Expand Down
1 change: 1 addition & 0 deletions test/blackbox-tests/test-cases/dune-cache/size.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@ the cache.

$ export DUNE_CACHE=enabled
$ export DUNE_CACHE_ROOT=$PWD/.cache
$ export DUNE_CACHE_RULES=enabled

$ cat > config << EOF
> (lang dune 3.7)
Expand Down
1 change: 1 addition & 0 deletions test/blackbox-tests/test-cases/dune-cache/symlink.t
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@ produced symbolic links work correctly and are appropriately cached.

$ export DUNE_CACHE=enabled
$ export DUNE_CACHE_ROOT=$PWD/.cache
$ export DUNE_CACHE_RULES=enabled

$ cat > dune-project <<EOF
> (lang dune 2.1)
Expand Down
1 change: 1 addition & 0 deletions test/blackbox-tests/test-cases/dune-cache/trim.t
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
$ export DUNE_CACHE=enabled
$ export DUNE_CACHE_RULES=enabled
$ export XDG_RUNTIME_DIR=$PWD/.xdg-runtime
$ export XDG_CACHE_HOME=$PWD/.xdg-cache

Expand Down
4 changes: 1 addition & 3 deletions test/blackbox-tests/test-cases/pkg/toolchain-installation.t
Original file line number Diff line number Diff line change
Expand Up @@ -85,9 +85,7 @@ but the fake compiler will end up installed as a toolchain package.
Unrecognized line: "Hello from fake ocamlc!"

Enumerate the contents of the fake toolchains directory:
$ find fake-cache | sort | remove_hash
fake-cache
fake-cache/dune
$ find fake-cache/dune/toolchains | sort | remove_hash
fake-cache/dune/toolchains
fake-cache/dune/toolchains/ocaml-base-compiler.1-HASH
fake-cache/dune/toolchains/ocaml-base-compiler.1-HASH/target
Expand Down
8 changes: 4 additions & 4 deletions test/expect-tests/dune_config_file/dune_config_test.ml
Original file line number Diff line number Diff line change
Expand Up @@ -22,9 +22,9 @@ let%expect_test "cache-check-probability 0.1" =
; concurrency = Fixed 1
; terminal_persistence = Clear_on_rebuild
; sandboxing_preference = []
; cache_enabled = Disabled
; cache_enabled = Enabled
; cache_reproducibility_check = Check_with_probability 0.1
; cache_storage_mode = None
; cache_storage_mode = Some Hardlink
; action_stdout_on_success = Print
; action_stderr_on_success = Print
; experimental = []
Expand All @@ -40,7 +40,7 @@ let%expect_test "cache-storage-mode copy" =
; concurrency = Fixed 1
; terminal_persistence = Clear_on_rebuild
; sandboxing_preference = []
; cache_enabled = Disabled
; cache_enabled = Enabled
; cache_reproducibility_check = Skip
; cache_storage_mode = Some Copy
; action_stdout_on_success = Print
Expand All @@ -58,7 +58,7 @@ let%expect_test "cache-storage-mode hardlink" =
; concurrency = Fixed 1
; terminal_persistence = Clear_on_rebuild
; sandboxing_preference = []
; cache_enabled = Disabled
; cache_enabled = Enabled
; cache_reproducibility_check = Skip
; cache_storage_mode = Some Hardlink
; action_stdout_on_success = Print
Expand Down

0 comments on commit 5607dd9

Please sign in to comment.