Skip to content

Commit

Permalink
pkg: lock dir args defaults to dune.lock rather than all lockdirs
Browse files Browse the repository at this point in the history
Signed-off-by: Ali Caglayan <[email protected]>
  • Loading branch information
Alizter committed Dec 11, 2023
1 parent fdf7233 commit f0c717e
Show file tree
Hide file tree
Showing 14 changed files with 102 additions and 68 deletions.
2 changes: 0 additions & 2 deletions bin/common.ml
Original file line number Diff line number Diff line change
Expand Up @@ -47,8 +47,6 @@ let debug_backtraces =

let default_build_dir = "_build"

(* Allow options from term1 or exclusively options from term2. If the user
passes options from both terms, an error is reported. *)
let one_of term1 term2 =
Term.ret
@@ let+ x, args1 = Term.with_used_args term1
Expand Down
4 changes: 4 additions & 0 deletions bin/common.mli
Original file line number Diff line number Diff line change
Expand Up @@ -87,3 +87,7 @@ module Let_syntax : sig
val ( let+ ) : 'a Cmdliner.Term.t -> ('a -> 'b) -> 'b Cmdliner.Term.t
val ( and+ ) : 'a Cmdliner.Term.t -> 'b Cmdliner.Term.t -> ('a * 'b) Cmdliner.Term.t
end

(** [one_of term1 term2] allows options from [term1] or exclusively options from
[term2]. If the user passes options from both terms, an error is reported. *)
val one_of : 'a Cmdliner.Term.t -> 'a Cmdliner.Term.t -> 'a Cmdliner.Term.t
25 changes: 15 additions & 10 deletions bin/describe/describe_pkg.ml
Original file line number Diff line number Diff line change
Expand Up @@ -3,12 +3,11 @@ module Lock_dir = Dune_pkg.Lock_dir
module Local_package = Dune_pkg.Local_package

module Show_lock = struct
let term =
let+ lock_dir_paths = Pkg_common.Lock_dirs.term in
let lock_dir_paths =
match lock_dir_paths with
| [] -> [ Lock_dir.default_path ]
| lock_dir_paths -> lock_dir_paths
let print_lock lock_dir_arg () =
let open Fiber.O in
let+ lock_dir_paths =
Memo.run (Workspace.workspace ())
>>| Pkg_common.Lock_dirs_arg.lock_dirs_of_workspace lock_dir_arg
in
Console.print
@@ List.map lock_dir_paths ~f:(fun lock_dir_path ->
Expand All @@ -23,6 +22,14 @@ module Show_lock = struct
|> Pp.vbox)
;;

let term =
let+ builder = Common.Builder.term
and+ lock_dir_arg = Pkg_common.Lock_dirs_arg.term in
let builder = Common.Builder.forbid_builds builder in
let common, config = Common.init builder in
Scheduler.go ~common ~config @@ print_lock lock_dir_arg
;;

let command =
let doc = "Display packages in a lock file" in
let info = Cmd.info ~doc "lock" in
Expand Down Expand Up @@ -110,9 +117,7 @@ module List_locked_dependencies = struct
let enumerate_lock_dirs_by_path ~lock_dirs =
let open Fiber.O in
let+ workspace = Memo.run (Workspace.workspace ()) in
let lock_dirs =
Pkg_common.Lock_dirs.of_workspace workspace ~chosen_lock_dirs:lock_dirs
in
let lock_dirs = Pkg_common.Lock_dirs_arg.lock_dirs_of_workspace lock_dirs workspace in
List.filter_map lock_dirs ~f:(fun lock_dir_path ->
if Path.exists (Path.source lock_dir_path)
then (
Expand Down Expand Up @@ -167,7 +172,7 @@ module List_locked_dependencies = struct
~doc:
"Display transitive dependencies (by default only immediate dependencies \
are displayed)")
and+ lock_dirs = Pkg_common.Lock_dirs.term in
and+ lock_dirs = Pkg_common.Lock_dirs_arg.term in
let builder = Common.Builder.forbid_builds builder in
let common, config = Common.init builder in
Scheduler.go ~common ~config @@ list_locked_dependencies ~transitive ~lock_dirs
Expand Down
12 changes: 6 additions & 6 deletions bin/pkg/lock.ml
Original file line number Diff line number Diff line change
Expand Up @@ -10,15 +10,15 @@ let solve
~update_opam_repositories
~solver_env_from_current_system
~version_preference
~lock_dirs
~lock_dirs_arg
=
let open Fiber.O in
(* a list of thunks that will perform all the file IO side
effects after performing validation so that if materializing any
lockdir would fail then no side effect takes place. *)
(let* local_packages = find_local_packages in
let+ solutions =
Lock_dirs.of_workspace workspace ~chosen_lock_dirs:lock_dirs
Pkg_common.Lock_dirs_arg.lock_dirs_of_workspace lock_dirs_arg workspace
|> Fiber.parallel_map ~f:(fun lock_dir_path ->
let lock_dir = Workspace.find_lock_dir workspace lock_dir_path in
let solver_env =
Expand Down Expand Up @@ -89,7 +89,7 @@ let lock
~dont_poll_system_solver_variables
~version_preference
~update_opam_repositories
~lock_dirs
~lock_dirs_arg
=
let open Fiber.O in
let* workspace = Memo.run (Workspace.workspace ())
Expand All @@ -106,7 +106,7 @@ let lock
~update_opam_repositories
~solver_env_from_current_system
~version_preference
~lock_dirs
~lock_dirs_arg
;;

let term =
Expand Down Expand Up @@ -134,15 +134,15 @@ let term =
~doc:
"Do not fetch updates of opam repositories, will use the cached opam \
metadata. This allows offline use if the repositories are cached locally.")
and+ lock_dirs = Lock_dirs.term in
and+ lock_dirs_arg = Pkg_common.Lock_dirs_arg.term in
let builder = Common.Builder.forbid_builds builder in
let common, config = Common.init builder in
Scheduler.go ~common ~config (fun () ->
lock
~dont_poll_system_solver_variables
~version_preference
~update_opam_repositories:(not skip_update)
~lock_dirs)
~lock_dirs_arg)
;;

let info =
Expand Down
8 changes: 4 additions & 4 deletions bin/pkg/outdated.ml
Original file line number Diff line number Diff line change
Expand Up @@ -3,11 +3,11 @@ open Pkg_common
module Lock_dir = Dune_pkg.Lock_dir
module Opam_repo = Dune_pkg.Opam_repo

let find_outdated_packages ~transitive ~lock_dirs () =
let find_outdated_packages ~transitive ~lock_dirs_arg () =
let open Fiber.O in
let+ pps, not_founds =
let* workspace = Memo.run (Workspace.workspace ()) in
Lock_dirs.of_workspace workspace ~chosen_lock_dirs:lock_dirs
Pkg_common.Lock_dirs_arg.lock_dirs_of_workspace lock_dirs_arg workspace
|> Fiber.parallel_map ~f:(fun lock_dir_path ->
(* updating makes sense when checking for outdated packages *)
let* repos =
Expand Down Expand Up @@ -69,10 +69,10 @@ let term =
& info
[ "transitive" ]
~doc:"Check for outdated packages in transitive dependencies")
and+ lock_dirs = Lock_dirs.term in
and+ lock_dirs_arg = Pkg_common.Lock_dirs_arg.term in
let builder = Common.Builder.forbid_builds builder in
let common, config = Common.init builder in
Scheduler.go ~common ~config @@ find_outdated_packages ~transitive ~lock_dirs
Scheduler.go ~common ~config @@ find_outdated_packages ~transitive ~lock_dirs_arg
;;

let info =
Expand Down
46 changes: 31 additions & 15 deletions bin/pkg/pkg_common.ml
Original file line number Diff line number Diff line change
Expand Up @@ -112,21 +112,36 @@ let pp_packages packages =
Pp.verbatim (Package_name.to_string name ^ "." ^ Package_version.to_string version))
;;

module Lock_dirs = struct
module Lock_dirs_arg = struct
type t =
| All
| Selected of Path.Source.t list

let term =
let+ arg =
Arg.(
value
& pos_all string []
& info
[]
~docv:"LOCKDIRS"
~doc:"Lock directories to check for outdated packages. Defaults to dune.lock.")
in
List.map arg ~f:Path.Source.of_string
Common.one_of
(let+ arg =
Arg.(
value
& pos_all string []
& info
[]
~docv:"LOCKDIRS"
~doc:
"Lock directories to check for outdated packages. Defaults to dune.lock.")
in
Selected (List.map arg ~f:Path.Source.of_string))
(let+ _all =
Arg.(
value
& flag
& info
[ "all" ]
~doc:"Check all lock directories in the workspace for outdated packages.")
in
All)
;;

let of_workspace (workspace : Workspace.t) ~chosen_lock_dirs =
let lock_dirs_of_workspace t (workspace : Workspace.t) =
let workspace_lock_dirs =
List.filter_map workspace.contexts ~f:(function
| Workspace.Context.Default { lock_dir; base = _ } ->
Expand All @@ -136,9 +151,10 @@ module Lock_dirs = struct
Some lock_dir_path
| Opam _ -> None)
in
match chosen_lock_dirs with
| [] -> workspace_lock_dirs
| _ ->
match t with
| All -> workspace_lock_dirs
| Selected [] -> [ Lock_dir.default_path ]
| Selected chosen_lock_dirs ->
let workspace_lock_dirs_set = Path.Source.Set.of_list workspace_lock_dirs in
let chosen_lock_dirs_set = Path.Source.Set.of_list chosen_lock_dirs in
if Path.Source.Set.is_subset chosen_lock_dirs_set ~of_:workspace_lock_dirs_set
Expand Down
35 changes: 21 additions & 14 deletions bin/pkg/pkg_common.mli
Original file line number Diff line number Diff line change
Expand Up @@ -40,25 +40,32 @@ val get_repos

val find_local_packages : Dune_pkg.Local_package.t Package_name.Map.t Fiber.t

module Lock_dirs : sig
(** [Lock_dirs.term] is a command-line argument that can be used to specify
the lock directories to consider. This can then be passed as
[~chosen_lock_dirs] to [Lock_dirs.of_workspace].*)
val term : Path.Source.t list Term.t
module Lock_dirs_arg : sig
(** [Lock_dirs_arg.t] is the type of lock directory arguments. This can be
created with [Lock_dirs_arg.term] and used with
[Lock_dirs_arg.lock_dirs_of_workspace]. *)
type t

(** [Lock_dirs.of_workspace workspace ~chosen_lock_dirs] returns the list of
lock directories that should be considered for various operations. If
[chosen_lock_dirs] is empty, then all lock directories are considered.
(** [Lock_dirs_arg.term] is a command-line argument that can be used to
specify the lock directories to consider. This can then be passed to
[Lock_dirs_arg.lock_dirs_of_workspace].
There are two mutually exclusive cases:
- The user passed a list of lick directories as positonal
arguments.contents
- The user passed the ["--all"] flag, in which case all lock directories
of the workspace are considered. *)
val term : t Term.t

(** [Lock_dirs_arg.lock_dirs_of_workspace t workspace] returns the list of
lock directories that should be considered for various operations.
The [workspace] argument is used to determine the list of all lock lock
directories.
A user error is raised if the [chosen_lock_dirs] are not a subset of the
lock directories of the workspace. *)
val of_workspace
: Workspace.t
-> chosen_lock_dirs:Path.Source.t list
-> Path.Source.t list
A user error is raised if the list of positional arguments used when
creating [t] is not a subset of the lock directories of the workspace. *)
val lock_dirs_of_workspace : t -> Workspace.t -> Path.Source.t list
end

(** [pp_packages lock_dir] returns a list of pretty-printed packages occuring in
Expand Down
8 changes: 4 additions & 4 deletions bin/pkg/print_solver_env.ml
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ let print_solver_env_for_lock_dir workspace ~solver_env_from_current_system lock
]
;;

let print_solver_env ~dont_poll_system_solver_variables ~lock_dirs =
let print_solver_env ~dont_poll_system_solver_variables ~lock_dirs_arg =
let open Fiber.O in
let+ workspace = Memo.run (Workspace.workspace ())
and+ solver_env_from_current_system =
Expand All @@ -26,7 +26,7 @@ let print_solver_env ~dont_poll_system_solver_variables ~lock_dirs =
~path:(Env_path.path Stdune.Env.initial)
>>| Option.some
in
let lock_dirs = Lock_dirs.of_workspace workspace ~chosen_lock_dirs:lock_dirs in
let lock_dirs = Lock_dirs_arg.lock_dirs_of_workspace lock_dirs_arg workspace in
List.iter
lock_dirs
~f:(print_solver_env_for_lock_dir workspace ~solver_env_from_current_system)
Expand All @@ -47,11 +47,11 @@ let term =
\"undefined\" which is treated as false. For example if a dependency has a \
filter `{os = \"linux\"}` and the variable \"os\" is unset, the dependency \
will be excluded. ")
and+ lock_dirs = Lock_dirs.term in
and+ lock_dirs_arg = Lock_dirs_arg.term in
let builder = Common.Builder.forbid_builds builder in
let common, config = Common.init builder in
Scheduler.go ~common ~config (fun () ->
print_solver_env ~dont_poll_system_solver_variables ~lock_dirs)
print_solver_env ~dont_poll_system_solver_variables ~lock_dirs_arg)
;;

let info =
Expand Down
4 changes: 2 additions & 2 deletions bin/pkg/validate_lock_dir.ml
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@ let enumerate_lock_dirs_by_path ~lock_dirs () =
let open Fiber.O in
let+ per_contexts =
Memo.run (Workspace.workspace ())
>>| Pkg_common.Lock_dirs.of_workspace ~chosen_lock_dirs:lock_dirs
>>| Pkg_common.Lock_dirs_arg.lock_dirs_of_workspace lock_dirs
in
List.filter_map per_contexts ~f:(fun lock_dir_path ->
if Path.exists (Path.source lock_dir_path)
Expand Down Expand Up @@ -72,7 +72,7 @@ let validate_lock_dirs ~lock_dirs () =

let term =
let+ builder = Common.Builder.term
and+ lock_dirs = Pkg_common.Lock_dirs.term in
and+ lock_dirs = Pkg_common.Lock_dirs_arg.term in
let builder = Common.Builder.forbid_builds builder in
let common, config = Common.init builder in
Scheduler.go ~common ~config @@ validate_lock_dirs ~lock_dirs
Expand Down
4 changes: 2 additions & 2 deletions test/blackbox-tests/test-cases/pkg/conflict-class.t
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,7 @@ Local conflict class defined in a local package:
> EOF

$ dune pkg lock
Error: Unable to solve dependencies in build context: default
Error: Unable to solve dependencies for dune.lock:
Can't find all required versions.
Selected: foo.dev x.dev foo&x
- bar -> (problem)
Expand All @@ -48,7 +48,7 @@ Now the conflict class comes from the opam repository
$ rm foo.opam

$ dune pkg lock
Error: Unable to solve dependencies in build context: default
Error: Unable to solve dependencies for dune.lock:
Can't find all required versions.
Selected: foo.0.0.1 x.dev
- bar -> (problem)
Expand Down
2 changes: 1 addition & 1 deletion test/blackbox-tests/test-cases/pkg/describe-pkg-lock.t
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,7 @@ First we setup a repo.
> EOF

Here is the output of solving for multiple contexts:
$ solve_project <<EOF
$ solve_project --all <<EOF
> (lang dune 3.11)
> (package
> (name x)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -53,7 +53,7 @@ Create a workspace config that defines separate build contexts for macos and lin
> EOF

Now the os-specific dependencies are included on their respective systems.
$ dune pkg lock --dont-poll-system-solver-variables
$ dune pkg lock --all
Solution for dune.macos.lock:
- foo.0.0.1
- foo-macos.0.0.1
Expand Down
2 changes: 1 addition & 1 deletion test/blackbox-tests/test-cases/pkg/just-print-solver-env.t
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,7 @@ Add some build contexts with different environments
> (lock_dir change-opam-version.lock)))
> EOF

$ dune pkg print-solver-env --dont-poll-system-solver-variables
$ dune pkg print-solver-env --all --dont-poll-system-solver-variables
Solver environment for lock directory change-opam-version.lock:
- opam-version = 42
- with-doc = false
Expand Down
Loading

0 comments on commit f0c717e

Please sign in to comment.