Skip to content

Commit db8c17f

Browse files
committed
refactor(pkg): consolidate repository handling
Signed-off-by: Ali Caglayan <[email protected]>
1 parent 1538b06 commit db8c17f

File tree

4 files changed

+37
-49
lines changed

4 files changed

+37
-49
lines changed

bin/pkg/pkg_common.ml

Lines changed: 1 addition & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -120,28 +120,7 @@ let unset_solver_vars_of_workspace workspace ~lock_dir_path =
120120
;;
121121

122122
let get_repos repos ~repositories =
123-
let module Repository = Dune_pkg.Pkg_workspace.Repository in
124-
repositories
125-
|> Fiber.parallel_map ~f:(fun (loc, name) ->
126-
match Repository.Name.Map.find repos name with
127-
| None ->
128-
User_error.raise
129-
~loc
130-
[ Pp.textf "Repository '%s' is not a known repository"
131-
@@ Repository.Name.to_string name
132-
]
133-
| Some repo ->
134-
let loc, opam_url = Repository.opam_url repo in
135-
let module Opam_repo = Dune_pkg.Opam_repo in
136-
(match Dune_pkg.OpamUrl.classify opam_url loc with
137-
| `Git -> Opam_repo.of_git_repo loc opam_url
138-
| `Path path -> Fiber.return @@ Opam_repo.of_opam_repo_dir_path loc path
139-
| `Archive ->
140-
User_error.raise
141-
~loc
142-
[ Pp.textf "Repositories stored in archives (%s) are currently unsupported"
143-
@@ OpamUrl.to_string opam_url
144-
]))
123+
Dune_pkg.Opam_repo.resolve_repositories ~available_repos:repos ~repositories
145124
;;
146125

147126
let find_local_packages =

src/dune_pkg/opam_repo.ml

Lines changed: 25 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -122,6 +122,31 @@ let of_git_repo loc url =
122122
{ source = Repo at_rev; serializable; loc }
123123
;;
124124

125+
let resolve_repositories ~available_repos ~repositories =
126+
repositories
127+
|> Fiber.parallel_map ~f:(fun (loc, name) ->
128+
match Workspace.Repository.Name.Map.find available_repos name with
129+
| None ->
130+
User_error.raise
131+
~loc
132+
[ Pp.textf
133+
"Repository '%s' is not a known repository"
134+
(Workspace.Repository.Name.to_string name)
135+
]
136+
| Some repo ->
137+
let loc, opam_url = Workspace.Repository.opam_url repo in
138+
(match OpamUrl.classify opam_url loc with
139+
| `Git -> of_git_repo loc opam_url
140+
| `Path path -> Fiber.return @@ of_opam_repo_dir_path loc path
141+
| `Archive ->
142+
User_error.raise
143+
~loc
144+
[ Pp.textf
145+
"Repositories stored in archives (%s) are currently unsupported"
146+
(OpamUrl.to_string opam_url)
147+
]))
148+
;;
149+
125150
let revision t =
126151
match t.source with
127152
| Repo r -> r

src/dune_pkg/opam_repo.mli

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -23,6 +23,16 @@ val of_opam_repo_dir_path : Loc.t -> Path.t -> t
2323
supports. *)
2424
val of_git_repo : Loc.t -> OpamUrl.t -> t Fiber.t
2525

26+
(** [resolve_repositories ~available_repos ~repositories] resolves a list of
27+
repository references by looking them up in [available_repos] and creating
28+
appropriate [t] instances based on their URL types (git, local path, or
29+
archive). Raises [User_error] if a repository is not found or if an archive
30+
URL is encountered (not supported). *)
31+
val resolve_repositories
32+
: available_repos:Workspace.Repository.t Workspace.Repository.Name.Map.t
33+
-> repositories:(Loc.t * Workspace.Repository.Name.t) list
34+
-> t list Fiber.t
35+
2636
val revision : t -> Rev_store.At_rev.t
2737
val serializable : t -> Serializable.t option
2838

src/dune_rules/lock_rules.ml

Lines changed: 1 addition & 27 deletions
Original file line numberDiff line numberDiff line change
@@ -312,9 +312,6 @@ let setup_lock_rules ~dir ~lock_dir : Gen_rules.result =
312312
>>| Dune_lang.Package.Name.Map.map ~f:Local_package.of_package
313313
|> Action_builder.of_memo
314314
and+ repos =
315-
(* CR-soon Alizter: This repository handling logic is duplicated in
316-
bin/pkg/pkg_common.ml:get_repos. The OpamUrl.classify pattern
317-
matching and repository resolution could be shared. *)
318315
Action_builder.of_memo
319316
(Memo.of_thunk (fun () ->
320317
let repositories =
@@ -334,30 +331,7 @@ let setup_lock_rules ~dir ~lock_dir : Gen_rules.result =
334331
Pkg_workspace.Repository.name repo, repo)
335332
|> Pkg_workspace.Repository.Name.Map.of_list_exn
336333
in
337-
let module Repository = Pkg_workspace.Repository in
338-
repositories
339-
|> Fiber.parallel_map ~f:(fun (loc, name) ->
340-
match Repository.Name.Map.find available_repos name with
341-
| None ->
342-
User_error.raise
343-
~loc
344-
[ Pp.textf "Repository '%s' is not a known repository"
345-
@@ Repository.Name.to_string name
346-
]
347-
| Some repo ->
348-
let loc, opam_url = Repository.opam_url repo in
349-
(match OpamUrl.classify opam_url loc with
350-
| `Git -> Opam_repo.of_git_repo loc opam_url
351-
| `Path path ->
352-
Fiber.return @@ Opam_repo.of_opam_repo_dir_path loc path
353-
| `Archive ->
354-
User_error.raise
355-
~loc
356-
[ Pp.textf
357-
"Repositories stored in archives (%s) are currently \
358-
unsupported"
359-
@@ OpamUrl.to_string opam_url
360-
]))
334+
Opam_repo.resolve_repositories ~available_repos ~repositories
361335
|> Memo.of_non_reproducible_fiber))
362336
and+ pins =
363337
(* CR-soon Alizter: This pin logic (extracting workspace pins,

0 commit comments

Comments
 (0)