Skip to content

Commit 008ed88

Browse files
committed
feat(oxcaml): parameterised inline_tests
Signed-off-by: ArthurW <[email protected]>
1 parent fed00c9 commit 008ed88

File tree

6 files changed

+207
-7
lines changed

6 files changed

+207
-7
lines changed

doc/tests.rst

Lines changed: 15 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -288,6 +288,21 @@ a ``deps`` field the ``inline_tests`` field. The argument of this
288288
(inline_tests (deps data.txt))
289289
(preprocess (pps ppx_expect)))
290290
291+
Specifying Inline Test arguments for Parameterised Libraries
292+
------------------------------------------------------------
293+
294+
If your library is parameterised (see
295+
:doc:`/reference/dune/library_parameter`), you must specify which
296+
implementation of the parameters to use with the ``arguments`` field:
297+
298+
.. code:: ocaml
299+
300+
(library
301+
(name foo)
302+
(parameters a_param b_param)
303+
(inline_tests
304+
(arguments a_impl b_impl)))
305+
291306
292307
Passing Special Arguments to the Test Runner
293308
--------------------------------------------

src/dune_rules/inline_tests.ml

Lines changed: 12 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -264,7 +264,18 @@ include Sub_system.Register_end_point (struct
264264
Resolve.Memo.List.concat_map backends ~f:(fun (backend : Backend.t) ->
265265
backend.runner_libraries)
266266
in
267-
let* lib = Lib.DB.resolve lib_db (loc, Library.best_name lib) in
267+
let* arguments =
268+
Resolve.Memo.lift_memo
269+
@@ Memo.List.map info.arguments ~f:(fun (loc, dep) ->
270+
let open Memo.O in
271+
let+ dep = Lib.DB.resolve lib_db (loc, dep) in
272+
loc, dep)
273+
in
274+
let* lib =
275+
let open Memo.O in
276+
let+ lib = Lib.DB.resolve lib_db (loc, Library.best_name lib) in
277+
Lib.Parameterised.instantiate ~loc lib arguments ~parent_parameters:[]
278+
in
268279
let* more_libs =
269280
Resolve.Memo.List.map info.libraries ~f:(Lib.DB.resolve lib_db)
270281
in

src/dune_rules/inline_tests_info.ml

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -134,6 +134,7 @@ module Tests = struct
134134
; executable_link_flags : Ordered_set_lang.Unexpanded.t
135135
; backend : (Loc.t * Lib_name.t) option
136136
; libraries : (Loc.t * Lib_name.t) list
137+
; arguments : (Loc.t * Lib_name.t) list
137138
; enabled_if : Blang.t
138139
}
139140

@@ -165,6 +166,12 @@ module Tests = struct
165166
ocaml_flags, link_flags))
166167
and+ backend = field_o "backend" (located Lib_name.decode)
167168
and+ libraries = field "libraries" (repeat (located Lib_name.decode)) ~default:[]
169+
and+ arguments =
170+
field
171+
"arguments"
172+
(Dune_lang.Syntax.since Dune_lang.Oxcaml.syntax (0, 1)
173+
>>> repeat (located Lib_name.decode))
174+
~default:[]
168175
and+ modes =
169176
field
170177
"modes"
@@ -180,6 +187,7 @@ module Tests = struct
180187
; executable_link_flags
181188
; backend
182189
; libraries
190+
; arguments
183191
; modes
184192
; enabled_if
185193
})

src/dune_rules/inline_tests_info.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -46,6 +46,7 @@ module Tests : sig
4646
; executable_link_flags : Ordered_set_lang.Unexpanded.t
4747
; backend : (Loc.t * Lib_name.t) option
4848
; libraries : (Loc.t * Lib_name.t) list
49+
; arguments : (Loc.t * Lib_name.t) list
4950
; enabled_if : Blang.t
5051
}
5152

src/dune_rules/parameterised_rules.ml

Lines changed: 18 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -248,12 +248,19 @@ let build_modules ~sctx ~obj_dir ~modules_obj_dir ~dep_graph ~mode ~requires ~li
248248
Module_name.Map.add_exn acc (Module.name module_) instance)
249249
;;
250250

251-
let dep_graph ~obj_dir ~modules impl_only =
251+
let dep_graph ~ocaml_version ~preprocess ~obj_dir ~modules impl_only =
252+
let pp_map =
253+
Staged.unstage
254+
@@ Pp_spec.pped_modules_map
255+
(Dune_lang.Preprocess.Per_module.without_instrumentation preprocess)
256+
ocaml_version
257+
in
252258
let per_module =
253259
List.fold_left impl_only ~init:Module_name.Unique.Map.empty ~f:(fun acc module_ ->
254260
let module_name_unique = Module.obj_name module_ in
255261
let deps =
256262
let open Action_builder.O in
263+
let module_ = pp_map module_ in
257264
let+ deps =
258265
Dep_rules.read_immediate_deps_of module_ ~modules ~obj_dir ~ml_kind:Impl
259266
in
@@ -276,10 +283,8 @@ let obj_dir_for_dep_rules dir =
276283
let instantiate ~sctx lib =
277284
let ctx = Super_context.context sctx in
278285
let build_dir = Context.build_dir ctx in
279-
let* { Lib_config.ext_lib; _ } =
280-
let+ ocaml = ctx |> Context.ocaml in
281-
ocaml.lib_config
282-
in
286+
let* ocaml = Context.ocaml ctx in
287+
let ext_lib = ocaml.lib_config.ext_lib in
283288
let lib_info = Lib.info lib in
284289
let modules_obj_dir = Lib_info.obj_dir lib_info in
285290
let* deps_obj_dir, modules =
@@ -295,7 +300,14 @@ let instantiate ~sctx lib =
295300
modules_obj_dir, Modules.With_vlib.modules modules
296301
in
297302
let impl_only = Modules.With_vlib.impl_only modules in
298-
let dep_graph = dep_graph ~obj_dir:deps_obj_dir ~modules impl_only in
303+
let dep_graph =
304+
dep_graph
305+
~ocaml_version:ocaml.version
306+
~preprocess:(Lib_info.preprocess lib_info)
307+
~obj_dir:deps_obj_dir
308+
~modules
309+
impl_only
310+
in
299311
let* requires =
300312
Lib.closure ~linking:true [ lib ]
301313
|> Resolve.Memo.map
Lines changed: 153 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,153 @@
1+
Testing the instantiation of parameterised inline tests.
2+
3+
$ cat >> dune-project <<EOF
4+
> (lang dune 3.20)
5+
> (using oxcaml 0.1)
6+
> EOF
7+
8+
We first define a parameter signature:
9+
10+
$ mkdir param
11+
$ echo 'val param : string' > param/param.mli
12+
$ cat > param/dune <<EOF
13+
> (library_parameter (name param))
14+
> EOF
15+
16+
Then a parameterised library, which uses inline tests:
17+
18+
$ mkdir lib
19+
$ cat > lib/lib.ml <<EOF
20+
> let param = Param.param
21+
> let%test _ = Param.param = "impl"
22+
> EOF
23+
$ cat > lib/dune <<EOF
24+
> (library
25+
> (name lib)
26+
> (parameters param)
27+
> (inline_tests)
28+
> (preprocess (pps ppx_inline_test)))
29+
> EOF
30+
31+
Running the test fails, because we did not specify an implementation for the
32+
parameter:
33+
34+
$ dune runtest
35+
File "lib/dune", lines 1-5, characters 0-97:
36+
1 | (library
37+
2 | (name lib)
38+
3 | (parameters param)
39+
4 | (inline_tests)
40+
5 | (preprocess (pps ppx_inline_test)))
41+
Error: Parameter "param" is missing.
42+
-> required by
43+
_build/default/lib/.lib.inline-tests/.t.eobjs/native/dune__exe__Main.cmx
44+
-> required by _build/default/lib/.lib.inline-tests/inline-test-runner.exe
45+
-> required by _build/default/lib/.lib.inline-tests/partitions-best
46+
-> required by alias lib/runtest-lib in lib/dune:4
47+
-> required by alias lib/runtest in lib/dune:1
48+
Hint: Pass an argument implementing param to the dependency, or add
49+
(parameters param)
50+
[1]
51+
52+
We add an implementation:
53+
54+
$ mkdir impl
55+
$ echo 'let param = "impl"' > impl/impl.ml
56+
$ cat > impl/dune <<EOF
57+
> (library
58+
> (name impl)
59+
> (implements param))
60+
> EOF
61+
62+
And specify that `(inline_tests)` should use it with `(arguments impl)`:
63+
64+
$ cat > lib/dune <<EOF
65+
> (library
66+
> (name lib)
67+
> (parameters param)
68+
> (inline_tests (arguments impl))
69+
> (preprocess (pps ppx_inline_test)))
70+
> EOF
71+
72+
It should work:
73+
74+
$ dune runtest
75+
76+
We break the test to confirm that the inline test is running:
77+
78+
$ cat > lib/lib.ml <<EOF
79+
> let param = "lib(" ^ Param.param ^ ")"
80+
> let%test _ = Param.param = "not impl"
81+
> EOF
82+
83+
$ dune runtest
84+
File "lib/lib.ml", line 2, characters 0-37: <<Param.param = "not impl">> is false.
85+
86+
FAILED 1 / 1 tests
87+
[1]
88+
89+
Using another implementation:
90+
91+
$ mkdir not_impl
92+
$ echo 'let param = "not impl"' > not_impl/not_impl.ml
93+
$ cat > not_impl/dune <<EOF
94+
> (library
95+
> (name not_impl)
96+
> (implements param))
97+
> EOF
98+
99+
$ cat > lib/dune <<EOF
100+
> (library
101+
> (name lib)
102+
> (parameters param)
103+
> (inline_tests (arguments not_impl))
104+
> (preprocess (pps ppx_inline_test)))
105+
> EOF
106+
107+
This now works:
108+
109+
$ dune runtest
110+
111+
Adding another library which has a dependency on the parameterised `lib`:
112+
113+
$ mkdir lib2
114+
$ cat > lib2/lib2_util.ml <<EOF
115+
> let lib_param = Lib.param
116+
> EOF
117+
$ cat > lib2/lib2.ml <<EOF
118+
> let%test _ = Lib2_util.lib_param = "lib(impl)"
119+
> EOF
120+
$ cat > lib2/dune <<EOF
121+
> (library
122+
> (name lib2)
123+
> (parameters param)
124+
> (libraries lib)
125+
> (inline_tests (arguments impl))
126+
> (preprocess (pps ppx_inline_test)))
127+
> EOF
128+
129+
(Note that the library has two files, which triggers the inline_test
130+
preprocessor to generate `.pp.ml` files, which influences how the parameterised
131+
libraries can read the ocamldep outputs since the filenames are not the
132+
unpreprocessed ones.)
133+
134+
This should also work:
135+
136+
$ dune runtest
137+
138+
Using the wrong implementation should break the test again:
139+
140+
$ cat > lib2/dune <<EOF
141+
> (library
142+
> (name lib2)
143+
> (parameters param)
144+
> (libraries lib)
145+
> (inline_tests (arguments not_impl))
146+
> (preprocess (pps ppx_inline_test)))
147+
> EOF
148+
149+
$ dune runtest
150+
File "lib2/lib2.ml", line 1, characters 0-46: <<Lib2_util.lib_param = "lib(impl)">> is false.
151+
152+
FAILED 1 / 1 tests
153+
[1]

0 commit comments

Comments
 (0)