File 2349-wx-make-wx_object-callbacks-optional.patch of Package erlang

From 9e396c8676e5a7eacbe5e7b2d93ee080298eb8fb Mon Sep 17 00:00:00 2001
From: Zandra Norman <zandra@erlang.org>
Date: Tue, 24 Jan 2017 16:13:48 +0100
Subject: [PATCH 4/4] wx: make wx_object callbacks optional

---
 lib/wx/src/wx_object.erl       |  49 ++++++++++---
 lib/wx/test/Makefile           |   1 +
 lib/wx/test/wx_basic_SUITE.erl | 155 ++++++++++++++++++++++++++++++++++++++++-
 lib/wx/test/wx_obj_test.erl    |   5 ++
 lib/wx/test/wx_oc_object.erl   |  44 ++++++++++++
 5 files changed, 243 insertions(+), 11 deletions(-)
 create mode 100644 lib/wx/test/wx_oc_object.erl

diff --git a/lib/wx/src/wx_object.erl b/lib/wx/src/wx_object.erl
index 40170b6eb..1907e3c72 100644
--- a/lib/wx/src/wx_object.erl
+++ b/lib/wx/src/wx_object.erl
@@ -39,19 +39,31 @@
 %%     {wxObject, State} | {wxObject, State, Timeout} |
 %%         ignore | {stop, Reason}
 %%
+%%   Asynchronous window event handling: <br/>
+%%   handle_event(#wx{}, State)  should return <br/>
+%%    {noreply, State} | {noreply, State, Timeout} | {stop, Reason, State} 
+%%
+%% The user module can export the following callback functions:
+%%
 %%   handle_call(Msg, {From, Tag}, State) should return <br/>
 %%    {reply, Reply, State} | {reply, Reply, State, Timeout} |
 %%        {noreply, State} | {noreply, State, Timeout} |
 %%        {stop, Reason, Reply, State}  
 %%
-%%   Asynchronous window event handling: <br/>
-%%   handle_event(#wx{}, State)  should return <br/>
-%%    {noreply, State} | {noreply, State, Timeout} | {stop, Reason, State} 
+%%   handle_cast(Msg, State) should return <br/>
+%%    {noreply, State} | {noreply, State, Timeout} |
+%%        {stop, Reason, State}  
+%%
+%% If the above are not exported but called, the wx_object process will crash.
+%% The user module can also export:
 %%
 %%   Info is message e.g. {'EXIT', P, R}, {nodedown, N}, ...  <br/>
 %%   handle_info(Info, State)  should return , ...  <br/>
 %%    {noreply, State} | {noreply, State, Timeout} | {stop, Reason, State} 
-%% 
+%%
+%% If a message is sent to the wx_object process when handle_info is not
+%% exported, the message will be dropped and ignored.
+%%
 %%   When stop is returned in one of the functions above with Reason =
 %% normal | shutdown | Term, terminate(State) is called. It lets the
 %% user module clean up, it is always called when server terminates or
@@ -135,6 +147,8 @@
     {'noreply', NewState :: term()} |
     {'noreply', NewState :: term(), timeout() | 'hibernate'} |
     {'stop', Reason :: term(), NewState :: term()}.
+-callback handle_sync_event(Request :: #wx{}, Ref :: #wx_ref{}, State :: term()) ->
+    ok.
 -callback terminate(Reason :: ('normal' | 'shutdown' | {'shutdown', term()} |
                                term()),
                     State :: term()) ->
@@ -143,6 +157,9 @@
                       Extra :: term()) ->
     {'ok', NewState :: term()} | {'error', Reason :: term()}.
 
+-optional_callbacks(
+    [handle_call/3, handle_cast/2, handle_info/2,
+     handle_sync_event/3, terminate/2, code_change/3]).
 
 %% System exports
 -export([system_continue/3,
@@ -426,6 +443,7 @@ dispatch(Msg = #wx{}, Mod, State) ->
     Mod:handle_event(Msg, State);
 dispatch(Info, Mod, State) ->
     Mod:handle_info(Info, State).
+
 %% @hidden
 handle_msg({'$gen_call', From, Msg}, Parent, Name, State, Mod) ->
     case catch Mod:handle_call(Msg, From, State) of
@@ -447,8 +465,12 @@ handle_msg({'$gen_call', From, Msg}, Parent, Name, State, Mod) ->
 	Other -> handle_common_reply(Other, Name, Msg, Mod, State, [])
     end;
 handle_msg(Msg, Parent, Name, State, Mod) ->
-    Reply = (catch dispatch(Msg, Mod, State)),
-    handle_no_reply(Reply, Parent, Name, Msg, Mod, State, []).
+    case catch dispatch(Msg, Mod, State) of
+        {'EXIT', {undef, [{Mod, handle_info, [_,_], _}|_]}} ->
+            handle_no_reply({noreply, State}, Parent, Name, Msg, Mod, State, []);
+        Reply ->
+            handle_no_reply(Reply, Parent, Name, Msg, Mod, State, [])
+    end.
 
 %% @hidden
 handle_msg({'$gen_call', From, Msg}, Parent, Name, State, Mod, Debug) ->
@@ -528,8 +550,8 @@ system_terminate(Reason, _Parent, Debug, [Name, State, Mod, _Time]) ->
 %% @hidden
 system_code_change([Name, State, Mod, Time], _Module, OldVsn, Extra) ->
     case catch Mod:code_change(OldVsn, State, Extra) of
-	{ok, NewState} -> {ok, [Name, NewState, Mod, Time]};
-	Else -> Else
+        {ok, NewState} -> {ok, [Name, NewState, Mod, Time]};
+        Else -> Else
     end.
 
 %%-----------------------------------------------------------------
@@ -560,7 +582,7 @@ print_event(Dev, Event, Name) ->
 %%% ---------------------------------------------------
 %% @hidden
 terminate(Reason, Name, Msg, Mod, State, Debug) ->
-    case catch Mod:terminate(Reason, State) of
+    case try_terminate(Mod, Reason, State) of
 	{'EXIT', R} ->
 	    error_info(R, Name, Msg, State, Debug),
 	    exit(R);
@@ -577,6 +599,15 @@ terminate(Reason, Name, Msg, Mod, State, Debug) ->
 		    exit(Reason)
 	    end
     end.
+
+try_terminate(Mod, Reason, State) ->
+    case erlang:function_exported(Mod, terminate, 2) of
+        true ->
+            catch Mod:terminate(Reason, State);
+        _ ->
+            ok
+    end.
+
 %% @hidden
 error_info(_Reason, application_controller, _Msg, _State, _Debug) ->
     ok;
diff --git a/lib/wx/test/Makefile b/lib/wx/test/Makefile
index 9a78307be..965db228f 100644
--- a/lib/wx/test/Makefile
+++ b/lib/wx/test/Makefile
@@ -29,6 +29,7 @@ APPDIR = $(shell dirname $(PWD))
 ERL_COMPILE_FLAGS = -pa $(APPDIR)/ebin
 
 Mods =  wxt wx_test_lib wx_obj_test \
+	wx_oc_object \
 	wx_app_SUITE \
 	wx_basic_SUITE \
 	wx_event_SUITE \
diff --git a/lib/wx/test/wx_basic_SUITE.erl b/lib/wx/test/wx_basic_SUITE.erl
index 6a2528780..d0ec0b1f2 100644
--- a/lib/wx/test/wx_basic_SUITE.erl
+++ b/lib/wx/test/wx_basic_SUITE.erl
@@ -49,10 +49,13 @@ suite() -> [{ct_hooks,[ts_install_cth]}, {timetrap,{minutes,2}}].
 
 all() -> 
     [silent_start, create_window, several_apps, wx_api, wx_misc,
-     data_types, wx_object].
+     data_types, wx_object, {group, undef_callbacks},
+     undef_in_handle_info, undef_in_terminate].
 
 groups() -> 
-    [].
+    [{undef_callbacks, [],
+     [undef_handle_event, undef_handle_call, undef_handle_cast, undef_handle_info,
+      undef_code_change, undef_terminate1, undef_terminate2]}].
 
 init_per_group(_GroupName, Config) ->
     Config.
@@ -426,6 +429,154 @@ wx_object(Config) ->
     catch wx:destroy(),
     ok.
 
+%% Test that the server crashes correctly if the handle_event callback is
+%% not exported in the callback module
+undef_handle_event(TestInfo) when is_atom(TestInfo) -> wx_test_lib:tc_info(TestInfo);
+undef_handle_event(_Config) ->
+    wx:new(),
+    {_, _, _, Pid} = wx_object:start(wx_oc_object, [], []),
+    MRef = monitor(process, Pid),
+    %% Mock a call to handle_event
+    Pid ! {wx, a, b, c, d},
+    ok = receive
+        {'DOWN', MRef, process, Pid,
+         {undef, [{wx_oc_object, handle_event, _, _}|_]}} ->
+            ok
+    after 5000 ->
+        ct:fail(should_crash)
+    end.
+
+%% Test that the server crashes correctly if the handle_call callback is
+%% not exported in the callback module
+undef_handle_call(TestInfo) when is_atom(TestInfo) -> wx_test_lib:tc_info(TestInfo);
+undef_handle_call(_Config) ->
+    wx:new(),
+    Frame = wx_object:start(wx_oc_object, [], []),
+    try
+        wx_object:call(Frame, call_msg),
+        ct:fail(should_crash)
+    catch error:{{undef, [{wx_oc_object,handle_call, _, _}|_]},
+                              {wx_object,call,_}} ->
+        ok
+    end.
+
+%% Test that the server crashes correctly if the handle_cast callback is
+%% not exported in the callback module
+undef_handle_cast(TestInfo) when is_atom(TestInfo) -> wx_test_lib:tc_info(TestInfo);
+undef_handle_cast(_Config) ->
+    wx:new(),
+    {_, _, _, Pid} = Frame = wx_object:start(wx_oc_object, [], []),
+    MRef = monitor(process, Pid),
+    wx_object:cast(Frame, cast_msg),
+    ok = receive
+        {'DOWN', MRef, process, Pid,
+         {undef, [{wx_oc_object, handle_cast, _, _}|_]}} ->
+            ok
+    after 5000 ->
+        ct:fail(should_crash)
+    end.
+
+%% Test the default implementation of handle_info if the callback module
+%% does not export it
+undef_handle_info(TestInfo) when is_atom(TestInfo) -> wx_test_lib:tc_info(TestInfo);
+undef_handle_info(_Config) ->
+    wx:new(),
+    {_, _, _, Pid} = wx_object:start(wx_oc_object, [], []),
+    MRef = monitor(process, Pid),
+    Pid ! test,
+    receive
+        {'DOWN', MRef, process, Pid, _} ->
+            ct:fail(should_not_crash)
+    after 500 ->
+        ok
+    end,
+    ok = wx_object:stop(Pid).
+
+%% Test the server crashes correctly if called and the code_change callback is
+%% not exported in the callback module
+undef_code_change(TestInfo) when is_atom(TestInfo) -> wx_test_lib:tc_info(TestInfo);
+undef_code_change(_Config) ->
+    wx:new(),
+    {_, _, _, Pid} = wx_object:start(wx_oc_object, [], []),
+    sys:suspend(Pid),
+    sys:replace_state(Pid, fun([P, S, M, T]) -> [P, {new, S}, M, T] end),
+    {error, {'EXIT', {undef, [{wx_oc_object,code_change, [_, _, _], _}|_]}}}
+         = sys:change_code(Pid, wx_oc_object, old_vsn, []),
+    ok = sys:resume(Pid),
+    ok = wx_object:stop(Pid).
+
+%% Test the default implementation of terminate if the callback module
+%% does not export it
+undef_terminate1(TestInfo) when is_atom(TestInfo) -> wx_test_lib:tc_info(TestInfo);
+undef_terminate1(_Config) ->
+    ok = terminate([], normal).
+
+%% Test the default implementation of terminate if the callback module
+%% does not export it
+undef_terminate2(TestInfo) when is_atom(TestInfo) -> wx_test_lib:tc_info(TestInfo);
+undef_terminate2(_Config) ->
+    ok = terminate([{error, test}, infinity], {error, test}).
+
+terminate(ArgsTl, Reason) ->
+    wx:new(),
+    {_, _, _, Pid} = wx_object:start(wx_oc_object, [], []),
+    MRef = monitor(process, Pid),
+    ok = apply(wx_object, stop, [Pid|ArgsTl]),
+    receive
+        {'DOWN', MRef, process, Pid, Reason} ->
+            ok
+    after 1000 ->
+        ct:fail(failed)
+    end.
+
+%% Test that the server crashes correctly if the handle_info callback is
+%% calling an undefined function
+undef_in_handle_info(TestInfo) when is_atom(TestInfo) -> wx_test_lib:tc_info(TestInfo);
+undef_in_handle_info(_Config) ->
+    wx:new(),
+    Init = ui_init_fun(),
+    {_, _, _, Pid} = wx_object:start(wx_obj_test,
+                                     [{parent, self()}, {init, Init}], []),
+    unlink(Pid),
+    MRef = monitor(process, Pid),
+    Pid ! {call_undef_fun, {wx_obj_test, handle_info}},
+    receive
+        {'DOWN', MRef, process, Pid,
+         {undef, [{wx_obj_test, handle_info, _, _}|_]}} ->
+            ok
+    after 1000 ->
+        ct:fail(failed)
+    end,
+    ok.
+
+%% Test that the server crashes correctly if the terminate callback is
+%% calling an undefined function
+undef_in_terminate(TestInfo) when is_atom(TestInfo) -> wx_test_lib:tc_info(TestInfo);
+undef_in_terminate(_Config) ->
+    wx:new(),
+    Init = ui_init_fun(),
+    Frame = wx_object:start(wx_obj_test,
+                            [{parent, self()}, {init, Init},
+                             {terminate, {wx_obj_test, terminate}}], []),
+    try
+        wx_object:stop(Frame),
+        ct:fail(should_crash)
+    catch error:{{undef, [{wx_obj_test, terminate, _, _}|_]}, _} ->
+        ok
+    end.
+
+ui_init_fun() ->
+    Init = fun() ->
+        Frame0 = wxFrame:new(wx:null(), ?wxID_ANY, "Test wx_object", [{size, {500, 400}}]),
+        Frame = wx_object:set_pid(Frame0, self()),
+        Sz = wxBoxSizer:new(?wxHORIZONTAL),
+        Panel = wxPanel:new(Frame),
+        wxSizer:add(Sz, Panel, [{flag, ?wxEXPAND}, {proportion, 1}]),
+        wxWindow:show(Frame),
+        {Frame, {Frame, Panel}}
+    end,
+    Init.
+
 check_events(Msgs) ->
     check_events(Msgs, 0,0).
 
diff --git a/lib/wx/test/wx_obj_test.erl b/lib/wx/test/wx_obj_test.erl
index 23142e28b..1b0a9e909 100644
--- a/lib/wx/test/wx_obj_test.erl
+++ b/lib/wx/test/wx_obj_test.erl
@@ -79,6 +79,9 @@ handle_cast(What, State = #state{parent=Pid}) ->
     Pid ! {cast, What},
     {noreply, State}.
 
+handle_info({call_undef_fun, {Mod, Fun}}, State) ->
+    Mod:Fun(),
+    {noreply, State};
 handle_info(What, State = #state{parent=Pid}) ->
     Pid ! {info, What},
     {noreply, State}.
@@ -87,6 +90,8 @@ terminate(What, #state{parent=Pid, opts=Opts, user_state=US}) ->
     case proplists:get_value(terminate, Opts) of
 	undefined ->
 	    ok;
+	{Mod, Fun} ->
+	    Mod:Fun();
 	Terminate ->
 	    Terminate(US)
     end,
diff --git a/lib/wx/test/wx_oc_object.erl b/lib/wx/test/wx_oc_object.erl
new file mode 100644
index 000000000..392420241
--- /dev/null
+++ b/lib/wx/test/wx_oc_object.erl
@@ -0,0 +1,44 @@
+%%
+%% %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(wx_oc_object).
+-include_lib("wx/include/wx.hrl").
+
+-behaviour(wx_object).
+
+%% gen_server callbacks
+-export([init/1]).
+
+-record(state, {}).
+
+init([]) ->
+    Init = fun() ->
+        Frame0 = wxFrame:new(wx:null(), ?wxID_ANY, "Test wx_object", [{size, {500, 400}}]),
+        Frame = wx_object:set_pid(Frame0, self()),
+        Sz = wxBoxSizer:new(?wxHORIZONTAL),
+        Panel = wxPanel:new(Frame),
+        wxSizer:add(Sz, Panel, [{flag, ?wxEXPAND}, {proportion, 1}]),
+        wxWindow:show(Frame),
+        {Frame, {Frame, Panel}}
+    end,
+    {Obj, _UserState} = Init(),
+    {Obj, #state{}};
+init([Init]) ->
+    {Obj, _UserState} = Init(),
+    {Obj, #state{}}.
-- 
2.12.2

openSUSE Build Service is sponsored by