diff --git a/src/client/opamClient.ml b/src/client/opamClient.ml index bd3129f5331..83944d24ed0 100644 --- a/src/client/opamClient.ml +++ b/src/client/opamClient.ml @@ -1846,10 +1846,17 @@ let init OpamStd.Sys.exit_because `Aborted); try (* Create the content of ~/.opam/config *) - let repos = match repo with - | Some r -> [r.repo_name, (r.repo_url, r.repo_trust)] - | None -> OpamFile.InitConfig.repositories init_config - in + let repos = + let open OpamFile.Repos_config in + match repo with + | Some r -> + [r.repo_name, + {repoc_url = r.repo_url; repoc_trust = r.repo_trust}] + | None -> + List.map (fun (n,(u,t)) -> + n, {repoc_url = u; repoc_trust = t}) + ( OpamFile.InitConfig.repositories init_config) + in let config = update_with_init_config OpamFile.Config.(with_opam_root_version root_version empty) diff --git a/src/format/opamFile.ml b/src/format/opamFile.ml index 1d94fa0a9b9..c4397cb650a 100644 --- a/src/format/opamFile.ml +++ b/src/format/opamFile.ml @@ -1386,7 +1386,7 @@ module ConfigSyntax = struct let internal = "config" let format_version = OpamVersion.of_string "2.1" let file_format_version = OpamVersion.of_string "2.0" - let root_version = OpamVersion.of_string "2.2" + let root_version = OpamVersion.of_string "2.4" let default_old_root_version = OpamVersion.of_string "2.1~~previous" @@ -1957,13 +1957,17 @@ module InitConfig = struct include SyntaxFile(InitConfigSyntax) end -module Repos_configSyntax = struct +module Repos_config_LegacySyntax = struct let internal = "repos-config" let format_version = OpamVersion.of_string "2.0" let file_format_version = OpamVersion.of_string "2.0" - type t = (url * trust_anchors option) OpamRepositoryName.Map.t + type repo = { + repoc_url: url; + repoc_trust: trust_anchors option; + } + type t = repo OpamRepositoryName.Map.t let empty = OpamRepositoryName.Map.empty @@ -1973,8 +1977,10 @@ module Repos_configSyntax = struct ((Pp.V.map_list ~depth:1 @@ InitConfigSyntax.pp_repository_def -| Pp.pp - (fun ~pos:_ (name, url, ta) -> (name, (url, ta))) - (fun (name, (url, ta)) -> (name, url, ta))) -| + (fun ~pos:_ (name, repoc_url, repoc_trust) -> + (name, {repoc_url; repoc_trust})) + (fun (name, {repoc_url; repoc_trust}) -> + (name, repoc_url, repoc_trust))) -| Pp.of_pair "repository-url-list" OpamRepositoryName.Map.(of_list, bindings)); ] @@ -1991,6 +1997,122 @@ module Repos_configSyntax = struct let pp = pp_cond () end + +module Repos_config_Legacy = struct + include Repos_config_LegacySyntax + include SyntaxFile(Repos_config_LegacySyntax) + module BestEffort = MakeBestEffort(Repos_config_LegacySyntax) +end + +module Repos_configSyntax = struct + + let internal = "repos-config" + let format_version = OpamVersion.of_string "2.1" + let file_format_version = OpamVersion.of_string "2.0" + + type repo = { + repoc_url: url; + repoc_trust: trust_anchors option; + } + type t = repo OpamRepositoryName.Map.t + + let empty = OpamRepositoryName.Map.empty + + let pp_repo = + let empty = { repoc_url = OpamUrl.empty; repoc_trust = None } in + Pp.I.fields ~name:"repos-config-repo" ~empty [ + "url", Pp.ppacc + (fun repoc_url t -> { t with repoc_url }) + (fun { repoc_url; _ } -> repoc_url) + Pp.V.url; + "fingerprint", Pp.ppacc_opt + (fun fingerprints t -> + match t.repoc_trust with + | Some x -> { t with repoc_trust = Some { x with fingerprints }} + | None -> { t with repoc_trust = Some { fingerprints; quorum = 1}}) + (fun t -> + match t.repoc_trust with + | Some {fingerprints; _} -> Some fingerprints + | None -> None) + (Pp.V.map_list ~depth:1 Pp.V.string); + "quorum", + Pp.ppacc_opt + (fun quorum t -> + match t.repoc_trust with + | Some x -> { t with repoc_trust = Some { x with quorum }} + | None -> { t with repoc_trust = Some { quorum; fingerprints = []}}) + (fun t -> + match t.repoc_trust with + | Some {quorum; _} -> Some quorum + | None -> None) + Pp.V.int; + ] + + let sections = + Pp.map_list + (Pp.I.section "repo" + -| Pp.pp ~name:"repo section" + (fun ~pos (name_opt, content) -> + let url = "repo", (Some pos, "missing URL") in + let name_repo = "repo", (Some pos, "missing repository name") in + let repo, errs = Pp.parse ~pos pp_repo content in + let nr, errs = + match name_opt with + | Some name -> + Some (OpamRepositoryName.of_string name, repo), errs + | None -> + None, name_repo::errs + in + if OpamUrl.equal OpamUrl.empty repo.repoc_url then + None, url::errs + else nr, errs + ) + (function + | Some (name, repo), _ -> + Some (OpamRepositoryName.to_string name), + Pp.print pp_repo (repo, []) + | None, _ -> None, [])) + -| Pp.pp ~name:"repositories" + (fun ~pos:_ repos -> + let repos, errs = List.split repos in + let repos = List.filter_map Fun.id repos in + let map = OpamRepositoryName.Map.of_list repos in + let errs = List.flatten errs in + map, errs) + (fun (map, _errs) -> + OpamRepositoryName.Map.bindings map + |> List.map (fun x -> Some x, [])) + + let pp_cond ?f ?condition () = + let name = internal in + let format_version = file_format_version in + Pp.I.map_file @@ + Pp.I.check_opam_version ~optional:true ?f ~format_version () -| + Pp.I.opam_version ~format_version ~undefined:true () -| + Pp.I.partition (fun i -> match i.pelem with + | Section ({ section_kind={pelem="repo";_}; section_name=Some _; _ }) -> + false + | _ -> true) + -| Pp.map_pair + (* we need to keep the fields parser in order to display + unknown field errors *) + (let condition = + (* we need to propagate the BestEffort condition value *) + OpamStd.Option.map (fun cond -> fun () -> cond empty) condition + in + Pp.I.fields ~name ~empty:() [] + -| Pp.I.show_errors ~name ?condition () + -| Pp.pp (fun ~pos:_ _ -> ()) (fun () -> ()) + ) + (sections + -| Pp.I.show_errors ~name ?condition ()) + -| Pp.pp (fun ~pos:_ (_, map) -> map) + (fun t -> (), t) + + let pp = pp_cond () + +end + module Repos_config = struct include Repos_configSyntax include SyntaxFile(Repos_configSyntax) diff --git a/src/format/opamFile.mli b/src/format/opamFile.mli index 45c51ef8320..445441d8554 100644 --- a/src/format/opamFile.mli +++ b/src/format/opamFile.mli @@ -1028,8 +1028,22 @@ module Repo_config_legacy : sig include IO_FILE with type t := t end +module Repos_config_Legacy: sig + type repo = { + repoc_url: url; + repoc_trust: trust_anchors option; + } + type t = repo OpamRepositoryName.Map.t + include IO_FILE with type t := t + module BestEffort: BestEffortRead with type t := t +end + module Repos_config: sig - type t = (url * trust_anchors option) OpamRepositoryName.Map.t + type repo = { + repoc_url: url; + repoc_trust: trust_anchors option; + } + type t = repo OpamRepositoryName.Map.t include IO_FILE with type t := t module BestEffort: BestEffortRead with type t := t end diff --git a/src/state/opamFormatUpgrade.ml b/src/state/opamFormatUpgrade.ml index f488f661fb9..afcd2b887ec 100644 --- a/src/state/opamFormatUpgrade.ml +++ b/src/state/opamFormatUpgrade.ml @@ -352,7 +352,7 @@ let opam_file_from_1_2_to_2_0 ?filename opam = (* Global state changes that need to be propagated *) let gtc_none = { gtc_repo = false; gtc_switch = false } -let _gtc_repo = { gtc_repo = true; gtc_switch = false } +let gtc_repo = { gtc_repo = true; gtc_switch = false } let _gtc_switch = { gtc_repo = false; gtc_switch = true } let _gtc_both = { gtc_repo = true; gtc_switch = true } @@ -770,7 +770,10 @@ let from_1_3_dev7_to_2_0_alpha ~on_the_fly:_ root conf = in OpamFile.Repos_config.write (OpamPath.repos_config root) (OpamRepositoryName.Map.of_list - (List.map (fun (_, r, u) -> r, (u,None)) prio_repositories)); + (List.map (fun (_, repo_name, repoc_url) -> + repo_name, + OpamFile.Repos_config.{repoc_url; repoc_trust = None}) + prio_repositories)); let prio_repositories = List.stable_sort (fun (prio1, _, _) (prio2, _, _) -> prio2 - prio1) prio_repositories @@ -1147,6 +1150,32 @@ let v2_2 = OpamVersion.of_string "2.2" let from_2_2_beta_to_2_2 ~on_the_fly:_ _ conf = conf, gtc_none +let v2_3 = OpamVersion.of_string "2.3" + +let from_2_2_to_2_3 ~on_the_fly:_ _ conf = conf, gtc_none + +let v2_4 = OpamVersion.of_string "2.4" + +let from_2_3_to_2_4 ~on_the_fly root conf = + (if on_the_fly then + OpamConsole.error_and_exit `Internal_error + "This 2.4 upgrade should be a hard upgrade"); + let f = OpamPath.repos_config root in + OpamStd.Option.iter (fun old_repoconfig -> + let repos = + OpamRepositoryName.Map.map (fun old_repo -> + let OpamFile.Repos_config_Legacy.{repoc_url; repoc_trust} = + old_repo + in + OpamFile.Repos_config.{repoc_url; repoc_trust}) + old_repoconfig + in + OpamFile.Repos_config.write f repos) + (OpamFile.Repos_config_Legacy.BestEffort.read_opt + (OpamFile.make + (OpamFile.filename f))); + conf, gtc_repo + (* To add an upgrade layer * If it is a light upgrade, returns as second element if the repo or switch need an light upgrade with `gtc_*` values. @@ -1156,7 +1185,7 @@ let from_2_2_beta_to_2_2 ~on_the_fly:_ _ conf = conf, gtc_none let latest_version = OpamFile.Config.root_version -let latest_hard_upgrade = (* to *) v2_0_beta5 +let latest_hard_upgrade = (* to *) v2_4 (* intermediate roots that need a hard upgrade when upgrading from them *) let v2_1_intermediate_roots = [ @@ -1218,9 +1247,11 @@ let as_necessary ?reinit requested_lock global_lock root config = let is_2_1_intermediate_root = List.exists (OpamVersion.equal root_version) v2_1_intermediate_roots in + (* As last hard upgrade is > 2.1~rc, we no more need that selection. let latest_hard_upgrade = if is_2_1_intermediate_root then v2_1_rc else latest_hard_upgrade in + *) (if is_2_1_intermediate_root then [ v2_1_alpha, from_2_0_to_2_1_alpha; v2_1_alpha2, from_2_1_alpha_to_2_1_alpha2; @@ -1244,6 +1275,8 @@ let as_necessary ?reinit requested_lock global_lock root config = v2_2_alpha, from_2_1_to_2_2_alpha; v2_2_beta, from_2_2_alpha_to_2_2_beta; v2_2, from_2_2_beta_to_2_2; + v2_3, from_2_2_to_2_3; + v2_4, from_2_3_to_2_4; ] |> List.filter (fun (v,_) -> OpamVersion.compare root_version v < 0) diff --git a/src/state/opamRepositoryState.ml b/src/state/opamRepositoryState.ml index b7e8ff69a64..66cd8be6ea5 100644 --- a/src/state/opamRepositoryState.ml +++ b/src/state/opamRepositoryState.ml @@ -164,10 +164,10 @@ let load lock_kind gt = load with best-effort (read-only)" (OpamVersion.to_string (OpamFile.Config.opam_root_version gt.config)) (OpamVersion.to_string (OpamFile.Config.root_version)); - let mk_repo name (url, ta) = { + let mk_repo name OpamFile.Repos_config.{repoc_url; repoc_trust} = { repo_name = name; - repo_url = url; - repo_trust = ta; + repo_url = repoc_url; + repo_trust = repoc_trust; } in let repositories = OpamRepositoryName.Map.mapi mk_repo repos_map in let repos_tmp_root = lazy (OpamFilename.mk_tmp_dir ()) in @@ -280,7 +280,9 @@ let write_config rt = OpamFile.Repos_config.write (OpamPath.repos_config rt.repos_global.root) (OpamRepositoryName.Map.filter_map (fun _ r -> if r.repo_url = OpamUrl.empty then None - else Some (r.repo_url, r.repo_trust)) + else + Some OpamFile.Repos_config.{ repoc_url = r.repo_url; + repoc_trust = r.repo_trust}) rt.repositories) let check_last_update () = diff --git a/tests/reftests/dune.inc b/tests/reftests/dune.inc index 479710810d0..e2b0a6c3c08 100644 --- a/tests/reftests/dune.inc +++ b/tests/reftests/dune.inc @@ -1931,27 +1931,6 @@ %{targets} (run ./run.exe %{exe:../../src/client/opamMain.exe.exe} %{dep:upgrade-format.test} %{read-lines:testing-env})))) -(rule - (alias reftest-upgrade-two-point-o) - (enabled_if (and (or (<> %{env:TESTALL=1} 0) (= %{env:TESTN0REP0=0} 1)))) - (action - (diff upgrade-two-point-o.test upgrade-two-point-o.out))) - -(alias - (name reftest) - (enabled_if (and (or (<> %{env:TESTALL=1} 0) (= %{env:TESTN0REP0=0} 1)))) - (deps (alias reftest-upgrade-two-point-o))) - -(rule - (targets upgrade-two-point-o.out) - (deps root-N0REP0) - (enabled_if (and (or (<> %{env:TESTALL=1} 0) (= %{env:TESTN0REP0=0} 1)))) - (package opam) - (action - (with-stdout-to - %{targets} - (run ./run.exe %{exe:../../src/client/opamMain.exe.exe} %{dep:upgrade-two-point-o.test} %{read-lines:testing-env})))) - (rule (alias reftest-upgrade) (enabled_if (and (or (<> %{env:TESTALL=1} 0) (= %{env:TESTN0REP0=0} 1)))) diff --git a/tests/reftests/init-ocaml-eval-variables.unix.test b/tests/reftests/init-ocaml-eval-variables.unix.test index 0cd6ccdfee3..ea4b9900991 100644 --- a/tests/reftests/init-ocaml-eval-variables.unix.test +++ b/tests/reftests/init-ocaml-eval-variables.unix.test @@ -7,6 +7,9 @@ let opamroot = Sys.getenv "OPAMROOT" let opam_version = Printf.sprintf "opam-version: %S" let opam_version_2_0 = opam_version "2.0" let opam_version_2_1 = opam_version "2.1" +let repos_config = Printf.sprintf {|opam-version: "2.0" +repositories: "default" {"file://%s/REPO"} +|} (Sys.getenv "BASEDIR") let repo = {|repositories: "default"|} let depext = {| depext: true @@ -33,6 +36,10 @@ let _ = let content = get_files Sys.argv.(1) in let fd = open_out name in List.iter (fun l -> output_string fd (l^"\n")) content; + close_out fd; + let rcname = Filename.concat (Filename.concat opamroot "repo") "repos-config" in + let fd = open_out rcname in + output_string fd repos_config; close_out fd ### rm -rf "$OPAMROOT" ### :::::::::::::::::::::::::: @@ -55,15 +62,24 @@ eval-variables: [sys-ocaml-version ["ocamlc" "-vnum"] "OCaml version present on ### # rw global state ### opam option jobs=4 | " ${OPAMROOTVERSION}($|,)" -> " current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG Light config upgrade, from 2.0 to current +FMT_UPG Hard 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 +Perform the update and continue? [Y/n] y [NOTE] The 'jobs' option was reset, its value was 1 and its new value will vary according to the current number of cores on your machine. You can restore the fixed value using: opam option jobs=1 --global Format upgrade done. -Set to '4' the field jobs in global configuration + +<><> Rerunning init and update ><><><><><><><><><><><><><><><><><><><><><><><><> +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM +RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM +RSTATE Cache found + +<><> Updating repositories ><><><><><><><><><><><><><><><><><><><><><><><><><><> +[default] no changes from file://${BASEDIR}/REPO +Update done, please now retry your command. +# Return code 10 # ### opam-cat $OPAMROOT/config | grep eval-variables eval-variables: [[sys-ocaml-system ["sh" "-c" "ocamlc -config 2>/dev/null | tr -d '/r' | sed -n -e 's/system: //p'"] "Target system of the OCaml compiler present on your system"] [sys-ocaml-libc ["sh" "-c" "ocamlc -config 2>/dev/null | tr -d '/r' | sed -n -e 's/^os_type: Win32/msvc/p;s/^os_type: .*/libc/p'"] "Host C Runtime Library type of the OCaml compiler present on your system"] [sys-ocaml-cc ["sh" "-c" "ocamlc -config 2>/dev/null | tr -d '/r' | sed -n -e 's/^ccomp_type: //p'"] "Host C Compiler type of the OCaml compiler present on your system"] [sys-ocaml-arch ["sh" "-c" "ocamlc -config 2>/dev/null | tr -d '/r' | sed -n -e 's/i386/i686/;s/amd64/x86_64/;s/^architecture: //p'"] "Target architecture of the OCaml compiler present on your system"] [sys-ocaml-version ["ocamlc" "-vnum"] "OCaml version present on your system independently of opam, if any"]] ### rm "$OPAMROOT/config" @@ -76,14 +92,23 @@ eval-variables: [[sys-ocaml-version ["ocamlc" "-vnum"] "OCaml version present on ### # rw global state ### opam option jobs=4 | "${OPAMROOTVERSION}($|,)" -> " current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG Light config upgrade, from 2.1 to current +FMT_UPG Hard config upgrade, from 2.1 to current This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.1 to version current which can't be reverted. You may want to back it up before going further. -Continue? [Y/n] y +Perform the update and continue? [Y/n] y [NOTE] The 'jobs' option was reset, its value was 1 and its new value will vary according to the current number of cores on your machine. You can restore the fixed value using: opam option jobs=1 --global Format upgrade done. -Set to '4' the field jobs in global configuration + +<><> Rerunning init and update ><><><><><><><><><><><><><><><><><><><><><><><><> +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM +RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM +RSTATE Cache found + +<><> Updating repositories ><><><><><><><><><><><><><><><><><><><><><><><><><><> +[default] no changes from file://${BASEDIR}/REPO +Update done, please now retry your command. +# Return code 10 # ### opam-cat $OPAMROOT/config | grep eval-variables eval-variables: [[sys-ocaml-system ["sh" "-c" "ocamlc -config 2>/dev/null | tr -d '/r' | sed -n -e 's/system: //p'"] "Target system of the OCaml compiler present on your system"] [sys-ocaml-version ["ocamlc" "-vnum"] "OCaml version present on your system independently of opam, if any"] [sys-ocaml-arch ["sh" "-c" "ocamlc -config 2>/dev/null | tr -d '/r' | sed -n -e 's/i386/i686/;s/amd64/x86_64/;s/^architecture: //p'"] "Target architecture of the OCaml compiler present on your system"] [sys-ocaml-cc ["sh" "-c" "ocamlc -config 2>/dev/null | tr -d '/r' | sed -n -e 's/^ccomp_type: //p'"] "Host C Compiler type of the OCaml compiler present on your system"] [sys-ocaml-libc ["sh" "-c" "ocamlc -config 2>/dev/null | tr -d '/r' | sed -n -e 's/^os_type: Win32/msvc/p;s/^os_type: .*/libc/p'"] "Host C Runtime Library type of the OCaml compiler present on your system"]] diff --git a/tests/reftests/init.test b/tests/reftests/init.test index d02ba15037f..67fb42378b5 100644 --- a/tests/reftests/init.test +++ b/tests/reftests/init.test @@ -242,7 +242,9 @@ wrap-install-commands: ["%{hooks}%/a-script.sh" "wrap-install"] wrap-remove-commands: ["%{hooks}%/a-script.sh" "wrap-remove"] ### opam-cat $OPAMROOT/repo/repos-config opam-version: "2.0" -repositories: "norepo" {"file://${BASEDIR}/REPO"} +repo "norepo" { +url: "file://${BASEDIR}/REPO" +} ### sh $OPAMROOT/opam-init/hooks/a-script.sh test script test launched STOP i repeat STOP script test launched ### :: partially configured opamrc :: @@ -296,4 +298,6 @@ wrap-install-commands: ["%{hooks}%/a-script.sh" "wrap-install"] wrap-remove-commands: ["%{hooks}%/sandbox.sh" "remove"] {os = "linux" | os = "macos"} ### opam-cat $OPAMROOT/repo/repos-config opam-version: "2.0" -repositories: "norepo" {"file://${BASEDIR}/REPO"} +repo "norepo" { +url: "file://${BASEDIR}/REPO" +} diff --git a/tests/reftests/opamroot-versions.test b/tests/reftests/opamroot-versions.test index 059becf1a75..d66fb1d948e 100644 --- a/tests/reftests/opamroot-versions.test +++ b/tests/reftests/opamroot-versions.test @@ -12,7 +12,7 @@ installed-switches: "foo" switch: "foo" |} let neant = "neant: 0" -let repo = {|repositories: [ "default" {"file:///${BASEDIR/dontexist"} ]|} +let repo = Printf.sprintf {|repo "default" {url:"file://%s/dontexist"}|} (Sys.getenv "BASEDIR") let switch_config = {|synopsis: "foo"|} let _ = let configs = @@ -29,7 +29,7 @@ let _ = ]) in let files = [ - "repos-config", [ repo ]; + "repos-config", [ opam_version "2.0"; repo ]; "switch-config", [ opam_version "2.0"; switch_config ]; ] @ configs in @@ -80,7 +80,7 @@ GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM [WARNING] Errors in ${BASEDIR}/OPAM/repo/repos-config, some fields have been ignored: - - At ${BASEDIR}/OPAM/repo/repos-config:2:0-2:8:: + - At ${BASEDIR}/OPAM/repo/repos-config:3:0-3:8:: Invalid field neant RSTATE Cache found @@ -91,7 +91,7 @@ GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM [WARNING] No switch is currently set, perhaps you meant '--set-default'? RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM [WARNING] Errors in ${BASEDIR}/OPAM/repo/repos-config, some fields have been ignored: - - At ${BASEDIR}/OPAM/repo/repos-config:2:0-2:8:: + - At ${BASEDIR}/OPAM/repo/repos-config:3:0-3:8:: Invalid field neant RSTATE Cache found @@ -261,7 +261,7 @@ GSTATE root version (4.8) is greater than running binar GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM 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:: +FORMAT File errors in ${BASEDIR}/OPAM/repo/repos-config, ignored fields: At ${BASEDIR}/OPAM/repo/repos-config:3:0-3:8:: Invalid field neant RSTATE root version (4.8) is greater than running binary's current; load with best-effort (read-only) RSTATE Cache found @@ -568,13 +568,15 @@ let invariant_sw_sys_comp = {|invariant: ["i-am-sys-compiler"]|} let root_version = Printf.sprintf "opam-root-version: %S" let synopsis = Printf.sprintf "synopsis: %S" let opam_root = Printf.sprintf "opam-root: %S" opamroot -let repos_config = Printf.sprintf {| -opam-version: "2.0" -repositories: "default" {"file://%s/default"} -|} (Sys.getenv "BASEDIR" |> String.map (function '\\' -> '/' | c -> c)) +let repos_config v = {|opam-version: "2.0" +|} ^ + Printf.sprintf + (if v < 2.4 then {|repositories: ["default" {"file://%s/default"}]|} + else {|repo "default" {url:"file://%s/default"}|}) + (Sys.getenv "BASEDIR" |> String.map (function '\\' -> '/' | c -> c)) let opam_20 = [ "config", [ opam_version_2_0; repo; installed_switches; eval; default_compiler ]; - "repo/repos-config", [ repos_config ]; + "repo/repos-config", [ repos_config 2.0 ]; "default/.opam-switch/switch-config", [ opam_version_2_0; synopsis "default switch" ]; "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" ]; @@ -587,7 +589,7 @@ let opam_20 = ] let opam_21alpha = [ "config", [ opam_version_2_0; repo; installed_switches; eval; default_compiler ]; - "repo/repos-config", [ repos_config ]; + "repo/repos-config", [ repos_config 2.1 ]; "default/.opam-switch/switch-config", [ opam_version_2_1; 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_1; synopsis "switch with compiler"; invariant_sw_comp ]; @@ -600,7 +602,7 @@ let opam_21alpha = ] let opam_21alpha2 = [ "config", [ opam_version_2_1; repo; installed_switches; eval; default_compiler; depext; ]; - "repo/repos-config", [ repos_config ]; + "repo/repos-config", [ repos_config 2.1 ]; "default/.opam-switch/switch-config", [ opam_version_2_1; 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_1; synopsis "switch with compiler"; invariant_sw_comp ]; @@ -614,7 +616,7 @@ let opam_21alpha2 = 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 ]; - "repo/repos-config", [ repos_config ]; + "repo/repos-config", [ repos_config 2.1 ]; "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 ]; @@ -627,7 +629,7 @@ let opam_21rc = ] let opam_current v = [ "config", [ opam_version_2_0; root_version v; repo; installed_switches; eval; default_compiler; default_invariant; depext ]; - "repo/repos-config", [ repos_config ]; + "repo/repos-config", [ repos_config (float_of_string (String.sub v 0 3)) ]; "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 ]; @@ -687,18 +689,33 @@ 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 | "${OPAMROOTVERSION}$" -> "current" +### opam option jobs | "${OPAMROOTVERSION}" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -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 | "${OPAMROOTVERSION}$" -> "current" +[WARNING] Removing global switch 'this-internal-error' as it no longer exists +FMT_UPG Hard 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. + +Perform the update and continue? [Y/n] y +[NOTE] The 'jobs' option was reset, its value was 1 and its new value will vary according to the current number of cores on your machine. You can restore the fixed value using: + opam option jobs=1 --global +Format upgrade done. + +<><> Rerunning init and update ><><><><><><><><><><><><><><><><><><><><><><><><> GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.0 to current -FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE No cache found RSTATE loaded opam files from repo default in 0.000s + +<><> Updating repositories ><><><><><><><><><><><><><><><><><><><><><><><><><><> +[default] no changes from file://${BASEDIR}/default +Update done, please now retry your command. +# Return code 10 # +### # ro global state, ro repo state, ro switch state +### opam list | "${OPAMROOTVERSION}$" -> "current" +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM +RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM +RSTATE Cache found STATE LOAD-SWITCH-STATE @ sw-sys-comp STATE Inferred invariant: from base packages { i-am-sys-compiler.1 }, (roots { i-am-sys-compiler.1 }) => ["i-am-sys-compiler"] STATE Switch state loaded in 0.000s @@ -710,8 +727,6 @@ 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 | "${OPAMROOTVERSION}$" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -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 STATE LOAD-SWITCH-STATE @ sw-comp @@ -731,34 +746,31 @@ Done. ### # rw global state ### 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 tocurrent -This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.0 to versioncurrent which can't be reverted. -You may want to back it up before going further. - -Continue? [Y/n] y -[NOTE] The 'jobs' option was reset, its value was 1 and its new value will vary according to the current number of cores on your machine. You can restore the fixed value using: - opam option jobs=1 --global -Format upgrade done. 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 | '"${OPAMROOTVERSION}"' -> "current" | grep -v sys-pkg-manager-cmd | grep -v global-variables | grep -v eval-variables: default-compiler: ["i-am-sys-compiler" "i-am-compiler"] +default-invariant: ["ocaml" {>= "4.05.0"}] depext: true depext-cannot-install: false depext-run-installs: true -download-jobs: 1 +download-jobs: 3 installed-switches: ["sw-comp" "sw-sys-comp" "default"] opam-root-version: current opam-version: "2.0" repositories: "default" swh-fallback: false switch: "sw-comp" +wrap-build-commands: ["%{hooks}%/sandbox.sh" "build"] {os = "linux" | os = "macos"} +wrap-install-commands: ["%{hooks}%/sandbox.sh" "install"] {os = "linux" | os = "macos"} +wrap-remove-commands: ["%{hooks}%/sandbox.sh" "remove"] {os = "linux" | os = "macos"} ### opam-cat $OPAMROOT/repo/repos-config opam-version: "2.0" -repositories: "default" {"file://${BASEDIR}/default"} +repo "default" { +url: "file://${BASEDIR}/default" +} ### opam-cat $OPAMROOT/sw-comp/.opam-switch/switch-config invariant: ["i-am-compiler" {>= "2"}] opam-version: "2.0" @@ -775,25 +787,32 @@ 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 | "${OPAMROOTVERSION}$" -> "current" +### 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.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. + +Perform the update and continue? [Y/n] y +[NOTE] The 'jobs' option was reset, its value was 1 and its new value will vary according to the current number of cores on your machine. You can restore the fixed value using: + opam option jobs=1 --global +Format upgrade done. + +<><> Rerunning init and update ><><><><><><><><><><><><><><><><><><><><><><><><> GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.0 to current -FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE No cache found RSTATE loaded opam files from repo default in 0.000s -STATE LOAD-SWITCH-STATE @ ${BASEDIR} -STATE Inferred invariant: from base packages { i-am-sys-compiler.2 }, (roots { i-am-sys-compiler.2 }) => ["i-am-sys-compiler"] -STATE Switch state loaded in 0.000s -# Packages matching: installed -# Name # Installed # Synopsis -i-am-sys-compiler 2 One-line description + +<><> Updating repositories ><><><><><><><><><><><><><><><><><><><><><><><><><><> +[default] no changes from file://${BASEDIR}/default +Update done, please now retry your command. +# Return code 10 # ### # ro global state, ro repo state, rw switch state ### OPAMSYSCOMP=2 ### opam install i-am-package | "${OPAMROOTVERSION}$" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -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 STATE LOAD-SWITCH-STATE @ ${BASEDIR} @@ -812,22 +831,14 @@ Done. ### # rw global state ### 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 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 -[NOTE] The 'jobs' option was reset, its value was 1 and its new value will vary according to the current number of cores on your machine. You can restore the fixed value using: - opam option jobs=1 --global -Format upgrade done. Set to '4' the field jobs in global configuration ### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" | grep -v sys-pkg-manager-cmd | grep -v global-variables | grep -v eval-variables: default-compiler: ["i-am-sys-compiler" "i-am-compiler"] +default-invariant: ["ocaml" {>= "4.05.0"}] depext: true depext-cannot-install: false depext-run-installs: true -download-jobs: 1 +download-jobs: 3 installed-switches: ["sw-sys-comp" "sw-comp" "${BASEDIR}" "default"] jobs: 4 opam-root-version: current @@ -835,9 +846,14 @@ opam-version: "2.0" repositories: "default" swh-fallback: false switch: "sw-sys-comp" +wrap-build-commands: ["%{hooks}%/sandbox.sh" "build"] {os = "linux" | os = "macos"} +wrap-install-commands: ["%{hooks}%/sandbox.sh" "install"] {os = "linux" | os = "macos"} +wrap-remove-commands: ["%{hooks}%/sandbox.sh" "remove"] {os = "linux" | os = "macos"} ### opam-cat $OPAMROOT/repo/repos-config opam-version: "2.0" -repositories: "default" {"file://${BASEDIR}/default"} +repo "default" { +url: "file://${BASEDIR}/default" +} ### opam-cat _opam/.opam-switch/switch-config invariant: ["i-am-sys-compiler"] opam-root: "${BASEDIR}/OPAM" @@ -856,24 +872,31 @@ 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 | "${OPAMROOTVERSION}$" -> " current" +### 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.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. + +Perform the update and continue? [Y/n] y +[NOTE] The 'jobs' option was reset, its value was 1 and its new value will vary according to the current number of cores on your machine. You can restore the fixed value using: + opam option jobs=1 --global +Format upgrade done. + +<><> Rerunning init and update ><><><><><><><><><><><><><><><><><><><><><><><><> GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.0 to current -FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE No cache found RSTATE loaded opam files from repo default in 0.000s -STATE LOAD-SWITCH-STATE @ ${BASEDIR} -STATE Inferred invariant: from base packages { i-am-sys-compiler.2 }, (roots { i-am-sys-compiler.2 }) => ["i-am-sys-compiler"] -STATE Switch state loaded in 0.000s -# Packages matching: installed -# Name # Installed # Synopsis -i-am-sys-compiler 2 One-line description + +<><> Updating repositories ><><><><><><><><><><><><><><><><><><><><><><><><><><> +[default] no changes from file://${BASEDIR}/default +Update done, please now retry your command. +# Return code 10 # ### # ro global state, ro repo state, rw switch state ### opam install i-am-package | "${OPAMROOTVERSION}$" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -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 STATE LOAD-SWITCH-STATE @ ${BASEDIR} @@ -892,22 +915,14 @@ Done. ### # rw global state ### 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 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 -[NOTE] The 'jobs' option was reset, its value was 1 and its new value will vary according to the current number of cores on your machine. You can restore the fixed value using: - opam option jobs=1 --global -Format upgrade done. Set to '4' the field jobs in global configuration ### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" | grep -v sys-pkg-manager-cmd | grep -v global-variables | grep -v eval-variables: default-compiler: ["i-am-sys-compiler" "i-am-compiler"] +default-invariant: ["ocaml" {>= "4.05.0"}] depext: true depext-cannot-install: false depext-run-installs: true -download-jobs: 1 +download-jobs: 3 installed-switches: ["sw-sys-comp" "sw-comp" "default"] jobs: 4 opam-root-version: current @@ -915,9 +930,14 @@ opam-version: "2.0" repositories: "default" swh-fallback: false switch: "sw-sys-comp" +wrap-build-commands: ["%{hooks}%/sandbox.sh" "build"] {os = "linux" | os = "macos"} +wrap-install-commands: ["%{hooks}%/sandbox.sh" "install"] {os = "linux" | os = "macos"} +wrap-remove-commands: ["%{hooks}%/sandbox.sh" "remove"] {os = "linux" | os = "macos"} ### opam-cat $OPAMROOT/repo/repos-config opam-version: "2.0" -repositories: "default" {"file://${BASEDIR}/default"} +repo "default" { +url: "file://${BASEDIR}/default" +} ### opam-cat _opam/.opam-switch/switch-config invariant: ["i-am-sys-compiler"] opam-root: "${BASEDIR}/OPAM" @@ -984,7 +1004,9 @@ swh-fallback: false switch: "sw-sys-comp" ### opam-cat $OPAMROOT/repo/repos-config opam-version: "2.0" -repositories: "default" {"file://${BASEDIR}/default"} +repo "default" { +url: "file://${BASEDIR}/default" +} ### opam-cat _opam/.opam-switch/switch-config invariant: ["i-am-sys-compiler"] opam-root: "${BASEDIR}/OPAM" @@ -1005,20 +1027,25 @@ roots: ["i-am-package.2" "i-am-sys-compiler.2"] 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 current +FMT_UPG Hard 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 +Perform the update and continue? [Y/n] y [NOTE] The 'jobs' option was reset, its value was 1 and its new value will vary according to the current number of cores on your machine. You can restore the fixed value using: opam option jobs=1 --global Format upgrade done. + +<><> Rerunning init and update ><><><><><><><><><><><><><><><><><><><><><><><><> +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE No cache found RSTATE loaded opam files from repo default in 0.000s <><> Updating repositories ><><><><><><><><><><><><><><><><><><><><><><><><><><> [default] no changes from file://${BASEDIR}/default +Update done, please now retry your command. +# Return code 10 # ### opam switch --short GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM ${BASEDIR} @@ -1129,7 +1156,9 @@ wrap-install-commands: ["%{hooks}%/sandbox.sh" "install"] {os = "linux" | os = " wrap-remove-commands: ["%{hooks}%/sandbox.sh" "remove"] {os = "linux" | os = "macos"} ### opam-cat $OPAMROOT/repo/repos-config opam-version: "2.0" -repositories: "default" {"file://${BASEDIR}/default"} +repo "default" { +url: "file://${BASEDIR}/default" +} ### opam-cat $OPAMROOT/sw-comp/.opam-switch/switch-config invariant: ["i-am-compiler"] opam-version: "2.0" @@ -1202,7 +1231,9 @@ wrap-install-commands: ["%{hooks}%/sandbox.sh" "install"] {os = "linux" | os = " wrap-remove-commands: ["%{hooks}%/sandbox.sh" "remove"] {os = "linux" | os = "macos"} ### opam-cat $OPAMROOT/repo/repos-config opam-version: "2.0" -repositories: "default" {"file://${BASEDIR}/default"} +repo "default" { +url: "file://${BASEDIR}/default" +} ### opam-cat _opam/.opam-switch/switch-config invariant: ["i-am-sys-compiler" | "i-am-compiler"] opam-root: "${BASEDIR}/OPAM" @@ -1278,7 +1309,9 @@ wrap-install-commands: ["%{hooks}%/sandbox.sh" "install"] {os = "linux" | os = " wrap-remove-commands: ["%{hooks}%/sandbox.sh" "remove"] {os = "linux" | os = "macos"} ### opam-cat $OPAMROOT/repo/repos-config opam-version: "2.0" -repositories: "default" {"file://${BASEDIR}/default"} +repo "default" { +url: "file://${BASEDIR}/default" +} ### opam-cat _opam/.opam-switch/switch-config invariant: ["i-am-sys-compiler" | "i-am-compiler"] opam-root: "${BASEDIR}/OPAM" @@ -1344,7 +1377,9 @@ swh-fallback: false switch: "sw-sys-comp" ### opam-cat $OPAMROOT/repo/repos-config opam-version: "2.0" -repositories: "default" {"file://${BASEDIR}/default"} +repo "default" { +url: "file://${BASEDIR}/default" +} ### opam-cat _opam/.opam-switch/switch-config invariant: ["i-am-sys-compiler" | "i-am-compiler"] opam-root: "${BASEDIR}/OPAM" @@ -1497,7 +1532,9 @@ wrap-install-commands: ["%{hooks}%/sandbox.sh" "install"] {os = "linux" | os = " wrap-remove-commands: ["%{hooks}%/sandbox.sh" "remove"] {os = "linux" | os = "macos"} ### opam-cat $OPAMROOT/repo/repos-config opam-version: "2.0" -repositories: "default" {"file://${BASEDIR}/default"} +repo "default" { +url: "file://${BASEDIR}/default" +} ### opam-cat $OPAMROOT/sw-comp/.opam-switch/switch-config invariant: ["i-am-compiler"] opam-version: "2.0" @@ -1572,7 +1609,9 @@ wrap-install-commands: ["%{hooks}%/sandbox.sh" "install"] {os = "linux" | os = " wrap-remove-commands: ["%{hooks}%/sandbox.sh" "remove"] {os = "linux" | os = "macos"} ### opam-cat $OPAMROOT/repo/repos-config opam-version: "2.0" -repositories: "default" {"file://${BASEDIR}/default"} +repo "default" { +url: "file://${BASEDIR}/default" +} ### opam-cat _opam/.opam-switch/switch-config invariant: ["i-am-sys-compiler" | "i-am-compiler"] opam-root: "${BASEDIR}/OPAM" @@ -1650,7 +1689,9 @@ wrap-install-commands: ["%{hooks}%/sandbox.sh" "install"] {os = "linux" | os = " wrap-remove-commands: ["%{hooks}%/sandbox.sh" "remove"] {os = "linux" | os = "macos"} ### opam-cat $OPAMROOT/repo/repos-config opam-version: "2.0" -repositories: "default" {"file://${BASEDIR}/default"} +repo "default" { +url: "file://${BASEDIR}/default" +} ### opam-cat _opam/.opam-switch/switch-config invariant: ["i-am-sys-compiler" | "i-am-compiler"] opam-root: "${BASEDIR}/OPAM" @@ -1716,7 +1757,9 @@ swh-fallback: false switch: "sw-sys-comp" ### opam-cat $OPAMROOT/repo/repos-config opam-version: "2.0" -repositories: "default" {"file://${BASEDIR}/default"} +repo "default" { +url: "file://${BASEDIR}/default" +} ### opam-cat _opam/.opam-switch/switch-config invariant: ["i-am-sys-compiler" | "i-am-compiler"] opam-root: "${BASEDIR}/OPAM" @@ -1794,16 +1837,31 @@ wrap-remove-commands: ["%{hooks}%/sandbox.sh" "remove"] {os = "linux" | os = "ma ### # ro global state ### opam option jobs | "${OPAMROOTVERSION}($|,)" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -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 | "${OPAMROOTVERSION}($|,)" -> "current" +[WARNING] Removing global switch 'this-internal-error' as it no longer exists +FMT_UPG Hard 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. + +Perform the update and continue? [Y/n] y +[NOTE] The 'jobs' option was reset, its value was 1 and its new value will vary according to the current number of cores on your machine. You can restore the fixed value using: + opam option jobs=1 --global +Format upgrade done. + +<><> Rerunning init and update ><><><><><><><><><><><><><><><><><><><><><><><><> GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -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 No cache found RSTATE loaded opam files from repo default in 0.000s + +<><> Updating repositories ><><><><><><><><><><><><><><><><><><><><><><><><><><> +[default] no changes from file://${BASEDIR}/default +Update done, please now retry your command. +# Return code 10 # +### # ro global state, ro repo state, ro switch state +### opam list | "${OPAMROOTVERSION}($|,)" -> "current" +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM +RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM +RSTATE Cache found STATE LOAD-SWITCH-STATE @ sw-sys-comp STATE Switch state loaded in 0.000s # Packages matching: installed @@ -1814,8 +1872,6 @@ 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 | "${OPAMROOTVERSION}($|,)" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -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 STATE LOAD-SWITCH-STATE @ sw-comp @@ -1832,15 +1888,6 @@ Done. ### # rw global state ### 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 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 -[NOTE] The 'jobs' option was reset, its value was 1 and its new value will vary according to the current number of cores on your machine. You can restore the fixed value using: - opam option jobs=1 --global -Format upgrade done. Set to '4' the field jobs in global configuration ### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" | grep -v sys-pkg-manager-cmd | grep -v global-variables | grep -v eval-variables: default-compiler: ["i-am-sys-compiler" "i-am-compiler"] @@ -1848,7 +1895,7 @@ default-invariant: ["i-am-sys-compiler"] depext: true depext-cannot-install: false depext-run-installs: true -download-jobs: 1 +download-jobs: 3 installed-switches: ["sw-sys-comp" "sw-comp" "default"] jobs: 4 opam-root-version: current @@ -1856,9 +1903,14 @@ opam-version: "2.0" repositories: "default" swh-fallback: false switch: "sw-sys-comp" +wrap-build-commands: ["%{hooks}%/sandbox.sh" "build"] {os = "linux" | os = "macos"} +wrap-install-commands: ["%{hooks}%/sandbox.sh" "install"] {os = "linux" | os = "macos"} +wrap-remove-commands: ["%{hooks}%/sandbox.sh" "remove"] {os = "linux" | os = "macos"} ### opam-cat $OPAMROOT/repo/repos-config opam-version: "2.0" -repositories: "default" {"file://${BASEDIR}/default"} +repo "default" { +url: "file://${BASEDIR}/default" +} ### opam-cat $OPAMROOT/sw-comp/.opam-switch/switch-config invariant: ["i-am-compiler"] opam-version: "2.0" @@ -1872,21 +1924,29 @@ roots: ["i-am-another-package.2" "i-am-compiler.2" "i-am-package.2"] ### ocaml generate.ml 2.1~rc local ### opam list | "${OPAMROOTVERSION}($|,)" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.1~rc to current -FMT_UPG Format upgrade done +[WARNING] Removing global switch 'this-internal-error' as it no longer exists +FMT_UPG Hard 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. + +Perform the update and continue? [Y/n] y +[NOTE] The 'jobs' option was reset, its value was 1 and its new value will vary according to the current number of cores on your machine. You can restore the fixed value using: + opam option jobs=1 --global +Format upgrade done. + +<><> Rerunning init and update ><><><><><><><><><><><><><><><><><><><><><><><><> +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE No cache found RSTATE loaded opam files from repo default in 0.000s -STATE LOAD-SWITCH-STATE @ ${BASEDIR} -STATE Switch state loaded in 0.000s -# Packages matching: installed -# Name # Installed # Synopsis -i-am-sys-compiler 2 One-line description + +<><> Updating repositories ><><><><><><><><><><><><><><><><><><><><><><><><><><> +[default] no changes from file://${BASEDIR}/default +Update done, please now retry your command. +# Return code 10 # ### # ro global state, ro repo state, rw switch state ### 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 current -FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE Cache found STATE LOAD-SWITCH-STATE @ ${BASEDIR} @@ -1904,15 +1964,6 @@ Done. ### # rw global state ### 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 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 -[NOTE] The 'jobs' option was reset, its value was 1 and its new value will vary according to the current number of cores on your machine. You can restore the fixed value using: - opam option jobs=1 --global -Format upgrade done. Set to '4' the field jobs in global configuration ### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" | grep -v sys-pkg-manager-cmd | grep -v global-variables | grep -v eval-variables: default-compiler: ["i-am-sys-compiler" "i-am-compiler"] @@ -1920,7 +1971,7 @@ default-invariant: ["i-am-sys-compiler"] depext: true depext-cannot-install: false depext-run-installs: true -download-jobs: 1 +download-jobs: 3 installed-switches: ["sw-sys-comp" "sw-comp" "${BASEDIR}" "default"] jobs: 4 opam-root-version: current @@ -1928,9 +1979,14 @@ opam-version: "2.0" repositories: "default" swh-fallback: false switch: "sw-sys-comp" +wrap-build-commands: ["%{hooks}%/sandbox.sh" "build"] {os = "linux" | os = "macos"} +wrap-install-commands: ["%{hooks}%/sandbox.sh" "install"] {os = "linux" | os = "macos"} +wrap-remove-commands: ["%{hooks}%/sandbox.sh" "remove"] {os = "linux" | os = "macos"} ### opam-cat $OPAMROOT/repo/repos-config opam-version: "2.0" -repositories: "default" {"file://${BASEDIR}/default"} +repo "default" { +url: "file://${BASEDIR}/default" +} ### opam-cat _opam/.opam-switch/switch-config invariant: ["i-am-sys-compiler" | "i-am-compiler"] opam-root: "${BASEDIR}/OPAM" @@ -1946,21 +2002,29 @@ roots: ["i-am-package.2" "i-am-sys-compiler.2"] ### ocaml generate.ml 2.1~rc local ### opam list | "${OPAMROOTVERSION}($|,)" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.1~rc to current -FMT_UPG Format upgrade done +[WARNING] Removing global switch 'this-internal-error' as it no longer exists +FMT_UPG Hard 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. + +Perform the update and continue? [Y/n] y +[NOTE] The 'jobs' option was reset, its value was 1 and its new value will vary according to the current number of cores on your machine. You can restore the fixed value using: + opam option jobs=1 --global +Format upgrade done. + +<><> Rerunning init and update ><><><><><><><><><><><><><><><><><><><><><><><><> +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE No cache found RSTATE loaded opam files from repo default in 0.000s -STATE LOAD-SWITCH-STATE @ ${BASEDIR} -STATE Switch state loaded in 0.000s -# Packages matching: installed -# Name # Installed # Synopsis -i-am-sys-compiler 2 One-line description + +<><> Updating repositories ><><><><><><><><><><><><><><><><><><><><><><><><><><> +[default] no changes from file://${BASEDIR}/default +Update done, please now retry your command. +# Return code 10 # ### # ro global state, ro repo state, rw switch state ### 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 current -FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE Cache found STATE LOAD-SWITCH-STATE @ ${BASEDIR} @@ -1978,15 +2042,6 @@ Done. ### # rw global state ### 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 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 -[NOTE] The 'jobs' option was reset, its value was 1 and its new value will vary according to the current number of cores on your machine. You can restore the fixed value using: - opam option jobs=1 --global -Format upgrade done. Set to '4' the field jobs in global configuration ### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" | grep -v sys-pkg-manager-cmd | grep -v global-variables | grep -v eval-variables: default-compiler: ["i-am-sys-compiler" "i-am-compiler"] @@ -1994,7 +2049,7 @@ default-invariant: ["i-am-sys-compiler"] depext: true depext-cannot-install: false depext-run-installs: true -download-jobs: 1 +download-jobs: 3 installed-switches: ["sw-sys-comp" "sw-comp" "${BASEDIR}" "default"] jobs: 4 opam-root-version: current @@ -2002,9 +2057,14 @@ opam-version: "2.0" repositories: "default" swh-fallback: false switch: "sw-sys-comp" +wrap-build-commands: ["%{hooks}%/sandbox.sh" "build"] {os = "linux" | os = "macos"} +wrap-install-commands: ["%{hooks}%/sandbox.sh" "install"] {os = "linux" | os = "macos"} +wrap-remove-commands: ["%{hooks}%/sandbox.sh" "remove"] {os = "linux" | os = "macos"} ### opam-cat $OPAMROOT/repo/repos-config opam-version: "2.0" -repositories: "default" {"file://${BASEDIR}/default"} +repo "default" { +url: "file://${BASEDIR}/default" +} ### opam-cat _opam/.opam-switch/switch-config invariant: ["i-am-sys-compiler" | "i-am-compiler"] opam-root: "${BASEDIR}/OPAM" @@ -2065,7 +2125,9 @@ swh-fallback: false switch: "sw-sys-comp" ### opam-cat $OPAMROOT/repo/repos-config opam-version: "2.0" -repositories: "default" {"file://${BASEDIR}/default"} +repo "default" { +url: "file://${BASEDIR}/default" +} ### opam-cat _opam/.opam-switch/switch-config invariant: ["i-am-sys-compiler" | "i-am-compiler"] opam-root: "${BASEDIR}/OPAM" @@ -2082,20 +2144,25 @@ roots: ["i-am-package.2" "i-am-sys-compiler.2"] 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 current +FMT_UPG Hard 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 +Perform the update and continue? [Y/n] y [NOTE] The 'jobs' option was reset, its value was 1 and its new value will vary according to the current number of cores on your machine. You can restore the fixed value using: opam option jobs=1 --global Format upgrade done. + +<><> Rerunning init and update ><><><><><><><><><><><><><><><><><><><><><><><><> +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE No cache found RSTATE loaded opam files from repo default in 0.000s <><> Updating repositories ><><><><><><><><><><><><><><><><><><><><><><><><><><> [default] no changes from file://${BASEDIR}/default +Update done, please now retry your command. +# Return code 10 # ### opam switch --short GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM ${BASEDIR} @@ -2132,18 +2199,33 @@ wrap-remove-commands: ["%{hooks}%/sandbox.sh" "remove"] {os = "linux" | os = "ma ### :V:5:a: From 2.1 root, global ### ocaml generate.ml 2.1 ### # ro global state -### opam option jobs | "${OPAMROOTVERSION}$" -> "current" +### opam option jobs | "${OPAMROOTVERSION}" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.1 to current -FMT_UPG Format upgrade done -### # ro global state, ro repo state, ro switch state -### opam list | "${OPAMROOTVERSION}$" -> "current" +[WARNING] Removing global switch 'this-internal-error' as it no longer exists +FMT_UPG Hard config upgrade, from 2.1 to current +This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.1 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 +[NOTE] The 'jobs' option was reset, its value was 1 and its new value will vary according to the current number of cores on your machine. You can restore the fixed value using: + opam option jobs=1 --global +Format upgrade done. + +<><> Rerunning init and update ><><><><><><><><><><><><><><><><><><><><><><><><> GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.1 to current -FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE No cache found RSTATE loaded opam files from repo default in 0.000s + +<><> Updating repositories ><><><><><><><><><><><><><><><><><><><><><><><><><><> +[default] no changes from file://${BASEDIR}/default +Update done, please now retry your command. +# Return code 10 # +### # ro global state, ro repo state, ro switch state +### opam list | "${OPAMROOTVERSION}$" -> "current" +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM +RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM +RSTATE Cache found STATE LOAD-SWITCH-STATE @ sw-sys-comp STATE Switch state loaded in 0.000s # Packages matching: installed @@ -2154,8 +2236,6 @@ 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 | "${OPAMROOTVERSION}$" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.1 to current -FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE Cache found STATE LOAD-SWITCH-STATE @ sw-comp @@ -2172,8 +2252,6 @@ Done. ### # ro global state, rw repo state ### opam repo add root-config ./root-config | "${OPAMROOTVERSION}$" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.1 to current -FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE Cache found [root-config] Initialised @@ -2183,15 +2261,6 @@ RSTATE Cache found ### # rw global state ### 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 to current -This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.1 to version current which can't be reverted. -You may want to back it up before going further. - -Continue? [Y/n] y -[NOTE] The 'jobs' option was reset, its value was 1 and its new value will vary according to the current number of cores on your machine. You can restore the fixed value using: - opam option jobs=1 --global -Format upgrade done. Set to '4' the field jobs in global configuration ### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" | grep -v sys-pkg-manager-cmd | grep -v global-variables | grep -v eval-variables: default-compiler: ["i-am-sys-compiler" "i-am-compiler"] @@ -2199,7 +2268,7 @@ default-invariant: ["i-am-sys-compiler"] depext: true depext-cannot-install: false depext-run-installs: true -download-jobs: 1 +download-jobs: 3 installed-switches: ["sw-sys-comp" "sw-comp" "default"] jobs: 4 opam-root-version: current @@ -2207,9 +2276,17 @@ opam-version: "2.0" repositories: "default" swh-fallback: false switch: "sw-sys-comp" +wrap-build-commands: ["%{hooks}%/sandbox.sh" "build"] {os = "linux" | os = "macos"} +wrap-install-commands: ["%{hooks}%/sandbox.sh" "install"] {os = "linux" | os = "macos"} +wrap-remove-commands: ["%{hooks}%/sandbox.sh" "remove"] {os = "linux" | os = "macos"} ### opam-cat $OPAMROOT/repo/repos-config opam-version: "2.0" -repositories: ["default" {"file://${BASEDIR}/default"} "root-config" {"file://${BASEDIR}/root-config"}] +repo "default" { +url: "file://${BASEDIR}/default" +} +repo "root-config" { +url: "file://${BASEDIR}/root-config" +} ### opam-cat $OPAMROOT/sw-comp/.opam-switch/switch-config invariant: ["i-am-compiler"] opam-version: "2.0" @@ -2223,20 +2300,28 @@ roots: ["i-am-another-package.2" "i-am-compiler.2" "i-am-package.2"] ### ocaml generate.ml 2.1 local ### opam list | "${OPAMROOTVERSION}($|,)" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.1 to current -FMT_UPG Format upgrade done +[WARNING] Removing global switch 'this-internal-error' as it no longer exists +FMT_UPG Hard config upgrade, from 2.1 to current +This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.1 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 +[NOTE] The 'jobs' option was reset, its value was 1 and its new value will vary according to the current number of cores on your machine. You can restore the fixed value using: + opam option jobs=1 --global +Format upgrade done. + +<><> Rerunning init and update ><><><><><><><><><><><><><><><><><><><><><><><><> +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE No cache found RSTATE loaded opam files from repo default in 0.000s -STATE LOAD-SWITCH-STATE @ ${BASEDIR} -STATE Switch state loaded in 0.000s -# Packages matching: installed -# Name # Installed # Synopsis -i-am-sys-compiler 2 One-line description + +<><> Updating repositories ><><><><><><><><><><><><><><><><><><><><><><><><><><> +[default] no changes from file://${BASEDIR}/default +Update done, please now retry your command. +# Return code 10 # ### opam install i-am-package | "${OPAMROOTVERSION}$" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.1 to current -FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE Cache found STATE LOAD-SWITCH-STATE @ ${BASEDIR} @@ -2254,15 +2339,6 @@ Done. ### # rw global state ### 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 to current -This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.1 to version current which can't be reverted. -You may want to back it up before going further. - -Continue? [Y/n] y -[NOTE] The 'jobs' option was reset, its value was 1 and its new value will vary according to the current number of cores on your machine. You can restore the fixed value using: - opam option jobs=1 --global -Format upgrade done. Set to '4' the field jobs in global configuration ### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" | grep -v sys-pkg-manager-cmd | grep -v global-variables | grep -v eval-variables: default-compiler: ["i-am-sys-compiler" "i-am-compiler"] @@ -2270,7 +2346,7 @@ default-invariant: ["i-am-sys-compiler"] depext: true depext-cannot-install: false depext-run-installs: true -download-jobs: 1 +download-jobs: 3 installed-switches: ["sw-sys-comp" "sw-comp" "${BASEDIR}" "default"] jobs: 4 opam-root-version: current @@ -2278,9 +2354,14 @@ opam-version: "2.0" repositories: "default" swh-fallback: false switch: "sw-sys-comp" +wrap-build-commands: ["%{hooks}%/sandbox.sh" "build"] {os = "linux" | os = "macos"} +wrap-install-commands: ["%{hooks}%/sandbox.sh" "install"] {os = "linux" | os = "macos"} +wrap-remove-commands: ["%{hooks}%/sandbox.sh" "remove"] {os = "linux" | os = "macos"} ### opam-cat $OPAMROOT/repo/repos-config opam-version: "2.0" -repositories: "default" {"file://${BASEDIR}/default"} +repo "default" { +url: "file://${BASEDIR}/default" +} ### opam-cat _opam/.opam-switch/switch-config invariant: ["i-am-sys-compiler" | "i-am-compiler"] opam-root: "${BASEDIR}/OPAM" @@ -2296,21 +2377,29 @@ roots: ["i-am-package.2" "i-am-sys-compiler.2"] ### # ro global state, ro repo state, ro switch state ### opam list | "${OPAMROOTVERSION}($|,)" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.1 to current -FMT_UPG Format upgrade done +[WARNING] Removing global switch 'this-internal-error' as it no longer exists +FMT_UPG Hard config upgrade, from 2.1 to current +This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.1 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 +[NOTE] The 'jobs' option was reset, its value was 1 and its new value will vary according to the current number of cores on your machine. You can restore the fixed value using: + opam option jobs=1 --global +Format upgrade done. + +<><> Rerunning init and update ><><><><><><><><><><><><><><><><><><><><><><><><> +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE No cache found RSTATE loaded opam files from repo default in 0.000s -STATE LOAD-SWITCH-STATE @ ${BASEDIR} -STATE Switch state loaded in 0.000s -# Packages matching: installed -# Name # Installed # Synopsis -i-am-sys-compiler 2 One-line description + +<><> Updating repositories ><><><><><><><><><><><><><><><><><><><><><><><><><><> +[default] no changes from file://${BASEDIR}/default +Update done, please now retry your command. +# Return code 10 # ### # ro global state, ro repo state, rw switch state ### opam install i-am-package | "${OPAMROOTVERSION}($|,)" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.1 to current -FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE Cache found STATE LOAD-SWITCH-STATE @ ${BASEDIR} @@ -2327,15 +2416,6 @@ Done. ### # rw global state ### 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 to current -This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.1 to version current which can't be reverted. -You may want to back it up before going further. - -Continue? [Y/n] y -[NOTE] The 'jobs' option was reset, its value was 1 and its new value will vary according to the current number of cores on your machine. You can restore the fixed value using: - opam option jobs=1 --global -Format upgrade done. Set to '4' the field jobs in global configuration ### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" | grep -v sys-pkg-manager-cmd | grep -v global-variables | grep -v eval-variables: default-compiler: ["i-am-sys-compiler" "i-am-compiler"] @@ -2343,7 +2423,7 @@ default-invariant: ["i-am-sys-compiler"] depext: true depext-cannot-install: false depext-run-installs: true -download-jobs: 1 +download-jobs: 3 installed-switches: ["sw-sys-comp" "sw-comp" "${BASEDIR}" "default"] jobs: 4 opam-root-version: current @@ -2351,9 +2431,14 @@ opam-version: "2.0" repositories: "default" swh-fallback: false switch: "sw-sys-comp" +wrap-build-commands: ["%{hooks}%/sandbox.sh" "build"] {os = "linux" | os = "macos"} +wrap-install-commands: ["%{hooks}%/sandbox.sh" "install"] {os = "linux" | os = "macos"} +wrap-remove-commands: ["%{hooks}%/sandbox.sh" "remove"] {os = "linux" | os = "macos"} ### opam-cat $OPAMROOT/repo/repos-config opam-version: "2.0" -repositories: "default" {"file://${BASEDIR}/default"} +repo "default" { +url: "file://${BASEDIR}/default" +} ### opam-cat _opam/.opam-switch/switch-config invariant: ["i-am-sys-compiler" | "i-am-compiler"] opam-root: "${BASEDIR}/OPAM" @@ -2367,23 +2452,31 @@ roots: ["i-am-package.2" "i-am-sys-compiler.2"] ### :V:5:d: Upgraded root and local 2.1 switch not recorded ### ocaml generate.ml 2.1 orphaned 2.1 ### # ro global state, ro repo state, ro switch state -### opam list | "${OPAMROOTVERSION}$" -> "current" +### 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 to current +This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.1 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 +[NOTE] The 'jobs' option was reset, its value was 1 and its new value will vary according to the current number of cores on your machine. You can restore the fixed value using: + opam option jobs=1 --global +Format upgrade done. + +<><> Rerunning init and update ><><><><><><><><><><><><><><><><><><><><><><><><> GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.1 to current -FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE No cache found RSTATE loaded opam files from repo default in 0.000s -STATE LOAD-SWITCH-STATE @ ${BASEDIR} -STATE Switch state loaded in 0.000s -# Packages matching: installed -# Name # Installed # Synopsis -i-am-sys-compiler 2 One-line description + +<><> Updating repositories ><><><><><><><><><><><><><><><><><><><><><><><><><><> +[default] no changes from file://${BASEDIR}/default +Update done, please now retry your command. +# Return code 10 # ### # ro global state, ro repo state, rw switch state ### opam install i-am-package | "${OPAMROOTVERSION}$" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.1 to current -FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE Cache found STATE LOAD-SWITCH-STATE @ ${BASEDIR} @@ -2400,15 +2493,6 @@ Done. ### # rw global state ### 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 to current -This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.1 to version current which can't be reverted. -You may want to back it up before going further. - -Continue? [Y/n] y -[NOTE] The 'jobs' option was reset, its value was 1 and its new value will vary according to the current number of cores on your machine. You can restore the fixed value using: - opam option jobs=1 --global -Format upgrade done. Set to '4' the field jobs in global configuration ### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" | grep -v sys-pkg-manager-cmd | grep -v global-variables | grep -v eval-variables: default-compiler: ["i-am-sys-compiler" "i-am-compiler"] @@ -2416,7 +2500,7 @@ default-invariant: ["i-am-sys-compiler"] depext: true depext-cannot-install: false depext-run-installs: true -download-jobs: 1 +download-jobs: 3 installed-switches: ["sw-sys-comp" "sw-comp" "default"] jobs: 4 opam-root-version: current @@ -2424,9 +2508,14 @@ opam-version: "2.0" repositories: "default" swh-fallback: false switch: "sw-sys-comp" +wrap-build-commands: ["%{hooks}%/sandbox.sh" "build"] {os = "linux" | os = "macos"} +wrap-install-commands: ["%{hooks}%/sandbox.sh" "install"] {os = "linux" | os = "macos"} +wrap-remove-commands: ["%{hooks}%/sandbox.sh" "remove"] {os = "linux" | os = "macos"} ### opam-cat $OPAMROOT/repo/repos-config opam-version: "2.0" -repositories: "default" {"file://${BASEDIR}/default"} +repo "default" { +url: "file://${BASEDIR}/default" +} ### opam-cat _opam/.opam-switch/switch-config invariant: ["i-am-sys-compiler" | "i-am-compiler"] opam-root: "${BASEDIR}/OPAM" @@ -2443,20 +2532,25 @@ roots: ["i-am-package.2" "i-am-sys-compiler.2"] 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 to current +FMT_UPG Hard config upgrade, from 2.1 to current This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.1 to version current which can't be reverted. You may want to back it up before going further. -Continue? [Y/n] y +Perform the update and continue? [Y/n] y [NOTE] The 'jobs' option was reset, its value was 1 and its new value will vary according to the current number of cores on your machine. You can restore the fixed value using: opam option jobs=1 --global Format upgrade done. + +<><> Rerunning init and update ><><><><><><><><><><><><><><><><><><><><><><><><> +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE No cache found RSTATE loaded opam files from repo default in 0.000s <><> Updating repositories ><><><><><><><><><><><><><><><><><><><><><><><><><><> [default] no changes from file://${BASEDIR}/default +Update done, please now retry your command. +# Return code 10 # ### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" | grep -v sys-pkg-manager-cmd | grep -v global-variables | grep -v eval-variables: default-compiler: ["i-am-sys-compiler" "i-am-compiler"] default-invariant: ["i-am-sys-compiler"] @@ -2493,18 +2587,33 @@ i-am-sys-compiler 2 One-line description ### :V:6:a: From 2.2~alpha root, global ### ocaml generate.ml 2.2~alpha ### # ro global state -### opam option jobs | "${OPAMROOTVERSION}$" -> "current" +### opam option jobs | "${OPAMROOTVERSION}" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.2~alpha to current -FMT_UPG Format upgrade done -### # ro global state, ro repo state, ro switch state -### opam list | "${OPAMROOTVERSION}$" -> "current" +[WARNING] Removing global switch 'this-internal-error' as it no longer exists +FMT_UPG Hard config upgrade, from 2.2~alpha to current +This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.2~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 +[NOTE] The 'jobs' option was reset, its value was 1 and its new value will vary according to the current number of cores on your machine. You can restore the fixed value using: + opam option jobs=1 --global +Format upgrade done. + +<><> Rerunning init and update ><><><><><><><><><><><><><><><><><><><><><><><><> GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.2~alpha to current -FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE No cache found RSTATE loaded opam files from repo default in 0.000s + +<><> Updating repositories ><><><><><><><><><><><><><><><><><><><><><><><><><><> +[default] no changes from file://${BASEDIR}/default +Update done, please now retry your command. +# Return code 10 # +### # ro global state, ro repo state, ro switch state +### opam list | "${OPAMROOTVERSION}$" -> "current" +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM +RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM +RSTATE Cache found STATE LOAD-SWITCH-STATE @ sw-sys-comp STATE Switch state loaded in 0.000s # Packages matching: installed @@ -2515,8 +2624,6 @@ 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 | "${OPAMROOTVERSION}$" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.2~alpha to current -FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE Cache found STATE LOAD-SWITCH-STATE @ sw-comp @@ -2533,8 +2640,6 @@ Done. ### # ro global state, rw repo state ### opam repo add root-config ./root-config | "${OPAMROOTVERSION}$" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.2~alpha to current -FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE Cache found [root-config] Initialised @@ -2544,15 +2649,6 @@ RSTATE Cache found ### # rw global state ### 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.2~alpha to current -This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.2~alpha to version current which can't be reverted. -You may want to back it up before going further. - -Continue? [Y/n] y -[NOTE] The 'jobs' option was reset, its value was 1 and its new value will vary according to the current number of cores on your machine. You can restore the fixed value using: - opam option jobs=1 --global -Format upgrade done. Set to '4' the field jobs in global configuration ### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" | grep -v sys-pkg-manager-cmd | grep -v global-variables default-compiler: ["i-am-sys-compiler" "i-am-compiler"] @@ -2560,7 +2656,7 @@ default-invariant: ["i-am-sys-compiler"] depext: true depext-cannot-install: false depext-run-installs: true -download-jobs: 1 +download-jobs: 3 eval-variables: [sys-comp-version ["sh" "-c" "echo $OPAMSYSCOMP"] "comp version"] installed-switches: ["sw-sys-comp" "sw-comp" "default"] jobs: 4 @@ -2569,9 +2665,17 @@ opam-version: "2.0" repositories: "default" swh-fallback: false switch: "sw-sys-comp" +wrap-build-commands: ["%{hooks}%/sandbox.sh" "build"] {os = "linux" | os = "macos"} +wrap-install-commands: ["%{hooks}%/sandbox.sh" "install"] {os = "linux" | os = "macos"} +wrap-remove-commands: ["%{hooks}%/sandbox.sh" "remove"] {os = "linux" | os = "macos"} ### opam-cat $OPAMROOT/repo/repos-config opam-version: "2.0" -repositories: ["default" {"file://${BASEDIR}/default"} "root-config" {"file://${BASEDIR}/root-config"}] +repo "default" { +url: "file://${BASEDIR}/default" +} +repo "root-config" { +url: "file://${BASEDIR}/root-config" +} ### opam-cat $OPAMROOT/sw-comp/.opam-switch/switch-config invariant: ["i-am-compiler"] opam-version: "2.0" @@ -2585,21 +2689,29 @@ roots: ["i-am-another-package.2" "i-am-compiler.2" "i-am-package.2"] ### ocaml generate.ml 2.2~alpha local ### opam list | "${OPAMROOTVERSION}($|,)" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.2~alpha to current -FMT_UPG Format upgrade done +[WARNING] Removing global switch 'this-internal-error' as it no longer exists +FMT_UPG Hard config upgrade, from 2.2~alpha to current +This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.2~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 +[NOTE] The 'jobs' option was reset, its value was 1 and its new value will vary according to the current number of cores on your machine. You can restore the fixed value using: + opam option jobs=1 --global +Format upgrade done. + +<><> Rerunning init and update ><><><><><><><><><><><><><><><><><><><><><><><><> +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE No cache found RSTATE loaded opam files from repo default in 0.000s -STATE LOAD-SWITCH-STATE @ ${BASEDIR} -STATE Switch state loaded in 0.000s -# Packages matching: installed -# Name # Installed # Synopsis -i-am-sys-compiler 2 One-line description + +<><> Updating repositories ><><><><><><><><><><><><><><><><><><><><><><><><><><> +[default] no changes from file://${BASEDIR}/default +Update done, please now retry your command. +# Return code 10 # ### # ro global state, ro repo state, rw switch state ### opam install i-am-package | "${OPAMROOTVERSION}$" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.2~alpha to current -FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE Cache found STATE LOAD-SWITCH-STATE @ ${BASEDIR} @@ -2617,15 +2729,83 @@ Done. ### # rw global state ### opam option jobs=4 | "${OPAMROOTVERSION}($|,)" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM +Set to '4' the field jobs in global configuration +### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" | grep -v sys-pkg-manager-cmd | grep -v global-variables +default-compiler: ["i-am-sys-compiler" "i-am-compiler"] +default-invariant: ["i-am-sys-compiler"] +depext: true +depext-cannot-install: false +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"] +jobs: 4 +opam-root-version: current +opam-version: "2.0" +repositories: "default" +swh-fallback: false +switch: "sw-sys-comp" +wrap-build-commands: ["%{hooks}%/sandbox.sh" "build"] {os = "linux" | os = "macos"} +wrap-install-commands: ["%{hooks}%/sandbox.sh" "install"] {os = "linux" | os = "macos"} +wrap-remove-commands: ["%{hooks}%/sandbox.sh" "remove"] {os = "linux" | os = "macos"} +### opam-cat $OPAMROOT/repo/repos-config +opam-version: "2.0" +repo "default" { +url: "file://${BASEDIR}/default" +} +### opam-cat _opam/.opam-switch/switch-config +invariant: ["i-am-sys-compiler" | "i-am-compiler"] +opam-root: "${BASEDIR}/OPAM" +opam-version: "2.0" +synopsis: "local switch" +### opam-cat _opam/.opam-switch/switch-state +compiler: ["i-am-sys-compiler.2"] +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:6:c: From 2.2~alpha root, local unknown from config +### ocaml generate.ml 2.2~alpha local +### opam list | "${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.2~alpha to current +FMT_UPG Hard config upgrade, from 2.2~alpha to current This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.2~alpha to version current which can't be reverted. You may want to back it up before going further. -Continue? [Y/n] y +Perform the update and continue? [Y/n] y [NOTE] The 'jobs' option was reset, its value was 1 and its new value will vary according to the current number of cores on your machine. You can restore the fixed value using: opam option jobs=1 --global Format upgrade done. + +<><> Rerunning init and update ><><><><><><><><><><><><><><><><><><><><><><><><> +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM +RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM +RSTATE No cache found +RSTATE loaded opam files from repo default in 0.000s + +<><> Updating repositories ><><><><><><><><><><><><><><><><><><><><><><><><><><> +[default] no changes from file://${BASEDIR}/default +Update done, please now retry your command. +# Return code 10 # +### # ro global state, ro repo state, rw switch state +### opam install i-am-package | "${OPAMROOTVERSION}($|,)" -> "current" +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM +RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM +RSTATE Cache found +STATE LOAD-SWITCH-STATE @ ${BASEDIR} +STATE Switch state loaded in 0.000s +STATE Detected changed packages (marked for reinstall): {} +The following actions will be performed: +=== install 1 package + - install i-am-package 2 + +<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><> +-> installed i-am-package.2 +STATE dependencies (0.000) result={ i-am-sys-compiler.2 } +Done. +### # rw global state +### opam option jobs=4 | "${OPAMROOTVERSION}($|,)" -> "current" +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM Set to '4' the field jobs in global configuration ### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" | grep -v sys-pkg-manager-cmd | grep -v global-variables default-compiler: ["i-am-sys-compiler" "i-am-compiler"] @@ -2633,7 +2813,7 @@ default-invariant: ["i-am-sys-compiler"] depext: true depext-cannot-install: false depext-run-installs: true -download-jobs: 1 +download-jobs: 3 eval-variables: [sys-comp-version ["sh" "-c" "echo $OPAMSYSCOMP"] "comp version"] installed-switches: ["sw-sys-comp" "sw-comp" "${BASEDIR}" "default"] jobs: 4 @@ -2642,9 +2822,14 @@ opam-version: "2.0" repositories: "default" swh-fallback: false switch: "sw-sys-comp" +wrap-build-commands: ["%{hooks}%/sandbox.sh" "build"] {os = "linux" | os = "macos"} +wrap-install-commands: ["%{hooks}%/sandbox.sh" "install"] {os = "linux" | os = "macos"} +wrap-remove-commands: ["%{hooks}%/sandbox.sh" "remove"] {os = "linux" | os = "macos"} ### opam-cat $OPAMROOT/repo/repos-config opam-version: "2.0" -repositories: "default" {"file://${BASEDIR}/default"} +repo "default" { +url: "file://${BASEDIR}/default" +} ### opam-cat _opam/.opam-switch/switch-config invariant: ["i-am-sys-compiler" | "i-am-compiler"] opam-root: "${BASEDIR}/OPAM" @@ -2655,25 +2840,343 @@ compiler: ["i-am-sys-compiler.2"] 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:6:c: From 2.2~alpha root, local unknown from config -### ocaml generate.ml 2.2~alpha local +### :V:6:d: Upgraded root and local 2.2~alpha switch not recorded +### ocaml generate.ml 2.2~alpha orphaned 2.2~alpha +### # ro global state, ro repo state, ro switch state +### 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.2~alpha to current +This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.2~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 +[NOTE] The 'jobs' option was reset, its value was 1 and its new value will vary according to the current number of cores on your machine. You can restore the fixed value using: + opam option jobs=1 --global +Format upgrade done. + +<><> Rerunning init and update ><><><><><><><><><><><><><><><><><><><><><><><><> +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM +RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM +RSTATE No cache found +RSTATE loaded opam files from repo default in 0.000s + +<><> Updating repositories ><><><><><><><><><><><><><><><><><><><><><><><><><><> +[default] no changes from file://${BASEDIR}/default +Update done, please now retry your command. +# Return code 10 # +### # ro global state, ro repo state, rw switch state +### opam install i-am-package | "${OPAMROOTVERSION}$" -> "current" +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM +RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM +RSTATE Cache found +STATE LOAD-SWITCH-STATE @ ${BASEDIR} +STATE Switch state loaded in 0.000s +STATE Detected changed packages (marked for reinstall): {} +The following actions will be performed: +=== install 1 package + - install i-am-package 2 + +<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><> +-> installed i-am-package.2 +STATE dependencies (0.000) result={ i-am-sys-compiler.2 } +Done. +### # rw global state +### opam option jobs=4 | "${OPAMROOTVERSION}($|,)" -> "current" +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM +Set to '4' the field jobs in global configuration +### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" | grep -v sys-pkg-manager-cmd | grep -v global-variables +default-compiler: ["i-am-sys-compiler" "i-am-compiler"] +default-invariant: ["i-am-sys-compiler"] +depext: true +depext-cannot-install: false +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"] +jobs: 4 +opam-root-version: current +opam-version: "2.0" +repositories: "default" +swh-fallback: false +switch: "sw-sys-comp" +wrap-build-commands: ["%{hooks}%/sandbox.sh" "build"] {os = "linux" | os = "macos"} +wrap-install-commands: ["%{hooks}%/sandbox.sh" "install"] {os = "linux" | os = "macos"} +wrap-remove-commands: ["%{hooks}%/sandbox.sh" "remove"] {os = "linux" | os = "macos"} +### opam-cat $OPAMROOT/repo/repos-config +opam-version: "2.0" +repo "default" { +url: "file://${BASEDIR}/default" +} +### opam-cat _opam/.opam-switch/switch-config +invariant: ["i-am-sys-compiler" | "i-am-compiler"] +opam-root: "${BASEDIR}/OPAM" +opam-version: "2.0" +synopsis: "local switch" +### opam-cat _opam/.opam-switch/switch-state +compiler: ["i-am-sys-compiler.2"] +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:6:e: reinit from 2.2~alpha +### ocaml generate.ml 2.2~alpha +### opam init --reinit --bypass-checks --no-setup | grep -v Cygwin | "${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.2~alpha to current +This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.2~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 +[NOTE] The 'jobs' option was reset, its value was 1 and its new value will vary according to the current number of cores on your machine. You can restore the fixed value using: + opam option jobs=1 --global +Format upgrade done. + +<><> Rerunning init and update ><><><><><><><><><><><><><><><><><><><><><><><><> +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM +RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM +RSTATE No cache found +RSTATE loaded opam files from repo default in 0.000s + +<><> Updating repositories ><><><><><><><><><><><><><><><><><><><><><><><><><><> +[default] no changes from file://${BASEDIR}/default +Update done, please now retry your command. +# Return code 10 # +### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" | grep -v sys-pkg-manager-cmd | grep -v global-variables +default-compiler: ["i-am-sys-compiler" "i-am-compiler"] +default-invariant: ["i-am-sys-compiler"] +depext: true +depext-cannot-install: false +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: current +opam-version: "2.0" +repositories: "default" +swh-fallback: false +switch: "sw-sys-comp" +wrap-build-commands: ["%{hooks}%/sandbox.sh" "build"] {os = "linux" | os = "macos"} +wrap-install-commands: ["%{hooks}%/sandbox.sh" "install"] {os = "linux" | os = "macos"} +wrap-remove-commands: ["%{hooks}%/sandbox.sh" "remove"] {os = "linux" | os = "macos"} +### opam switch --short +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM +${BASEDIR} +default +sw-comp +sw-sys-comp +### opam list +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM +RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM +RSTATE Cache found +STATE LOAD-SWITCH-STATE @ ${BASEDIR} +STATE Switch state loaded in 0.000s +# Packages matching: installed +# Name # Installed # Synopsis +i-am-package 2 One-line description +i-am-sys-compiler 2 One-line description +### rm -rf _opam +### :V:7:a: From 2.2~beta root, global +### ocaml generate.ml 2.2~beta +### # ro global state +### opam option jobs | "${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.2~beta to current +This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.2~beta 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 +Format upgrade done. + +<><> Rerunning init and update ><><><><><><><><><><><><><><><><><><><><><><><><> +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM +RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM +RSTATE No cache found +RSTATE loaded opam files from repo default in 0.000s + +<><> Updating repositories ><><><><><><><><><><><><><><><><><><><><><><><><><><> +[default] no changes from file://${BASEDIR}/default +Update done, please now retry your command. +# Return code 10 # +### # ro global state, ro repo state, ro switch state +### opam list | "${OPAMROOTVERSION}$" -> "current" +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM +RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM +RSTATE Cache found +STATE LOAD-SWITCH-STATE @ sw-sys-comp +STATE Switch state loaded in 0.000s +# Packages matching: installed +# Name # Installed # Synopsis +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 | "${OPAMROOTVERSION}$" -> "current" +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM +RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM +RSTATE Cache found +STATE LOAD-SWITCH-STATE @ sw-comp +STATE Switch state loaded in 0.000s +STATE Detected changed packages (marked for reinstall): {} +The following actions will be performed: +=== install 1 package + - install i-am-another-package 2 + +<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><> +-> installed i-am-another-package.2 +STATE dependencies (0.000) result={ i-am-compiler.2 } +Done. +### # ro global state, rw repo state +### opam repo add root-config ./root-config | "${OPAMROOTVERSION}$" -> "current" +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM +RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM +RSTATE Cache found +[root-config] Initialised +[NOTE] Repository root-config has been added to the selections of switch sw-sys-comp only. + Run `opam repository add root-config --all-switches|--set-default' to use it in all existing switches, or in newly created switches, respectively. + +### # rw global state +### opam option jobs=4 | "${OPAMROOTVERSION}$" -> "current" +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM +Set to '4' the field jobs in global configuration +### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" | grep -v sys-pkg-manager-cmd | grep -v global-variables +default-compiler: ["i-am-sys-compiler" "i-am-compiler"] +default-invariant: ["i-am-sys-compiler"] +depext: true +depext-cannot-install: false +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"] +jobs: 4 +opam-root-version: current +opam-version: "2.0" +repositories: "default" +swh-fallback: false +switch: "sw-sys-comp" +wrap-build-commands: ["%{hooks}%/sandbox.sh" "build"] {os = "linux" | os = "macos"} +wrap-install-commands: ["%{hooks}%/sandbox.sh" "install"] {os = "linux" | os = "macos"} +wrap-remove-commands: ["%{hooks}%/sandbox.sh" "remove"] {os = "linux" | os = "macos"} +### opam-cat $OPAMROOT/repo/repos-config +opam-version: "2.0" +repo "default" { +url: "file://${BASEDIR}/default" +} +repo "root-config" { +url: "file://${BASEDIR}/root-config" +} +### opam-cat $OPAMROOT/sw-comp/.opam-switch/switch-config +invariant: ["i-am-compiler"] +opam-version: "2.0" +synopsis: "switch with compiler" +### opam-cat $OPAMROOT/sw-comp/.opam-switch/switch-state +compiler: ["i-am-compiler.2"] +installed: ["i-am-another-package.2" "i-am-compiler.2" "i-am-package.2"] +opam-version: "2.0" +roots: ["i-am-another-package.2" "i-am-compiler.2" "i-am-package.2"] +### :V:7:b: From 2.2~beta root, local +### ocaml generate.ml 2.2~beta local +### 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.2~beta to current +This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.2~beta 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 +Format upgrade done. + +<><> Rerunning init and update ><><><><><><><><><><><><><><><><><><><><><><><><> +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM +RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM +RSTATE No cache found +RSTATE loaded opam files from repo default in 0.000s + +<><> Updating repositories ><><><><><><><><><><><><><><><><><><><><><><><><><><> +[default] no changes from file://${BASEDIR}/default +Update done, please now retry your command. +# Return code 10 # +### # ro global state, ro repo state, rw switch state +### opam install i-am-package | "${OPAMROOTVERSION}$" -> "current" +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM +RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM +RSTATE Cache found +STATE LOAD-SWITCH-STATE @ ${BASEDIR} +STATE Definition missing for installed package i-am-sys-compiler.2, copying from repo +STATE Switch state loaded in 0.000s +STATE Detected changed packages (marked for reinstall): {} +The following actions will be performed: +=== install 1 package + - install i-am-package 2 + +<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><> +-> installed i-am-package.2 +STATE dependencies (0.000) result={ i-am-sys-compiler.2 } +Done. +### # rw global state +### opam option jobs=4 | "${OPAMROOTVERSION}$" -> "current" +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM +Set to '4' the field jobs in global configuration +### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" | grep -v sys-pkg-manager-cmd | grep -v global-variables +default-compiler: ["i-am-sys-compiler" "i-am-compiler"] +default-invariant: ["i-am-sys-compiler"] +depext: true +depext-cannot-install: false +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"] +jobs: 4 +opam-root-version: current +opam-version: "2.0" +repositories: "default" +swh-fallback: false +switch: "sw-sys-comp" +wrap-build-commands: ["%{hooks}%/sandbox.sh" "build"] {os = "linux" | os = "macos"} +wrap-install-commands: ["%{hooks}%/sandbox.sh" "install"] {os = "linux" | os = "macos"} +wrap-remove-commands: ["%{hooks}%/sandbox.sh" "remove"] {os = "linux" | os = "macos"} +### opam-cat $OPAMROOT/repo/repos-config +opam-version: "2.0" +repo "default" { +url: "file://${BASEDIR}/default" +} +### opam-cat _opam/.opam-switch/switch-config +invariant: ["i-am-sys-compiler" | "i-am-compiler"] +opam-root: "${BASEDIR}/OPAM" +opam-version: "2.0" +synopsis: "local switch" +### opam-cat _opam/.opam-switch/switch-state +compiler: ["i-am-sys-compiler.2"] +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:7:c: From 2.2~beta root, local unknown from config +### ocaml generate.ml 2.2~beta local ### opam list | "${OPAMROOTVERSION}($|,)" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.2~alpha to current -FMT_UPG Format upgrade done +[WARNING] Removing global switch 'this-internal-error' as it no longer exists +FMT_UPG Hard config upgrade, from 2.2~beta to current +This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.2~beta 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 +Format upgrade done. + +<><> Rerunning init and update ><><><><><><><><><><><><><><><><><><><><><><><><> +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE No cache found RSTATE loaded opam files from repo default in 0.000s -STATE LOAD-SWITCH-STATE @ ${BASEDIR} -STATE Switch state loaded in 0.000s -# Packages matching: installed -# Name # Installed # Synopsis -i-am-sys-compiler 2 One-line description + +<><> Updating repositories ><><><><><><><><><><><><><><><><><><><><><><><><><><> +[default] no changes from file://${BASEDIR}/default +Update done, please now retry your command. +# Return code 10 # ### # ro global state, ro repo state, rw switch state ### opam install i-am-package | "${OPAMROOTVERSION}($|,)" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.2~alpha to current -FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE Cache found STATE LOAD-SWITCH-STATE @ ${BASEDIR} @@ -2688,17 +3191,8 @@ The following actions will be performed: STATE dependencies (0.000) result={ i-am-sys-compiler.2 } Done. ### # rw global state -### opam option jobs=4 | "${OPAMROOTVERSION}($|,)" -> "current" +### 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.2~alpha to current -This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.2~alpha to version current which can't be reverted. -You may want to back it up before going further. - -Continue? [Y/n] y -[NOTE] The 'jobs' option was reset, its value was 1 and its new value will vary according to the current number of cores on your machine. You can restore the fixed value using: - opam option jobs=1 --global -Format upgrade done. Set to '4' the field jobs in global configuration ### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" | grep -v sys-pkg-manager-cmd | grep -v global-variables default-compiler: ["i-am-sys-compiler" "i-am-compiler"] @@ -2706,7 +3200,7 @@ default-invariant: ["i-am-sys-compiler"] depext: true depext-cannot-install: false depext-run-installs: true -download-jobs: 1 +download-jobs: 3 eval-variables: [sys-comp-version ["sh" "-c" "echo $OPAMSYSCOMP"] "comp version"] installed-switches: ["sw-sys-comp" "sw-comp" "${BASEDIR}" "default"] jobs: 4 @@ -2715,9 +3209,14 @@ opam-version: "2.0" repositories: "default" swh-fallback: false switch: "sw-sys-comp" +wrap-build-commands: ["%{hooks}%/sandbox.sh" "build"] {os = "linux" | os = "macos"} +wrap-install-commands: ["%{hooks}%/sandbox.sh" "install"] {os = "linux" | os = "macos"} +wrap-remove-commands: ["%{hooks}%/sandbox.sh" "remove"] {os = "linux" | os = "macos"} ### opam-cat $OPAMROOT/repo/repos-config opam-version: "2.0" -repositories: "default" {"file://${BASEDIR}/default"} +repo "default" { +url: "file://${BASEDIR}/default" +} ### opam-cat _opam/.opam-switch/switch-config invariant: ["i-am-sys-compiler" | "i-am-compiler"] opam-root: "${BASEDIR}/OPAM" @@ -2728,26 +3227,32 @@ compiler: ["i-am-sys-compiler.2"] 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:6:d: Upgraded root and local 2.2~alpha switch not recorded -### ocaml generate.ml 2.2~alpha orphaned 2.2~alpha +### :V:7:d: Upgraded root and local 2.2~beta switch not recorded +### ocaml generate.ml 2.2~beta orphaned 2.2~beta ### # ro global state, ro repo state, ro switch state -### opam list | "${OPAMROOTVERSION}$" -> "current" +### 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.2~beta to current +This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.2~beta 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 +Format upgrade done. + +<><> Rerunning init and update ><><><><><><><><><><><><><><><><><><><><><><><><> GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.2~alpha to current -FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE No cache found RSTATE loaded opam files from repo default in 0.000s -STATE LOAD-SWITCH-STATE @ ${BASEDIR} -STATE Switch state loaded in 0.000s -# Packages matching: installed -# Name # Installed # Synopsis -i-am-sys-compiler 2 One-line description + +<><> Updating repositories ><><><><><><><><><><><><><><><><><><><><><><><><><><> +[default] no changes from file://${BASEDIR}/default +Update done, please now retry your command. +# Return code 10 # ### # ro global state, ro repo state, rw switch state ### opam install i-am-package | "${OPAMROOTVERSION}$" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.2~alpha to current -FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE Cache found STATE LOAD-SWITCH-STATE @ ${BASEDIR} @@ -2762,17 +3267,8 @@ The following actions will be performed: STATE dependencies (0.000) result={ i-am-sys-compiler.2 } Done. ### # rw global state -### opam option jobs=4 | "${OPAMROOTVERSION}($|,)" -> "current" +### 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.2~alpha to current -This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.2~alpha to version current which can't be reverted. -You may want to back it up before going further. - -Continue? [Y/n] y -[NOTE] The 'jobs' option was reset, its value was 1 and its new value will vary according to the current number of cores on your machine. You can restore the fixed value using: - opam option jobs=1 --global -Format upgrade done. Set to '4' the field jobs in global configuration ### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" | grep -v sys-pkg-manager-cmd | grep -v global-variables default-compiler: ["i-am-sys-compiler" "i-am-compiler"] @@ -2780,7 +3276,7 @@ default-invariant: ["i-am-sys-compiler"] depext: true depext-cannot-install: false depext-run-installs: true -download-jobs: 1 +download-jobs: 3 eval-variables: [sys-comp-version ["sh" "-c" "echo $OPAMSYSCOMP"] "comp version"] installed-switches: ["sw-sys-comp" "sw-comp" "default"] jobs: 4 @@ -2789,9 +3285,14 @@ opam-version: "2.0" repositories: "default" swh-fallback: false switch: "sw-sys-comp" +wrap-build-commands: ["%{hooks}%/sandbox.sh" "build"] {os = "linux" | os = "macos"} +wrap-install-commands: ["%{hooks}%/sandbox.sh" "install"] {os = "linux" | os = "macos"} +wrap-remove-commands: ["%{hooks}%/sandbox.sh" "remove"] {os = "linux" | os = "macos"} ### opam-cat $OPAMROOT/repo/repos-config opam-version: "2.0" -repositories: "default" {"file://${BASEDIR}/default"} +repo "default" { +url: "file://${BASEDIR}/default" +} ### opam-cat _opam/.opam-switch/switch-config invariant: ["i-am-sys-compiler" | "i-am-compiler"] opam-root: "${BASEDIR}/OPAM" @@ -2802,26 +3303,29 @@ compiler: ["i-am-sys-compiler.2"] 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:6:e: reinit from 2.2~alpha -### ocaml generate.ml 2.2~alpha -### opam init --reinit --bypass-checks --no-setup | grep -v Cygwin | "${OPAMROOTVERSION}($|,)" -> "current" +### :V:7:e: reinit from 2.2~beta +### ocaml generate.ml 2.2~beta +### opam init --reinit --bypass-checks --no-setup | grep -v Cygwin | "${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.2~alpha to current -This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.2~alpha to version current which can't be reverted. +FMT_UPG Hard config upgrade, from 2.2~beta to current +This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.2~beta to version current, which can't be reverted. You may want to back it up before going further. -Continue? [Y/n] y -[NOTE] The 'jobs' option was reset, its value was 1 and its new value will vary according to the current number of cores on your machine. You can restore the fixed value using: - opam option jobs=1 --global +Perform the update and continue? [Y/n] y Format upgrade done. + +<><> Rerunning init and update ><><><><><><><><><><><><><><><><><><><><><><><><> +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE No cache found RSTATE loaded opam files from repo default in 0.000s <><> Updating repositories ><><><><><><><><><><><><><><><><><><><><><><><><><><> [default] no changes from file://${BASEDIR}/default +Update done, please now retry your command. +# Return code 10 # ### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" | grep -v sys-pkg-manager-cmd | grep -v global-variables default-compiler: ["i-am-sys-compiler" "i-am-compiler"] default-invariant: ["i-am-sys-compiler"] @@ -2856,21 +3360,34 @@ STATE Switch state loaded in 0.000s i-am-package 2 One-line description i-am-sys-compiler 2 One-line description ### rm -rf _opam -### :V:7:a: From 2.2~beta root, global -### ocaml generate.ml 2.2~beta +### :V:8:a: From 2.2 root, global +### ocaml generate.ml 2.2 ### # ro global state -### opam option jobs | "${OPAMROOTVERSION}$" -> "current" +### opam option jobs | "${OPAMROOTVERSION}" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.2~beta to current -FMT_UPG Format upgrade done -### # ro global state, ro repo state, ro switch state -### opam list | "${OPAMROOTVERSION}$" -> "current" +[WARNING] Removing global switch 'this-internal-error' as it no longer exists +FMT_UPG Hard config upgrade, from 2.2 to current +This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.2 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 +Format upgrade done. + +<><> Rerunning init and update ><><><><><><><><><><><><><><><><><><><><><><><><> GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.2~beta to current -FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE No cache found RSTATE loaded opam files from repo default in 0.000s + +<><> Updating repositories ><><><><><><><><><><><><><><><><><><><><><><><><><><> +[default] no changes from file://${BASEDIR}/default +Update done, please now retry your command. +# Return code 10 # +### # ro global state, ro repo state, ro switch state +### opam list +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM +RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM +RSTATE Cache found STATE LOAD-SWITCH-STATE @ sw-sys-comp STATE Switch state loaded in 0.000s # Packages matching: installed @@ -2879,10 +3396,8 @@ 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 | "${OPAMROOTVERSION}$" -> "current" +### opam install i-am-another-package --switch sw-comp GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.2~beta to current -FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE Cache found STATE LOAD-SWITCH-STATE @ sw-comp @@ -2897,10 +3412,8 @@ The following actions will be performed: STATE dependencies (0.000) result={ i-am-compiler.2 } Done. ### # ro global state, rw repo state -### opam repo add root-config ./root-config | "${OPAMROOTVERSION}$" -> "current" +### opam repo add root-config ./root-config GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.2~beta to current -FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE Cache found [root-config] Initialised @@ -2908,15 +3421,8 @@ RSTATE Cache found Run `opam repository add root-config --all-switches|--set-default' to use it in all existing switches, or in newly created switches, respectively. ### # rw global state -### opam option jobs=4 | "${OPAMROOTVERSION}$" -> "current" +### opam option jobs=4 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.2~beta to current -This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.2~beta to version 2.2, 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 | '"${OPAMROOTVERSION}"' -> "current" | grep -v sys-pkg-manager-cmd | grep -v global-variables default-compiler: ["i-am-sys-compiler" "i-am-compiler"] @@ -2924,7 +3430,7 @@ default-invariant: ["i-am-sys-compiler"] depext: true depext-cannot-install: false depext-run-installs: true -download-jobs: 1 +download-jobs: 3 eval-variables: [sys-comp-version ["sh" "-c" "echo $OPAMSYSCOMP"] "comp version"] installed-switches: ["sw-sys-comp" "sw-comp" "default"] jobs: 4 @@ -2933,9 +3439,17 @@ opam-version: "2.0" repositories: "default" swh-fallback: false switch: "sw-sys-comp" +wrap-build-commands: ["%{hooks}%/sandbox.sh" "build"] {os = "linux" | os = "macos"} +wrap-install-commands: ["%{hooks}%/sandbox.sh" "install"] {os = "linux" | os = "macos"} +wrap-remove-commands: ["%{hooks}%/sandbox.sh" "remove"] {os = "linux" | os = "macos"} ### opam-cat $OPAMROOT/repo/repos-config opam-version: "2.0" -repositories: ["default" {"file://${BASEDIR}/default"} "root-config" {"file://${BASEDIR}/root-config"}] +repo "default" { +url: "file://${BASEDIR}/default" +} +repo "root-config" { +url: "file://${BASEDIR}/root-config" +} ### opam-cat $OPAMROOT/sw-comp/.opam-switch/switch-config invariant: ["i-am-compiler"] opam-version: "2.0" @@ -2945,25 +3459,31 @@ compiler: ["i-am-compiler.2"] installed: ["i-am-another-package.2" "i-am-compiler.2" "i-am-package.2"] opam-version: "2.0" roots: ["i-am-another-package.2" "i-am-compiler.2" "i-am-package.2"] -### :V:7:b: From 2.2~beta root, local -### ocaml generate.ml 2.2~beta local +### :V:8:b: From 2.2 root, local +### ocaml generate.ml 2.2 local ### opam list | "${OPAMROOTVERSION}($|,)" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.2~beta to current -FMT_UPG Format upgrade done +[WARNING] Removing global switch 'this-internal-error' as it no longer exists +FMT_UPG Hard config upgrade, from 2.2 to current +This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.2 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 +Format upgrade done. + +<><> Rerunning init and update ><><><><><><><><><><><><><><><><><><><><><><><><> +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE No cache found RSTATE loaded opam files from repo default in 0.000s -STATE LOAD-SWITCH-STATE @ ${BASEDIR} -STATE Switch state loaded in 0.000s -# Packages matching: installed -# Name # Installed # Synopsis -i-am-sys-compiler 2 One-line description + +<><> Updating repositories ><><><><><><><><><><><><><><><><><><><><><><><><><><> +[default] no changes from file://${BASEDIR}/default +Update done, please now retry your command. +# Return code 10 # ### # ro global state, ro repo state, rw switch state -### opam install i-am-package | "${OPAMROOTVERSION}$" -> "current" +### opam install i-am-package GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.2~beta to current -FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE Cache found STATE LOAD-SWITCH-STATE @ ${BASEDIR} @@ -2979,15 +3499,8 @@ The following actions will be performed: STATE dependencies (0.000) result={ i-am-sys-compiler.2 } Done. ### # rw global state -### opam option jobs=4 | "${OPAMROOTVERSION}$" -> "current" +### opam option jobs=4 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.2~beta to current -This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.2~beta to version 2.2, 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 | '"${OPAMROOTVERSION}"' -> "current" | grep -v sys-pkg-manager-cmd | grep -v global-variables default-compiler: ["i-am-sys-compiler" "i-am-compiler"] @@ -2995,7 +3508,7 @@ default-invariant: ["i-am-sys-compiler"] depext: true depext-cannot-install: false depext-run-installs: true -download-jobs: 1 +download-jobs: 3 eval-variables: [sys-comp-version ["sh" "-c" "echo $OPAMSYSCOMP"] "comp version"] installed-switches: ["sw-sys-comp" "sw-comp" "${BASEDIR}" "default"] jobs: 4 @@ -3004,9 +3517,14 @@ opam-version: "2.0" repositories: "default" swh-fallback: false switch: "sw-sys-comp" +wrap-build-commands: ["%{hooks}%/sandbox.sh" "build"] {os = "linux" | os = "macos"} +wrap-install-commands: ["%{hooks}%/sandbox.sh" "install"] {os = "linux" | os = "macos"} +wrap-remove-commands: ["%{hooks}%/sandbox.sh" "remove"] {os = "linux" | os = "macos"} ### opam-cat $OPAMROOT/repo/repos-config opam-version: "2.0" -repositories: "default" {"file://${BASEDIR}/default"} +repo "default" { +url: "file://${BASEDIR}/default" +} ### opam-cat _opam/.opam-switch/switch-config invariant: ["i-am-sys-compiler" | "i-am-compiler"] opam-root: "${BASEDIR}/OPAM" @@ -3017,25 +3535,31 @@ compiler: ["i-am-sys-compiler.2"] 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:7:c: From 2.2~beta root, local unknown from config -### ocaml generate.ml 2.2~beta local +### :V:8:c: From 2.2 root, local unknown from config +### ocaml generate.ml 2.2 local ### opam list | "${OPAMROOTVERSION}($|,)" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.2~beta to current -FMT_UPG Format upgrade done +[WARNING] Removing global switch 'this-internal-error' as it no longer exists +FMT_UPG Hard config upgrade, from 2.2 to current +This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.2 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 +Format upgrade done. + +<><> Rerunning init and update ><><><><><><><><><><><><><><><><><><><><><><><><> +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE No cache found RSTATE loaded opam files from repo default in 0.000s -STATE LOAD-SWITCH-STATE @ ${BASEDIR} -STATE Switch state loaded in 0.000s -# Packages matching: installed -# Name # Installed # Synopsis -i-am-sys-compiler 2 One-line description + +<><> Updating repositories ><><><><><><><><><><><><><><><><><><><><><><><><><><> +[default] no changes from file://${BASEDIR}/default +Update done, please now retry your command. +# Return code 10 # ### # ro global state, ro repo state, rw switch state ### opam install i-am-package | "${OPAMROOTVERSION}($|,)" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.2~beta to current -FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE Cache found STATE LOAD-SWITCH-STATE @ ${BASEDIR} @@ -3050,15 +3574,8 @@ The following actions will be performed: STATE dependencies (0.000) result={ i-am-sys-compiler.2 } Done. ### # rw global state -### opam option jobs=4 | "${OPAMROOTVERSION}$" -> "current" +### opam option jobs=4 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.2~beta to current -This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.2~beta to version 2.2, 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 | '"${OPAMROOTVERSION}"' -> "current" | grep -v sys-pkg-manager-cmd | grep -v global-variables default-compiler: ["i-am-sys-compiler" "i-am-compiler"] @@ -3066,7 +3583,7 @@ default-invariant: ["i-am-sys-compiler"] depext: true depext-cannot-install: false depext-run-installs: true -download-jobs: 1 +download-jobs: 3 eval-variables: [sys-comp-version ["sh" "-c" "echo $OPAMSYSCOMP"] "comp version"] installed-switches: ["sw-sys-comp" "sw-comp" "${BASEDIR}" "default"] jobs: 4 @@ -3075,9 +3592,14 @@ opam-version: "2.0" repositories: "default" swh-fallback: false switch: "sw-sys-comp" +wrap-build-commands: ["%{hooks}%/sandbox.sh" "build"] {os = "linux" | os = "macos"} +wrap-install-commands: ["%{hooks}%/sandbox.sh" "install"] {os = "linux" | os = "macos"} +wrap-remove-commands: ["%{hooks}%/sandbox.sh" "remove"] {os = "linux" | os = "macos"} ### opam-cat $OPAMROOT/repo/repos-config opam-version: "2.0" -repositories: "default" {"file://${BASEDIR}/default"} +repo "default" { +url: "file://${BASEDIR}/default" +} ### opam-cat _opam/.opam-switch/switch-config invariant: ["i-am-sys-compiler" | "i-am-compiler"] opam-root: "${BASEDIR}/OPAM" @@ -3088,26 +3610,32 @@ compiler: ["i-am-sys-compiler.2"] 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:7:d: Upgraded root and local 2.2~beta switch not recorded -### ocaml generate.ml 2.2~beta orphaned 2.2~beta +### :V:8:d: Upgraded root and local 2.2 switch not recorded +### ocaml generate.ml 2.2 orphaned 2.2 ### # ro global state, ro repo state, ro switch state -### opam list | "${OPAMROOTVERSION}$" -> "current" +### opam list +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.2 to 2.4 +This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.2 to version 2.4, which can't be reverted. +You may want to back it up before going further. + +Perform the update and continue? [Y/n] y +Format upgrade done. + +<><> Rerunning init and update ><><><><><><><><><><><><><><><><><><><><><><><><> GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.2~beta to current -FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE No cache found RSTATE loaded opam files from repo default in 0.000s -STATE LOAD-SWITCH-STATE @ ${BASEDIR} -STATE Switch state loaded in 0.000s -# Packages matching: installed -# Name # Installed # Synopsis -i-am-sys-compiler 2 One-line description + +<><> Updating repositories ><><><><><><><><><><><><><><><><><><><><><><><><><><> +[default] no changes from file://${BASEDIR}/default +Update done, please now retry your command. +# Return code 10 # ### # ro global state, ro repo state, rw switch state -### opam install i-am-package | "${OPAMROOTVERSION}$" -> "current" +### opam install i-am-package GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM -FMT_UPG On-the-fly config upgrade, from 2.2~beta to current -FMT_UPG Format upgrade done RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE Cache found STATE LOAD-SWITCH-STATE @ ${BASEDIR} @@ -3122,15 +3650,8 @@ The following actions will be performed: STATE dependencies (0.000) result={ i-am-sys-compiler.2 } Done. ### # rw global state -### opam option jobs=4 | "${OPAMROOTVERSION}$" -> "current" +### opam option jobs=4 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.2~beta to current -This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.2~beta to version 2.2, 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 | '"${OPAMROOTVERSION}"' -> "current" | grep -v sys-pkg-manager-cmd | grep -v global-variables default-compiler: ["i-am-sys-compiler" "i-am-compiler"] @@ -3138,7 +3659,7 @@ default-invariant: ["i-am-sys-compiler"] depext: true depext-cannot-install: false depext-run-installs: true -download-jobs: 1 +download-jobs: 3 eval-variables: [sys-comp-version ["sh" "-c" "echo $OPAMSYSCOMP"] "comp version"] installed-switches: ["sw-sys-comp" "sw-comp" "default"] jobs: 4 @@ -3147,9 +3668,14 @@ opam-version: "2.0" repositories: "default" swh-fallback: false switch: "sw-sys-comp" +wrap-build-commands: ["%{hooks}%/sandbox.sh" "build"] {os = "linux" | os = "macos"} +wrap-install-commands: ["%{hooks}%/sandbox.sh" "install"] {os = "linux" | os = "macos"} +wrap-remove-commands: ["%{hooks}%/sandbox.sh" "remove"] {os = "linux" | os = "macos"} ### opam-cat $OPAMROOT/repo/repos-config opam-version: "2.0" -repositories: "default" {"file://${BASEDIR}/default"} +repo "default" { +url: "file://${BASEDIR}/default" +} ### opam-cat _opam/.opam-switch/switch-config invariant: ["i-am-sys-compiler" | "i-am-compiler"] opam-root: "${BASEDIR}/OPAM" @@ -3160,24 +3686,29 @@ compiler: ["i-am-sys-compiler.2"] 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:7:e: reinit from 2.2~beta -### ocaml generate.ml 2.2~beta -### opam init --reinit --bypass-checks --no-setup | grep -v Cygwin +### :V:8:e: reinit from 2.2 +### ocaml generate.ml 2.2 +### opam init --reinit --bypass-checks --no-setup | grep -v Cygwin | "${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.2~beta to 2.2 -This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.2~beta to version 2.2, which can't be reverted. +FMT_UPG Hard config upgrade, from 2.2 to current +This version of opam requires an update to the layout of ${BASEDIR}/OPAM from version 2.2 to version current, which can't be reverted. You may want to back it up before going further. -Continue? [Y/n] y +Perform the update and continue? [Y/n] y Format upgrade done. + +<><> Rerunning init and update ><><><><><><><><><><><><><><><><><><><><><><><><> +GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM RSTATE No cache found RSTATE loaded opam files from repo default in 0.000s <><> Updating repositories ><><><><><><><><><><><><><><><><><><><><><><><><><><> [default] no changes from file://${BASEDIR}/default +Update done, please now retry your command. +# Return code 10 # ### opam-cat $OPAMROOT/config | '"${OPAMROOTVERSION}"' -> "current" | grep -v sys-pkg-manager-cmd | grep -v global-variables default-compiler: ["i-am-sys-compiler" "i-am-compiler"] default-invariant: ["i-am-sys-compiler"] @@ -3212,8 +3743,8 @@ STATE Switch state loaded in 0.000s i-am-package 2 One-line description i-am-sys-compiler 2 One-line description ### rm -rf _opam -### :V:8:a: From 2.2 root, global -### ocaml generate.ml $OPAMROOTVERSION +### :V:9:a: From 2.4 root, global +### ocaml generate.ml 2.4 ### # ro global state ### opam option jobs GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM @@ -3276,7 +3807,12 @@ swh-fallback: false switch: "sw-sys-comp" ### opam-cat $OPAMROOT/repo/repos-config opam-version: "2.0" -repositories: ["default" {"file://${BASEDIR}/default"} "root-config" {"file://${BASEDIR}/root-config"}] +repo "default" { +url: "file://${BASEDIR}/default" +} +repo "root-config" { +url: "file://${BASEDIR}/root-config" +} ### opam-cat $OPAMROOT/sw-comp/.opam-switch/switch-config invariant: ["i-am-compiler"] opam-version: "2.0" @@ -3286,8 +3822,8 @@ compiler: ["i-am-compiler.2"] installed: ["i-am-another-package.2" "i-am-compiler.2" "i-am-package.2"] opam-version: "2.0" roots: ["i-am-another-package.2" "i-am-compiler.2" "i-am-package.2"] -### :V:8:b: From 2.2 root, local -### ocaml generate.ml $OPAMROOTVERSION local +### :V:9:b: From 2.4 root, local +### ocaml generate.ml 2.4 local ### opam list | "${OPAMROOTVERSION}($|,)" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM @@ -3336,7 +3872,9 @@ swh-fallback: false switch: "sw-sys-comp" ### opam-cat $OPAMROOT/repo/repos-config opam-version: "2.0" -repositories: "default" {"file://${BASEDIR}/default"} +repo "default" { +url: "file://${BASEDIR}/default" +} ### opam-cat _opam/.opam-switch/switch-config invariant: ["i-am-sys-compiler" | "i-am-compiler"] opam-root: "${BASEDIR}/OPAM" @@ -3347,8 +3885,8 @@ compiler: ["i-am-sys-compiler.2"] 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:8:c: From 2.2 root, local unknown from config -### ocaml generate.ml $OPAMROOTVERSION local +### :V:9:c: From 2.4 root, local unknown from config +### ocaml generate.ml 2.4 local ### opam list | "${OPAMROOTVERSION}($|,)" -> "current" GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM @@ -3396,7 +3934,9 @@ swh-fallback: false switch: "sw-sys-comp" ### opam-cat $OPAMROOT/repo/repos-config opam-version: "2.0" -repositories: "default" {"file://${BASEDIR}/default"} +repo "default" { +url: "file://${BASEDIR}/default" +} ### opam-cat _opam/.opam-switch/switch-config invariant: ["i-am-sys-compiler" | "i-am-compiler"] opam-root: "${BASEDIR}/OPAM" @@ -3407,8 +3947,8 @@ compiler: ["i-am-sys-compiler.2"] 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:8:d: Upgraded root and local 2.2 switch not recorded -### ocaml generate.ml $OPAMROOTVERSION orphaned 2.2 +### :V:9:d: Upgraded root and local 2.4 switch not recorded +### ocaml generate.ml 2.4 orphaned 2.4 ### # ro global state, ro repo state, ro switch state ### opam list GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM @@ -3457,7 +3997,9 @@ swh-fallback: false switch: "sw-sys-comp" ### opam-cat $OPAMROOT/repo/repos-config opam-version: "2.0" -repositories: "default" {"file://${BASEDIR}/default"} +repo "default" { +url: "file://${BASEDIR}/default" +} ### opam-cat _opam/.opam-switch/switch-config invariant: ["i-am-sys-compiler" | "i-am-compiler"] opam-root: "${BASEDIR}/OPAM" @@ -3468,9 +4010,9 @@ compiler: ["i-am-sys-compiler.2"] 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:8:e: reinit from 2.2 -### ocaml generate.ml 2.2 -### opam init --reinit --bypass-checks --no-setup | grep -v Cygwin +### :V:9:e: reinit from 2.4 +### ocaml generate.ml 2.4 +### opam init --reinit --bypass-checks --no-setup | grep -v Cygwin | "${OPAMROOTVERSION}" -> "current" No configuration file found, using built-in defaults. GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM @@ -3513,3 +4055,4 @@ 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 +### rm -rf _opam diff --git a/tests/reftests/repository.test b/tests/reftests/repository.test index fa07335b318..9030137ee1c 100644 --- a/tests/reftests/repository.test +++ b/tests/reftests/repository.test @@ -838,34 +838,34 @@ nourl file://${BASEDIR}/nourl nourl no -- ### opam-version: "2.0" -repositories: [ "nourl" ] +repo "nourl" { } ### opam repo --all [WARNING] Errors in ${BASEDIR}/OPAM/repo/repos-config, some fields have been ignored: - - At ${BASEDIR}/OPAM/repo/repos-config:2:16-2:23:: - expected url + - In ${BASEDIR}/OPAM/repo/repos-config: + missing URL # Repository # Url # Switches(rank) ### opam-version: "2.0" ### opam update nourl [WARNING] Errors in ${BASEDIR}/OPAM/repo/repos-config, some fields have been ignored: - - At ${BASEDIR}/OPAM/repo/repos-config:2:16-2:23:: - expected url + - In ${BASEDIR}/OPAM/repo/repos-config: + missing URL [ERROR] Unknown repositories or installed packages: nourl # Return code 40 # ### opam list -A [WARNING] Errors in ${BASEDIR}/OPAM/repo/repos-config, some fields have been ignored: - - At ${BASEDIR}/OPAM/repo/repos-config:2:16-2:23:: - expected url + - In ${BASEDIR}/OPAM/repo/repos-config: + missing URL # Packages matching: any # No matches found ### sh -c "rm OPAM/repo/state-*.cache" ### opam list -A [WARNING] Errors in ${BASEDIR}/OPAM/repo/repos-config, some fields have been ignored: - - At ${BASEDIR}/OPAM/repo/repos-config:2:16-2:23:: - expected url + - In ${BASEDIR}/OPAM/repo/repos-config: + missing URL # Packages matching: any # No matches found diff --git a/tests/reftests/upgrade-two-point-o.test b/tests/reftests/upgrade-two-point-o.test.disabled similarity index 94% rename from tests/reftests/upgrade-two-point-o.test rename to tests/reftests/upgrade-two-point-o.test.disabled index d880a4c45b1..bd6d3c88452 100644 --- a/tests/reftests/upgrade-two-point-o.test +++ b/tests/reftests/upgrade-two-point-o.test.disabled @@ -1,3 +1,4 @@ +### : Disabled with the integration of the new hard upgrade for 2.4, this test make no more sense N0REP0 ### opam-version: "2.0"