diff --git a/master_changes.md b/master_changes.md index 25a995a0365..485fc9a31ec 100644 --- a/master_changes.md +++ b/master_changes.md @@ -279,7 +279,7 @@ users) ## Client * Check whether the repository might need updating more often [#4935 @kit-ty-kate] * ✘ It is no longer possible to process actions on packages that depend on a package that was removed upstream [#4969 @altgr] - * Fix (at least some of the) empty conflict explanations [#4982 @kit-ty-kate] + * [BUG] Fix all empty conflict explanations [#4982 #5263 @kit-ty-kate] * Fix json double printing [#5143 @rjbou] * [BUG] Fix passing `archive-mirrors` field from init config file to config [#5315 @hannesm] diff --git a/src/solver/opamCudf.ml b/src/solver/opamCudf.ml index 533040eaaea..162988ca530 100644 --- a/src/solver/opamCudf.ml +++ b/src/solver/opamCudf.ml @@ -845,7 +845,6 @@ end let extract_explanations packages cudfnv2opam reasons : explanation list = log "Conflict reporting"; let open Dose_algo.Diagnostic in - let open Set.Op in let module CS = ChainSet in (* Definitions and printers *) log ~level:3 "Reasons: %a" (Pp_explanation.pp_reasonlist cudfnv2opam) reasons; @@ -909,6 +908,8 @@ let extract_explanations packages cudfnv2opam reasons : explanation list = (fun (n, _) -> Set.exists (fun p -> p.package = n) pkgs) vpkgl in + (* TODO: We should aim to use what does give us not guess the formula *) + (* Dose is precise enough from what i'm seeing *) formula_of_vpkgl cudfnv2opam packages vpkgl in let s = OpamFormula.to_string f in @@ -929,9 +930,9 @@ let extract_explanations packages cudfnv2opam reasons : explanation list = let rdeps = Hashtbl.create 53 in let missing = Hashtbl.create 53 in List.iter (function - | Conflict (l, r, _) -> + | Conflict (l, r, (_pkgname, _constr)) -> add_set ct l (Set.singleton r); - add_set ct r (Set.singleton l) + add_set ct r (Set.singleton l); | Dependency (l, _, rs) -> add_set deps l (Set.of_list rs); List.iter (fun r -> add_set rdeps r (Set.singleton l)) rs @@ -947,45 +948,31 @@ let extract_explanations packages cudfnv2opam reasons : explanation list = in Set.empty |> add_artefacts deps |> add_artefacts missing |> add_artefacts ct in - let conflicting = - Hashtbl.fold (fun p _ -> Set.add p) ct Set.empty - in - let all_conflicting = - Hashtbl.fold (fun k _ acc -> Set.add k acc) missing conflicting - in - let ct_chains = - (* get a covering tree from the roots to all reachable packages. - We keep only shortest chains, but all of them *) - (* The chains are stored as lists from packages back to the roots *) - let rec aux pchains seen acc = - if Map.is_empty pchains then acc else - let seen, new_chains = - Map.fold (fun p chains (seen1, new_chains) -> - let append_to_chains pkg acc = - let chain = CS.map (fun c -> pkg :: c) chains in - Map.update pkg (CS.union chain) CS.empty acc - in - let ds = get deps p in - let dsc = match Hashtbl.length missing with - | 0 -> ds (* Hack to fix https://github.com/ocaml/opam/issues/4373. We should try to do better at some point *) - | _ -> ds %% all_conflicting - in - if not (Set.is_empty dsc) then - dsc ++ seen1, Set.fold append_to_chains (dsc -- seen1) new_chains - else - Set.fold (fun d (seen1, new_chains) -> - if Set.mem d seen then seen1, new_chains - else Set.add d seen1, append_to_chains d new_chains) - ds (seen1, new_chains)) - pchains (seen, Map.empty) - in - aux new_chains seen @@ - Map.union (fun _ _ -> assert false) pchains acc + let _seen, ct_chains = + (* get a covering tree from the roots to all reachable packages. *) + let rec aux seen ct_chains = + Map.fold (fun pkg parent_chain (seen, ct_chains) -> + if Set.mem pkg seen then (seen, ct_chains) else + let dependencies = get deps pkg in + let seen = Set.add pkg seen in + Set.fold (fun dep (seen, ct_chains) -> + let chain = CS.map (fun c -> dep :: c) parent_chain in + let ct_chains = Map.update dep (CS.union chain) CS.empty ct_chains in + aux seen ct_chains + ) dependencies (seen, ct_chains) + ) ct_chains + (seen, ct_chains) in let init_chains = Set.fold (fun p -> Map.add p (CS.singleton [p])) roots Map.empty in - aux init_chains roots Map.empty + aux Set.empty init_chains + in + let ct_chains = + (* We keep only shortest chains. *) + (* TODO: choose is probably not the right thing here. *) + (* e.g. if two lists have the size, we should probably have both. *) + Map.map (fun x -> CS.singleton (CS.choose x)) ct_chains in let reasons = (* order "reasons" by most interesting first: version conflicts then package diff --git a/tests/reftests/conflict-badversion.test b/tests/reftests/conflict-badversion.test index f34916a8447..768d60cd831 100644 --- a/tests/reftests/conflict-badversion.test +++ b/tests/reftests/conflict-badversion.test @@ -1,4 +1,5 @@ f372039d +### OPAMVAR_arch=x86_64 OPAMVAR_os=linux OPAMVAR_os_family=arch OPAMVAR_os_distribution=archarm ### opam switch create --fake ocaml-base-compiler.4.02.3 <><> Installing new switch packages <><><><><><><><><><><><><><><><><><><><><><> @@ -17,6 +18,16 @@ Done. [ERROR] Package conflict! * No agreement on the version of core: - core != 112.17.00 + * No agreement on the version of ocaml: + - (invariant) -> ocaml-base-compiler = 4.02.3 -> ocaml = 4.02.3 + - core != 112.17.00 -> ocaml < 4.00.1 + You can temporarily relax the switch invariant with `--update-invariant' + * No agreement on the version of ocaml-base-compiler: + - (invariant) -> ocaml-base-compiler = 4.02.3 + - core != 112.17.00 -> ocaml < 4.00.1 -> ocaml-base-compiler < 3.07+1 + * Missing dependency: + - core != 112.17.00 -> ocaml < 4.00.1 -> ocaml-variants -> ocaml-beta + unmet availability conditions: 'enable-ocaml-beta-repository' No solution found, exiting # Return code 20 # diff --git a/tests/reftests/conflict-core.test b/tests/reftests/conflict-core.test index 5599383540a..0134005998f 100644 --- a/tests/reftests/conflict-core.test +++ b/tests/reftests/conflict-core.test @@ -1,4 +1,5 @@ f372039d +### OPAMVAR_arch=x86_64 OPAMVAR_os=linux OPAMVAR_os_family=arch OPAMVAR_os_distribution=archarm ### opam switch create ocaml-base-compiler.4.08.0 --fake <><> Installing new switch packages <><><><><><><><><><><><><><><><><><><><><><> @@ -18,6 +19,12 @@ Done. - (invariant) -> ocaml-base-compiler >= 4.08.0 -> ocaml = 4.08.0 - core < 112.17.00 -> ocaml < 4.00.1 You can temporarily relax the switch invariant with `--update-invariant' + * No agreement on the version of ocaml-base-compiler: + - (invariant) -> ocaml-base-compiler >= 4.08.0 + - core < 112.17.00 -> ocaml < 4.00.1 -> ocaml-base-compiler = 3.07+2 + * Missing dependency: + - core < 112.17.00 -> ocaml < 4.00.1 -> ocaml-variants >= 3.09.3 -> ocaml-beta + unmet availability conditions: 'enable-ocaml-beta-repository' No solution found, exiting # Return code 20 # diff --git a/tests/reftests/empty-conflicts-001.test b/tests/reftests/empty-conflicts-001.test index 525e53f2caa..492b822359a 100644 --- a/tests/reftests/empty-conflicts-001.test +++ b/tests/reftests/empty-conflicts-001.test @@ -16,6 +16,34 @@ Faking installation of ocaml.4.07.1 Done. ### opam install --show h2-mirage.0.9.0 [ERROR] Package conflict! -[ERROR] Internal error while computing conflict explanations: - sorry about that. Please report how you got here in https://github.com/ocaml/opam/discussions/5130 if possible. -# Return code 99 # + * No agreement on the version of ocaml: + - (invariant) -> ocaml-base-compiler = 4.07.1 -> ocaml = 4.07.1 + - h2-mirage >= 0.9.0 -> gluten-mirage >= 0.3.0 -> conduit-mirage >= 2.0.2 -> ocaml >= 4.08.0 + You can temporarily relax the switch invariant with `--update-invariant' + * No agreement on the version of ocaml-base-compiler: + - (invariant) -> ocaml-base-compiler = 4.07.1 + - h2-mirage >= 0.9.0 -> gluten-mirage >= 0.3.0 -> conduit-mirage >= 2.0.2 -> tls -> ocaml >= 4.08.0 -> ocaml-base-compiler >= 4.12.0~ + * No agreement on the version of cstruct: + - h2-mirage >= 0.9.0 -> gluten-mirage >= 0.3.0 -> conduit-mirage >= 2.0.2 -> tls -> cstruct < 4.0.0 + - h2-mirage >= 0.9.0 -> gluten-mirage >= 0.3.0 -> cstruct >= 6.0.0 + * No agreement on the version of cstruct: + - h2-mirage >= 0.9.0 -> gluten-mirage >= 0.3.0 -> conduit-mirage >= 2.0.2 -> tls -> cstruct < 6.0.0 + - h2-mirage >= 0.9.0 -> gluten-mirage >= 0.3.0 -> cstruct >= 6.0.0 + * Missing dependency: + - h2-mirage >= 0.9.0 -> gluten-mirage >= 0.3.0 -> conduit-mirage >= 2.0.2 -> dns-client >= 5.0.0 -> mirage-crypto-rng >= 0.8.0 -> mirage-crypto = 0.8.1 + unmet availability conditions: 'false' + * Missing dependency: + - h2-mirage >= 0.9.0 -> gluten-mirage >= 0.3.0 -> conduit-mirage >= 2.0.2 -> dns-client >= 5.0.0 -> mirage-crypto-rng >= 0.8.0 -> mirage-crypto = 0.8.2 + unmet availability conditions: 'false' + * Missing dependency: + - h2-mirage >= 0.9.0 -> gluten-mirage >= 0.3.0 -> conduit-mirage >= 2.0.2 -> dns-client >= 5.0.0 -> mirage-crypto-rng >= 0.8.0 -> mirage-crypto = 0.8.3 + unmet availability conditions: 'false' + * Missing dependency: + - h2-mirage >= 0.9.0 -> gluten-mirage >= 0.3.0 -> conduit-mirage >= 2.0.2 -> dns-client >= 5.0.0 -> mirage-crypto-rng >= 0.8.0 -> mirage-crypto = 0.8.4 + unmet availability conditions: 'false' + * Missing dependency: + - h2-mirage >= 0.9.0 -> gluten-mirage >= 0.3.0 -> conduit-mirage >= 2.0.2 -> tls -> sexplib < 113.01.00 -> ocaml < 4.03.0 -> ocaml-variants -> ocaml-beta + unmet availability conditions: 'enable-ocaml-beta-repository' + +No solution found, exiting +# Return code 20 # diff --git a/tests/reftests/empty-conflicts-002.test b/tests/reftests/empty-conflicts-002.test index 223a6732309..07ded8e7980 100644 --- a/tests/reftests/empty-conflicts-002.test +++ b/tests/reftests/empty-conflicts-002.test @@ -51,6 +51,19 @@ Faking installation of ppx_deriving_yojson.3.7.0 Done. ### opam install --show fstar.2022.01.15 [ERROR] Package conflict! -[ERROR] Internal error while computing conflict explanations: - sorry about that. Please report how you got here in https://github.com/ocaml/opam/discussions/5130 if possible. -# Return code 99 # + * No agreement on the version of ocaml: + - (invariant) -> ocaml-base-compiler = 4.14.0 -> ocaml = 4.14.0 + - fstar >= 2022.01.15 -> ppxlib < 0.26.0 -> ocaml < 4.14 + You can temporarily relax the switch invariant with `--update-invariant' + * No agreement on the version of ocaml-base-compiler: + - (invariant) -> ocaml-base-compiler = 4.14.0 + - fstar >= 2022.01.15 -> ppxlib < 0.26.0 -> ocaml < 4.08.0 -> ocaml-base-compiler = 3.08.4 + * No agreement on the version of ppxlib: + - fstar >= 2022.01.15 -> ppx_deriving_yojson -> ppxlib >= 0.26.0 + - fstar >= 2022.01.15 -> ppxlib < 0.26.0 + * Missing dependency: + - fstar >= 2022.01.15 -> ppxlib < 0.26.0 -> ocaml < 4.08.0 -> ocaml-variants >= 3.11.1 -> ocaml-beta + unmet availability conditions: 'enable-ocaml-beta-repository' + +No solution found, exiting +# Return code 20 # diff --git a/tests/reftests/empty-conflicts-003.test b/tests/reftests/empty-conflicts-003.test index ac600ff5418..4f78b921d30 100644 --- a/tests/reftests/empty-conflicts-003.test +++ b/tests/reftests/empty-conflicts-003.test @@ -17,6 +17,67 @@ Faking installation of ocaml-options-vanilla.1 Done. ### opam install --show disml [ERROR] Package conflict! -[ERROR] Internal error while computing conflict explanations: - sorry about that. Please report how you got here in https://github.com/ocaml/opam/discussions/5130 if possible. -# Return code 99 # + * No agreement on the version of ocaml-base-compiler: + - (invariant) -> ocaml-base-compiler = 4.14.0 + - disml -> ppx_deriving_yojson >= 3.3 -> ocaml < 4.08.0 -> ocaml-base-compiler = 4.02.1 + You can temporarily relax the switch invariant with `--update-invariant' + * No agreement on the version of yojson: + - disml -> ppx_deriving_yojson >= 3.3 -> yojson >= 1.6.0 + - disml -> yojson < 1.6.0 + * No agreement on the version of ocaml: + - (invariant) -> ocaml-base-compiler = 4.14.0 -> ocaml = 4.14.0 + - disml -> ppx_deriving_yojson >= 3.3 -> result -> dune -> ocaml < 4.08.0 + * Incompatible packages: + - disml -> ppx_deriving_yojson >= 3.3 -> result -> dune + - disml -> yojson < 1.6.0 + * Missing dependency: + - disml -> ppx_deriving_yojson >= 3.3 -> ocaml < 4.08.0 -> ocaml-variants >= 4.02.1 -> ocaml-beta + unmet availability conditions: 'enable-ocaml-beta-repository' + * Missing dependency: + - disml -> ppx_deriving_yojson >= 3.3 -> result -> dune -> ocaml < 4.08.0 -> ocaml-base-compiler < 3.07+1 | ocaml-system < 3.07+1 | ocaml-variants < 3.8~ + unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' + unmet availability conditions: 'sys-ocaml-version = "3.07"' + no matching version + * Missing dependency: + - disml -> ppx_deriving_yojson >= 3.3 -> result -> dune -> ocaml < 4.08.0 -> ocaml-base-compiler = 3.07+1 | ocaml-system = 3.07+1 | ocaml-variants < 3.8~ + unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' + unmet availability conditions: 'sys-ocaml-version = "3.07+1"' + no matching version + * Missing dependency: + - disml -> ppx_deriving_yojson >= 3.3 -> result -> dune -> ocaml < 4.08.0 -> ocaml-base-compiler = 3.07+2 | ocaml-system = 3.07+2 | ocaml-variants < 3.8~ + unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' + unmet availability conditions: 'sys-ocaml-version = "3.07+2"' + no matching version + * Missing dependency: + - disml -> ppx_deriving_yojson >= 3.3 -> result -> dune -> ocaml < 4.08.0 -> ocaml-base-compiler = 3.08.0 | ocaml-system < 3.08.1~ | ocaml-variants < 3.08.1~ + unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' + unmet availability conditions, e.g. 'sys-ocaml-version = "3.08.0"' + no matching version + * Missing dependency: + - disml -> ppx_deriving_yojson >= 3.3 -> result -> dune -> ocaml < 4.08.0 -> ocaml-base-compiler = 3.08.1 | ocaml-system < 3.08.2~ | ocaml-variants < 3.08.2~ + unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' + unmet availability conditions, e.g. 'sys-ocaml-version = "3.08.1"' + no matching version + * Missing dependency: + - disml -> ppx_deriving_yojson >= 3.3 -> result -> dune -> ocaml < 4.08.0 -> ocaml-base-compiler = 3.08.2 | ocaml-system < 3.08.3~ | ocaml-variants < 3.08.3~ + unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' + unmet availability conditions, e.g. 'sys-ocaml-version = "3.08.2"' + no matching version + * Missing dependency: + - disml -> ppx_deriving_yojson >= 3.3 -> result -> dune -> ocaml < 4.08.0 -> ocaml-base-compiler = 3.08.3 | ocaml-system < 3.08.4~ | ocaml-variants < 3.08.4~ + unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' + unmet availability conditions, e.g. 'sys-ocaml-version = "3.08.3"' + no matching version + * Missing dependency: + - disml -> ppx_deriving_yojson >= 3.3 -> result -> dune -> ocaml < 4.08.0 -> ocaml-base-compiler = 3.08.4 | ocaml-system < 3.08.5~ | ocaml-variants < 3.08.5~ + unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' + unmet availability conditions, e.g. 'sys-ocaml-version = "3.08.4"' + no matching version + * Missing dependency: + - disml -> ppx_deriving_yojson >= 3.3 -> result -> dune -> ocaml < 4.08.0 -> ocaml-base-compiler = 3.09.0 | ocaml-system < 3.09.1~ | ocaml-variants < 3.09.1~ + unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' + unmet availability conditions, e.g. 'sys-ocaml-version = "3.09.0"' + no matching version + +No solution found, exiting +# Return code 20 # diff --git a/tests/reftests/empty-conflicts-004.test b/tests/reftests/empty-conflicts-004.test index 6066552891c..541076a7bdc 100644 --- a/tests/reftests/empty-conflicts-004.test +++ b/tests/reftests/empty-conflicts-004.test @@ -16,6 +16,79 @@ Faking installation of ocaml.4.14.0 Done. ### opam install --show camlp5 GT ppxlib.0.25.0 [ERROR] Package conflict! -[ERROR] Internal error while computing conflict explanations: - sorry about that. Please report how you got here in https://github.com/ocaml/opam/discussions/5130 if possible. -# Return code 99 # + * No agreement on the version of ppxlib: + - GT -> ppxlib < 0.25 + - ppxlib >= 0.25.0 + * No agreement on the version of ocaml: + - (invariant) -> ocaml-variants = 4.14.0+trunk -> ocaml = 4.14.0 + - GT -> ocaml < 4.12 + You can temporarily relax the switch invariant with `--update-invariant' + * No agreement on the version of ocaml-variants: + - (invariant) -> ocaml-variants = 4.14.0+trunk + - GT -> camlp5 < 8.00 -> ocaml < 4.00.1 -> ocaml-variants < 3.09.2~ + * Missing dependency: + - GT -> ocaml < 4.12 -> ocaml-base-compiler < 3.07+1 | ocaml-system < 3.07+1 | ocaml-variants < 3.8~ + unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' + unmet availability conditions: 'sys-ocaml-version = "3.07"' + no matching version + * Missing dependency: + - GT -> ocaml < 4.12 -> ocaml-base-compiler = 3.07+1 | ocaml-system = 3.07+1 | ocaml-variants < 3.8~ + unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' + unmet availability conditions: 'sys-ocaml-version = "3.07+1"' + no matching version + * Missing dependency: + - GT -> ocaml < 4.12 -> ocaml-base-compiler = 3.07+2 | ocaml-system = 3.07+2 | ocaml-variants < 3.8~ + unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' + unmet availability conditions: 'sys-ocaml-version = "3.07+2"' + no matching version + * Missing dependency: + - GT -> ocaml < 4.12 -> ocaml-base-compiler = 3.08.0 | ocaml-system < 3.08.1~ | ocaml-variants < 3.08.1~ + unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' + unmet availability conditions, e.g. 'sys-ocaml-version = "3.08.0"' + no matching version + * Missing dependency: + - GT -> ocaml < 4.12 -> ocaml-base-compiler = 3.08.1 | ocaml-system < 3.08.2~ | ocaml-variants < 3.08.2~ + unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' + unmet availability conditions, e.g. 'sys-ocaml-version = "3.08.1"' + no matching version + * Missing dependency: + - GT -> ocaml < 4.12 -> ocaml-base-compiler = 3.08.2 | ocaml-system < 3.08.3~ | ocaml-variants < 3.08.3~ + unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' + unmet availability conditions, e.g. 'sys-ocaml-version = "3.08.2"' + no matching version + * Missing dependency: + - GT -> ocaml < 4.12 -> ocaml-base-compiler = 3.08.3 | ocaml-system < 3.08.4~ | ocaml-variants < 3.08.4~ + unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' + unmet availability conditions, e.g. 'sys-ocaml-version = "3.08.3"' + no matching version + * Missing dependency: + - GT -> ocaml < 4.12 -> ocaml-base-compiler = 3.08.4 | ocaml-system < 3.08.5~ | ocaml-variants < 3.08.5~ + unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' + unmet availability conditions, e.g. 'sys-ocaml-version = "3.08.4"' + no matching version + * Missing dependency: + - GT -> ocaml < 4.12 -> ocaml-base-compiler = 3.09.0 | ocaml-system < 3.09.1~ | ocaml-variants < 3.09.1~ + unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' + unmet availability conditions, e.g. 'sys-ocaml-version = "3.09.0"' + no matching version + * Missing dependency: + - GT -> camlp5 < 8.00 -> ocaml < 4.08.1 -> ocaml-variants < 4.08.1~ -> ocaml-beta + unmet availability conditions: 'enable-ocaml-beta-repository' + * Missing dependency: + - GT -> camlp5 < 8.00 -> ocaml < 4.10.0 -> ocaml-variants < 4.08.2~ -> ocaml-beta + unmet availability conditions: 'enable-ocaml-beta-repository' + * Missing dependency: + - GT -> camlp5 < 8.00 -> ocaml < 4.10.0 -> ocaml-variants < 4.09.1~ -> ocaml-beta + unmet availability conditions: 'enable-ocaml-beta-repository' + * Missing dependency: + - GT -> camlp5 < 8.00 -> ocaml < 4.10.1 -> ocaml-variants < 4.10.1~ -> ocaml-beta + unmet availability conditions: 'enable-ocaml-beta-repository' + * Missing dependency: + - GT -> camlp5 < 8.00 -> ocaml < 4.11.1 -> ocaml-variants < 4.10.2~ -> ocaml-beta + unmet availability conditions: 'enable-ocaml-beta-repository' + * Missing dependency: + - GT -> camlp5 < 8.00 -> ocaml < 4.11.1 -> ocaml-variants < 4.11.1~ -> ocaml-beta + unmet availability conditions: 'enable-ocaml-beta-repository' + +No solution found, exiting +# Return code 20 # diff --git a/tests/reftests/empty-conflicts-005.test b/tests/reftests/empty-conflicts-005.test index 8894e2b0c7c..445d7d13d8a 100644 --- a/tests/reftests/empty-conflicts-005.test +++ b/tests/reftests/empty-conflicts-005.test @@ -16,6 +16,31 @@ Faking installation of ocaml.4.12.0 Done. ### opam install --show pgocaml_ppx.4.2.2 [ERROR] Package conflict! -[ERROR] Internal error while computing conflict explanations: - sorry about that. Please report how you got here in https://github.com/ocaml/opam/discussions/5130 if possible. -# Return code 99 # + * No agreement on the version of ocaml: + - (invariant) -> ocaml-variants = 4.12.0+trunk -> ocaml = 4.12.0 + - pgocaml_ppx >= 4.2.2 -> ocaml-migrate-parsetree < 2.0.0 -> ocaml < 4.06.0 + You can temporarily relax the switch invariant with `--update-invariant' + * No agreement on the version of ocaml-variants: + - (invariant) -> ocaml-variants = 4.12.0+trunk + - pgocaml_ppx >= 4.2.2 -> ocaml-migrate-parsetree < 2.0.0 -> ocaml < 4.06.0 -> ocaml-variants < 3.09.2~ + * No agreement on the version of ocaml-migrate-parsetree: + - pgocaml_ppx >= 4.2.2 -> ocaml-migrate-parsetree < 2.0.0 + - pgocaml_ppx >= 4.2.2 -> ppx_deriving >= 4.0 -> ppxlib >= 0.20.0 -> ocaml-migrate-parsetree >= 2.1.0 + * Missing dependency: + - pgocaml_ppx >= 4.2.2 -> ocaml-migrate-parsetree < 2.0.0 -> ocaml < 4.09.0 -> ocaml-variants < 4.08.2~ -> ocaml-beta + unmet availability conditions: 'enable-ocaml-beta-repository' + * Missing dependency: + - pgocaml_ppx >= 4.2.2 -> ocaml-migrate-parsetree < 2.0.0 -> ocaml < 4.11 -> ocaml-variants < 4.10.1~ -> ocaml-beta + unmet availability conditions: 'enable-ocaml-beta-repository' + * Missing dependency: + - pgocaml_ppx >= 4.2.2 -> ocaml-migrate-parsetree < 2.0.0 -> ocaml < 4.11 -> ocaml-variants < 4.10.2~ -> ocaml-beta + unmet availability conditions: 'enable-ocaml-beta-repository' + * Missing dependency: + - pgocaml_ppx >= 4.2.2 -> ocaml-migrate-parsetree < 2.0.0 -> ocaml < 4.12 -> ocaml-variants < 4.11.1~ -> ocaml-beta + unmet availability conditions: 'enable-ocaml-beta-repository' + * Missing dependency: + - pgocaml_ppx >= 4.2.2 -> ocaml-migrate-parsetree < 2.0.0 -> ocaml < 4.12 -> ocaml-variants < 4.11.3~ -> ocaml-beta + unmet availability conditions: 'enable-ocaml-beta-repository' + +No solution found, exiting +# Return code 20 # diff --git a/tests/reftests/empty-conflicts-006.test b/tests/reftests/empty-conflicts-006.test index 100eeed48f8..5914fa51c09 100644 --- a/tests/reftests/empty-conflicts-006.test +++ b/tests/reftests/empty-conflicts-006.test @@ -20,16 +20,16 @@ Done. ### : Fixed by https://github.com/ocaml/opam/pull/4982 ### opam install --show gen_js_api.1.0.6 [ERROR] Package conflict! - * No agreement on the version of ocaml-variants: - - (invariant) -> ocaml-variants = 4.12.0+trunk - - gen_js_api >= 1.0.6 -> ocaml-migrate-parsetree < 2.0.0 -> ocaml-variants = 4.08.0+beta2 - You can temporarily relax the switch invariant with `--update-invariant' * No agreement on the version of ocaml: - (invariant) -> ocaml-variants = 4.12.0+trunk -> ocaml = 4.12.0 - gen_js_api >= 1.0.6 -> ocaml-migrate-parsetree < 2.0.0 -> ocaml < 4.06.0 + You can temporarily relax the switch invariant with `--update-invariant' * No agreement on the version of ocaml-migrate-parsetree: - gen_js_api >= 1.0.6 -> ocaml-migrate-parsetree < 2.0.0 - gen_js_api >= 1.0.6 -> ppxlib >= 0.9 -> ocaml-migrate-parsetree >= 2.1.0 + * No agreement on the version of ocaml-variants: + - (invariant) -> ocaml-variants = 4.12.0+trunk + - gen_js_api >= 1.0.6 -> ocaml-migrate-parsetree < 2.0.0 -> ocaml < 4.06.0 -> ocaml-variants < 4.00.2~ No solution found, exiting # Return code 20 # diff --git a/tests/reftests/install-formula.test b/tests/reftests/install-formula.test index d1d7d28db1d..27beec773bb 100644 --- a/tests/reftests/install-formula.test +++ b/tests/reftests/install-formula.test @@ -78,6 +78,13 @@ Nothing to do. * Incompatible packages: - mirage-no-solo5 - mirage-solo5 + * Incompatible packages: + - (invariant) -> ocaml-system + - mirage-solo5 -> ocaml-freestanding < 0.3.0 -> ocaml < 4.04.0 -> ocaml-base-compiler < 3.07+1 + You can temporarily relax the switch invariant with `--update-invariant' + * Missing dependency: + - mirage-solo5 -> ocaml-freestanding < 0.3.0 -> ocaml < 4.04.0 -> ocaml-variants -> ocaml-beta + unmet availability conditions: 'enable-ocaml-beta-repository' No solution found, exiting # Return code 20 # @@ -87,6 +94,13 @@ No solution found, exiting * Incompatible packages: - mirage-no-solo5 - mirage-solo5 + * Incompatible packages: + - (invariant) -> ocaml-system + - mirage-solo5 -> ocaml-freestanding < 0.3.0 -> ocaml < 4.04.0 -> ocaml-base-compiler < 3.07+1 + You can temporarily relax the switch invariant with `--update-invariant' + * Missing dependency: + - mirage-solo5 -> ocaml-freestanding < 0.3.0 -> ocaml < 4.04.0 -> ocaml-variants -> ocaml-beta + unmet availability conditions: 'enable-ocaml-beta-repository' No solution found, exiting # Return code 20 # @@ -96,6 +110,13 @@ No solution found, exiting - Incompatible packages: - mirage-no-solo5 - mirage-solo5 + - Incompatible packages: + - (invariant) -> ocaml-system + - mirage-solo5 -> ocaml-freestanding < 0.3.0 -> ocaml < 4.04.0 -> ocaml-base-compiler < 3.07+1 + You can temporarily relax the switch invariant with `--update-invariant' + - Missing dependency: + - mirage-solo5 -> ocaml-freestanding < 0.3.0 -> ocaml < 4.04.0 -> ocaml-variants -> ocaml-beta + unmet availability conditions: 'enable-ocaml-beta-repository' You may run "opam upgrade --fixup" to let opam fix the current state. # Return code 20 # diff --git a/tests/reftests/install-pgocaml.test b/tests/reftests/install-pgocaml.test index 57a11030154..777654fa761 100644 --- a/tests/reftests/install-pgocaml.test +++ b/tests/reftests/install-pgocaml.test @@ -1,4 +1,5 @@ f372039d +### OPAMVAR_arch=x86_64 OPAMVAR_os=linux OPAMVAR_os_family=arch OPAMVAR_os_distribution=archarm ### opam switch create --fake 4.06.1 <><> Installing new switch packages <><><><><><><><><><><><><><><><><><><><><><> @@ -18,6 +19,12 @@ Done. - (invariant) -> ocaml-base-compiler = 4.06.1 -> ocaml = 4.06.1 - pgocaml < 2.0 -> ocaml < 4.06.0 You can temporarily relax the switch invariant with `--update-invariant' + * No agreement on the version of ocaml-base-compiler: + - (invariant) -> ocaml-base-compiler = 4.06.1 + - pgocaml < 2.0 -> extlib = 1.5.3 -> ocaml < 4.05.0 -> ocaml-base-compiler < 3.07+1 + * Missing dependency: + - pgocaml < 2.0 -> extlib = 1.5.3 -> ocaml < 4.05.0 -> ocaml-variants >= 3.09.3 -> ocaml-beta + unmet availability conditions: 'enable-ocaml-beta-repository' No solution found, exiting # Return code 20 # diff --git a/tests/reftests/unhelpful-conflicts-001.test b/tests/reftests/unhelpful-conflicts-001.test index ff23ac5fe33..9148315a0e9 100644 --- a/tests/reftests/unhelpful-conflicts-001.test +++ b/tests/reftests/unhelpful-conflicts-001.test @@ -19,251 +19,255 @@ Faking installation of ocaml-options-vanilla.1 Done. ### opam install dune-release [ERROR] Package conflict! + * No agreement on the version of ocaml-base-compiler: + - (invariant) -> ocaml-base-compiler >= 5.0.0~alpha0 + - dune-release -> fmt < 0.8.7 -> ocaml < 5.0 -> ocaml-base-compiler = 4.10.2 + You can temporarily relax the switch invariant with `--update-invariant' * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 4.06.0 -> ocaml-base-compiler < 3.07+1 | ocaml-system < 3.07+1 | ocaml-variants < 3.8~ + - dune-release -> fmt < 0.8.7 -> ocaml < 5.0 -> ocaml-base-compiler = 4.08.1 | ocaml-system >= 4.08.1 | ocaml-variants < 4.08.2~ + unmet availability conditions: '!(os = "macos" & arch = "arm64")' + unmet availability conditions, e.g. 'sys-ocaml-version = "4.08.1"' + unmet availability conditions, e.g. '!(os = "macos" & arch = "arm64")' + * Missing dependency: + - dune-release -> fmt < 0.8.7 -> ocaml < 5.0 -> ocaml-base-compiler = 4.08.2 | ocaml-system >= 4.08.2 | ocaml-variants < 4.08.3~ + no matching version + unmet availability conditions, e.g. 'sys-ocaml-version = "4.14.0"' + unmet availability conditions, e.g. '!(os = "macos" & arch = "arm64")' + * Missing dependency: + - dune-release -> fmt < 0.8.7 -> ocaml < 5.0 -> ocaml-base-compiler = 4.09.0 | ocaml-system >= 4.09.0 | ocaml-variants < 4.09.1~ + unmet availability conditions: '!(os = "macos" & arch = "arm64")' + unmet availability conditions, e.g. 'sys-ocaml-version = "4.09.0"' + unmet availability conditions, e.g. '!(os = "macos" & arch = "arm64")' + * Missing dependency: + - dune-release -> fmt < 0.8.7 -> ocaml < 5.0 -> ocaml-base-compiler = 4.09.1 | ocaml-system >= 4.09.1 | ocaml-variants < 4.09.2~ + unmet availability conditions: '!(os = "macos" & arch = "arm64")' + unmet availability conditions, e.g. 'sys-ocaml-version = "4.09.1"' + unmet availability conditions, e.g. '!(os = "macos" & arch = "arm64")' + * Missing dependency: + - dune-release -> fmt < 0.8.7 -> ocaml < 5.0 -> ocaml-base-compiler = 4.09.2 | ocaml-system >= 4.09.2 | ocaml-variants < 4.09.3~ + no matching version + unmet availability conditions, e.g. 'sys-ocaml-version = "4.14.0"' + unmet availability conditions, e.g. '!(os = "macos" & arch = "arm64")' + * Missing dependency: + - dune-release -> fmt < 0.8.7 -> ocaml < 5.0 -> ocaml-base-compiler = 4.10.0 | ocaml-system >= 4.10.0 | ocaml-variants < 4.10.1~ + unmet availability conditions: '!(os = "macos" & arch = "arm64")' + unmet availability conditions, e.g. 'sys-ocaml-version = "4.10.0"' + unmet availability conditions, e.g. '!(os = "macos" & arch = "arm64")' + * Missing dependency: + - dune-release -> fmt < 0.8.7 -> ocaml < 5.0 -> ocaml-base-compiler = 4.10.1 | ocaml-system >= 4.10.1 | ocaml-variants < 4.10.2~ + unmet availability conditions: '!(os = "macos" & arch = "arm64")' + unmet availability conditions, e.g. 'sys-ocaml-version = "4.10.1"' + unmet availability conditions, e.g. '!(os = "macos" & arch = "arm64")' + * Missing dependency: + - dune-release -> odoc -> doc-ock -> ocaml < 4.04 -> ocaml-base-compiler < 3.07+1 | ocaml-system < 3.07+1 | ocaml-variants < 3.8~ unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' unmet availability conditions: 'sys-ocaml-version = "3.07"' no matching version * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 4.06.0 -> ocaml-base-compiler = 3.07+1 | ocaml-system = 3.07+1 | ocaml-variants < 3.8~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.04 -> ocaml-base-compiler = 3.07+1 | ocaml-system = 3.07+1 | ocaml-variants < 3.8~ unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' unmet availability conditions: 'sys-ocaml-version = "3.07+1"' no matching version * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 4.06.0 -> ocaml-base-compiler = 3.07+2 | ocaml-system = 3.07+2 | ocaml-variants < 3.8~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.04 -> ocaml-base-compiler = 3.07+2 | ocaml-system = 3.07+2 | ocaml-variants < 3.8~ unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' unmet availability conditions: 'sys-ocaml-version = "3.07+2"' no matching version * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 4.06.0 -> ocaml-base-compiler = 3.08.0 | ocaml-system < 3.08.1~ | ocaml-variants < 3.08.1~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.04 -> ocaml-base-compiler = 3.08.0 | ocaml-system < 3.08.1~ | ocaml-variants < 3.08.1~ unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' unmet availability conditions, e.g. 'sys-ocaml-version = "3.08.0"' no matching version * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 4.06.0 -> ocaml-base-compiler = 3.08.1 | ocaml-system < 3.08.2~ | ocaml-variants < 3.08.2~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.04 -> ocaml-base-compiler = 3.08.1 | ocaml-system < 3.08.2~ | ocaml-variants < 3.08.2~ unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' unmet availability conditions, e.g. 'sys-ocaml-version = "3.08.1"' no matching version * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 4.06.0 -> ocaml-base-compiler = 3.08.2 | ocaml-system < 3.08.3~ | ocaml-variants < 3.08.3~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.04 -> ocaml-base-compiler = 3.08.2 | ocaml-system < 3.08.3~ | ocaml-variants < 3.08.3~ unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' unmet availability conditions, e.g. 'sys-ocaml-version = "3.08.2"' no matching version * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 4.06.0 -> ocaml-base-compiler = 3.08.3 | ocaml-system < 3.08.4~ | ocaml-variants < 3.08.4~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.04 -> ocaml-base-compiler = 3.08.3 | ocaml-system < 3.08.4~ | ocaml-variants < 3.08.4~ unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' unmet availability conditions, e.g. 'sys-ocaml-version = "3.08.3"' no matching version * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 4.06.0 -> ocaml-base-compiler = 3.08.4 | ocaml-system < 3.08.5~ | ocaml-variants < 3.08.5~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.04 -> ocaml-base-compiler = 3.08.4 | ocaml-system < 3.08.5~ | ocaml-variants < 3.08.5~ unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' unmet availability conditions, e.g. 'sys-ocaml-version = "3.08.4"' no matching version * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 4.06.0 -> ocaml-base-compiler = 3.09.0 | ocaml-system < 3.09.1~ | ocaml-variants < 3.09.1~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.04 -> ocaml-base-compiler = 3.09.0 | ocaml-system < 3.09.1~ | ocaml-variants < 3.09.1~ unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' unmet availability conditions, e.g. 'sys-ocaml-version = "3.09.0"' no matching version * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 4.06.0 -> ocaml-base-compiler = 3.09.1 | ocaml-system < 3.09.2~ | ocaml-variants < 3.09.2~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.04 -> ocaml-base-compiler = 3.09.1 | ocaml-system < 3.09.2~ | ocaml-variants < 3.09.2~ unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' unmet availability conditions, e.g. 'sys-ocaml-version = "3.09.1"' unmet availability conditions: '!(os = "macos" & arch = "arm64")' * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 4.06.0 -> ocaml-base-compiler = 3.09.2 | ocaml-system < 3.09.3~ | ocaml-variants < 3.09.3~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.04 -> ocaml-base-compiler = 3.09.2 | ocaml-system < 3.09.3~ | ocaml-variants < 3.09.3~ unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' unmet availability conditions, e.g. 'sys-ocaml-version = "3.09.2"' unmet availability conditions: '!(os = "macos" & arch = "arm64")' * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 4.06.0 -> ocaml-base-compiler = 3.09.3 | ocaml-system < 3.09.4~ | ocaml-variants < 3.09.4~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.04 -> ocaml-base-compiler = 3.09.3 | ocaml-system < 3.09.4~ | ocaml-variants < 3.09.4~ unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' unmet availability conditions, e.g. 'sys-ocaml-version = "3.09.3"' unmet availability conditions: '!(os = "macos" & arch = "arm64")' * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 4.06.0 -> ocaml-base-compiler = 3.10.0 | ocaml-system < 3.10.1~ | ocaml-variants < 3.10.1~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.04 -> ocaml-base-compiler = 3.10.0 | ocaml-system < 3.10.1~ | ocaml-variants < 3.10.1~ unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' unmet availability conditions, e.g. 'sys-ocaml-version = "3.10.0"' unmet availability conditions: '!(os = "macos" & arch = "arm64")' * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 4.06.0 -> ocaml-base-compiler = 3.10.1 | ocaml-system < 3.10.2~ | ocaml-variants < 3.10.2~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.04 -> ocaml-base-compiler = 3.10.1 | ocaml-system < 3.10.2~ | ocaml-variants < 3.10.2~ unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' unmet availability conditions, e.g. 'sys-ocaml-version = "3.10.1"' unmet availability conditions: '!(os = "macos" & arch = "arm64")' * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 4.06.0 -> ocaml-base-compiler = 3.10.2 | ocaml-system < 3.10.3~ | ocaml-variants < 3.10.3~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.04 -> ocaml-base-compiler = 3.10.2 | ocaml-system < 3.10.3~ | ocaml-variants < 3.10.3~ unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' unmet availability conditions, e.g. 'sys-ocaml-version = "3.10.2"' unmet availability conditions: '!(os = "macos" & arch = "arm64")' * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 4.06.0 -> ocaml-base-compiler = 3.11.0 | ocaml-system < 3.11.1~ | ocaml-variants < 3.11.1~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.04 -> ocaml-base-compiler = 3.11.0 | ocaml-system < 3.11.1~ | ocaml-variants < 3.11.1~ unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' unmet availability conditions, e.g. 'sys-ocaml-version = "3.11.0"' unmet availability conditions: '!(os = "macos" & arch = "arm64")' * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 4.06.0 -> ocaml-base-compiler = 3.11.1 | ocaml-system < 3.11.2~ | ocaml-variants < 3.11.2~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.04 -> ocaml-base-compiler = 3.11.1 | ocaml-system < 3.11.2~ | ocaml-variants < 3.11.2~ unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' unmet availability conditions, e.g. 'sys-ocaml-version = "3.11.1"' unmet availability conditions: '!(os = "macos" & arch = "arm64")' * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 4.06.0 -> ocaml-base-compiler = 3.11.2 | ocaml-system < 3.11.3~ | ocaml-variants < 3.11.3~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.04 -> ocaml-base-compiler = 3.11.2 | ocaml-system < 3.11.3~ | ocaml-variants < 3.11.3~ unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' unmet availability conditions, e.g. 'sys-ocaml-version = "3.11.2"' unmet availability conditions: '!(os = "macos" & arch = "arm64")' * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 4.06.0 -> ocaml-base-compiler = 3.12.0 | ocaml-system < 3.12.1~ | ocaml-variants < 3.12.1~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.04 -> ocaml-base-compiler = 3.12.0 | ocaml-system < 3.12.1~ | ocaml-variants < 3.12.1~ unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' unmet availability conditions, e.g. 'sys-ocaml-version = "3.12.0"' unmet availability conditions: '!(os = "macos" & arch = "arm64")' * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 4.06.0 -> ocaml-base-compiler = 3.12.1 | ocaml-system < 3.12.2~ | ocaml-variants < 3.12.2~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.04 -> ocaml-base-compiler = 3.12.1 | ocaml-system < 3.12.2~ | ocaml-variants < 3.12.2~ unmet availability conditions: 'arch != "arm64" & arch != "arm32" & arch != "ppc64"' unmet availability conditions, e.g. 'sys-ocaml-version = "3.12.1"' unmet availability conditions: '!(os = "macos" & arch = "arm64")' * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 4.06.0 -> ocaml-base-compiler = 4.00.0 | ocaml-system < 4.00.1~ | ocaml-variants < 4.00.1~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.04 -> ocaml-base-compiler = 4.00.0 | ocaml-system < 4.00.1~ | ocaml-variants < 4.00.1~ unmet availability conditions: 'arch != "arm64" & arch != "ppc64"' unmet availability conditions, e.g. 'sys-ocaml-version = "4.00.0"' unmet availability conditions, e.g. 'false' * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 4.06.0 -> ocaml-base-compiler = 4.00.1 | ocaml-system < 4.00.2~ | ocaml-variants < 4.00.2~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.04 -> ocaml-base-compiler = 4.00.1 | ocaml-system < 4.00.2~ | ocaml-variants < 4.00.2~ unmet availability conditions: 'arch != "arm64" & arch != "ppc64"' unmet availability conditions, e.g. 'sys-ocaml-version = "4.00.1"' unmet availability conditions, e.g. '!(os = "macos" & arch = "arm64")' * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 4.06.0 -> ocaml-base-compiler = 4.01.0 | ocaml-system < 4.01.1~ | ocaml-variants < 4.01.1~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.04 -> ocaml-base-compiler = 4.01.0 | ocaml-system < 4.01.1~ | ocaml-variants < 4.01.1~ unmet availability conditions: 'arch != "arm64" & arch != "ppc64"' unmet availability conditions, e.g. 'sys-ocaml-version = "4.01.0"' unmet availability conditions, e.g. '!(os = "macos" & arch = "arm64")' * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 4.06.0 -> ocaml-base-compiler = 4.02.0 | ocaml-system < 4.02.1~ | ocaml-variants < 4.02.1~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.04 -> ocaml-base-compiler = 4.02.0 | ocaml-system < 4.02.1~ | ocaml-variants < 4.02.1~ unmet availability conditions: '!(os = "macos" & arch = "arm64") & arch != "ppc64"' unmet availability conditions, e.g. 'sys-ocaml-version = "4.02.0"' unmet availability conditions, e.g. '!(os = "macos" & arch = "arm64")' * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 4.06.0 -> ocaml-base-compiler = 4.02.1 | ocaml-system < 4.02.2~ | ocaml-variants < 4.02.2~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.04 -> ocaml-base-compiler = 4.02.1 | ocaml-system < 4.02.2~ | ocaml-variants < 4.02.2~ unmet availability conditions: '!(os = "macos" & arch = "arm64") & arch != "ppc64"' unmet availability conditions, e.g. 'sys-ocaml-version = "4.02.1"' unmet availability conditions, e.g. '!(os = "macos" & arch = "arm64")' * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 4.06.0 -> ocaml-base-compiler = 4.02.2 | ocaml-system < 4.02.3~ | ocaml-variants < 4.02.3~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.04 -> ocaml-base-compiler = 4.02.2 | ocaml-system < 4.02.3~ | ocaml-variants < 4.02.3~ unmet availability conditions: '!(os = "macos" & arch = "arm64") & arch != "ppc64"' unmet availability conditions, e.g. 'sys-ocaml-version = "4.02.2"' unmet availability conditions, e.g. '!(os = "macos" & arch = "arm64")' * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 4.06.0 -> ocaml-base-compiler = 4.02.3 | ocaml-system < 4.02.4~ | ocaml-variants < 4.02.4~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.04 -> ocaml-base-compiler = 4.02.3 | ocaml-system < 4.02.4~ | ocaml-variants < 4.02.4~ unmet availability conditions: '!(os = "macos" & arch = "arm64") & arch != "ppc64"' unmet availability conditions, e.g. 'sys-ocaml-version = "4.02.3"' unmet availability conditions, e.g. '!(os = "macos" & arch = "arm64")' * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 4.06.0 -> ocaml-base-compiler = 4.02.4 | ocaml-system < 4.02.5~ | ocaml-variants < 4.02.5~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.04 -> ocaml-base-compiler = 4.02.4 | ocaml-system < 4.02.5~ | ocaml-variants < 4.02.5~ no matching version unmet availability conditions, e.g. 'sys-ocaml-version = "4.02.3"' unmet availability conditions, e.g. '!(os = "macos" & arch = "arm64")' * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 4.06.0 -> ocaml-base-compiler = 4.03.0 | ocaml-system < 4.03.1~ | ocaml-variants < 4.03.1~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.04 -> ocaml-base-compiler = 4.03.0 | ocaml-system < 4.03.1~ | ocaml-variants < 4.03.1~ unmet availability conditions: '!(os = "macos" & arch = "arm64")' unmet availability conditions, e.g. 'sys-ocaml-version = "4.03.0"' unmet availability conditions, e.g. '!(os = "macos" & arch = "arm64")' * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 4.06.0 -> ocaml-base-compiler = 4.03.1 | ocaml-system < 4.03.2~ | ocaml-variants < 4.03.2~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.04 -> ocaml-base-compiler = 4.03.1 | ocaml-system < 4.03.2~ | ocaml-variants < 4.03.2~ no matching version unmet availability conditions, e.g. 'sys-ocaml-version = "4.03.0"' unmet availability conditions, e.g. '!(os = "macos" & arch = "arm64")' * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 4.06.0 -> ocaml-base-compiler = 4.04.0 | ocaml-system < 4.04.1~ | ocaml-variants < 4.04.1~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.06 -> ocaml-base-compiler = 4.04.0 | ocaml-system < 4.04.1~ | ocaml-variants < 4.04.1~ unmet availability conditions: '!(os = "macos" & arch = "arm64")' unmet availability conditions, e.g. 'sys-ocaml-version = "4.04.0"' unmet availability conditions, e.g. '!(os = "macos" & arch = "arm64")' * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 4.06.0 -> ocaml-base-compiler = 4.04.1 | ocaml-system < 4.04.2~ | ocaml-variants < 4.04.2~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.06 -> ocaml-base-compiler = 4.04.1 | ocaml-system < 4.04.2~ | ocaml-variants < 4.04.2~ unmet availability conditions: '!(os = "macos" & arch = "arm64")' unmet availability conditions, e.g. 'sys-ocaml-version = "4.04.1"' unmet availability conditions, e.g. '!(os = "macos" & arch = "arm64")' * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 4.06.0 -> ocaml-base-compiler = 4.04.2 | ocaml-system < 4.04.3~ | ocaml-variants < 4.04.3~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.06 -> ocaml-base-compiler = 4.04.2 | ocaml-system < 4.04.3~ | ocaml-variants < 4.04.3~ unmet availability conditions: '!(os = "macos" & arch = "arm64")' unmet availability conditions, e.g. 'sys-ocaml-version = "4.04.2"' unmet availability conditions, e.g. '!(os = "macos" & arch = "arm64")' * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 4.06.0 -> ocaml-base-compiler = 4.04.3 | ocaml-system < 4.04.4~ | ocaml-variants < 4.04.4~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.06 -> ocaml-base-compiler = 4.04.3 | ocaml-system < 4.04.4~ | ocaml-variants < 4.04.4~ no matching version unmet availability conditions, e.g. 'sys-ocaml-version = "4.04.2"' unmet availability conditions, e.g. '!(os = "macos" & arch = "arm64")' * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 4.06.0 -> ocaml-base-compiler = 4.05.0 | ocaml-system < 4.05.1~ | ocaml-variants < 4.05.1~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.06 -> ocaml-base-compiler = 4.05.0 | ocaml-system < 4.05.1~ | ocaml-variants < 4.05.1~ unmet availability conditions: '!(os = "macos" & arch = "arm64")' unmet availability conditions, e.g. 'sys-ocaml-version = "4.05.0"' unmet availability conditions, e.g. '!(os = "macos" & arch = "arm64")' * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 4.06.0 -> ocaml-base-compiler = 4.05.1 | ocaml-system < 4.05.2~ | ocaml-variants < 4.05.2~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.06 -> ocaml-base-compiler = 4.05.1 | ocaml-system < 4.05.2~ | ocaml-variants < 4.05.2~ no matching version unmet availability conditions, e.g. 'sys-ocaml-version = "4.05.0"' unmet availability conditions, e.g. '!(os = "macos" & arch = "arm64")' * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 5.0 -> ocaml-base-compiler = 4.06.0 | ocaml-system < 4.06.1~ | ocaml-variants < 4.06.1~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.08.0 -> ocaml-base-compiler = 4.06.0 | ocaml-system < 4.06.1~ | ocaml-variants < 4.06.1~ unmet availability conditions: '!(os = "macos" & arch = "arm64")' unmet availability conditions, e.g. 'sys-ocaml-version = "4.06.0"' unmet availability conditions, e.g. '!(os = "macos" & arch = "arm64")' * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 5.0 -> ocaml-base-compiler = 4.06.1 | ocaml-system < 4.06.2~ | ocaml-variants < 4.06.2~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.08.0 -> ocaml-base-compiler = 4.06.1 | ocaml-system < 4.06.2~ | ocaml-variants < 4.06.2~ unmet availability conditions: '!(os = "macos" & arch = "arm64")' unmet availability conditions, e.g. 'sys-ocaml-version = "4.06.1"' unmet availability conditions, e.g. '!(os = "macos" & arch = "arm64")' * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 5.0 -> ocaml-base-compiler = 4.06.2 | ocaml-system < 4.06.3~ | ocaml-variants < 4.06.3~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.08.0 -> ocaml-base-compiler = 4.06.2 | ocaml-system < 4.06.3~ | ocaml-variants < 4.06.3~ no matching version unmet availability conditions, e.g. 'sys-ocaml-version = "4.06.1"' unmet availability conditions, e.g. '!(os = "macos" & arch = "arm64")' * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 5.0 -> ocaml-base-compiler = 4.07.0 | ocaml-system < 4.07.1~ | ocaml-variants < 4.07.1~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.08.0 -> ocaml-base-compiler = 4.07.0 | ocaml-system < 4.07.1~ | ocaml-variants < 4.07.1~ unmet availability conditions: '!(os = "macos" & arch = "arm64")' unmet availability conditions, e.g. 'sys-ocaml-version = "4.07.0"' unmet availability conditions, e.g. '!(os = "macos" & arch = "arm64")' * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 5.0 -> ocaml-base-compiler = 4.07.1 | ocaml-system < 4.07.2~ | ocaml-variants < 4.07.2~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.08.0 -> ocaml-base-compiler = 4.07.1 | ocaml-system < 4.07.2~ | ocaml-variants < 4.07.2~ unmet availability conditions: '!(os = "macos" & arch = "arm64")' unmet availability conditions, e.g. 'sys-ocaml-version = "4.07.1"' unmet availability conditions, e.g. '!(os = "macos" & arch = "arm64")' * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 5.0 -> ocaml-base-compiler = 4.07.2 | ocaml-system < 4.07.3~ | ocaml-variants < 4.07.3~ + - dune-release -> odoc -> doc-ock -> ocaml < 4.08.0 -> ocaml-base-compiler = 4.07.2 | ocaml-system < 4.07.3~ | ocaml-variants < 4.07.3~ no matching version unmet availability conditions, e.g. 'sys-ocaml-version = "4.07.1"' unmet availability conditions, e.g. '!(os = "macos" & arch = "arm64")' - * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 5.0 -> ocaml-base-compiler = 4.08.1 | ocaml-system >= 4.08.1 | ocaml-variants < 4.08.2~ - unmet availability conditions: '!(os = "macos" & arch = "arm64")' - unmet availability conditions, e.g. 'sys-ocaml-version = "4.08.1"' - unmet availability conditions, e.g. '!(os = "macos" & arch = "arm64")' - * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 5.0 -> ocaml-base-compiler = 4.08.2 | ocaml-system >= 4.08.2 | ocaml-variants < 4.08.3~ - no matching version - unmet availability conditions, e.g. 'sys-ocaml-version = "4.14.0"' - unmet availability conditions, e.g. '!(os = "macos" & arch = "arm64")' - * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 5.0 -> ocaml-base-compiler = 4.09.0 | ocaml-system >= 4.09.0 | ocaml-variants < 4.09.1~ - unmet availability conditions: '!(os = "macos" & arch = "arm64")' - unmet availability conditions, e.g. 'sys-ocaml-version = "4.09.0"' - unmet availability conditions, e.g. '!(os = "macos" & arch = "arm64")' - * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 5.0 -> ocaml-base-compiler = 4.09.1 | ocaml-system >= 4.09.1 | ocaml-variants < 4.09.2~ - unmet availability conditions: '!(os = "macos" & arch = "arm64")' - unmet availability conditions, e.g. 'sys-ocaml-version = "4.09.1"' - unmet availability conditions, e.g. '!(os = "macos" & arch = "arm64")' - * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 5.0 -> ocaml-base-compiler = 4.09.2 | ocaml-system >= 4.09.2 | ocaml-variants < 4.09.3~ - no matching version - unmet availability conditions, e.g. 'sys-ocaml-version = "4.14.0"' - unmet availability conditions, e.g. '!(os = "macos" & arch = "arm64")' - * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 5.0 -> ocaml-base-compiler = 4.10.0 | ocaml-system >= 4.10.0 | ocaml-variants < 4.10.1~ - unmet availability conditions: '!(os = "macos" & arch = "arm64")' - unmet availability conditions, e.g. 'sys-ocaml-version = "4.10.0"' - unmet availability conditions, e.g. '!(os = "macos" & arch = "arm64")' - * Missing dependency: - - dune-release -> fmt < 0.8.7 -> ocaml < 5.0 -> ocaml-base-compiler = 4.10.1 | ocaml-system >= 4.10.1 | ocaml-variants < 4.10.2~ - unmet availability conditions: '!(os = "macos" & arch = "arm64")' - unmet availability conditions, e.g. 'sys-ocaml-version = "4.10.1"' - unmet availability conditions, e.g. '!(os = "macos" & arch = "arm64")' No solution found, exiting # Return code 20 #