Skip to content

Commit

Permalink
refactor(pkg): move [user_restrictions] (#11334)
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 2450be4 commit 66084ea
Showing 1 changed file with 10 additions and 11 deletions.
21 changes: 10 additions & 11 deletions src/dune_pkg/opam_solver.ml
Original file line number Diff line number Diff line change
Expand Up @@ -346,6 +346,14 @@ module Solver = struct

include T

let user_restrictions = function
| Virtual _ -> None
| Real role ->
(match Context.user_restrictions role.context role.name with
| None -> None
| Some f -> Some { kind = `Ensure; expr = OpamFormula.Atom f })
;;

let pp = pp_role

module Map = Map.Make (T)
Expand Down Expand Up @@ -524,14 +532,6 @@ module Solver = struct
Ordering.to_int (Poly.compare b a)
;;

let user_restrictions = function
| Virtual _ -> None
| Real role ->
(match Context.user_restrictions role.context role.name with
| None -> None
| Some f -> Some { kind = `Ensure; expr = OpamFormula.Atom f })
;;

let string_of_op =
let pos = { OpamParserTypes.FullPos.filename = ""; start = 0, 0; stop = 0, 0 } in
fun pelem -> OpamPrinter.FullPos.relop { pelem; pos }
Expand Down Expand Up @@ -1203,9 +1203,8 @@ module Solver = struct
(* Check for user-supplied restrictions *)
let examine_extra_restrictions report =
Role.Map.iteri report ~f:(fun role component ->
Model.user_restrictions role
|> Option.iter ~f:(fun restriction ->
Component.apply_user_restriction component restriction))
Model.Role.user_restrictions role
|> Option.iter ~f:(Component.apply_user_restriction component))
;;

(** For each selected implementation with a conflict class, reject all candidates
Expand Down

0 comments on commit 66084ea

Please sign in to comment.