Skip to content

Commit 56d6850

Browse files
authored
Merge pull request #12642 from gridbugs/portable-lockdirs-dedup-errors
Deduplicate solver errors when generating portable lockdirs
2 parents ce22e00 + 25af255 commit 56d6850

File tree

3 files changed

+161
-37
lines changed

3 files changed

+161
-37
lines changed

bin/pkg/lock.ml

Lines changed: 69 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -84,6 +84,33 @@ let resolve_project_pins project_pins =
8484
Pin.resolve project_pins ~scan_project
8585
;;
8686

87+
module Platforms_by_message = struct
88+
module Message_map = Map.Make (struct
89+
type t = User_message.Style.t Pp.t
90+
91+
let to_dyn = Pp.to_dyn User_message.Style.to_dyn
92+
let compare = Pp.compare ~compare:User_message.Style.compare
93+
end)
94+
95+
(* Map messages to the list of platforms for which those messages are
96+
relevant. If a dependency problem has no solution on any platform, it's
97+
likely that the error from the solver will be identical across all
98+
platforms. We don't want to print the same error message once for each
99+
platform, so this type collects messages and the platforms for which they
100+
are relevant, deduplicating common messages. *)
101+
type t = Solver_env.t list Message_map.t
102+
103+
let singleton message platform : t = Message_map.singleton message [ platform ]
104+
105+
let to_list (t : t) : (User_message.Style.t Pp.t * Solver_env.t list) list =
106+
Message_map.to_list t
107+
;;
108+
109+
let union_all ts : t = Message_map.union_all ts ~f:(fun _ a b -> Some (a @ b))
110+
let all_platforms (t : t) = Message_map.values t |> List.concat
111+
let all_messages (t : t) = Message_map.keys t
112+
end
113+
87114
let solve_multiple_platforms
88115
base_solver_env
89116
version_preference
@@ -117,7 +144,7 @@ let solve_multiple_platforms
117144
let solver_env = Solver_env.extend portable_solver_env platform_env in
118145
let+ solver_result = solve_for_env solver_env in
119146
Result.map_error solver_result ~f:(fun (`Diagnostic_message message) ->
120-
platform_env, message))
147+
Platforms_by_message.singleton message platform_env))
121148
in
122149
let solver_results, errors =
123150
List.partition_map results ~f:(function
@@ -126,14 +153,14 @@ let solve_multiple_platforms
126153
in
127154
match solver_results, errors with
128155
| [], [] -> Code_error.raise "Solver did not run for any platforms." []
129-
| [], errors -> `All_error errors
156+
| [], errors -> `All_error (Platforms_by_message.union_all errors)
130157
| x :: xs, errors ->
131158
let merged_solver_result =
132159
List.fold_left xs ~init:x ~f:Dune_pkg.Opam_solver.Solver_result.merge
133160
in
134161
if List.is_empty errors
135162
then `All_ok merged_solver_result
136-
else `Partial (merged_solver_result, errors)
163+
else `Partial (merged_solver_result, Platforms_by_message.union_all errors)
137164
;;
138165

139166
let summary_message
@@ -207,6 +234,23 @@ let summary_message
207234
@ maybe_unsolved_platforms_message
208235
;;
209236

237+
let pp_solve_errors_by_platforms platforms_by_message =
238+
Platforms_by_message.to_list platforms_by_message
239+
|> List.map ~f:(fun (solver_error, platforms) ->
240+
Pp.concat
241+
~sep:Pp.cut
242+
[ Pp.nop
243+
; Pp.box
244+
@@ Pp.text
245+
"The dependency solver failed to find a solution for the following \
246+
platforms:"
247+
; Pp.enumerate platforms ~f:Solver_env.pp_oneline
248+
; Pp.box @@ Pp.text "...with this error:"
249+
; solver_error
250+
]
251+
|> Pp.vbox)
252+
;;
253+
210254
let solve_lock_dir
211255
workspace
212256
~local_packages
@@ -285,14 +329,7 @@ let solve_lock_dir
285329
| `All_error messages -> Error messages
286330
| `All_ok solver_result -> Ok (solver_result, [])
287331
| `Partial (solver_result, errors) ->
288-
Log.info
289-
@@ List.map errors ~f:(fun (platform, solver_error) ->
290-
Pp.concat
291-
~sep:Pp.newline
292-
[ Pp.box @@ Pp.text "Failed to find package solution for platform:"
293-
; Solver_env.pp platform
294-
; solver_error
295-
]);
332+
Log.info @@ pp_solve_errors_by_platforms errors;
296333
Ok
297334
( solver_result
298335
, [ Pp.nop
@@ -303,8 +340,9 @@ let solve_lock_dir
303340
@@ Pp.text "No package solution was found for some requsted platforms."
304341
; Pp.nop
305342
; Pp.box @@ Pp.text "Platforms with no solution:"
306-
; Pp.enumerate errors ~f:(fun (platform, _) ->
307-
Solver_env.pp_oneline platform)
343+
; Pp.enumerate
344+
(Platforms_by_message.all_platforms errors)
345+
~f:Solver_env.pp_oneline
308346
; Pp.nop
309347
; Pp.box
310348
@@ Pp.text
@@ -395,13 +433,24 @@ let solve
395433
| _ -> Error errors)
396434
>>| function
397435
| Error errors ->
398-
User_error.raise
399-
([ Pp.text "Unable to solve dependencies for the following lock directories:" ]
400-
@ List.concat_map errors ~f:(fun (path, messages_by_platform) ->
401-
let messages = List.map messages_by_platform ~f:snd in
402-
[ Pp.textf "Lock directory %s:" (Path.to_string_maybe_quoted path)
403-
; Pp.hovbox (Pp.concat ~sep:Pp.newline messages)
404-
]))
436+
if portable_lock_dir
437+
then
438+
User_error.raise
439+
(List.concat_map errors ~f:(fun (path, errors) ->
440+
[ Pp.box
441+
@@ Pp.textf
442+
"Unable to solve dependencies while generating lock directory: %s"
443+
(Path.to_string_maybe_quoted path)
444+
; Pp.vbox (Pp.concat ~sep:Pp.cut (pp_solve_errors_by_platforms errors))
445+
]))
446+
else
447+
User_error.raise
448+
([ Pp.text "Unable to solve dependencies for the following lock directories:" ]
449+
@ List.concat_map errors ~f:(fun (path, errors) ->
450+
let messages = Platforms_by_message.all_messages errors in
451+
[ Pp.textf "Lock directory %s:" (Path.to_string_maybe_quoted path)
452+
; Pp.vbox (Pp.concat ~sep:Pp.cut messages)
453+
]))
405454
| Ok write_disks_with_summaries ->
406455
let write_disk_list, summary_messages = List.split write_disks_with_summaries in
407456
List.iter summary_messages ~f:Console.print_user_message;
Lines changed: 86 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,86 @@
1+
Demonstrate the case where a project can't be solved at all.
2+
3+
$ . ../helpers.sh
4+
$ mkrepo
5+
$ add_mock_repo_if_needed
6+
7+
Make some packages that can't be coinstalled:
8+
$ mkpkg a <<EOF
9+
> depends: [
10+
> "c" {= "0.1"}
11+
> ]
12+
> EOF
13+
14+
$ mkpkg b <<EOF
15+
> depends: [
16+
> "c" {= "0.2"}
17+
> ]
18+
> EOF
19+
20+
$ mkpkg c "0.2"
21+
22+
Depend on a pair of packages which can't be coinstalled:
23+
$ cat > dune-project <<EOF
24+
> (lang dune 3.18)
25+
> (package
26+
> (name foo)
27+
> (depends a b))
28+
> EOF
29+
30+
Solver error when solving fails with the same error on all platforms:
31+
$ DUNE_CONFIG__PORTABLE_LOCK_DIR=enabled dune pkg lock
32+
Error:
33+
Unable to solve dependencies while generating lock directory: dune.lock
34+
35+
The dependency solver failed to find a solution for the following platforms:
36+
- arch = x86_64; os = linux
37+
- arch = arm64; os = linux
38+
- arch = x86_64; os = macos
39+
- arch = arm64; os = macos
40+
- arch = x86_64; os = win32
41+
...with this error:
42+
Couldn't solve the package dependency formula.
43+
Selected candidates: a.0.0.1 b.0.0.1 foo.dev
44+
- c -> (problem)
45+
a 0.0.1 requires = 0.1
46+
Rejected candidates:
47+
c.0.2: Incompatible with restriction: = 0.1
48+
[1]
49+
50+
Modify the "a" package so the solver error is different on different platforms:
51+
$ mkpkg a <<EOF
52+
> depends: [
53+
> "c" {= "0.1" & os = "linux"}
54+
> "c" {= "0.3" & os != "linux"}
55+
> ]
56+
> EOF
57+
58+
This time there will be two different solver errors. Both will be printed along
59+
with the platforms where they are relevant:
60+
$ DUNE_CONFIG__PORTABLE_LOCK_DIR=enabled dune pkg lock
61+
Error:
62+
Unable to solve dependencies while generating lock directory: dune.lock
63+
64+
The dependency solver failed to find a solution for the following platforms:
65+
- arch = x86_64; os = linux
66+
- arch = arm64; os = linux
67+
...with this error:
68+
Couldn't solve the package dependency formula.
69+
Selected candidates: a.0.0.1 b.0.0.1 foo.dev
70+
- c -> (problem)
71+
a 0.0.1 requires = 0.1
72+
Rejected candidates:
73+
c.0.2: Incompatible with restriction: = 0.1
74+
75+
The dependency solver failed to find a solution for the following platforms:
76+
- arch = x86_64; os = macos
77+
- arch = arm64; os = macos
78+
- arch = x86_64; os = win32
79+
...with this error:
80+
Couldn't solve the package dependency formula.
81+
Selected candidates: a.0.0.1 b.0.0.1 foo.dev
82+
- c -> (problem)
83+
a 0.0.1 requires = 0.3
84+
Rejected candidates:
85+
c.0.2: Incompatible with restriction: = 0.3
86+
[1]

test/blackbox-tests/test-cases/pkg/portable-lockdirs/portable-lockdirs-partial-solve.t

Lines changed: 6 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -53,23 +53,12 @@ to solve for macos, linux, and windows by default.
5353
solve for in the dune-workspace file.
5454

5555
The log file will contain errors about the package being unavailable.
56-
$ sed -n -e "/Couldn't solve the package dependency formula./,\$p" _build/log
57-
# Couldn't solve the package dependency formula.
58-
# Selected candidates: x.dev
59-
# - foo -> (problem)
60-
# No usable implementations:
61-
# foo.0.0.1: Availability condition not satisfied
62-
# Failed to find package solution for platform:
63-
# - arch = arm64
64-
# - os = linux
65-
# Couldn't solve the package dependency formula.
66-
# Selected candidates: x.dev
67-
# - foo -> (problem)
68-
# No usable implementations:
69-
# foo.0.0.1: Availability condition not satisfied
70-
# Failed to find package solution for platform:
71-
# - arch = x86_64
72-
# - os = win32
56+
$ sed -n -e "/The dependency solver failed to find a solution for the following platforms:/,\$p" _build/log
57+
# The dependency solver failed to find a solution for the following platforms:
58+
# - arch = x86_64; os = linux
59+
# - arch = arm64; os = linux
60+
# - arch = x86_64; os = win32
61+
# ...with this error:
7362
# Couldn't solve the package dependency formula.
7463
# Selected candidates: x.dev
7564
# - foo -> (problem)

0 commit comments

Comments
 (0)