diff --git a/master_changes.md b/master_changes.md index 082f8428b25..81a7058ffa4 100644 --- a/master_changes.md +++ b/master_changes.md @@ -102,6 +102,7 @@ users) * [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] * [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] * Allow opam pin remove to take a package (.) as argument [#5325 @kit-ty-kate] + * ◈ Add opam pin remove --all to remove all the pinned packages from a switch [#5308 @kit-ty-kate] ## List * Some optimisations to 'opam list --installable' queries combined with other filters [#4882 @altgr - fix #4311] @@ -577,3 +578,4 @@ users) * `OpamCompat`: add `Int.equal` (for ocaml < 4.12) * `OpamFilename.clean_dir`: as the directory is recreated after removal, checks that the directory exists beforhand. It avoid creating a new empty directory uselessly [#4967 @rjbou] * `OpamStd.Map`: add `filter_map` [#5337 @rjbou] + * `OpamStd.Set`: Add `to_list_map` [#5308 @kit-ty-kate] diff --git a/src/client/opamCommands.ml b/src/client/opamCommands.ml index ac3cd5eb386..51ba9737ca0 100644 --- a/src/client/opamCommands.ml +++ b/src/client/opamCommands.ml @@ -3184,6 +3184,10 @@ let pin ?(unpin_only=false) cli = changes, and may also be used to keep a package that was removed \ upstream." in + let all = + mk_flag ~cli (cli_from cli2_2) ["all"] + "When unpinning, removes all pins in the given switch." + in let guess_names kind ?locked ~recurse ?subpath url k = let found, cleanup = match OpamUrl.local_dir url with @@ -3300,7 +3304,7 @@ let pin ?(unpin_only=false) cli = let pin global_options build_options kind edit no_act dev_repo print_short recurse subpath normalise - with_version current + with_version current all command params () = apply_global_options cli global_options; apply_build_options cli build_options; @@ -3317,6 +3321,10 @@ let pin ?(unpin_only=false) cli = `list | Some `scan, [url] -> `scan url + | Some `remove, [] when all -> + `remove_all + | _, _ when all -> + `incorrect | Some `remove, (_::_ as arg) -> `remove arg | Some `edit, [nv] -> @@ -3418,6 +3426,14 @@ let pin ?(unpin_only=false) cli = else (OpamSwitchState.drop @@ OpamClient.PIN.unpin st ~action to_unpin; `Ok ()) + | `remove_all -> + OpamGlobalState.with_ `Lock_none @@ fun gt -> + OpamSwitchState.with_ `Lock_write gt @@ fun st -> + let to_unpin = + OpamPackage.Set.to_list_map OpamPackage.name (OpamPinned.packages st) + in + OpamSwitchState.drop @@ OpamClient.PIN.unpin st ~action to_unpin; + `Ok () | `edit nv -> (match (fst package) nv with | `Ok (name, version) -> @@ -3515,7 +3531,7 @@ let pin ?(unpin_only=false) cli = $global_options cli $build_options cli $kind $edit $no_act $dev_repo $print_short_flag cli cli_original $recurse cli $subpath cli - $normalise $with_version $current + $normalise $with_version $current $all $command $params) (* SOURCE *) diff --git a/src/core/opamStd.ml b/src/core/opamStd.ml index 3d5a65ac425..6d42782a55b 100644 --- a/src/core/opamStd.ml +++ b/src/core/opamStd.ml @@ -16,6 +16,7 @@ module type SET = sig val choose_one : t -> elt val choose_opt : t -> elt option val of_list: elt list -> t + val to_list_map: (elt -> 'b) -> t -> 'b list val to_string: t -> string val to_json: t OpamJson.encoder val of_json: t OpamJson.decoder @@ -222,6 +223,9 @@ module Set = struct let of_list l = List.fold_left (fun set e -> add e set) empty l + let to_list_map f set = + fold (fun x acc -> f x :: acc) set [] + let to_string s = if S.cardinal s > max_print then Printf.sprintf "%d elements" (S.cardinal s) diff --git a/src/core/opamStd.mli b/src/core/opamStd.mli index 34a40ec58a1..06ddac456c7 100644 --- a/src/core/opamStd.mli +++ b/src/core/opamStd.mli @@ -29,6 +29,7 @@ module type SET = sig val choose_opt: t -> elt option val of_list: elt list -> t + val to_list_map: (elt -> 'b) -> t -> 'b list val to_string: t -> string val to_json: t OpamJson.encoder val of_json: t OpamJson.decoder diff --git a/tests/reftests/pin.test b/tests/reftests/pin.test index 1490a2f2fd1..88e68d455e5 100644 --- a/tests/reftests/pin.test +++ b/tests/reftests/pin.test @@ -176,13 +176,61 @@ echo "another-inexistant" "inexistant" -> installed bar.dev Done. ### : Test opam pin remove . +### opam pin remove --no-action bar.dev +Ok, bar is no longer pinned to file://${BASEDIR}/bar (version dev) +### opam pin remove --no-action nip.wrong-version +[ERROR] nip is pinned but not to version wrong-version. Skipping. +# Return code 2 # +### : Test opam pin remove --all +### OPAMNODEPEXTS=1 +### opam pin add --no-action bar.dev ./bar +[bar.dev] synchronised (file://${BASEDIR}/bar) +bar is now pinned to file://${BASEDIR}/bar (version dev) ### opam pin bar.dev rsync file://${BASEDIR}/bar foo.1 local definition nip.dev rsync file://${BASEDIR}/nip qux.dev rsync file://${BASEDIR}/qux -### opam pin remove --no-action bar.dev +### opam pin remove --no-action --all +Ok, qux is no longer pinned to file://${BASEDIR}/qux (version dev) +Ok, nip is no longer pinned to file://${BASEDIR}/nip (version dev) +Ok, foo is no longer pinned locally (version 1) Ok, bar is no longer pinned to file://${BASEDIR}/bar (version dev) -### opam pin remove --no-action nip.wrong-version -[ERROR] nip is pinned but not to version wrong-version. Skipping. +### opam pin +### opam pin ./bar +The following additional pinnings are required by bar.dev: + - qux.dev at file://${BASEDIR}/qux +Pin and install them? [y/n] y +[qux.dev] synchronised (no changes) +qux is now pinned to file://${BASEDIR}/qux (version dev) +bar is now pinned to file://${BASEDIR}/bar (version dev) + +Already up-to-date. +Nothing to do. +### opam pin --current foo +foo is now pinned locally (version 1) +### opam pin +bar.dev rsync file://${BASEDIR}/bar +foo.1 local definition +qux.dev rsync file://${BASEDIR}/qux +### opam pin remove --all foo +opam: opamMain.exe: Too many arguments. + Usage: opamMain.exe pin [OPTION]... remove PACKAGES...|TARGET + # Return code 2 # +### opam pin remove --all +Ok, qux is no longer pinned to file://${BASEDIR}/qux (version dev) +Ok, foo is no longer pinned locally (version 1) +Ok, bar is no longer pinned to file://${BASEDIR}/bar (version dev) +The following actions will be performed: +=== remove 3 packages + - remove bar dev + - remove foo 1 + - remove qux dev + +<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><> +-> removed bar.dev +-> removed foo.1 +-> removed qux.dev +Done. +### opam pin