Skip to content

Commit

Permalink
Set the caching property on make
Browse files Browse the repository at this point in the history
Signed-off-by: Marek Kubica <marek@tarides.com>
  • Loading branch information
Leonidas-from-XIV committed Aug 28, 2024
1 parent dc495fa commit da2366e
Show file tree
Hide file tree
Showing 3 changed files with 5 additions and 11 deletions.
1 change: 0 additions & 1 deletion src/dune_engine/action.ml
Original file line number Diff line number Diff line change
Expand Up @@ -351,6 +351,5 @@ module Full = struct
{ t with can_go_in_shared_cache = t.can_go_in_shared_cache && b }
;;

let allowed_in_shared_cache t = { t with can_go_in_shared_cache = true }
let add_sandbox s t = { t with sandbox = Sandbox_config.inter t.sandbox s }
end
3 changes: 0 additions & 3 deletions src/dune_engine/action.mli
Original file line number Diff line number Diff line change
Expand Up @@ -172,8 +172,5 @@ module Full : sig
val add_sandbox : Sandbox_config.t -> t -> t
val add_can_go_in_shared_cache : bool -> t -> t

(** Marks action as safe to be cached *)
val allowed_in_shared_cache : t -> t

include Monoid with type t := t
end
12 changes: 5 additions & 7 deletions src/dune_rules/fetch_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -181,10 +181,10 @@ let find_checksum, find_url =
;;

let gen_rules_for_checksum_or_url (loc_url, (url : OpamUrl.t)) checksum =
let checksum_or_url, allowed_in_shared_cache =
let checksum_or_url, can_go_in_shared_cache =
match checksum with
| Some (_, checksum) -> `Checksum checksum, Action.Full.allowed_in_shared_cache
| None -> `Url url, Fun.id
| Some (_, checksum) -> `Checksum checksum, Some true
| None -> `Url url, None
in
let directory_targets =
let target_dir = make_target ~kind:`Directory checksum_or_url in
Expand All @@ -205,8 +205,7 @@ let gen_rules_for_checksum_or_url (loc_url, (url : OpamUrl.t)) checksum =
let make_target = make_target checksum_or_url in
let action ~target ~kind =
action ~url:(loc_url, url) ~checksum ~target ~kind
|> Action.Full.make
|> allowed_in_shared_cache
|> Action.Full.make ?can_go_in_shared_cache
|> Action_builder.return
|> Action_builder.with_no_targets
in
Expand Down Expand Up @@ -327,8 +326,7 @@ let fetch ~target kind (source : Source.t) =
.fetch context. This would just add pointless additional overhead. *)
action ~url:source.url ~checksum:source.checksum ~target ~kind
in
Action.Full.make action
|> Action.Full.allowed_in_shared_cache
Action.Full.make ~can_go_in_shared_cache:true action
|> Action_builder.With_targets.return
|> Action_builder.With_targets.add_directories ~directory_targets:[ target ]
;;

0 comments on commit da2366e

Please sign in to comment.