File 5991-Test-change_callback_module-with-state_enter.patch of Package erlang

From 3e51657168dbb7b4c044bc7aae224888c7ade33d Mon Sep 17 00:00:00 2001
From: Raimo Niskanen <raimo@erlang.org>
Date: Thu, 8 Sep 2022 17:33:55 +0200
Subject: [PATCH 1/4] Test change_callback_module with state_enter

---
 lib/stdlib/test/gen_statem_SUITE.erl          | 32 +++++++++++--------
 .../test/gen_statem_SUITE_data/oc_statem.erl  | 18 ++++++-----
 2 files changed, 29 insertions(+), 21 deletions(-)

diff --git a/lib/stdlib/test/gen_statem_SUITE.erl b/lib/stdlib/test/gen_statem_SUITE.erl
index b9084cc825..88cc2c412b 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-2020. All Rights Reserved.
+%% Copyright Ericsson AB 2016-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.
@@ -88,7 +88,10 @@ init_per_group(GroupName, Config)
        GroupName =:= sys_handle_event ->
     [{callback_mode,handle_event_function}|Config];
 init_per_group(undef_callbacks, Config) ->
-    compile_oc_statem(Config),
+    try compile_oc_statem(Config)
+    catch Class : Reason : Stacktrace ->
+             {fail,{Class,Reason,Stacktrace}}
+    end,
     Config;
 init_per_group(_GroupName, Config) ->
     Config.
@@ -1851,12 +1854,14 @@ pop_too_many(_Config) ->
     Machine =
 	#{init =>
 	      fun () ->
-		      {ok,start,undefined}
+		      {ok,state_1,undefined}
 	      end,
-	  start =>
-	      fun ({call, From}, {change_callback_module, _Module} = Action,
-                   undefined = _Data) ->
-		      {keep_state_and_data,
+	  state_1 =>
+	      fun (enter, state_2, undefined) ->
+                      {keep_state, enter}; % OTP-18239, should not be called
+                  ({call, From}, {change_callback_module, _Module} = Action,
+                   undefined = Data) ->
+                      {next_state, state_2, Data,
                        [Action,
                         {reply,From,ok}]};
                   ({call, From}, {verify, ?MODULE},
@@ -1864,8 +1869,8 @@ pop_too_many(_Config) ->
 		      {keep_state_and_data,
                        [{reply,From,ok}]};
                   ({call, From}, pop_callback_module = Action,
-                   undefined = _Data) ->
-		      {keep_state_and_data,
+                   undefined = Data) ->
+                      {next_state, state_2, Data,
                        [Action,
                         {reply,From,ok}]}
 	      end},
@@ -1875,10 +1880,11 @@ pop_too_many(_Config) ->
           {map_statem, Machine, []},
           [{debug, [trace]}]),
 
-    ok = gen_statem:call(STM, {change_callback_module, oc_statem}),
-    ok = gen_statem:call(STM, {push_callback_module, ?MODULE}),
-    ok = gen_statem:call(STM, {verify, ?MODULE}),
-    ok = gen_statem:call(STM, pop_callback_module),
+    ok    = gen_statem:call(STM, {change_callback_module, oc_statem}),
+    enter = gen_statem:call(STM, get_data), % OTP-18239
+    ok    = gen_statem:call(STM, {push_callback_module, ?MODULE}),
+    ok    = gen_statem:call(STM, {verify, ?MODULE}),
+    ok    = gen_statem:call(STM, pop_callback_module),
     BadAction = {bad_action_from_state_function, pop_callback_module},
     {{BadAction, _},
      {gen_statem,call,[STM,pop_callback_module,infinity]}} =
diff --git a/lib/stdlib/test/gen_statem_SUITE_data/oc_statem.erl b/lib/stdlib/test/gen_statem_SUITE_data/oc_statem.erl
index 1de7de527b..04d9cfaad9 100644
--- a/lib/stdlib/test/gen_statem_SUITE_data/oc_statem.erl
+++ b/lib/stdlib/test/gen_statem_SUITE_data/oc_statem.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 2017-2020. All Rights Reserved.
+%% Copyright Ericsson AB 2017-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.
@@ -49,22 +49,24 @@ init([]) ->
                           exit(Statem, kill)
                   end
           end),
-    {ok, start, #{}}.
+    {ok, state_2, [undefined]}.
 
 callback_mode() ->
     [handle_event_function, state_enter].
 
-handle_event(enter, start, start, _Data) ->
-    keep_state_and_data;
+handle_event(enter, _OldState, state_2, [undefined|Data]) ->
+    {keep_state, [enter|Data]};
+handle_event({call,From}, get_data, state_2, Data) ->
+    {keep_state_and_data, [{reply,From,hd(Data)}]};
 handle_event(
-  {call,From}, {push_callback_module,NewModule} = Action,
-  start, _Data) ->
-    {keep_state_and_data,
+  {call,From}, {push_callback_module,_NewModule} = Action,
+  state_2, [enter|Data]) ->
+    {next_state, state_1, [undefined|Data],
      [Action,
       {reply,From,ok}]};
 handle_event(
   {call,From}, pop_callback_module = Action,
-  start, _Data) ->
+  state_2, [enter|_Data]) ->
     {keep_state_and_data,
      [Action,
       {reply,From,ok}]}.
-- 
2.35.3

openSUSE Build Service is sponsored by