Skip to content

Commit c19d90f

Browse files
committed
feature: [enabled_if] on packages
Add [enabled_if] when defining packages. This construct is limited to the variables we can inspect using [Sys_poll]. The interpretation of this field is the same including or excluding it from the set of visible packages with --only-packages. Signed-off-by: Rudi Grinberg <[email protected]>
1 parent acc217a commit c19d90f

File tree

20 files changed

+277
-54
lines changed

20 files changed

+277
-54
lines changed

bin/dune_init.ml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -434,6 +434,7 @@ module Component = struct
434434
}
435435
]
436436
~contents_basename:None
437+
~enabled_if:None
437438
in
438439
let packages = Package.Name.Map.singleton (Package.name package) package in
439440
let info =

doc/changes/added/12905.md

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,4 @@
1+
- Add `enabled_if` on packages in `dune-project` files. If this field is set,
2+
the expression is evaluated to determine whether to mask the package in this
3+
workspace. When opam file generation is enabled, this field is converted to
4+
a corresponding `available` expression (#12905, @rgrinbreg, @gridbugs)

src/dune_lang/package.ml

Lines changed: 17 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -22,6 +22,7 @@ type t =
2222
; depends : Package_dependency.t list
2323
; conflicts : Package_dependency.t list
2424
; depopts : Package_dependency.t list
25+
; enabled_if : Blang.t option
2526
; info : Package_info.t
2627
; version : Package_version.t option
2728
; has_opam_file : opam_file
@@ -55,6 +56,7 @@ let original_opam_file t = t.original_opam_file
5556
let set_inside_opam_dir t ~dir = { t with opam_file = Name.file t.id.name ~dir }
5657
let set_version_and_info t ~version ~info = { t with version; info }
5758
let exclusive_dir t = t.exclusive_dir
59+
let enabled_if t = t.enabled_if
5860

5961
let encode
6062
(name : Name.t)
@@ -75,6 +77,7 @@ let encode
7577
; opam_file = _
7678
; original_opam_file = _
7779
; exclusive_dir
80+
; enabled_if
7881
}
7982
=
8083
let open Encoder in
@@ -87,6 +90,7 @@ let encode
8790
; field_l "depends" Package_dependency.encode depends
8891
; field_l "conflicts" Package_dependency.encode conflicts
8992
; field_l "depopts" Package_dependency.encode depopts
93+
; field_o "enabled_if" Blang.encode enabled_if
9094
; field_o "version" Package_version.encode version
9195
; field "tags" (list string) ~default:[] tags
9296
; field_l
@@ -109,6 +113,11 @@ let decode_name ~version =
109113
;;
110114

111115
let decode =
116+
let enabled_if =
117+
String_with_vars.set_decoding_env
118+
Pform.Env.package_enabled_if
119+
(Blang.Ast.decode ~override_decode_bare_literal:None String_with_vars.decode)
120+
in
112121
let open Decoder in
113122
let name_map syntax of_list_map to_string name decode print_value error_msg =
114123
let+ names = field ~default:[] name (syntax >>> repeat decode) in
@@ -133,6 +142,9 @@ let decode =
133142
and+ depends = field ~default:[] "depends" (repeat Package_dependency.decode)
134143
and+ conflicts = field ~default:[] "conflicts" (repeat Package_dependency.decode)
135144
and+ depopts = field ~default:[] "depopts" (repeat Package_dependency.decode)
145+
and+ enabled_if =
146+
(* CR rgrinberg: limit this to variables from [Sys_poll] *)
147+
field_o "enabled_if" (Syntax.since Stanza.syntax (3, 21) >>> enabled_if)
136148
and+ info = Package_info.decode ~since:(2, 0) ()
137149
and+ tags = field "tags" (enter (repeat string)) ~default:[]
138150
and+ exclusive_dir =
@@ -180,6 +192,7 @@ let decode =
180192
; opam_file
181193
; original_opam_file = None
182194
; exclusive_dir
195+
; enabled_if
183196
}
184197
;;
185198

@@ -208,6 +221,7 @@ let to_dyn
208221
; opam_file = _
209222
; original_opam_file = _
210223
; exclusive_dir = _
224+
; enabled_if
211225
}
212226
=
213227
let open Dyn in
@@ -225,6 +239,7 @@ let to_dyn
225239
; "deprecated_package_names", Name.Map.to_dyn Loc.to_dyn_hum deprecated_package_names
226240
; "sites", Site.Map.to_dyn Section.to_dyn sites
227241
; "allow_empty", Bool allow_empty
242+
; "enabled_if", (option Blang.to_dyn) enabled_if
228243
]
229244
;;
230245

@@ -241,6 +256,7 @@ let create
241256
~conflicts
242257
~depends
243258
~depopts
259+
~enabled_if
244260
~info
245261
~has_opam_file
246262
~dir
@@ -272,5 +288,6 @@ let create
272288
; original_opam_file
273289
; exclusive_dir =
274290
Option.map contents_basename ~f:(fun (loc, s) -> loc, Path.Source.relative dir s)
291+
; enabled_if
275292
}
276293
;;

src/dune_lang/package.mli

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -36,6 +36,7 @@ val tags : t -> string list
3636
val synopsis : t -> string option
3737
val info : t -> Package_info.t
3838
val description : t -> string option
39+
val enabled_if : t -> Blang.t option
3940
val id : t -> Id.t
4041

4142
val set_version_and_info
@@ -60,6 +61,7 @@ val create
6061
-> conflicts:Package_dependency.t list
6162
-> depends:Package_dependency.t list
6263
-> depopts:Package_dependency.t list
64+
-> enabled_if:Blang.t option
6365
-> info:Package_info.t
6466
-> has_opam_file:opam_file
6567
-> dir:Path.Source.t

src/dune_lang/package_constraint.ml

Lines changed: 8 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -34,7 +34,7 @@ end
3434

3535
module T = struct
3636
type t =
37-
| Bvar of Package_variable_name.t
37+
| Bvar of Value.t
3838
| Uop of Relop.t * Value.t
3939
| Bop of Relop.t * Value.t * Value.t
4040
| And of t list
@@ -44,7 +44,7 @@ module T = struct
4444
let rec to_dyn =
4545
let open Dyn in
4646
function
47-
| Bvar v -> variant "Bvar" [ Package_variable_name.to_dyn v ]
47+
| Bvar v -> variant "Bvar" [ Value.to_dyn v ]
4848
| Uop (b, x) -> variant "Uop" [ Relop.to_dyn b; Value.to_dyn x ]
4949
| Bop (b, x, y) -> variant "Bop" [ Relop.to_dyn b; Value.to_dyn x; Value.to_dyn y ]
5050
| And t -> variant "And" (List.map ~f:to_dyn t)
@@ -55,7 +55,7 @@ module T = struct
5555
let rec compare a b =
5656
let open Ordering.O in
5757
match a, b with
58-
| Bvar a, Bvar b -> Package_variable_name.compare a b
58+
| Bvar a, Bvar b -> Value.compare a b
5959
| Bvar _, _ -> Lt
6060
| _, Bvar _ -> Gt
6161
| Uop (a_op, a_value), Uop (b_op, b_value) ->
@@ -85,7 +85,10 @@ include Comparable.Make (T)
8585
let rec encode c =
8686
let open Encoder in
8787
match c with
88-
| Bvar x -> Package_variable_name.Project.encode x
88+
| Bvar (String_literal _) ->
89+
(* We aren't ever able to decode these *)
90+
assert false
91+
| Bvar (Variable x) -> Package_variable_name.Project.encode x
8992
| Uop (op, x) -> pair Relop.encode Value.encode (op, x)
9093
| Bop (op, x, y) -> triple Relop.encode Value.encode Value.encode (op, x, y)
9194
| And conjuncts -> list sexp (string "and" :: List.map ~f:encode conjuncts)
@@ -154,7 +157,7 @@ let decode =
154157
>>= function
155158
| Atom (_loc, A s) when String.is_prefix s ~prefix:":" ->
156159
let+ () = junk in
157-
Bvar (Package_variable_name.of_string (String.drop s 1))
160+
Bvar (Variable (Package_variable_name.of_string (String.drop s 1)))
158161
| _ -> sum (ops @ logops))
159162
;;
160163

src/dune_lang/package_constraint.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -13,7 +13,7 @@ end
1313
represent strings and booleans. If a variable appears in a position where a
1414
boolean is expected it will be assumed to represent a boolean. *)
1515
type t =
16-
| Bvar of Package_variable_name.t (** A boolean variable *)
16+
| Bvar of Value.t
1717
| Uop of Relop.t * Value.t
1818
(** A unary operator applied to a value. Unary operators are operators
1919
whose LHS is implied by context. E.g. when placing version constraints

src/dune_lang/package_dependency.ml

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -61,7 +61,8 @@ let check_for_typo ~loc { name; constraint_ } =
6161
]
6262
in
6363
Some message
64-
| Some (Bvar var) when String.equal (Package_variable_name.to_string var) "with_test" ->
64+
| Some (Bvar (Variable var))
65+
when String.equal (Package_variable_name.to_string var) "with_test" ->
6566
let message =
6667
User_message.make
6768
~loc

src/dune_lang/pform.ml

Lines changed: 21 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -649,6 +649,10 @@ module Env = struct
649649
}
650650
;;
651651

652+
let os ~version =
653+
List.map Var.Os.all ~f:(fun v -> Var.Os.to_string v, since ~version (Var.Os v))
654+
;;
655+
652656
let initial =
653657
let macros =
654658
let macro (x : Macro.t) = No_info x in
@@ -766,11 +770,8 @@ module Env = struct
766770
; "dune-warnings", since ~version:(3, 21) Var.Dune_warnings
767771
]
768772
in
769-
let os =
770-
List.map Var.Os.all ~f:(fun v ->
771-
Var.Os.to_string v, since ~version:(3, 20) (Var.Os v))
772-
in
773-
String.Map.of_list_exn (List.concat [ lowercased; uppercased; other; os ])
773+
String.Map.of_list_exn
774+
(List.concat [ lowercased; uppercased; other; os ~version:(3, 20) ])
774775
in
775776
fun ~stanza:syntax_version ~extensions ->
776777
let extensions =
@@ -779,6 +780,21 @@ module Env = struct
779780
{ syntax_version; syntax_lang = Stanza.syntax; vars; macros; extensions }
780781
;;
781782

783+
let package_enabled_if =
784+
let syntax_version = 3, 21 in
785+
let vars =
786+
let os = os ~version:syntax_version in
787+
(* CR rgrinberg: This has to be disabled for multi context builds *)
788+
("architecture", No_info Var.Architecture) :: os
789+
in
790+
{ syntax_version = 3, 21
791+
; syntax_lang = Stanza.syntax
792+
; vars = String.Map.of_list_exn vars
793+
; macros = String.Map.empty
794+
; extensions = Syntax.Map.singleton Stanza.syntax syntax_version
795+
}
796+
;;
797+
782798
let lt_renamed_input_file t =
783799
{ t with
784800
vars =

src/dune_lang/pform.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -204,6 +204,7 @@ module Env : sig
204204
-> extensions:(Syntax.t * Syntax.Version.t) list
205205
-> t
206206

207+
val package_enabled_if : t
207208
val add_user_vars : t -> string list -> t
208209
val parse : t -> Template.Pform.t -> pform
209210

src/dune_pkg/opam_file.ml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -282,6 +282,7 @@ let load_opam_file_with_contents ~contents:opam_file_string file name =
282282
~conflicts:[]
283283
~depends:[]
284284
~depopts:[]
285+
~enabled_if:None (* CR-someday rgrinberg: would be nice to interpret this *)
285286
~info
286287
~synopsis:(get_one "synopsis")
287288
~description:(get_one "description")

0 commit comments

Comments
 (0)