Skip to content
Open
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
15 changes: 15 additions & 0 deletions doc/tests.rst
Original file line number Diff line number Diff line change
Expand Up @@ -288,6 +288,21 @@ a ``deps`` field the ``inline_tests`` field. The argument of this
(inline_tests (deps data.txt))
(preprocess (pps ppx_expect)))

Specifying Inline Test arguments for Parameterised Libraries
------------------------------------------------------------

If your library is parameterised (see
:doc:`/reference/dune/library_parameter`), you must specify which
implementation of the parameters to use with the ``arguments`` field:

.. code:: ocaml

(library
(name foo)
(parameters a_param b_param)
(inline_tests
(arguments a_impl b_impl)))

Comment on lines +296 to +305
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Just a suggstion, feel free to disregard:

I think it can help with readability to accompany examples with descriptions how how to map the example to the general concept:

Suggested change
implementation of the parameters to use with the ``arguments`` field:
.. code:: ocaml
(library
(name foo)
(parameters a_param b_param)
(inline_tests
(arguments a_impl b_impl)))
implementation of the parameters to use with the ``arguments`` field. E.g.,
if `foo` is a parameterised library, taking parameters `a_param` and
`b_param`, you can specify the implementations to use for the parameters for
inline tests as follows:
.. code:: ocaml
(library
(name foo)
(parameters a_param b_param)
(inline_tests
(arguments a_impl b_impl)))

IMO, this can leave the reader with less to puzzle out, tho it does come at the cost of redundancy.


Passing Special Arguments to the Test Runner
--------------------------------------------
Expand Down
13 changes: 12 additions & 1 deletion src/dune_rules/inline_tests.ml
Original file line number Diff line number Diff line change
Expand Up @@ -264,7 +264,18 @@ include Sub_system.Register_end_point (struct
Resolve.Memo.List.concat_map backends ~f:(fun (backend : Backend.t) ->
backend.runner_libraries)
in
let* lib = Lib.DB.resolve lib_db (loc, Library.best_name lib) in
let* arguments =
Resolve.Memo.lift_memo
@@ Memo.List.map info.arguments ~f:(fun (loc, dep) ->
let open Memo.O in
let+ dep = Lib.DB.resolve lib_db (loc, dep) in
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Is there a reason to not also use Library.best_name on the dep here?

loc, dep)
Comment on lines +270 to +272
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

On the one hand, I like that the local open of Memo.O makes clear where our binding ops are coming from. On the other hand, since we are also already in the context of a monadic bind, this made me assume we must be in some other binding context, so I went looking up the file. From line 2, it seems that Memo.O is just opened thought this file already. So this means the applicative bind on line 253 just above is also Memo.O.

My conclusion is that the extra local open here actually makes the code more confusing, given the pre-existing context. My suggestion is to stick with the surrounding convention for now

Suggested change
let open Memo.O in
let+ dep = Lib.DB.resolve lib_db (loc, dep) in
loc, dep)
let+ dep = Lib.DB.resolve lib_db (loc, dep) in
loc, dep)

and maybe do a followup to make the binding context more narrowly scoped throughout this file in a followup, if you think it is worth it.

in
let* lib =
let open Memo.O in
let+ lib = Lib.DB.resolve lib_db (loc, Library.best_name lib) in
Lib.Parameterised.instantiate ~loc lib arguments ~parent_parameters:[]
in
let* more_libs =
Resolve.Memo.List.map info.libraries ~f:(Lib.DB.resolve lib_db)
in
Expand Down
8 changes: 8 additions & 0 deletions src/dune_rules/inline_tests_info.ml
Original file line number Diff line number Diff line change
Expand Up @@ -134,6 +134,7 @@ module Tests = struct
; executable_link_flags : Ordered_set_lang.Unexpanded.t
; backend : (Loc.t * Lib_name.t) option
; libraries : (Loc.t * Lib_name.t) list
; arguments : (Loc.t * Lib_name.t) list
; enabled_if : Blang.t
}

Expand Down Expand Up @@ -165,6 +166,12 @@ module Tests = struct
ocaml_flags, link_flags))
and+ backend = field_o "backend" (located Lib_name.decode)
and+ libraries = field "libraries" (repeat (located Lib_name.decode)) ~default:[]
and+ arguments =
field
"arguments"
(Dune_lang.Syntax.since Dune_lang.Oxcaml.syntax (0, 1)
>>> repeat (located Lib_name.decode))
~default:[]
and+ modes =
field
"modes"
Expand All @@ -180,6 +187,7 @@ module Tests = struct
; executable_link_flags
; backend
; libraries
; arguments
; modes
; enabled_if
})
Expand Down
1 change: 1 addition & 0 deletions src/dune_rules/inline_tests_info.mli
Original file line number Diff line number Diff line change
Expand Up @@ -46,6 +46,7 @@ module Tests : sig
; executable_link_flags : Ordered_set_lang.Unexpanded.t
; backend : (Loc.t * Lib_name.t) option
; libraries : (Loc.t * Lib_name.t) list
; arguments : (Loc.t * Lib_name.t) list
; enabled_if : Blang.t
}

Expand Down
24 changes: 18 additions & 6 deletions src/dune_rules/parameterised_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -248,12 +248,19 @@ let build_modules ~sctx ~obj_dir ~modules_obj_dir ~dep_graph ~mode ~requires ~li
Module_name.Map.add_exn acc (Module.name module_) instance)
;;

let dep_graph ~obj_dir ~modules impl_only =
let dep_graph ~ocaml_version ~preprocess ~obj_dir ~modules impl_only =
let pp_map =
Staged.unstage
@@ Pp_spec.pped_modules_map
(Dune_lang.Preprocess.Per_module.without_instrumentation preprocess)
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Isn't this change just an unrelated bug fix?

ocaml_version
in
let per_module =
List.fold_left impl_only ~init:Module_name.Unique.Map.empty ~f:(fun acc module_ ->
let module_name_unique = Module.obj_name module_ in
let deps =
let open Action_builder.O in
let module_ = pp_map module_ in
let+ deps =
Dep_rules.read_immediate_deps_of module_ ~modules ~obj_dir ~ml_kind:Impl
in
Expand All @@ -276,10 +283,8 @@ let obj_dir_for_dep_rules dir =
let instantiate ~sctx lib =
let ctx = Super_context.context sctx in
let build_dir = Context.build_dir ctx in
let* { Lib_config.ext_lib; _ } =
let+ ocaml = ctx |> Context.ocaml in
ocaml.lib_config
in
let* ocaml = Context.ocaml ctx in
let ext_lib = ocaml.lib_config.ext_lib in
let lib_info = Lib.info lib in
let modules_obj_dir = Lib_info.obj_dir lib_info in
let* deps_obj_dir, modules =
Expand All @@ -295,7 +300,14 @@ let instantiate ~sctx lib =
modules_obj_dir, Modules.With_vlib.modules modules
in
let impl_only = Modules.With_vlib.impl_only modules in
let dep_graph = dep_graph ~obj_dir:deps_obj_dir ~modules impl_only in
let dep_graph =
dep_graph
~ocaml_version:ocaml.version
~preprocess:(Lib_info.preprocess lib_info)
~obj_dir:deps_obj_dir
~modules
impl_only
in
let* requires =
Lib.closure ~linking:true [ lib ]
|> Resolve.Memo.map
Expand Down
153 changes: 153 additions & 0 deletions test/blackbox-tests/test-cases/oxcaml/parameterised-inline-test.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,153 @@
Testing the instantiation of parameterised inline tests.

$ cat >> dune-project <<EOF
> (lang dune 3.20)
> (using oxcaml 0.1)
> EOF

We first define a parameter signature:

$ mkdir param
$ echo 'val param : string' > param/param.mli
$ cat > param/dune <<EOF
> (library_parameter (name param))
> EOF

Then a parameterised library, which uses inline tests:

$ mkdir lib
$ cat > lib/lib.ml <<EOF
> let param = Param.param
> let%test _ = Param.param = "impl"
> EOF
$ cat > lib/dune <<EOF
> (library
> (name lib)
> (parameters param)
> (inline_tests)
> (preprocess (pps ppx_inline_test)))
> EOF

Running the test fails, because we did not specify an implementation for the
parameter:

$ dune runtest
File "lib/dune", lines 1-5, characters 0-97:
1 | (library
2 | (name lib)
3 | (parameters param)
4 | (inline_tests)
5 | (preprocess (pps ppx_inline_test)))
Error: Parameter "param" is missing.
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Can we make this error more exact and point to the parameters field?

-> required by
_build/default/lib/.lib.inline-tests/.t.eobjs/native/dune__exe__Main.cmx
-> required by _build/default/lib/.lib.inline-tests/inline-test-runner.exe
-> required by _build/default/lib/.lib.inline-tests/partitions-best
-> required by alias lib/runtest-lib in lib/dune:4
-> required by alias lib/runtest in lib/dune:1
Hint: Pass an argument implementing param to the dependency, or add
(parameters param)
Comment on lines +48 to +49
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I'm not sure how to interpret

or add (parameters param)

Isn't (parameters param) already in the stanza? What does fixing using the second disjunct in the hint look like?

[1]

We add an implementation:

$ mkdir impl
$ echo 'let param = "impl"' > impl/impl.ml
$ cat > impl/dune <<EOF
> (library
> (name impl)
> (implements param))
> EOF

And specify that `(inline_tests)` should use it with `(arguments impl)`:

$ cat > lib/dune <<EOF
> (library
> (name lib)
> (parameters param)
> (inline_tests (arguments impl))
> (preprocess (pps ppx_inline_test)))
> EOF

It should work:

$ dune runtest

We break the test to confirm that the inline test is running:

$ cat > lib/lib.ml <<EOF
> let param = "lib(" ^ Param.param ^ ")"
> let%test _ = Param.param = "not impl"
> EOF

$ dune runtest
File "lib/lib.ml", line 2, characters 0-37: <<Param.param = "not impl">> is false.

FAILED 1 / 1 tests
[1]

Using another implementation:

$ mkdir not_impl
$ echo 'let param = "not impl"' > not_impl/not_impl.ml
$ cat > not_impl/dune <<EOF
> (library
> (name not_impl)
> (implements param))
> EOF

$ cat > lib/dune <<EOF
> (library
> (name lib)
> (parameters param)
> (inline_tests (arguments not_impl))
> (preprocess (pps ppx_inline_test)))
> EOF

This now works:

$ dune runtest

Adding another library which has a dependency on the parameterised `lib`:

$ mkdir lib2
$ cat > lib2/lib2_util.ml <<EOF
> let lib_param = Lib.param
> EOF
$ cat > lib2/lib2.ml <<EOF
> let%test _ = Lib2_util.lib_param = "lib(impl)"
> EOF
$ cat > lib2/dune <<EOF
> (library
> (name lib2)
> (parameters param)
> (libraries lib)
> (inline_tests (arguments impl))
> (preprocess (pps ppx_inline_test)))
> EOF

(Note that the library has two files, which triggers the inline_test
preprocessor to generate `.pp.ml` files, which influences how the parameterised
libraries can read the ocamldep outputs since the filenames are not the
unpreprocessed ones.)

This should also work:

$ dune runtest

Using the wrong implementation should break the test again:

$ cat > lib2/dune <<EOF
> (library
> (name lib2)
> (parameters param)
> (libraries lib)
> (inline_tests (arguments not_impl))
> (preprocess (pps ppx_inline_test)))
> EOF

$ dune runtest
File "lib2/lib2.ml", line 1, characters 0-46: <<Lib2_util.lib_param = "lib(impl)">> is false.

FAILED 1 / 1 tests
[1]
Loading