Skip to content

Commit 745254e

Browse files
authored
refactor(pkg): unify concrete deps of local package (#10531)
the with/without versions just differ in error message, so they're easy to unify Signed-off-by: Rudi Grinberg <[email protected]>
1 parent cd9595a commit 745254e

File tree

2 files changed

+34
-33
lines changed

2 files changed

+34
-33
lines changed

src/dune_pkg/package_universe.ml

Lines changed: 18 additions & 29 deletions
Original file line numberDiff line numberDiff line change
@@ -47,32 +47,36 @@ let version_by_package_name local_packages (lock_dir : Lock_dir.t) =
4747
])
4848
;;
4949

50-
let concrete_dependencies_of_local_package_with_test t local_package_name =
50+
let concrete_dependencies_of_local_package t local_package_name ~with_test =
5151
let local_package = Package_name.Map.find_exn t.local_packages local_package_name in
5252
Local_package.(for_solver local_package |> For_solver.opam_filtered_dependency_formula)
5353
|> Resolve_opam_formula.filtered_formula_to_package_names
54-
~with_test:true
54+
~with_test
5555
(Solver_env.to_env t.solver_env)
5656
t.version_by_package_name
5757
|> Result.map_error ~f:(function
5858
| `Formula_could_not_be_satisfied unsatisfied_formula_hints ->
5959
User_message.make
60-
~hints:lockdir_regenerate_hints
60+
?hints:(Option.some_if with_test lockdir_regenerate_hints)
6161
~loc:local_package.loc
6262
(Pp.textf
63-
"The dependencies of local package %S could not be satisfied from the lockdir:"
63+
"The dependencies of local package %S could not be satisfied from the lockdir%s:"
6464
(Package_name.to_string local_package.name)
65+
(if with_test
66+
then ""
67+
else " when the solver variable 'with_test' is set to 'false'")
6568
:: List.map
6669
unsatisfied_formula_hints
6770
~f:Resolve_opam_formula.Unsatisfied_formula_hint.pp))
68-
|> Result.map ~f:Package_name.Set.of_list
6971
;;
7072
7173
let all_non_local_dependencies_of_local_packages t =
7274
let open Result.O in
7375
let+ all_dependencies_of_local_packages =
7476
Package_name.Map.keys t.local_packages
75-
|> Result.List.map ~f:(concrete_dependencies_of_local_package_with_test t)
77+
|> Result.List.map ~f:(fun p ->
78+
concrete_dependencies_of_local_package ~with_test:true t p
79+
|> Result.map ~f:Package_name.Set.of_list)
7680
|> Result.map ~f:Package_name.Set.union_all
7781
in
7882
Package_name.Set.diff
@@ -205,31 +209,14 @@ let create local_packages lock_dir =
205209
t
206210
;;
207211
208-
let concrete_dependencies_of_local_package_without_test t local_package_name =
209-
let local_package = Package_name.Map.find_exn t.local_packages local_package_name in
210-
Local_package.(for_solver local_package |> For_solver.opam_filtered_dependency_formula)
211-
|> Resolve_opam_formula.filtered_formula_to_package_names
212-
~with_test:false
213-
(Solver_env.to_env t.solver_env)
214-
t.version_by_package_name
215-
|> function
216-
| Ok x -> x
217-
| Error (`Formula_could_not_be_satisfied hints) ->
218-
User_error.raise
219-
(Pp.textf
220-
"Unable to find dependencies of package %S in lockdir when the solver variable \
221-
'with_test' is set to 'false':"
222-
(Package_name.to_string local_package.name)
223-
:: List.map hints ~f:Resolve_opam_formula.Unsatisfied_formula_hint.pp)
224-
;;
225-
226212
let local_transitive_dependency_closure_without_test =
227213
let module Top_closure = Top_closure.Make (Package_name.Set) (Monad.Id) in
228214
fun t start ->
229215
match
230216
Top_closure.top_closure
231217
~deps:(fun a ->
232-
concrete_dependencies_of_local_package_without_test t a
218+
concrete_dependencies_of_local_package t a ~with_test:false
219+
|> User_error.ok_exn
233220
|> List.filter ~f:(Package_name.Map.mem t.local_packages))
234221
~key:Fun.id
235222
start
@@ -251,7 +238,8 @@ let transitive_dependency_closure_without_test t start =
251238
|> Package_name.Set.to_list
252239
|> Package_name.Set.union_map ~f:(fun name ->
253240
let all_deps =
254-
concrete_dependencies_of_local_package_without_test t name
241+
concrete_dependencies_of_local_package t name ~with_test:false
242+
|> User_error.ok_exn
255243
|> Package_name.Set.of_list
256244
in
257245
Package_name.Set.diff all_deps local_package_names)
@@ -295,8 +283,8 @@ let check_contains_package t package_name =
295283
let all_dependencies t package ~traverse =
296284
check_contains_package t package;
297285
let immediate_deps =
298-
match concrete_dependencies_of_local_package_with_test t package with
299-
| Ok x -> x
286+
match concrete_dependencies_of_local_package t package ~with_test:true with
287+
| Ok x -> Package_name.Set.of_list x
300288
| Error e ->
301289
Code_error.raise
302290
"Invalid package universe which should have already been validated"
@@ -313,7 +301,8 @@ let non_test_dependencies t package ~traverse =
313301
check_contains_package t package;
314302
match traverse with
315303
| `Immediate ->
316-
concrete_dependencies_of_local_package_without_test t package
304+
concrete_dependencies_of_local_package t package ~with_test:false
305+
|> User_error.ok_exn
317306
|> Package_name.Set.of_list
318307
| `Transitive ->
319308
let closure =

test/blackbox-tests/test-cases/pkg/test-only-deps.t

Lines changed: 16 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -90,8 +90,14 @@ is run with with-test=true so the dependency won't even be in the lockdir.
9090
- bar.0.0.1
9191
- c.0.0.1
9292
$ dune describe pkg list-locked-dependencies
93-
Error: Unable to find dependencies of package "local_1" in lockdir when the
94-
solver variable 'with_test' is set to 'false':
93+
File "dune-project", lines 2-6, characters 0-71:
94+
2 | (package
95+
3 | (name local_1)
96+
4 | (depends
97+
5 | (foo (= :with-test false))
98+
6 | bar))
99+
The dependencies of local package "local_1" could not be satisfied from the
100+
lockdir when the solver variable 'with_test' is set to 'false':
95101
Package "foo" is missing
96102
[1]
97103
Test that we can detect the case where a local package depends on some package
@@ -112,8 +118,14 @@ incompatible version of the dependency will be in the lockdir.
112118
- bar.0.0.1
113119
- c.0.0.1
114120
$ dune describe pkg list-locked-dependencies
115-
Error: Unable to find dependencies of package "local_1" in lockdir when the
116-
solver variable 'with_test' is set to 'false':
121+
File "dune-project", lines 2-6, characters 0-90:
122+
2 | (package
123+
3 | (name local_1)
124+
4 | (depends
125+
5 | (a (or (= 0.0.1) (and :with-test (= 0.0.2))))
126+
6 | bar))
127+
The dependencies of local package "local_1" could not be satisfied from the
128+
lockdir when the solver variable 'with_test' is set to 'false':
117129
Found version "0.0.2" of package "a" which doesn't satisfy the required
118130
version constraint "= 0.0.1"
119131
[1]

0 commit comments

Comments
 (0)