Skip to content

Commit

Permalink
Ensure each repositories stored in repos-config is associated with an…
Browse files Browse the repository at this point in the history
… URL
  • Loading branch information
kit-ty-kate committed Oct 17, 2024
1 parent d5d6ddd commit 5ece562
Show file tree
Hide file tree
Showing 6 changed files with 16 additions and 43 deletions.
2 changes: 2 additions & 0 deletions master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -95,6 +95,7 @@ users)
## Shell

## Internal
* Ensure each repositories stored in repos-config is associated with an URL [#6249 @kit-ty-kate]

## Internal: Windows

Expand Down Expand Up @@ -125,5 +126,6 @@ users)
## opam-solver

## opam-format
* `OpamFile.Repos_config.t`: change the type to not allow repositories without an URL [#6249 @kit-ty-kate]

## opam-core
5 changes: 1 addition & 4 deletions src/client/opamClient.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1885,10 +1885,7 @@ let init
else config
in
OpamFile.Config.write config_f config;
let repos_config =
OpamRepositoryName.Map.of_list repos |>
OpamRepositoryName.Map.map OpamStd.Option.some
in
let repos_config = OpamRepositoryName.Map.of_list repos in
OpamFile.Repos_config.write (OpamPath.repos_config root)
repos_config;

Expand Down
18 changes: 6 additions & 12 deletions src/format/opamFile.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1798,7 +1798,7 @@ module InitConfigSyntax = struct
Pp.V.map_options_3
(Pp.V.string -|
Pp.of_module "repository" (module OpamRepositoryName))
(Pp.opt @@ Pp.singleton -| Pp.V.url)
(Pp.singleton -| Pp.V.url)
(Pp.map_list Pp.V.string)
(Pp.opt @@
Pp.singleton -| Pp.V.int -|
Expand All @@ -1821,10 +1821,8 @@ module InitConfigSyntax = struct
with_repositories repositories
(Pp.V.map_list ~depth:1 @@
pp_repository_def -|
Pp.pp (fun ~pos -> function
| (name, Some url, ta) -> (name, (url, ta))
| (_, None, _) -> Pp.bad_format ~pos "Missing repository URL")
(fun (name, (url, ta)) -> (name, Some url, ta)));
Pp.pp (fun ~pos:_ (name, url, ta) -> (name, (url, ta)))
(fun (name, (url, ta)) -> (name, url, ta)));
"default-compiler", Pp.ppacc
with_default_compiler default_compiler
(Pp.V.package_formula `Disj Pp.V.(constraints Pp.V.version));
Expand Down Expand Up @@ -1965,7 +1963,7 @@ module Repos_configSyntax = struct
let format_version = OpamVersion.of_string "2.0"
let file_format_version = OpamVersion.of_string "2.0"

type t = ((url * trust_anchors option) option) OpamRepositoryName.Map.t
type t = (url * trust_anchors option) OpamRepositoryName.Map.t

let empty = OpamRepositoryName.Map.empty

Expand All @@ -1975,12 +1973,8 @@ module Repos_configSyntax = struct
((Pp.V.map_list ~depth:1 @@
InitConfigSyntax.pp_repository_def -|
Pp.pp
(fun ~pos:_ -> function
| (name, Some url, ta) -> name, Some (url, ta)
| (name, None, _) -> name, None)
(fun (name, def) -> match def with
| Some (url, ta) -> name, Some url, ta
| None -> name, None, None)) -|
(fun ~pos:_ (name, url, ta) -> (name, (url, ta)))
(fun (name, (url, ta)) -> (name, url, ta))) -|
Pp.of_pair "repository-url-list"
OpamRepositoryName.Map.(of_list, bindings));
]
Expand Down
2 changes: 1 addition & 1 deletion src/format/opamFile.mli
Original file line number Diff line number Diff line change
Expand Up @@ -1028,7 +1028,7 @@ module Repo_config_legacy : sig
end

module Repos_config: sig
type t = (url * trust_anchors option) option OpamRepositoryName.Map.t
type t = (url * trust_anchors option) OpamRepositoryName.Map.t
include IO_FILE with type t := t
module BestEffort: BestEffortRead with type t := t
end
Expand Down
2 changes: 1 addition & 1 deletion src/state/opamFormatUpgrade.ml
Original file line number Diff line number Diff line change
Expand Up @@ -770,7 +770,7 @@ let from_1_3_dev7_to_2_0_alpha ~on_the_fly:_ root conf =
in
OpamFile.Repos_config.write (OpamPath.repos_config root)
(OpamRepositoryName.Map.of_list
(List.map (fun (_, r, u) -> r, Some (u,None)) prio_repositories));
(List.map (fun (_, r, u) -> r, (u,None)) prio_repositories));
let prio_repositories =
List.stable_sort (fun (prio1, _, _) (prio2, _, _) -> prio2 - prio1)
prio_repositories
Expand Down
30 changes: 5 additions & 25 deletions src/state/opamRepositoryState.ml
Original file line number Diff line number Diff line change
Expand Up @@ -164,16 +164,11 @@ let load lock_kind gt =
load with best-effort (read-only)"
(OpamVersion.to_string (OpamFile.Config.opam_root_version gt.config))
(OpamVersion.to_string (OpamFile.Config.root_version));
let mk_repo name url_opt = {
let mk_repo name (url, ta) = {
repo_name = name;
repo_url = OpamStd.Option.Op.((url_opt >>| fst) +! OpamUrl.empty);
repo_trust = OpamStd.Option.Op.(url_opt >>= snd);
repo_url = url;
repo_trust = ta;
} in
let uncached =
(* Don't cache repositories without remote, as they should be editable
in-place *)
OpamRepositoryName.Map.filter (fun _ url -> url = None) repos_map
in
let repositories = OpamRepositoryName.Map.mapi mk_repo repos_map in
let repos_tmp_root = lazy (OpamFilename.mk_tmp_dir ()) in
let repos_tmp = Hashtbl.create 23 in
Expand Down Expand Up @@ -211,22 +206,8 @@ let load lock_kind gt =
rt
in
match Cache.load gt.root with
| Some (repofiles, opams) when OpamRepositoryName.Map.is_empty uncached ->
log "Cache found";
make_rt repofiles opams
| Some (repofiles, opams) ->
log "Cache found, loading repositories without remote only";
OpamFilename.with_flock_upgrade `Lock_read lock @@ fun _ ->
let repofiles, opams =
OpamRepositoryName.Map.fold (fun name url (defs, opams) ->
let repo = mk_repo name url in
let repo_def, repo_opams =
load_repo repo (get_root_raw gt.root repos_tmp name)
in
OpamRepositoryName.Map.add name repo_def defs,
OpamRepositoryName.Map.add name repo_opams opams)
uncached (repofiles, opams)
in
log "Cache found";
make_rt repofiles opams
| None ->
log "No cache found";
Expand Down Expand Up @@ -297,7 +278,7 @@ let with_ lock gt f =

let write_config rt =
OpamFile.Repos_config.write (OpamPath.repos_config rt.repos_global.root)
(OpamRepositoryName.Map.map (fun r ->
(OpamRepositoryName.Map.filter_map (fun _ r ->
if r.repo_url = OpamUrl.empty then None
else Some (r.repo_url, r.repo_trust))
rt.repositories)
Expand All @@ -312,4 +293,3 @@ let check_last_update () =
OpamConsole.note "It seems you have not updated your repositories \
for a while. Consider updating them with:\n%s\n"
(OpamConsole.colorise `bold "opam update");

0 comments on commit 5ece562

Please sign in to comment.