Skip to content

Commit 689ce38

Browse files
committed
Reuse dependencies between project and tools
This allows the dependencies of the project to be shared with dev tools, preventing unnecessarily rebuilding dependencies while building a tool if an identical version of the package has already been built or vice versa. This requires storing build artifacts of dependencies of dev tools and the project (when built in the "default" context) in a single directory, since their relative path within the _build directory is part of the key used to cache build artifacts. Previously the build artifacts of a package were placed in a directory named after that package, however since dev tools and the project may depend on different versions of the same package, directories needed to be renamed to avoid collisions. Even if the project and dev tools rely on the same version of some package, it may still need to be rebuilt on occasion due to the presence/absence of depopts, or due to manual modification to lockfiles. For this reason, the directories containing package build artifacts contain in their name, a hash of the contents of the lockfile of the metadata in the package's transitive dependency closure. This change introduces the concept of a "package digest" which is a unique directory name for a package comprising its name, version, and dependency closure hash. The DB type used to store metadata while building packages has been updated to be keyed based on package digests, and to store package metadata for dev tools and the project's default build context in the same table to allow dependencies to be shared. Signed-off-by: Stephen Sherratt <[email protected]>
1 parent 3802d47 commit 689ce38

33 files changed

+597
-223
lines changed

bin/pkg/group.ml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,7 @@ let subcommands =
1313
; Outdated.command
1414
; Validate_lock_dir.command
1515
; Pkg_enabled.command
16+
; Print_digest.command
1617
]
1718
;;
1819

bin/pkg/print_digest.ml

Lines changed: 36 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,36 @@
1+
open Import
2+
3+
let term =
4+
let+ builder = Common.Builder.term
5+
and+ package_name =
6+
Arg.(
7+
required
8+
& pos 0 (some string) None
9+
& info [] ~doc:"The name of the package" ~docv:"PACKAGE")
10+
and+ context_name = Common.context_arg ~doc:"Context used to determine lockdir" in
11+
let builder = Common.Builder.forbid_builds builder in
12+
let common, config = Common.init builder in
13+
let package_name = Package_name.of_string package_name in
14+
Scheduler.go_with_rpc_server ~common ~config (fun () ->
15+
let open Fiber.O in
16+
let+ pkg_digest_opt =
17+
build_exn (fun () ->
18+
Dune_rules.Pkg_rules.pkg_digest_of_project_dependency context_name package_name)
19+
in
20+
match pkg_digest_opt with
21+
| Some pkg_digest ->
22+
print_endline (Dune_rules.Pkg_rules.Pkg_digest.to_string pkg_digest)
23+
| None ->
24+
User_error.raise
25+
[ Pp.textf
26+
"The project does not depend on the package %S."
27+
(Package_name.to_string package_name)
28+
])
29+
;;
30+
31+
let info =
32+
let doc = "Print the digest of a package in the project's lockdir." in
33+
Cmd.info "print-digest" ~doc
34+
;;
35+
36+
let command = Cmd.v info term

bin/pkg/print_digest.mli

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,4 @@
1+
open Import
2+
3+
(** Command to print the slug of a given package within the current project. *)
4+
val command : unit Cmd.t

src/dune_digest/digest.ml

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -91,14 +91,15 @@ module Feed = struct
9191
feed_c hasher c
9292
;;
9393

94-
let digest t x = Hasher.with_singleton (fun hasher -> t hasher x)
94+
let digest hasher digest = contramap string ~f:to_string hasher digest
95+
let compute_digest t x = Hasher.with_singleton (fun hasher -> t hasher x)
9596
end
9697

97-
let string s = Feed.digest Feed.string s
98+
let string s = Feed.compute_digest Feed.string s
9899
let to_string_raw s = Blake3_mini.Digest.to_binary s
99100

100101
let generic a =
101-
Metrics.Timer.record "generic_digest" ~f:(fun () -> Feed.digest Feed.generic a)
102+
Metrics.Timer.record "generic_digest" ~f:(fun () -> Feed.compute_digest Feed.generic a)
102103
;;
103104

104105
let path_with_executable_bit =

src/dune_digest/digest.mli

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -27,8 +27,11 @@ module Feed : sig
2727
val tuple2 : 'a t -> 'b t -> ('a * 'b) t
2828
val tuple3 : 'a t -> 'b t -> 'c t -> ('a * 'b * 'c) t
2929

30+
(** Feed a digest into a hasher. *)
31+
val digest : digest t
32+
3033
(** Compute the digest of a value given a feed for the type of that value. *)
31-
val digest : 'a t -> 'a -> digest
34+
val compute_digest : 'a t -> 'a -> digest
3235
end
3336

3437
include Comparable_intf.S with type key := t

src/dune_lang/package_name.mli

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -31,3 +31,5 @@ val file : t -> dir:Path.Source.t -> Path.Source.t
3131
val decode_opam_compatible : t Decoder.t
3232
val opam_fn : t -> Filename.t
3333
val of_opam_file_basename : Filename.t -> t option
34+
35+
module Table : Hashtbl.S with type key = t

src/dune_lang/package_version.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@ val of_string_opt : string -> t option
77
val of_string_user_error : Loc.t * string -> (t, User_message.t) result
88
val to_string : t -> string
99
val equal : t -> t -> bool
10+
val compare : t -> t -> ordering
1011
val hash : t -> int
1112
val digest_feed : t Dune_digest.Feed.t
1213
val to_dyn : t -> Dyn.t

src/dune_pkg/dune_pkg.ml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -26,3 +26,4 @@ module Package_name = Package_name
2626
module Ocamlformat = Ocamlformat
2727
module Dev_tool = Dev_tool
2828
module Outdated = Outdated
29+
module Dune_dep = Dune_dep

src/dune_pkg/package_name.mli

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -6,3 +6,5 @@ include module type of Dune_lang.Package_name with type t := t
66

77
val of_opam_package_name : OpamTypes.name -> t
88
val to_opam_package_name : t -> OpamTypes.name
9+
10+
module Table : Hashtbl.S with type key = t

src/dune_pkg/package_version.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,7 @@ val of_string : string -> t
66
val of_string_user_error : Loc.t * string -> (t, User_message.t) result
77
val to_string : t -> string
88
val equal : t -> t -> bool
9+
val compare : t -> t -> ordering
910
val hash : t -> int
1011
val digest_feed : t Dune_digest.Feed.t
1112
val to_dyn : t -> Dyn.t

0 commit comments

Comments
 (0)