From 2d4e2b04bb1b0102480d2ba431133f21d9bf8674 Mon Sep 17 00:00:00 2001 From: Wojtek Mach Date: Fri, 4 Jul 2025 12:48:39 +0200 Subject: [PATCH 1/4] ex_unit: Add :capture_io tag --- lib/ex_unit/lib/ex_unit.ex | 13 +++++++- lib/ex_unit/lib/ex_unit/case.ex | 32 ++++++++++++++++++ lib/ex_unit/lib/ex_unit/cli_formatter.ex | 9 ++++++ lib/ex_unit/lib/ex_unit/runner.ex | 41 ++++++++++++++++++++---- lib/ex_unit/test/ex_unit_test.exs | 37 +++++++++++++++++++++ 5 files changed, 125 insertions(+), 7 deletions(-) diff --git a/lib/ex_unit/lib/ex_unit.ex b/lib/ex_unit/lib/ex_unit.ex index 4c1baecfef5..af1f2002afc 100644 --- a/lib/ex_unit/lib/ex_unit.ex +++ b/lib/ex_unit/lib/ex_unit.ex @@ -149,10 +149,21 @@ defmodule ExUnit do * `:time` - the duration in microseconds of the test's runtime * `:tags` - the test tags * `:logs` - the captured logs + * `:capture_io` - (since v1.20.0) the captured IO * `:parameters` - the test parameters """ - defstruct [:name, :case, :module, :state, time: 0, tags: %{}, logs: "", parameters: %{}] + defstruct [ + :name, + :case, + :module, + :state, + time: 0, + tags: %{}, + logs: "", + capture_io: "", + parameters: %{} + ] # TODO: Remove the `:case` field on v2.0 @type t :: %__MODULE__{ diff --git a/lib/ex_unit/lib/ex_unit/case.ex b/lib/ex_unit/lib/ex_unit/case.ex index 69103257b05..b48daed583a 100644 --- a/lib/ex_unit/lib/ex_unit/case.ex +++ b/lib/ex_unit/lib/ex_unit/case.ex @@ -183,6 +183,8 @@ defmodule ExUnit.Case do The following tags customize how tests behave: + * `:capture_io` - (since v1.20.0) see the "IO Capture" section below + * `:capture_log` - see the "Log Capture" section below * `:skip` - skips the test with the given reason @@ -258,6 +260,34 @@ defmodule ExUnit.Case do Keep in mind that all tests are included by default, so unless they are excluded first, the `include` option has no effect. + ## IO Capture + + ExUnit can optionally suppress printing of standard output messages generated + during a test. Messages generated while running a test are captured and + only if the test fails are they printed to aid with debugging. + + The captured IO is available in the test context under `:capture_io` + key and can be read using `StringIO.flush/1`: + + defmodule MyTest do + use ExUnit.Case, async: true + + @tag :capture_io + test "with io", %{capture_io: io} do + IO.puts("Hello, World!") + + assert StringIO.flush(io) == "Hello, World!\n" + end + end + + As with other tags, `:capture_io` can also be set as `@moduletag` and + `@describetag`. + + Since `setup_all` blocks don't belong to a specific test, standard output + messages generated in them (or between tests) are never captured. + + See also `ExUnit.CaptureIO`. + ## Log Capture ExUnit can optionally suppress printing of log messages that are generated @@ -278,6 +308,8 @@ defmodule ExUnit.Case do config :logger, :default_handler, false + See also `ExUnit.CaptureLog`. + ## Tmp Dir ExUnit automatically creates a temporary directory for tests tagged with diff --git a/lib/ex_unit/lib/ex_unit/cli_formatter.ex b/lib/ex_unit/lib/ex_unit/cli_formatter.ex index f4d2982c3d5..54524ecb4a0 100644 --- a/lib/ex_unit/lib/ex_unit/cli_formatter.ex +++ b/lib/ex_unit/lib/ex_unit/cli_formatter.ex @@ -132,6 +132,7 @@ defmodule ExUnit.CLIFormatter do ) print_failure(formatted, config) + print_capture_io(test.capture_io) print_logs(test.logs) test_counter = update_test_counter(config.test_counter, test) @@ -519,4 +520,12 @@ defmodule ExUnit.CLIFormatter do output = String.replace(output, "\n", indent) IO.puts([" The following output was logged:", indent | output]) end + + defp print_capture_io(""), do: nil + + defp print_capture_io(output) do + indent = "\n " + output = String.replace(output, "\n", indent) + IO.puts([" The following standard output was captured:", indent | output]) + end end diff --git a/lib/ex_unit/lib/ex_unit/runner.ex b/lib/ex_unit/lib/ex_unit/runner.ex index ff4c3b218fc..c39a38b1096 100644 --- a/lib/ex_unit/lib/ex_unit/runner.ex +++ b/lib/ex_unit/lib/ex_unit/runner.ex @@ -439,16 +439,19 @@ defmodule ExUnit.Runner do generate_test_seed(seed, test, rand_algorithm) context = context |> Map.merge(test.tags) |> Map.put(:test_pid, self()) capture_log = Map.get(context, :capture_log, capture_log) + capture_io = Map.get(context, :capture_io, false) {time, test} = :timer.tc( maybe_capture_log(capture_log, test, fn -> - context = maybe_create_tmp_dir(context, test) - - case exec_test_setup(test, context) do - {:ok, context} -> exec_test(test, context) - {:error, test} -> test - end + maybe_capture_io(capture_io, context, fn context -> + context = maybe_create_tmp_dir(context, test) + + case exec_test_setup(test, context) do + {:ok, context} -> exec_test(test, context) + {:error, test} -> test + end + end) end) ) @@ -482,6 +485,32 @@ defmodule ExUnit.Runner do end end + defp maybe_capture_io(true, context, fun) do + {:ok, gl} = StringIO.open("") + Process.group_leader(self(), gl) + context = put_in(context.capture_io, gl) + test = fun.(context) + put_in(test.capture_io, StringIO.flush(gl)) + end + + defp maybe_capture_io(false, context, fun) do + fun.(context) + end + + defp maybe_capture_io(other, _context, _fun) do + raise ArgumentError, """ + invalid value for @tag :capture_io, expected one of: + + @tag :capture_io + @tag capture_io: true + @tag capture_io: false + + got: + + @tag capture_io: #{inspect(other)} + """ + end + defp receive_test_reply(test, test_pid, test_ref, timeout) do receive do {^test_pid, :test_finished, test} -> diff --git a/lib/ex_unit/test/ex_unit_test.exs b/lib/ex_unit/test/ex_unit_test.exs index 336b0bd4b85..677eade461f 100644 --- a/lib/ex_unit/test/ex_unit_test.exs +++ b/lib/ex_unit/test/ex_unit_test.exs @@ -350,6 +350,43 @@ defmodule ExUnitTest do assert output =~ "\n1 test, 1 failure (3 excluded)\n" end + test "io capturing" do + defmodule IOCapturingTest do + use ExUnit.Case + + @tag :capture_io + test "one" do + # test successful, captured "one" isn't printed + IO.puts("one") + assert 1 == 1 + end + + @tag :capture_io + test "two" do + # test failed, captured "two" is printed + IO.puts("two") + assert 1 == 2 + end + + @tag :capture_io + test "three, four", %{capture_io: io} do + # io is flushed, captured "three" isn't printed + IO.puts("three") + assert StringIO.flush(io) == "three\n" + + # test failed, captured "four" is printed + IO.puts("four") + assert 1 == 2 + end + end + + output = capture_io(&ExUnit.run/0) + refute output =~ "one\n" + assert output =~ "two\n" + refute output =~ "three\n" + assert output =~ "four\n" + end + test "log capturing" do defmodule LogCapturingTest do use ExUnit.Case From 1449d71f841ce321e7b038dd5935f4b2ec162d13 Mon Sep 17 00:00:00 2001 From: Wojtek Mach Date: Fri, 4 Jul 2025 14:35:09 +0200 Subject: [PATCH 2/4] Change some tests to use `@tag :capture_io` --- lib/elixir/test/elixir/kernel/cli_test.exs | 33 +++-- .../test/mix/tasks/compile.erlang_test.exs | 133 ++++++++---------- 2 files changed, 78 insertions(+), 88 deletions(-) diff --git a/lib/elixir/test/elixir/kernel/cli_test.exs b/lib/elixir/test/elixir/kernel/cli_test.exs index 5f2e9f3edff..8b47e79df59 100644 --- a/lib/elixir/test/elixir/kernel/cli_test.exs +++ b/lib/elixir/test/elixir/kernel/cli_test.exs @@ -39,29 +39,28 @@ end defmodule Kernel.CLITest do use ExUnit.Case, async: true - import ExUnit.CaptureIO - defp run(argv) do {config, argv} = Kernel.CLI.parse_argv(Enum.map(argv, &String.to_charlist/1)) assert Kernel.CLI.process_commands(config) == [] Enum.map(argv, &IO.chardata_to_string/1) end - test "argv handling" do - assert capture_io(fn -> - assert run(["-e", "IO.puts :ok", "sample.exs", "-o", "1", "2"]) == - ["sample.exs", "-o", "1", "2"] - end) == "ok\n" - - assert capture_io(fn -> - assert run(["-e", "IO.puts :ok", "--", "sample.exs", "-o", "1", "2"]) == - ["sample.exs", "-o", "1", "2"] - end) == "ok\n" - - assert capture_io(fn -> - assert run(["-e", "", "--", "sample.exs", "-o", "1", "2"]) == - ["sample.exs", "-o", "1", "2"] - end) + @tag :capture_io + test "argv handling", %{capture_io: io} do + assert run(["-e", "IO.puts :ok1", "sample.exs", "-o", "1", "2"]) == + ["sample.exs", "-o", "1", "2"] + + assert StringIO.flush(io) == "ok1\n" + + assert run(["-e", "IO.puts :ok2", "--", "sample.exs", "-o", "1", "2"]) == + ["sample.exs", "-o", "1", "2"] + + assert StringIO.flush(io) == "ok2\n" + + assert run(["-e", "", "--", "sample.exs", "-o", "1", "2"]) == + ["sample.exs", "-o", "1", "2"] + + assert StringIO.flush(io) == "" end end diff --git a/lib/mix/test/mix/tasks/compile.erlang_test.exs b/lib/mix/test/mix/tasks/compile.erlang_test.exs index 2cc13d301a5..f938b84d130 100644 --- a/lib/mix/test/mix/tasks/compile.erlang_test.exs +++ b/lib/mix/test/mix/tasks/compile.erlang_test.exs @@ -6,7 +6,6 @@ Code.require_file("../../test_helper.exs", __DIR__) defmodule Mix.Tasks.Compile.ErlangTest do use MixTest.Case - import ExUnit.CaptureIO defmacro position(line, column), do: {line, column} @@ -18,12 +17,11 @@ defmodule Mix.Tasks.Compile.ErlangTest do end @tag erlc_options: [{:d, ~c"foo", ~c"bar"}] + @tag :capture_io test "raises on invalid erlc_options" do in_fixture("compile_erlang", fn -> assert_raise Mix.Error, ~r/Compiling Erlang file ".*" failed/, fn -> - capture_io(fn -> - Mix.Tasks.Compile.Erlang.run([]) - end) + Mix.Tasks.Compile.Erlang.run([]) end end) end @@ -84,6 +82,7 @@ defmodule Mix.Tasks.Compile.ErlangTest do end) end + @tag :capture_io test "continues even if one file fails to compile" do in_fixture("compile_erlang", fn -> file = Path.absname("src/zzz.erl") @@ -94,24 +93,23 @@ defmodule Mix.Tasks.Compile.ErlangTest do def zzz(), do: b """) - capture_io(fn -> - assert {:error, [diagnostic]} = Mix.Tasks.Compile.Erlang.run([]) - - assert %Mix.Task.Compiler.Diagnostic{ - compiler_name: "erl_parse", - file: ^source, - source: ^source, - message: "syntax error before: zzz", - position: position(2, 5), - severity: :error - } = diagnostic - end) + assert {:error, [diagnostic]} = Mix.Tasks.Compile.Erlang.run([]) + + assert %Mix.Task.Compiler.Diagnostic{ + compiler_name: "erl_parse", + file: ^source, + source: ^source, + message: "syntax error before: zzz", + position: position(2, 5), + severity: :error + } = diagnostic assert File.regular?("_build/dev/lib/sample/ebin/b.beam") assert File.regular?("_build/dev/lib/sample/ebin/c.beam") end) end + @tag :capture_io test "saves warnings between builds" do in_fixture("compile_erlang", fn -> file = Path.absname("src/has_warning.erl") @@ -122,41 +120,40 @@ defmodule Mix.Tasks.Compile.ErlangTest do my_fn() -> ok. """) - capture_io(fn -> - assert {:ok, [diagnostic]} = Mix.Tasks.Compile.Erlang.run([]) - - assert %Mix.Task.Compiler.Diagnostic{ - file: ^source, - source: ^source, - compiler_name: "erl_lint", - message: "function my_fn/0 is unused", - position: position(2, 1), - severity: :warning - } = diagnostic - - capture_io(:stderr, fn -> - # Should return warning without recompiling file - assert {:noop, [^diagnostic]} = Mix.Tasks.Compile.Erlang.run(["--verbose"]) - refute_received {:mix_shell, :info, ["Compiled src/has_warning.erl"]} - - assert [^diagnostic] = Mix.Tasks.Compile.Erlang.diagnostics() - assert [^diagnostic] = Mix.Task.Compiler.diagnostics() - - # Should not return warning after changing file - File.write!(file, """ - -module(has_warning). - -export([my_fn/0]). - my_fn() -> ok. - """) - - ensure_touched(file) - assert {:ok, []} = Mix.Tasks.Compile.Erlang.run([]) - end) + assert {:ok, [diagnostic]} = Mix.Tasks.Compile.Erlang.run([]) + + assert %Mix.Task.Compiler.Diagnostic{ + file: ^source, + source: ^source, + compiler_name: "erl_lint", + message: "function my_fn/0 is unused", + position: position(2, 1), + severity: :warning + } = diagnostic + + ExUnit.CaptureIO.capture_io(:stderr, fn -> + # Should return warning without recompiling file + assert {:noop, [^diagnostic]} = Mix.Tasks.Compile.Erlang.run(["--verbose"]) + refute_received {:mix_shell, :info, ["Compiled src/has_warning.erl"]} + + assert [^diagnostic] = Mix.Tasks.Compile.Erlang.diagnostics() + assert [^diagnostic] = Mix.Task.Compiler.diagnostics() + + # Should not return warning after changing file + File.write!(file, """ + -module(has_warning). + -export([my_fn/0]). + my_fn() -> ok. + """) + + ensure_touched(file) + assert {:ok, []} = Mix.Tasks.Compile.Erlang.run([]) end) end) end - test "prints warnings from stale files with --all-warnings" do + @tag :capture_io + test "prints warnings from stale files with --all-warnings", %{capture_io: io} do in_fixture("compile_erlang", fn -> file = Path.absname("src/has_warning.erl") @@ -165,13 +162,14 @@ defmodule Mix.Tasks.Compile.ErlangTest do my_fn() -> ok. """) - capture_io(fn -> Mix.Tasks.Compile.Erlang.run([]) end) + Mix.Tasks.Compile.Erlang.run([]) + assert StringIO.flush(io) =~ "Warning: function my_fn/0 is unused" - assert capture_io(:stderr, fn -> + assert ExUnit.CaptureIO.capture_io(:stderr, fn -> assert {:noop, _} = Mix.Tasks.Compile.Erlang.run([]) end) =~ ~r"has_warning.erl:2:(1:)? warning: function my_fn/0 is unused\n" - assert capture_io(:stderr, fn -> + assert ExUnit.CaptureIO.capture_io(:stderr, fn -> assert {:noop, _} = Mix.Tasks.Compile.Erlang.run([]) end) =~ ~r"has_warning.erl:2:(1:)? warning: function my_fn/0 is unused\n" @@ -182,19 +180,14 @@ defmodule Mix.Tasks.Compile.ErlangTest do ensure_touched(file) - output = - capture_io(fn -> - Mix.Tasks.Compile.Erlang.run(["--all-warnings"]) - end) - - assert output == "" + Mix.Tasks.Compile.Erlang.run(["--all-warnings"]) + assert StringIO.flush(io) == "" end) end + @tag :capture_io test "returns syntax error from an Erlang file when --return-errors is set" do in_fixture("no_mixfile", fn -> - import ExUnit.CaptureIO - file = Path.absname("src/a.erl") source = deterministic_source(file) @@ -205,19 +198,17 @@ defmodule Mix.Tasks.Compile.ErlangTest do def b(), do: b """) - capture_io(fn -> - assert {:error, [diagnostic]} = - Mix.Tasks.Compile.Erlang.run(["--force", "--return-errors"]) - - assert %Mix.Task.Compiler.Diagnostic{ - compiler_name: "erl_parse", - file: ^source, - source: ^source, - message: "syntax error before: b", - position: position(2, 5), - severity: :error - } = diagnostic - end) + assert {:error, [diagnostic]} = + Mix.Tasks.Compile.Erlang.run(["--force", "--return-errors"]) + + assert %Mix.Task.Compiler.Diagnostic{ + compiler_name: "erl_parse", + file: ^source, + source: ^source, + message: "syntax error before: b", + position: position(2, 5), + severity: :error + } = diagnostic refute File.regular?("ebin/Elixir.A.beam") refute File.regular?("ebin/Elixir.B.beam") From b294ea711d3f44aa35fc091b02be1380b32f752b Mon Sep 17 00:00:00 2001 From: Wojtek Mach Date: Mon, 7 Jul 2025 11:32:35 +0200 Subject: [PATCH 3/4] Rename test.capture_io to .stdout --- lib/ex_unit/lib/ex_unit.ex | 7 ++++--- lib/ex_unit/lib/ex_unit/cli_formatter.ex | 6 +++--- lib/ex_unit/lib/ex_unit/runner.ex | 2 +- 3 files changed, 8 insertions(+), 7 deletions(-) diff --git a/lib/ex_unit/lib/ex_unit.ex b/lib/ex_unit/lib/ex_unit.ex index af1f2002afc..83206b683df 100644 --- a/lib/ex_unit/lib/ex_unit.ex +++ b/lib/ex_unit/lib/ex_unit.ex @@ -148,8 +148,9 @@ defmodule ExUnit do * `:state` - the finished test state (see `t:ExUnit.state/0`) * `:time` - the duration in microseconds of the test's runtime * `:tags` - the test tags - * `:logs` - the captured logs - * `:capture_io` - (since v1.20.0) the captured IO + * `:logs` - the captured logs (see ["Log Capture"](`ExUnit.Case#module-log-capture`)) + * `:stdout` - (since v1.20.0) the captured IO (see + ["IO Capture"](`ExUnit.Case#module-io-capture`)) * `:parameters` - the test parameters """ @@ -161,7 +162,7 @@ defmodule ExUnit do time: 0, tags: %{}, logs: "", - capture_io: "", + stdout: "", parameters: %{} ] diff --git a/lib/ex_unit/lib/ex_unit/cli_formatter.ex b/lib/ex_unit/lib/ex_unit/cli_formatter.ex index 54524ecb4a0..5cd69c657ae 100644 --- a/lib/ex_unit/lib/ex_unit/cli_formatter.ex +++ b/lib/ex_unit/lib/ex_unit/cli_formatter.ex @@ -132,7 +132,7 @@ defmodule ExUnit.CLIFormatter do ) print_failure(formatted, config) - print_capture_io(test.capture_io) + print_stdout(test.stdout) print_logs(test.logs) test_counter = update_test_counter(config.test_counter, test) @@ -521,9 +521,9 @@ defmodule ExUnit.CLIFormatter do IO.puts([" The following output was logged:", indent | output]) end - defp print_capture_io(""), do: nil + defp print_stdout(""), do: nil - defp print_capture_io(output) do + defp print_stdout(output) do indent = "\n " output = String.replace(output, "\n", indent) IO.puts([" The following standard output was captured:", indent | output]) diff --git a/lib/ex_unit/lib/ex_unit/runner.ex b/lib/ex_unit/lib/ex_unit/runner.ex index c39a38b1096..3ad80c9fb66 100644 --- a/lib/ex_unit/lib/ex_unit/runner.ex +++ b/lib/ex_unit/lib/ex_unit/runner.ex @@ -490,7 +490,7 @@ defmodule ExUnit.Runner do Process.group_leader(self(), gl) context = put_in(context.capture_io, gl) test = fun.(context) - put_in(test.capture_io, StringIO.flush(gl)) + put_in(test.stdout, StringIO.flush(gl)) end defp maybe_capture_io(false, context, fun) do From 7b4c802552c3fa5f87f6d4750d743b269b09589c Mon Sep 17 00:00:00 2001 From: Wojtek Mach Date: Mon, 7 Jul 2025 14:36:46 +0200 Subject: [PATCH 4/4] Fix docs --- lib/ex_unit/lib/ex_unit/case.ex | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/lib/ex_unit/lib/ex_unit/case.ex b/lib/ex_unit/lib/ex_unit/case.ex index b48daed583a..68d58b614d4 100644 --- a/lib/ex_unit/lib/ex_unit/case.ex +++ b/lib/ex_unit/lib/ex_unit/case.ex @@ -276,7 +276,7 @@ defmodule ExUnit.Case do test "with io", %{capture_io: io} do IO.puts("Hello, World!") - assert StringIO.flush(io) == "Hello, World!\n" + assert StringIO.flush(io) == "Hello, World!\\n" end end