File tree Expand file tree Collapse file tree 6 files changed +88
-14
lines changed
test/blackbox-tests/test-cases Expand file tree Collapse file tree 6 files changed +88
-14
lines changed Original file line number Diff line number Diff line change @@ -288,13 +288,56 @@ module Unexpanded = struct
288288 }
289289 ;;
290290
291- let field ?check name =
291+ let is_expanded t =
292+ let rec loop (t : ast ) =
293+ let open Ast in
294+ match t with
295+ | Standard -> true
296+ | Include _ -> false
297+ | Element s -> Option. is_some (String_with_vars. text_only s)
298+ | Union l -> List. for_all l ~f: loop
299+ | Diff (l , r ) -> loop l && loop r
300+ in
301+ loop t.ast
302+ ;;
303+
304+ let field_gen field ?check ?since_expanded is_expanded =
292305 let decode =
293306 match check with
294307 | None -> decode
295308 | Some x -> Decoder. ( >>> ) x decode
296309 in
297- Decoder. field name decode ~default: standard
310+ let x = field decode in
311+ match since_expanded with
312+ | None -> x
313+ | Some since_expanded ->
314+ let open Decoder in
315+ let + loc, x = located x
316+ and + ver = Syntax. get_exn Stanza. syntax in
317+ if ver < since_expanded && not (is_expanded x)
318+ then
319+ Syntax.Error. since
320+ loc
321+ Stanza. syntax
322+ since_expanded
323+ ~what: " the ability to specify non-constant module lists" ;
324+ x
325+ ;;
326+
327+ let field ?check ?since_expanded name =
328+ field_gen
329+ (Decoder. field name ~default: standard ?on_dup:None )
330+ ?check
331+ ?since_expanded
332+ is_expanded
333+ ;;
334+
335+ let field_o ?check ?since_expanded name =
336+ field_gen
337+ (Decoder. field_o name ?on_dup:None )
338+ ?check
339+ ?since_expanded
340+ (Option. forall ~f: is_expanded)
298341 ;;
299342
300343 let has_special_forms t =
Original file line number Diff line number Diff line change @@ -53,7 +53,19 @@ module Unexpanded : sig
5353 val standard : t
5454 val of_strings : pos :string * int * int * int -> string list -> t
5555 val include_single : context :Univ_map .t -> pos :string * int * int * int -> string -> t
56- val field : ?check : unit Decoder .t -> string -> t Decoder .fields_parser
56+
57+ val field
58+ : ?check:unit Decoder. t
59+ -> ?since_expanded:Syntax.Version. t
60+ -> string
61+ -> t Decoder. fields_parser
62+
63+ val field_o
64+ : ?check:unit Decoder. t
65+ -> ?since_expanded:Syntax.Version. t
66+ -> string
67+ -> t option Decoder. fields_parser
68+
5769 val has_special_forms : t -> bool
5870 val has_standard : t -> bool
5971
Original file line number Diff line number Diff line change @@ -665,10 +665,10 @@ module Library = struct
665665 ()
666666 and + sub_systems = Sub_system_info. record_parser
667667 and + virtual_modules =
668- field_o
668+ Ordered_set_lang.Unexpanded. field_o
669+ ~check: (Dune_lang.Syntax. since Stanza. syntax (1 , 7 ))
670+ ~since_expanded: Stanza_common.Modules_settings. since_expanded
669671 " virtual_modules"
670- (Dune_lang.Syntax. since Stanza. syntax (1 , 7 )
671- >>> Ordered_set_lang.Unexpanded. decode)
672672 and + implements =
673673 field_o
674674 " implements"
@@ -678,10 +678,10 @@ module Library = struct
678678 " default_implementation"
679679 (Dune_lang.Syntax. since Stanza. syntax (2 , 6 ) >>> located Lib_name. decode)
680680 and + private_modules =
681- field_o
681+ Ordered_set_lang.Unexpanded. field_o
682+ ~check: (Dune_lang.Syntax. since Stanza. syntax (1 , 2 ))
683+ ~since_expanded: Stanza_common.Modules_settings. since_expanded
682684 " private_modules"
683- (Dune_lang.Syntax. since Stanza. syntax (1 , 2 )
684- >>> Ordered_set_lang.Unexpanded. decode)
685685 and + stdlib =
686686 field_o
687687 " stdlib"
Original file line number Diff line number Diff line change @@ -206,11 +206,13 @@ module Modules_settings = struct
206206 ; modules : Ordered_set_lang.Unexpanded .t
207207 }
208208
209+ let since_expanded = 3 , 13
210+
209211 let decode =
210212 let + root_module = field_o " root_module" Module_name. decode_loc
211213 and + modules_without_implementation =
212- Ordered_set_lang.Unexpanded. field " modules_without_implementation"
213- and + modules = Ordered_set_lang.Unexpanded. field " modules" in
214+ Ordered_set_lang.Unexpanded. field ~since_expanded " modules_without_implementation"
215+ and + modules = Ordered_set_lang.Unexpanded. field ~since_expanded " modules" in
214216 { root_module; modules; modules_without_implementation }
215217 ;;
216218end
Original file line number Diff line number Diff line change @@ -26,5 +26,6 @@ module Modules_settings : sig
2626 ; modules : Ordered_set_lang.Unexpanded .t
2727 }
2828
29+ val since_expanded : Syntax.Version .t
2930 val decode : t Dune_lang.Decoder .fields_parser
3031end
Original file line number Diff line number Diff line change 11Here we test the ability of (modules) to be contain dynamic forms such as
22`(: include)` and variables such as `" %{ read-lines: } " `.
33
4- Begin by setting up a project. Note that the feature is not currently versioned;
5- this should be done before merging.
4+ Begin by setting up a project and check the versioning guards.
65
76 $ cat > dune-project << EOF
87 > (lang dune 3.11 )
@@ -34,7 +33,24 @@ file `gen/lst`:
3433 > (executable (name mod ) (modules (: include gen/ lst)))
3534 > EOF
3635
37- Let's check that it works :
36+ Let's check that it fails in the current version of Dune :
37+
38+ $ dune exec ./mod .exe
39+ File "dune ", line 1 , characters 23-51 :
40+ 1 | (executable (name mod ) (modules (: include gen/ lst)))
41+ ^^^^^^^^^^^^^^^^^^^^^^^^^^^^
42+ Error : the ability to specify non-constant module lists is only available
43+ since version 3 .13 of the dune language . Please update your dune-project file
44+ to have (lang dune 3.13 ).
45+ [1 ]
46+
47+ Update the version ...
48+
49+ $ cat >dune-project <<EOF
50+ > (lang dune 3.13 )
51+ > EOF
52+
53+ ... and it works !
3854
3955 $ dune exec ./mod .exe
4056 Hello , Mod !
You can’t perform that action at this time.
0 commit comments