From 9d8199938464b7c058068bcde61d4d9ffc2d0d5f Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Ulysse=20G=C3=A9rard?= Date: Mon, 12 Apr 2021 17:24:00 +0200 Subject: [PATCH] [cram] Add locks to the Cram stanza (#4397) MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit * Add locks to Cram stanza * Add timing-based tests for the locks * Reference the new option in the docs * Add changelog entry Signed-off-by: Ulysse GĂ©rard --- CHANGES.md | 5 +++++ doc/tests.rst | 2 ++ src/dune_rules/cram_rules.ml | 17 +++++++++++++++-- src/dune_rules/cram_stanza.ml | 8 +++++++- src/dune_rules/cram_stanza.mli | 3 ++- .../test-cases/tests-locks.t/dune-project | 3 +++ .../test-cases/tests-locks.t/run.t | 9 +++++++++ .../test-cases/tests-locks.t/tests-no-locks/b.t | 1 + .../tests-locks.t/tests-no-locks/dune | 3 +++ .../tests-locks.t/tests-no-locks/sub/d.t | 1 + .../test-cases/tests-locks.t/tests/a.t | 1 + .../test-cases/tests-locks.t/tests/dune | 4 ++++ .../test-cases/tests-locks.t/tests/sub/b.t | 1 + 13 files changed, 54 insertions(+), 4 deletions(-) create mode 100644 test/blackbox-tests/test-cases/tests-locks.t/dune-project create mode 100644 test/blackbox-tests/test-cases/tests-locks.t/run.t create mode 100644 test/blackbox-tests/test-cases/tests-locks.t/tests-no-locks/b.t create mode 100644 test/blackbox-tests/test-cases/tests-locks.t/tests-no-locks/dune create mode 100644 test/blackbox-tests/test-cases/tests-locks.t/tests-no-locks/sub/d.t create mode 100644 test/blackbox-tests/test-cases/tests-locks.t/tests/a.t create mode 100644 test/blackbox-tests/test-cases/tests-locks.t/tests/dune create mode 100644 test/blackbox-tests/test-cases/tests-locks.t/tests/sub/b.t diff --git a/CHANGES.md b/CHANGES.md index d5d1d0e4a824..6e21f9ed5123 100644 --- a/CHANGES.md +++ b/CHANGES.md @@ -1,3 +1,8 @@ +unreleased +------------------ + +- Add the possibility to use `locks` with the cram tests stanza (#4480, @voodoos) + 2.8.5 (28/03/2021) ------------------ diff --git a/doc/tests.rst b/doc/tests.rst index c2b95bf26c61..674100519b3a 100644 --- a/doc/tests.rst +++ b/doc/tests.rst @@ -608,6 +608,8 @@ The ``cram`` stanza accepts the following fields: - ``alias`` - alias that can be used to run the test. In addition to the user alias, every test ``foo.t`` is attached to the ``@runtest`` alias and gets its own ``@foo`` alias to make it convenient to run individually. +- ``(locks ())`` specify that the tests must be run while + holding the following locks. See the :ref:`locks` section for more details. - ``deps`` - dependencies of the test A single test may be configured by more than one ``cram`` stanza. In such cases, diff --git a/src/dune_rules/cram_rules.ml b/src/dune_rules/cram_rules.ml index c10b0b368338..8bfa95561762 100644 --- a/src/dune_rules/cram_rules.ml +++ b/src/dune_rules/cram_rules.ml @@ -10,6 +10,7 @@ type effective = ; alias : Alias.Name.Set.t ; deps : unit Build.t list ; enabled_if : Blang.t list + ; locks : Path.Set.t ; packages : Package.Name.Set.t } @@ -17,6 +18,7 @@ let empty_effective = { loc = Loc.none ; alias = Alias.Name.Set.singleton Alias.Name.runtest ; enabled_if = [ Blang.true_ ] + ; locks = Path.Set.empty ; deps = [] ; packages = Package.Name.Set.empty } @@ -96,9 +98,10 @@ let test_rule ~sctx ~expander ~dir (spec : effective) in action in + let locks = Path.Set.to_list spec.locks in let cram = Build.with_no_targets cram in List.iter aliases ~f:(fun alias -> - Alias_rules.add sctx ~alias ~stamp ~loc cram ~locks:[]) ) + Alias_rules.add sctx ~alias ~stamp ~loc cram ~locks) ) let rules ~sctx ~expander ~dir tests = let stanzas = @@ -175,7 +178,17 @@ let rules ~sctx ~expander ~dir tests = | Some (p : Package.t) -> Package.Name.Set.add acc.packages (Package.Id.name p.id) in - { acc with enabled_if; deps; alias; packages }) + let locks = + (* Locks must be relative to the cram stanza directory and not + the individual tests direcories *) + List.fold_left ~init:acc.locks + ~f:(fun acc lock -> + Expander.Static.expand_str expander lock + |> Path.relative (Path.build dir) + |> Path.Set.add acc) + spec.locks + in + { acc with enabled_if; locks; deps; alias; packages }) in let test_rule () = test_rule ~sctx ~expander ~dir effective test in match !Clflags.only_packages with diff --git a/src/dune_rules/cram_stanza.ml b/src/dune_rules/cram_stanza.ml index e353d92819c1..73e99ba11924 100644 --- a/src/dune_rules/cram_stanza.ml +++ b/src/dune_rules/cram_stanza.ml @@ -27,6 +27,7 @@ type t = ; alias : Alias.Name.t option ; deps : Dep_conf.t Bindings.t option ; enabled_if : Blang.t + ; locks : String_with_vars.t list ; package : Package.t option } @@ -38,9 +39,14 @@ let decode = and+ alias = field_o "alias" Alias.Name.decode and+ deps = field_o "deps" (Bindings.decode Dep_conf.decode) and+ enabled_if = Enabled_if.decode ~allowed_vars:Any ~since:None () + and+ locks = + field "locks" + (Dune_lang.Syntax.since Stanza.syntax (2, 9) + >>> repeat String_with_vars.decode) + ~default:[] and+ package = Stanza_common.Pkg.field_opt ~check:(Dune_lang.Syntax.since Stanza.syntax (2, 8)) () in - { loc; alias; deps; enabled_if; applies_to; package }) + { loc; alias; deps; enabled_if; locks; applies_to; package }) diff --git a/src/dune_rules/cram_stanza.mli b/src/dune_rules/cram_stanza.mli index 0541092ff656..4b0445558959 100644 --- a/src/dune_rules/cram_stanza.mli +++ b/src/dune_rules/cram_stanza.mli @@ -6,11 +6,12 @@ type applies_to = | Files_matching_in_this_dir of Predicate_lang.Glob.t type t = - { loc : Loc.t + { loc : Loc.t (* ; dir : Path.t *) ; applies_to : applies_to ; alias : Alias.Name.t option ; deps : Dep_conf.t Bindings.t option ; enabled_if : Blang.t + ; locks : String_with_vars.t list ; package : Package.t option } diff --git a/test/blackbox-tests/test-cases/tests-locks.t/dune-project b/test/blackbox-tests/test-cases/tests-locks.t/dune-project new file mode 100644 index 000000000000..bced59eab593 --- /dev/null +++ b/test/blackbox-tests/test-cases/tests-locks.t/dune-project @@ -0,0 +1,3 @@ +(lang dune 2.9) + +(cram enable) diff --git a/test/blackbox-tests/test-cases/tests-locks.t/run.t b/test/blackbox-tests/test-cases/tests-locks.t/run.t new file mode 100644 index 000000000000..3c7bc9f84723 --- /dev/null +++ b/test/blackbox-tests/test-cases/tests-locks.t/run.t @@ -0,0 +1,9 @@ +These tests are run with locks. They should not end together (<> expected) + $ dune build --root=. -j 2 --diff-command=diff @all-tests 2>&1 | + > grep "^> *" | uniq -c | [ $(wc -l) -eq 1 ] && echo '=' || echo '<>' + <> + +These tests are run without locks. They should end together (= expected) + $ dune build --root=. -j 2 --diff-command=diff @all-tests-nolocks 2>&1 | + > grep "^> *" | uniq -c | [ $(wc -l) -eq 1 ] && echo '=' || echo '<>' + = diff --git a/test/blackbox-tests/test-cases/tests-locks.t/tests-no-locks/b.t b/test/blackbox-tests/test-cases/tests-locks.t/tests-no-locks/b.t new file mode 100644 index 000000000000..e5af6b7795a0 --- /dev/null +++ b/test/blackbox-tests/test-cases/tests-locks.t/tests-no-locks/b.t @@ -0,0 +1 @@ + $ sleep 1 && date +%s diff --git a/test/blackbox-tests/test-cases/tests-locks.t/tests-no-locks/dune b/test/blackbox-tests/test-cases/tests-locks.t/tests-no-locks/dune new file mode 100644 index 000000000000..8711d4f1d793 --- /dev/null +++ b/test/blackbox-tests/test-cases/tests-locks.t/tests-no-locks/dune @@ -0,0 +1,3 @@ +(cram + (applies_to :whole_subtree) + (alias all-tests-nolocks)) diff --git a/test/blackbox-tests/test-cases/tests-locks.t/tests-no-locks/sub/d.t b/test/blackbox-tests/test-cases/tests-locks.t/tests-no-locks/sub/d.t new file mode 100644 index 000000000000..e5af6b7795a0 --- /dev/null +++ b/test/blackbox-tests/test-cases/tests-locks.t/tests-no-locks/sub/d.t @@ -0,0 +1 @@ + $ sleep 1 && date +%s diff --git a/test/blackbox-tests/test-cases/tests-locks.t/tests/a.t b/test/blackbox-tests/test-cases/tests-locks.t/tests/a.t new file mode 100644 index 000000000000..e5af6b7795a0 --- /dev/null +++ b/test/blackbox-tests/test-cases/tests-locks.t/tests/a.t @@ -0,0 +1 @@ + $ sleep 1 && date +%s diff --git a/test/blackbox-tests/test-cases/tests-locks.t/tests/dune b/test/blackbox-tests/test-cases/tests-locks.t/tests/dune new file mode 100644 index 000000000000..888089f358f8 --- /dev/null +++ b/test/blackbox-tests/test-cases/tests-locks.t/tests/dune @@ -0,0 +1,4 @@ +(cram + (applies_to :whole_subtree) + (locks a) + (alias all-tests)) diff --git a/test/blackbox-tests/test-cases/tests-locks.t/tests/sub/b.t b/test/blackbox-tests/test-cases/tests-locks.t/tests/sub/b.t new file mode 100644 index 000000000000..e5af6b7795a0 --- /dev/null +++ b/test/blackbox-tests/test-cases/tests-locks.t/tests/sub/b.t @@ -0,0 +1 @@ + $ sleep 1 && date +%s