Skip to content

Commit

Permalink
[3.11] Backport #8849 (inline tests) (#8893)
Browse files Browse the repository at this point in the history
* Parallel inline_tests: expose bug with empty partition list

Signed-off-by: Hugo Heuzard <[email protected]>

* Parallel inline_tests: Fix when partition list is empty

Signed-off-by: Hugo Heuzard <[email protected]>

---------

Signed-off-by: Hugo Heuzard <[email protected]>
Co-authored-by: Hugo Heuzard <[email protected]>
  • Loading branch information
emillon and hhugo authored Oct 9, 2023
1 parent a760f8c commit 4b30514
Show file tree
Hide file tree
Showing 7 changed files with 42 additions and 16 deletions.
1 change: 1 addition & 0 deletions doc/changes/8848.md
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
- Fix inline_tests when the partition list is empty (#8848, @hhugo)
21 changes: 12 additions & 9 deletions src/dune_rules/inline_tests.ml
Original file line number Diff line number Diff line change
Expand Up @@ -347,15 +347,18 @@ include Sub_system.Register_end_point (struct
List.map partitions_flags ~f:(fun p -> action mode (flags p))
|> Action_builder.all
and+ () = Action_builder.paths source_files in
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"
|> Action.diff ~optional:true fn)
|> Action.concurrent
in
Action.Full.make ~sandbox @@ Action.progn [ run_tests; diffs ]))
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"
|> 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
Original file line number Diff line number Diff line change
Expand Up @@ -30,14 +30,14 @@ let register ~libname ~partition name run =

let run () =
Arg.parse speclist anon_fun usage_msg;
if !libname = "" then failwith "Should specify libname";
if !list_partitions then
let partitions =
List.fold_left
(fun acc t -> StringSet.add t.partition acc)
(fun acc t -> if !libname = t.libname then StringSet.add t.partition acc else acc)
StringSet.empty !tests
in
StringSet.iter print_endline partitions
else if !libname = "" then failwith "Should specify libname";
StringSet.iter print_endline partitions;
List.iter
(fun t ->
if t.libname = !libname && t.partition = !partition then (
Expand Down
11 changes: 11 additions & 0 deletions test/blackbox-tests/test-cases/inline_tests/parallel.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -27,3 +27,14 @@ See that we indeed have 3 partitions
p1
p2
p3


$ dune build --display short @test3/runtest
ocamlc test3/.test_lib3.inline-tests/.test_lib3.inline-tests.eobjs/byte/dune__exe__Inline_test_runner_test_lib3.{cmi,cmo,cmt}
ocamlopt test3/.test_lib3.inline-tests/.test_lib3.inline-tests.eobjs/native/dune__exe__Inline_test_runner_test_lib3.{cmx,o}
ocamlopt test3/.test_lib3.inline-tests/inline_test_runner_test_lib3.exe
inline_test_runner_test_lib3 test3/.test_lib3.inline-tests/partitions-best

See that we have no partition.

$ cat _build/default/test3/.test_lib3.inline-tests/partitions-best
Original file line number Diff line number Diff line change
@@ -1,19 +1,23 @@
let () =
Fake_backend_runner.register ~libname:"test_lib" ~partition:"p1" "first test"
Fake_backend_runner.register ~libname:"test_lib2" ~partition:"p1" "first test"
(fun () -> assert true)

let () =
Fake_backend_runner.register ~libname:"test_lib" ~partition:"p1" "second test"
Fake_backend_runner.register ~libname:"test_lib2" ~partition:"p1" "second test"
(fun () -> () )

let () =
Fake_backend_runner.register ~libname:"test_lib" ~partition:"p2" "first test"
Fake_backend_runner.register ~libname:"test_lib2" ~partition:"p2" "first test"
(fun () -> ())

let () =
Fake_backend_runner.register ~libname:"test_lib" ~partition:"p3" "first test"
Fake_backend_runner.register ~libname:"test_lib2" ~partition:"p3" "first test"
(fun () -> failwith "This failure is expected")

let () =
Fake_backend_runner.register ~libname:"other_lib" ~partition:"p1"
"second test" (fun () -> assert false)

let () =
Fake_backend_runner.register ~libname:"other_lib" ~partition:"pn"
"second test" (fun () -> assert false)
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
(library
(name test_lib3)
(libraries fake_backend_runner)
(inline_tests (backend fake_backend_2)))
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
let () =
Fake_backend_runner.register ~libname:"other_lib" ~partition:"p1"
"second test" (fun () -> assert false)

0 comments on commit 4b30514

Please sign in to comment.