From fa37ce87fea115dfab533c765fdb90603f528c12 Mon Sep 17 00:00:00 2001 From: Raja Boujbel Date: Thu, 4 Nov 2021 18:13:23 +0100 Subject: [PATCH 01/14] reftest: open with meld only changed tests --- Makefile | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/Makefile b/Makefile index 4eb44941a96..9faf156e193 100644 --- a/Makefile +++ b/Makefile @@ -223,7 +223,11 @@ reftest-%: $(DUNE_DEP) src/client/no-git-version $(DUNE) build $(DUNE_ARGS) $(DUNE_PROFILE_ARG) --root . @reftest-$* --force reftests-meld: - meld `for t in tests/reftests/*.test; do echo --diff $$t _build/default/$${t%.test}.out; done` + meld `for t in tests/reftests/*.test; do \ + out=_build/default/$${t%.test}.out; \ + if test -f $$out && ! diff -q $$t $$out 2> /dev/null > /dev/null; then \ + echo --diff $$t $$out; \ + fi; done` .PHONY: doc doc: all From 8a07275a7790edac3b06e0da413e58b700e7f29d Mon Sep 17 00:00:00 2001 From: Raja Boujbel Date: Thu, 28 Oct 2021 16:21:39 +0200 Subject: [PATCH 02/14] reftests: add grep -v --- tests/reftests/run.ml | 27 ++++++++++++++++++--------- 1 file changed, 18 insertions(+), 9 deletions(-) diff --git a/tests/reftests/run.ml b/tests/reftests/run.ml index f4e091b9f37..ac1e59c8563 100644 --- a/tests/reftests/run.ml +++ b/tests/reftests/run.ml @@ -35,6 +35,7 @@ * rewrites: `| 'REGEXP' -> 'STR'` (can be repeated; set `STR` to `\c` to clear the line) * `| grep REGEXP` + * `| grep -v REGEXP` * `| unordered` compares lines without considering their ordering * variables from command outputs: `cmd args >$ VAR` * `### : comment` @@ -127,6 +128,11 @@ let rec waitpid pid = exception Command_failure of int * string * string +type filt_sort = + | Sed of string + | Grep + | GrepV + let str_replace_path ?(escape=false) whichway filters s = let escape = if escape then Re.(replace_string (compile @@ char '\\') ~by:"\\\\") @@ -137,12 +143,13 @@ let str_replace_path ?(escape=false) whichway filters s = seq [re; group (rep (diff any space))] ) in match by with - | Some by -> + | Sed by -> Re.replace (Re.compile re_path) s ~f:(fun g -> escape (by ^ whichway (Re.Group.get g 1))) - | None -> - if Re.execp (Re.compile re) s then s else "\\c") + | Grep | GrepV -> + let way = if by = Grep then fun x -> x else not in + if way @@ Re.execp (Re.compile re) s then s else "\\c") s filters let command @@ -253,7 +260,7 @@ type command = | Run of { env: (string * string) list; cmd: string; args: string list; (* still escaped *) - filter: (Re.t * string option) list; + filter: (Re.t * filt_sort) list; output: string option; unordered: bool; } | Export of (string * string) list @@ -356,9 +363,11 @@ module Parse = struct | "|" :: _ as rewr -> let rec get_rewr (unordered, acc) = function | "|" :: re :: "->" :: str :: r -> - get_rewr (unordered, (Posix.re (get_str re), Some (get_str str)) :: acc) r + get_rewr (unordered, (Posix.re (get_str re), Sed (get_str str)) :: acc) r + | "|" :: "grep" :: "-v" :: re :: r -> + get_rewr (unordered, (Posix.re (get_str re), GrepV) :: acc) r | "|" :: "grep" :: re :: r -> - get_rewr (unordered, (Posix.re (get_str re), None) :: acc) r + get_rewr (unordered, (Posix.re (get_str re), Grep) :: acc) r | "|" :: "unordered" :: r -> get_rewr (true, acc) r | ">$" :: output :: [] -> @@ -396,14 +405,14 @@ let common_filters dir = let tmpdir = Filename.get_temp_dir_name () in Re.[ alt [str dir; str (OpamSystem.back_to_forward dir)], - Some "${BASEDIR}"; + Sed "${BASEDIR}"; seq [opt (str "/private"); alt [str tmpdir; str (OpamSystem.back_to_forward tmpdir)]; rep (set "/\\"); str "opam-"; rep1 (alt [alnum; char '-'])], - Some "${OPAMTMP}"; + Sed "${OPAMTMP}"; ] let run_cmd ~opam ~dir ?(vars=[]) ?(filter=[]) ?(silent=false) cmd args = @@ -418,7 +427,7 @@ let run_cmd ~opam ~dir ?(vars=[]) ?(filter=[]) ?(silent=false) cmd args = List.rev_map (fun (v, x) -> Re.(alt [seq [str "${"; str v; str "}"]; seq [char '$'; str v; eow]];), - Some x) + Sed x) env_vars in let cmd = if cmd = "opam" then opam else cmd in From 8290e811292e5907af84a9ce8aaa3ce77dd27a67 Mon Sep 17 00:00:00 2001 From: Raja Boujbel Date: Thu, 30 Sep 2021 15:27:01 +0200 Subject: [PATCH 03/14] reftests: add BASEDIR to environment --- tests/reftests/run.ml | 1 + 1 file changed, 1 insertion(+) diff --git a/tests/reftests/run.ml b/tests/reftests/run.ml index ac1e59c8563..bf63585807d 100644 --- a/tests/reftests/run.ml +++ b/tests/reftests/run.ml @@ -421,6 +421,7 @@ let run_cmd ~opam ~dir ?(vars=[]) ?(filter=[]) ?(silent=false) cmd args = let env_vars = [ "OPAM", opam; "OPAMROOT", opamroot; + "BASEDIR", dir; ] @ vars in let var_filters = From c8f03120fcace0e6c9e10d8614805de2f8834eb4 Mon Sep 17 00:00:00 2001 From: Raja Boujbel Date: Thu, 28 Oct 2021 16:21:59 +0200 Subject: [PATCH 04/14] reftests: replace opam bin path --- tests/reftests/run.ml | 12 ++++++++---- 1 file changed, 8 insertions(+), 4 deletions(-) diff --git a/tests/reftests/run.ml b/tests/reftests/run.ml index bf63585807d..9da07d9fa3e 100644 --- a/tests/reftests/run.ml +++ b/tests/reftests/run.ml @@ -401,9 +401,10 @@ end let parse_command = Parse.command -let common_filters dir = +let common_filters ?opam dir = let tmpdir = Filename.get_temp_dir_name () in - Re.[ + let open Re in + [ alt [str dir; str (OpamSystem.back_to_forward dir)], Sed "${BASEDIR}"; seq [opt (str "/private"); @@ -413,10 +414,13 @@ let common_filters dir = str "opam-"; rep1 (alt [alnum; char '-'])], Sed "${OPAMTMP}"; - ] + ] @ + (match opam with + | None -> [] + | Some opam -> [ str opam, Sed "${OPAMBIN}" ]) let run_cmd ~opam ~dir ?(vars=[]) ?(filter=[]) ?(silent=false) cmd args = - let filter = common_filters dir @ filter in + let filter = common_filters ~opam dir @ filter in let opamroot = Filename.concat dir "OPAM" in let env_vars = [ "OPAM", opam; From e9a819c026940bd8394f7b82142c0e1f0a444f73 Mon Sep 17 00:00:00 2001 From: Raja Boujbel Date: Mon, 15 Nov 2021 13:43:18 +0100 Subject: [PATCH 05/14] reftests: don't take the first group but latest on replacement --- tests/reftests/run.ml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/reftests/run.ml b/tests/reftests/run.ml index 9da07d9fa3e..3ba61b34261 100644 --- a/tests/reftests/run.ml +++ b/tests/reftests/run.ml @@ -146,7 +146,7 @@ let str_replace_path ?(escape=false) whichway filters s = | Sed by -> Re.replace (Re.compile re_path) s ~f:(fun g -> - escape (by ^ whichway (Re.Group.get g 1))) + escape (by ^ whichway (Re.Group.(get g (nb_groups g - 1))))) | Grep | GrepV -> let way = if by = Grep then fun x -> x else not in if way @@ Re.execp (Re.compile re) s then s else "\\c") From 1ea50352223f9cbd7bf5f51302b2fe80b86ed0d5 Mon Sep 17 00:00:00 2001 From: Raja Boujbel Date: Mon, 15 Nov 2021 16:00:38 +0100 Subject: [PATCH 06/14] reftests: apply grep & sed in the good order --- tests/reftests/run.ml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/reftests/run.ml b/tests/reftests/run.ml index 3ba61b34261..35f8b5061a8 100644 --- a/tests/reftests/run.ml +++ b/tests/reftests/run.ml @@ -381,7 +381,7 @@ module Parse = struct unordered, List.rev acc, None in let unordered, rewr, out = get_rewr (false, []) rewr in - List.rev acc, unordered, rewr, out + List.rev acc, unordered, List.rev rewr, out | arg :: r -> get_args_rewr (arg :: acc) r in let args, unordered, rewr, output = get_args_rewr [] args in From fa48aca2056e265cdc83734d4105ff8c9b38e773 Mon Sep 17 00:00:00 2001 From: Raja Boujbel Date: Mon, 15 Nov 2021 16:01:27 +0100 Subject: [PATCH 07/14] reftests: avoid confusion between opamtmp & basedir (hexa regexp) --- tests/reftests/run.ml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/reftests/run.ml b/tests/reftests/run.ml index 35f8b5061a8..6d9506f17ed 100644 --- a/tests/reftests/run.ml +++ b/tests/reftests/run.ml @@ -412,7 +412,7 @@ let common_filters ?opam dir = str (OpamSystem.back_to_forward tmpdir)]; rep (set "/\\"); str "opam-"; - rep1 (alt [alnum; char '-'])], + rep1 (alt [xdigit; char '-'])], Sed "${OPAMTMP}"; ] @ (match opam with From c43a038db8ea821f5978127db83fee949d1c8d33 Mon Sep 17 00:00:00 2001 From: Raja Boujbel Date: Mon, 22 Nov 2021 13:26:39 +0100 Subject: [PATCH 08/14] reftests: workaround to have several replacement on a single line --- tests/reftests/run.ml | 13 ++++++++++--- 1 file changed, 10 insertions(+), 3 deletions(-) diff --git a/tests/reftests/run.ml b/tests/reftests/run.ml index 6d9506f17ed..19a257bc8d0 100644 --- a/tests/reftests/run.ml +++ b/tests/reftests/run.ml @@ -144,9 +144,16 @@ let str_replace_path ?(escape=false) whichway filters s = ) in match by with | Sed by -> - Re.replace (Re.compile re_path) s - ~f:(fun g -> - escape (by ^ whichway (Re.Group.(get g (nb_groups g - 1))))) + (* workaround to have several replacement, and handle paths *) + let rec loop prev = + let replaced = + Re.replace (Re.compile re_path) prev + ~f:(fun g -> + escape (by ^ whichway (Re.Group.(get g (nb_groups g - 1))))) + in + if prev = replaced then prev else loop replaced + in + loop s | Grep | GrepV -> let way = if by = Grep then fun x -> x else not in if way @@ Re.execp (Re.compile re) s then s else "\\c") From e687c9cb38f376f6cc322dc42c9d0d460b8c6f1e Mon Sep 17 00:00:00 2001 From: Raja Boujbel Date: Mon, 22 Nov 2021 19:34:49 +0100 Subject: [PATCH 09/14] reftest: handle replacement on an opam-cat, and substitution in regexps --- tests/reftests/run.ml | 59 ++++++++++++++++++++++++++++--------------- 1 file changed, 38 insertions(+), 21 deletions(-) diff --git a/tests/reftests/run.ml b/tests/reftests/run.ml index 19a257bc8d0..d13f4765976 100644 --- a/tests/reftests/run.ml +++ b/tests/reftests/run.ml @@ -159,6 +159,12 @@ let str_replace_path ?(escape=false) whichway filters s = if way @@ Re.execp (Re.compile re) s then s else "\\c") s filters +let filters_of_var = + List.rev_map (fun (v, x) -> + Re.(alt [seq [str "${"; str v; str "}"]; + seq [char '$'; str v; eow]];), + Sed x) + let command ?(allowed_codes = [0]) ?(vars=[]) ?(silent=false) ?(filter=[]) cmd args = @@ -263,7 +269,8 @@ let rec with_temp_dir f = type command = | File_contents of string - | Cat of string list + | Cat of { files: string list; + filter: (Re.t * filt_sort) list; } | Run of { env: (string * string) list; cmd: string; args: string list; (* still escaped *) @@ -323,7 +330,7 @@ module Parse = struct char '>' ] - let command str = + let command ?(vars=[]) str = if str.[0] = '<' && str.[String.length str - 1] = '>' then let f = try @@ -344,10 +351,6 @@ module Parse = struct else if str.[0] = ':' || str.[0] = '#' then Comment str else - match OpamStd.String.cut_at str ' ' with - | Some ("opam-cat", files) -> - Cat (OpamStd.String.split files ' ') - | _ -> let varbinds, pos = let gr = exec (compile @@ rep re_varbind) str in List.map (fun gr -> Group.get gr 1, get_str (Group.get gr 2)) @@ -365,16 +368,26 @@ module Parse = struct let grs = all ~pos (compile re_str_atom) str in List.map (fun gr -> Group.get gr 0) grs in + let get_str s = + str_replace_path OpamSystem.back_to_forward + (filters_of_var vars) + (get_str s) + in + let posix_re re = + try Posix.re (get_str re) + with Posix.Parse_error -> + failwith (Printf.sprintf "Parse error: %s" re) + in let rec get_args_rewr acc = function | [] -> List.rev acc, false, [], None | "|" :: _ as rewr -> let rec get_rewr (unordered, acc) = function | "|" :: re :: "->" :: str :: r -> - get_rewr (unordered, (Posix.re (get_str re), Sed (get_str str)) :: acc) r + get_rewr (unordered, (posix_re re, Sed (get_str str)) :: acc) r | "|" :: "grep" :: "-v" :: re :: r -> - get_rewr (unordered, (Posix.re (get_str re), GrepV) :: acc) r + get_rewr (unordered, (posix_re re, GrepV) :: acc) r | "|" :: "grep" :: re :: r -> - get_rewr (unordered, (Posix.re (get_str re), Grep) :: acc) r + get_rewr (unordered, (posix_re re, Grep) :: acc) r | "|" :: "unordered" :: r -> get_rewr (true, acc) r | ">$" :: output :: [] -> @@ -393,6 +406,8 @@ module Parse = struct in let args, unordered, rewr, output = get_args_rewr [] args in match cmd with + | Some "opam-cat" -> + Cat { files = args; filter = rewr; } | Some cmd -> Run { env = varbinds; @@ -435,13 +450,7 @@ let run_cmd ~opam ~dir ?(vars=[]) ?(filter=[]) ?(silent=false) cmd args = "BASEDIR", dir; ] @ vars in - let var_filters = - List.rev_map (fun (v, x) -> - Re.(alt [seq [str "${"; str v; str "}"]; - seq [char '$'; str v; eow]];), - Sed x) - env_vars - in + let var_filters = filters_of_var env_vars in let cmd = if cmd = "opam" then opam else cmd in let args = List.map (fun a -> @@ -494,7 +503,7 @@ let run_test ?(vars=[]) ~opam t = List.fold_left (fun vars (cmd, out) -> print_string cmd_prompt; print_endline cmd; - match parse_command cmd with + match parse_command ~vars cmd with | Comment _ -> vars | File_contents path -> let contents = String.concat "\n" out ^ "\n" in @@ -505,7 +514,7 @@ let run_test ?(vars=[]) ~opam t = List.fold_left (fun vars (v, r) -> (v, r) :: List.filter (fun (w, _) -> v <> w) vars) vars bindings - | Cat files -> + | Cat { files; filter } -> let print_opamfile header file = let content = let open OpamParserTypes.FullPos in @@ -513,8 +522,16 @@ let run_test ?(vars=[]) ~opam t = let rec mangle item = match item.pelem with | Section s -> - {item with pelem = Section {s with section_name = OpamStd.Option.map (fun v -> {v with pelem = mangle_string v.pelem}) s.section_name; - section_items = {s.section_items with pelem = List.map mangle s.section_items.pelem}}} + {item with + pelem = + Section {s with + section_name = + OpamStd.Option.map (fun v -> + {v with pelem = mangle_string v.pelem}) + s.section_name; + section_items = + {s.section_items with + pelem = List.map mangle s.section_items.pelem}}} | Variable(name, value) -> {item with pelem = Variable(name, mangle_value value)} and mangle_value item = @@ -551,7 +568,7 @@ let run_test ?(vars=[]) ~opam t = let str = Printf.sprintf "%s%s" str content in let str = str_replace_path OpamSystem.back_to_forward - (common_filters dir) str + (filter @ common_filters dir) str in print_string str in From 61cca36e723165f69dcb4129070b2f5447999583 Mon Sep 17 00:00:00 2001 From: Raja Boujbel Date: Wed, 20 Oct 2021 19:44:06 +0200 Subject: [PATCH 10/14] reftest: update cli versioning with norepo --- tests/reftests/cli-versioning.test | 43 +++++++++++------------------- 1 file changed, 15 insertions(+), 28 deletions(-) diff --git a/tests/reftests/cli-versioning.test b/tests/reftests/cli-versioning.test index 21894a4451b..812f1fd40ce 100644 --- a/tests/reftests/cli-versioning.test +++ b/tests/reftests/cli-versioning.test @@ -90,64 +90,51 @@ opam: lock was added in version 2.1 of the opam CLI, but version 2.0 has been re ### # Check for build test env ### # Note: you must have an installed opam with cli version enabled to pass these tests ### OPAMSHOW=0 -### +### opam-version: "2.0" build: ["sh" "-c" "env | grep -qFx 'OPAMCLI=2.0'"] install: ["sh" "-c" "env | grep -qFx 'OPAMCLI=2.0'"] remove: ["sh" "-c" "env | grep -qFx 'OPAMCLI=2.0'"] -### +### opam-version: "2.0" build-env: [OPAMCLI = "2.1"] build: ["sh" "-c" "env | grep -qFx 'OPAMCLI=2.1'"] install: ["sh" "-c" "env | grep -qFx 'OPAMCLI=2.1'"] remove: ["sh" "-c" "env | grep -qFx 'OPAMCLI=2.1'"] -### opam pin opams -yn -This will pin the following packages: env-2-0, env-2-1. Continue? [Y/n] y -Package env-2-0 does not exist, create as a NEW package? [Y/n] y -env-2-0 is now pinned to file://${BASEDIR}/opams (version ~dev) -Package env-2-1 does not exist, create as a NEW package? [Y/n] y -env-2-1 is now pinned to file://${BASEDIR}/opams (version ~dev) +### opam update + +<><> Updating package repositories ><><><><><><><><><><><><><><><><><><><><><><> +[default] synchronised from file://${BASEDIR}/REPO +Now run 'opam upgrade' to apply any package updates. ### opam switch set-invariant --formula "[]" The switch invariant was set to [] ### opam install env-2-0 - -<><> Synchronising pinned packages ><><><><><><><><><><><><><><><><><><><><><><> -[env-2-0.~dev] synchronised (no changes) - The following actions will be performed: - - install env-2-0 ~dev* + - install env-2-0 1 <><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><> --> retrieved env-2-0.~dev (file://${BASEDIR}/opams) --> installed env-2-0.~dev +-> installed env-2-0.1 Done. ### opam install env-2-1 - -<><> Synchronising pinned packages ><><><><><><><><><><><><><><><><><><><><><><> -[env-2-1.~dev] synchronised (no changes) - The following actions will be performed: - - install env-2-1 ~dev* + - install env-2-1 1 <><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><> --> retrieved env-2-1.~dev (file://${BASEDIR}/opams) --> installed env-2-1.~dev +-> installed env-2-1.1 Done. ### opam remove env-2-0 The following actions will be performed: - - remove env-2-0 ~dev* + - remove env-2-0 1 <><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><> --> retrieved env-2-0.~dev (no changes) --> removed env-2-0.~dev +-> removed env-2-0.1 Done. ### opam remove env-2-1 The following actions will be performed: - - remove env-2-1 ~dev* + - remove env-2-1 1 <><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><> --> retrieved env-2-1.~dev (no changes) --> removed env-2-1.~dev +-> removed env-2-1.1 Done. ### # Environement variables cli versioning ### OPAMBUILDDOC=1 opam var share From 5dd364126a393e8b47548fd97af4c79a791959a9 Mon Sep 17 00:00:00 2001 From: Raja Boujbel Date: Mon, 15 Nov 2021 16:16:02 +0100 Subject: [PATCH 11/14] reftests: update some tests --- tests/reftests/env.test | 10 +++++----- tests/reftests/legacy-git.test | 2 +- tests/reftests/legacy-local.test | 2 +- 3 files changed, 7 insertions(+), 7 deletions(-) diff --git a/tests/reftests/env.test b/tests/reftests/env.test index e7289640753..98e235992c8 100644 --- a/tests/reftests/env.test +++ b/tests/reftests/env.test @@ -17,13 +17,13 @@ Switch invariant: ["nv"] <><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><> -> installed nv.1 Done. -### opam env | grep "NV_VARS" | '[:;]' -> '-' | '[:;]' -> '-' | '[:;]' -> '-' -NV_VARS='${BASEDIR}/OPAM/setenv/doc/nv-${OPAMTMP}/OPAM/setenv/share/nv'- export NV_VARS- -### opam exec -- opam env --revert | grep "NV_VARS" | '[:;]' -> '-' | '[:;]' -> '-' | '[:;]' -> '-' +### opam env | grep "NV_VARS" | '[:;]' -> '-' +NV_VARS='${BASEDIR}/OPAM/setenv/doc/nv-${BASEDIR}/OPAM/setenv/share/nv'- export NV_VARS- +### opam exec -- opam env --revert | grep "NV_VARS" | '[:;]' -> '-' NV_VARS=''- export NV_VARS- ### NV_VARS=/another/path -### opam env | grep "NV_VARS" | '[:;]' -> '-' | '[:;]' -> '-' | '[:;]' -> '-' -NV_VARS='${BASEDIR}/OPAM/setenv/doc/nv-${OPAMTMP}/OPAM/setenv/share/nv-/another/path'- export NV_VARS- +### opam env | grep "NV_VARS" | '[:;]' -> '-' +NV_VARS='${BASEDIR}/OPAM/setenv/doc/nv-${BASEDIR}/OPAM/setenv/share/nv-/another/path'- export NV_VARS- ### opam exec -- opam env --revert | grep "NV_VARS" | '[:;]' -> '-' NV_VARS='/another/path'- export NV_VARS- ### : package variable available at install stage : diff --git a/tests/reftests/legacy-git.test b/tests/reftests/legacy-git.test index 0291a5d7ca0..04a429732db 100644 --- a/tests/reftests/legacy-git.test +++ b/tests/reftests/legacy-git.test @@ -726,7 +726,7 @@ Switch invariant: ["ocaml" {= "system"}] <><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><> -> installed ocaml.system Done. -### opam exec -- ocamlc -config | 'ext_lib: .' -> '#' | '^[^#].*' -> '\c' | '^#' -> '' >$ LIB_EXT +### opam exec -- ocamlc -config | '^#' -> '' | '^[^#].*' -> '\c' | 'ext_lib: .' -> '#' >$ LIB_EXT ### opam var ext_lib=$LIB_EXT --switch system | '.*' -> '\c' ### : INSTALL-REMOVE : ### opam list -is --columns=package diff --git a/tests/reftests/legacy-local.test b/tests/reftests/legacy-local.test index 16196637afd..b2566a0ab3a 100644 --- a/tests/reftests/legacy-local.test +++ b/tests/reftests/legacy-local.test @@ -665,7 +665,7 @@ Switch invariant: ["ocaml" {= "system"}] <><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><> -> installed ocaml.system Done. -### opam exec -- ocamlc -config | 'ext_lib: .' -> '#' | '^[^#].*' -> '\c' | '^#' -> '' >$ LIB_EXT +### opam exec -- ocamlc -config | '^#' -> '' | '^[^#].*' -> '\c' | 'ext_lib: .' -> '#' >$ LIB_EXT ### opam var ext_lib=$LIB_EXT --switch system | .* -> '\c' ### : INSTALL-REMOVE : ### opam list -is --columns=package From 36ac3dabbe19346749e0f0ec0103612fea9e1840 Mon Sep 17 00:00:00 2001 From: Raja Boujbel Date: Mon, 22 Nov 2021 19:40:16 +0100 Subject: [PATCH 12/14] stateConfig: fix newer opam root error message with root version instead of binary --- src/state/opamStateConfig.ml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/state/opamStateConfig.ml b/src/state/opamStateConfig.ml index 765652764df..c03f671bb2f 100644 --- a/src/state/opamStateConfig.ml +++ b/src/state/opamStateConfig.ml @@ -214,7 +214,7 @@ let load_if_possible_raw ?lock_kind root version (read,read_wo_err) f = opam (%s > %s), aborting." (OpamFilename.Dir.to_string root) (OpamStd.Option.to_string OpamVersion.to_string version) - OpamVersion.(to_string current_nopatch) + OpamVersion.(to_string OpamFile.Config.root_version) | Some true -> read_wo_err f | Some false -> read f From c41b8daa2a5842addbd57c96aa2b93367bc591da Mon Sep 17 00:00:00 2001 From: Raja Boujbel Date: Mon, 22 Nov 2021 19:40:41 +0100 Subject: [PATCH 13/14] reftests: opam root untie from current version --- tests/reftests/opamroot-versions.test | 427 +++++++++++++------------- 1 file changed, 214 insertions(+), 213 deletions(-) diff --git a/tests/reftests/opamroot-versions.test b/tests/reftests/opamroot-versions.test index 02b7964ab42..b4de88aae0b 100644 --- a/tests/reftests/opamroot-versions.test +++ b/tests/reftests/opamroot-versions.test @@ -1,7 +1,9 @@ N0REP0 +### opam option opam-root-version --global | '"' -> '' >$ OPAMROOTVERSION ### OPAMYES=1 OPAMDEBUG=-1 OPAMSTRICT=0 OPAMDEBUGSECTIONS="FMT_UPG FORMAT GSTATE RSTATE STATE" ### : setup ### +let current = Sys.argv.(1) let opam_version = Printf.sprintf "opam-version: %S" let root_version = Printf.sprintf "opam-root-version: %S" let switches = {| @@ -17,10 +19,10 @@ let _ = List.map (fun v -> [ "config."^v, [ opam_v ; root_version v ]; "config-w-swfoo."^v, [ opam_v; root_version v; switches ]; - ]) ["2.0"; "2.1"; "2.2"] + ]) ["2.0"; current; "4.8"] |> List.flatten) - @ (let opam_v = opam_version "2.1" in - let v = "2.3" in [ + @ (let opam_v = opam_version current in + let v = "9.6" in [ "config."^v, [ opam_v; root_version v ]; "config-w-swfoo."^v, [ opam_v; root_version v; switches ]; ]) @@ -32,8 +34,8 @@ let _ = in let errs = List.map (fun (n,c) -> n^".err" , c@[neant]) files - @ (let v = "2.1" in - let opam_v = opam_version "2.1" in [ + @ (let v = current in + let opam_v = opam_version current in [ "config."^v^".wrong", [ opam_v; root_version v ]; "switch-config.wrong", [ opam_v; switch_config ]; ]) @@ -43,7 +45,7 @@ let _ = List.iter (fun l -> output_string fd (l^"\n")) content; close_out fd) (files @ errs) -### ocaml generate.ml +### ocaml generate.ml $OPAMROOTVERSION ### opam-version: "2.0" ### mkdir root-config/packages @@ -51,7 +53,7 @@ opam-version: "2.0" ### :I: Current opam root : ### : : ### :I:1:a: Bad config file -### cp config.2.1.err $OPAMROOT/config +### cp config.$OPAMROOTVERSION.err $OPAMROOT/config ### # ro global state ### opam switch [WARNING] Errors in ${BASEDIR}/OPAM/config, some fields have been ignored: @@ -65,7 +67,7 @@ GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM # switch compiler description ### :I:1:b: Good config file -### cp config.2.1 $OPAMROOT/config +### cp config.$OPAMROOTVERSION $OPAMROOT/config ### # ro global state ### opam switch GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM @@ -161,7 +163,7 @@ STATE Switch state loaded in 0.000s [ERROR] No package named bar found. # Return code 5 # ### :I:1:a: Bad config file -### cp config-w-swfoo.2.1.err $OPAMROOT/config +### cp config-w-swfoo.$OPAMROOTVERSION.err $OPAMROOT/config ### # rw global state ### opam switch remove foo [WARNING] Errors in ${BASEDIR}/OPAM/config, some fields have been ignored: @@ -176,7 +178,7 @@ GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM Switch foo and all its packages will be wiped. Are you sure? [Y/n] y ### :I:1:b: Good config file ### opam switch create foo --empty --debug-level=0 -### cp config-w-swfoo.2.1 $OPAMROOT/config +### cp config-w-swfoo.$OPAMROOTVERSION $OPAMROOT/config ### # rw global state ### opam switch remove foo GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM @@ -185,7 +187,7 @@ Switch foo and all its packages will be wiped. Are you sure? [Y/n] y ### :II: Current opam root & newer opam file version : ### : : ### :II:1: config with newer opam version file & no update of root version -### cp config.2.1.wrong $OPAMROOT/config +### cp config.$OPAMROOTVERSION.wrong $OPAMROOT/config ### # ro global state ### opam switch GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM @@ -207,7 +209,7 @@ In ${BASEDIR}/OPAM/config: unsupported or missing file format version; should be 2.0 or older # Return code 99 # ### :II:2: switch-config with newer opam version file & no update of root version -### cp config.2.1 $OPAMROOT/config +### cp config.$OPAMROOTVERSION $OPAMROOT/config ### opam switch create foo --empty --debug-level=0 ### cp switch-config.wrong $OPAMROOT/foo/.opam-switch/switch-config ### # ro global state @@ -224,138 +226,138 @@ Fatal error: In ${BASEDIR}/OPAM/foo/.opam-switch/switch-config: unsupported or missing file format version; should be 2.0 or older # Return code 99 # -### : : -### : Newer opam root : -### : : +### : : +### : III:Newer opam root : +### : : ### :III:1:a: Bad config file -### cp config.2.2.err $OPAMROOT/config +### cp config.4.8.err $OPAMROOT/config ### # ro global state -### opam switch +### opam switch | "(${OPAMROOTVERSION})" -> "current" FORMAT File errors in ${BASEDIR}/OPAM/config, ignored fields: At ${BASEDIR}/OPAM/config:3:0-3:8:: Invalid field neant GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM FORMAT File errors in ${BASEDIR}/OPAM/config, ignored fields: At ${BASEDIR}/OPAM/config:3:0-3:8:: Invalid field neant -GSTATE root version (2.2) is greater than running binary's (2.1); load with best-effort (read-only) +GSTATE root version (4.8) is greater than running binary's (current); load with best-effort (read-only) # switch compiler description ### :III:1:b: Good config file -### cp config.2.2 $OPAMROOT/config +### cp config.4.8 $OPAMROOT/config ### # ro global state -### opam switch +### opam switch | "(${OPAMROOTVERSION})" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -GSTATE root version (2.2) is greater than running binary's (2.1); load with best-effort (read-only) +GSTATE root version (4.8) is greater than running binary's (current); load with best-effort (read-only) # switch compiler description ### :III:2:a: Bad repo config file : ### cp repos-config.err $OPAMROOT/repo/repos-config ### # ro global state, ro repo state -### opam list --no-switch +### opam list --no-switch | "(${OPAMROOTVERSION})" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -GSTATE root version (2.2) is greater than running binary's (2.1); load with best-effort (read-only) +GSTATE root version (4.8) is greater than running binary's (current); load with best-effort (read-only) RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM FORMAT File errors in ${BASEDIR}/OPAM/repo/repos-config, ignored fields: At ${BASEDIR}/OPAM/repo/repos-config:2:0-2:8:: Invalid field neant -RSTATE root version (2.2) is greater than running binary's (2.1); load with best-effort (read-only) +RSTATE root version (4.8) is greater than running binary's (current); load with best-effort (read-only) RSTATE Cache found # No matches found ### # ro global state, rw repo state -### opam repo add root-config ./root-config --set-default +### opam repo add root-config ./root-config --set-default | "(${OPAMROOTVERSION})" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -GSTATE root version (2.2) is greater than running binary's (2.1); load with best-effort (read-only) +GSTATE root version (4.8) is greater than running binary's (current); load with best-effort (read-only) RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM -[ERROR] Refusing write access to ${BASEDIR}/OPAM, which is more recent than this version of opam (2.2 > 2.2), aborting. +[ERROR] Refusing write access to ${BASEDIR}/OPAM, which is more recent than this version of opam (4.8 > current), aborting. # Return code 15 # ### :III:2:b: Good repo config file : ### cp repos-config $OPAMROOT/repo/repos-config ### # ro global state, ro repo state -### opam list --no-switch +### opam list --no-switch | "(${OPAMROOTVERSION})" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -GSTATE root version (2.2) is greater than running binary's (2.1); load with best-effort (read-only) +GSTATE root version (4.8) is greater than running binary's (current); load with best-effort (read-only) RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM -RSTATE root version (2.2) is greater than running binary's (2.1); load with best-effort (read-only) +RSTATE root version (4.8) is greater than running binary's (current); load with best-effort (read-only) RSTATE Cache found # No matches found ### # ro global state, rw repo state -### opam repo add root-config ./root-config --set-default +### opam repo add root-config ./root-config --set-default | "(${OPAMROOTVERSION})" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -GSTATE root version (2.2) is greater than running binary's (2.1); load with best-effort (read-only) +GSTATE root version (4.8) is greater than running binary's (current); load with best-effort (read-only) RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM -[ERROR] Refusing write access to ${BASEDIR}/OPAM, which is more recent than this version of opam (2.2 > 2.2), aborting. +[ERROR] Refusing write access to ${BASEDIR}/OPAM, which is more recent than this version of opam (4.8 > current), aborting. # Return code 15 # -### cp config.2.1 $OPAMROOT/config -### cp config-w-swfoo.2.2 $OPAMROOT/config +### cp config.$OPAMROOTVERSION $OPAMROOT/config +### cp config-w-swfoo.4.8 $OPAMROOT/config ### :III:3:a: Bad switch config file : ### cp switch-config.err $OPAMROOT/foo/.opam-switch/switch-config ### # ro global state, ro repo state, ro switch state -### opam list +### opam list | "(${OPAMROOTVERSION})" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -GSTATE root version (2.2) is greater than running binary's (2.1); load with best-effort (read-only) +GSTATE root version (4.8) is greater than running binary's (current); load with best-effort (read-only) RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM -RSTATE root version (2.2) is greater than running binary's (2.1); load with best-effort (read-only) +RSTATE root version (4.8) is greater than running binary's (current); load with best-effort (read-only) RSTATE Cache found STATE LOAD-SWITCH-STATE @ foo FORMAT File errors in ${BASEDIR}/OPAM/foo/.opam-switch/switch-config, ignored fields: At ${BASEDIR}/OPAM/foo/.opam-switch/switch-config:3:0-3:8:: Invalid field neant -STATE root version (2.2) is greater than running binary's (2.1); load with best-effort (read-only) +STATE root version (4.8) is greater than running binary's (current); load with best-effort (read-only) STATE Inferred invariant: from base packages {}, (roots {}) => [] STATE Switch state loaded in 0.000s # Packages matching: installed # No matches found ### # ro global state, ro repo state, rw switch state -### opam install bar +### opam install bar | "(${OPAMROOTVERSION})" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -GSTATE root version (2.2) is greater than running binary's (2.1); load with best-effort (read-only) +GSTATE root version (4.8) is greater than running binary's (current); load with best-effort (read-only) RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM -RSTATE root version (2.2) is greater than running binary's (2.1); load with best-effort (read-only) +RSTATE root version (4.8) is greater than running binary's (current); load with best-effort (read-only) RSTATE Cache found STATE LOAD-SWITCH-STATE @ foo -[ERROR] Refusing write access to ${BASEDIR}/OPAM, which is more recent than this version of opam (2.2 > 2.2), aborting. +[ERROR] Refusing write access to ${BASEDIR}/OPAM, which is more recent than this version of opam (4.8 > current), aborting. # Return code 15 # ### :III:3:b: Good switch config file : ### cp switch-config $OPAMROOT/foo/.opam-switch/switch-config ### # ro global state, ro repo state, ro switch state -### opam list +### opam list | "(${OPAMROOTVERSION})" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -GSTATE root version (2.2) is greater than running binary's (2.1); load with best-effort (read-only) +GSTATE root version (4.8) is greater than running binary's (current); load with best-effort (read-only) RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM -RSTATE root version (2.2) is greater than running binary's (2.1); load with best-effort (read-only) +RSTATE root version (4.8) is greater than running binary's (current); load with best-effort (read-only) RSTATE Cache found STATE LOAD-SWITCH-STATE @ foo -STATE root version (2.2) is greater than running binary's (2.1); load with best-effort (read-only) +STATE root version (4.8) is greater than running binary's (current); load with best-effort (read-only) STATE Inferred invariant: from base packages {}, (roots {}) => [] STATE Switch state loaded in 0.000s # Packages matching: installed # No matches found ### # ro global state, ro repo state, rw switch state -### opam install bar +### opam install bar | "(${OPAMROOTVERSION})" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -GSTATE root version (2.2) is greater than running binary's (2.1); load with best-effort (read-only) +GSTATE root version (4.8) is greater than running binary's (current); load with best-effort (read-only) RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM -RSTATE root version (2.2) is greater than running binary's (2.1); load with best-effort (read-only) +RSTATE root version (4.8) is greater than running binary's (current); load with best-effort (read-only) RSTATE Cache found STATE LOAD-SWITCH-STATE @ foo -[ERROR] Refusing write access to ${BASEDIR}/OPAM, which is more recent than this version of opam (2.2 > 2.2), aborting. +[ERROR] Refusing write access to ${BASEDIR}/OPAM, which is more recent than this version of opam (4.8 > current), aborting. # Return code 15 # ### :III:1:a: Bad config file -### cp config-w-swfoo.2.2.err $OPAMROOT/config +### cp config-w-swfoo.4.8.err $OPAMROOT/config ### # rw global state -### opam switch remove foo +### opam switch remove foo | "(${OPAMROOTVERSION})" -> "current" FORMAT File errors in ${BASEDIR}/OPAM/config, ignored fields: At ${BASEDIR}/OPAM/config:7:0-7:8:: Invalid field neant GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -[ERROR] Refusing write access to ${BASEDIR}/OPAM, which is more recent than this version of opam (2.2 > 2.2), aborting. +[ERROR] Refusing write access to ${BASEDIR}/OPAM, which is more recent than this version of opam (4.8 > current), aborting. # Return code 15 # ### :III:1:b: Good config file -### cp config-w-swfoo.2.2 $OPAMROOT/config +### cp config-w-swfoo.4.8 $OPAMROOT/config ### # rw global state -### opam switch remove foo +### opam switch remove foo | "(${OPAMROOTVERSION})" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -[ERROR] Refusing write access to ${BASEDIR}/OPAM, which is more recent than this version of opam (2.2 > 2.2), aborting. +[ERROR] Refusing write access to ${BASEDIR}/OPAM, which is more recent than this version of opam (4.8 > current), aborting. # Return code 15 # -### : : -### : Newer opam root & new file version : -### : : +### : : +### : IV:Newer opam root & new file version : +### : : ### :IV:1:a: Bad config file -### cp config.2.3.err $OPAMROOT/config +### cp config.9.6.err $OPAMROOT/config ### # ro global state ### opam switch GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM @@ -364,7 +366,7 @@ In ${BASEDIR}/OPAM/config: unsupported or missing file format version; should be 2.0 or older # Return code 99 # ### :IV:1:b: Good config file -### cp config.2.3 $OPAMROOT/config +### cp config.9.6 $OPAMROOT/config ### # ro global state ### opam switch GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM @@ -404,9 +406,9 @@ Fatal error: In ${BASEDIR}/OPAM/config: unsupported or missing file format version; should be 2.0 or older # Return code 99 # -### cp config.2.1 $OPAMROOT/config +### cp config.$OPAMROOTVERSION $OPAMROOT/config ### #opam switch create foo --empty --debug-level=0 -### cp config-w-swfoo.2.3 $OPAMROOT/config +### cp config-w-swfoo.9.6 $OPAMROOT/config ### :IV:3:a: Bad switch config file : ### cp switch-config.err $OPAMROOT/foo/.opam-switch/switch-config ### # ro global state, ro repo state, ro switch state @@ -440,22 +442,22 @@ In ${BASEDIR}/OPAM/config: unsupported or missing file format version; should be 2.0 or older # Return code 99 # ### :IV:1:a: Bad config file -### cp config-w-swfoo.2.3.err $OPAMROOT/config +### cp config-w-swfoo.9.6.err $OPAMROOT/config ### # rw global state -### opam switch remove foo +### opam switch remove foo | "(${OPAMROOTVERSION})" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -[ERROR] Refusing write access to ${BASEDIR}/OPAM, which is more recent than this version of opam (2.3 > 2.2), aborting. +[ERROR] Refusing write access to ${BASEDIR}/OPAM, which is more recent than this version of opam (9.6 > current), aborting. # Return code 15 # ### :IV:1:b: Good config file -### cp config-w-swfoo.2.3 $OPAMROOT/config +### cp config-w-swfoo.9.6 $OPAMROOT/config ### # rw global state -### opam switch remove foo +### opam switch remove foo | "(${OPAMROOTVERSION})" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -[ERROR] Refusing write access to ${BASEDIR}/OPAM, which is more recent than this version of opam (2.3 > 2.2), aborting. +[ERROR] Refusing write access to ${BASEDIR}/OPAM, which is more recent than this version of opam (9.6 > current), aborting. # Return code 15 # -### : : -### : Older opam root : -### : : +### : : +### : V:Older opam root, intermediate upgrade from 2.0 to current : +### : : ### let content = {|opam-version: "2.0" synopsis: "One-line description" @@ -509,7 +511,7 @@ let mode = match Sys.argv.(2) with | "local" -> `Local version | "orphaned" -> `Orphaned version - | _ -> assert false + | s -> failwith s let opam_version = Printf.sprintf "opam-version: %S" let opam_version_2_0 = opam_version "2.0" @@ -551,8 +553,7 @@ installed: ["i-am-another-package.2" "i-am-package.2" "i-am-sys-compiler.1"] let invariant_default = {|invariant: ["i-am-sys-compiler" | "i-am-compiler"]|} let invariant_sw_comp = {|invariant: ["i-am-compiler"]|} let invariant_sw_sys_comp = {|invariant: ["i-am-sys-compiler"]|} -let root_version = {|opam-root-version: "2.1~rc"|} -let root_version_21 = {|opam-root-version: "2.1"|} +let root_version = Printf.sprintf "opam-root-version: %S" let synopsis = Printf.sprintf "synopsis: %S" let opam_root = Printf.sprintf "opam-root: %S" (Sys.getenv "OPAMROOT") let opam_20 = @@ -592,6 +593,7 @@ let opam_21alpha2 = "_opam/.opam-switch/switch-state", [ opam_version_2_0; sw_state_default ]; ] let opam_21rc = + let root_version = {|opam-root-version: "2.1~rc"|} in [ "config", [ opam_version_2_0; root_version; repo; installed_switches; eval; default_compiler; default_invariant; depext ]; "default/.opam-switch/switch-config", [ opam_version_2_0; synopsis "default switch"; invariant_default ]; "default/.opam-switch/switch-state", [ opam_version_2_0; sw_state_default ]; @@ -603,8 +605,8 @@ let opam_21rc = "_opam/.opam-switch/switch-config", [ opam_version_2_0; synopsis "local switch"; invariant_default; opam_root ]; "_opam/.opam-switch/switch-state", [ opam_version_2_0; sw_state_default ]; ] -let opam_21 = - [ "config", [ opam_version_2_0; root_version_21; repo; installed_switches; eval; default_compiler; default_invariant; depext ]; +let opam_current v = + [ "config", [ opam_version_2_0; root_version v; repo; installed_switches; eval; default_compiler; default_invariant; depext ]; "default/.opam-switch/switch-config", [ opam_version_2_0; synopsis "default switch"; invariant_default ]; "default/.opam-switch/switch-state", [ opam_version_2_0; sw_state_default ]; "sw-comp/.opam-switch/switch-config", [ opam_version_2_0; synopsis "switch with compiler"; invariant_sw_comp ]; @@ -621,8 +623,7 @@ let _ = | "2.1~alpha" -> opam_21alpha | "2.1~alpha2" -> opam_21alpha2 | "2.1~rc" -> opam_21rc - | "2.1" -> opam_21 - | _ -> assert false + | v -> opam_current v in let write dir (name, content) = let name = Filename.concat dir name in @@ -648,14 +649,14 @@ No configuration file found, using built-in defaults. ### :V:1:a: From 2.0 root, global ### ocaml generate.ml 2.0 ### # ro global state -### opam option jobs +### opam option jobs | "(${OPAMROOTVERSION})" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.0 to 2.1 +FMT_UPG On-the-fly config upgrade, from 2.0 to current FMT_UPG Format upgrade done ### # ro global state, ro repo state, ro switch state -### opam list +### opam list | "(${OPAMROOTVERSION})" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.0 to 2.1 +FMT_UPG On-the-fly config upgrade, from 2.0 to current FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE Cache found @@ -668,9 +669,9 @@ i-am-another-package 2 One-line description i-am-package 2 One-line description i-am-sys-compiler 1 One-line description ### # ro global state, ro repo state, rw switch state -### opam install i-am-another-package --switch sw-comp +### opam install i-am-another-package --switch sw-comp | "(${OPAMROOTVERSION})" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.0 to 2.1 +FMT_UPG On-the-fly config upgrade, from 2.0 to current FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE Cache found @@ -687,11 +688,11 @@ The following actions will be performed: -> installed i-am-another-package.2 Done. ### # rw global state -### opam switch sw-comp +### opam switch sw-comp | "(${OPAMROOTVERSION})" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM [WARNING] Removing global switch 'this-internal-error' as it no longer exists -FMT_UPG Light config upgrade, from 2.0 to 2.1 -This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.0 to version 2.1, which can't be reverted. +FMT_UPG Light config upgrade, from 2.0 to current +This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.0 to version current, which can't be reverted. You may want to back it up before going further. Continue? [Y/n] y @@ -700,7 +701,7 @@ RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE Cache found STATE LOAD-SWITCH-STATE @ sw-comp STATE Switch state loaded in 0.000s -### opam-cat $OPAMROOT/config +### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" default-compiler: ["i-am-sys-compiler" "i-am-compiler"] depext: true depext-cannot-install: false @@ -708,7 +709,7 @@ depext-run-installs: true download-jobs: 1 eval-variables: [sys-comp-version ["sh" "-c" "echo $OPAMSYSCOMP"] "comp version"] installed-switches: ["sw-sys-comp" "sw-comp" "default"] -opam-root-version: "2.1" +opam-root-version: current opam-version: "2.0" repositories: "default" switch: "sw-comp" @@ -730,9 +731,9 @@ roots: ["i-am-another-package.2" "i-am-compiler.2" "i-am-package.2"] ### :V:1:b: From 2.0 root, local ### ocaml generate.ml 2.0 local ### # ro global state, ro repo state, ro switch state -### opam list +### opam list | "(${OPAMROOTVERSION})" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.0 to 2.1 +FMT_UPG On-the-fly config upgrade, from 2.0 to current FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE Cache found @@ -743,9 +744,9 @@ STATE Switch state loaded in 0.000s # Name # Installed # Synopsis i-am-sys-compiler 2 One-line description ### # ro global state, ro repo state, rw switch state -### opam install i-am-package +### opam install i-am-package | "(${OPAMROOTVERSION})" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.0 to 2.1 +FMT_UPG On-the-fly config upgrade, from 2.0 to current FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE Cache found @@ -760,17 +761,17 @@ The following actions will be performed: <><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><> -> installed i-am-package.2 Done. -### opam option jobs=4 +### opam option jobs=4 | "(${OPAMROOTVERSION})" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM [WARNING] Removing global switch 'this-internal-error' as it no longer exists -FMT_UPG Light config upgrade, from 2.0 to 2.1 -This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.0 to version 2.1, which can't be reverted. +FMT_UPG Light config upgrade, from 2.0 to current +This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.0 to version current, which can't be reverted. You may want to back it up before going further. Continue? [Y/n] y Format upgrade done. Set to '4' the field jobs in global configuration -### opam-cat $OPAMROOT/config +### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" default-compiler: ["i-am-sys-compiler" "i-am-compiler"] depext: true depext-cannot-install: false @@ -779,7 +780,7 @@ download-jobs: 1 eval-variables: [sys-comp-version ["sh" "-c" "echo $OPAMSYSCOMP"] "comp version"] installed-switches: ["sw-sys-comp" "sw-comp" "${BASEDIR}" "default"] jobs: 4 -opam-root-version: "2.1" +opam-root-version: current opam-version: "2.0" repositories: "default" switch: "sw-sys-comp" @@ -803,9 +804,9 @@ roots: ["i-am-package.2" "i-am-sys-compiler.2"] ### :V:1:c: From 2.0 root, local unknown from config ### ocaml generate.ml 2.0 orphaned ### # ro global state, ro repo state, ro switch state -### opam list +### opam list | "(${OPAMROOTVERSION})" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.0 to 2.1 +FMT_UPG On-the-fly config upgrade, from 2.0 to current FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE Cache found @@ -816,9 +817,9 @@ STATE Switch state loaded in 0.000s # Name # Installed # Synopsis i-am-sys-compiler 2 One-line description ### # ro global state, ro repo state, rw switch state -### opam install i-am-package +### opam install i-am-package | "(${OPAMROOTVERSION})" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.0 to 2.1 +FMT_UPG On-the-fly config upgrade, from 2.0 to current FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE Cache found @@ -833,17 +834,17 @@ The following actions will be performed: <><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><> -> installed i-am-package.2 Done. -### opam option jobs=4 +### opam option jobs=4 | "(${OPAMROOTVERSION})" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM [WARNING] Removing global switch 'this-internal-error' as it no longer exists -FMT_UPG Light config upgrade, from 2.0 to 2.1 -This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.0 to version 2.1, which can't be reverted. +FMT_UPG Light config upgrade, from 2.0 to current +This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.0 to version current, which can't be reverted. You may want to back it up before going further. Continue? [Y/n] y Format upgrade done. Set to '4' the field jobs in global configuration -### opam-cat $OPAMROOT/config +### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" default-compiler: ["i-am-sys-compiler" "i-am-compiler"] depext: true depext-cannot-install: false @@ -852,7 +853,7 @@ download-jobs: 1 eval-variables: [sys-comp-version ["sh" "-c" "echo $OPAMSYSCOMP"] "comp version"] installed-switches: ["sw-sys-comp" "sw-comp" "default"] jobs: 4 -opam-root-version: "2.1" +opam-root-version: current opam-version: "2.0" repositories: "default" switch: "sw-sys-comp" @@ -873,7 +874,7 @@ installed: ["i-am-package.2" "i-am-sys-compiler.2"] opam-version: "2.0" roots: ["i-am-package.2" "i-am-sys-compiler.2"] ### :V:1:d: Upgraded root and local 2.0 switch not recorded -### ocaml generate.ml 2.1 orphaned 2.0 +### ocaml generate.ml $OPAMROOTVERSION orphaned 2.0 ### # ro global state, ro repo state, ro switch state ### opam list GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM @@ -903,7 +904,7 @@ Done. ### opam option jobs=4 GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM Set to '4' the field jobs in global configuration -### opam-cat $OPAMROOT/config +### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" default-compiler: ["i-am-sys-compiler" "i-am-compiler"] default-invariant: ["i-am-sys-compiler"] depext: true @@ -913,7 +914,7 @@ download-jobs: 1 eval-variables: [sys-comp-version ["sh" "-c" "echo $OPAMSYSCOMP"] "comp version"] installed-switches: ["sw-sys-comp" "sw-comp" "default" "this-internal-error"] jobs: 4 -opam-root-version: "2.1" +opam-root-version: current opam-version: "2.0" repositories: "default" switch: "sw-sys-comp" @@ -935,12 +936,12 @@ opam-version: "2.0" roots: ["i-am-package.2" "i-am-sys-compiler.2"] ### :V:1:e: reinit from 2.0 ### ocaml generate.ml 2.0 -### opam init --reinit --bypass-checks --no-setup +### opam init --reinit --bypass-checks --no-setup | "(${OPAMROOTVERSION})" -> "current" No configuration file found, using built-in defaults. GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM [WARNING] Removing global switch 'this-internal-error' as it no longer exists -FMT_UPG Light config upgrade, from 2.0 to 2.1 -This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.0 to version 2.1, which can't be reverted. +FMT_UPG Light config upgrade, from 2.0 to current +This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.0 to version current, which can't be reverted. You may want to back it up before going further. Continue? [Y/n] y @@ -966,7 +967,7 @@ STATE Switch state loaded in 0.000s # Name # Installed # Synopsis i-am-package 2 One-line description i-am-sys-compiler 2 One-line description -### opam-cat $OPAMROOT/config +### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" default-compiler: ["i-am-sys-compiler" "i-am-compiler"] default-invariant: ["ocaml" {>= "4.05.0"}] depext: true @@ -975,7 +976,7 @@ depext-run-installs: true download-jobs: 3 eval-variables: [sys-comp-version ["sh" "-c" "echo $OPAMSYSCOMP"] "comp version"] installed-switches: ["sw-sys-comp" "sw-comp" "default"] -opam-root-version: "2.1" +opam-root-version: current opam-version: "2.0" repositories: "default" switch: "sw-sys-comp" @@ -985,11 +986,11 @@ wrap-remove-commands: ["%{hooks}%/sandbox.sh" "remove"] {os = "linux" | os = "ma ### rm -rf _opam ### :V:2:a: From 2.1~alpha root, global ### ocaml generate.ml 2.1~alpha -### opam list +### opam list | "${OPAMROOTVERSION}($|,)" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM [WARNING] Removing global switch 'this-internal-error' as it no longer exists -FMT_UPG Hard config upgrade, from 2.1~alpha to 2.1 -This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.1~alpha to version 2.1, which can't be reverted. +FMT_UPG Hard config upgrade, from 2.1~alpha to current +This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.1~alpha to version current which can't be reverted. You may want to back it up before going further. Perform the update and continue? [Y/n] y @@ -1037,7 +1038,7 @@ RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE Cache found STATE LOAD-SWITCH-STATE @ sw-comp STATE Switch state loaded in 0.000s -### opam-cat $OPAMROOT/config +### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" default-compiler: ["i-am-sys-compiler" "i-am-compiler"] default-invariant: ["ocaml" {>= "4.05.0"}] depext: true @@ -1046,7 +1047,7 @@ depext-run-installs: true download-jobs: 3 eval-variables: [sys-comp-version ["sh" "-c" "echo $OPAMSYSCOMP"] "comp version"] installed-switches: ["sw-sys-comp" "sw-comp" "default"] -opam-root-version: "2.1" +opam-root-version: current opam-version: "2.0" repositories: "default" switch: "sw-comp" @@ -1070,11 +1071,11 @@ opam-version: "2.0" roots: ["i-am-another-package.2" "i-am-compiler.2" "i-am-package.2"] ### :V:2:b: From 2.1~alpha root, local ### ocaml generate.ml 2.1~alpha local -### opam list +### opam list | "${OPAMROOTVERSION}($|,)" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM [WARNING] Removing global switch 'this-internal-error' as it no longer exists -FMT_UPG Hard config upgrade, from 2.1~alpha to 2.1 -This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.1~alpha to version 2.1, which can't be reverted. +FMT_UPG Hard config upgrade, from 2.1~alpha to current +This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.1~alpha to version current which can't be reverted. You may want to back it up before going further. Perform the update and continue? [Y/n] y @@ -1103,7 +1104,7 @@ The following actions will be performed: <><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><> -> installed i-am-package.2 Done. -### opam-cat $OPAMROOT/config +### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" default-compiler: ["i-am-sys-compiler" "i-am-compiler"] default-invariant: ["ocaml" {>= "4.05.0"}] depext: true @@ -1112,7 +1113,7 @@ depext-run-installs: true download-jobs: 3 eval-variables: [sys-comp-version ["sh" "-c" "echo $OPAMSYSCOMP"] "comp version"] installed-switches: ["sw-sys-comp" "sw-comp" "${BASEDIR}" "default"] -opam-root-version: "2.1" +opam-root-version: current opam-version: "2.0" repositories: "default" switch: "sw-sys-comp" @@ -1138,11 +1139,11 @@ roots: ["i-am-package.2" "i-am-sys-compiler.2"] ### rm -rf _opam ### :V:2:c: From 2.1~alpha root, local unknown from config ### ocaml generate.ml 2.1~alpha orphaned -### opam list +### opam list | "${OPAMROOTVERSION}($|,)" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM [WARNING] Removing global switch 'this-internal-error' as it no longer exists -FMT_UPG Hard config upgrade, from 2.1~alpha to 2.1 -This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.1~alpha to version 2.1, which can't be reverted. +FMT_UPG Hard config upgrade, from 2.1~alpha to current +This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.1~alpha to version current which can't be reverted. You may want to back it up before going further. Perform the update and continue? [Y/n] y @@ -1172,7 +1173,7 @@ The following actions will be performed: <><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><> -> installed i-am-package.2 Done. -### opam-cat $OPAMROOT/config +### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" default-compiler: ["i-am-sys-compiler" "i-am-compiler"] default-invariant: ["ocaml" {>= "4.05.0"}] depext: true @@ -1181,7 +1182,7 @@ depext-run-installs: true download-jobs: 3 eval-variables: [sys-comp-version ["sh" "-c" "echo $OPAMSYSCOMP"] "comp version"] installed-switches: ["sw-sys-comp" "sw-comp" "default"] -opam-root-version: "2.1" +opam-root-version: current opam-version: "2.0" repositories: "default" switch: "sw-sys-comp" @@ -1205,7 +1206,7 @@ installed: ["i-am-package.2" "i-am-sys-compiler.2"] opam-version: "2.0" roots: ["i-am-package.2" "i-am-sys-compiler.2"] ### :V:2:d: Upgraded root and local 2.1~alpha switch not recorded -### ocaml generate.ml 2.1 orphaned 2.1~alpha +### ocaml generate.ml $OPAMROOTVERSION orphaned 2.1~alpha ### # ro global state, ro repo state, ro switch state ### opam list FILE(switch-config) Wrote ${BASEDIR}/_opam/.opam-switch/switch-config in 0.000s @@ -1234,7 +1235,7 @@ Done. ### opam option jobs=4 GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM Set to '4' the field jobs in global configuration -### opam-cat $OPAMROOT/config +### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" default-compiler: ["i-am-sys-compiler" "i-am-compiler"] default-invariant: ["i-am-sys-compiler"] depext: true @@ -1244,7 +1245,7 @@ download-jobs: 1 eval-variables: [sys-comp-version ["sh" "-c" "echo $OPAMSYSCOMP"] "comp version"] installed-switches: ["sw-sys-comp" "sw-comp" "default" "this-internal-error"] jobs: 4 -opam-root-version: "2.1" +opam-root-version: current opam-version: "2.0" repositories: "default" switch: "sw-sys-comp" @@ -1266,12 +1267,12 @@ opam-version: "2.0" roots: ["i-am-package.2" "i-am-sys-compiler.2"] ### :V:2:e: reinit from 2.1~alpha ### ocaml generate.ml 2.1~alpha -### opam init --reinit --bypass-checks --no-setup +### opam init --reinit --bypass-checks --no-setup | "${OPAMROOTVERSION}($|,)" -> "current" No configuration file found, using built-in defaults. GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM [WARNING] Removing global switch 'this-internal-error' as it no longer exists -FMT_UPG Hard config upgrade, from 2.1~alpha to 2.1 -This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.1~alpha to version 2.1, which can't be reverted. +FMT_UPG Hard config upgrade, from 2.1~alpha to current +This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.1~alpha to version current which can't be reverted. You may want to back it up before going further. Perform the update and continue? [Y/n] y @@ -1302,7 +1303,7 @@ STATE Switch state loaded in 0.000s # Name # Installed # Synopsis i-am-package 2 One-line description i-am-sys-compiler 2 One-line description -### opam-cat $OPAMROOT/config +### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" default-compiler: ["i-am-sys-compiler" "i-am-compiler"] default-invariant: ["ocaml" {>= "4.05.0"}] depext: true @@ -1311,7 +1312,7 @@ depext-run-installs: true download-jobs: 3 eval-variables: [sys-comp-version ["sh" "-c" "echo $OPAMSYSCOMP"] "comp version"] installed-switches: ["sw-sys-comp" "sw-comp" "default"] -opam-root-version: "2.1" +opam-root-version: current opam-version: "2.0" repositories: "default" switch: "sw-sys-comp" @@ -1322,13 +1323,13 @@ wrap-remove-commands: ["%{hooks}%/sandbox.sh" "remove"] {os = "linux" | os = "ma ### :V:3:a: From 2.1~alpha2 root, global ### ocaml generate.ml 2.1~alpha2 ### # ro global state -### opam option jobs +### opam option jobs | "${OPAMROOTVERSION}($|,)" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM FMT_UPG Intermediate opam root detected, launch hard upgrade FMT_UPG Downgrade config opam-version to fix up [WARNING] Removing global switch 'this-internal-error' as it no longer exists -FMT_UPG Hard config upgrade, from 2.1~alpha2 to 2.1 -This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.1~alpha2 to version 2.1, which can't be reverted. +FMT_UPG Hard config upgrade, from 2.1~alpha2 to current +This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.1~alpha2 to version current which can't be reverted. You may want to back it up before going further. Perform the update and continue? [Y/n] y @@ -1376,7 +1377,7 @@ RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE Cache found STATE LOAD-SWITCH-STATE @ sw-comp STATE Switch state loaded in 0.000s -### opam-cat $OPAMROOT/config +### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" default-compiler: ["i-am-sys-compiler" "i-am-compiler"] default-invariant: ["ocaml" {>= "4.05.0"}] depext: true @@ -1385,7 +1386,7 @@ depext-run-installs: true download-jobs: 3 eval-variables: [sys-comp-version ["sh" "-c" "echo $OPAMSYSCOMP"] "comp version"] installed-switches: ["sw-sys-comp" "sw-comp" "default"] -opam-root-version: "2.1" +opam-root-version: current opam-version: "2.0" repositories: "default" switch: "sw-comp" @@ -1409,13 +1410,13 @@ opam-version: "2.0" roots: ["i-am-another-package.2" "i-am-compiler.2" "i-am-package.2"] ### :V:3:b: From 2.1~alpha2 root, local ### ocaml generate.ml 2.1~alpha2 local -### opam list +### opam list | "${OPAMROOTVERSION}($|,)" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM FMT_UPG Intermediate opam root detected, launch hard upgrade FMT_UPG Downgrade config opam-version to fix up [WARNING] Removing global switch 'this-internal-error' as it no longer exists -FMT_UPG Hard config upgrade, from 2.1~alpha2 to 2.1 -This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.1~alpha2 to version 2.1, which can't be reverted. +FMT_UPG Hard config upgrade, from 2.1~alpha2 to current +This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.1~alpha2 to version current which can't be reverted. You may want to back it up before going further. Perform the update and continue? [Y/n] y @@ -1444,7 +1445,7 @@ The following actions will be performed: <><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><> -> installed i-am-package.2 Done. -### opam-cat $OPAMROOT/config +### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" default-compiler: ["i-am-sys-compiler" "i-am-compiler"] default-invariant: ["ocaml" {>= "4.05.0"}] depext: true @@ -1453,7 +1454,7 @@ depext-run-installs: true download-jobs: 3 eval-variables: [sys-comp-version ["sh" "-c" "echo $OPAMSYSCOMP"] "comp version"] installed-switches: ["sw-sys-comp" "sw-comp" "${BASEDIR}" "default"] -opam-root-version: "2.1" +opam-root-version: current opam-version: "2.0" repositories: "default" switch: "sw-sys-comp" @@ -1479,13 +1480,13 @@ roots: ["i-am-package.2" "i-am-sys-compiler.2"] ### rm -rf _opam ### :V:3:c: From 2.1~alpha2 root, local unknown from config ### ocaml generate.ml 2.1~alpha2 orphaned -### opam list +### opam list | "${OPAMROOTVERSION}($|,)" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM FMT_UPG Intermediate opam root detected, launch hard upgrade FMT_UPG Downgrade config opam-version to fix up [WARNING] Removing global switch 'this-internal-error' as it no longer exists -FMT_UPG Hard config upgrade, from 2.1~alpha2 to 2.1 -This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.1~alpha2 to version 2.1, which can't be reverted. +FMT_UPG Hard config upgrade, from 2.1~alpha2 to current +This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.1~alpha2 to version current which can't be reverted. You may want to back it up before going further. Perform the update and continue? [Y/n] y @@ -1515,7 +1516,7 @@ The following actions will be performed: <><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><> -> installed i-am-package.2 Done. -### opam-cat $OPAMROOT/config +### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" default-compiler: ["i-am-sys-compiler" "i-am-compiler"] default-invariant: ["ocaml" {>= "4.05.0"}] depext: true @@ -1524,7 +1525,7 @@ depext-run-installs: true download-jobs: 3 eval-variables: [sys-comp-version ["sh" "-c" "echo $OPAMSYSCOMP"] "comp version"] installed-switches: ["sw-sys-comp" "sw-comp" "default"] -opam-root-version: "2.1" +opam-root-version: current opam-version: "2.0" repositories: "default" switch: "sw-sys-comp" @@ -1548,7 +1549,7 @@ installed: ["i-am-package.2" "i-am-sys-compiler.2"] opam-version: "2.0" roots: ["i-am-package.2" "i-am-sys-compiler.2"] ### :V:3:d: Upgraded root and local 2.1~alpha2 switch not recorded -### ocaml generate.ml 2.1 orphaned 2.1~alpha2 +### ocaml generate.ml $OPAMROOTVERSION orphaned 2.1~alpha2 ### # ro global state, ro repo state, ro switch state ### opam list FILE(switch-config) Wrote ${BASEDIR}/_opam/.opam-switch/switch-config in 0.000s @@ -1577,7 +1578,7 @@ Done. ### opam option jobs=4 GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM Set to '4' the field jobs in global configuration -### opam-cat $OPAMROOT/config +### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" default-compiler: ["i-am-sys-compiler" "i-am-compiler"] default-invariant: ["i-am-sys-compiler"] depext: true @@ -1587,7 +1588,7 @@ download-jobs: 1 eval-variables: [sys-comp-version ["sh" "-c" "echo $OPAMSYSCOMP"] "comp version"] installed-switches: ["sw-sys-comp" "sw-comp" "default" "this-internal-error"] jobs: 4 -opam-root-version: "2.1" +opam-root-version: current opam-version: "2.0" repositories: "default" switch: "sw-sys-comp" @@ -1609,13 +1610,13 @@ opam-version: "2.0" roots: ["i-am-package.2" "i-am-sys-compiler.2"] ### :V:3:e: reinit from 2.1~alpha2 ### ocaml generate.ml 2.1~alpha2 -### opam init --reinit --bypass-checks --no-setup +### opam init --reinit --bypass-checks --no-setup | "${OPAMROOTVERSION}($|,)" -> "current" No configuration file found, using built-in defaults. FMT_UPG Intermediate opam root detected, launch hard upgrade FMT_UPG Downgrade config opam-version to fix up [WARNING] Removing global switch 'this-internal-error' as it no longer exists -FMT_UPG Hard config upgrade, from 2.1~alpha2 to 2.1 -This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.1~alpha2 to version 2.1, which can't be reverted. +FMT_UPG Hard config upgrade, from 2.1~alpha2 to current +This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.1~alpha2 to version current which can't be reverted. You may want to back it up before going further. Perform the update and continue? [Y/n] y @@ -1645,7 +1646,7 @@ STATE Switch state loaded in 0.000s # Name # Installed # Synopsis i-am-package 2 One-line description i-am-sys-compiler 2 One-line description -### opam-cat $OPAMROOT/config +### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" default-compiler: ["i-am-sys-compiler" "i-am-compiler"] default-invariant: ["ocaml" {>= "4.05.0"}] depext: true @@ -1654,7 +1655,7 @@ depext-run-installs: true download-jobs: 3 eval-variables: [sys-comp-version ["sh" "-c" "echo $OPAMSYSCOMP"] "comp version"] installed-switches: ["sw-sys-comp" "sw-comp" "default"] -opam-root-version: "2.1" +opam-root-version: current opam-version: "2.0" repositories: "default" switch: "sw-sys-comp" @@ -1665,14 +1666,14 @@ wrap-remove-commands: ["%{hooks}%/sandbox.sh" "remove"] {os = "linux" | os = "ma ### :V:4:a: From 2.1~rc root, global ### ocaml generate.ml 2.1~rc ### # ro global state -### opam option jobs +### opam option jobs | "${OPAMROOTVERSION}($|,)" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.1~rc to 2.1 +FMT_UPG On-the-fly config upgrade, from 2.1~rc to current FMT_UPG Format upgrade done ### # ro global state, ro repo state, ro switch state -### opam list +### opam list | "${OPAMROOTVERSION}($|,)" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.1~rc to 2.1 +FMT_UPG On-the-fly config upgrade, from 2.1~rc to current FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE Cache found @@ -1684,9 +1685,9 @@ i-am-another-package 2 One-line description i-am-package 2 One-line description i-am-sys-compiler 1 One-line description ### # ro global state, ro repo state, rw switch state -### opam install i-am-another-package --switch sw-comp +### opam install i-am-another-package --switch sw-comp | "${OPAMROOTVERSION}($|,)" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.1~rc to 2.1 +FMT_UPG On-the-fly config upgrade, from 2.1~rc to current FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE Cache found @@ -1699,17 +1700,17 @@ The following actions will be performed: <><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><> -> installed i-am-another-package.2 Done. -### opam option jobs=4 +### opam option jobs=4 | "${OPAMROOTVERSION}($|,)" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM [WARNING] Removing global switch 'this-internal-error' as it no longer exists -FMT_UPG Light config upgrade, from 2.1~rc to 2.1 -This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.1~rc to version 2.1, which can't be reverted. +FMT_UPG Light config upgrade, from 2.1~rc to current +This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.1~rc to version current which can't be reverted. You may want to back it up before going further. Continue? [Y/n] y Format upgrade done. Set to '4' the field jobs in global configuration -### opam-cat $OPAMROOT/config +### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" default-compiler: ["i-am-sys-compiler" "i-am-compiler"] default-invariant: ["i-am-sys-compiler"] depext: true @@ -1719,7 +1720,7 @@ download-jobs: 1 eval-variables: [sys-comp-version ["sh" "-c" "echo $OPAMSYSCOMP"] "comp version"] installed-switches: ["sw-sys-comp" "sw-comp" "default"] jobs: 4 -opam-root-version: "2.1" +opam-root-version: current opam-version: "2.0" repositories: "default" switch: "sw-sys-comp" @@ -1734,9 +1735,9 @@ opam-version: "2.0" roots: ["i-am-another-package.2" "i-am-compiler.2" "i-am-package.2"] ### :V:4:b: From 2.1~rc root, local ### ocaml generate.ml 2.1~rc local -### opam list +### opam list | "${OPAMROOTVERSION}($|,)" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.1~rc to 2.1 +FMT_UPG On-the-fly config upgrade, from 2.1~rc to current FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE Cache found @@ -1745,9 +1746,9 @@ STATE Switch state loaded in 0.000s # Packages matching: installed # Name # Installed # Synopsis i-am-sys-compiler 2 One-line description -### opam install i-am-package +### opam install i-am-package | "${OPAMROOTVERSION}($|,)" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.1~rc to 2.1 +FMT_UPG On-the-fly config upgrade, from 2.1~rc to current FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE Cache found @@ -1761,17 +1762,17 @@ The following actions will be performed: <><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><> -> installed i-am-package.2 Done. -### opam option jobs=4 +### opam option jobs=4 | "${OPAMROOTVERSION}($|,)" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM [WARNING] Removing global switch 'this-internal-error' as it no longer exists -FMT_UPG Light config upgrade, from 2.1~rc to 2.1 -This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.1~rc to version 2.1, which can't be reverted. +FMT_UPG Light config upgrade, from 2.1~rc to current +This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.1~rc to version current which can't be reverted. You may want to back it up before going further. Continue? [Y/n] y Format upgrade done. Set to '4' the field jobs in global configuration -### opam-cat $OPAMROOT/config +### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" default-compiler: ["i-am-sys-compiler" "i-am-compiler"] default-invariant: ["i-am-sys-compiler"] depext: true @@ -1781,7 +1782,7 @@ download-jobs: 1 eval-variables: [sys-comp-version ["sh" "-c" "echo $OPAMSYSCOMP"] "comp version"] installed-switches: ["sw-sys-comp" "sw-comp" "${BASEDIR}" "default"] jobs: 4 -opam-root-version: "2.1" +opam-root-version: current opam-version: "2.0" repositories: "default" switch: "sw-sys-comp" @@ -1798,9 +1799,9 @@ roots: ["i-am-package.2" "i-am-sys-compiler.2"] ### rm -rf _opam ### :V:4:c: From 2.1~rc root, local unknown from config ### ocaml generate.ml 2.1~rc local -### opam list +### opam list | "${OPAMROOTVERSION}($|,)" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.1~rc to 2.1 +FMT_UPG On-the-fly config upgrade, from 2.1~rc to current FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE Cache found @@ -1809,9 +1810,9 @@ STATE Switch state loaded in 0.000s # Packages matching: installed # Name # Installed # Synopsis i-am-sys-compiler 2 One-line description -### opam install i-am-package +### opam install i-am-package | "${OPAMROOTVERSION}($|,)" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.1~rc to 2.1 +FMT_UPG On-the-fly config upgrade, from 2.1~rc to current FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE Cache found @@ -1825,17 +1826,17 @@ The following actions will be performed: <><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><> -> installed i-am-package.2 Done. -### opam option jobs=4 +### opam option jobs=4 | "${OPAMROOTVERSION}($|,)" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM [WARNING] Removing global switch 'this-internal-error' as it no longer exists -FMT_UPG Light config upgrade, from 2.1~rc to 2.1 -This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.1~rc to version 2.1, which can't be reverted. +FMT_UPG Light config upgrade, from 2.1~rc to current +This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.1~rc to version current which can't be reverted. You may want to back it up before going further. Continue? [Y/n] y Format upgrade done. Set to '4' the field jobs in global configuration -### opam-cat $OPAMROOT/config +### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" default-compiler: ["i-am-sys-compiler" "i-am-compiler"] default-invariant: ["i-am-sys-compiler"] depext: true @@ -1845,7 +1846,7 @@ download-jobs: 1 eval-variables: [sys-comp-version ["sh" "-c" "echo $OPAMSYSCOMP"] "comp version"] installed-switches: ["sw-sys-comp" "sw-comp" "${BASEDIR}" "default"] jobs: 4 -opam-root-version: "2.1" +opam-root-version: current opam-version: "2.0" repositories: "default" switch: "sw-sys-comp" @@ -1860,7 +1861,7 @@ installed: ["i-am-package.2" "i-am-sys-compiler.2"] opam-version: "2.0" roots: ["i-am-package.2" "i-am-sys-compiler.2"] ### :V:4:d: Upgraded root and local 2.1~rc switch not recorded -### ocaml generate.ml 2.1 orphaned 2.1~rc +### ocaml generate.ml $OPAMROOTVERSION orphaned 2.1~rc ### # ro global state, ro repo state, ro switch state ### opam list GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM @@ -1888,7 +1889,7 @@ Done. ### opam option jobs=4 GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM Set to '4' the field jobs in global configuration -### opam-cat $OPAMROOT/config +### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" default-compiler: ["i-am-sys-compiler" "i-am-compiler"] default-invariant: ["i-am-sys-compiler"] depext: true @@ -1898,7 +1899,7 @@ download-jobs: 1 eval-variables: [sys-comp-version ["sh" "-c" "echo $OPAMSYSCOMP"] "comp version"] installed-switches: ["sw-sys-comp" "sw-comp" "default" "this-internal-error"] jobs: 4 -opam-root-version: "2.1" +opam-root-version: current opam-version: "2.0" repositories: "default" switch: "sw-sys-comp" @@ -1914,12 +1915,12 @@ opam-version: "2.0" roots: ["i-am-package.2" "i-am-sys-compiler.2"] ### :V:4:e: reinit from 2.1~rc ### ocaml generate.ml 2.1~rc -### opam init --reinit --bypass-checks --no-setup +### opam init --reinit --bypass-checks --no-setup | "${OPAMROOTVERSION}($|,)" -> "current" No configuration file found, using built-in defaults. GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM [WARNING] Removing global switch 'this-internal-error' as it no longer exists -FMT_UPG Light config upgrade, from 2.1~rc to 2.1 -This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.1~rc to version 2.1, which can't be reverted. +FMT_UPG Light config upgrade, from 2.1~rc to current +This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.1~rc to version current which can't be reverted. You may want to back it up before going further. Continue? [Y/n] y @@ -1945,7 +1946,7 @@ STATE Switch state loaded in 0.000s # Name # Installed # Synopsis i-am-package 2 One-line description i-am-sys-compiler 2 One-line description -### opam-cat $OPAMROOT/config +### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" default-compiler: ["i-am-sys-compiler" "i-am-compiler"] default-invariant: ["i-am-sys-compiler"] depext: true @@ -1954,7 +1955,7 @@ depext-run-installs: true download-jobs: 3 eval-variables: [sys-comp-version ["sh" "-c" "echo $OPAMSYSCOMP"] "comp version"] installed-switches: ["sw-sys-comp" "sw-comp" "default"] -opam-root-version: "2.1" +opam-root-version: current opam-version: "2.0" repositories: "default" switch: "sw-sys-comp" @@ -1993,7 +1994,7 @@ The following actions will be performed: <><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><> -> installed i-am-another-package.2 Done. -### opam-cat $OPAMROOT/config +### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" default-compiler: ["i-am-sys-compiler" "i-am-compiler"] default-invariant: ["i-am-sys-compiler"] depext: true @@ -2001,7 +2002,7 @@ depext-cannot-install: false depext-run-installs: true eval-variables: [sys-comp-version ["sh" "-c" "echo $OPAMSYSCOMP"] "comp version"] installed-switches: ["sw-sys-comp" "sw-comp" "default" "${BASEDIR}/why-did-you-delete-me" "this-internal-error"] -opam-root-version: "2.1" +opam-root-version: current opam-version: "2.0" repositories: "default" switch: "sw-sys-comp" @@ -2016,7 +2017,7 @@ opam-version: "2.0" roots: ["i-am-another-package.2" "i-am-compiler.2" "i-am-package.2"] ### :V:5:b: From 2.1 root, local ### ocaml generate.ml 2.1 local -### opam list +### opam list | "${OPAMROOTVERSION}($|,)" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE Cache found @@ -2039,7 +2040,7 @@ The following actions will be performed: <><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><> -> installed i-am-package.2 Done. -### opam-cat $OPAMROOT/config +### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" default-compiler: ["i-am-sys-compiler" "i-am-compiler"] default-invariant: ["i-am-sys-compiler"] depext: true @@ -2047,7 +2048,7 @@ depext-cannot-install: false depext-run-installs: true eval-variables: [sys-comp-version ["sh" "-c" "echo $OPAMSYSCOMP"] "comp version"] installed-switches: ["sw-sys-comp" "sw-comp" "${BASEDIR}" "default" "${BASEDIR}/why-did-you-delete-me" "this-internal-error"] -opam-root-version: "2.1" +opam-root-version: current opam-version: "2.0" repositories: "default" switch: "sw-sys-comp" @@ -2063,7 +2064,7 @@ opam-version: "2.0" roots: ["i-am-package.2" "i-am-sys-compiler.2"] ### :V:5:c: From 2.1 root, local unknown from config ### ocaml generate.ml 2.1 local -### opam list +### opam list | "${OPAMROOTVERSION}($|,)" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE Cache found @@ -2072,7 +2073,7 @@ STATE Switch state loaded in 0.000s # Packages matching: installed # Name # Installed # Synopsis i-am-sys-compiler 2 One-line description -### opam install i-am-package +### opam install i-am-package | "${OPAMROOTVERSION}($|,)" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE Cache found @@ -2085,7 +2086,7 @@ The following actions will be performed: <><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><> -> installed i-am-package.2 Done. -### opam-cat $OPAMROOT/config +### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" default-compiler: ["i-am-sys-compiler" "i-am-compiler"] default-invariant: ["i-am-sys-compiler"] depext: true @@ -2093,7 +2094,7 @@ depext-cannot-install: false depext-run-installs: true eval-variables: [sys-comp-version ["sh" "-c" "echo $OPAMSYSCOMP"] "comp version"] installed-switches: ["sw-sys-comp" "sw-comp" "${BASEDIR}" "default" "${BASEDIR}/why-did-you-delete-me" "this-internal-error"] -opam-root-version: "2.1" +opam-root-version: current opam-version: "2.0" repositories: "default" switch: "sw-sys-comp" @@ -2136,7 +2137,7 @@ Done. ### opam option jobs=4 GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM Set to '4' the field jobs in global configuration -### opam-cat $OPAMROOT/config +### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" default-compiler: ["i-am-sys-compiler" "i-am-compiler"] default-invariant: ["i-am-sys-compiler"] depext: true @@ -2146,7 +2147,7 @@ download-jobs: 1 eval-variables: [sys-comp-version ["sh" "-c" "echo $OPAMSYSCOMP"] "comp version"] installed-switches: ["sw-sys-comp" "sw-comp" "default" "this-internal-error"] jobs: 4 -opam-root-version: "2.1" +opam-root-version: current opam-version: "2.0" repositories: "default" switch: "sw-sys-comp" @@ -2170,7 +2171,7 @@ RSTATE Cache found <><> Updating repositories ><><><><><><><><><><><><><><><><><><><><><><><><><><> [default] no changes from file://${BASEDIR}/default -### opam-cat $OPAMROOT/config +### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" default-compiler: ["i-am-sys-compiler" "i-am-compiler"] default-invariant: ["i-am-sys-compiler"] depext: true @@ -2179,7 +2180,7 @@ depext-run-installs: true download-jobs: 3 eval-variables: [sys-comp-version ["sh" "-c" "echo $OPAMSYSCOMP"] "comp version"] installed-switches: ["sw-sys-comp" "sw-comp" "default" "${BASEDIR}/why-did-you-delete-me" "this-internal-error"] -opam-root-version: "2.1" +opam-root-version: current opam-version: "2.0" repositories: "default" switch: "sw-sys-comp" From 772cd9326980529f037e66a29f4e396deabd90ac Mon Sep 17 00:00:00 2001 From: Raja Boujbel Date: Thu, 28 Oct 2021 16:36:30 +0200 Subject: [PATCH 14/14] update changes --- master_changes.md | 12 +++++++++++- 1 file changed, 11 insertions(+), 1 deletion(-) diff --git a/master_changes.md b/master_changes.md index 21b50c958dc..cb46a4e637d 100644 --- a/master_changes.md +++ b/master_changes.md @@ -153,8 +153,18 @@ users) * Add switch-invariant test [#4866 @rjbou] * opam root version: add local switch cases [#4763 @rjbou] [2.1.0~rc2 #4715] * opam root version: add reinit test casess [#4763 @rjbou] [2.1.0~rc2 #4750] - * Add `opam-cat` to normalise opam file printing [#4763 @rjbou @dra27] [2.1.0~rc2 #4715] * Add & update env tests [#4861 #4841 @rjbou @dra27] + * Add `opam-cat` to normalise opam file printing [#4763 @rjbou @dra27] [2.1.0~rc2 #4715] + * Fix meld reftest: open only with failing ones [#4913 @rjbou] + * Add `BASEDIR` to environement [#4913 @rjbou] + * Replace opam bin path [#4913 @rjbou] + * Add `grep -v` command [#4913 @rjbou] + * Apply grep & seds on file order [#4913 @rjbou] + * Precise `OPAMTMP` regexp, `hexa` instead of `'alphanum` to avoid confusion with `BASEDIR` [#4913 @rjbou] + * Hackish way to have several replacement in a single line [#4913 @rjbou] + * Substitution in regexp pattern (for environment variables) [#4913 @rjbou] + * Substitution for opam-cat content [#4913 @rjbou] + ## Github Actions * Add solver backends compile test [#4723 @rjbou] [2.1.0~rc2 #4720]