Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
3 changes: 3 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -69,6 +69,9 @@ Unreleased
- Compute digests and manage sandboxes in background threads (#7947,
@rgrinberg)

- Add `(build_if)` to the `(test)` stanza. When it evaluates to false, the
executable is not built. (#7899, fixes #6938, @emillon)

3.8.1 (2023-06-05)
------------------

Expand Down
4 changes: 4 additions & 0 deletions doc/stanzas/test.rst
Original file line number Diff line number Diff line change
Expand Up @@ -37,6 +37,10 @@ In particular, all fields except for ``public_names`` are supported from the
:ref:`executables stanza <shared-exe-fields>`. Alias fields apart from ``name``
are allowed.

The ``(enabled_if)`` field has special semantics: when present, it only applies
to running the tests. The test executable is always built by default.
If you need to restrict building the test executable, use ``(build_if)`` instead.

By default, the test binaries are run without options. The ``action`` field can
override the test binary invocation, i.e., if you're using Alcotest and wish to
see all the test failures on the standard output. When running Dune ``runtest``
Expand Down
6 changes: 6 additions & 0 deletions src/dune_rules/dune_file.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1892,6 +1892,7 @@ module Tests = struct
; package : Package.t option
; deps : Dep_conf.t Bindings.t
; enabled_if : Blang.t
; build_if : Blang.t
; action : Dune_lang.Action.t option
}

Expand Down Expand Up @@ -1923,6 +1924,10 @@ module Tests = struct
(Dune_lang.Syntax.since Stanza.syntax (2, 0)
>>> repeat (located Lib_name.decode))
~default:[]
and+ build_if =
field "build_if" ~default:Blang.true_
(Syntax.since Stanza.syntax (3, 9)
>>> Enabled_if.decode_value ~allowed_vars:Any ())
in
{ exes =
{ Executables.link_flags
Expand All @@ -1944,6 +1949,7 @@ module Tests = struct
; package
; deps
; enabled_if
; build_if
; action
}))

Expand Down
1 change: 1 addition & 0 deletions src/dune_rules/dune_file.mli
Original file line number Diff line number Diff line change
Expand Up @@ -359,6 +359,7 @@ module Tests : sig
; package : Package.t option
; deps : Dep_conf.t Bindings.t
; enabled_if : Blang.t
; build_if : Blang.t
; action : Dune_lang.Action.t option
}
end
Expand Down
45 changes: 23 additions & 22 deletions src/dune_rules/enabled_if.ml
Original file line number Diff line number Diff line change
Expand Up @@ -40,30 +40,31 @@ let emit_warning allowed_vars is_error var =
(Dune_lang.Template.Pform.name var)
]

let decode ~allowed_vars ?(is_error = true) ~since () =
let decode =
match allowed_vars with
| Any -> Blang.decode
| Only allowed_vars ->
Blang.decode_manually (fun env var ->
match Dune_lang.Template.Pform.payload var with
| Some _ ->
let decode_value ~allowed_vars ?(is_error = true) () =
match allowed_vars with
| Any -> Blang.decode
| Only allowed_vars ->
Blang.decode_manually (fun env var ->
match Dune_lang.Template.Pform.payload var with
| Some _ ->
emit_warning allowed_vars is_error var;
Pform.Env.parse env var
| None -> (
let name = Dune_lang.Template.Pform.name var in
match List.assoc allowed_vars name with
| None ->
emit_warning allowed_vars is_error var;
Pform.Env.parse env var
| None -> (
let name = Dune_lang.Template.Pform.name var in
match List.assoc allowed_vars name with
| None ->
emit_warning allowed_vars is_error var;
Pform.Env.parse env var
| Some min_ver ->
let current_ver = Pform.Env.syntax_version env in
if min_ver > current_ver then
let loc = Dune_lang.Template.Pform.loc var in
let what = Dune_lang.Template.Pform.describe var in
Dune_lang.Syntax.Error.since loc Stanza.syntax min_ver ~what
else Pform.Env.unsafe_parse_without_checking_version env var))
in
| Some min_ver ->
let current_ver = Pform.Env.syntax_version env in
if min_ver > current_ver then
let loc = Dune_lang.Template.Pform.loc var in
let what = Dune_lang.Template.Pform.describe var in
Dune_lang.Syntax.Error.since loc Stanza.syntax min_ver ~what
else Pform.Env.unsafe_parse_without_checking_version env var))

let decode ~allowed_vars ?is_error ~since () =
let decode = decode_value ?is_error ~allowed_vars () in
let decode =
match since with
| None -> decode
Expand Down
6 changes: 6 additions & 0 deletions src/dune_rules/enabled_if.mli
Original file line number Diff line number Diff line change
Expand Up @@ -12,3 +12,9 @@ val decode :
-> since:Dune_lang.Syntax.Version.t option
-> unit
-> Blang.t Dune_lang.Decoder.fields_parser

val decode_value :
allowed_vars:allowed_vars
-> ?is_error:bool
-> unit
-> Blang.t Dune_lang.Decoder.t
19 changes: 11 additions & 8 deletions src/dune_rules/gen_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -110,14 +110,17 @@ end = struct
let+ () = Simple_rules.alias sctx alias ~dir ~expander in
empty_none
| Tests tests ->
let+ cctx, merlin =
Test_rules.rules tests ~sctx ~dir ~scope ~expander ~dir_contents
in
{ merlin = Some merlin
; cctx = Some (tests.exes.buildable.loc, cctx)
; js = None
; source_dirs = None
}
let* enabled = Expander.eval_blang expander tests.build_if in
if enabled then
let+ cctx, merlin =
Test_rules.rules tests ~sctx ~dir ~scope ~expander ~dir_contents
in
{ merlin = Some merlin
; cctx = Some (tests.exes.buildable.loc, cctx)
; js = None
; source_dirs = None
}
else Memo.return empty_none
| Copy_files { files = glob; _ } ->
let* source_dirs =
let loc = String_with_vars.loc glob in
Expand Down
76 changes: 76 additions & 0 deletions test/blackbox-tests/test-cases/test-build-if/feature.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,76 @@
enabled_if has a limitation: it attempts building even if enabled_if evaluates to false.

$ cat > dune-project << EOF
> (lang dune 3.9)
> EOF

$ cat > dune << EOF
> (test
> (name t)
> (enabled_if %{env:ENABLED=false}))
> EOF

$ touch t.ml

We test the various combinations:

$ test_one () {
> dune clean
> output=$( dune build "$1" --display short 2>&1 )
> echo When building $1 with ENABLED=${ENABLED:-unset}:
> if echo $output|grep -q ocamlopt ; then
> echo ' build was done: YES'
> else
> echo ' build was done: NO'
> fi
> if echo $output|grep -q "alias runtest" ; then
> echo ' test did run: YES'
> else
> echo ' test did run: NO'
> fi
> }

$ test_all () {
> test_one @all
> test_one @runtest
> ENABLED=true test_one @all
> ENABLED=true test_one @runtest
> }

$ test_all
When building @all with ENABLED=unset:
build was done: YES
test did run: NO
When building @runtest with ENABLED=unset:
build was done: NO
test did run: NO
When building @all with ENABLED=true:
build was done: YES
test did run: NO
When building @runtest with ENABLED=true:
build was done: YES
test did run: YES

Now with build_if:

$ cat > dune << EOF
> (test
> (name t)
> (build_if %{env:ENABLED=false}))
> EOF

Notice that in the first case, nothing is done at all:

$ test_all
When building @all with ENABLED=unset:
build was done: NO
test did run: NO
When building @runtest with ENABLED=unset:
build was done: NO
test did run: NO
When building @all with ENABLED=true:
build was done: YES
test did run: NO
When building @runtest with ENABLED=true:
build was done: YES
test did run: YES
42 changes: 42 additions & 0 deletions test/blackbox-tests/test-cases/test-build-if/package.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,42 @@
build_if is compatible with package.

This is important to test because in that case, (test) can not be split into two stanzas:

$ cat > dune-project << EOF
> (lang dune 3.9)
>
> (package (name a) (allow_empty))
> EOF

$ cat > dune << EOF
> (test
> (name t)
> (package a)
> (build_if %{env:ENABLED=false}))
> EOF

$ touch t.ml

$ dune runtest

If we try to split it we get an error:

$ cat > dune << EOF
> (executable
> (name t)
> (package a)
> (enabled_if %{env:ENABLED=false}))
>
> (rule
> (alias runtest)
> (action (run ./t.exe))
> (package a)
> (enabled_if %{env:ENABLED=false}))
> EOF

$ dune runtest
File "dune", line 3, characters 1-12:
3 | (package a)
^^^^^^^^^^^
Error: This field is useless without a (public_name ...) field.
[1]
25 changes: 25 additions & 0 deletions test/blackbox-tests/test-cases/test-build-if/version.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,25 @@
$ cat > dune-project << EOF
> (lang dune 3.8)
> EOF

$ cat > dune << EOF
> (test
> (name t)
> (build_if true))
> EOF

$ touch t.ml

$ dune build
File "dune", line 3, characters 1-16:
3 | (build_if true))
^^^^^^^^^^^^^^^
Error: 'build_if' is only available since version 3.9 of the dune language.
Please update your dune-project file to have (lang dune 3.9).
[1]

$ cat > dune-project << EOF
> (lang dune 3.9)
> EOF

$ dune build