Skip to content

Commit

Permalink
Add opam pin remove --all/-a
Browse files Browse the repository at this point in the history
  • Loading branch information
kit-ty-kate committed Oct 7, 2022
1 parent 5fb5c15 commit ea85f86
Show file tree
Hide file tree
Showing 3 changed files with 19 additions and 2 deletions.
16 changes: 14 additions & 2 deletions src/client/opamCommands.ml
Original file line number Diff line number Diff line change
Expand Up @@ -3147,6 +3147,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) ["a"; "all"]
"When unpinning, removes all pin 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 @@ -3263,7 +3267,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 @@ -3280,6 +3284,8 @@ let pin ?(unpin_only=false) cli =
`list
| Some `scan, [url] ->
`scan url
| Some `remove, _ when all ->
`remove_all
| Some `remove, (_::_ as arg) ->
`remove arg
| Some `edit, [nv] ->
Expand Down Expand Up @@ -3374,6 +3380,12 @@ 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 @@ -3471,7 +3483,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 @@ -221,6 +222,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

0 comments on commit ea85f86

Please sign in to comment.