Skip to content

Commit

Permalink
Merge pull request #4638 from rjbou/root-version
Browse files Browse the repository at this point in the history
Error-free opam root changes
  • Loading branch information
rjbou authored May 28, 2021
2 parents acff158 + abb7e1d commit d1b967a
Show file tree
Hide file tree
Showing 33 changed files with 1,636 additions and 194 deletions.
16 changes: 10 additions & 6 deletions Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -177,7 +177,7 @@ uninstall: opam.install
$(OPAMINSTALLER) -u $(OPAMINSTALLER_FLAGS) opam-installer.install

.PHONY: tests
tests: $(DUNE_DEP)
tests: $(DUNE_DEP) src/client/no-git-version
@$(DUNE) runtest $(DUNE_PROFILE_ARG) --root . $(DUNE_ARGS) src/ tests/ --no-buffer; \
ret=$$?; \
echo "### TESTS RESULT SUMMARY ###"; \
Expand All @@ -203,20 +203,24 @@ crowbar-afl: $(DUNE_DEP)
echo foo > /tmp/opam-crowbar-input/foo
afl-fuzz -i /tmp/opam-crowbar-input -o /tmp/opam-crowbar-output dune exec src/crowbar/test.exe @@

INTERMEDIATE: src/client/no-git-version
src/client/no-git-version:
touch src/client/no-git-version

# tests-local, tests-git
tests-%: $(DUNE_DEP)
tests-%: $(DUNE_DEP) src/client/no-git-version
$(DUNE) build $(DUNE_ARGS) $(DUNE_PROFILE_ARG) --root . @reftest-legacy-$* --force

reftest-gen: $(DUNE_DEP)
reftest-gen: $(DUNE_DEP) src/client/no-git-version
$(DUNE) build $(DUNE_ARGS) $(DUNE_PROFILE_ARG) --root . @reftest-gen --auto-promote --force

reftest-runner: $(DUNE_DEP)
reftest-runner: $(DUNE_DEP) src/client/no-git-version
$(DUNE) build $(DUNE_ARGS) $(DUNE_PROFILE_ARG) --root . tests/reftests/run.exe

reftests: $(DUNE_DEP)
reftests: $(DUNE_DEP) src/client/no-git-version
$(DUNE) build $(DUNE_ARGS) $(DUNE_PROFILE_ARG) --root . @reftest

reftests-%: $(DUNE_DEP)
reftests-%: $(DUNE_DEP) src/client/no-git-version
$(DUNE) build $(DUNE_ARGS) $(DUNE_PROFILE_ARG) --root . @reftest-$* --force

reftests-meld:
Expand Down
12 changes: 12 additions & 0 deletions master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -25,6 +25,9 @@ New option/command/subcommand are prefixed with ◈.
* Introduce a `default-invariant` config field, restore the 2.0 semantics for
`default-compiler` [#4607 @AltGr]
* Fix default invariant with no system compiler [#4644 @AltGr - fix #4640]
* Perform an hard upgrade on intermediate roots, ie root from `2.1~alpha/beta`, and keep a light upgrade from `2.0` [#4638 @rjbou]
* If opam root is different from the binary, allow reading it and try to read in best effort mode [#4638 @rjbou - fix #4636]
* Don't check opam system dependencies on reinit after a format upgrade [#4638 @rjbou]

## Config report
* Fix `Not_found` (config file) error [#4570 @rjbou]
Expand All @@ -48,6 +51,7 @@ New option/command/subcommand are prefixed with ◈.
with base packages but doesn't make sense with 2.1 switch invariants) [#4569 @dra27]
* Don't refer to base packages in messages any more [#4623 @dra27 - fixes #4572]
* Give the correct command when demonstrating switch creation [#4675 @dra27 - fixes #4673]
* On switch loading, if invariant is inferred and a write lock required, write the file [#4638 @rjbou]

## Pin
* Don't look for lock files for pin depends [#4511 @rjbou - fix #4505]
Expand All @@ -72,6 +76,7 @@ New option/command/subcommand are prefixed with ◈.
* Fix W59 & E60 with conf flag handling (no url required) [#4550 @rjbou - fix #4549]
* Fix W59 & E60 with VCS urls, don't check upstream if url has VCS backend [#4635 @rjbou]
* Add E67 checksum specified with non archive url [#4635 @rjbou]
* Disable subpath warning E63,W64 [#4638 @rjbou]

## Lock
* Don't write lock file with `--read-only', `--safe`, and `--dryrun` [#4562 @rjbou - fix #4320]
Expand All @@ -83,6 +88,11 @@ New option/command/subcommand are prefixed with ◈.
* Fix rewriting with preserved format empty field error [#4634 @rjbou - fix #4628]
* Fix rewrtiting with preserved format empty field error [#4633 @rjbou - fix #4628]
* Require opam-file-format 2.1.3+ in order to enforce opam-version: "2.1" as first non-comment line [#4639 @dra27 - fix #4394]
* Switch config: Defined `invariant` field as an option to differentiate when it is not defined [#4638 @rjbou]
* Differentiate bad format from bad (opam) version with `Bad_version` exception, raised from `OpamFormat.check_opam_version` [#4638 @rjbou]
* Always print the `opam-version` field on files [#4638 @rjbou]
* Config: add `opam-root-version` field as a marker for the whole opam root [#4638 @rjbou - fix #4636]
* Add `BestEffort` modules with reading functions that don't show errors, given the `opam_file_format` internal field [#4638 @rjbou - fix #4636]

## External dependencies
* Handle macport variants [#4509 @rjbou - fix #4297]
Expand Down Expand Up @@ -120,6 +130,7 @@ New option/command/subcommand are prefixed with ◈.
* Fix build from source when a dune-project file is presented in the parent directory [#4545 @kit-ty-kate - fix #4537]
* Fix opam-devel.install not to install two files called opam [#4664 @dra27]
* Build release tags as non-dev versions, as for release tarballs [#4665 @dra27 - fix #4656]
* Disable dev version for tests (needed for format upgrade test) [#4638 @rjbou]

## Infrastructure
* Release scripts: switch to OCaml 4.10.2 by default, add macos/arm64 builds by default [#4559 @AltGr]
Expand Down Expand Up @@ -178,6 +189,7 @@ New option/command/subcommand are prefixed with ◈.
* Remove debug information from reftest [#4612 @rjbou]
* Add preserved format test [#4634 @rjbou]
* Use the dev profile when testing [#4672 @dra27]
* Add a test to test various case of opam root loading (several version, and several lock kinds) [#4638 @rjbou]

## Shell
*
Expand Down
5 changes: 3 additions & 2 deletions src/client/opamAdminCommand.ml
Original file line number Diff line number Diff line change
Expand Up @@ -126,7 +126,7 @@ let index_command cli =

let cache_urls repo_root repo_def =
let global_dl_cache =
OpamStd.Option.Op.(OpamStateConfig.(load !r.root_dir) +!
OpamStd.Option.Op.(OpamStateConfig.(load ~lock_kind:`Lock_read !r.root_dir) +!
OpamFile.Config.empty)
|> OpamFile.Config.dl_cache
in
Expand Down Expand Up @@ -771,7 +771,8 @@ let get_virtual_switch_state repo_root env =
let gt = {
global_lock = OpamSystem.lock_none;
root = OpamStateConfig.(!r.root_dir);
config = OpamStd.Option.Op.(OpamStateConfig.(load !r.root_dir) +!
config = OpamStd.Option.Op.(OpamStateConfig.(
load ~lock_kind:`Lock_read !r.root_dir) +!
OpamFile.Config.empty);
global_variables = OpamVariable.Map.empty;
} in
Expand Down
30 changes: 15 additions & 15 deletions src/client/opamCliMain.ml
Original file line number Diff line number Diff line change
Expand Up @@ -141,22 +141,22 @@ let check_and_run_external_commands () =
OpamFormatConfig.init ();
let root_dir = OpamStateConfig.opamroot () in
let has_init, root_upgraded =
match OpamStateConfig.load_defaults root_dir with
match OpamStateConfig.load_defaults ~lock_kind:`Lock_read root_dir with
| None -> (false, false)
| Some config ->
let root_upgraded =
let config_version = OpamFile.Config.opam_version config in
let cmp =
OpamVersion.(compare OpamFile.Config.format_version config_version)
in
if cmp < 0 then
OpamConsole.error_and_exit `Configuration_error
"%s reports a newer opam version, aborting."
(OpamFilename.Dir.to_string root_dir)
else
cmp = 0
let root_upgraded =
let cmp =
OpamVersion.compare OpamFile.Config.root_version
(OpamFile.Config.opam_root_version config)
in
(true, root_upgraded)
if cmp < 0 then
OpamConsole.error_and_exit `Configuration_error
"%s reports a newer opam version, aborting."
(OpamFilename.Dir.to_string root_dir)
else
cmp = 0
in
(true, root_upgraded)
in
let plugins_bin = OpamPath.plugins_bin root_dir in
let plugin_symlink_present =
Expand Down Expand Up @@ -300,8 +300,8 @@ let rec main_catch_all f =
| OpamFormatUpgrade.Upgrade_done conf ->
main_catch_all @@ fun () ->
OpamConsole.header_msg "Rerunning init and update";
OpamClient.reinit ~interactive:true ~update_config:false conf
(OpamStd.Sys.guess_shell_compat ());
OpamClient.reinit ~interactive:true ~update_config:false ~bypass_checks:true
conf (OpamStd.Sys.guess_shell_compat ());
OpamConsole.msg
"Update done, please now retry your command.\n";
exit (OpamStd.Sys.get_exit_code `Aborted)
Expand Down
11 changes: 8 additions & 3 deletions src/client/opamClient.ml
Original file line number Diff line number Diff line change
Expand Up @@ -773,11 +773,14 @@ let update_with_init_config ?(overwrite=false) config init_config =

let reinit ?(init_config=OpamInitDefaults.init_config()) ~interactive
?dot_profile ?update_config ?env_hook ?completion ?inplace
?(check_sandbox=true)
?(check_sandbox=true) ?(bypass_checks=false)
config shell =
let root = OpamStateConfig.(!r.root_dir) in
let config = update_with_init_config config init_config in
let _all_ok = init_checks ~hard_fail_exn:false init_config in
let _all_ok =
if bypass_checks then false else
init_checks ~hard_fail_exn:false init_config
in
let custom_init_scripts =
let env v =
let vs = OpamVariable.Full.variable v in
Expand Down Expand Up @@ -843,7 +846,9 @@ let init
| None -> OpamFile.InitConfig.repositories init_config
in
let config =
update_with_init_config OpamFile.Config.empty init_config |>
update_with_init_config
OpamFile.Config.(with_opam_root_version root_version empty)
init_config |>
OpamFile.Config.with_repositories (List.map fst repos)
in

Expand Down
2 changes: 1 addition & 1 deletion src/client/opamClient.mli
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@ val init:
val reinit:
?init_config:OpamFile.InitConfig.t -> interactive:bool -> ?dot_profile:filename ->
?update_config:bool -> ?env_hook:bool -> ?completion:bool -> ?inplace:bool ->
?check_sandbox:bool ->
?check_sandbox:bool -> ?bypass_checks:bool ->
OpamFile.Config.t -> shell -> unit

(** Install the given list of packages. [add_to_roots], if given, specifies that
Expand Down
2 changes: 1 addition & 1 deletion src/client/opamClientConfig.ml
Original file line number Diff line number Diff line change
Expand Up @@ -215,7 +215,7 @@ let opam_init ?root_dir ?strict ?solver =
(* the init for OpamFormat is done in advance since (a) it has an effect on
loading the global config (b) the global config has no effect on it *)
OpamFormatConfig.initk ?strict @@ fun ?log_dir ->
let config = OpamStateConfig.load_defaults root in
let config = OpamStateConfig.load_defaults ~lock_kind:`Lock_read root in
let initialised = config <> None in
(* !X fixme: don't drop the loaded config file to reload it afterwards (when
loading the global_state) like that... *)
Expand Down
23 changes: 13 additions & 10 deletions src/client/opamCommands.ml
Original file line number Diff line number Diff line change
Expand Up @@ -372,9 +372,9 @@ let init cli =
~no_default_config_file:no_config_file ~add_config_file:config_file
in
OpamClient.reinit ~init_config ~interactive ~dot_profile
?update_config ?env_hook ?completion ~inplace
~check_sandbox:(not no_sandboxing)
(OpamFile.Config.safe_read config_f) shell;
?update_config ?env_hook ?completion ~inplace
~check_sandbox:(not no_sandboxing)
(OpamStateConfig.safe_load ~lock_kind:`Lock_write root) shell;
else
(if not interactive &&
update_config <> Some true && completion <> Some true && env_hook <> Some true then
Expand Down Expand Up @@ -833,7 +833,8 @@ let show cli =
print_just_file None opam;
`Ok ()
with
| Parsing.Parse_error | OpamLexer.Error _ | OpamPp.Bad_format _ as exn ->
| Parsing.Parse_error | OpamLexer.Error _
| OpamPp.Bad_version _ | OpamPp.Bad_format _ as exn ->
OpamConsole.error_and_exit `File_error
"Stdin parsing failed:\n%s" (Printexc.to_string exn))
| atom_locs, false ->
Expand Down Expand Up @@ -884,7 +885,8 @@ let show cli =
try
errors, (Some opamf, (OpamFile.OPAM.read opamf))::opams
with
| Parsing.Parse_error | OpamLexer.Error _ | OpamPp.Bad_format _ as exn ->
| Parsing.Parse_error | OpamLexer.Error _
| OpamPp.Bad_version _ | OpamPp.Bad_format _ as exn ->
(opamf, exn)::errors, opams)
([],[]) opamfs
in
Expand Down Expand Up @@ -2235,7 +2237,7 @@ let repository cli =
let names = List.map OpamRepositoryName.of_string names in
OpamGlobalState.with_ `Lock_none @@ fun gt ->
let repos =
OpamFile.Repos_config.safe_read (OpamPath.repos_config gt.root)
OpamStateConfig.Repos.safe_read ~lock_kind:`Lock_read gt
in
let not_found =
List.filter (fun r -> not (OpamRepositoryName.Map.mem r repos)) names
Expand Down Expand Up @@ -2675,7 +2677,7 @@ let switch cli =
OpamSwitchState.drop st;
`Ok ())
| Some `export, [filename] ->
OpamGlobalState.with_ `Lock_write @@ fun gt ->
OpamGlobalState.with_ `Lock_none @@ fun gt ->
OpamRepositoryState.with_ `Lock_none gt @@ fun rt ->
OpamSwitchCommand.export rt
~full:(full || freeze) ~freeze
Expand Down Expand Up @@ -3536,6 +3538,7 @@ let lint cli =
with
| Parsing.Parse_error
| OpamLexer.Error _
| OpamPp.Bad_version _
| OpamPp.Bad_format _ ->
msg "File format error\n";
(true, json))
Expand Down Expand Up @@ -3664,7 +3667,7 @@ let clean cli =
(OpamFilename.with_flock `Lock_write (OpamPath.repos_lock gt.root)
@@ fun _lock ->
let repos_config =
OpamFile.Repos_config.safe_read (OpamPath.repos_config gt.root)
OpamStateConfig.Repos.safe_read ~lock_kind:`Lock_write gt
in
let all_repos =
OpamRepositoryName.Map.keys repos_config |>
Expand All @@ -3677,8 +3680,8 @@ let clean cli =
let unused_repos =
List.fold_left (fun repos sw ->
let switch_config =
OpamFile.Switch_config.safe_read
(OpamPath.Switch.switch_config root sw)
OpamStateConfig.Switch.safe_load
~lock_kind:`Lock_read gt sw
in
let used_repos =
OpamStd.Option.default []
Expand Down
22 changes: 13 additions & 9 deletions src/client/opamConfigCommand.ml
Original file line number Diff line number Diff line change
Expand Up @@ -567,18 +567,24 @@ let confset_switch gt switch switch_config =
let with_switch:
'a global_state -> 'b lock -> 'b switch_state option
-> (switch -> OpamFile.Switch_config.t -> 'c) -> 'c =
fun gt lock st_opt k ->
fun gt lock_kind st_opt k ->
match st_opt with
| Some st -> k st.switch st.switch_config
| None ->
let switch = OpamStateConfig.get_switch () in
let switch_config =
try OpamStateConfig.Switch.safe_load ~lock_kind gt switch
with OpamPp.Bad_version _ as e ->
OpamFormatUpgrade.hard_upgrade_from_2_1_intermediates
~global_lock:gt.global_lock gt.root;
raise e
in
let lock_file = OpamPath.Switch.lock gt.root switch in
let config_f = OpamPath.Switch.switch_config gt.root switch in
if not (OpamFile.exists config_f) then
if switch_config = OpamFile.Switch_config.empty then
OpamConsole.error "switch %s not found, display default values"
(OpamSwitch.to_string switch);
OpamFilename.with_flock lock lock_file @@ fun _ ->
k switch (OpamFile.Switch_config.safe_read config_f)
OpamFilename.with_flock lock_kind lock_file @@ fun _ ->
k switch switch_config

let set_opt_switch_t ?inner gt switch switch_config field value =
set_opt ?inner field value (confset_switch gt switch switch_config)
Expand Down Expand Up @@ -897,8 +903,7 @@ let vars_list_switch ?st gt =
| None ->
let switch = OpamStateConfig.get_switch () in
switch,
OpamFile.Switch_config.safe_read
(OpamPath.Switch.switch_config gt.root switch)
OpamStateConfig.Switch.safe_load ~lock_kind:`Lock_read gt switch
in
List.map (fun stdpath -> [
OpamTypesBase.string_of_std_path stdpath % `bold;
Expand Down Expand Up @@ -986,8 +991,7 @@ let var_switch_raw gt v =
match OpamStateConfig.get_switch_opt () with
| Some switch ->
let switch_config =
OpamFile.Switch_config.safe_read
(OpamPath.Switch.switch_config gt.root switch)
OpamStateConfig.Switch.safe_load ~lock_kind:`Lock_read gt switch
in
let rsc =
if is_switch_defined_var switch_config v then
Expand Down
4 changes: 2 additions & 2 deletions src/client/opamRepositoryCommand.ml
Original file line number Diff line number Diff line change
Expand Up @@ -145,8 +145,8 @@ let print_selection rt ~short repos_list =

let switch_repos rt sw =
let switch_config =
OpamFile.Switch_config.safe_read
(OpamPath.Switch.switch_config rt.repos_global.root sw)
OpamStateConfig.Switch.safe_load
~lock_kind:`Lock_read rt.repos_global sw
in
match switch_config.OpamFile.Switch_config.repos with
| None -> OpamGlobalState.repos_list rt.repos_global
Expand Down
10 changes: 7 additions & 3 deletions src/client/opamSolution.ml
Original file line number Diff line number Diff line change
Expand Up @@ -338,7 +338,10 @@ let parallel_apply t

(* only needed when --update-invariant is set. Use the configured invariant,
not the current one which will be empty. *)
let original_invariant = t.switch_config.OpamFile.Switch_config.invariant in
let original_invariant =
OpamStd.Option.default OpamFormula.Empty
t.switch_config.OpamFile.Switch_config.invariant
in
let original_invariant_packages =
OpamFormula.packages t.installed original_invariant
in
Expand Down Expand Up @@ -406,7 +409,8 @@ let parallel_apply t
bypass_ref := bypass;
invariant_ref := invariant;
let switch_config =
{!t_ref.switch_config with invariant; depext_bypass = bypass }
{!t_ref.switch_config with
invariant = Some invariant; depext_bypass = bypass }
in
t_ref := {!t_ref with switch_invariant = invariant; switch_config};
if not OpamStateConfig.(!r.dryrun) then
Expand Down Expand Up @@ -775,7 +779,7 @@ let parallel_apply t
| _ -> OpamFormula.Empty)
t.switch_invariant
in
let switch_config = {t.switch_config with invariant} in
let switch_config = {t.switch_config with invariant = Some invariant} in
if not OpamStateConfig.(!r.dryrun) then
OpamSwitchAction.install_switch_config t.switch_global.root t.switch
switch_config;
Expand Down
Loading

0 comments on commit d1b967a

Please sign in to comment.