Skip to content

Commit

Permalink
Allow runtest to run individual tests (#11041)
Browse files Browse the repository at this point in the history
* feature: dune runtest can run individual tests
  • Loading branch information
Alizter authored Oct 31, 2024
1 parent 05124de commit dc43cd7
Show file tree
Hide file tree
Showing 10 changed files with 222 additions and 23 deletions.
111 changes: 97 additions & 14 deletions bin/runtest.ml
Original file line number Diff line number Diff line change
Expand Up @@ -4,11 +4,24 @@ let runtest_info =
let doc = "Run tests." in
let man =
[ `S "DESCRIPTION"
; `P {|This is a short-hand for calling:|}
; `Pre {| dune build @runtest|}
; `P "Run the given tests. The [TEST] argument can be either:"
; `I
( "-"
, "A directory: If a directory is provided, dune will recursively run all tests \
within that directory." )
; `I
( "-"
, "A file name: If a specific file name is provided, dune will run the tests \
with that name." )
; `P
"If no [TEST] is provided, dune will run all tests in the current directory and \
its subdirectories."
; `P "See EXAMPLES below for additional information on use cases."
; `Blocks Common.help_secs
; Common.examples
[ ( "Run all tests in the current source tree (including those that passed on \
[ "Run all tests in a given directory", "dune runtest path/to/dir/"
; "Run a specific cram test", "dune runtest path/to/mytest.t"
; ( "Run all tests in the current source tree (including those that passed on \
the last run)"
, "dune runtest --force" )
; ( "Run tests sequentially without output buffering"
Expand All @@ -19,21 +32,91 @@ let runtest_info =
Cmd.info "runtest" ~doc ~man ~envs:Common.envs
;;

let find_cram_test path ~parent_dir =
let open Memo.O in
Source_tree.nearest_dir parent_dir
>>= Dune_rules.Cram_rules.cram_tests
(* We ignore the errors we get when searching for cram tests as they will
be reported during building anyway. We are only interested in the
presence of cram tests. *)
>>| List.filter_map ~f:Result.to_option
(* We search our list of known cram tests for the test we are looking
for. *)
>>| List.find ~f:(fun (test : Dune_rules.Cram_test.t) ->
let src =
match test with
| File src -> src
| Dir { dir = src; _ } -> src
in
Path.Source.equal path src)
;;

(* [disambiguate_test_name path] is a function that takes in a
directory [path] and classifies it as either a cram test or a directory to
run tests in. *)
let disambiguate_test_name path =
match Path.Source.parent path with
| None -> Memo.return @@ `Runtest (Path.source Path.Source.root)
| Some parent_dir ->
let open Memo.O in
find_cram_test path ~parent_dir
>>= (function
| Some test ->
(* If we find the cram test, then we request that is run. *)
Memo.return (`Test (parent_dir, Dune_rules.Cram_test.name test))
| None ->
(* If we don't find it, then we assume the user intended a directory for
@runtest to be used. *)
Source_tree.find_dir path
>>= (function
(* We need to make sure that this directory or file exists. *)
| Some _ -> Memo.return (`Runtest (Path.source path))
| None ->
(* If the user misspelled the test name, we give them a hint. *)
let+ hints =
let+ candidates =
let+ files = Source_tree.files_of parent_dir in
Path.Source.Set.to_list_map files ~f:Path.Source.basename
in
User_message.did_you_mean (Path.Source.basename path) ~candidates
in
User_error.raise
~hints
[ Pp.textf "%S was not found." (Path.Source.to_string path) ]))
;;

let runtest_term =
let name_ = Arg.info [] ~docv:"DIR" in
let name = Arg.info [] ~docv:"TEST" in
let+ builder = Common.Builder.term
and+ dirs = Arg.(value & pos_all string [ "." ] name_) in
and+ dirs = Arg.(value & pos_all string [ "." ] name) in
let common, config = Common.init builder in
let request (setup : Import.Main.build_system) =
Action_builder.all_unit
(List.map dirs ~f:(fun dir ->
let dir = Path.(relative root) (Common.prefix_target common dir) in
Alias.in_dir
~name:Dune_rules.Alias.runtest
~recursive:true
~contexts:setup.contexts
dir
|> Alias.request))
List.map dirs ~f:(fun dir ->
let dir = Path.(relative root) (Common.prefix_target common dir) in
let open Action_builder.O in
let* alias_kind =
match Path.as_in_source_tree dir with
| Some path -> Action_builder.of_memo (disambiguate_test_name path)
| None ->
(* If the path is in the source tree, we disambiguate it. *)
Action_builder.return (`Runtest dir)
in
Alias.request
@@
match alias_kind with
| `Test (dir, alias_name) ->
Alias.in_dir
~name:(Dune_engine.Alias.Name.of_string alias_name)
~recursive:false
~contexts:setup.contexts
(Path.source dir)
| `Runtest dir ->
Alias.in_dir
~name:Dune_rules.Alias.runtest
~recursive:true
~contexts:setup.contexts
dir)
|> Action_builder.all_unit
in
Build_cmd.run_build_command ~common ~config ~request
;;
Expand Down
2 changes: 2 additions & 0 deletions doc/changes/11041.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
- `dune runtest` can now run individual tests with `dune runtest mytest.t`
(#11041, @Alizter).
3 changes: 2 additions & 1 deletion doc/explanation/mental-model.rst
Original file line number Diff line number Diff line change
Expand Up @@ -129,7 +129,8 @@ Dune can build *files* and *aliases*. These can be found on the command line:
- ``dune build tool.exe @example`` will build both the file ``tool.exe`` and
the ``example`` alias.
- ``dune runtest`` is a shortcut for ``dune build @runtest``: it will build the
``runtest`` alias.
``runtest`` alias. Passing a directory will build all tests in that directory.
Passing the path to a cram test will run that test individually.
- ``dune build`` is a shortcut for ``dune build @@default``: it will build the
default alias in the current directory (by default the ``all`` alias).

Expand Down
3 changes: 2 additions & 1 deletion doc/reference/aliases/runtest.rst
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@
Actions that run tests are attached to this alias. For example this convention
is used by the ``(test)`` stanza.

``dune runtest`` is a shortcut for ``dune build @runtest``.
``dune runtest`` is a shortcut for ``dune build @runtest`` but is also able to
run individual tests.

.. seealso:: :doc:`/tests`
3 changes: 3 additions & 0 deletions doc/reference/cram.rst
Original file line number Diff line number Diff line change
Expand Up @@ -179,11 +179,14 @@ Every Cram test has a name. For file tests, the name of ``something.t`` is

There are several ways to execute Cram tests:

- Running ``dune runtest something.t`` will run the cram test with filename
``something.t``.
- All Cram tests are attached to the :doc:`/reference/aliases/runtest` alias.
So ``dune runtest`` will run all Cram tests.
- Every Cram test creates an alias after its name. So, ``dune build
@something`` will run tests named ``something``.


When a Cram test is executed, the commands it contains are executed, and a
corrected file is created where the command outputs are inserted after
each command. This corrected file is then offered for :doc:`promotion
Expand Down
9 changes: 3 additions & 6 deletions doc/tests.rst
Original file line number Diff line number Diff line change
Expand Up @@ -63,16 +63,13 @@ exec`` to run the test executable (for the sake of this example,
$ dune exec project/tests/myTest.exe
To run :ref:`cram-tests`, you can use the alias that is created for the test.
The name of the alias corresponds to the name of the test without the ``.t``
extension. For directory tests, this is the name of the directory without the
``.t`` extension. Assuming a ``cram-test.t`` or ``cram-test.t/run.t`` file
exists, it can be run with:
To run :ref:`cram-tests` you can pass their paths to the ``dune test`` command.

.. code:: console
$ dune build @cram-test
$ dune test tests/myCramTest.t
This works both for directory and file cram tests.

Running Tests in a Directory
----------------------------
Expand Down
2 changes: 1 addition & 1 deletion doc/usage.rst
Original file line number Diff line number Diff line change
Expand Up @@ -258,7 +258,7 @@ Running Tests
There are two ways to run tests:

- ``dune build @runtest``
- ``dune test`` (or the more explicit ``dune runtest``)
- ``dune test`` (or its alias ``dune runtest``)

The two commands are equivalent, and they will run all the tests defined in the
current directory and its children directories recursively. You can also run the tests in a
Expand Down
7 changes: 7 additions & 0 deletions src/dune_rules/cram/cram_rules.mli
Original file line number Diff line number Diff line change
Expand Up @@ -2,4 +2,11 @@

open Import

(** The type of errors that can occur when searching for cram tests *)
type error

(** Memoized list of cram tests in a directory. *)
val cram_tests : Source_tree.Dir.t -> (Cram_test.t, error) result list Memo.t

(** Cram test rules *)
val rules : sctx:Super_context.t -> dir:Path.Build.t -> Source_tree.Dir.t -> unit Memo.t
2 changes: 2 additions & 0 deletions src/dune_rules/dune_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -73,6 +73,8 @@ module Lock_dir = Lock_dir
module Pkg_dev_tool = Pkg_dev_tool
module Pkg_build_progress = Pkg_build_progress
module Compile_time = Compile_time
module Cram_rules = Cram_rules
module Cram_test = Cram_test

module Install_rules = struct
let install_file = Install_rules.install_file
Expand Down
103 changes: 103 additions & 0 deletions test/blackbox-tests/test-cases/runtest-cmd.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,103 @@
Here we test the features of the `dune runtest` command.

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

$ cat > mytest.t <<EOF
> $ echo "Hello, world!"
> "Goodbye, world!"
> EOF
$ mkdir -p tests/myothertest.t
$ cat > tests/myothertest.t/run.t <<EOF
> $ echo "Hello, world!"
> "Goodbye, world!"
> EOF
$ cat > tests/filetest.t <<EOF
> $ echo "Hello, world!"
> "Goodbye, world!"
> EOF


This should work:

$ dune test tests/myothertest.t
File "tests/myothertest.t/run.t", line 1, characters 0-0:
Error: Files _build/default/tests/myothertest.t/run.t and
_build/default/tests/myothertest.t/run.t.corrected differ.
[1]

This should not work

$ dune test myotherttest.t
Error: "myotherttest.t" was not found.
[1]

Should this work? Debatable but giving a hint if it doesn't would be good.

$ dune test tests/myothertest.t/run.t
File "tests/myothertest.t/run.t", line 1, characters 0-0:
Error: Files _build/default/tests/myothertest.t/run.t and
_build/default/tests/myothertest.t/run.t.corrected differ.
[1]

Passing no arguments to $ dune runtest should be equivalent to $ dune build
@runtest.

$ dune test 2>&1 | grep "^File"
File "mytest.t", line 1, characters 0-0:
File "tests/filetest.t", line 1, characters 0-0:
File "tests/myothertest.t/run.t", line 1, characters 0-0:

Passing the name of a test should only run that test.

$ dune test mytest.t 2>&1 | grep "^File"
File "mytest.t", line 1, characters 0-0:
$ dune test tests/myothertest.t 2>&1 | grep "^File"
File "tests/myothertest.t/run.t", line 1, characters 0-0:

Passing a directory should run all the tests in that directory (recursively).

- The current working directory:
$ dune test . 2>&1 | grep "^File"
File "mytest.t", line 1, characters 0-0:
File "tests/filetest.t", line 1, characters 0-0:
File "tests/myothertest.t/run.t", line 1, characters 0-0:

- The tests/ subdirectory:
$ dune test tests/ 2>&1 | grep "^File"
File "tests/filetest.t", line 1, characters 0-0:
File "tests/myothertest.t/run.t", line 1, characters 0-0:

- We can also build in _build/ directories:
$ dune test _build/default 2>&1 | grep "^File"
File "mytest.t", line 1, characters 0-0:
File "tests/filetest.t", line 1, characters 0-0:
File "tests/myothertest.t/run.t", line 1, characters 0-0:
$ dune test _build/default/tests 2>&1 | grep "^File"
File "tests/filetest.t", line 1, characters 0-0:
File "tests/myothertest.t/run.t", line 1, characters 0-0:

Here we test some error cases a user may encounter and make sure the error
messages are informative enough.

- Giving a path outside the workspace gives an informative error:
$ dune test ..
Error: @@ on the command line must be followed by a relative path
[1]
- Giving a nonexistent path gives an informative error:
$ dune test nonexistent
Error: "nonexistent" was not found.
[1]
$ dune test tests/non
Error: "tests/non" was not found.
[1]
- Passing the _build directory on its own is an error.
$ dune test _build
Error: This path is internal to dune: _build
[1]
- Typos are caught and aided with hints:
$ dune test mytest1.t
Error: "mytest1.t" was not found.
Hint: did you mean mytest.t?
[1]

0 comments on commit dc43cd7

Please sign in to comment.