Skip to content

Commit

Permalink
Merge pull request #10671 from vouillon/expect-test-deps
Browse files Browse the repository at this point in the history
Expect test fixes
  • Loading branch information
rgrinberg authored Jun 30, 2024
2 parents 24dab51 + 0850c49 commit 408970b
Show file tree
Hide file tree
Showing 11 changed files with 21 additions and 14 deletions.
1 change: 1 addition & 0 deletions doc/changes/10671.md
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
- Expect test fixes: support multiple modes and fix dependencies when there is a custom runner (#10671, @vouillon)
23 changes: 12 additions & 11 deletions src/dune_rules/test_rules.ml
Original file line number Diff line number Diff line change
@@ -1,14 +1,14 @@
open Import

let rules (t : Tests.t) ~sctx ~dir ~scope ~expander ~dir_contents =
let test_kind (loc, name) =
let test_kind (loc, name, ext) =
let files = Dir_contents.text_files dir_contents in
let expected_basename = name ^ ".expected" in
if Filename.Set.mem files expected_basename
then
`Expect
{ Diff.file1 = String_with_vars.make_text loc expected_basename
; file2 = String_with_vars.make_text loc (name ^ ".output")
; file2 = String_with_vars.make_text loc (name ^ ext ^ ".output")
; optional = false
; mode = Text
}
Expand Down Expand Up @@ -70,32 +70,33 @@ let rules (t : Tests.t) ~sctx ~dir ~scope ~expander ~dir_contents =
| `js -> Jsoo_rules.js_of_ocaml_runtest_alias ~dir
| `exe | `bc -> Memo.return Alias0.runtest
in
let deps =
match custom_runner with
| Some _ ->
Bindings.Unnamed (Dep_conf.File (String_with_vars.make_text loc test_exe))
:: t.deps
| None -> t.deps
in
let add_alias ~loc ~action ~locks =
(* CR-rgrinberg: why are we going through the stanza api? *)
let alias =
{ Alias_conf.name = runtest_alias
; locks
; package = t.package
; deps =
(match custom_runner with
| Some _ ->
Bindings.Unnamed
(Dep_conf.File (String_with_vars.make_text loc test_exe))
:: t.deps
| None -> t.deps)
; deps
; action = Some (loc, action)
; enabled_if = t.enabled_if
; loc
}
in
Simple_rules.alias sctx ~extra_bindings ~dir ~expander alias
in
match test_kind (loc, s) with
match test_kind (loc, s, ext) with
| `Regular -> add_alias ~loc ~action:run_action ~locks:[]
| `Expect diff ->
let rule =
{ Rule_conf.targets = Infer
; deps = t.deps
; deps
; action =
( loc
, Action_unexpanded.Redirect_out (Stdout, diff.file2, Normal, run_action)
Expand Down
1 change: 1 addition & 0 deletions test/blackbox-tests/test-cases/jsoo/tests.t/b.expected
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
b: ok
1 change: 0 additions & 1 deletion test/blackbox-tests/test-cases/jsoo/tests.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -2,4 +2,3 @@ tests stanza with jsoo

$ dune build @default @runtest-js
a: ok
b: ok
Original file line number Diff line number Diff line change
Expand Up @@ -23,4 +23,4 @@ This is visible when trying to build the `@all` alias. See #5950.

$ cp data.txt t.expected

$ dune build t.output
$ dune build t.exe.output
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
$ dune runtest
File "generated.expected", line 1, characters 0-0:
Error: Files _build/default/generated.expected and
_build/default/generated.output differ.
_build/default/generated.exe.output differ.
[1]
1 change: 1 addition & 0 deletions test/blackbox-tests/test-cases/tests-stanza/modes.t/dune
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
(test (name modes) (modes byte native))
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
(lang dune 3.0)
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
testing multiple modes
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
print_endline "testing multiple modes"
1 change: 1 addition & 0 deletions test/blackbox-tests/test-cases/tests-stanza/modes.t/run.t
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
$ dune runtest

0 comments on commit 408970b

Please sign in to comment.