Skip to content

Commit

Permalink
Merge pull request #4715 from rjbou/fmt-upg-sw-fx
Browse files Browse the repository at this point in the history
Format upgrade fix: remove missing switches from config file
  • Loading branch information
rjbou authored Jun 21, 2021
2 parents a0dcd85 + e524e22 commit 68329da
Show file tree
Hide file tree
Showing 9 changed files with 1,479 additions and 308 deletions.
7 changes: 6 additions & 1 deletion CHANGES
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,12 @@ are not marked). Those prefixed with "(+)" are new command/option (since
2.1.0~alpha2).

2.1.0~rc2:
* Remove OPAMZ3DEBUG evironment variable [#4720 @rjbou - fix #4718]
* Remove OPAMZ3DEBUG evironment variable [#4720 @rjbou - fix #4717]
* Fix format upgrade when there is missing local switches in the config file
[#4715 @rjbou - fix #4713]
* Fix not recorded local switch handling, with format upgrade [#4715 @rjbou]
* Set opam root version to 2.1 [#4715 @rjbou]
* Improved and extended tests [#4715 @rjbou]

2.1.0~rc:
* (*) Environment variables initialised only at opam client launch, no more via
Expand Down
4 changes: 2 additions & 2 deletions src/format/opamFile.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1020,7 +1020,7 @@ module SyntaxFile(X: SyntaxFileArg) : IO_FILE with type t := X.t = struct
| {file_contents = [{pelem = Variable({pelem = "opam-version"; _}, {pelem = String ver; _}); _ };
{pelem = Section {section_kind = {pelem = "#"; _}; _}; pos}]; _}
when OpamVersion.(compare (nopatch (of_string ver)) (nopatch X.format_version)) <= 0 ->
raise (OpamPp.Bad_format (Some pos, "Parse error"))
raise (OpamPp.Bad_version (Some pos, "Parse error"))
| opamfile -> opamfile

let of_channel filename (ic:in_channel) =
Expand Down Expand Up @@ -1225,7 +1225,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.1~rc"
let root_version = OpamVersion.of_string "2.1"

let default_old_root_version = OpamVersion.of_string "2.1~~previous"

Expand Down
113 changes: 63 additions & 50 deletions src/state/opamFormatUpgrade.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1054,57 +1054,46 @@ let v2_1_alpha2 = OpamVersion.of_string "2.1~alpha2"
(* config & sw config downgrade opam-version to 2.0 and add opam root version *)
let v2_1_rc = OpamVersion.of_string "2.1~rc"

let _v2_1 = OpamVersion.of_string "2.1"
let v2_1 = OpamVersion.of_string "2.1"

let from_2_0_to_2_1_alpha _ conf = conf

let downgrade_2_1_switches root conf =
let downgrade f =
let filename = OpamFile.filename f in
let str_f = OpamFilename.to_string filename in
let opamfile = OpamParser.FullPos.file str_f in
let opamfile' =
let open OpamParserTypes.FullPos in
{ opamfile with
file_contents =
List.map (fun item ->
match item.pelem with
| Variable (({pelem = "opam-version"; _} as opam_v),
({pelem = String "2.1"; _} as v)) ->
{ item with
pelem = Variable ({opam_v with pelem = "opam-version"},
{v with pelem = String "2.0"})}
| _ -> item) opamfile.file_contents}
in
let updated = opamfile' <> opamfile in
if updated then
OpamFilename.write filename (OpamPrinter.FullPos.opamfile opamfile')
in
List.iter (fun switch ->
let f = OpamPath.Switch.switch_config root switch in
downgrade f;
ignore @@ OpamFile.Switch_config.BestEffort.read f)
(OpamFile.Config.installed_switches conf)
OpamStd.Option.iter (OpamFile.Switch_config.write f)
(OpamStateConfig.downgrade_2_1_switch f))
(OpamFile.Config.installed_switches conf);
conf

let from_2_1_alpha_to_2_1_alpha2 root conf =
downgrade_2_1_switches root conf;
conf
downgrade_2_1_switches root conf

let from_2_1_alpha2_to_v2_1_rc root conf =
downgrade_2_1_switches root conf;
conf
downgrade_2_1_switches root conf

let from_2_0_to_v2_1_rc _ conf = conf
let from_2_1_rc_to_v2_1 _ conf = conf

let from_2_0_to_v2_1 _ conf = conf

let latest_version = OpamFile.Config.root_version

let latest_hard_upgrade = (* to *) v2_0_beta5

(* intermediates roots that need an hard upgrade *)
let intermediate_roots = [
v2_1_alpha; v2_1_alpha2
v2_1_alpha; v2_1_alpha2; v2_1_rc
]

let remove_missing_switches root conf =
let exists, missing =
List.partition (fun switch ->
OpamFilename.exists (OpamFile.filename
(OpamPath.Switch.switch_config root switch)))
(OpamFile.Config.installed_switches conf)
in
OpamFile.Config.with_installed_switches exists conf, missing

let as_necessary requested_lock global_lock root config =
let root_version =
match OpamFile.Config.opam_root_version_opt config with
Expand All @@ -1119,29 +1108,29 @@ let as_necessary requested_lock global_lock root config =
(OpamPath.Switch.switch_config root switch))
(OpamFile.Config.installed_switches config);
v
with OpamPp.Bad_version _ -> v2_1_alpha
with Sys_error _ | OpamPp.Bad_version _ -> v2_1_alpha
in
let cmp = OpamVersion.(compare OpamFile.Config.root_version root_version) in
if cmp <= 0 then config (* newer or same *) else
let is_intermdiate_root = List.mem root_version intermediate_roots in
let need_hard_upg =
OpamVersion.compare root_version latest_hard_upgrade < 0
|| is_intermdiate_root
in
let on_the_fly, global_lock_kind =
if not need_hard_upg && requested_lock <> `Lock_write then
true, `Lock_read
else
false, `Lock_write
let keep_needed_upgrades =
List.filter (fun (v,_) -> OpamVersion.compare root_version v < 0)
in
(* to generalise *)
let intermediates = [
v2_1_alpha, from_2_0_to_2_1_alpha;
v2_1_alpha2, from_2_1_alpha_to_2_1_alpha2;
v2_1_rc, from_2_1_alpha2_to_v2_1_rc;
] in
let intermediates =
let hard = [
v2_1_alpha, from_2_0_to_2_1_alpha;
v2_1_alpha2, from_2_1_alpha_to_2_1_alpha2;
v2_1_rc, from_2_1_alpha2_to_v2_1_rc;
] in
let light = [
v2_1, from_2_1_rc_to_v2_1;
] in
keep_needed_upgrades hard,
light
in
let hard_upg, light_upg =
if is_intermdiate_root then intermediates, [] else
if is_intermdiate_root then intermediates else
[
v1_1, from_1_0_to_1_1;
v1_2, from_1_1_to_1_2;
Expand All @@ -1155,12 +1144,19 @@ let as_necessary requested_lock global_lock root config =
v2_0_beta, from_2_0_alpha3_to_2_0_beta;
v2_0_beta5, from_2_0_beta_to_2_0_beta5;
v2_0, from_2_0_beta5_to_2_0;
v2_1_rc, from_2_0_to_v2_1_rc;
v2_1, from_2_0_to_v2_1;
]
|> List.filter (fun (v,_) -> OpamVersion.compare root_version v < 0)
|> keep_needed_upgrades
|> List.partition (fun (v,_) ->
OpamVersion.compare v latest_hard_upgrade <= 0)
in
let need_hard_upg = hard_upg <> [] in
let on_the_fly, global_lock_kind =
if not need_hard_upg && requested_lock <> `Lock_write then
true, `Lock_read
else
false, `Lock_write
in
let erase_plugin_links root =
let plugins_bin = OpamPath.plugins_bin root in
if OpamFilename.exists_dir plugins_bin then begin
Expand Down Expand Up @@ -1189,6 +1185,23 @@ let as_necessary requested_lock global_lock root config =
config)
config hard_upg
in
let config =
let config, missing_switches = remove_missing_switches root config in
let global = List.filter (OpamSwitch.is_external @> not) missing_switches in
if not on_the_fly && global <> [] then
OpamConsole.warning "Removing global switch%s %s as %s"
(match global with | [_] -> "" | _ -> "es")
(OpamStd.Format.pretty_list
(List.map (OpamSwitch.to_string
@> OpamConsole.colorise `bold
@> Printf.sprintf "'%s'")
global))
(match global with
| [_] -> "it no longer exists"
| _ -> "they no longer exist");
config
in
if hard_upg = [] && light_upg = [] then config (* no upgrade to do *) else
let is_dev = OpamVersion.is_dev_version () in
log "%s config upgrade, from %s to %s"
(if on_the_fly then "On-the-fly" else
Expand Down Expand Up @@ -1247,7 +1260,7 @@ let hard_upgrade_from_2_1_intermediates ?global_lock root =
let opam_root_version = OpamFile.Config.raw_root_version config_f in
match opam_root_version with
| Some v when OpamVersion.compare v v2_0 <= 0
|| OpamVersion.compare v2_1_rc v <= 0 ->
|| OpamVersion.compare v2_1 v <= 0 ->
() (* do nothing, need to reraise parsing exception *)
| _ ->
log "Intermediate opam root detected%s, launch hard upgrade"
Expand Down
3 changes: 2 additions & 1 deletion src/state/opamGlobalState.ml
Original file line number Diff line number Diff line change
Expand Up @@ -200,7 +200,8 @@ let fix_switch_list gt =
OpamFile.Config.with_installed_switches known_switches gt.config
in
let gt = { gt with config } in
if not OpamCoreConfig.(!r.safe_mode) then
if not OpamCoreConfig.(!r.safe_mode)
&& OpamSystem.get_lock_flag gt.global_lock = `Lock_write then
try
snd @@ with_write_lock ~dontblock:true gt @@ fun gt ->
write gt, gt
Expand Down
53 changes: 44 additions & 9 deletions src/state/opamStateConfig.ml
Original file line number Diff line number Diff line change
Expand Up @@ -281,12 +281,45 @@ module Repos = struct
(OpamPath.repos_config gt.root)
end

let downgrade_2_1_switch f =
let filename = OpamFile.filename f in
let str_f = OpamFilename.to_string filename in
let opamfile = OpamParser.FullPos.file str_f in
let opamfile' =
let open OpamParserTypes.FullPos in
{ opamfile with
file_contents =
List.map (fun item ->
match item.pelem with
| Variable (({pelem = "opam-version"; _} as opam_v),
({pelem = String "2.1"; _} as v)) ->
{ item with
pelem = Variable ({opam_v with pelem = "opam-version"},
{v with pelem = String "2.0"})}
| _ -> item)
opamfile.file_contents}
in
if opamfile' = opamfile then None else
Some (opamfile'
|> OpamPrinter.FullPos.opamfile
|> OpamFile.Switch_config.read_from_string)

let local_switch_exists root switch =
(* we don't use safe loading function to avoid errors displaying *)
OpamPath.Switch.switch_config root switch |>
OpamFile.Switch_config.BestEffort.read_opt |> function
let f = OpamPath.Switch.switch_config root switch in
match OpamFile.Switch_config.BestEffort.read_opt f with
| None -> false
| Some conf -> conf.OpamFile.Switch_config.opam_root = Some root
| exception (OpamPp.Bad_version _ as e) ->
match OpamFile.Config.raw_root_version (OpamPath.config root) with
| None -> raise e
| Some _ ->
match downgrade_2_1_switch f with
| None -> raise e
| Some conf ->
if conf.OpamFile.Switch_config.opam_root = Some root then
(OpamFile.Switch_config.write f conf; true)
else false

let resolve_local_switch root s =
let switch_root = OpamSwitch.get_root root s in
Expand All @@ -295,13 +328,15 @@ let resolve_local_switch root s =
else s

let get_current_switch_from_cwd root =
let open OpamStd.Option.Op in
OpamFilename.find_in_parents (fun dir ->
OpamSwitch.of_string (OpamFilename.Dir.to_string dir) |>
local_switch_exists root)
(OpamFilename.cwd ())
>>| OpamSwitch.of_dirname
>>| resolve_local_switch root
try
let open OpamStd.Option.Op in
OpamFilename.find_in_parents (fun dir ->
OpamSwitch.of_string (OpamFilename.Dir.to_string dir) |>
local_switch_exists root)
(OpamFilename.cwd ())
>>| OpamSwitch.of_dirname
>>| resolve_local_switch root
with OpamPp.Bad_version _ -> None

(* do we want `load_defaults` to fail / run a format upgrade ? *)
let load_defaults ?lock_kind root_dir =
Expand Down
9 changes: 9 additions & 0 deletions src/state/opamStateConfig.mli
Original file line number Diff line number Diff line change
Expand Up @@ -137,3 +137,12 @@ module Repos : sig
val safe_read:
?lock_kind: 'a lock -> 'b global_state -> OpamFile.Repos_config.t
end

(* Raw read an switch config to downgrade its [opam-version] from 2.1 to 2.0.
It is necessary to handle opam root and switch upgrade from 2.1
intermediates roots to 2.1: this allows a workaround for a bug in versions
2.1~alpha which wrongly updated the declared switch versions, requiring that
we fix it during [OpamFormatUpgrade] from these specific intermediate
versions, and at switch loading for that specific case. *)
val downgrade_2_1_switch:
OpamFile.Switch_config.t OpamFile.t -> OpamFile.Switch_config.t option
2 changes: 1 addition & 1 deletion tests/reftests/dune
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@

(executable
(name run)
(libraries opam-core)
(libraries opam-core opam-file-format)
(modules run))

(executable
Expand Down
Loading

0 comments on commit 68329da

Please sign in to comment.