diff --git a/src/0install-solver/diagnostics.ml b/src/0install-solver/diagnostics.ml index 8d932fd0c09..36c57eb2322 100644 --- a/src/0install-solver/diagnostics.ml +++ b/src/0install-solver/diagnostics.ml @@ -65,7 +65,6 @@ module Make (Results : S.SOLVER_RESULT) = struct type t = { role : Model.Role.t - ; replacement : Model.Role.t option ; diagnostics : Stdune.User_message.Style.t Pp.t Lazy.t ; selected_impl : Model.impl option ; (* orig_good is all the implementations passed to the SAT solver (these are the @@ -88,10 +87,9 @@ module Make (Results : S.SOLVER_RESULT) = struct (diagnostics : _ Pp.t Lazy.t) (selected_impl : Model.impl option) = - let { Model.impls; Model.replacement } = candidates in + let { Model.impls } = candidates in let notes = List.map ~f:(fun x -> Note.Feed_problem x) feed_problems in { role - ; replacement ; orig_good = impls ; orig_bad ; good = impls @@ -164,7 +162,6 @@ module Make (Results : S.SOLVER_RESULT) = struct t.good <- [] ;; - let replacement t = t.replacement let selected_impl t = t.selected_impl (* When something conflicts with itself then our usual trick of selecting @@ -338,19 +335,6 @@ module Make (Results : S.SOLVER_RESULT) = struct (* Find all restrictions that are in play and affect this interface *) let examine_selection report role component = - (* Note any conflicts caused by elements *) - let () = - match Component.replacement component with - | Some replacement when RoleMap.mem replacement report -> - Component.note component (ReplacedByConflict replacement); - Component.reject_all component (`ConflictsRole replacement); - (match RoleMap.find_opt replacement report with - | Some replacement_component -> - Component.note replacement_component (ReplacesConflict role); - Component.reject_all replacement_component (`ConflictsRole role) - | None -> ()) - | _ -> () - in match Component.selected_impl component with | Some our_impl -> (* For each dependency of our selected impl, explain why it rejected impls in the dependency's interface. *) diff --git a/src/0install-solver/s.ml b/src/0install-solver/s.ml index 9e2b53b40ea..3e5a295cd16 100644 --- a/src/0install-solver/s.ml +++ b/src/0install-solver/s.ml @@ -53,10 +53,7 @@ module type SOLVER_INPUT = sig include CORE_MODEL (** Information provided to the solver about a role. *) - type role_information = - { replacement : Role.t option (** Another role that conflicts with this one. *) - ; impls : impl list (** Candidates to fill the role. *) - } + type role_information = { impls : impl list (** Candidates to fill the role. *) } (** A restriction limits which implementations can fill a role. *) type restriction diff --git a/src/0install-solver/solver_core.ml b/src/0install-solver/solver_core.ml index c864a7fefc4..ba84a7fc161 100644 --- a/src/0install-solver/solver_core.ml +++ b/src/0install-solver/solver_core.ml @@ -181,23 +181,6 @@ module Make (Model : S.SOLVER_INPUT) = struct ; diagnostics : diagnostics (** Extra information useful for diagnostics *) } - (* Make each interface conflict with its replacement (if any). - * We do this at the end because if we didn't use the replacement feed, there's no need to conflict - * (avoids getting it added to feeds_used). *) - let add_replaced_by_conflicts sat impl_clauses = - List.iter ~f:(fun (clause, replacement) -> - ImplCache.get replacement impl_clauses - |> Option.iter (fun replacement_candidates -> - (* Our replacement was also added to [sat], so conflict with it. *) - let our_vars = clause#get_real_vars in - let replacements = replacement_candidates#get_real_vars in - if our_vars <> [] && replacements <> [] - then - (* Must select one implementation out of all candidates from both interfaces. - Dummy implementations don't conflict, though. *) - S.at_most_one sat (our_vars @ replacements) |> ignore)) - ;; - module Conflict_classes = struct module Map = Map.Make (struct type t = Model.conflict_class @@ -272,8 +255,8 @@ module Make (Model : S.SOLVER_INPUT) = struct ;; (* Add the implementations of an interface to the ImplCache (called the first time we visit it). *) - let make_impl_clause sat ~dummy_impl replacements role = - let+ { Model.replacement; impls } = Model.implementations role in + let make_impl_clause sat ~dummy_impl role = + let+ { impls } = Model.implementations role in (* Insert dummy_impl (last) if we're trying to diagnose a problem. *) let impls = match dummy_impl with @@ -289,10 +272,6 @@ module Make (Model : S.SOLVER_INPUT) = struct if impls <> [] then Some (S.at_most_one sat (List.map ~f:fst impls)) else None in let clause = new impl_candidates role impl_clause impls dummy_impl in - (* If we have a , remember to add a conflict with our replacement *) - replacement - |> Option.iter (fun replacement -> - replacements := (clause, replacement) :: !replacements); clause, impls ;; @@ -302,10 +281,8 @@ 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 - (* Handle conflicts after building the problem. *) - let replacements = ref [] in let rec add_impls_to_cache role = - let+ clause, impls = make_impl_clause sat ~dummy_impl replacements role in + let+ clause, impls = make_impl_clause sat ~dummy_impl role in ( clause , fun () -> impls @@ -325,7 +302,6 @@ module Make (Model : S.SOLVER_INPUT) = struct in (* All impl_candidates have now been added, so snapshot the cache. *) let impl_clauses = ImplCache.snapshot impl_cache in - add_replaced_by_conflicts sat impl_clauses !replacements; Conflict_classes.seal conflict_classes; impl_clauses ;; diff --git a/src/opam-0install/lib/model.ml b/src/opam-0install/lib/model.ml index 6e7b9fe2a3d..64b1f39c3c5 100644 --- a/src/opam-0install/lib/model.ml +++ b/src/opam-0install/lib/model.ml @@ -137,11 +137,7 @@ module Make (Context : S.CONTEXT) = struct { dep_role = drole; dep_importance = importance } ;; - type role_information = - { replacement : Role.t option - ; impls : impl list - } - + type role_information = { impls : impl list } type conflict_class = string let conflict_class = function @@ -179,7 +175,7 @@ module Make (Context : S.CONTEXT) = struct (* Get all the candidates for a role. *) let implementations = function - | Virtual (_, impls) -> Fiber.return { impls; replacement = None } + | Virtual (_, impls) -> Fiber.return { impls } | Real role -> let context = role.context in let+ impls = @@ -202,7 +198,7 @@ module Make (Context : S.CONTEXT) = struct in Some (RealImpl { pkg; opam; requires })) in - { impls; replacement = None } + { impls } ;; let restrictions dependency = dependency.restrictions