Skip to content

Commit 99be673

Browse files
committed
Taint failure manifest if requiring or compiling tests fail, closes #13728
1 parent b799e9e commit 99be673

File tree

5 files changed

+119
-80
lines changed

5 files changed

+119
-80
lines changed

lib/ex_unit/lib/ex_unit/failures_manifest.ex

+25-17
Original file line numberDiff line numberDiff line change
@@ -8,20 +8,6 @@ defmodule ExUnit.FailuresManifest do
88
@spec new() :: t
99
def new, do: %{}
1010

11-
@spec files_with_failures(t) :: MapSet.t(Path.t())
12-
def files_with_failures(%{} = manifest) do
13-
manifest
14-
|> Map.values()
15-
|> MapSet.new()
16-
end
17-
18-
@spec failed_test_ids(t) :: MapSet.t(ExUnit.test_id())
19-
def failed_test_ids(%{} = manifest) do
20-
manifest
21-
|> Map.keys()
22-
|> MapSet.new()
23-
end
24-
2511
@spec put_test(t, ExUnit.Test.t()) :: t
2612
def put_test(%{} = manifest, %ExUnit.Test{state: {ignored_state, _}})
2713
when ignored_state in [:skipped, :excluded],
@@ -44,21 +30,43 @@ defmodule ExUnit.FailuresManifest do
4430
File.write!(file, binary)
4531
end
4632

33+
@spec fail_all!(Path.t()) :: :ok
34+
def fail_all!(file) when is_binary(file) do
35+
binary = :erlang.term_to_binary({@manifest_vsn, :all})
36+
Path.dirname(file) |> File.mkdir_p!()
37+
File.write!(file, binary)
38+
end
39+
4740
@spec read(Path.t()) :: t
4841
def read(file) when is_binary(file) do
4942
with {:ok, binary} <- File.read(file),
50-
{:ok, {@manifest_vsn, manifest}} when is_map(manifest) <- safe_binary_to_term(binary) do
43+
{:ok, {@manifest_vsn, %{} = manifest}} <- safe_binary_to_term(binary) do
5144
manifest
5245
else
5346
_ -> new()
5447
end
5548
end
5649

50+
@spec info(Path.t()) :: {MapSet.t(Path.t()), MapSet.t(ExUnit.test_id())} | :all
51+
def info(file) when is_binary(file) do
52+
with {:ok, binary} <- File.read(file),
53+
{:ok, {@manifest_vsn, manifest}} <- safe_binary_to_term(binary) do
54+
case manifest do
55+
:all ->
56+
:all
57+
58+
%{} ->
59+
{manifest |> Map.values() |> MapSet.new(), manifest |> Map.keys() |> MapSet.new()}
60+
end
61+
else
62+
_ -> {MapSet.new(), MapSet.new()}
63+
end
64+
end
65+
5766
defp safe_binary_to_term(binary) do
5867
{:ok, :erlang.binary_to_term(binary)}
5968
rescue
60-
ArgumentError ->
61-
:error
69+
ArgumentError -> :error
6270
end
6371

6472
defp prune_deleted_tests(manifest) do

lib/ex_unit/lib/ex_unit/filters.ex

+18-5
Original file line numberDiff line numberDiff line change
@@ -146,18 +146,31 @@ defmodule ExUnit.Filters do
146146
defp parse_kv(key, value), do: {key, value}
147147

148148
@doc """
149-
Returns a tuple containing useful information about test failures from the
150-
manifest. The tuple contains:
149+
Returns failure information from the manifest file.
150+
151+
It returns either `:all`, meaning all tests should be considered as stale,
152+
or a tuple containing:
151153
152154
* A set of files that contain tests that failed the last time they ran.
153155
The paths are absolute paths.
156+
154157
* A set of test IDs that failed the last time they ran
155158
156159
"""
157-
@spec failure_info(Path.t()) :: {MapSet.t(Path.t()), MapSet.t(ExUnit.test_id())}
160+
@spec failure_info(Path.t()) :: {MapSet.t(Path.t()), MapSet.t(ExUnit.test_id())} | :all
158161
def failure_info(manifest_file) do
159-
manifest = FailuresManifest.read(manifest_file)
160-
{FailuresManifest.files_with_failures(manifest), FailuresManifest.failed_test_ids(manifest)}
162+
FailuresManifest.info(manifest_file)
163+
end
164+
165+
@doc """
166+
Marks the whole suite as failed in the manifest.
167+
168+
This is useful when the test suite cannot be loaded
169+
and there is a desire to make all tests fail.
170+
"""
171+
@spec fail_all!(Path.t()) :: :ok
172+
def fail_all!(manifest_file) do
173+
FailuresManifest.fail_all!(manifest_file)
161174
end
162175

163176
@doc """

lib/ex_unit/test/ex_unit/failures_manifest_test.exs

+27-19
Original file line numberDiff line numberDiff line change
@@ -10,29 +10,40 @@ defmodule ExUnit.FailuresManifestTest do
1010
@excluded {:excluded, "reason"}
1111
@failed {:failed, []}
1212
@invalid {:invalid, %ExUnit.TestModule{}}
13+
@manifest_path "example.manifest"
1314

14-
describe "files_with_failures/1" do
15-
test "returns the set of files with failures" do
15+
describe "info/1" do
16+
@tag :tmp_dir
17+
test "returns the sets of files and test IDs with failures", context do
1618
manifest =
1719
new()
18-
|> put_test(new_test(@failed, "file_1"))
19-
|> put_test(new_test(@failed, "file_2"))
20-
|> put_test(new_test(@passed, "file_3"))
21-
|> put_test(new_test(@failed, "file_1"))
20+
|> put_test(failed_1 = new_test(@failed, context))
21+
|> put_test(failed_2 = new_test(@failed, context))
22+
|> put_test(new_test(@passed, context))
23+
|> put_test(invalid_1 = new_test(@invalid, context))
24+
25+
File.cd!(context.tmp_dir, fn ->
26+
write!(manifest, @manifest_path)
2227

23-
assert files_with_failures(manifest) == MapSet.new(["file_1", "file_2"])
28+
assert info(@manifest_path) ==
29+
{MapSet.new([context.file]),
30+
MapSet.new([test_id(failed_1), test_id(failed_2), test_id(invalid_1)])}
31+
end)
2432
end
25-
end
2633

27-
describe "failed_test_ids/1" do
28-
test "returns the set of failed test IDs" do
29-
manifest =
30-
new()
31-
|> put_test(failed_1 = new_test(@failed))
32-
|> put_test(__passed = new_test(@passed))
33-
|> put_test(failed_2 = new_test(@invalid))
34+
@tag :tmp_dir
35+
test "returns all when the whole suite should be considered as failed", context do
36+
File.cd!(context.tmp_dir, fn ->
37+
fail_all!(@manifest_path)
38+
assert info(@manifest_path) == :all
39+
end)
40+
end
3441

35-
assert failed_test_ids(manifest) == MapSet.new([test_id(failed_1), test_id(failed_2)])
42+
@tag :tmp_dir
43+
test "returns no information when loading a file that does not exit", context do
44+
path = Path.join(context.tmp_dir, "missing.manifest")
45+
refute File.exists?(path)
46+
assert info(path) == {MapSet.new(), MapSet.new()}
3647
end
3748
end
3849

@@ -93,8 +104,6 @@ defmodule ExUnit.FailuresManifestTest do
93104
end
94105
end
95106

96-
@manifest_path "example.manifest"
97-
98107
describe "write!/2" do
99108
@tag :tmp_dir
100109
test "stores a manifest that can later be read with read/1", context do
@@ -172,7 +181,6 @@ defmodule ExUnit.FailuresManifestTest do
172181
assert write!(manifest, @manifest_path) == :ok
173182
assert {vsn, ^manifest} = @manifest_path |> File.read!() |> :erlang.binary_to_term()
174183
File.write!(@manifest_path, :erlang.term_to_binary({vsn + 1, manifest}))
175-
176184
assert read(@manifest_path) == new()
177185
end)
178186
end

lib/mix/lib/mix/tasks/test.ex

+33-25
Original file line numberDiff line numberDiff line change
@@ -473,6 +473,7 @@ defmodule Mix.Tasks.Test do
473473
@impl true
474474
def run(args) do
475475
{opts, files} = OptionParser.parse!(args, strict: @switches, aliases: [b: :breakpoints])
476+
opts = put_manifest_file(opts)
476477

477478
if not Mix.Task.recursing?() do
478479
do_run(opts, args, files)
@@ -591,30 +592,31 @@ defmodule Mix.Tasks.Test do
591592
{ex_unit_opts, allowed_files} = process_ex_unit_opts(opts)
592593
ExUnit.configure(ex_unit_opts)
593594

595+
# Prepare and extract all files to require and run
594596
test_paths = project[:test_paths] || default_test_paths()
595-
Enum.each(test_paths, &require_test_helper(shell, &1))
596-
ExUnit.configure(merge_helper_opts(ex_unit_opts))
597-
598-
# Finally parse, require and load the files
599597
test_files = if files != [], do: parse_file_paths(files), else: test_paths
600598
test_pattern = project[:test_pattern] || "*_test.exs"
601599
warn_test_pattern = project[:warn_test_pattern] || "*_test.ex"
602-
603-
files_with_matched_path = Mix.Utils.extract_files(test_files, test_pattern)
600+
unfiltered_test_files = Mix.Utils.extract_files(test_files, test_pattern)
604601

605602
matched_test_files =
606-
files_with_matched_path
603+
unfiltered_test_files
607604
|> filter_to_allowed_files(allowed_files)
608605
|> filter_by_partition(shell, partitions)
609606

610-
display_warn_test_pattern(
611-
test_files,
612-
test_pattern,
613-
files_with_matched_path,
614-
warn_test_pattern
615-
)
616-
617-
case CT.require_and_run(matched_test_files, test_paths, test_elixirc_options, opts) do
607+
display_warn_test_pattern(test_files, test_pattern, unfiltered_test_files, warn_test_pattern)
608+
609+
try do
610+
Enum.each(test_paths, &require_test_helper(shell, &1))
611+
ExUnit.configure(merge_helper_opts(ex_unit_opts))
612+
CT.require_and_run(matched_test_files, test_paths, test_elixirc_options, opts)
613+
catch
614+
kind, reason ->
615+
# Also mark the whole suite as failed
616+
file = Keyword.fetch!(opts, :failures_manifest_path)
617+
ExUnit.Filters.fail_all!(file)
618+
:erlang.raise(kind, reason, __STACKTRACE__)
619+
else
618620
{:ok, %{excluded: excluded, failures: failures, total: total}} ->
619621
Mix.shell(shell)
620622
cover && cover.()
@@ -776,23 +778,29 @@ defmodule Mix.Tasks.Test do
776778

777779
@manifest_file_name ".mix_test_failures"
778780

779-
defp manifest_opts(opts) do
780-
opts =
781-
Keyword.put_new(
782-
opts,
783-
:failures_manifest_path,
784-
Path.join(Mix.Project.manifest_path(), @manifest_file_name)
785-
)
781+
defp put_manifest_file(opts) do
782+
Keyword.put_new_lazy(
783+
opts,
784+
:failures_manifest_path,
785+
fn -> Path.join(Mix.Project.manifest_path(), @manifest_file_name) end
786+
)
787+
end
786788

787-
manifest_file = Keyword.get(opts, :failures_manifest_path)
789+
defp manifest_opts(opts) do
790+
manifest_file = Keyword.fetch!(opts, :failures_manifest_path)
788791

789792
if opts[:failed] do
790793
if opts[:stale] do
791794
Mix.raise("Combining --failed and --stale is not supported.")
792795
end
793796

794-
{allowed_files, failed_ids} = ExUnit.Filters.failure_info(manifest_file)
795-
{Keyword.put(opts, :only_test_ids, failed_ids), allowed_files}
797+
case ExUnit.Filters.failure_info(manifest_file) do
798+
{allowed_files, failed_ids} ->
799+
{Keyword.put(opts, :only_test_ids, failed_ids), allowed_files}
800+
801+
:all ->
802+
{opts, nil}
803+
end
796804
else
797805
{opts, nil}
798806
end

lib/mix/test/mix/tasks/test_test.exs

+16-14
Original file line numberDiff line numberDiff line change
@@ -33,25 +33,14 @@ defmodule Mix.Tasks.TestTest do
3333
end
3434

3535
test "accepts custom :exit_status" do
36-
assert {:exit_status, 5} in ex_unit_opts(exit_status: 5)
36+
assert {:exit_status, 5} in ex_unit_opts(exit_status: 5, failures_manifest_path: "foo.bar")
3737
end
3838

3939
test "includes some default options" do
40-
assert ex_unit_opts([]) == [
40+
assert ex_unit_opts(failures_manifest_path: "foo.bar") == [
4141
autorun: false,
4242
exit_status: 2,
43-
failures_manifest_path:
44-
Path.join(Mix.Project.manifest_path(), ".mix_test_failures")
45-
]
46-
end
47-
48-
test "respect failures_manifest_path option" do
49-
custom_manifest_file = Path.join(Mix.Project.manifest_path(), ".mix_test_failures_custom")
50-
51-
assert ex_unit_opts(failures_manifest_path: custom_manifest_file) == [
52-
autorun: false,
53-
exit_status: 2,
54-
failures_manifest_path: custom_manifest_file
43+
failures_manifest_path: "foo.bar"
5544
]
5645
end
5746

@@ -62,6 +51,7 @@ defmodule Mix.Tasks.TestTest do
6251

6352
defp ex_unit_opts_from_given(passed) do
6453
passed
54+
|> Keyword.put(:failures_manifest_path, "foo.bar")
6555
|> ex_unit_opts()
6656
|> Keyword.drop([:failures_manifest_path, :autorun, :exit_status])
6757
end
@@ -268,6 +258,18 @@ defmodule Mix.Tasks.TestTest do
268258
after
269259
System.delete_env("PASS_FAILING_TESTS")
270260
end
261+
262+
test "marks the whole suite as failed on compilation error" do
263+
in_fixture("test_failed", fn ->
264+
File.write!("test/passing_and_failing_test_failed.exs", "raise ~s(oops)")
265+
266+
output = mix(["test"])
267+
assert output =~ "** (RuntimeError) oops"
268+
269+
output = mix(["test", "--failed"])
270+
assert output =~ "** (RuntimeError) oops"
271+
end)
272+
end
271273
end
272274

273275
describe "--listen-on-stdin" do

0 commit comments

Comments
 (0)