Skip to content

Commit c4a6e84

Browse files
authored
fix(pkg): pinning depopts (#10754)
depopts aren't conjunctions, but disjunctions Signed-off-by: Rudi Grinberg <[email protected]>
1 parent 7ed503b commit c4a6e84

File tree

4 files changed

+21
-27
lines changed

4 files changed

+21
-27
lines changed

src/dune_pkg/local_package.ml

Lines changed: 4 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -147,12 +147,10 @@ let of_package (t : Dune_lang.Package.t) =
147147
let opam_file =
148148
Opam_file.read_from_string_exn ~contents:opam_file_string (Path.source file)
149149
in
150-
let convert_filtered_formula filtered_formula =
151-
Package_dependency.list_of_opam_filtered_formula loc filtered_formula
152-
in
153-
let dependencies = convert_filtered_formula (OpamFile.OPAM.depends opam_file) in
154-
let conflicts = convert_filtered_formula (OpamFile.OPAM.conflicts opam_file) in
155-
let depopts = convert_filtered_formula (OpamFile.OPAM.depopts opam_file) in
150+
let convert_filtered_formula = Package_dependency.list_of_opam_filtered_formula loc in
151+
let dependencies = convert_filtered_formula `And (OpamFile.OPAM.depends opam_file) in
152+
let conflicts = convert_filtered_formula `And (OpamFile.OPAM.conflicts opam_file) in
153+
let depopts = convert_filtered_formula `Or (OpamFile.OPAM.depopts opam_file) in
156154
let conflict_class =
157155
OpamFile.OPAM.conflict_class opam_file
158156
|> List.map ~f:Package_name.of_opam_package_name

src/dune_pkg/package_dependency.ml

Lines changed: 12 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,7 @@ module Convert_from_opam_error = struct
77
type t =
88
| Can't_convert_opam_filter_to_value of OpamTypes.filter
99
| Can't_convert_opam_filter_to_condition of OpamTypes.filter
10-
| Filtered_formula_is_not_a_conjunction_of_atoms of
10+
| Filtered_formula_is_not_the_correct_kind of
1111
{ non_atom : OpamTypes.filtered_formula }
1212
end
1313

@@ -200,19 +200,21 @@ let list_to_opam_filtered_formula ts =
200200
|> OpamFormula.ands
201201
;;
202202

203-
let list_of_opam_filtered_formula loc filtered_formula =
203+
let list_of_opam_filtered_formula loc kind filtered_formula =
204204
let exception E of Convert_from_opam_error.t in
205205
try
206-
OpamFormula.ands_to_list filtered_formula
206+
(match kind with
207+
| `And -> OpamFormula.ands_to_list
208+
| `Or -> OpamFormula.ors_to_list)
209+
filtered_formula
207210
|> List.map ~f:(fun (filtered_formula : OpamTypes.filtered_formula) ->
208211
match filtered_formula with
209212
| Atom (name, condition) ->
210213
let name = Package_name.of_opam_package_name name in
211214
(match Constraint.opt_of_opam_condition condition with
212215
| Ok constraint_ -> { name; constraint_ }
213216
| Error error -> raise (E error))
214-
| non_atom ->
215-
raise (E (Filtered_formula_is_not_a_conjunction_of_atoms { non_atom })))
217+
| non_atom -> raise (E (Filtered_formula_is_not_the_correct_kind { non_atom })))
216218
with
217219
| E e ->
218220
let message =
@@ -229,11 +231,13 @@ let list_of_opam_filtered_formula loc filtered_formula =
229231
"Can't convert opam filter '%s' into dune condition. Only global variables may \
230232
appear in this position."
231233
filter_string
232-
| Filtered_formula_is_not_a_conjunction_of_atoms { non_atom } ->
234+
| Filtered_formula_is_not_the_correct_kind { non_atom } ->
233235
let formula_string = OpamFilter.string_of_filtered_formula non_atom in
234236
sprintf
235-
"Expected formula to be a conjunction of atoms but encountered non-atom term \
236-
'%s'"
237+
"Expected formula to be a %s of atoms but encountered non-atom term '%s'"
238+
(match kind with
239+
| `And -> "conjunction"
240+
| `Or -> "disjunction")
237241
formula_string
238242
in
239243
User_error.raise ~loc [ Pp.text message ]

src/dune_pkg/package_dependency.mli

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -29,4 +29,8 @@ val list_to_opam_filtered_formula : t list -> OpamTypes.filtered_formula
2929

3030
(** Attempt to interpret a [OpamTypes.filtered_formula] as a list of [t]s by
3131
treating the formula as a conjunction of packages with constraints. *)
32-
val list_of_opam_filtered_formula : Loc.t -> OpamTypes.filtered_formula -> t list
32+
val list_of_opam_filtered_formula
33+
: Loc.t
34+
-> [ `Or | `And ]
35+
-> OpamTypes.filtered_formula
36+
-> t list

test/blackbox-tests/test-cases/pkg/pin-stanza/pin-depopts.t

Lines changed: 0 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -29,15 +29,3 @@ package with depopts.
2929
$ dune pkg lock
3030
Solution for dune.lock:
3131
- pkg-with-depopts.5.2.0
32-
33-
Try locking the project again after adding a bare dune-project file to
34-
the pinned package. Currently this doesn't work correctly. See
35-
https://github.com/ocaml/dune/issues/10739
36-
$ cat > pkg-with-depopts/dune-project <<EOF
37-
> (lang dune 3.16)
38-
> EOF
39-
$ dune pkg lock
40-
File "pkg-with-depopts/pkg-with-depopts.opam", line 1, characters 0-0:
41-
Error: Expected formula to be a conjunction of atoms but encountered non-atom
42-
term 'option-a | option-b'
43-
[1]

0 commit comments

Comments
 (0)