File 5472-stdlib-test-Update-gen_server-and-gen_statem-suite-s.patch of Package erlang

From c0a2e2e185a728140a4352d82f44dca1d5ddede9 Mon Sep 17 00:00:00 2001
From: Micael Karlberg <bmk@erlang.org>
Date: Tue, 31 Jan 2023 10:17:29 +0100
Subject: [PATCH 2/3] [stdlib|test] Update gen_server and gen_statem suite(s)

Update the 'start' test case of the gen_server_SUITE
and gen_statem_SUITE.

OTP-18423
---
 lib/stdlib/test/gen_server_SUITE.erl | 21 +++++++++++++++++++-
 lib/stdlib/test/gen_statem_SUITE.erl | 29 +++++++++++++++++++++++++---
 2 files changed, 46 insertions(+), 4 deletions(-)

diff --git a/lib/stdlib/test/gen_server_SUITE.erl b/lib/stdlib/test/gen_server_SUITE.erl
index 5fa604d4fd..961920b3e1 100644
--- a/lib/stdlib/test/gen_server_SUITE.erl
+++ b/lib/stdlib/test/gen_server_SUITE.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 1996-2021. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2023. 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.
@@ -148,6 +148,7 @@ start(Config) when is_list(Config) ->
     OldFl = process_flag(trap_exit, true),
 
     %% anonymous
+    io:format("anonymous~n", []),
     {ok, Pid0} = gen_server:start(gen_server_SUITE, [], []),
     ok = gen_server:call(Pid0, started_p),
     ok = gen_server:call(Pid0, stop),
@@ -155,6 +156,7 @@ start(Config) when is_list(Config) ->
     {'EXIT', {noproc,_}} = (catch gen_server:call(Pid0, started_p, 1)),
 
     %% anonymous with timeout
+    io:format("try init timeout~n", []),
     {ok, Pid00} = gen_server:start(gen_server_SUITE, [],
 				   [{timeout,1000}]),
     ok = gen_server:call(Pid00, started_p),
@@ -163,9 +165,16 @@ start(Config) when is_list(Config) ->
 					[{timeout,100}]),
 
     %% anonymous with ignore
+    io:format("try init ignore~n", []),
     ignore = gen_server:start(gen_server_SUITE, ignore, []),
 
+    %% anonymous with shutdown
+    io:format("try init shutdown~n", []),
+    {error, foobar} =
+        gen_server:start(gen_server_SUITE, {error, foobar}, []),
+
     %% anonymous with stop
+    io:format("try init stop~n", []),
     {error, stopped} = gen_server:start(gen_server_SUITE, stop, []),
 
     %% anonymous linked
@@ -2483,18 +2492,27 @@ spec_init_not_proc_lib(Options) ->
 init([]) ->
     {ok, []};
 init(ignore) ->
+    io:format("init(ignore)~n"),
     ignore;
+init({error, Reason}) ->
+    io:format("init(error) -> ~w~n", [Reason]),
+    {error, Reason};
 init(stop) ->
+    io:format("init(stop)~n"),
     {stop, stopped};
 init(hibernate) ->
+    io:format("init(hibernate)~n"),
     {ok,[],hibernate};
 init(sleep) ->
+    io:format("init(sleep)~n"),
     ct:sleep(1000),
     {ok, []};
 init({continue, Pid}) ->
+    io:format("init(continue) -> ~p~n", [Pid]),
     self() ! {after_continue, Pid},
     {ok, [], {continue, {message, Pid}}};
 init({state,State}) ->
+    io:format("init(state) -> ~p~n", [State]),
     {ok,State}.
 
 handle_call(started_p, _From, State) ->
@@ -2507,6 +2525,7 @@ handle_call({call_within, T}, _From, _) ->
 handle_call(next_call, _From, call_within) ->
     {reply,ok,[]};
 handle_call(next_call, _From, State) ->
+    io:format("handle_call(next_call) -> State: ~p~n", [State]),
     {reply,false,State};
 handle_call(badreturn, _From, _State) ->
     badreturn;
diff --git a/lib/stdlib/test/gen_statem_SUITE.erl b/lib/stdlib/test/gen_statem_SUITE.erl
index cb8bee9fab..8f18c42dc1 100644
--- a/lib/stdlib/test/gen_statem_SUITE.erl
+++ b/lib/stdlib/test/gen_statem_SUITE.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 2016-2022. All Rights Reserved.
+%% Copyright Ericsson AB 2016-2023. 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.
@@ -61,7 +61,7 @@ groups() ->
      {format_log, [], tcs(format_log)}].
 
 tcs(start) ->
-    [start1, start2, start3, start4, start5, start6, start7,
+    [start1, start2, start3, start4, start5a, start5b, start6, start7,
      start8, start9, start10, start11, start12, next_events];
 tcs(stop) ->
     [stop1, stop2, stop3, stop4, stop5, stop6, stop7, stop8, stop9, stop10];
@@ -210,7 +210,7 @@ start4(Config) ->
     ok = verify_empty_msgq().
 
 %% anonymous with stop
-start5(Config) ->
+start5a(Config) ->
     OldFl = process_flag(trap_exit, true),
 
     {error,stopped} = gen_statem:start(?MODULE, start_arg(Config, stop), []),
@@ -218,6 +218,16 @@ start5(Config) ->
     process_flag(trap_exit, OldFl),
     ok = verify_empty_msgq().
 
+%% anonymous with shutdown
+start5b(Config) ->
+    OldFl = process_flag(trap_exit, true),
+
+    {error, foobar} =
+        gen_statem:start(?MODULE, start_arg(Config, {error, foobar}), []),
+
+    process_flag(trap_exit, OldFl),
+    ok = verify_empty_msgq().
+
 %% anonymous linked
 start6(Config) ->
     {ok,Pid} = gen_statem:start_link(?MODULE, start_arg(Config, []), []),
@@ -2753,25 +2763,37 @@ start_arg(Config, Arg) ->
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
 init(ignore) ->
+    io:format("init(ignore)~n", []),
     ignore;
 init(stop) ->
+    io:format("init(stop)~n", []),
     {stop,stopped};
+init({error, Reason}) ->
+    io:format("init(error) -> Reason: ~p~n", [Reason]),
+    {error, Reason};
 init(stop_shutdown) ->
+    io:format("init(stop_shutdown)~n", []),
     {stop,shutdown};
 init(sleep) ->
+    io:format("init(sleep)~n", []),
     ct:sleep(1000),
     init_sup({ok,idle,data});
 init(hiber) ->
+    io:format("init(hiber)~n", []),
     init_sup({ok,hiber_idle,[]});
 init(hiber_now) ->
+    io:format("init(hiber_now)~n", []),
     init_sup({ok,hiber_idle,[],[hibernate]});
 init({data, Data}) ->
+    io:format("init(data)~n", []),
     init_sup({ok,idle,Data});
 init({callback_mode,CallbackMode,Arg}) ->
+    io:format("init(callback_mode)~n", []),
     ets:new(?MODULE, [named_table,private]),
     ets:insert(?MODULE, {callback_mode,CallbackMode}),
     init(Arg);
 init({map_statem,#{init := Init}=Machine,Modes}) ->
+    io:format("init(map_statem)~n", []),
     ets:new(?MODULE, [named_table,private]),
     ets:insert(?MODULE, {callback_mode,[handle_event_function|Modes]}),
     case Init() of
@@ -2783,6 +2805,7 @@ init({map_statem,#{init := Init}=Machine,Modes}) ->
 	    init_sup(Other)
     end;
 init([]) ->
+    io:format("init~n", []),
     init_sup({ok,idle,data}).
 
 %% Supervise state machine parent i.e the test case, and if it dies
-- 
2.35.3

openSUSE Build Service is sponsored by