Skip to content

Commit

Permalink
Reimplement --unlock-base as --update-invariant
Browse files Browse the repository at this point in the history
The approach is to
- remove the invariant while resolving
- update the configured invariant, keeping the package names that were
  part of it, but replacing the constraints that no longer match with
  adjusted ones.

Note that this should work OK for allowing compiler up/downgrades, but
can lead to an empty invariant if you just switched compiler
implementation. Doing the simpler things still seems better in this case
than some magic, though, and the user is told how to update.
  • Loading branch information
AltGr committed Mar 11, 2020
1 parent ea5b67f commit 8ca4d4c
Show file tree
Hide file tree
Showing 5 changed files with 64 additions and 10 deletions.
2 changes: 1 addition & 1 deletion src/client/opamArg.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1129,7 +1129,7 @@ let build_options =
to setting $(b,\\$OPAMIGNORECONSTRAINTS)."
Arg.(some (list package_name)) None ~vopt:(Some []) in
let unlock_base =
mk_flag ~section ["unlock-base"]
mk_flag ~section ["update-invariant"; "unlock-base"]
"Allow changes to the packages set as switch base (typically, the main \
compiler). Use with caution. This is equivalent to setting the \
$(b,\\$OPAMUNLOCKBASE) environment variable" in
Expand Down
36 changes: 35 additions & 1 deletion src/client/opamSolution.ml
Original file line number Diff line number Diff line change
Expand Up @@ -305,9 +305,37 @@ let parallel_apply t ~requested ?add_roots ~assume_built ?(force_remove=false)
as an operation terminates *)
let t_ref = ref t in

(* only needed when --update-invariant is set. Use the configured invariant,
not the current one which will be empty. *)
let original_invariant = t.switch_config.OpamFile.Switch_config.invariant in
let invariant_ref = ref original_invariant in

let add_to_install nv =
let root = OpamPackage.Name.Set.mem nv.name root_installs in
t_ref := OpamSwitchAction.add_to_installed !t_ref ~root nv
t_ref := OpamSwitchAction.add_to_installed !t_ref ~root nv;
if OpamStateConfig.(!r.unlock_base) then
let invariant =
OpamFormula.map (fun (n, cstr as at) ->
if n <> nv.name || OpamFormula.check_version_formula cstr nv.version
then Atom at else
let cstr =
OpamFormula.map (fun (relop, _ as vat) ->
if OpamFormula.check_version_formula (Atom vat) nv.version
then Atom vat
else match relop with
| `Neq | `Gt | `Lt -> OpamFormula.Empty
| `Eq | `Geq | `Leq -> Atom (relop, nv.version))
cstr
in
Atom (n, cstr))
!invariant_ref
in
if invariant <> !invariant_ref then
(invariant_ref := invariant;
let switch_config = {!t_ref.switch_config with invariant} in
t_ref := {!t_ref with switch_config};
OpamSwitchAction.install_switch_config t.switch_global.root t.switch
switch_config)
in

let remove_from_install ?keep_as_root nv =
Expand Down Expand Up @@ -632,6 +660,12 @@ let parallel_apply t ~requested ?add_roots ~assume_built ?(force_remove=false)
| _ -> assert false)
graph
in
if !invariant_ref <> original_invariant then
OpamConsole.note "Switch invariant was updated to %s\n\
Use `opam switch set-invariant' to change it."
(match !invariant_ref with
| OpamFormula.Empty -> "<empty>"
| f -> OpamFileTools.dep_formula_to_string f);
match action_results with
| `Successful successful ->
cleanup_artefacts action_graph;
Expand Down
6 changes: 6 additions & 0 deletions src/state/opamFileTools.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1015,6 +1015,12 @@ let read_repo_opam ~repo_name ~repo_root dir =
OpamFile.OPAM.with_metadata_dir
(Some (Some repo_name, OpamFilename.remove_prefix_dir repo_root dir))

let dep_formula_to_string f =
let pp =
OpamFormat.V.(package_formula `Conj (constraints version))
in
OpamPrinter.value (OpamPp.print pp f)

let sort_opam opam =
log "sorting %s" (OpamPackage.to_string (package opam));
let sort_ff =
Expand Down
8 changes: 6 additions & 2 deletions src/state/opamFileTools.mli
Original file line number Diff line number Diff line change
Expand Up @@ -105,6 +105,10 @@ val map_all_variables:
val map_all_filters:
(filter -> filter) -> OpamFile.OPAM.t -> OpamFile.OPAM.t

(* Sort opam fields: author, tags, depexts, depends, depopts, conflicts,
pin_depends, extra_files, extra_sources *)
(** Converts a dependency formula to the same format as used in opam package
definition files. *)
val dep_formula_to_string: formula -> string

(** Sort opam fields: author, tags, depexts, depends, depopts, conflicts,
pin_depends, extra_files, extra_sources *)
val sort_opam: OpamFile.OPAM.t -> OpamFile.OPAM.t
22 changes: 16 additions & 6 deletions src/state/opamSwitchState.ml
Original file line number Diff line number Diff line change
Expand Up @@ -696,12 +696,18 @@ let universe st
in
let u_depopts = get_deps OpamFile.OPAM.depopts st.opams in
let u_conflicts = get_conflicts st st.packages st.opams in
let base =
if OpamStateConfig.(!r.unlock_base) then OpamPackage.Set.empty
else st.compiler_packages
let base = st.compiler_packages in
let u_invariant =
if OpamStateConfig.(!r.unlock_base) then OpamFormula.Empty
else st.switch_invariant
in
let u_available =
remove_conflicts st base (Lazy.force st.available_packages)
(* TODO: removing what conflicts with the base is no longer correct now that
we use invariants instead. Removing what conflicts with the invariant
would be much more involved, but some solvers might struggle without any
cleanup at this point *)
(* remove_conflicts st base *)
(Lazy.force st.available_packages)
in
let u_reinstall =
(* Ignore reinstalls outside of the dependency cone of
Expand Down Expand Up @@ -733,7 +739,7 @@ let universe st
u_installed_roots = st.installed_roots;
u_pinned = OpamPinned.packages st;
u_base = base;
u_invariant = st.switch_invariant;
u_invariant;
u_reinstall;
u_attrs = ["opam-query", requested_allpkgs];
}
Expand Down Expand Up @@ -854,7 +860,11 @@ let unavailable_reason st ?(default="") (name, vformula) =
"conflict with the base packages of this switch"
else if OpamPackage.has_name st.compiler_packages name &&
not OpamStateConfig.(!r.unlock_base) then
"base of this switch (use `--unlock-base' to force)"
Printf.sprintf
"incompatible with the switch invariant %s (use `--update-invariant' \
to force)"
(OpamConsole.colorise `bold
(OpamFileTools.dep_formula_to_string st.switch_invariant))
else
default

Expand Down

0 comments on commit 8ca4d4c

Please sign in to comment.