Skip to content

Commit

Permalink
Merge pull request #5308 from kit-ty-kate/pin-remove-all
Browse files Browse the repository at this point in the history
Add opam pin remove --all
  • Loading branch information
kit-ty-kate authored Nov 16, 2022
2 parents 061d730 + 8a63708 commit b540b2e
Show file tree
Hide file tree
Showing 5 changed files with 76 additions and 5 deletions.
2 changes: 2 additions & 0 deletions master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -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 (<pkg>.<version>) 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]
Expand Down Expand Up @@ -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]
20 changes: 18 additions & 2 deletions src/client/opamCommands.ml
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down Expand Up @@ -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;
Expand All @@ -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] ->
Expand Down Expand Up @@ -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) ->
Expand Down Expand Up @@ -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 *)
Expand Down
4 changes: 4 additions & 0 deletions src/core/opamStd.ml
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down Expand Up @@ -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)
Expand Down
1 change: 1 addition & 0 deletions src/core/opamStd.mli
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
54 changes: 51 additions & 3 deletions tests/reftests/pin.test
Original file line number Diff line number Diff line change
Expand Up @@ -176,13 +176,61 @@ echo "another-inexistant" "inexistant"
-> installed bar.dev
Done.
### : Test opam pin remove <pkg>.<version>
### 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

0 comments on commit b540b2e

Please sign in to comment.