File 2347-stdlib-Make-gen_event-callbacks-optional.patch of Package erlang

From db632b91f41c4a01be68d821d6942ff32b86e40b Mon Sep 17 00:00:00 2001
From: Zandra Norman <zandra@erlang.org>
Date: Mon, 23 Jan 2017 16:07:52 +0100
Subject: [PATCH 2/4] stdlib: Make gen_event callbacks optional

---
 lib/stdlib/doc/src/gen_event.xml                  |  18 +++
 lib/stdlib/src/gen_event.erl                      |  19 +++-
 lib/stdlib/test/dummy_h.erl                       |   6 +-
 lib/stdlib/test/erl_internal_SUITE.erl            |   2 +-
 lib/stdlib/test/gen_event_SUITE.erl               | 132 +++++++++++++++++++++-
 lib/stdlib/test/gen_event_SUITE_data/oc_event.erl |  40 +++++++
 6 files changed, 207 insertions(+), 10 deletions(-)
 create mode 100644 lib/stdlib/test/gen_event_SUITE_data/oc_event.erl

diff --git a/lib/stdlib/doc/src/gen_event.xml b/lib/stdlib/doc/src/gen_event.xml
index 42e952fd4..56cb7974a 100644
--- a/lib/stdlib/doc/src/gen_event.xml
+++ b/lib/stdlib/doc/src/gen_event.xml
@@ -579,6 +579,13 @@ gen_event:stop             ----->  Module:terminate/2
         <v>Extra = 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/3</c>
+            isn't implemented the event handler will crash with an <c>undef</c> error
+            reason.</p>
+        </note>
         <p>This function is called for an installed event handler that
           is to update its internal state during a release
           upgrade/downgrade, that is, when the instruction
@@ -759,6 +766,12 @@ gen_event:stop             ----->  Module:terminate/2
         <v>&nbsp;&nbsp;Id = term()</v>
       </type>
       <desc>
+        <note>
+          <p>This callback is optional, so callback modules need not
+            export it. The <c>gen_event</c> module provides a default
+            implementation of this function that logs about the unexpected
+            <c>Info</c> message, drops it and returns <c>{noreply, State}</c>.</p>
+        </note>
         <p>This function is called for each installed event handler when
           an event manager receives any other message than an event or
           a synchronous request (or a system message).</p>
@@ -815,6 +828,11 @@ gen_event:stop             ----->  Module:terminate/2
         <v>&nbsp;Args = Reason = Term = term()</v>
       </type>
       <desc>
+        <note>
+          <p>This callback is optional, so callback modules need not
+            export it. The <c>gen_event</c> module provides a default
+            implementation without cleanup.</p>
+        </note>
         <p>Whenever an event handler is deleted from an event manager,
           this function is called. It is to be the opposite of
           <seealso marker="#Module:init/1"><c>Module:init/1</c></seealso>
diff --git a/lib/stdlib/src/gen_event.erl b/lib/stdlib/src/gen_event.erl
index 0aebf1bdc..0c50b2aa0 100644
--- a/lib/stdlib/src/gen_event.erl
+++ b/lib/stdlib/src/gen_event.erl
@@ -109,7 +109,8 @@
       State :: term(),
       Status :: term().
 
--optional_callbacks([format_status/2]).
+-optional_callbacks(
+    [handle_info/2, terminate/2, code_change/3, format_status/2]).
 
 %%---------------------------------------------------------------------------
 
@@ -577,6 +578,10 @@ server_update(Handler1, Func, Event, SName) ->
 	    do_terminate(Mod1, Handler1, remove_handler, State,
 			 remove, SName, normal),
 	    no;
+        {'EXIT', {undef, [{Mod1, handle_info, [_,_], _}|_]}} ->
+            error_logger:warning_msg("** Undefined handle_info in ~p~n"
+                                     "** Unhandled message: ~p~n", [Mod1, Event]),
+           {ok, Handler1};
 	Other ->
 	    do_terminate(Mod1, Handler1, {error, Other}, State,
 			 Event, SName, crash),
@@ -698,9 +703,15 @@ server_call_update(Handler1, Query, SName) ->
     end.
 
 do_terminate(Mod, Handler, Args, State, LastIn, SName, Reason) ->
-    Res = (catch Mod:terminate(Args, State)),
-    report_terminate(Handler, Reason, Args, State, LastIn, SName, Res),
-    Res.
+    case erlang:function_exported(Mod, terminate, 2) of
+	true ->
+	    Res = (catch Mod:terminate(Args, State)),
+	    report_terminate(Handler, Reason, Args, State, LastIn, SName, Res),
+	    Res;
+	false ->
+	    report_terminate(Handler, Reason, Args, State, LastIn, SName, ok),
+	    ok
+    end.
 
 report_terminate(Handler, crash, {error, Why}, State, LastIn, SName, _) ->
     report_terminate(Handler, Why, State, LastIn, SName);
diff --git a/lib/stdlib/test/dummy_h.erl b/lib/stdlib/test/dummy_h.erl
index bc89cb4fd..70c0eafbd 100644
--- a/lib/stdlib/test/dummy_h.erl
+++ b/lib/stdlib/test/dummy_h.erl
@@ -26,6 +26,8 @@
 
 init(make_error) ->
     {error, my_error};
+init({state, State}) ->
+    {ok, State};
 init([Parent]) ->
     {ok, Parent};  %% We will send special responses for every handled event.
 init([Parent,hibernate]) ->
@@ -83,7 +85,9 @@ terminate(swap, State) ->
     {ok, State};
 terminate({error, {return, faulty}}, Parent) ->
     Parent ! {dummy_h, returned_error};
+terminate(_Reason, {undef_in_terminate, {Mod, Fun}}) ->
+    Mod:Fun(),
+    ok;
 terminate(_Reason, _State) ->
     ok.
 
-
diff --git a/lib/stdlib/test/erl_internal_SUITE.erl b/lib/stdlib/test/erl_internal_SUITE.erl
index 23d011e27..c4c4a0408 100644
--- a/lib/stdlib/test/erl_internal_SUITE.erl
+++ b/lib/stdlib/test/erl_internal_SUITE.erl
@@ -101,7 +101,7 @@ optional_callbacks(gen_server) ->
 optional_callbacks(gen_fsm) ->
     [{format_status,2}];
 optional_callbacks(gen_event) ->
-    [{format_status,2}];
+    [{handle_info, 2}, {terminate, 2}, {code_change, 3}, {format_status, 2}];
 optional_callbacks(supervisor_bridge) ->
     [];
 optional_callbacks(supervisor) ->
diff --git a/lib/stdlib/test/gen_event_SUITE.erl b/lib/stdlib/test/gen_event_SUITE.erl
index 9a7400c84..3f949ca10 100644
--- a/lib/stdlib/test/gen_event_SUITE.erl
+++ b/lib/stdlib/test/gen_event_SUITE.erl
@@ -22,13 +22,17 @@
 -include_lib("common_test/include/ct.hrl").
 
 -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
-	 init_per_group/2,end_per_group/2]).
+	 init_per_group/2,end_per_group/2, init_per_testcase/2,
+         end_per_testcase/2]).
 -export([start/1, add_handler/1, add_sup_handler/1,
 	 delete_handler/1, swap_handler/1, swap_sup_handler/1,
 	 notify/1, sync_notify/1, call/1, info/1, hibernate/1,
 	 call_format_status/1, call_format_status_anon/1,
          error_format_status/1, get_state/1, replace_state/1,
-         start_opt/1]).
+         start_opt/1,
+         undef_init/1, undef_handle_call/1, undef_handle_event/1,
+         undef_handle_info/1, undef_code_change/1, undef_terminate/1,
+         undef_in_terminate/1]).
 
 suite() -> [{ct_hooks,[ts_install_cth]}].
 
@@ -36,13 +40,16 @@ all() ->
     [start, {group, test_all}, hibernate,
      call_format_status, call_format_status_anon, error_format_status,
      get_state, replace_state,
-     start_opt].
+     start_opt, {group, undef_callbacks}, undef_in_terminate].
 
 groups() ->
     [{test_all, [],
       [add_handler, add_sup_handler, delete_handler,
        swap_handler, swap_sup_handler, notify, sync_notify,
-       call, info]}].
+       call, info]},
+     {undef_callbacks, [],
+      [undef_init, undef_handle_call, undef_handle_event, undef_handle_info,
+       undef_code_change, undef_terminate]}].
 
 init_per_suite(Config) ->
     Config.
@@ -50,12 +57,40 @@ init_per_suite(Config) ->
 end_per_suite(_Config) ->
     ok.
 
+init_per_group(undef_callbacks, Config) ->
+    DataDir = ?config(data_dir, Config),
+    Event1 = filename:join(DataDir, "oc_event.erl"),
+    {ok, oc_event} = compile:file(Event1),
+    Config;
 init_per_group(_GroupName, Config) ->
     Config.
 
 end_per_group(_GroupName, Config) ->
     Config.
 
+init_per_testcase(Case, Config) when Case == undef_handle_call;
+                                     Case == undef_handle_info;
+                                     Case == undef_handle_event;
+                                     Case == undef_code_change;
+                                     Case == undef_terminate ->
+    {ok, Pid} = oc_event:start(),
+    [{event_pid, Pid}|Config];
+init_per_testcase(undef_init, Config) ->
+    {ok, Pid} = gen_event:start({local, oc_init_event}),
+    [{event_pid, Pid}|Config];
+init_per_testcase(_Case, Config) ->
+    Config.
+
+end_per_testcase(Case, Config) when Case == undef_init;
+                                    Case == undef_handle_call;
+                                    Case == undef_handle_info;
+                                    Case == undef_handle_event;
+                                    Case == undef_code_change;
+                                    Case == undef_terminate ->
+    Pid = ?config(event_pid, Config),
+    gen_event:stop(Pid);
+end_per_testcase(_Case, _Config) ->
+    ok.
 
 %% --------------------------------------
 %% Start an event manager.
@@ -1055,3 +1090,92 @@ replace_state(Config) when is_list(Config) ->
     ok = sys:resume(Pid),
     [{dummy1_h,false,NState3}] = sys:get_state(Pid),
     ok.
+
+%% No default provided for init, so it should fail
+undef_init(Config) ->
+    Pid = ?config(event_pid, Config),
+    {'EXIT', {undef, [{oc_init_event, init, [_], _}|_]}}
+        = gen_event:add_handler(Pid, oc_init_event, []),
+    ok.
+
+%% No default provided for init, so it should fail
+undef_handle_call(Config) when is_list(Config) ->
+    Pid = ?config(event_pid, Config),
+    {error, {'EXIT', {undef, [{oc_event, handle_call, _, _}|_]}}}
+        = gen_event:call(Pid, oc_event, call_msg),
+    [] = gen_event:which_handlers(Pid),
+    ok.
+
+%% No default provided for init, so it should fail
+undef_handle_event(Config) ->
+    Pid = ?config(event_pid, Config),
+    ok = gen_event:sync_notify(Pid, event_msg),
+    [] = gen_event:which_handlers(Pid),
+
+    gen_event:add_handler(oc_event, oc_event, []),
+    [oc_event] = gen_event:which_handlers(Pid),
+
+    ok = gen_event:notify(Pid, event_msg),
+    [] = gen_event:which_handlers(Pid),
+    ok.
+
+%% Defaulting to doing nothing with a log warning.
+undef_handle_info(Config) when is_list(Config) ->
+    error_logger_forwarder:register(),
+    Pid = ?config(event_pid, Config),
+    Pid ! hej,
+    wait_until_processed(Pid, hej, 10),
+    [oc_event] = gen_event:which_handlers(Pid),
+    receive
+        {warning_msg, _GroupLeader,
+         {Pid, "** Undefined handle_info in " ++ _, [oc_event, hej]}} ->
+            ok;
+        Other ->
+            io:format("Unexpected: ~p", [Other]),
+            ct:fail(failed)
+    end.
+
+wait_until_processed(_Pid, _Message, 0) ->
+    ct:fail(not_processed);
+wait_until_processed(Pid, Message, N) ->
+    {messages, Messages} = erlang:process_info(Pid, messages),
+    case lists:member(Message, Messages) of
+        true ->
+            timer:sleep(100),
+            wait_until_processed(Pid, Message, N-1);
+        false ->
+            ok
+    end.
+
+%% No default provided for init, so it should fail
+undef_code_change(Config) when is_list(Config) ->
+    Pid = ?config(event_pid, Config),
+    {error, {'EXIT', {undef, [{oc_event, code_change, [_, _, _], _}|_]}}} =
+        fake_upgrade(Pid, oc_event),
+    [oc_event] = gen_event:which_handlers(Pid),
+    ok.
+
+%% Defaulting to doing nothing. Test that it works when not defined.
+undef_terminate(Config) when is_list(Config) ->
+    Pid = ?config(event_pid, Config),
+    ok = gen_event:delete_handler(Pid, oc_event, []),
+    [] = gen_event:which_handlers(Pid),
+    ok.
+
+%% Test that the default implementation doesn't catch the wrong undef error
+undef_in_terminate(_Config) ->
+    {ok, Pid} = gen_event:start({local, dummy}),
+    State = {undef_in_terminate, {dummy_h, terminate}},
+    ok = gen_event:add_handler(Pid, dummy_h, {state, State}),
+    [dummy_h] = gen_event:which_handlers(Pid),
+    {'EXIT', {undef, [{dummy_h, terminate, [], []}|_]}}
+        = gen_event:delete_handler(Pid, dummy_h, []),
+    [] = gen_event:which_handlers(Pid),
+    ok.
+
+fake_upgrade(Pid, Mod) ->
+    sys:suspend(Pid),
+    sys:replace_state(Pid, fun(S) -> {new, S} end),
+    Ret = sys:change_code(Pid, Mod, old_vsn, []),
+    ok = sys:resume(Pid),
+    Ret.
diff --git a/lib/stdlib/test/gen_event_SUITE_data/oc_event.erl b/lib/stdlib/test/gen_event_SUITE_data/oc_event.erl
new file mode 100644
index 000000000..eb664ef55
--- /dev/null
+++ b/lib/stdlib/test/gen_event_SUITE_data/oc_event.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_event).
+
+-behaviour(gen_event).
+
+%% API
+-export([start/0]).
+
+%% gen_event callbacks
+-export([init/1]).
+
+-define(SERVER, ?MODULE).
+
+-record(state, {}).
+
+start() ->
+    {ok, Pid} = gen_event:start({local, ?SERVER}),
+    gen_event:add_handler(?SERVER, ?MODULE, []),
+    {ok, Pid}.
+
+init([]) ->
+    {ok, #state{}}.
-- 
2.12.2

openSUSE Build Service is sponsored by