Skip to content

Commit

Permalink
Added env var CACHE_USER_RULES, trying to use it with default cache e…
Browse files Browse the repository at this point in the history
…nabled

Signed-off-by: Ambre Austen Suhamy <ambre@tarides.com>
  • Loading branch information
ElectreAAS committed Aug 2, 2024
1 parent 1f8bb8e commit 54718f8
Show file tree
Hide file tree
Showing 9 changed files with 48 additions and 28 deletions.
17 changes: 17 additions & 0 deletions bin/common.ml
Original file line number Diff line number Diff line change
Expand Up @@ -418,6 +418,21 @@ let shared_with_config_file =
value
& opt (some (enum Config.Toggle.all)) None
& info [ "cache" ] ~docs ~env:(Cmd.Env.info ~doc "DUNE_CACHE") ~doc)
and+ cache_user_rules =
let doc =
Printf.sprintf
"Enable or disable caching user-created rules (%s). Default is `%s'."
(Arg.doc_alts_enum Config.Toggle.all)
(Config.Toggle.to_string Dune_config.default.cache_user_rules)
in
Arg.(
value
& opt (some (enum Config.Toggle.all)) None
& info
[ "cache-user-rules" ]
~docs
~env:(Cmd.Env.info ~doc "DUNE_CACHE_USER_RULES")
~doc)
and+ cache_storage_mode =
let doc =
Printf.sprintf
Expand Down Expand Up @@ -480,6 +495,7 @@ let shared_with_config_file =
; sandboxing_preference = Option.map sandboxing_preference ~f:(fun x -> [ x ])
; terminal_persistence
; cache_enabled
; cache_user_rules
; cache_reproducibility_check =
Option.map
cache_check_probability
Expand Down Expand Up @@ -1217,6 +1233,7 @@ let init (builder : Builder.t) =
Enabled
{ storage_mode = Option.value config.cache_storage_mode ~default:Hardlink
; reproducibility_check = config.cache_reproducibility_check
; cache_user_rules = config.cache_user_rules = `Enabled
}
in
Log.info [ Pp.textf "Shared cache: %s" (Config.Toggle.to_string config.cache_enabled) ];
Expand Down
1 change: 1 addition & 0 deletions src/dune_cache/config.ml
Original file line number Diff line number Diff line change
Expand Up @@ -43,4 +43,5 @@ type t =
| Enabled of
{ storage_mode : Dune_cache_storage.Mode.t
; reproducibility_check : Reproducibility_check.t
; cache_user_rules : bool
}
1 change: 1 addition & 0 deletions src/dune_cache/config.mli
Original file line number Diff line number Diff line change
Expand Up @@ -47,4 +47,5 @@ type t =
| Enabled of
{ storage_mode : Dune_cache_storage.Mode.t
; reproducibility_check : Reproducibility_check.t
; cache_user_rules : bool
}
31 changes: 15 additions & 16 deletions src/dune_cache/shared.ml
Original file line number Diff line number Diff line change
Expand Up @@ -65,28 +65,27 @@ struct
| Error exn -> Miss (Error (Printexc.to_string exn))
;;

let lookup_impl ~rule_digest ~targets =
let lookup_impl ~can_go_in_shared_cache ~rule_digest ~targets =
match config with
| Disabled -> Fiber.return (Hit_or_miss.Miss Miss_reason.Cache_disabled)
| Enabled { storage_mode = mode; reproducibility_check } ->
(match Config.Reproducibility_check.sample reproducibility_check with
| true ->
(* CR-someday amokhov: Here we re-execute the rule, as in Jenga. To make
[check_probability] more meaningful, we could first make sure that
the shared cache actually does contain an entry for [rule_digest]. *)
Fiber.return (Hit_or_miss.Miss Miss_reason.Rerunning_for_reproducibility_check)
| false -> try_to_restore_from_shared_cache ~mode ~rule_digest ~targets)
| Enabled { storage_mode = mode; reproducibility_check; cache_user_rules } ->
if can_go_in_shared_cache || cache_user_rules
then (
match Config.Reproducibility_check.sample reproducibility_check with
| true ->
(* CR-someday amokhov: Here we re-execute the rule, as in Jenga. To make
[check_probability] more meaningful, we could first make sure that
the shared cache actually does contain an entry for [rule_digest]. *)
Fiber.return (Hit_or_miss.Miss Miss_reason.Rerunning_for_reproducibility_check)
| false -> try_to_restore_from_shared_cache ~mode ~rule_digest ~targets)
else Fiber.return (Hit_or_miss.Miss Miss_reason.Cannot_go_in_shared_cache)
;;

let lookup ~can_go_in_shared_cache ~rule_digest ~targets
: Digest.t Targets.Produced.t option Fiber.t
=
let open Fiber.O in
let+ result =
match can_go_in_shared_cache with
| false -> Fiber.return (Hit_or_miss.Miss Miss_reason.Cannot_go_in_shared_cache)
| true -> lookup_impl ~rule_digest ~targets
in
let+ result = lookup_impl ~can_go_in_shared_cache ~rule_digest ~targets in
match result with
| Hit result -> Some result
| Miss reason ->
Expand Down Expand Up @@ -277,8 +276,8 @@ struct
: Digest.t Targets.Produced.t Fiber.t
=
match config with
| Enabled { storage_mode = mode; reproducibility_check = _ }
when can_go_in_shared_cache ->
| Enabled { storage_mode = mode; reproducibility_check = _; cache_user_rules }
when can_go_in_shared_cache || cache_user_rules ->
let open Fiber.O in
let+ produced_targets_with_digests =
try_to_store_to_shared_cache ~mode ~rule_digest ~produced_targets ~action
Expand Down
20 changes: 11 additions & 9 deletions src/dune_config_file/dune_config_file.ml
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,6 @@ module Dune_config = struct
module Log = Dune_util.Log
module Config = Dune_config.Config
module Execution_env = Dune_util.Execution_env
module Feature_flags = Feature_flags

(* the configuration file use the same version numbers as dune-project files for
simplicity *)
Expand Down Expand Up @@ -123,6 +122,7 @@ module Dune_config = struct
; terminal_persistence : Terminal_persistence.t field
; sandboxing_preference : Sandboxing_preference.t field
; cache_enabled : Config.Toggle.t field
; cache_user_rules : Config.Toggle.t field
; cache_reproducibility_check : Dune_cache.Config.Reproducibility_check.t field
; cache_storage_mode : Cache.Storage_mode.t field
; action_stdout_on_success : Action_output_on_success.t field
Expand All @@ -147,6 +147,7 @@ module Dune_config = struct
; terminal_persistence = field a.terminal_persistence b.terminal_persistence
; sandboxing_preference = field a.sandboxing_preference b.sandboxing_preference
; cache_enabled = field a.cache_enabled b.cache_enabled
; cache_user_rules = field a.cache_user_rules b.cache_user_rules
; cache_reproducibility_check =
field a.cache_reproducibility_check b.cache_reproducibility_check
; cache_storage_mode = field a.cache_storage_mode b.cache_storage_mode
Expand All @@ -173,6 +174,7 @@ module Dune_config = struct
; terminal_persistence
; sandboxing_preference
; cache_enabled
; cache_user_rules
; cache_reproducibility_check
; cache_storage_mode
; action_stdout_on_success
Expand All @@ -187,6 +189,7 @@ module Dune_config = struct
; ( "sandboxing_preference"
, field (Dyn.list Sandbox_mode.to_dyn) sandboxing_preference )
; "cache_enabled", field Config.Toggle.to_dyn cache_enabled
; "cache_user_rules", field Config.Toggle.to_dyn cache_user_rules
; ( "cache_reproducibility_check"
, field
Dune_cache.Config.Reproducibility_check.to_dyn
Expand Down Expand Up @@ -215,6 +218,7 @@ module Dune_config = struct
; terminal_persistence = None
; sandboxing_preference = None
; cache_enabled = None
; cache_user_rules = None
; cache_reproducibility_check = None
; cache_storage_mode = None
; action_stdout_on_success = None
Expand Down Expand Up @@ -280,14 +284,10 @@ module Dune_config = struct
; concurrency = (if Execution_env.inside_dune then Fixed 1 else Auto)
; terminal_persistence = Clear_on_rebuild
; sandboxing_preference = []
; cache_enabled =
(if Feature_flags.cache_enabled_by_default then `Enabled else `Disabled)
; cache_reproducibility_check =
(if Feature_flags.cache_enabled_by_default then Check else Skip)
; cache_storage_mode =
(if Feature_flags.cache_enabled_by_default
then Some (Dune_cache_storage.Mode.default ())
else None)
; cache_enabled = `Enabled
; cache_user_rules = `Disabled
; cache_reproducibility_check = Check
; cache_storage_mode = Some (Dune_cache_storage.Mode.default ())
; action_stdout_on_success = Print
; action_stderr_on_success = Print
; experimental = []
Expand All @@ -307,6 +307,7 @@ module Dune_config = struct
and+ sandboxing_preference =
field_o "sandboxing_preference" (1, 0) Sandboxing_preference.decode
and+ cache_enabled = field_o "cache" (2, 0) (enum Config.Toggle.all)
and+ cache_user_rules = field_o "cache-user-rules" (2, 0) (enum Config.Toggle.all)
and+ _cache_transport_unused_since_3_0 =
field_o
"cache-transport"
Expand Down Expand Up @@ -369,6 +370,7 @@ module Dune_config = struct
; terminal_persistence
; sandboxing_preference
; cache_enabled
; cache_user_rules
; cache_reproducibility_check
; cache_storage_mode
; action_stdout_on_success
Expand Down
1 change: 1 addition & 0 deletions src/dune_config_file/dune_config_file.mli
Original file line number Diff line number Diff line change
Expand Up @@ -52,6 +52,7 @@ module Dune_config : sig
; terminal_persistence : Terminal_persistence.t field
; sandboxing_preference : Sandboxing_preference.t field
; cache_enabled : Config.Toggle.t field
; cache_user_rules : Config.Toggle.t field
; cache_reproducibility_check : Dune_cache.Config.Reproducibility_check.t field
; cache_storage_mode : Cache.Storage_mode.t field
; action_stdout_on_success : Action_output_on_success.t field
Expand Down
1 change: 0 additions & 1 deletion src/dune_config_file/feature_flags.ml

This file was deleted.

2 changes: 1 addition & 1 deletion src/dune_engine/action.ml
Original file line number Diff line number Diff line change
Expand Up @@ -357,7 +357,7 @@ module Full = struct
let make
?(env = Env.empty)
?(locks = [])
?(can_go_in_shared_cache = true)
?(can_go_in_shared_cache = false)
?(sandbox = Sandbox_config.default)
action
=
Expand Down
2 changes: 1 addition & 1 deletion src/dune_engine/action.mli
Original file line number Diff line number Diff line change
Expand Up @@ -151,7 +151,7 @@ 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 [false] *)
-> ?sandbox:Sandbox_config.t (** default [Sandbox_config.default] *)
-> action
-> t
Expand Down

0 comments on commit 54718f8

Please sign in to comment.