File 2464-stdlib-Make-gen_statem-callbacks-optional.patch of Package erlang

From eff1ee5ebf1d767d610cd6bc059e5f4dea57d2af Mon Sep 17 00:00:00 2001
From: Zandra Norman <zandra@erlang.org>
Date: Mon, 23 Jan 2017 17:06:48 +0100
Subject: [PATCH 4/4] stdlib: Make gen_statem callbacks optional

---
 lib/stdlib/doc/src/gen_statem.xml                  | 10 ++++
 lib/stdlib/test/erl_internal_SUITE.erl             |  9 ++-
 lib/stdlib/test/gen_statem_SUITE.erl               | 64 ++++++++++++++++++++--
 .../test/gen_statem_SUITE_data/oc_statem.erl       | 40 ++++++++++++++
 4 files changed, 118 insertions(+), 5 deletions(-)
 create mode 100644 lib/stdlib/test/gen_statem_SUITE_data/oc_statem.erl

diff --git a/lib/stdlib/doc/src/gen_statem.xml b/lib/stdlib/doc/src/gen_statem.xml
index 1b99b65e0..bc86415d2 100644
--- a/lib/stdlib/doc/src/gen_statem.xml
+++ b/lib/stdlib/doc/src/gen_statem.xml
@@ -1733,6 +1733,16 @@ handle_event(_, _, State, Data) ->
 	<v>Reason = term()</v>
       </type>
       <desc>
+        <note>
+          <p>
+	    This callback is optional, so callback modules need not export it.
+            If a release upgrade/downgrade with
+	    <c>Change={advanced,Extra}</c>
+	    specified in the <c>.appup</c> file is made
+	    when <c>code_change/4</c> is not implemented
+	    the process will crash with exit reason <c>undef</c>.
+	  </p>
+        </note>
         <p>
 	  This function is called by a <c>gen_statem</c> when it is to
 	  update its internal state during a release upgrade/downgrade,
diff --git a/lib/stdlib/test/erl_internal_SUITE.erl b/lib/stdlib/test/erl_internal_SUITE.erl
index bfa48de6b..e60c202a5 100644
--- a/lib/stdlib/test/erl_internal_SUITE.erl
+++ b/lib/stdlib/test/erl_internal_SUITE.erl
@@ -60,7 +60,7 @@ end_per_testcase(_Case, _Config) ->
 %% Check that the behaviour callbacks are correctly defined.
 behav(_) ->
     Modules = [application, gen_server, gen_fsm, gen_event,
-               supervisor_bridge, supervisor],
+               gen_statem, supervisor_bridge, supervisor],
     lists:foreach(fun check_behav/1, Modules).
 
 check_behav(Module) ->
@@ -89,6 +89,10 @@ callbacks(gen_event) ->
     [{init,1}, {handle_event,2}, {handle_call,2},
      {handle_info,2}, {terminate,2}, {code_change,3},
      {format_status,2}];
+callbacks(gen_statem) ->
+    [{init, 1}, {callback_mode, 0}, {state_name, 3},
+     {handle_event, 4}, {terminate, 3}, {code_change, 4},
+     {format_status, 2}];
 callbacks(supervisor_bridge) ->
     [{init,1}, {terminate,2}];
 callbacks(supervisor) ->
@@ -102,6 +106,9 @@ optional_callbacks(gen_fsm) ->
     [{handle_info, 3}, {terminate, 3}, {code_change, 4}, {format_status, 2}];
 optional_callbacks(gen_event) ->
     [{handle_info, 2}, {terminate, 2}, {code_change, 3}, {format_status, 2}];
+optional_callbacks(gen_statem) ->
+    [{format_status, 2}, {state_name, 3},
+     {handle_event, 4}, {terminate, 3}, {code_change, 4}];
 optional_callbacks(supervisor_bridge) ->
     [];
 optional_callbacks(supervisor) ->
diff --git a/lib/stdlib/test/gen_statem_SUITE.erl b/lib/stdlib/test/gen_statem_SUITE.erl
index 36b1f761a..cb045ca49 100644
--- a/lib/stdlib/test/gen_statem_SUITE.erl
+++ b/lib/stdlib/test/gen_statem_SUITE.erl
@@ -40,7 +40,8 @@ all() ->
      shutdown, stop_and_reply, state_enter, event_order,
      state_timeout, event_types, generic_timers, code_change,
      {group, sys},
-     hibernate, enter_loop].
+     hibernate, enter_loop, {group, undef_callbacks},
+     undef_in_terminate].
 
 groups() ->
     [{start, [], tcs(start)},
@@ -50,7 +51,8 @@ groups() ->
      {abnormal, [], tcs(abnormal)},
      {abnormal_handle_event, [], tcs(abnormal)},
      {sys, [], tcs(sys)},
-     {sys_handle_event, [], tcs(sys)}].
+     {sys_handle_event, [], tcs(sys)},
+     {undef_callbacks, [], tcs(undef_callbacks)}].
 
 tcs(start) ->
     [start1, start2, start3, start4, start5, start6, start7,
@@ -62,8 +64,9 @@ tcs(abnormal) ->
 tcs(sys) ->
     [sys1, call_format_status,
      error_format_status, terminate_crash_format,
-     get_state, replace_state].
-
+     get_state, replace_state];
+tcs(undef_callbacks) ->
+    [undef_code_change, undef_terminate1, undef_terminate2].
 
 init_per_suite(Config) ->
     Config.
@@ -77,6 +80,11 @@ init_per_group(GroupName, Config)
        GroupName =:= abnormal_handle_event;
        GroupName =:= sys_handle_event ->
     [{callback_mode,handle_event_function}|Config];
+init_per_group(undef_callbacks, Config) ->
+    DataDir = ?config(data_dir, Config),
+    StatemPath = filename:join(DataDir, "oc_statem.erl"),
+    {ok, oc_statem} = compile:file(StatemPath),
+    Config;
 init_per_group(_GroupName, Config) ->
     Config.
 
@@ -1461,6 +1469,51 @@ enter_loop(Reg1, Reg2) ->
 	    gen_statem:enter_loop(?MODULE, [], state0, [])
     end.
 
+undef_code_change(_Config) ->
+    {ok, Statem} = gen_statem:start(oc_statem, [], []),
+    {error, {'EXIT',
+             {undef, [{oc_statem, code_change, [_, _, _, _], _}|_]}}}
+        = fake_upgrade(Statem, oc_statem).
+
+fake_upgrade(Pid, Mod) ->
+    sys:suspend(Pid),
+    sys:replace_state(Pid, fun(State) -> {new, State} end),
+    Ret = sys:change_code(Pid, Mod, old_vsn, []),
+    ok = sys:resume(Pid),
+    Ret.
+
+undef_terminate1(_Config) ->
+    {ok, Statem} = gen_statem:start(oc_statem, [], []),
+    MRef = monitor(process, Statem),
+    ok = gen_statem:stop(Statem),
+    verify_down(Statem, MRef, normal),
+    ok.
+
+undef_terminate2(_Config) ->
+    Reason = {error, test},
+    {ok, Statem} = oc_statem:start(),
+    MRef = monitor(process, Statem),
+    ok = gen_statem:stop(Statem, Reason, infinity),
+    verify_down(Statem, MRef, Reason).
+
+undef_in_terminate(_Config) ->
+    Data =  {undef_in_terminate, {?MODULE, terminate}},
+    {ok, Statem} = gen_statem:start(?MODULE, {data, Data}, []),
+    try
+        gen_statem:stop(Statem),
+        ct:fail(should_crash)
+    catch
+        exit:{undef, [{?MODULE, terminate, _, _}|_]} ->
+            ok
+    end.
+
+verify_down(Statem, MRef, Reason) ->
+    receive
+        {'DOWN', MRef, process, Statem, Reason} ->
+            ok
+    after 5000 ->
+        ct:fail(default_terminate_failed)
+    end.
 
 %% Test the order for multiple {next_event,T,C}
 next_events(Config) ->
@@ -1639,6 +1692,9 @@ callback_mode() ->
 
 terminate(_, _State, crash_terminate) ->
     exit({crash,terminate});
+terminate(_, _State, {undef_in_terminate, {Mod, Fun}}) ->
+    Mod:Fun(),
+    ok;
 terminate({From,stopped}, State, _Data) ->
     From ! {self(),{stopped,State}},
     ok;
diff --git a/lib/stdlib/test/gen_statem_SUITE_data/oc_statem.erl b/lib/stdlib/test/gen_statem_SUITE_data/oc_statem.erl
new file mode 100644
index 000000000..577abe052
--- /dev/null
+++ b/lib/stdlib/test/gen_statem_SUITE_data/oc_statem.erl
@@ -0,0 +1,40 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2017. 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.
+%% 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.
+%%
+%% %CopyrightEnd%
+%%
+-module(oc_statem).
+
+-behaviour(gen_statem).
+
+%% API
+-export([start/0]).
+
+%% gen_statem callbacks
+-export([init/1, callback_mode/0]).
+
+start() ->
+    gen_statem:start({local, ?MODULE}, ?MODULE, [], []).
+
+init([]) ->
+    {ok, state_name, #{}}.
+
+callback_mode() ->
+    handle_event_function.
+
+
+
-- 
2.12.2

openSUSE Build Service is sponsored by