Skip to content

Commit

Permalink
feature: add aliases for inline tests
Browse files Browse the repository at this point in the history
For a given library with inlines tests, we add an alias with the name of
the library for running those tests.

Further work on separating out the partition actions would allow us to
have an alias for each partition.

For now, this allows us to run inline tests with the runtest command.

Signed-off-by: Ali Caglayan <[email protected]>

<!-- ps-id: 8fef343c-46e6-4486-aa50-d31b6cfe1d46 -->
  • Loading branch information
Alizter committed Nov 10, 2024
1 parent f7af2d0 commit b5d5d4f
Show file tree
Hide file tree
Showing 2 changed files with 45 additions and 29 deletions.
66 changes: 37 additions & 29 deletions src/dune_rules/inline_tests.ml
Original file line number Diff line number Diff line change
Expand Up @@ -343,35 +343,43 @@ include Sub_system.Register_end_point (struct
| Native | Best | Byte -> Memo.return Alias0.runtest
| Jsoo mode -> Jsoo_rules.js_of_ocaml_runtest_alias ~dir ~mode
in
Super_context.add_alias_action
sctx
~dir
~loc:info.loc
(Alias.make ~dir runtest_alias)
(let open Action_builder.O in
let+ actions =
let* partitions_flags =
match partitions_flags with
| None -> Action_builder.return [ None ]
| Some _ ->
let+ partitions = Action_builder.lines_of (Path.build partition_file) in
List.map ~f:(fun x -> Some x) partitions
in
List.map partitions_flags ~f:(fun p -> action mode (flags p))
|> Action_builder.all
and+ () = Action_builder.paths source_files in
match actions with
| [] -> Action.Full.empty
| _ :: _ ->
let run_tests = Action.concurrent actions in
let diffs =
List.map source_files ~f:(fun fn ->
Path.as_in_build_dir_exn fn
|> Path.Build.extend_basename ~suffix:".corrected"
|> Promote.Diff_action.diff ~optional:true fn)
|> Action.concurrent
in
Action.Full.make ~sandbox @@ Action.progn [ run_tests; diffs ]))
let aliases =
List.map
~f:(Alias.make ~dir)
[ runtest_alias; Alias.Name.of_string (Lib_name.Local.to_string lib_name) ]
in
Memo.parallel_iter aliases ~f:(fun alias ->
Super_context.add_alias_action
sctx
~dir
~loc:info.loc
alias
(let open Action_builder.O in
let+ actions =
let* partitions_flags =
match partitions_flags with
| None -> Action_builder.return [ None ]
| Some _ ->
let+ partitions =
Action_builder.lines_of (Path.build partition_file)
in
List.map ~f:(fun x -> Some x) partitions
in
List.map partitions_flags ~f:(fun p -> action mode (flags p))
|> Action_builder.all
and+ () = Action_builder.paths source_files in
match actions with
| [] -> Action.Full.empty
| _ :: _ ->
let run_tests = Action.concurrent actions in
let diffs =
List.map source_files ~f:(fun fn ->
Path.as_in_build_dir_exn fn
|> Path.Build.extend_basename ~suffix:".corrected"
|> Promote.Diff_action.diff ~optional:true fn)
|> Action.concurrent
in
Action.Full.make ~sandbox @@ Action.progn [ run_tests; diffs ])))
;;

let gen_rules c ~(info : Info.t) ~backends =
Expand Down
8 changes: 8 additions & 0 deletions test/blackbox-tests/test-cases/inline_tests/simple.t
Original file line number Diff line number Diff line change
Expand Up @@ -30,6 +30,14 @@
Fatal error: exception File ".foo_simple.inline-tests/inline_test_runner_foo_simple.ml-gen", line 1, characters 40-46: Assertion failed
[1]

Inline tests also generate an alias
$ dune build @foo_simple
File "dune", line 9, characters 1-40:
9 | (inline_tests (backend backend_simple)))
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Fatal error: exception File ".foo_simple.inline-tests/inline_test_runner_foo_simple.ml-gen", line 1, characters 40-46: Assertion failed
[1]

The expected behavior for the following three tests is to output nothing: the tests are disabled or ignored.
$ env -u OCAMLRUNPARAM dune runtest --profile release

Expand Down

0 comments on commit b5d5d4f

Please sign in to comment.