Skip to content

Commit

Permalink
pkg: don't expand deps of restricting deps
Browse files Browse the repository at this point in the history
Previously dune would expand dependencies of packages that are only
ever marked as conflicting with packages in the solution. This led to
the expansion of far more packages that necessary. Expanding a package
requires reading an opam file and so is a relatively expensive
operation.

For packages that only depend on the compiler (ocaml-base-compiler),
this reduces the number of expanded packages from 8376 to 1841 at the
time of writing.

Signed-off-by: Stephen Sherratt <[email protected]>
  • Loading branch information
gridbugs committed Jan 2, 2025
1 parent 8a30fb1 commit 1a64582
Showing 1 changed file with 25 additions and 3 deletions.
28 changes: 25 additions & 3 deletions src/0install-solver/solver_core.ml
Original file line number Diff line number Diff line change
Expand Up @@ -197,21 +197,43 @@ module Make (Model : S.SOLVER_INPUT) = struct
(* For each (iface, source) we have a list of implementations. *)
let impl_cache = ImplCache.create () in
let conflict_classes = Conflict_classes.create sat in
let deferred = ref [] in
let expand_deps = ref true in
let rec add_impls_to_cache role =
let+ clause, impls = make_impl_clause sat ~dummy_impl role in
( clause
, fun () ->
Fiber.sequential_iter impls ~f:(fun (impl_var, impl) ->
Conflict_classes.process conflict_classes impl_var impl;
Model.requires role impl
|> Fiber.sequential_iter ~f:(process_dep sat lookup_impl impl_var)) )
if !expand_deps
then
Model.requires role impl
|> Fiber.sequential_iter ~f:(fun dep ->
let f () = process_dep sat lookup_impl impl_var dep in
let { Model.dep_importance; _ } = Model.dep_info dep in
match dep_importance with
| `Essential -> f ()
| `Restricts ->
(* Defer processing restricting deps until all essential deps have
been processed for the entire problem. Restricting deps will be
processed later without recurring into their dependencies. *)
deferred := f :: !deferred;
Fiber.return ())
else Fiber.return ()) )
and lookup_impl key = ImplCache.lookup impl_cache add_impls_to_cache key in
let+ () =
let* () =
(* This recursively builds the whole problem up. *)
lookup_impl root_req
>>| Candidates.vars
>>| S.at_least_one sat ~reason:"need root" (* Must get what we came for! *)
in
(* Now process any restricting deps. Due to the cache, only restricting
deps that aren't also an essential dep will be expanded. The solver will
not process any transitive dependencies here since the dependencies of
restricting dependencies are irrelevant to solving the dependency
problem. *)
expand_deps := false;
let+ () = Fiber.sequential_iter !deferred ~f:(fun f -> f ()) in
(* All impl_candidates have now been added, so snapshot the cache. *)
let impl_clauses = ImplCache.snapshot impl_cache in
Conflict_classes.seal conflict_classes;
Expand Down

0 comments on commit 1a64582

Please sign in to comment.