Skip to content

Commit 17646fd

Browse files
authored
Support not in package dependencies constraints (#11404)
* Support not in package dependencies constraints Signed-off-by: ArthurW <arthur@tarides.com> * Fix after review Signed-off-by: ArthurW <arthur@tarides.com> --------- Signed-off-by: ArthurW <arthur@tarides.com>
1 parent d826e9b commit 17646fd

File tree

9 files changed

+198
-37
lines changed

9 files changed

+198
-37
lines changed

doc/changes/11404.md

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
- Support `not` in package dependencies constraints (#11404, @art-w, reported by @hannesm)

src/dune_lang/package_constraint.ml

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -39,6 +39,7 @@ module T = struct
3939
| Bop of Relop.t * Value.t * Value.t
4040
| And of t list
4141
| Or of t list
42+
| Not of t
4243

4344
let rec to_dyn =
4445
let open Dyn in
@@ -48,6 +49,7 @@ module T = struct
4849
| Bop (b, x, y) -> variant "Bop" [ Relop.to_dyn b; Value.to_dyn x; Value.to_dyn y ]
4950
| And t -> variant "And" (List.map ~f:to_dyn t)
5051
| Or t -> variant "Or" (List.map ~f:to_dyn t)
52+
| Not t -> variant "Not" [ to_dyn t ]
5153
;;
5254

5355
let rec compare a b =
@@ -71,6 +73,9 @@ module T = struct
7173
| And _, _ -> Lt
7274
| _, And _ -> Gt
7375
| Or a, Or b -> List.compare a b ~compare
76+
| Or _, _ -> Lt
77+
| _, Or _ -> Gt
78+
| Not a, Not b -> compare a b
7479
;;
7580
end
7681

@@ -85,6 +90,7 @@ let rec encode c =
8590
| Bop (op, x, y) -> triple Relop.encode Value.encode Value.encode (op, x, y)
8691
| And conjuncts -> list sexp (string "and" :: List.map ~f:encode conjuncts)
8792
| Or disjuncts -> list sexp (string "or" :: List.map ~f:encode disjuncts)
93+
| Not x -> list sexp [ string "not"; encode x ]
8894
;;
8995

9096
let logical_op t =
@@ -138,6 +144,10 @@ let decode =
138144
; ( "or"
139145
, let+ x = logical_op t in
140146
Or x )
147+
; ( "not"
148+
, let+ x = t
149+
and+ () = Dune_sexp.Syntax.since Stanza.syntax (3, 18) ~what:"Not operator" in
150+
Not x )
141151
]
142152
in
143153
peek_exn

src/dune_lang/package_constraint.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -23,6 +23,7 @@ type t =
2323
(** A binary operator applied to LHS and RHS values *)
2424
| And of t list (** The conjunction of a list of boolean expressions *)
2525
| Or of t list (** The disjunction of a list of boolean expressions *)
26+
| Not of t (** The negation of a boolean expression *)
2627

2728
val encode : t Dune_sexp.Encoder.t
2829
val decode : t Dune_sexp.Decoder.t

src/dune_pkg/package_dependency.ml

Lines changed: 23 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -85,6 +85,12 @@ module Constraint = struct
8585
(Value.to_opam_filter lhs, Op.to_relop_pelem op, Value.to_opam_filter rhs)))
8686
| And conjunction -> OpamFormula.ands (List.map conjunction ~f:to_opam_condition)
8787
| Or disjunction -> OpamFormula.ors (List.map disjunction ~f:to_opam_condition)
88+
| Not constraint_ ->
89+
OpamFormula.neg
90+
(function
91+
| OpamTypes.Constraint (op, v) -> Constraint (OpamFormula.neg_relop op, v)
92+
| Filter f -> Filter (FNot f))
93+
(to_opam_condition constraint_)
8894
;;
8995

9096
let rec of_opam_filter (filter : OpamTypes.filter) =
@@ -104,6 +110,9 @@ module Constraint = struct
104110
let+ lhs = of_opam_filter lhs
105111
and+ rhs = of_opam_filter rhs in
106112
Or [ lhs; rhs ]
113+
| FNot constraint_ ->
114+
let+ constraint_ = of_opam_filter constraint_ in
115+
Not constraint_
107116
| _ -> Error (Convert_from_opam_error.Can't_convert_opam_filter_to_condition filter)
108117
;;
109118

@@ -138,6 +147,7 @@ type context =
138147
| Root
139148
| Ctx_and
140149
| Ctx_or
150+
| Ctx_not
141151

142152
(* The printer in opam-file-format does not insert parentheses on its own,
143153
but it is possible to use the [Group] constructor with a singleton to
@@ -165,15 +175,27 @@ let opam_constraint t : OpamParserTypes.FullPos.value =
165175
( nopos @@ Constraint.Op.to_opam op
166176
, Constraint.Value.to_opam x
167177
, Constraint.Value.to_opam y ))
168-
| And cs -> logical_op `And cs ~inner_ctx:Ctx_and ~group_needed:false
178+
| And cs ->
179+
let group_needed =
180+
match context with
181+
| Root -> false
182+
| Ctx_and -> false
183+
| Ctx_or -> false
184+
| Ctx_not -> true
185+
in
186+
logical_op `And cs ~inner_ctx:Ctx_and ~group_needed
169187
| Or cs ->
170188
let group_needed =
171189
match context with
172190
| Root -> false
173191
| Ctx_and -> true
174192
| Ctx_or -> false
193+
| Ctx_not -> true
175194
in
176195
logical_op `Or cs ~inner_ctx:Ctx_or ~group_needed
196+
| Not c ->
197+
let _c = opam_constraint Ctx_not c in
198+
nopos (Pfxop (nopos `Not, _c))
177199
and logical_op op cs ~inner_ctx ~group_needed =
178200
List.map cs ~f:(opam_constraint inner_ctx) |> op_list op |> group_if group_needed
179201
in

src/dune_rules/opam_create.ml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -179,6 +179,7 @@ let rec already_requires_odoc : Package_constraint.t -> bool = function
179179
| Bvar var -> Dune_lang.Package_variable_name.(one_of var [ with_doc; build; post ])
180180
| And l -> List.for_all ~f:already_requires_odoc l
181181
| Or l -> List.exists ~f:already_requires_odoc l
182+
| Not t -> not (already_requires_odoc t)
182183
;;
183184

184185
let insert_odoc_dep depends =

test/blackbox-tests/test-cases/dune-project-meta/binops.t

Lines changed: 0 additions & 36 deletions
This file was deleted.
Lines changed: 107 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,107 @@
1+
Using binary operators for dependencies
2+
---------------------------------------
3+
4+
Not supported before 2.1:
5+
6+
$ cat > dune-project <<EOF
7+
> (lang dune 2.0)
8+
> (name foo)
9+
> (generate_opam_files true)
10+
> (package
11+
> (name foo)
12+
> (depends (conf-libX11 (<> :os win32))))
13+
> EOF
14+
15+
$ dune build @install
16+
File "dune-project", line 6, characters 23-37:
17+
6 | (depends (conf-libX11 (<> :os win32))))
18+
^^^^^^^^^^^^^^
19+
Error: Passing two arguments to <> is only available since version 2.1 of the
20+
dune language. Please update your dune-project file to have (lang dune 2.1).
21+
[1]
22+
23+
Supported since 2.1:
24+
25+
$ cat > dune-project <<EOF
26+
> (lang dune 2.1)
27+
> (name foo)
28+
> (generate_opam_files true)
29+
> (package
30+
> (name foo)
31+
> (depends (conf-libX11 (<> :os win32))))
32+
> EOF
33+
34+
$ dune build @install
35+
$ grep conf-libX11 foo.opam
36+
"conf-libX11" {os != "win32"}
37+
38+
39+
Using negation operator for dependencies
40+
----------------------------------------
41+
42+
Not supported before 3.18:
43+
44+
$ cat > dune-project <<EOF
45+
> (lang dune 3.17)
46+
> (generate_opam_files)
47+
> (package
48+
> (name foo)
49+
> (allow_empty)
50+
> (depends
51+
> (ocp-indent
52+
> (not :with-test))))
53+
> EOF
54+
$ dune build
55+
File "dune-project", line 8, characters 4-20:
56+
8 | (not :with-test))))
57+
^^^^^^^^^^^^^^^^
58+
Error: Not operator is only available since version 3.18 of the dune
59+
language. Please update your dune-project file to have (lang dune 3.18).
60+
[1]
61+
62+
Supported since 3.18:
63+
64+
$ cat > dune-project <<EOF
65+
> (lang dune 3.18)
66+
> (generate_opam_files)
67+
> (package
68+
> (name foo)
69+
> (allow_empty)
70+
> (depends
71+
> (ocp-indent
72+
> (not
73+
> (or
74+
> (and
75+
> (not :with-test)
76+
> (>= 1.0))
77+
> (not
78+
> (and
79+
> (not (= :os win32))
80+
> (not (>= 1.5)))))))
81+
> (not (>= 2.0))))
82+
> EOF
83+
$ dune build
84+
$ cat foo.opam
85+
# This file is generated by dune, edit dune-project instead
86+
opam-version: "2.0"
87+
depends: [
88+
"dune" {>= "3.18"}
89+
"ocp-indent" {!(!with-test & >= "1.0" | !(!os = "win32" & !>= "1.5"))}
90+
"not" {>= "2.0"}
91+
"odoc" {with-doc}
92+
]
93+
build: [
94+
["dune" "subst"] {dev}
95+
[
96+
"dune"
97+
"build"
98+
"-p"
99+
name
100+
"-j"
101+
jobs
102+
"@install"
103+
"@runtest" {with-test}
104+
"@doc" {with-doc}
105+
]
106+
]
107+
x-maintenance-intent: ["(latest)"]

test/blackbox-tests/test-cases/pkg/additional-constraints.t

Lines changed: 43 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -30,3 +30,46 @@ Notice that the constraints field doesn't introduce additional packages. The
3030
Solution for dune.lock:
3131
- bar.1.0.0
3232
- foo.1.0.0
33+
34+
Constraint negation is supported since 3.18:
35+
36+
$ cat >dune-workspace <<EOF
37+
> (lang dune 3.18)
38+
> (lock_dir
39+
> (constraints doesnotexist (foo (not (= 1.0.0))) (bar (not (= 1.0.0))))
40+
> (repositories mock))
41+
> (repository
42+
> (name mock)
43+
> (url "file://$(pwd)/mock-opam-repository"))
44+
> EOF
45+
46+
There are no valid version of foo at the moment:
47+
48+
$ solve_project <<EOF
49+
> (lang dune 3.18)
50+
> (package
51+
> (name x)
52+
> (depends foo bar))
53+
> EOF
54+
Error: Unable to solve dependencies for the following lock directories:
55+
Lock directory dune.lock:
56+
Couldn't solve the package dependency formula.
57+
Selected candidates: bar.1.9.1 x.dev
58+
- foo -> (problem)
59+
No usable implementations:
60+
foo.1.0.0: Package does not satisfy constraints of local package x
61+
[1]
62+
63+
If we add one:
64+
65+
$ mkpkg foo 0.9.0
66+
67+
$ solve_project <<EOF
68+
> (lang dune 3.18)
69+
> (package
70+
> (name x)
71+
> (depends foo bar))
72+
> EOF
73+
Solution for dune.lock:
74+
- bar.1.9.1
75+
- foo.0.9.0

test/blackbox-tests/test-cases/pkg/opam-solver-or.t

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -54,6 +54,17 @@ which is completely omitted from the solution).
5454
- a2.0.0.2
5555
- b.0.0.2
5656

57+
Same solution if a1 only known version is excluded:
58+
59+
$ mkpkg b 0.0.2 <<EOF
60+
> depends: [ "a1" {!= "0.0.1" } | "a2" {= "0.0.2" } ]
61+
> EOF
62+
63+
$ solve b
64+
Solution for dune.lock:
65+
- a2.0.0.2
66+
- b.0.0.2
67+
5768
Update a2.0.0.2 marking it as avoid-version which should tell the
5869
solver to try to find a solution which doesn't include it.
5970

@@ -65,3 +76,4 @@ $ mkpkg a2 0.0.2 <<EOF
6576
Solution for dune.lock:
6677
- a2.0.0.2
6778
- b.0.0.2
79+

0 commit comments

Comments
 (0)