Skip to content

Commit

Permalink
Drastically simplify output when packages are missing in solve (#11040)
Browse files Browse the repository at this point in the history
Signed-off-by: Ambre Austen Suhamy <[email protected]>
  • Loading branch information
ElectreAAS authored Nov 20, 2024
1 parent 1e15301 commit 7f23a4b
Show file tree
Hide file tree
Showing 11 changed files with 64 additions and 61 deletions.
3 changes: 2 additions & 1 deletion src/0install-solver/diagnostics.ml
Original file line number Diff line number Diff line change
Expand Up @@ -40,7 +40,8 @@ module Make (Results : S.SOLVER_RESULT) = struct
(format_role other_role
++ Pp.char ' '
++ Model.pp_version impl
++ Pp.textf " requires %s" (format_restrictions r))
++ Pp.text " requires "
++ Pp.paragraph (format_restrictions r))
| Feed_problem msg -> Pp.text msg
;;
end
Expand Down
46 changes: 28 additions & 18 deletions src/opam-0install/lib/solver.ml
Original file line number Diff line number Diff line change
Expand Up @@ -33,31 +33,41 @@ module Make (Context : S.CONTEXT) = struct
| None -> Error req
;;

let pp_short = Input.pp_impl

let rec partition f = function
| [] -> [], []
| x :: xs ->
let ys, zs = partition f xs in
(match f x with
| `Left y -> y :: ys, zs
| `Right z -> ys, z :: zs)
let rec partition_three f = function
| [] -> [], [], []
| first :: rest ->
let xs, ys, zs = partition_three f rest in
(match f first with
| `Left x -> x :: xs, ys, zs
| `Middle y -> xs, y :: ys, zs
| `Right z -> xs, ys, z :: zs)
;;

let pp_rolemap ~verbose reasons =
let short, long =
let good, bad, unknown =
reasons
|> Solver.Output.RoleMap.bindings
|> partition (fun (_role, component) ->
|> partition_three (fun (role, component) ->
match Diagnostics.Component.selected_impl component with
| Some impl when Diagnostics.Component.notes component = [] -> `Left impl
| _ -> `Right component)
| _ ->
(match Diagnostics.Component.rejects component with
| _, `No_candidates -> `Right role
| _, _ -> `Middle component))
in
let pp_item = Diagnostics.Component.pp ~verbose in
Pp.paragraph "Selected: "
++ Pp.hovbox (Pp.concat_map ~sep:Pp.space short ~f:pp_short)
++ Pp.cut
++ Pp.enumerate long ~f:pp_item
let pp_bad = Diagnostics.Component.pp ~verbose in
let pp_unknown role = Pp.box (Solver.Output.Role.pp role) in
match unknown with
| [] ->
Pp.paragraph "Selected candidates: "
++ Pp.hovbox (Pp.concat_map ~sep:Pp.space good ~f:Input.pp_impl)
++ Pp.cut
++ Pp.enumerate bad ~f:pp_bad
| _ ->
(* In case of unknown packages, no need to print the full diagnostic list, the problem is simpler. *)
Pp.hovbox
(Pp.text "The following packages couldn't be found: "
++ Pp.concat_map ~sep:Pp.space unknown ~f:pp_unknown)
;;

let diagnostics_rolemap req =
Expand All @@ -66,7 +76,7 @@ module Make (Context : S.CONTEXT) = struct

let diagnostics ?(verbose = false) req =
let+ diag = diagnostics_rolemap req in
Pp.paragraph "Can't find all required versions."
Pp.paragraph "Couldn't solve the package dependency formula."
++ Pp.cut
++ Pp.vbox (pp_rolemap ~verbose diag)
;;
Expand Down
8 changes: 4 additions & 4 deletions test/blackbox-tests/test-cases/pkg/conflict-class.t
Original file line number Diff line number Diff line change
Expand Up @@ -32,8 +32,8 @@ Local conflict class defined in a local package:
$ dune pkg lock
Error: Unable to solve dependencies for the following lock directories:
Lock directory dune.lock:
Can't find all required versions.
Selected: foo.dev x.dev foo&x
Couldn't solve the package dependency formula.
Selected candidates: foo.dev x.dev foo&x
- bar -> (problem)
Rejected candidates:
bar.0.0.1: In same conflict class (ccc) as foo
Expand All @@ -51,8 +51,8 @@ Now the conflict class comes from the opam repository
$ dune pkg lock
Error: Unable to solve dependencies for the following lock directories:
Lock directory dune.lock:
Can't find all required versions.
Selected: foo.0.0.1 x.dev
Couldn't solve the package dependency formula.
Selected candidates: foo.0.0.1 x.dev
- bar -> (problem)
Rejected candidates:
bar.0.0.1: In same conflict class (ccc) as foo
Expand Down
4 changes: 2 additions & 2 deletions test/blackbox-tests/test-cases/pkg/conflicts.t
Original file line number Diff line number Diff line change
Expand Up @@ -19,8 +19,8 @@ The solver should say no solution rather than just ignoring the conflict.
> EOF
Error: Unable to solve dependencies for the following lock directories:
Lock directory dune.lock:
Can't find all required versions.
Selected: bar.0.0.1 x.dev
Couldn't solve the package dependency formula.
Selected candidates: bar.0.0.1 x.dev
- foo -> (problem)
x dev requires conflict with all versions
Rejected candidates:
Expand Down
4 changes: 2 additions & 2 deletions test/blackbox-tests/test-cases/pkg/implicit-dune-constraint.t
Original file line number Diff line number Diff line change
Expand Up @@ -19,8 +19,8 @@ dependency.
$ test "2.0.0"
Error: Unable to solve dependencies for the following lock directories:
Lock directory dune.lock:
Can't find all required versions.
Selected: foo.0.0.1 x.dev
Couldn't solve the package dependency formula.
Selected candidates: foo.0.0.1 x.dev
- dune -> (problem)
User requested = 3.17
Rejected candidates:
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -147,8 +147,8 @@ Run the solver again. This time it will fail.
$ dune pkg lock
Error: Unable to solve dependencies for the following lock directories:
Lock directory dune.lock:
Can't find all required versions.
Selected: baz.0.1.0 foo.0.0.1 lockfile_generation_test.dev
Couldn't solve the package dependency formula.
Selected candidates: baz.0.1.0 foo.0.0.1 lockfile_generation_test.dev
- bar -> (problem)
foo 0.0.1 requires >= 0.2
lockfile_generation_test dev requires >= 0.6
Expand Down
17 changes: 5 additions & 12 deletions test/blackbox-tests/test-cases/pkg/non-existent-dep.t
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
A package depending on a package that doesn't exist.
The solver should give a more sane error message.
The solver now gives a more sane error message.

A few packages here so the errors get large.
A few packages here so the errors could get large.
$ . ./helpers.sh
$ mkrepo
$ add_mock_repo_if_needed
Expand Down Expand Up @@ -36,14 +36,7 @@ A few packages here so the errors get large.
$ dune pkg lock
Error: Unable to solve dependencies for the following lock directories:
Lock directory dune.lock:
Can't find all required versions.
Selected: a.0.1.0 abc.dev b.0.0.1 d.0.0.1
- c -> (problem)
Rejected candidates:
c.0.0.1: Requires a < 0.1.0
- e -> e.0.1.0
abc dev requires = 0.1.0
- foobar -> (problem)
No known implementations at all
Couldn't solve the package dependency formula.
The following packages couldn't be found: foobar
[1]
The problem with foobar seems important enough to not show the wall of text above...
We only report about non-existent packages.
Original file line number Diff line number Diff line change
Expand Up @@ -61,11 +61,11 @@ This should fail as there is no version matching 0.24.1:
$ DUNE_CONFIG__LOCK_DEV_TOOL=enabled dune fmt
Error: Unable to solve dependencies for the following lock directories:
Lock directory dev-tools.locks/ocamlformat:
Can't find all required versions.
Selected: ocamlformat_dev_tool_wrapper.dev
Couldn't solve the package dependency formula.
Selected candidates: ocamlformat_dev_tool_wrapper.dev
- ocamlformat -> (problem)
ocamlformat_dev_tool_wrapper dev requires >= 0.24.1 & <=
0.24.1___MAX_VERSION
ocamlformat_dev_tool_wrapper dev requires
>= 0.24.1 & <= 0.24.1___MAX_VERSION
Rejected candidates:
ocamlformat.0.25+bar:
Incompatible with restriction: >= 0.24.1 & <= 0.24.1___MAX_VERSION
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -16,8 +16,6 @@ Format, it shows the solving error.
$ DUNE_CONFIG__LOCK_DEV_TOOL=enabled dune fmt
Error: Unable to solve dependencies for the following lock directories:
Lock directory dev-tools.locks/ocamlformat:
Can't find all required versions.
Selected: ocamlformat_dev_tool_wrapper.dev
- ocamlformat -> (problem)
No known implementations at all
Couldn't solve the package dependency formula.
The following packages couldn't be found: ocamlformat
[1]
16 changes: 8 additions & 8 deletions test/blackbox-tests/test-cases/pkg/unavailable-packages.t
Original file line number Diff line number Diff line change
Expand Up @@ -83,8 +83,8 @@ available on linux.
- linux-only.0.0.2
Error: Unable to solve dependencies for the following lock directories:
Lock directory dune.macos.lock:
Can't find all required versions.
Selected: x.dev
Couldn't solve the package dependency formula.
Selected candidates: x.dev
- linux-only -> (problem)
No usable implementations:
linux-only.0.0.2: Availability condition not satisfied
Expand All @@ -107,8 +107,8 @@ variable in its `available` filter. The undefined-var.0.0.2 package has a valid
- undefined-var.0.0.2
Error: Unable to solve dependencies for the following lock directories:
Lock directory dune.macos.lock:
Can't find all required versions.
Selected: x.dev
Couldn't solve the package dependency formula.
Selected candidates: x.dev
- undefined-var -> (problem)
No usable implementations:
undefined-var.0.0.2: Availability condition not satisfied
Expand All @@ -120,16 +120,16 @@ filter resolves to a string instead of to a boolean.
$ solve availability-string
Error: Unable to solve dependencies for the following lock directories:
Lock directory dune.lock:
Can't find all required versions.
Selected: x.dev
Couldn't solve the package dependency formula.
Selected candidates: x.dev
- availability-string -> (problem)
No usable implementations:
availability-string.0.0.2: Availability condition not satisfied
availability-string.0.0.1: Availability condition not satisfied
Error: Unable to solve dependencies for the following lock directories:
Lock directory dune.macos.lock:
Can't find all required versions.
Selected: x.dev
Couldn't solve the package dependency formula.
Selected candidates: x.dev
- availability-string -> (problem)
No usable implementations:
availability-string.0.0.2: Availability condition not satisfied
Expand Down
9 changes: 5 additions & 4 deletions test/blackbox-tests/test-cases/pkg/with-test-dependencies.t
Original file line number Diff line number Diff line change
Expand Up @@ -57,8 +57,8 @@ Conflicting packages can't be co-installed:
$ solve foo conflicts-with-foo
Error: Unable to solve dependencies for the following lock directories:
Lock directory dune.lock:
Can't find all required versions.
Selected: foo.0.0.1 foo-dependency.0.0.1 x.dev
Couldn't solve the package dependency formula.
Selected candidates: foo.0.0.1 foo-dependency.0.0.1 x.dev
- conflicts-with-foo -> (problem)
Rejected candidates:
conflicts-with-foo.0.0.1: Requires foo conflict with all versions
Expand All @@ -68,8 +68,9 @@ Conflicting packages in transitive dependencies can't be co-installed:
$ solve depends-on-foo conflicts-with-foo
Error: Unable to solve dependencies for the following lock directories:
Lock directory dune.lock:
Can't find all required versions.
Selected: depends-on-foo.0.0.1 foo.0.0.1 foo-dependency.0.0.1 x.dev
Couldn't solve the package dependency formula.
Selected candidates: depends-on-foo.0.0.1 foo.0.0.1 foo-dependency.0.0.1
x.dev
- conflicts-with-foo -> (problem)
Rejected candidates:
conflicts-with-foo.0.0.1: Requires foo conflict with all versions
Expand Down

0 comments on commit 7f23a4b

Please sign in to comment.