Skip to content

Commit

Permalink
Merge pull request #3747 from lubegasimon/inline-tests-compile-flags
Browse files Browse the repository at this point in the history
add flexibility to compile a test executable
  • Loading branch information
rgrinberg authored Sep 12, 2020
2 parents 7bfd8df + 851445e commit bf02581
Show file tree
Hide file tree
Showing 12 changed files with 158 additions and 91 deletions.
3 changes: 3 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,9 @@ Unreleased

- Fix bootstrap script with custom configuration. (#3757, fixes #3774, @marsam)

- Add the `executable` field to `inline_tests` to customize the compilation
flags of the test runner executable (#3747, fixes #3679, @lubegasimon)

2.7.1 (2/09/2020)
-----------------

Expand Down
184 changes: 102 additions & 82 deletions doc/tests.rst
Original file line number Diff line number Diff line change
Expand Up @@ -33,8 +33,8 @@ with other targets by passing ``@runtest`` to ``dune build``. For instance:

.. code:: bash
$ dune build @install @runtest
$ dune build @install @test/runtest
$ dune build @install @runtest
$ dune build @install @test/runtest
Running a single test
Expand Down Expand Up @@ -71,39 +71,39 @@ follows:

.. code:: ocaml
let rec fact n = if n = 1 then 1 else n * fact (n - 1)
let rec fact n = if n = 1 then 1 else n * fact (n - 1)
let%test _ = fact 5 = 120
let%test _ = fact 5 = 120
The file has to be preprocessed with the ppx_inline_test ppx rewriter,
so for instance the ``dune`` file might look like this:

.. code:: scheme
(library
(name foo)
(preprocess (pps ppx_inline_test)))
(library
(name foo)
(preprocess (pps ppx_inline_test)))
In order to instruct dune that our library contains inline tests,
all we have to do is add an ``inline_tests`` field:

.. code:: scheme
(library
(name foo)
(inline_tests)
(preprocess (pps ppx_inline_test)))
(library
(name foo)
(inline_tests)
(preprocess (pps ppx_inline_test)))
We can now build and execute this test by running ``dune runtest``. For
instance, if we make the test fail by replacing ``120`` by ``0`` we get:

.. code:: bash
$ dune runtest
[...]
File "src/fact.ml", line 3, characters 0-25: <<(fact 5) = 0>> is false.
$ dune runtest
[...]
File "src/fact.ml", line 3, characters 0-25: <<(fact 5) = 0>> is false.
FAILED 1 / 1 tests
FAILED 1 / 1 tests
Note that in this case Dune knew how to build and run the tests
without any special configuration. This is because ppx_inline_test
Expand All @@ -115,9 +115,9 @@ field:
.. code:: scheme
(library
(name foo)
(inline_tests (backend qtest.lib)))
(library
(name foo)
(inline_tests (backend qtest.lib)))
In the example above, the name `qtest.lib` comes from the `public_name` field
in `qtest`'s own `dune` file.
Expand All @@ -132,11 +132,11 @@ expect this code to print. For instance, using ppx_expect_:
.. code:: ocaml
let%expect_test _ =
print_endline "Hello, world!";
[%expect{|
Hello, world!
|}]
let%expect_test _ =
print_endline "Hello, world!";
[%expect{|
Hello, world!
|}]
The test procedure consist of executing the OCaml code and replacing
the contents of the ``[%expect]`` extension point by the real
Expand All @@ -163,41 +163,41 @@ your list of ppx rewriters as follows:
.. code:: scheme
(library
(name foo)
(inline_tests)
(preprocess (pps ppx_expect)))
(library
(name foo)
(inline_tests)
(preprocess (pps ppx_expect)))
Then calling ``dune runtest`` will run these tests and in case of
mismatch dune will print a diff of the original source file and
the suggested correction. For instance:
.. code:: bash
$ dune runtest
[...]
-src/fact.ml
+src/fact.ml.corrected
File "src/fact.ml", line 5, characters 0-1:
let rec fact n = if n = 1 then 1 else n * fact (n - 1)
$ dune runtest
[...]
-src/fact.ml
+src/fact.ml.corrected
File "src/fact.ml", line 5, characters 0-1:
let rec fact n = if n = 1 then 1 else n * fact (n - 1)
let%expect_test _ =
print_int (fact 5);
- [%expect]
+ [%expect{| 120 |}]
let%expect_test _ =
print_int (fact 5);
- [%expect]
+ [%expect{| 120 |}]
In order to accept the correction, simply run:
.. code:: bash
$ dune promote
$ dune promote
You can also make dune automatically accept the correction after
running the tests by typing:
.. code:: bash
$ dune runtest --auto-promote
$ dune runtest --auto-promote
Finally, some editor integration is possible to make the editor do the
promotion and make the workflow even smoother.
Expand Down Expand Up @@ -234,10 +234,10 @@ For instance:
.. code:: ocaml
(library
(name foo)
(inline_tests (modes byte best js))
(preprocess (pps ppx_expect)))
(library
(name foo)
(inline_tests (modes byte best js))
(preprocess (pps ppx_expect)))
Specifying inline test dependencies
-----------------------------------
Expand All @@ -248,10 +248,10 @@ a ``deps`` field the ``inline_tests`` field. The argument of this
.. code:: ocaml
(library
(name foo)
(inline_tests (deps data.txt))
(preprocess (pps ppx_expect)))
(library
(name foo)
(inline_tests (deps data.txt))
(preprocess (pps ppx_expect)))
Passing special arguments to the test runner
--------------------------------------------
Expand All @@ -263,10 +263,30 @@ as:
.. code:: ocaml
(library
(name foo)
(inline_tests (flags (-foo bar)))
(preprocess (pps ppx_expect)))
(library
(name foo)
(inline_tests (flags (-foo bar)))
(preprocess (pps ppx_expect)))
The argument of the ``flags`` field follows the :ref:`ordered-set-language`.
Passing special arguments to the test executable
------------------------------------------------
To control how the test executable is built, it’s possible to customize a subset
of compilation options for an executable using the ``executable`` field. Dune
gives you the right to do that by simply specifying command line arguments as flags.
You can specify such flags by using ``flags`` field. For instance:
.. code:: ocaml
(library
(name foo)
(inline_tests
(flags (-foo bar)
(executable
(flags (-foo bar))))
(preprocess (pps ppx_expect))))
The argument of the ``flags`` field follows the :ref:`ordered-set-language`.
Expand All @@ -280,10 +300,11 @@ such libraries using a ``libraries`` field, such as:
.. code:: ocaml
(library
(name foo)
(inline_tests (backend qtest)
(libraries bar)))
(library
(name foo)
(inline_tests
(backend qtest)
(libraries bar)))
Defining your own inline test backend
-------------------------------------
Expand All @@ -308,10 +329,10 @@ These three parameters can be specified inside the
.. code:: scheme
(generate_runner <action>)
(runner_libraries (<ocaml-libraries>))
(flags <flags>)
(extends (<backends>))
(generate_runner <action>)
(runner_libraries (<ocaml-libraries>))
(flags <flags>)
(extends (<backends>))
For instance:
Expand Down Expand Up @@ -357,17 +378,16 @@ In this example, we put tests in comments of the form:
.. code:: ocaml
(*TEST: assert (fact 5 = 120) *)
(*TEST: assert (fact 5 = 120) *)
The backend for such a framework looks like this:
.. code:: lisp
(library
(name simple_tests)
(inline_tests.backend
(generate_runner (run sed "s/(\\*TEST:\\(.*\\)\\*)/let () = \\1;;/" %{impl-files}))
))
(library
(name simple_tests)
(inline_tests.backend
(generate_runner (run sed "s/(\\*TEST:\\(.*\\)\\*)/let () = \\1;;/" %{impl-files}))))
Now all you have to do is write ``(inline_tests ((backend
simple_tests)))`` wherever you want to write such tests. Note that
Expand All @@ -385,9 +405,9 @@ running your testsuite, simply add this to a dune file:
.. code:: scheme
(rule
(alias runtest)
(action (run ./tests.exe)))
(rule
(alias runtest)
(action (run ./tests.exe)))
Hence to define an a test a pair of alias and executable stanzas are required.
To simplify this common pattern, dune provides a :ref:`tests-stanza` stanza to
Expand All @@ -408,12 +428,12 @@ command. For instance let's consider this test:
.. code:: scheme
(rule
(with-stdout-to tests.output (run ./tests.exe)))
(rule
(with-stdout-to tests.output (run ./tests.exe)))
(rule
(alias runtest)
(action (diff tests.expected test.output)))
(rule
(alias runtest)
(action (diff tests.expected test.output)))
After having run ``tests.exe`` and dumping its output to ``tests.output``, dune
will compare the latter to ``tests.expected``. In case of mismatch, dune will
Expand All @@ -434,15 +454,15 @@ This provides a nice way of dealing with the usual *write code*,
.. code:: bash
$ dune runtest
[...]
-tests.expected
+tests.output
File "tests.expected", line 1, characters 0-1:
-Hello, world!
+Good bye!
$ dune promote
Promoting _build/default/tests.output to tests.expected.
$ dune runtest
[...]
-tests.expected
+tests.output
File "tests.expected", line 1, characters 0-1:
-Hello, world!
+Good bye!
$ dune promote
Promoting _build/default/tests.output to tests.expected.
Note that if available, the diffing is done using the patdiff_ tool,
which displays nicer looking diffs that the standard ``diff``
Expand Down
2 changes: 1 addition & 1 deletion src/dune_rules/exe_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -87,7 +87,7 @@ let executables_rules ~sctx ~dir ~expander ~dir_contents ~scope ~compile_info
else
l
in
let flags = SC.ocaml_flags sctx ~dir exes.buildable in
let flags = SC.ocaml_flags sctx ~dir exes.buildable.flags in
let link_deps = Dep_conf_eval.unnamed ~expander exes.link_deps in
let foreign_archives = exes.buildable.foreign_archives |> List.map ~f:snd in
let link_flags =
Expand Down
15 changes: 12 additions & 3 deletions src/dune_rules/inline_tests.ml
Original file line number Diff line number Diff line change
Expand Up @@ -164,6 +164,7 @@ include Sub_system.Register_end_point (struct
; deps : Dep_conf.t list
; modes : Mode_conf.Set.t
; flags : Ordered_set_lang.Unexpanded.t
; executable : Ocaml_flags.Spec.t
; backend : (Loc.t * Lib_name.t) option
; libraries : (Loc.t * Lib_name.t) list
}
Expand All @@ -183,6 +184,10 @@ include Sub_system.Register_end_point (struct
(let+ loc = loc
and+ deps = field "deps" (repeat Dep_conf.decode) ~default:[]
and+ flags = Ordered_set_lang.Unexpanded.field "flags"
and+ executable =
field "executable" ~default:Ocaml_flags.Spec.standard
( Dune_lang.Syntax.since Stanza.syntax (2, 8)
>>> fields Ocaml_flags.Spec.decode )
and+ backend = field_o "backend" (located Lib_name.decode)
and+ libraries =
field "libraries" (repeat (located Lib_name.decode)) ~default:[]
Expand All @@ -191,7 +196,7 @@ include Sub_system.Register_end_point (struct
(Dune_lang.Syntax.since syntax (1, 11) >>> Mode_conf.Set.decode)
~default:Mode_conf.Set.default
in
{ loc; deps; flags; backend; libraries; modes })
{ loc; deps; flags; executable; backend; libraries; modes })

(* We don't use this at the moment, but we could implement it for debugging
purposes *)
Expand Down Expand Up @@ -278,11 +283,15 @@ include Sub_system.Register_end_point (struct
in
Build.With_targets.add ~targets:[ target ] action);
let cctx =
let flags =
Ocaml_flags.append_common
(Super_context.ocaml_flags sctx ~dir info.executable)
[ "-w"; "-24"; "-g" ]
in
Compilation_context.create () ~super_context:sctx ~expander ~scope
~obj_dir ~modules ~opaque:(Explicit false) ~requires_compile:runner_libs
~requires_link:(lazy runner_libs)
~flags:(Ocaml_flags.of_list [ "-w"; "-24"; "-g" ])
~js_of_ocaml:(Some lib.buildable.js_of_ocaml) ~dynlink:false
~flags ~js_of_ocaml:(Some lib.buildable.js_of_ocaml) ~dynlink:false
~package:(Option.map lib.public ~f:Dune_file.Public_lib.package)
in
let linkages =
Expand Down
Loading

0 comments on commit bf02581

Please sign in to comment.