Skip to content

Commit

Permalink
feat(pkg): Remove opam-repository-url option
Browse files Browse the repository at this point in the history
Since the repositories are specified in the workspace file where more
information like URL, branch or tag can be stored this makes for a
better set-up.

Signed-off-by: Marek Kubica <[email protected]>
  • Loading branch information
Leonidas-from-XIV committed Dec 4, 2023
1 parent 9c41108 commit 0c28f48
Show file tree
Hide file tree
Showing 5 changed files with 18 additions and 67 deletions.
12 changes: 1 addition & 11 deletions bin/pkg/lock.ml
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,6 @@ let check_for_dup_lock_dir_paths ts =
let solve
per_context
~opam_repository_path
~opam_repository_url
~update_opam_repositories
~solver_env_from_current_system
~experimental_translate_opam_filters
Expand Down Expand Up @@ -64,12 +63,7 @@ let solve
solver_env ~solver_env_from_context ~solver_env_from_current_system
in
let* repos =
get_repos
repos
~opam_repository_path
~opam_repository_url
~repositories
~update_opam_repositories
get_repos repos ~opam_repository_path ~repositories ~update_opam_repositories
in
let overlay =
Console.Status_line.add_overlay (Constant (Pp.text "Solving for Build Plan"))
Expand Down Expand Up @@ -129,7 +123,6 @@ let lock
~dont_poll_system_solver_variables
~version_preference
~opam_repository_path
~opam_repository_url
~update_opam_repositories
~experimental_translate_opam_filters
=
Expand All @@ -150,7 +143,6 @@ let lock
solve
per_context
~opam_repository_path
~opam_repository_url
~update_opam_repositories
~solver_env_from_current_system
~experimental_translate_opam_filters
Expand All @@ -159,7 +151,6 @@ let lock
let term =
let+ builder = Common.Builder.term
and+ opam_repository_path = Opam_repository_path.term
and+ opam_repository_url = Opam_repository_url.term
and+ context_name =
context_term
~doc:
Expand Down Expand Up @@ -212,7 +203,6 @@ let term =
~dont_poll_system_solver_variables
~version_preference
~opam_repository_path
~opam_repository_url
~update_opam_repositories:(not skip_update)
~experimental_translate_opam_filters)
;;
Expand Down
4 changes: 0 additions & 4 deletions bin/pkg/outdated.ml
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,6 @@ let find_outdated_packages
~context_name_arg
~all_contexts_arg
~opam_repository_path
~opam_repository_url
~transitive
()
=
Expand All @@ -30,7 +29,6 @@ let find_outdated_packages
get_repos
repos
~opam_repository_path
~opam_repository_url
~repositories
~update_opam_repositories:true
and+ local_packages = find_local_packages in
Expand Down Expand Up @@ -89,7 +87,6 @@ let term =
& flag
& info [ "all-contexts" ] ~doc:"Check for outdated packages in all contexts")
and+ opam_repository_path = Opam_repository_path.term
and+ opam_repository_url = Opam_repository_url.term
and+ transitive =
Arg.(
value
Expand All @@ -105,7 +102,6 @@ let term =
~context_name_arg
~all_contexts_arg
~opam_repository_path
~opam_repository_url
~transitive
;;

Expand Down
52 changes: 7 additions & 45 deletions bin/pkg/pkg_common.ml
Original file line number Diff line number Diff line change
Expand Up @@ -133,40 +133,23 @@ let location_of_opam_url url =
]
;;

let get_repos
repos
~opam_repository_path
~opam_repository_url
~repositories
~update_opam_repositories
=
let get_repos repos ~opam_repository_path ~repositories ~update_opam_repositories =
let module Repository_id = Dune_pkg.Repository_id in
let module Opam_repo = Dune_pkg.Opam_repo in
let open Fiber.O in
match opam_repository_path, opam_repository_url with
| Some _, Some _ ->
(* in theory you can set both, but how to prioritize them? *)
User_error.raise [ Pp.text "Can't specify both path and URL to an opam-repository" ]
| Some path, None ->
let module Repository = Dune_pkg.Pkg_workspace.Repository in
match opam_repository_path with
| Some path ->
let repo_id = Repository_id.of_path path in
Fiber.return @@ [ Opam_repo.of_opam_repo_dir_path ~source:None ~repo_id path ]
| None, Some (url : OpamUrl.t) ->
let+ opam_repo =
Opam_repo.of_git_repo
~repo_id:None
~update:update_opam_repositories
~source:url.path
in
[ opam_repo ]
| None, None ->
| None ->
repositories
|> Fiber.parallel_map ~f:(fun name ->
match Dune_pkg.Pkg_workspace.Repository.Name.Map.find repos name with
match Repository.Name.Map.find repos name with
| None ->
(* TODO: have loc for this failure? *)
User_error.raise
[ Pp.textf "Repository '%s' is not a known repository"
@@ Dune_pkg.Pkg_workspace.Repository.Name.to_string name
@@ Repository.Name.to_string name
]
| Some repo ->
let opam_url = Dune_pkg.Pkg_workspace.Repository.opam_url repo in
Expand Down Expand Up @@ -212,27 +195,6 @@ module Opam_repository_path = struct
;;
end

module Opam_repository_url = struct
let term =
let parser s =
match OpamUrl.parse_opt s with
| Some url -> Ok url
| None -> Error (`Msg "URL can't be parsed")
in
let printer pf u = Pp.to_fmt pf (Pp.text (OpamUrl.to_string u)) in
let opam_url = Arg.conv (parser, printer) in
Arg.(
value
& opt (some opam_url) None
& info
[ "opam-repository-url" ]
~docv:"URL"
~doc:
"URL of opam repository to download. Can be either a git repository or a \
link to the tarball of a repository.")
;;
end

let pp_packages packages =
let module Package_version = Dune_pkg.Package_version in
Pp.enumerate
Expand Down
5 changes: 0 additions & 5 deletions bin/pkg/pkg_common.mli
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,6 @@ end
val get_repos
: Dune_pkg.Pkg_workspace.Repository.t Dune_pkg.Pkg_workspace.Repository.Name.Map.t
-> opam_repository_path:Path.t option
-> opam_repository_url:OpamUrl.t option
-> repositories:Dune_pkg.Pkg_workspace.Repository.Name.t list
-> update_opam_repositories:bool
-> Dune_pkg.Opam_repo.t list Fiber.t
Expand All @@ -49,10 +48,6 @@ module Opam_repository_path : sig
val term : Path.t option Term.t
end

module Opam_repository_url : sig
val term : OpamUrl.t option Term.t
end

(** [pp_packages lock_dir] returns a list of pretty-printed packages
occuring in [lock_dir]. *)
val pp_packages : Dune_pkg.Lock_dir.Pkg.t list -> 'a Pp.t
12 changes: 10 additions & 2 deletions test/blackbox-tests/test-cases/pkg/opam-repository-download.t
Original file line number Diff line number Diff line change
Expand Up @@ -19,15 +19,23 @@ Make a mock repo tarball that will get used by dune to download the package
$ mkdir fake-xdg-cache

$ cat > dune-project <<EOF
> (lang dune 3.8)
> (lang dune 3.10)
> (generate_opam_files true)
>
> (package
> (name baz)
> (depends bar))
> EOF
$ cat > dune-workspace <<EOF
> (lang dune 3.10)
> (lock_dir
> (repositories mock))
> (repository
> (name mock)
> (source "git+file://$(pwd)/mock-opam-repository"))
> EOF

$ XDG_CACHE_HOME=$(pwd)/fake-xdg-cache dune pkg lock --opam-repository-url=git+file://$(pwd)/mock-opam-repository
$ XDG_CACHE_HOME=$(pwd)/fake-xdg-cache dune pkg lock
Solution for dune.lock:
- bar.0.0.1
- foo.0.0.1
Expand Down

0 comments on commit 0c28f48

Please sign in to comment.