Skip to content

Commit

Permalink
refactor(pkg): remove some useless int conversions (#11343)
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg authored Jan 19, 2025
1 parent 1e0e1d7 commit 7e2635c
Showing 1 changed file with 6 additions and 7 deletions.
13 changes: 6 additions & 7 deletions src/dune_pkg/opam_solver.ml
Original file line number Diff line number Diff line change
Expand Up @@ -537,12 +537,11 @@ module Solver = struct

let compare_version a b =
match a, b with
| RealImpl a, RealImpl b -> OpamPackage.compare a.pkg b.pkg
| VirtualImpl (ia, _), VirtualImpl (ib, _) -> Ordering.to_int (Int.compare ia ib)
| Reject a, Reject b -> OpamPackage.compare a b
| RealImpl a, RealImpl b -> Ordering.of_int (OpamPackage.compare a.pkg b.pkg)
| VirtualImpl (ia, _), VirtualImpl (ib, _) -> Int.compare ia ib
| Reject a, Reject b -> Ordering.of_int (OpamPackage.compare a b)
| ( (RealImpl _ | Reject _ | VirtualImpl _ | Dummy)
, (RealImpl _ | Reject _ | VirtualImpl _ | Dummy) ) ->
Ordering.to_int (Poly.compare b a)
, (RealImpl _ | Reject _ | VirtualImpl _ | Dummy) ) -> Poly.compare b a
;;

let string_of_op =
Expand Down Expand Up @@ -946,7 +945,7 @@ module Solver = struct
If [t] selected a better version anyway then we don't need to report this rejection. *)
let affected_selection t impl =
match t.selected_impl with
| Some selected when Input.compare_version selected impl > 0 -> false
| Some selected when Input.compare_version selected impl = Gt -> false
| _ -> true
;;

Expand Down Expand Up @@ -1052,7 +1051,7 @@ module Solver = struct
;;

let show_rejections ~verbose rejected =
let by_version (a, _) (b, _) = Input.compare_version b a |> Ordering.of_int in
let by_version (a, _) (b, _) = Input.compare_version b a in
let rejected = List.sort ~compare:by_version rejected in
let rec aux i = function
| [] -> Pp.nop
Expand Down

0 comments on commit 7e2635c

Please sign in to comment.