Skip to content

Commit 144fd3f

Browse files
authored
Add a new implementation of the shared cache and start using it (#4443)
This PR switches Dune to use well-tested and optimised Jenga's implementation of the shared cache. Apart from using the new logic with fewer races (which now matches the documentation in [doc/dev/cache.md]), there are a few other changes: * We no longer plumb store/restore requests through the daemon, i.e. we switch to using the direct mode exclusively. This simplifies Dune quite a bit. The only cost is that in the copying mode, we currently need to wait until the artifacts are copied to the cache before proceeding with the build. * The cache metadata format has been simplified: we no longer store full paths to build artifacts, it is sufficient to store the names of files. Hence the bump of the version to [meta/v5]. Some changes are left for follow-up PRs to keep this one as small as possible: * Remove the cache daemon. * Refactor the cache trimmer to use the new cache storage libraries. * Change the cache configuration format. * Reuse Jenga's shared cache test suite. * Implement the cloud cache functionality. * Update developer and user docs. Signed-off-by: Andrey Mokhov <[email protected]>
1 parent 6993df6 commit 144fd3f

File tree

40 files changed

+1377
-406
lines changed

40 files changed

+1377
-406
lines changed

bin/build_cmd.ml

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -45,8 +45,7 @@ let run_build_command ~(common : Common.t) ~config ~targets =
4545
run_build_command_poll
4646
else
4747
run_build_command_once)
48-
~setup ~common ~config ~targets;
49-
Build_system.cache_teardown ()
48+
~setup ~common ~config ~targets
5049

5150
let runtest =
5251
let doc = "Run tests." in

bin/caching.ml

Lines changed: 13 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -60,8 +60,8 @@ let trim ~trimmed_size ~size =
6060
let open Result.O in
6161
match
6262
let* cache =
63-
(* CR-someday amokhov: The [Hadrlink] duplication mode is chosen
64-
artitrarily here, instead of respecting the corresponding configuration
63+
(* CR-someday amokhov: The [Hardlink] duplication mode is chosen
64+
arbitrarily here, instead of respecting the corresponding configuration
6565
setting, because the mode doesn't matter for the trimmer. It would be
6666
better to refactor the code to avoid such arbitrary choices. *)
6767
Cache.Local.make ~duplication_mode:Cache.Duplication_mode.Hardlink
@@ -123,7 +123,7 @@ let term =
123123
and+ root =
124124
Arg.(
125125
value
126-
& opt path_conv (Cache.Local.default_root ())
126+
& opt path_conv (Dune_cache_storage.Layout.default_root_path ())
127127
& info ~docv:"PATH" [ "root" ] ~doc:"Root of the dune cache")
128128
and+ trimmed_size =
129129
Arg.(
@@ -140,9 +140,18 @@ let term =
140140
let config = Dune_config.(superpose default) config in
141141
match mode with
142142
| Some Start ->
143+
(* CR-soon amokhov: Right now, types [Dune_config.Caching.Duplication.t]
144+
and [Dune_cache_storage.Mode.t] are the same. They will be unified
145+
after removing the cache daemon and adapting the configuration format. *)
143146
let config =
144147
{ Cache_daemon.exit_no_client
145-
; duplication_mode = config.cache_duplication
148+
; duplication_mode =
149+
(match
150+
(config.cache_duplication : Dune_cache_storage.Mode.t option)
151+
with
152+
| None -> None
153+
| Some Hardlink -> Some Hardlink
154+
| Some Copy -> Some Copy)
146155
}
147156
in
148157
`Ok (start ~config ~foreground ~port_path ~root ~display)

bin/dune

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,8 @@
88
unix
99
cache_daemon
1010
cache
11+
dune_cache
12+
dune_cache_storage
1113
dune_rules
1214
dune_engine
1315
dune_util

bin/import.ml

Lines changed: 20 additions & 48 deletions
Original file line numberDiff line numberDiff line change
@@ -32,57 +32,12 @@ include Common.Let_syntax
3232

3333
let in_group (t, info) = (Term.Group.Term t, info)
3434

35-
let make_cache (config : Dune_config.t) =
36-
let make_cache () =
37-
let command_handler (Cache.Dedup file) =
38-
match Build_system.get_cache () with
39-
| None -> Code_error.raise "deduplication message and no caching" []
40-
| Some caching ->
41-
Scheduler.send_sync_task (fun () ->
42-
let (module Caching : Cache.Caching) = caching.cache in
43-
match Cached_digest.peek_file (Path.build file.path) with
44-
| None -> ()
45-
| Some d when not (Digest.equal d file.digest) -> ()
46-
| _ -> Caching.Cache.deduplicate Caching.cache file)
47-
in
48-
match config.cache_transport with
49-
| Dune_config.Caching.Transport.Direct ->
50-
Log.info [ Pp.text "enable binary cache in direct access mode" ];
51-
let cache =
52-
Result.ok_exn
53-
(Result.map_error
54-
~f:(fun s -> User_error.E (User_error.make [ Pp.text s ]))
55-
(Cache.Local.make ?duplication_mode:config.cache_duplication
56-
~command_handler ()))
57-
in
58-
Cache.make_caching (module Cache.Local) cache
59-
| Daemon ->
60-
Log.info [ Pp.text "enable binary cache in daemon mode" ];
61-
let cache =
62-
Result.ok_exn
63-
(Cache.Client.make ?duplication_mode:config.cache_duplication
64-
~command_handler ())
65-
in
66-
Cache.make_caching (module Cache.Client) cache
67-
in
68-
Fiber.return
69-
(match config.cache_mode with
70-
| Dune_config.Caching.Mode.Enabled ->
71-
Some
72-
{ Build_system.cache = make_cache ()
73-
; check_probability = config.cache_check_probability
74-
}
75-
| Dune_config.Caching.Mode.Disabled ->
76-
Log.info [ Pp.text "disable binary cache" ];
77-
None)
78-
7935
module Main = struct
8036
include Dune_rules.Main
8137

82-
let setup common config =
38+
let setup common (config : Dune_config.t) =
8339
let open Fiber.O in
84-
let* caching = make_cache config
85-
and* conf = Memo.Build.run (Dune_rules.Dune_load.load ())
40+
let* conf = Memo.Build.run (Dune_rules.Dune_load.load ())
8641
and* contexts = Memo.Build.run (Context.DB.all ()) in
8742
let stats = Common.stats common in
8843
List.iter contexts ~f:(fun (ctx : Context.t) ->
@@ -91,8 +46,25 @@ module Main = struct
9146
[ Pp.box ~indent:1
9247
(Pp.text "Dune context:" ++ Pp.cut ++ Dyn.pp (Context.to_dyn ctx))
9348
]);
49+
(* CR-soon amokhov: Right now, types [Dune_config.Caching.Duplication.t] and
50+
[Dune_cache_storage.Mode.t] are the same. They will be unified after
51+
removing the cache daemon and adapting the configuration format. *)
52+
let cache_config =
53+
match config.cache_mode with
54+
| Disabled -> Dune_cache.Config.Disabled
55+
| Enabled ->
56+
Enabled
57+
{ storage_mode =
58+
(match config.cache_duplication with
59+
| None
60+
| Some Hardlink ->
61+
Dune_cache_storage.Mode.Hardlink
62+
| Some Copy -> Copy)
63+
; check_probability = config.cache_check_probability
64+
}
65+
in
9466
init_build_system ~stats ~sandboxing_preference:config.sandboxing_preference
95-
~caching ~conf ~contexts
67+
~cache_config ~conf ~contexts
9668
end
9769

9870
module Scheduler = struct

boot/libs.ml

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -15,6 +15,8 @@ let local_libraries =
1515
; ("src/memo", Some "Memo", false, None)
1616
; ("src/dune_util", Some "Dune_util", false, None)
1717
; ("src/xdg", Some "Xdg", false, None)
18+
; ("src/dune_cache_storage", Some "Dune_cache_storage", false, None)
19+
; ("src/dune_cache", Some "Dune_cache", false, None)
1820
; ("src/cache", Some "Cache", false, None)
1921
; ("src/cache_daemon", Some "Cache_daemon", false, None)
2022
; ("vendor/re/src", Some "Dune_re", false, None)

otherlibs/stdune-unstable/digest.ml

Lines changed: 16 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -35,21 +35,24 @@ let to_string_raw s = s
3535
or to different memory locations. *)
3636
let generic a = string (Marshal.to_string a [ No_sharing ])
3737

38-
let file_with_stats p (stats : Unix.stats) =
38+
let file_with_executable_bit ~executable path =
39+
(* We follow the digest scheme used by Jenga. *)
40+
let string_and_bool ~digest_hex ~bool =
41+
D.string
42+
(digest_hex
43+
^
44+
if bool then
45+
"\001"
46+
else
47+
"\000")
48+
in
49+
let content_digest = file path in
50+
string_and_bool ~digest_hex:content_digest ~bool:executable
51+
52+
let file_with_stats path (stats : Unix.stats) =
3953
match stats.st_kind with
4054
| S_DIR ->
4155
generic (stats.st_size, stats.st_perm, stats.st_mtime, stats.st_ctime)
4256
| _ ->
43-
(* We follow the digest scheme used by Jenga. *)
44-
let string_and_bool ~digest_hex ~bool =
45-
D.string
46-
(digest_hex
47-
^
48-
if bool then
49-
"\001"
50-
else
51-
"\000")
52-
in
53-
let content_digest = file p in
5457
let executable = stats.st_perm land 0o100 <> 0 in
55-
string_and_bool ~digest_hex:content_digest ~bool:executable
58+
file_with_executable_bit ~executable path

otherlibs/stdune-unstable/digest.mli

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -26,5 +26,9 @@ val to_string_raw : t -> string
2626

2727
val generic : 'a -> t
2828

29-
(** Digest a file and its stats. Does something sensible for directories *)
29+
(** Digest a file and its stats. Does something sensible for directories. *)
3030
val file_with_stats : Path.t -> Unix.stats -> t
31+
32+
(** Digest a file taking its executable bit into account. Should not be called
33+
on a directory. *)
34+
val file_with_executable_bit : executable:bool -> Path.t -> t

otherlibs/stdune-unstable/path.ml

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -715,6 +715,10 @@ module Build = struct
715715

716716
let chmod t ~mode = Unix.chmod (to_string t) mode
717717

718+
let lstat t = Unix.lstat (to_string t)
719+
720+
let unlink_no_err t = Fpath.unlink_no_err (to_string t)
721+
718722
module Kind = Kind
719723
end
720724

otherlibs/stdune-unstable/path.mli

Lines changed: 7 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -186,6 +186,10 @@ module Build : sig
186186
(** Set permissions for a given path. You can use the [Permissions] module if
187187
you need to modify existing permissions in a non-trivial way. *)
188188
val chmod : t -> mode:int -> unit
189+
190+
val lstat : t -> Unix.stats
191+
192+
val unlink_no_err : t -> unit
189193
end
190194

191195
type t = private
@@ -379,10 +383,9 @@ val set_of_build_paths_list : Build.t list -> Set.t
379383

380384
val string_of_file_kind : Unix.file_kind -> string
381385

382-
(** Rename a file. rename oldpath newpath renames the file called oldpath,
383-
giving it newpath as its new name, moving it between directories if needed.
384-
If newpath already exists, its contents will be replaced with those of
385-
oldpath. *)
386+
(** Rename a file. [rename oldpath newpath] renames the file called [oldpath] to
387+
[newpath], moving it between directories if needed. If [newpath] already
388+
exists, its contents will be replaced with those of [oldpath]. *)
386389
val rename : t -> t -> unit
387390

388391
(** Set permissions for a given path. You can use the [Permissions] module if

otherlibs/stdune-unstable/temp.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,7 @@ val destroy : what -> Path.t -> unit
2020
itself. *)
2121
val clear_dir : Path.t -> unit
2222

23-
(** [temp_path ~dir ~prefix ~suffix] generate a temporary path in [dir]. The
23+
(** [temp_path ~dir ~prefix ~suffix] generates a temporary path in [dir]. The
2424
base name of the temporary file is formed by concatenating [prefix], then a
2525
suitably chosen integer number, then [suffix]. *)
2626
val temp_path : dir:Path.t -> prefix:string -> suffix:string -> Path.t

0 commit comments

Comments
 (0)