File 4281-eunit-exact_execution-option.patch of Package erlang

From c194380712236c301188f0b401352f14c608c145 Mon Sep 17 00:00:00 2001
From: Jakub Witczak <kuba@erlang.org>
Date: Fri, 2 Sep 2022 09:37:30 +0200
Subject: [PATCH] eunit: exact_execution option

- option for avoiding automatic execution of a module with "_tests" suffix
---
 lib/eunit/src/eunit.erl                |   5 +
 lib/eunit/src/eunit_data.erl           | 267 +++++++++++++------------
 lib/eunit/src/eunit_internal.hrl       |   1 +
 lib/eunit/src/eunit_proc.erl           |  12 +-
 lib/eunit/src/eunit_server.erl         |   3 +-
 lib/eunit/test/Makefile                |   1 +
 lib/eunit/test/eunit_SUITE.erl         |  39 +++-
 lib/eunit/test/eunit_test_listener.erl |  85 ++++++++
 8 files changed, 268 insertions(+), 145 deletions(-)
 create mode 100644 lib/eunit/test/eunit_test_listener.erl

diff --git a/lib/eunit/src/eunit.erl b/lib/eunit/src/eunit.erl
index 0238885708..f30c238366 100644
--- a/lib/eunit/src/eunit.erl
+++ b/lib/eunit/src/eunit.erl
@@ -135,6 +135,11 @@ test(Tests) ->
 %% <dd>Displays more details about the running tests.</dd>
 %% <dt>`print_depth'</dt>
 %% <dd>Maximum depth to which terms are printed in case of error.</dd>
+%% <dt>`exact_execution'</dt>
+%% <dd>If this boolean flag is set to `true' framework will
+%% not automatically execute tests found in related module suffixed with "_tests".
+%% This behaviour might be unwanted if execution of modules found in a folder
+%% is ordered while it contains both source and test modules.</dd>
 %% </dl>
 %%
 %% Options in the environment variable EUNIT are also included last in
diff --git a/lib/eunit/src/eunit_data.erl b/lib/eunit/src/eunit_data.erl
index e36f6cad13..dfc6662a96 100644
--- a/lib/eunit/src/eunit_data.erl
+++ b/lib/eunit/src/eunit_data.erl
@@ -31,10 +31,8 @@
 
 -include_lib("kernel/include/file.hrl").
 
--export([iter_init/2, iter_next/1, iter_prev/1, iter_id/1,
-	 enter_context/3, get_module_tests/1]).
-
--import(lists, [foldr/3]).
+-export([iter_init/3, iter_next/1, iter_prev/1, iter_id/1,
+	 enter_context/3, get_module_tests/2]).
 
 -define(TICKS_PER_SECOND, 1000).
 
@@ -115,14 +113,15 @@
 	{prev = [],
 	 next = [],
 	 tests = [],
+         options,
 	 pos = 0,
 	 parent = []}).
 
 %% @spec (tests(), [integer()]) -> testIterator()
 %% @type testIterator()
 
-iter_init(Tests, ParentID) ->
-    #iter{tests = Tests, parent = lists:reverse(ParentID)}.
+iter_init(Tests, ParentID, Options) ->
+    #iter{tests = Tests, parent = lists:reverse(ParentID), options = Options}.
 
 %% @spec (testIterator()) -> [integer()]
 
@@ -131,8 +130,8 @@ iter_id(#iter{pos = N, parent = Ns}) ->
 
 %% @spec (testIterator()) -> none | {testItem(), testIterator()}
 
-iter_next(I = #iter{next = []}) ->
-    case next(I#iter.tests) of
+iter_next(I = #iter{next = [], options = Options}) ->
+    case next(I#iter.tests, Options) of
 	{T, Tests} ->
 	    {T, I#iter{prev = [T | I#iter.prev],
 		       tests = Tests,
@@ -169,12 +168,12 @@ iter_prev(#iter{prev = [T | Ts]} = I) ->
 %%       | {file_read_error, {Reason::atom(), Message::string(),
 %%                            fileName()}}
 
-next(Tests) ->
+next(Tests, Options) ->
     case eunit_lib:dlist_next(Tests) of
 	[T | Ts] ->
-	    case parse(T) of
+	    case parse(T, Options) of
 		{data, T1} ->
-		    next([T1 | Ts]);
+		    next([T1 | Ts], Options);
 		T1 ->
 		    {T1, Ts}
 	    end;
@@ -188,15 +187,15 @@ next(Tests) ->
 %% this returns either a #test{} or #group{} record, or {data, T} to
 %% signal that T has been substituted for the given representation
 
-parse({foreach, S, Fs}) when is_function(S), is_list(Fs) ->
-    parse({foreach, S, fun ok/1, Fs});
-parse({foreach, S, C, Fs})
+parse({foreach, S, Fs}, Options) when is_function(S), is_list(Fs) ->
+    parse({foreach, S, fun ok/1, Fs}, Options);
+parse({foreach, S, C, Fs}, Options)
   when is_function(S), is_function(C), is_list(Fs) ->
-    parse({foreach, ?DEFAULT_SETUP_PROCESS, S, C, Fs});
-parse({foreach, P, S, Fs})
+    parse({foreach, ?DEFAULT_SETUP_PROCESS, S, C, Fs}, Options);
+parse({foreach, P, S, Fs}, Options)
   when is_function(S), is_list(Fs) ->
-    parse({foreach, P, S, fun ok/1, Fs});
-parse({foreach, P, S, C, Fs} = T)
+    parse({foreach, P, S, fun ok/1, Fs}, Options);
+parse({foreach, P, S, C, Fs} = T, _Options)
   when is_function(S), is_function(C), is_list(Fs) ->
     check_arity(S, 0, T),
     check_arity(C, 1, T),
@@ -206,15 +205,15 @@ parse({foreach, P, S, C, Fs} = T)
 	[] ->
 	    {data, []}
     end;
-parse({foreachx, S1, Ps}) when is_function(S1), is_list(Ps) ->
-    parse({foreachx, S1, fun ok/2, Ps});
-parse({foreachx, S1, C1, Ps})
+parse({foreachx, S1, Ps}, Options) when is_function(S1), is_list(Ps) ->
+    parse({foreachx, S1, fun ok/2, Ps}, Options);
+parse({foreachx, S1, C1, Ps}, Options)
   when is_function(S1), is_function(C1), is_list(Ps) ->
-    parse({foreachx, ?DEFAULT_SETUP_PROCESS, S1, C1, Ps});
-parse({foreachx, P, S1, Ps})
+    parse({foreachx, ?DEFAULT_SETUP_PROCESS, S1, C1, Ps}, Options);
+parse({foreachx, P, S1, Ps}, Options)
   when is_function(S1), is_list(Ps) ->
-    parse({foreachx, P, S1, fun ok/2, Ps});
-parse({foreachx, P, S1, C1, Ps} = T) 
+    parse({foreachx, P, S1, fun ok/2, Ps}, Options);
+parse({foreachx, P, S1, C1, Ps} = T, _Options)
   when is_function(S1), is_function(C1), is_list(Ps) ->
     check_arity(S1, 1, T),
     check_arity(C1, 2, T),
@@ -230,12 +229,12 @@ parse({foreachx, P, S1, C1, Ps} = T)
 	[] ->
 	    {data, []}
     end;
-parse({generator, F}) when is_function(F) ->
+parse({generator, F}, Options) when is_function(F) ->
     {module, M} = erlang:fun_info(F, module),
     {name, N} = erlang:fun_info(F, name),
     {arity, A} = erlang:fun_info(F, arity),
-    parse({generator, F, {M,N,A}});
-parse({generator, F, {M,N,A}} = T)
+    parse({generator, F, {M,N,A}}, Options);
+parse({generator, F, {M,N,A}} = T, _Options)
   when is_function(F), is_atom(M), is_atom(N), is_integer(A) ->
     check_arity(F, 0, T),
     %% use run_testfun/1 to handle wrapper exceptions
@@ -249,38 +248,38 @@ parse({generator, F, {M,N,A}} = T)
 	{error, {Class, Reason, Trace}} ->
 	    throw({generator_failed, {{M,N,A}, {Class, Reason, Trace}}})
     end;
-parse({generator, M, F}) when is_atom(M), is_atom(F) ->
-    parse({generator, eunit_test:mf_wrapper(M, F), {M,F,0}});
-parse({inorder, T}) ->
-    group(#group{tests = T, order = inorder});
-parse({inparallel, T}) ->
-    parse({inparallel, 0, T});
-parse({inparallel, N, T}) when is_integer(N), N >= 0 ->
-    group(#group{tests = T, order = {inparallel, N}});
-parse({timeout, N, T}) when is_number(N), N >= 0 ->
-    group(#group{tests = T, timeout = round(N * ?TICKS_PER_SECOND)});
-parse({spawn, T}) ->
-    group(#group{tests = T, spawn = local});
-parse({spawn, N, T}) when is_atom(N) ->
-    group(#group{tests = T, spawn = {remote, N}});
-parse({setup, S, I}) when is_function(S); is_list(S) ->
-    parse({setup, ?DEFAULT_SETUP_PROCESS, S, I});
-parse({setup, S, C, I}) when is_function(S), is_function(C) ->
-    parse({setup, ?DEFAULT_SETUP_PROCESS, S, C, I});
-parse({setup, P, S, I}) when is_function(S) ->
-    parse({setup, P, S, fun ok/1, I});
-parse({setup, P, L, I} = T) when is_list(L) ->
+parse({generator, M, F}, Options) when is_atom(M), is_atom(F) ->
+    parse({generator, eunit_test:mf_wrapper(M, F), {M,F,0}}, Options);
+parse({inorder, T}, Options) ->
+    group(#group{tests = T, options = Options, order = inorder});
+parse({inparallel, T}, Options) ->
+    parse({inparallel, 0, T}, Options);
+parse({inparallel, N, T}, Options) when is_integer(N), N >= 0 ->
+    group(#group{tests = T, options = Options, order = {inparallel, N}});
+parse({timeout, N, T}, Options) when is_number(N), N >= 0 ->
+    group(#group{tests = T, options = Options, timeout = round(N * ?TICKS_PER_SECOND)});
+parse({spawn, T}, Options) ->
+    group(#group{tests = T, options = Options, spawn = local});
+parse({spawn, N, T}, Options) when is_atom(N) ->
+    group(#group{tests = T, options = Options, spawn = {remote, N}});
+parse({setup, S, I}, Options) when is_function(S); is_list(S) ->
+    parse({setup, ?DEFAULT_SETUP_PROCESS, S, I}, Options);
+parse({setup, S, C, I}, Options) when is_function(S), is_function(C) ->
+    parse({setup, ?DEFAULT_SETUP_PROCESS, S, C, I}, Options);
+parse({setup, P, S, I}, Options) when is_function(S) ->
+    parse({setup, P, S, fun ok/1, I}, Options);
+parse({setup, P, L, I} = T, Options) when is_list(L) ->
     check_setup_list(L, T),
     {S, C} = eunit_test:multi_setup(L),
-    parse({setup, P, S, C, I});
-parse({setup, P, S, C, I} = T)
+    parse({setup, P, S, C, I}, Options);
+parse({setup, P, S, C, I} = T, Options)
   when is_function(S), is_function(C), is_function(I) ->
     check_arity(S, 0, T),
     check_arity(C, 1, T),
     case erlang:fun_info(I, arity) of
 	{arity, 0} ->
 	    %% if I is nullary, it is a plain test
-	    parse({setup, S, C, fun (_) -> I end});
+	    parse({setup, S, C, fun (_) -> I end}, Options);
 	_ ->
 	    %% otherwise, I must be an instantiator function
 	    check_arity(I, 1, T),
@@ -294,13 +293,13 @@ parse({setup, P, S, C, I} = T)
 			 context = #context{setup = S, cleanup = C,
 					    process = P}})
     end;
-parse({setup, P, S, C, {with, As}}) when is_list(As) ->
-    parse({setup, P, S, C, fun (X) -> {with, X, As} end});
-parse({setup, P, S, C, T}) when is_function(S), is_function(C) ->
-    parse({setup, P, S, C, fun (_) -> T end});
-parse({node, N, T}) when is_atom(N) ->
-    parse({node, N, "", T});
-parse({node, N, A, T1}=T) when is_atom(N) ->
+parse({setup, P, S, C, {with, As}}, Options) when is_list(As) ->
+    parse({setup, P, S, C, fun (X) -> {with, X, As} end}, Options);
+parse({setup, P, S, C, T}, Options) when is_function(S), is_function(C) ->
+    parse({setup, P, S, C, fun (_) -> T end}, Options);
+parse({node, N, T}, Options) when is_atom(N) ->
+    parse({node, N, "", T}, Options);
+parse({node, N, A, T1}=T, Options) when is_atom(N) ->
     case eunit_lib:is_string(A) of
 	true ->
 	    %% TODO: better stack traces for internal funs like these
@@ -336,14 +335,14 @@ parse({node, N, A, T1}=T) when is_atom(N) ->
 			       false -> ok
 			   end
 		   end,
-		   T1});
+		   T1}, Options);
 	false ->
 	    bad_test(T)
     end;
-parse({module, M}) when is_atom(M) ->
-    {data, {"module '" ++ atom_to_list(M) ++ "'", get_module_tests(M)}};
-parse({application, A}) when is_atom(A) ->
-    try parse({file, atom_to_list(A)++".app"})
+parse({module, M}, Options) when is_atom(M) ->
+    {data, {"module '" ++ atom_to_list(M) ++ "'", get_module_tests(M, Options)}};
+parse({application, A}, Options) when is_atom(A) ->
+    try parse({file, atom_to_list(A)++".app"}, Options)
     catch
 	{file_read_error,{enoent,_,_}} ->
 	    case code:lib_dir(A) of
@@ -352,15 +351,15 @@ parse({application, A}) when is_atom(A) ->
 		    BinDir = filename:join(Dir, "ebin"),
 		    case file:read_file_info(BinDir) of
 			{ok, #file_info{type=directory}} ->
-			    parse({dir, BinDir});
+			    parse({dir, BinDir}, Options);
 			_ ->
-			    parse({dir, Dir})
+			    parse({dir, Dir}, Options)
 		    end;
 		_ ->
 		    throw({application_not_found, A})
 	    end
     end;
-parse({application, A, Info}=T) when is_atom(A) ->
+parse({application, A, Info}=T, _Options) when is_atom(A) ->
     case proplists:get_value(modules, Info) of
 	Ms when is_list(Ms) ->
 	    case [M || M <- Ms, not is_atom(M)] of
@@ -372,14 +371,14 @@ parse({application, A, Info}=T) when is_atom(A) ->
 	_ ->
 	    bad_test(T)
     end;
-parse({file, F} = T) when is_list(F) ->
+parse({file, F} = T, _Options) when is_list(F) ->
     case eunit_lib:is_string(F) of
 	true ->
 	    {data, {"file \"" ++ F ++ "\"", get_file_tests(F)}};
 	false ->
 	    bad_test(T)
     end;
-parse({dir, D}=T) when is_list(D) ->
+parse({dir, D}=T, _Options) when is_list(D) ->
     case eunit_lib:is_string(D) of
 	true ->
 	    {data, {"directory \"" ++ D ++ "\"",
@@ -387,7 +386,7 @@ parse({dir, D}=T) when is_list(D) ->
 	false ->
 	    bad_test(T)
     end;
-parse({with, X, As}=T) when is_list(As) ->
+parse({with, X, As}=T, _Options) when is_list(As) ->
     case As of
 	[A | As1] ->
 	    check_arity(A, 1, T),
@@ -396,36 +395,36 @@ parse({with, X, As}=T) when is_list(As) ->
 	[] ->
 	    {data, []}
     end;
-parse({S, T1} = T) when is_list(S) ->
+parse({S, T1} = T, _Options) when is_list(S) ->
     case eunit_lib:is_string(S) of
 	true ->
 	    group(#group{tests = T1, desc = unicode:characters_to_binary(S)});
 	false ->
 	    bad_test(T)
     end;
-parse({S, T1}) when is_binary(S) ->
+parse({S, T1}, _Options) when is_binary(S) ->
     group(#group{tests = T1, desc = S});
-parse(T) when tuple_size(T) > 2, is_list(element(1, T)) ->
+parse(T, Options) when tuple_size(T) > 2, is_list(element(1, T)) ->
     [S | Es] = tuple_to_list(T),
-    parse({S, list_to_tuple(Es)});
-parse(T) when tuple_size(T) > 2, is_binary(element(1, T)) ->
+    parse({S, list_to_tuple(Es)}, Options);
+parse(T, Options) when tuple_size(T) > 2, is_binary(element(1, T)) ->
     [S | Es] = tuple_to_list(T),
-    parse({S, list_to_tuple(Es)});
-parse(M) when is_atom(M) ->
-    parse({module, M});
-parse(T) when is_list(T) ->
+    parse({S, list_to_tuple(Es)}, Options);
+parse(M, Options) when is_atom(M) ->
+    parse({module, M}, Options);
+parse(T, Options) when is_list(T) ->
     case eunit_lib:is_string(T) of
 	true ->
-	    try parse({dir, T})
+	    try parse({dir, T}, Options)
 	    catch
 		{file_read_error,{R,_,_}}
 		  when R =:= enotdir; R =:= enoent ->
-		    parse({file, T})
+		    parse({file, T}, Options)
 	    end;
 	false ->
 	    bad_test(T)
     end;
-parse(T) ->
+parse(T, _Options) ->
     parse_simple(T).
 
 %% parse_simple always produces a #test{} record
@@ -481,10 +480,10 @@ group(#group{context = #context{}} = G) ->
     %% suitable for lookahead (and anyway, properties of the setup
     %% should not be merged with properties of its body, e.g. spawn)
     G;
-group(#group{tests = T0, desc = Desc, order = Order, context = Context,
-	     spawn = Spawn, timeout = Timeout} = G) ->
-    {T1, Ts} = lookahead(T0),
-    {T2, _} = lookahead(Ts),
+group(#group{tests = T0, desc = Desc, options = Options, order = Order,
+             context = Context, spawn = Spawn, timeout = Timeout} = G) ->
+    {T1, Ts} = lookahead(T0, Options),
+    {T2, _} = lookahead(Ts, Options),
     case T1 of
 	#test{desc = Desc1, timeout = Timeout1}
 	when T2 =:= none, Spawn =:= undefined, Context =:= undefined,
@@ -529,8 +528,8 @@ group(#group{tests = T0, desc = Desc, order = Order, context = Context,
 	    G
     end.
 
-lookahead(T) ->
-    case next(T) of
+lookahead(T, Options) ->
+    case next(T, Options) of
 	{T1, Ts} -> {T1, Ts};
 	none -> {none, []}
     end.
@@ -559,58 +558,62 @@ push_order(_, _, G) ->
 
 %% @throws {module_not_found, moduleName()}
 
-get_module_tests(M) ->
-    try M:module_info(exports) of
-	Es ->
-	    Fs = get_module_tests_1(M, Es),
-	    W = ?DEFAULT_MODULE_WRAPPER_NAME,
-	    case lists:member({W,1}, Es) of
-		false -> Fs;
-		true -> {generator, fun () -> M:W(Fs) end}
+get_module_tests(Module, Options) ->
+    try Module:module_info(exports) of
+	Exports ->
+	    TestFuns = extract_module_tests(Module, Exports, Options),
+	    case lists:member({?DEFAULT_MODULE_WRAPPER_NAME, 1}, Exports) of
+		false -> TestFuns;
+		true -> {generator,
+                         fun() ->
+                                 Module:?DEFAULT_MODULE_WRAPPER_NAME(TestFuns)
+                         end}
 	    end
     catch
-	error:undef -> 
-	    throw({module_not_found, M})
+	error:undef ->
+	    throw({module_not_found, Module})
     end.
 
-get_module_tests_1(M, Es) ->
-    Fs = testfuns(Es, M, ?DEFAULT_TEST_SUFFIX,
-		  ?DEFAULT_GENERATOR_SUFFIX),
-    Name = atom_to_list(M),
-    case lists:suffix(?DEFAULT_TESTMODULE_SUFFIX, Name) of
-	false ->
-	    Name1 = Name ++ ?DEFAULT_TESTMODULE_SUFFIX,
-	    M1 = list_to_atom(Name1),
-	    try get_module_tests(M1) of
-		Fs1 ->
-		    Fs ++ [{"module '" ++ Name1 ++ "'", Fs1}]
+extract_module_tests(Module, Exports, Options) ->
+    TestFuns = extract_testfuns(Exports, Module, ?DEFAULT_TEST_SUFFIX,
+                                ?DEFAULT_GENERATOR_SUFFIX),
+    ModuleName = atom_to_list(Module),
+    Exact = proplists:get_bool(exact_execution, Options),
+    case {lists:suffix(?DEFAULT_TESTMODULE_SUFFIX, ModuleName),
+          Exact} of
+	{false, false} ->
+	    ModuleNameWithSuffix = ModuleName ++ ?DEFAULT_TESTMODULE_SUFFIX,
+	    ModuleWithSuffix = list_to_atom(ModuleNameWithSuffix),
+	    try get_module_tests(ModuleWithSuffix, Options) of
+		MoreTestFuns ->
+		    TestFuns ++ [{"module '" ++ ModuleNameWithSuffix ++ "'",
+                                  MoreTestFuns}]
 	    catch
-		{module_not_found, M1} ->
-		    Fs
+		{module_not_found, ModuleWithSuffix} ->
+		    TestFuns
 	    end;
-	true ->
-	    Fs
+	_ ->
+	    TestFuns
     end.
 
-testfuns(Es, M, TestSuffix, GeneratorSuffix) ->
-    foldr(fun ({F, 0}, Fs) ->
-		  N = atom_to_list(F),
-		  case lists:suffix(TestSuffix, N) of
-		      true ->
-			  [{test, M, F} | Fs];
-		      false ->
-			  case lists:suffix(GeneratorSuffix, N) of
-			      true ->
-				  [{generator, M, F} | Fs];
-			      false ->
-				  Fs
-			  end
-		  end;
-	      (_, Fs) ->
-		  Fs
-	  end,
-	  [],
-	  Es).    
+extract_testfuns(Exports, Module, TestSuffix, GeneratorSuffix) ->
+    GetTestFun = fun({Function, 0}, Acc) ->
+                         FunctionName = atom_to_list(Function),
+                         case lists:suffix(TestSuffix, FunctionName) of
+                             true ->
+                                 [{test, Module, Function} | Acc];
+                             false ->
+                                 case lists:suffix(GeneratorSuffix, FunctionName) of
+                                     true ->
+                                         [{generator, Module, Function} | Acc];
+                                     false ->
+                                         Acc
+                                 end
+                         end;
+                    (_, Acc) ->
+                         Acc
+                 end,
+    lists:foldr(GetTestFun, [], Exports).
 
 
 %% ---------------------------------------------------------------------
diff --git a/lib/eunit/src/eunit_internal.hrl b/lib/eunit/src/eunit_internal.hrl
index 65f4c433e7..217d4a304c 100644
--- a/lib/eunit/src/eunit_internal.hrl
+++ b/lib/eunit/src/eunit_internal.hrl
@@ -50,6 +50,7 @@
 	      }).
 
 -record(group, {desc = undefined,
+                options = undefined,
 		order = undefined,	% run in order or in parallel
 		timeout = undefined,
 		context = undefined,	% setup-context record
diff --git a/lib/eunit/src/eunit_proc.erl b/lib/eunit/src/eunit_proc.erl
index 7622bab2a9..48254f53a3 100644
--- a/lib/eunit/src/eunit_proc.erl
+++ b/lib/eunit/src/eunit_proc.erl
@@ -29,13 +29,12 @@
 -include("eunit.hrl").
 -include("eunit_internal.hrl").
 
--export([start/4, get_output/0]).
+-export([start/5, get_output/0]).
 
 %% This must be exported; see new_group_leader/1 for details.
 -export([group_leader_process/1]).
 
--record(procstate, {ref, id, super, insulator, parent, order}).
-
+-record(procstate, {ref, id, super, insulator, parent, order, options}).
 
 %% Spawns test process and returns the process Pid; sends {done,
 %% Reference, Pid} to caller when finished. See the function
@@ -44,12 +43,13 @@
 %% The `Super' process receives a stream of status messages; see
 %% message_super/3 for details.
 
-start(Tests, Order, Super, Reference)
+start(Tests, Order, Super, Reference, Options)
   when is_pid(Super), is_reference(Reference) ->
     St = #procstate{ref = Reference,
 		    id = [],
 		    super = Super,
-		    order = Order},
+		    order = Order,
+                    options = Options},
     spawn_group(local, #group{tests = Tests}, St).
 
 %% Fetches the output captured by the eunit group leader. This is
@@ -436,7 +436,7 @@ wait_for_tasks(PidSet, St) ->
 %% TODO: Flow control, starting new job as soon as slot is available
 
 tests(T, St) ->
-    I = eunit_data:iter_init(T, St#procstate.id),
+    I = eunit_data:iter_init(T, St#procstate.id, St#procstate.options),
     case St#procstate.order of
 	inorder -> tests_inorder(I, St);
 	inparallel -> tests_inparallel(I, 0, St);
diff --git a/lib/eunit/src/eunit_server.erl b/lib/eunit/src/eunit_server.erl
index e46394d88c..6fb44e0170 100644
--- a/lib/eunit/src/eunit_server.erl
+++ b/lib/eunit/src/eunit_server.erl
@@ -243,7 +243,8 @@ start_job(Job, From, Reference, St) ->
     From ! {start, Reference},
     %% The default is to run tests in order unless otherwise specified
     Order = proplists:get_value(order, Job#job.options, inorder),
-    eunit_proc:start(Job#job.test, Order, Job#job.super, Reference),
+    eunit_proc:start(Job#job.test, Order, Job#job.super, Reference,
+                     Job#job.options),
     St#state{jobs = dict:store(Reference, From, St#state.jobs)}.
 
 handle_done(Reference, St) ->
diff --git a/lib/eunit/test/Makefile b/lib/eunit/test/Makefile
index 1bd9c0a07c..a5b1b719ad 100644
--- a/lib/eunit/test/Makefile
+++ b/lib/eunit/test/Makefile
@@ -21,6 +21,7 @@ include $(ERL_TOP)/make/target.mk
 include $(ERL_TOP)/make/$(TARGET)/otp.mk
 
 MODULES =  \
+	eunit_test_listener \
 	eunit_SUITE \
 	tc0 \
 	tlatin \
diff --git a/lib/eunit/test/eunit_SUITE.erl b/lib/eunit/test/eunit_SUITE.erl
index b637b5f314..b0c2259971 100644
--- a/lib/eunit/test/eunit_SUITE.erl
+++ b/lib/eunit/test/eunit_SUITE.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 2010-2021. All Rights Reserved.
+%% Copyright Ericsson AB 2010-2022. All Rights Reserved.
 %%
 %% Licensed under the Apache License, Version 2.0 (the "License");
 %% you may not use this file except in compliance with the License.
@@ -19,19 +19,22 @@
 %%
 -module(eunit_SUITE).
 
--export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
-	 init_per_group/2,end_per_group/2,
-	 app_test/1,appup_test/1,eunit_test/1,surefire_utf8_test/1,surefire_latin_test/1,
+-export([all/0, suite/0, groups/0, init_per_suite/1, end_per_suite/1,
+	 init_per_group/2, end_per_group/2,
+	 app_test/1, appup_test/1, eunit_test/1, eunit_exact_test/1,
+         surefire_utf8_test/1, surefire_latin_test/1,
 	 surefire_c0_test/1, surefire_ensure_dir_test/1,
 	 stacktrace_at_timeout_test/1]).
 
 -include_lib("common_test/include/ct.hrl").
+-define(TIMEOUT, 1000).
 
 suite() -> [{ct_hooks,[ts_install_cth]}].
 
 all() ->
-    [app_test, appup_test, eunit_test, surefire_utf8_test, surefire_latin_test,
-     surefire_c0_test, surefire_ensure_dir_test, stacktrace_at_timeout_test].
+    [app_test, appup_test, eunit_test, eunit_exact_test, surefire_utf8_test,
+     surefire_latin_test, surefire_c0_test, surefire_ensure_dir_test,
+     stacktrace_at_timeout_test].
 
 groups() ->
     [].
@@ -58,6 +61,30 @@ eunit_test(Config) when is_list(Config) ->
     ok = file:set_cwd(code:lib_dir(eunit)),
     ok = eunit:test(eunit).
 
+eunit_exact_test(Config) when is_list(Config) ->
+    ok = file:set_cwd(code:lib_dir(eunit)),
+    ok = eunit:test([eunit, eunit_tests],
+                    [{report, {eunit_test_listener, [self()]}}]),
+    check_test_results(14, 0, 0, 0),
+    ok = eunit:test([eunit, eunit_tests],
+                    [{report, {eunit_test_listener, [self()]}},
+                     {exact_execution, false}]),
+    check_test_results(14, 0, 0, 0),
+    ok = eunit:test([eunit, eunit_tests],
+                    [{report, {eunit_test_listener, [self()]}},
+                     {exact_execution, true}]),
+    check_test_results(7, 0, 0, 0),
+    ok.
+
+check_test_results(Pass, Fail, Skip, Cancel) ->
+    receive
+        {test_report, TestReport} ->
+            #{pass := Pass, fail := Fail,
+              skip := Skip, cancel := Cancel} = TestReport
+    after ?TIMEOUT ->
+            ct:fail(no_test_report_not_received)
+    end.
+
 surefire_latin_test(Config) when is_list(Config) ->
     ok = file:set_cwd(proplists:get_value(priv_dir, Config, ".")),
 	check_surefire(tlatin),
diff --git a/lib/eunit/test/eunit_test_listener.erl b/lib/eunit/test/eunit_test_listener.erl
new file mode 100644
index 0000000000..95894a02ff
--- /dev/null
+++ b/lib/eunit/test/eunit_test_listener.erl
@@ -0,0 +1,85 @@
+%% Licensed under the Apache License, Version 2.0 (the "License"); you may
+%% not use this file except in compliance with the License. You may obtain
+%% a copy of the License at <http://www.apache.org/licenses/LICENSE-2.0>
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%%
+%% Alternatively, you may use this file under the terms of the GNU Lesser
+%% General Public License (the "LGPL") as published by the Free Software
+%% Foundation; either version 2.1, or (at your option) any later version.
+%% If you wish to allow use of your version of this file only under the
+%% terms of the LGPL, you should delete the provisions above and replace
+%% them with the notice and other provisions required by the LGPL; see
+%% <http://www.gnu.org/licenses/>. If you do not delete the provisions
+%% above, a recipient may use your version of this file under the terms of
+%% either the Apache License or the LGPL.
+%%
+%% @author The OTP team at Ericsson
+%% @copyright Ericsson AB 2022
+%% @private
+%% @see eunit
+%% @doc Module for receiving EUnit events for verification purposes
+
+-module(eunit_test_listener).
+-behaviour(eunit_listener).
+
+-export([start/0, start/1]).
+-export([init/1, handle_begin/3, handle_end/3, handle_cancel/3,
+	 terminate/2]).
+
+-record(state, {test_process = undefined}).
+
+start() ->
+    start([]).
+
+start(Options) ->
+    eunit_listener:start(?MODULE, Options).
+
+init(Options) ->
+    [TestProcess] = Options,
+    receive
+	{start, _Reference} ->
+            #state{test_process = TestProcess}
+    end.
+
+terminate({ok, Data}, #state{test_process = TestProcess}) ->
+    Pass = proplists:get_value(pass, Data, 0),
+    Fail = proplists:get_value(fail, Data, 0),
+    Skip = proplists:get_value(skip, Data, 0),
+    Cancel = proplists:get_value(cancel, Data, 0),
+    TestProcess ! {test_report,
+                   #{pass => Pass, fail => Fail, skip => Skip,
+                     cancel => Cancel}},
+    if Fail =:= 0, Skip =:= 0, Cancel =:= 0 ->
+	    sync_end(ok);
+       true ->
+	    sync_end(error)
+    end;
+terminate({error, _Reason}, #state{}) ->
+    sync_end(error).
+
+sync_end(Result) ->
+    receive
+	{stop, Reference, ReplyTo} ->
+	    ReplyTo ! {result, Reference, Result},
+	    ok
+    end.
+
+handle_begin(group, _Data, St) ->
+    St;
+handle_begin(test, _Data, St) ->
+    St.
+
+handle_end(group, _Data, St) ->
+    St;
+handle_end(test, _Data, St) ->
+    St.
+
+handle_cancel(group, _Data, St) ->
+    St;
+handle_cancel(test, _Data, St) ->
+    St.
-- 
2.35.3

openSUSE Build Service is sponsored by