Skip to content

Commit

Permalink
refactor: use Virtual_id instead of objects (#11335)
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg authored Jan 18, 2025
1 parent 66084ea commit 779919f
Showing 1 changed file with 5 additions and 3 deletions.
8 changes: 5 additions & 3 deletions src/dune_pkg/opam_solver.ml
Original file line number Diff line number Diff line change
Expand Up @@ -281,14 +281,16 @@ module Solver = struct
; expr : OpamFormula.version_formula
}

module Virtual_id = Id.Make ()

type real_role =
{ context : Context.t
; name : OpamPackage.Name.t
}

type role =
| Real of real_role (* A role is usually an opam package name *)
| Virtual of < > * impl list (* (Object just for sorting) *)
| Virtual of Virtual_id.t * impl list

and real_impl =
{ pkg : OpamPackage.t
Expand Down Expand Up @@ -336,7 +338,7 @@ module Solver = struct
let compare a b =
match a, b with
| Real a, Real b -> Ordering.of_int (OpamPackage.Name.compare a.name b.name)
| Virtual (a, _), Virtual (b, _) -> Poly.compare a b
| Virtual (a, _), Virtual (b, _) -> Virtual_id.compare a b
| Real _, Virtual _ -> Lt
| Virtual _, Real _ -> Gt
;;
Expand Down Expand Up @@ -390,7 +392,7 @@ module Solver = struct
| VirtualImpl (_, x) -> VirtualImpl (i, x)
| x -> x)
in
Virtual (object end, impls)
Virtual (Virtual_id.gen (), impls)
;;

type dep_info =
Expand Down

0 comments on commit 779919f

Please sign in to comment.