Skip to content

Commit

Permalink
pkg: remove context arguments
Browse files Browse the repository at this point in the history
Signed-off-by: Ali Caglayan <[email protected]>
  • Loading branch information
Alizter committed Dec 1, 2023
1 parent f64e045 commit 121be2e
Show file tree
Hide file tree
Showing 22 changed files with 48 additions and 344 deletions.
27 changes: 5 additions & 22 deletions bin/describe/describe_pkg.ml
Original file line number Diff line number Diff line change
Expand Up @@ -117,14 +117,9 @@ module List_locked_dependencies = struct
|> Pp.vbox
;;

let enumerate_lock_dirs_by_path ~context_name_arg ~all_contexts_arg =
let enumerate_lock_dirs_by_path =
let open Fiber.O in
let+ per_contexts =
Pkg_common.Per_context.choose
~context_name_arg
~all_contexts_arg
~version_preference_arg:None
in
let+ per_contexts = Pkg_common.Per_context.choose ~version_preference_arg:None in
List.filter_map per_contexts ~f:(fun { Pkg_common.Per_context.lock_dir_path; _ } ->
if Path.exists (Path.source lock_dir_path)
then (
Expand All @@ -140,10 +135,9 @@ module List_locked_dependencies = struct
else None)
;;

let list_locked_dependencies ~context_name_arg ~all_contexts_arg ~transitive =
let list_locked_dependencies ~transitive =
let open Fiber.O in
let+ lock_dirs_by_path =
enumerate_lock_dirs_by_path ~context_name_arg ~all_contexts_arg
let+ lock_dirs_by_path = enumerate_lock_dirs_by_path
and+ local_packages = Pkg_common.find_local_packages in
let pp =
Pp.concat
Expand Down Expand Up @@ -171,12 +165,6 @@ module List_locked_dependencies = struct

let term =
let+ builder = Common.Builder.term
and+ context_name =
Pkg_common.context_term
~doc:"Print information about the lockdir associated with this context"
and+ all_contexts =
Arg.(
value & flag & info [ "all-contexts" ] ~doc:"Print information about all lockdirs")
and+ transitive =
Arg.(
value
Expand All @@ -189,12 +177,7 @@ module List_locked_dependencies = struct
in
let builder = Common.Builder.forbid_builds builder in
let common, config = Common.init builder in
Scheduler.go ~common ~config
@@ fun () ->
list_locked_dependencies
~context_name_arg:context_name
~all_contexts_arg:all_contexts
~transitive
Scheduler.go ~common ~config @@ fun () -> list_locked_dependencies ~transitive
;;

let command = Cmd.v info term
Expand Down
18 changes: 1 addition & 17 deletions bin/pkg/lock.ml
Original file line number Diff line number Diff line change
Expand Up @@ -124,8 +124,6 @@ let solve
;;

let lock
~context_name
~all_contexts
~dont_poll_system_solver_variables
~version_preference
~opam_repository_path
Expand All @@ -134,11 +132,7 @@ let lock
~experimental_translate_opam_filters
=
let open Fiber.O in
let* per_context =
Per_context.choose
~context_name_arg:context_name
~all_contexts_arg:all_contexts
~version_preference_arg:version_preference
let* per_context = Per_context.choose ~version_preference_arg:version_preference
and* solver_env_from_current_system =
if dont_poll_system_solver_variables
then Fiber.return None
Expand All @@ -160,14 +154,6 @@ 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:
"Generate the lockdir associated with this context (the default context will be \
used if this is omitted)"
and+ all_contexts =
Arg.(
value & flag & info [ "all-contexts" ] ~doc:"Generate the lockdir for all contexts")
and+ version_preference = Version_preference.term
and+ dont_poll_system_solver_variables =
Arg.(
Expand Down Expand Up @@ -207,8 +193,6 @@ let term =
let common, config = Common.init builder in
Scheduler.go ~common ~config (fun () ->
lock
~context_name
~all_contexts
~dont_poll_system_solver_variables
~version_preference
~opam_repository_path
Expand Down
24 changes: 3 additions & 21 deletions bin/pkg/outdated.ml
Original file line number Diff line number Diff line change
Expand Up @@ -3,17 +3,10 @@ open Pkg_common
module Lock_dir = Dune_pkg.Lock_dir
module Opam_repo = Dune_pkg.Opam_repo

let find_outdated_packages
~context_name_arg
~all_contexts_arg
~opam_repository_path
~opam_repository_url
~transitive
()
=
let find_outdated_packages ~opam_repository_path ~opam_repository_url ~transitive () =
let open Fiber.O in
let+ pps, not_founds =
Per_context.choose ~context_name_arg ~all_contexts_arg ~version_preference_arg:None
Per_context.choose ~version_preference_arg:None
>>= Fiber.parallel_map
~f:
(fun
Expand Down Expand Up @@ -82,12 +75,6 @@ let find_outdated_packages

let term =
let+ builder = Common.Builder.term
and+ context_name_arg = context_term ~doc:"Check for outdated packages in this context"
and+ all_contexts_arg =
Arg.(
value
& 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 =
Expand All @@ -101,12 +88,7 @@ let term =
let builder = Common.Builder.forbid_builds builder in
let common, config = Common.init builder in
Scheduler.go ~common ~config
@@ find_outdated_packages
~context_name_arg
~all_contexts_arg
~opam_repository_path
~opam_repository_url
~transitive
@@ find_outdated_packages ~opam_repository_path ~opam_repository_url ~transitive
;;

let info =
Expand Down
45 changes: 6 additions & 39 deletions bin/pkg/pkg_common.ml
Original file line number Diff line number Diff line change
Expand Up @@ -4,10 +4,6 @@ module Solver_env = Dune_pkg.Solver_env
module Variable_name = Dune_pkg.Variable_name
module Variable_value = Dune_pkg.Variable_value

let context_term ~doc =
Arg.(value & opt (some Arg.context_name) None & info [ "context" ] ~docv:"CONTEXT" ~doc)
;;

let solver_env ~solver_env_from_current_system ~solver_env_from_context =
[ solver_env_from_current_system; solver_env_from_context ]
|> List.filter_opt
Expand Down Expand Up @@ -82,42 +78,13 @@ module Per_context = struct
}
;;

let choose ~context_name_arg ~all_contexts_arg ~version_preference_arg =
let choose ~version_preference_arg =
let open Fiber.O in
match context_name_arg, all_contexts_arg with
| Some _, true ->
User_error.raise [ Pp.text "--context and --all-contexts are mutually exclusive" ]
| context_name_opt, false ->
let+ workspace = Memo.run (Workspace.workspace ()) in
let context_name =
Option.value context_name_opt ~default:Dune_engine.Context_name.default
in
let context =
(* TODO this doesn't work for target contexts defined by cross compilation *)
List.find workspace.contexts ~f:(fun context ->
Dune_engine.Context_name.equal (Workspace.Context.name context) context_name)
in
(match context with
| None ->
User_error.raise
[ Pp.textf
"Unknown build context: %s"
(Dune_engine.Context_name.to_string context_name |> String.maybe_quoted)
]
| Some (Default { lock; base = context_common; _ }) ->
[ make_solver workspace context_common ~version_preference_arg ~lock ]
| Some (Opam _) ->
User_error.raise
[ Pp.textf
"Unexpected opam build context: %s"
(Dune_engine.Context_name.to_string context_name |> String.maybe_quoted)
])
| None, true ->
let+ workspace = Memo.run (Workspace.workspace ()) in
List.filter_map workspace.contexts ~f:(function
| Workspace.Context.Default { lock; base = context_common } ->
Some (make_solver workspace context_common ~version_preference_arg ~lock)
| Opam _ -> None)
let+ workspace = Memo.run (Workspace.workspace ()) in
List.filter_map workspace.contexts ~f:(function
| Workspace.Context.Default { lock; base = context_common } ->
Some (make_solver workspace context_common ~version_preference_arg ~lock)
| Opam _ -> None)
;;
end

Expand Down
6 changes: 1 addition & 5 deletions bin/pkg/pkg_common.mli
Original file line number Diff line number Diff line change
@@ -1,7 +1,5 @@
open Import

val context_term : doc:string -> Context_name.t option Term.t

(** Create a [Dune_pkg.Solver_env.t] by combining variables taken from the
current system and variables taken from the current context, with priority
being given to the latter. Also adds a binding from the variable
Expand All @@ -27,9 +25,7 @@ module Per_context : sig
}

val choose
: context_name_arg:Context_name.t option
-> all_contexts_arg:bool
-> version_preference_arg:Dune_pkg.Version_preference.t option
: version_preference_arg:Dune_pkg.Version_preference.t option
-> t list Fiber.t
end

Expand Down
27 changes: 3 additions & 24 deletions bin/pkg/print_solver_env.ml
Original file line number Diff line number Diff line change
Expand Up @@ -17,18 +17,9 @@ let print_solver_env_for_one_context
]
;;

let print_solver_env
~context_name
~all_contexts
~version_preference
~dont_poll_system_solver_variables
=
let print_solver_env ~version_preference ~dont_poll_system_solver_variables =
let open Fiber.O in
let+ per_context =
Per_context.choose
~context_name_arg:context_name
~all_contexts_arg:all_contexts
~version_preference_arg:version_preference
let+ per_context = Per_context.choose ~version_preference_arg:version_preference
and+ solver_env_from_current_system =
if dont_poll_system_solver_variables
then Fiber.return None
Expand All @@ -44,14 +35,6 @@ let print_solver_env

let term =
let+ builder = Common.Builder.term
and+ context_name =
context_term
~doc:
"Generate the lockdir associated with this context (the default context will be \
used if this is omitted)"
and+ all_contexts =
Arg.(
value & flag & info [ "all-contexts" ] ~doc:"Generate the lockdir for all contexts")
and+ version_preference = Version_preference.term
and+ dont_poll_system_solver_variables =
Arg.(
Expand All @@ -70,11 +53,7 @@ let term =
let builder = Common.Builder.forbid_builds builder in
let common, config = Common.init builder in
Scheduler.go ~common ~config (fun () ->
print_solver_env
~context_name
~all_contexts
~version_preference
~dont_poll_system_solver_variables)
print_solver_env ~version_preference ~dont_poll_system_solver_variables)
;;

let info =
Expand Down
24 changes: 6 additions & 18 deletions bin/pkg/validate_lock_dir.ml
Original file line number Diff line number Diff line change
Expand Up @@ -11,14 +11,9 @@ let info =
Cmd.info "validate-lockdir" ~doc ~man
;;

let enumerate_lock_dirs_by_path ~context_name_arg ~all_contexts_arg =
let enumerate_lock_dirs_by_path () =
let open Fiber.O in
let+ per_contexts =
Pkg_common.Per_context.choose
~context_name_arg
~all_contexts_arg
~version_preference_arg:None
in
let+ per_contexts = Pkg_common.Per_context.choose ~version_preference_arg:None in
List.filter_map per_contexts ~f:(fun { Pkg_common.Per_context.lock_dir_path; _ } ->
if Path.exists (Path.source lock_dir_path)
then (
Expand All @@ -27,9 +22,9 @@ let enumerate_lock_dirs_by_path ~context_name_arg ~all_contexts_arg =
else None)
;;

let validate_lock_dirs ~context_name_arg ~all_contexts_arg =
let validate_lock_dirs () =
let open Fiber.O in
let+ lock_dirs_by_path = enumerate_lock_dirs_by_path ~context_name_arg ~all_contexts_arg
let+ lock_dirs_by_path = enumerate_lock_dirs_by_path ()
and+ local_packages = Pkg_common.find_local_packages in
if List.is_empty lock_dirs_by_path
then Console.print [ Pp.text "No lockdirs to validate." ]
Expand Down Expand Up @@ -70,17 +65,10 @@ let validate_lock_dirs ~context_name_arg ~all_contexts_arg =
;;

let term =
let+ builder = Common.Builder.term
and+ context_name =
Pkg_common.context_term ~doc:"Validate the lockdir associated with this context"
and+ all_contexts =
Arg.(value & flag & info [ "all-contexts" ] ~doc:"Validate all lockdirs")
in
let+ builder = Common.Builder.term in
let builder = Common.Builder.forbid_builds builder in
let common, config = Common.init builder in
Scheduler.go ~common ~config
@@ fun () ->
validate_lock_dirs ~context_name_arg:context_name ~all_contexts_arg:all_contexts
Scheduler.go ~common ~config validate_lock_dirs
;;

let command = Cmd.v info term
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 @@ -23,7 +23,7 @@ First we setup a repo.
> EOF

Here is the output of solving for multiple contexts:
$ solve_project --all-contexts <<EOF
$ solve_project <<EOF
> (lang dune 3.11)
> (package
> (name x)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -14,19 +14,8 @@ Define several build contexts that all use the default lockdir
> (name custom-context-with-default-lock-dir)))
> EOF

Check that we can still generate lockdirs for individual contexts:
It's an error to lock when multiple contexts have the same lockdir:
$ dune pkg lock --opam-repository-path=mock-opam-repository
Solution for dune.lock:
(no dependencies to lock)
$ dune pkg lock --opam-repository-path=mock-opam-repository --context=default
Solution for dune.lock:
(no dependencies to lock)
$ dune pkg lock --opam-repository-path=mock-opam-repository --context=custom-context-with-default-lock-dir
Solution for dune.lock:
(no dependencies to lock)

It's an error to use --all-contexts when there are multiple contexts with the same lockdir:
$ dune pkg lock --opam-repository-path=mock-opam-repository --all-contexts
File "dune-workspace", line 5, characters 1-56:
5 | (default
6 | (name custom-context-with-default-lock-dir)))
Expand All @@ -50,16 +39,8 @@ Define several build contexts that all use the same custom lockdir:
> (lock foo.lock)))
> EOF

Check that we can still generate lockdirs for individual contexts:
$ dune pkg lock --opam-repository-path=mock-opam-repository --context=a
Solution for foo.lock:
(no dependencies to lock)
$ dune pkg lock --opam-repository-path=mock-opam-repository --context=b
Solution for foo.lock:
(no dependencies to lock)

It's an error to use --all-contexts when there are multiple contexts with the same lockdir:
$ dune pkg lock --opam-repository-path=mock-opam-repository --all-contexts
It's an error to lock when multiple contexts have the same lockdir:
$ dune pkg lock --opam-repository-path=mock-opam-repository
File "dune-workspace", line 7, characters 1-39:
7 | (default
8 | (name a)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -48,7 +48,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 --opam-repository-path=mock-opam-repository --all-contexts
$ dune pkg lock --dont-poll-system-solver-variables --opam-repository-path=mock-opam-repository
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 @@ -28,7 +28,7 @@ Add some build contexts with different environments
> (lock dune.linux.no-doc.lock)))
> EOF

$ dune pkg print-solver-env --all-contexts --dont-poll-system-solver-variables
$ dune pkg print-solver-env --dont-poll-system-solver-variables
Solver environment for context no-doc:
- arch = x86_64
- opam-version = 2.2.0~alpha-vendored
Expand Down

This file was deleted.

This file was deleted.

This file was deleted.

Loading

0 comments on commit 121be2e

Please sign in to comment.