Skip to content

Commit

Permalink
Merge pull request #5014 from kit-ty-kate/check-repos-remove-exist
Browse files Browse the repository at this point in the history
Check that the repositories given to "opam repository remove" actually exist
  • Loading branch information
rjbou authored Dec 18, 2024
2 parents 68f993d + 567cd03 commit 26290a4
Show file tree
Hide file tree
Showing 4 changed files with 86 additions and 16 deletions.
2 changes: 2 additions & 0 deletions master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -70,6 +70,7 @@ users)
* [BUG] Fix SWH liveness check [#6036 @rjbou - fix #5721]
* Update SWH API request [#6036 @rjbou]
* Rework SWH fallback to have a more correct archive retrieval and more fine grained error handling [#6036 @rjbou - fix #5721]
* Check that the repositories given to `opam repository remove` actually exist [#5014 @kit-ty-kate - fixes #5012]

## Lock

Expand Down Expand Up @@ -185,6 +186,7 @@ users)
## opam-client
* `OpamArg.InvalidCLI`: export exception [#6150 @rjbou]
* `OpamArg`: export `require_checksums` and `no_checksums`, that are shared with `build_options` [#5563 @rjbou]
* `OpamRepositoryCommand.switch_repos`: expose the function [#5014 @kit-ty-kate]

## opam-repository
* `OpamDownload.get_output`: fix `wget` option for `POST` requests [#6036 @rjbou]
Expand Down
54 changes: 38 additions & 16 deletions src/client/opamCommands.ml
Original file line number Diff line number Diff line change
Expand Up @@ -2345,13 +2345,14 @@ let repository cli =
OpamStd.List.insert_at rank new_repo
(List.filter (( <> ) new_repo ) repos)
in
let check_for_repos rt names err =
let check_for_repos repos names err =
match
List.filter (fun n ->
not (OpamRepositoryName.Map.mem n rt.repositories))
not (List.exists (OpamRepositoryName.equal n) repos))
names
with [] -> () | l ->
err (OpamStd.List.concat_map " " OpamRepositoryName.to_string l)
with [] -> true | l ->
err (OpamStd.List.concat_map " " OpamRepositoryName.to_string l);
List.compare_lengths l names <> 0
in
OpamGlobalState.with_ `Lock_none @@ fun gt ->
let all_switches = OpamFile.Config.installed_switches gt.config in
Expand Down Expand Up @@ -2421,30 +2422,51 @@ let repository cli =
`Ok ()
| Some `remove, names ->
let names = List.map OpamRepositoryName.of_string names in
let rm = List.filter (fun n -> not (List.mem n names)) in
let full_wipe = List.mem `All scope in
let global = global || full_wipe in
let gt =
OpamRepositoryCommand.update_selection gt
~global ~switches:switches rm
in
if full_wipe then
OpamRepositoryState.with_ `Lock_write gt @@ fun rt ->
check_for_repos rt names
let repos =
OpamRepositoryName.Map.keys rt.OpamStateTypes.repositories
in
ignore @@ check_for_repos repos names
(OpamConsole.warning
"No configured repositories by these names found: %s");
OpamRepositoryState.drop @@
List.fold_left OpamRepositoryCommand.remove rt names
else if scope = [`Current_switch] then
OpamConsole.msg
"Repositories removed from the selections of switch %s. \
Use '--all' to forget about them altogether.\n"
(OpamSwitch.to_string (OpamStateConfig.get_switch ()));
else begin
let has_known_repos =
OpamRepositoryState.with_ `Lock_none gt @@ fun rt ->
List.fold_left (fun has_known_repos switch ->
let repos = OpamRepositoryCommand.switch_repos rt switch in
check_for_repos repos names
(OpamConsole.warning
"No configured repositories by these names found in \
the selection of switch '%s': %s"
(OpamSwitch.to_string switch))
|| has_known_repos)
false switches
in
if scope = [`Current_switch] && has_known_repos then
OpamConsole.msg
"Repositories removed from the selections of switch %s. \
Use '--all' to forget about them altogether.\n"
(OpamSwitch.to_string (OpamStateConfig.get_switch ()));
end;
let rm =
List.filter (fun n ->
not (List.exists (OpamRepositoryName.equal n) names))
in
ignore @@ OpamRepositoryCommand.update_selection gt
~global ~switches:switches rm;
`Ok ()
| Some `add, [name] ->
let name = OpamRepositoryName.of_string name in
OpamRepositoryState.with_ `Lock_none gt (fun rt ->
check_for_repos rt [name]
let repos =
OpamRepositoryName.Map.keys rt.OpamStateTypes.repositories
in
ignore @@ check_for_repos repos [name]
(OpamConsole.error_and_exit `Not_found
"No configured repository '%s' found, you must specify an URL"));
OpamGlobalState.drop @@
Expand Down
3 changes: 3 additions & 0 deletions src/client/opamRepositoryCommand.mli
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,9 @@
open OpamTypes
open OpamStateTypes

(** Returns the repository names registered in the given switch *)
val switch_repos : 'a repos_state -> OpamSwitch.t -> OpamRepositoryName.t list

(** List the selected repositories in the global default and/or selected
switches. *)
val list:
Expand Down
43 changes: 43 additions & 0 deletions tests/reftests/repository.test
Original file line number Diff line number Diff line change
Expand Up @@ -817,6 +817,7 @@ GARBAGE
[ERROR] No package matching two-three found
# Return code 5 #
### : Repo config with no url repo
### cp OPAM/repo/repos-config repos-config.bak
### opam switch create nourl --empty
### opam repo remove --all repo versions
### <nourl/repo>
Expand Down Expand Up @@ -868,3 +869,45 @@ opam-version: "2.0"

# Packages matching: any
# No matches found
### mv repos-config.bak OPAM/repo/repos-config
### : Check the behaviour of opam repository remove when given unknown repositories
### <REM/repo>
opam-version: "2.0"
### mkdir REM/packages
### opam switch create rm-unknown --empty
### opam repository add oper ./REM --this-switch
[oper] Initialised
### opam repository add oper3 ./REM --this-switch
[oper3] Initialised
### opam repository add repo2 ./REM --dont-select
[repo2] Initialised
### opam repository add to-many-commits ./REM --this-switch
[to-many-commits] Initialised
### opam repository remove repo versions --all
### opam repository --all --short
oper
oper3
repo2
to-many-commits
### opam repository --short
to-many-commits
oper3
oper
### opam repository remove does-not-exist
[WARNING] No configured repositories by these names found in the selection of switch 'rm-unknown': does-not-exist
### opam repository remove does-not-exist --all
[WARNING] No configured repositories by these names found: does-not-exist
### opam repository remove does-not-exist oper
[WARNING] No configured repositories by these names found in the selection of switch 'rm-unknown': does-not-exist
Repositories removed from the selections of switch rm-unknown. Use '--all' to forget about them altogether.
### opam repository remove does-not-exist repo2
[WARNING] No configured repositories by these names found in the selection of switch 'rm-unknown': does-not-exist repo2
### opam repository remove does-not-exist repo2 --all
[WARNING] No configured repositories by these names found: does-not-exist
### opam repository --all --short
oper
oper3
to-many-commits
### opam repository --short
to-many-commits
oper3

0 comments on commit 26290a4

Please sign in to comment.