Skip to content

Commit

Permalink
refactor: inline some more functions
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <[email protected]>

<!-- ps-id: 4572bdc9-61bb-4d24-8554-8f635c19b2cd -->

Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg committed Jan 19, 2025
1 parent 1d5ee8c commit 0b69862
Showing 1 changed file with 29 additions and 35 deletions.
64 changes: 29 additions & 35 deletions src/dune_pkg/opam_solver.ml
Original file line number Diff line number Diff line change
Expand Up @@ -444,32 +444,6 @@ module Solver = struct
Virtual (Virtual_id.gen (), impls)
;;

(* Turn an opam dependency formula into a 0install list of dependencies. *)
let list_deps ~context ~importance ~rank deps =
let rec aux (formula : _ OpamTypes.generic_formula) =
match formula with
| Empty -> []
| Atom (name, restrictions) ->
let drole = Real { context; name } in
[ { drole; restrictions; importance } ]
| Block x -> aux x
| And (x, y) -> aux x @ aux y
| Or _ as o ->
let impls = group_ors o in
let drole = virtual_role impls in
(* Essential because we must apply a restriction, even if its
components are only restrictions. *)
[ { drole; restrictions = []; importance = Ensure } ]
and group_ors = function
| Or (x, y) -> group_ors x @ group_ors y
| expr ->
let i = !rank in
rank := i + 1;
[ VirtualImpl (i, aux expr) ]
in
aux deps
;;

module Conflict_class = struct
type t = OpamPackage.Name.t

Expand Down Expand Up @@ -507,6 +481,32 @@ module Solver = struct
OpamFormula.Atom (name, rlist))
;;

(* Turn an opam dependency formula into a 0install list of dependencies. *)
let list_deps ~context ~importance ~rank deps =
let rec aux (formula : _ OpamTypes.generic_formula) =
match formula with
| Empty -> []
| Atom (name, restrictions) ->
let drole = Real { context; name } in
[ { drole; restrictions; importance } ]
| Block x -> aux x
| And (x, y) -> aux x @ aux y
| Or _ as o ->
let impls = group_ors o in
let drole = virtual_role impls in
(* Essential because we must apply a restriction, even if its
components are only restrictions. *)
[ { drole; restrictions = []; importance = Ensure } ]
and group_ors = function
| Or (x, y) -> group_ors x @ group_ors y
| expr ->
let i = !rank in
rank := i + 1;
[ VirtualImpl (i, aux expr) ]
in
aux deps
;;

(* Get all the candidates for a role. *)
let implementations = function
| Virtual (_, impls) -> Fiber.return impls
Expand Down Expand Up @@ -617,13 +617,6 @@ module Solver = struct
| Some lit -> Undecided lit
| None -> Unselected (* No remaining candidates, and none was chosen. *)))
;;

(* Apply [test impl] to each implementation, partitioning the vars into two
lists. Only defined for [impl_candidates]. *)
let partition t ~f:test =
List.partition_map t.vars ~f:(fun (var, impl) ->
if test impl then Either.Left var else Right var)
;;
end

type selection =
Expand Down Expand Up @@ -738,8 +731,9 @@ module Solver = struct
let meets_restrictions (* Restrictions on the candidates *) impl =
List.for_all ~f:(Input.meets_restriction impl) dep.restrictions
in
lookup_impl expand_deps dep.drole
>>| Candidates.partition ~f:meets_restrictions
let+ candidates = lookup_impl expand_deps dep.drole in
List.partition_map candidates.vars ~f:(fun (var, impl) ->
if meets_restrictions impl then Left var else Right var)
in
match dep.importance with
| Ensure ->
Expand Down

0 comments on commit 0b69862

Please sign in to comment.