Skip to content

Commit

Permalink
Merge pull request #5231 from rjbou/213
Browse files Browse the repository at this point in the history
Backport PR to 2.1.3
  • Loading branch information
kit-ty-kate authored Aug 9, 2022
2 parents f737853 + 75983c3 commit c69fecc
Show file tree
Hide file tree
Showing 18 changed files with 563 additions and 76 deletions.
8 changes: 8 additions & 0 deletions CHANGES
Original file line number Diff line number Diff line change
Expand Up @@ -26,10 +26,18 @@ are not marked). Those prefixed with "(+)" are new command/option (since
an invalid `switch-config` file [#5027 @rjbou]
* When a field is defined in switch and global scope, try to determine the
scope also by checking switch selection [#5027 @rjbou]
* [BUG] Handle external dependencies when updating switch state pin status (all
pins), instead as a post pin action (only when called with `opam pin`
[#5047 @rjbou - fix #5046]
* [BUG] When reinstalling a package that has a dirty source, if uncommitted
changes are the same than the ones stored in opam's cache, opam consider that
it is up to date and nothing is updated [4879 @rjbou]
* Stop Zypper from upgrading packages on updates on OpenSUSE
[#4978 @kit-ty-kate]
* Clearer error message if a command doesn't exist
[#4971 @kit-ty-kat - fix #4112]
* [BUG] Remove windows double printing on commands and their output
[#4940 @rjbou]
* Actually allow multiple state caches to co-exist
[#4934 @dra27 - actually fixes #4554]
* Update cold compiler to 4.13 to avoid issues with glibc 2.34 on Unix
Expand Down
4 changes: 3 additions & 1 deletion Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -183,7 +183,9 @@ tests: $(DUNE_DEP) src/client/no-git-version
echo "### TESTS RESULT SUMMARY ###"; \
for t in _build/default/tests/reftests/*.test; do \
printf "%-30s" $$(basename $$t .test); \
if diff -q --strip-trailing-cr $$t $${t%.test}.out >/dev/null; \
if [ ! -e $${t%.test}.out ]; \
then printf '\033[33m[SKIP]\033[m\n'; \
elif diff -q --strip-trailing-cr $$t $${t%.test}.out >/dev/null; \
then printf '\033[32m[ OK ]\033[m\n'; \
else printf '\033[31m[FAIL]\033[m\n'; \
fi; \
Expand Down
47 changes: 47 additions & 0 deletions master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -83,6 +83,53 @@ New option/command/subcommand are prefixed with ◈.
## Reftests
### Tests
### Engine
* Add switch-invariant test [#4866 @rjbou]
* opam root version: add local switch cases [#4763 @rjbou] [2.1.0~rc2 #4715]
* opam root version: add reinit test casess [#4763 @rjbou] [2.1.0~rc2 #4750]
* Add & update env tests [#4861 #4841 @rjbou @dra27]
* Port opam-rt tests: orphans, dep-cycles, reinstall, and big-upgrade [#4979 @AltGr]
* Add & update env tests [#4861 #4841 #4974 @rjbou @dra27 @AltGr]
* Add remove test [#5004 @AltGr]
* Add some simple tests for the "opam list" command [#5006 @kit-ty-kate]
* Add clean test for untracked option [#4915 @rjbou]
* Harmonise some repo hash to reduce opam repository checkout [#5031 @AltGr]
### Engine
* Add `opam-cat` to normalise opam file printing [#4763 @rjbou @dra27] [2.1.0~rc2 #4715]
* Fix meld reftest: open only with failing ones [#4913 @rjbou]
* Add `BASEDIR` to environement [#4913 @rjbou]
* Replace opam bin path [#4913 @rjbou]
* Add `grep -v` command [#4913 @rjbou]
* Apply grep & seds on file order [#4913 @rjbou]
* Precise `OPAMTMP` regexp, `hexa` instead of `'alphanum` to avoid confusion with `BASEDIR` [#4913 @rjbou]
* Hackish way to have several replacement in a single line [#4913 @rjbou]
* Substitution in regexp pattern (for environment variables) [#4913 @rjbou]
* Substitution for opam-cat content [#4913 @rjbou]
* Allow one char package name on repo [#4966 @AltGr]
* Remove opam output beginning with `###` [#4966 @AltGr]
* Add `<pin:path>` header to specify incomplete opam files to pin, it is updated from a template in reftest run (no lint errors) [#4966 @rjbou]
* Unescape output [#4966 @rjbou]
* Clean outputs from opam error reporting block [#4966 @rjbou]
* Avoid diff when the repo is too old [#4979 @AltGr]
* Escape regexps characters in string replacements primitives [#5009 @kit-ty-kate]
* Automatically update default repo when adding a package file [#5004 @AltGr]
* Make all the tests work on macOS/arm64 [#5019 @kit-ty-kate]
* Add unix only tests handling [#5031 @AltGr]

## Github Actions
* Add solver backends compile test [#4723 @rjbou] [2.1.0~rc2 #4720]
* Fix ocaml link (http -> https) [#4729 @rjbou]
* Separate code from install workflow [#4773 @rjbou]
* Specify whitelist of changed files to launch workflow [#473 @rjbou]
* Update changelog checker list [#4773 @rjbou]
* Launch main hygiene job on configure/src_ext changes [#4773 @rjbou]
* Add opam.ocaml.org cache to reach disappearing archive [#4865 @rjbou]
* Update ocaml version frm 4.11.2 to 4.12.0 (because of macos failure) [#4865 @rjbou]
* Add a depext checkup, launched only is `OpamSysInteract` is changed [#4788 @rjbou]
* Arrange scripts directory [#4922 @rjbou]
* Run ci on tests changes [#4966 @rjbou]

## Shell
* fish: fix deprecated redirection syntax `^` [#4736 @vzaliva]

## Doc

Expand Down
39 changes: 8 additions & 31 deletions src/client/opamClient.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1479,39 +1479,16 @@ module PIN = struct
open OpamPinCommand

let post_pin_action st was_pinned names =
let pkgs =
let newly = st.pinned -- was_pinned in
let old =
OpamPackage.packages_of_names was_pinned
OpamPackage.Name.Set.Op.(
OpamPackage.Name.Set.of_list names
-- OpamPackage.names_of_packages newly)
in
newly ++ old
in
let no_depexts =
not (OpamFile.Config.depext st.switch_global.config)
|| OpamSysPkg.Set.is_empty
((OpamPackage.Set.fold (fun pkg acc ->
OpamSysPkg.Set.union acc (OpamSwitchState.depexts st pkg)))
pkgs OpamSysPkg.Set.empty)
let names =
OpamPackage.Set.Op.(st.pinned -- was_pinned)
|> OpamPackage.names_of_packages
|> (fun s ->
List.fold_left
(fun s p -> OpamPackage.Name.Set.add p s)
s names)
|> OpamPackage.Name.Set.elements
in
try
let st =
if no_depexts then st else
let st =
{ st with sys_packages = lazy (
OpamPackage.Map.union (fun _ n -> n)
(Lazy.force st.sys_packages)
(OpamSwitchState.depexts_status_of_packages st pkgs)
)}
in
{ st with available_packages = lazy (
OpamPackage.Set.filter (fun nv ->
OpamSwitchState.depexts_unavailable st nv = None)
(Lazy.force st.available_packages)
)}
in
upgrade_t
~strict_upgrade:false ~auto_install:true ~ask:true ~terse:true
~all:false
Expand Down
4 changes: 2 additions & 2 deletions src/core/opamProcess.ml
Original file line number Diff line number Diff line change
Expand Up @@ -641,8 +641,8 @@ let exit_status p return =
if isset_verbose_f () then
stop_verbose_f ()
else if p.p_verbose then
(verbose_print_cmd p;
List.iter verbose_print_out stdout;
(List.iter verbose_print_out stdout;
if p.p_stdout <> p.p_stderr then
List.iter verbose_print_out stderr;
flush Stdlib.stdout);
let info =
Expand Down
6 changes: 5 additions & 1 deletion src/repository/opamDarcs.ml
Original file line number Diff line number Diff line change
Expand Up @@ -81,10 +81,14 @@ module VCS = struct
OpamSystem.raise_on_process_error r;
Done ()

let reset_tree repo_root _repo_url =
let clean repo_root =
darcs repo_root [ "obliterate"; "--all"; "-t"; opam_local_tag ]
@@> fun r ->
OpamSystem.raise_on_process_error r;
Done ()

let reset_tree repo_root _repo_url =
clean repo_root @@+ fun () ->
darcs repo_root [ "obliterate"; "--all"; "-p"; opam_reverse_commit ]
@@> fun r ->
(* returns 0 even if patch doesn't exist *)
Expand Down
12 changes: 7 additions & 5 deletions src/repository/opamGit.ml
Original file line number Diff line number Diff line change
Expand Up @@ -162,18 +162,20 @@ module VCS : OpamVCS.VCS = struct
else
Done (Some full))

let clean repo_root =
git repo_root [ "clean"; "-fdx" ]
@@> fun r ->
OpamSystem.raise_on_process_error r;
Done ()

let reset_tree repo_root repo_url =
let rref = remote_ref repo_url in
git repo_root [ "reset" ; "--hard"; rref; "--" ]
@@> fun r ->
if OpamProcess.is_failure r then
OpamSystem.internal_error "Git error: %s not found." rref
else
git repo_root [ "clean"; "-fdx" ]
@@> fun r ->
if OpamProcess.is_failure r then
OpamSystem.internal_error "Git error: %s not found." rref
else
clean repo_root @@+ fun () ->
if OpamFilename.exists (repo_root // ".gitmodules") then
git repo_root [ "submodule"; "update"; "--init"; "--recursive" ]
@@> fun r ->
Expand Down
6 changes: 6 additions & 0 deletions src/repository/opamHg.ml
Original file line number Diff line number Diff line change
Expand Up @@ -56,6 +56,12 @@ module VCS = struct
if String.length full > 8 then Done (Some (String.sub full 0 8))
else Done (Some full)

let clean repo_root =
hg repo_root ["revert"; "--all"; "--no-backup"]
@@> fun r ->
OpamSystem.raise_on_process_error r;
Done ()

let reset_tree repo_root repo_url =
let mark = mark_from_url repo_url in
hg repo_root [ "update"; "--clean"; "--rev"; mark ] @@> fun r ->
Expand Down
2 changes: 2 additions & 0 deletions src/repository/opamVCS.ml
Original file line number Diff line number Diff line change
Expand Up @@ -29,6 +29,7 @@ module type VCS = sig
val is_dirty: ?subpath:string -> dirname -> bool OpamProcess.job
val modified_files: dirname -> string list OpamProcess.job
val get_remote_url: ?hash:string -> dirname -> url option OpamProcess.job
val clean: dirname -> unit OpamProcess.job
end

let convert_path =
Expand Down Expand Up @@ -83,6 +84,7 @@ module Make (VCS: VCS) = struct
Done (Not_available (None, OpamUrl.to_string url)))
@@ fun () ->
if VCS.exists dirname then
VCS.clean dirname @@+ fun () ->
VCS.fetch ?cache_dir ?subpath dirname url @@+ fun () ->
VCS.is_up_to_date dirname url @@+ function
| true -> Done (Up_to_date None)
Expand Down
6 changes: 5 additions & 1 deletion src/repository/opamVCS.mli
Original file line number Diff line number Diff line change
Expand Up @@ -68,10 +68,14 @@ module type VCS = sig
val is_dirty: ?subpath:string -> dirname -> bool OpamProcess.job

(** Returns the list of files under version control, modified in the working
tree but not comitted *)
tree but not committed *)
val modified_files: dirname -> string list OpamProcess.job

(* Returns associated remote url, if found *)
val get_remote_url: ?hash:string -> dirname -> url option OpamProcess.job

(* Remove uncommitted changes *)
val clean: dirname -> unit OpamProcess.job
end

(** Create a backend from a [VCS] implementation. *)
Expand Down
31 changes: 22 additions & 9 deletions src/state/opamSwitchState.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1172,15 +1172,28 @@ let update_pin nv opam st =
OpamStd.Option.default nv.version (OpamFile.OPAM.version_opt opam)
in
let nv = OpamPackage.create nv.name version in
update_package_metadata nv opam @@
{ st with
pinned =
OpamPackage.Set.add nv
(OpamPackage.filter_name_out st.pinned nv.name);
available_packages = lazy (
OpamPackage.filter_name_out (Lazy.force st.available_packages) nv.name
);
}
let pinned =
OpamPackage.Set.add nv (OpamPackage.filter_name_out st.pinned nv.name)
in
let available_packages = lazy (
OpamPackage.filter_name_out (Lazy.force st.available_packages) nv.name
) in
let st =
update_package_metadata nv opam { st with pinned; available_packages }
in
if not (OpamFile.Config.depext st.switch_global.config)
|| OpamSysPkg.Set.is_empty (depexts st nv)
then st else
let sys_packages = lazy (
OpamPackage.Map.union (fun _ n -> n)
(Lazy.force st.sys_packages)
(depexts_status_of_packages st (OpamPackage.Set.singleton nv))
) in
let available_packages = lazy (
OpamPackage.Set.filter (fun nv -> depexts_unavailable st nv = None)
(Lazy.force st.available_packages)
) in
{ st with sys_packages; available_packages }

let do_backup lock st = match lock with
| `Lock_write ->
Expand Down
2 changes: 1 addition & 1 deletion tests/reftests/conflict-resto.test
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
a5d7cdc0c914
a5d7cdc0
### <resto/ezresto-directory.opam>
opam-version: "2.0"
synopsis: "A minimal OCaml library for type-safe HTTP/JSON RPCs"
Expand Down
Loading

0 comments on commit c69fecc

Please sign in to comment.