aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test
diff options
context:
space:
mode:
authorSteve Vinoski <[email protected]>2010-02-28 00:13:10 -0500
committerBjörn Gustavsson <[email protected]>2010-05-12 07:40:26 +0200
commit6281020ef3ac85afbfbe811de662ae5e1f19901d (patch)
treebb1c66bc55011631d0ba706908a8e917e6ab754c /lib/stdlib/test
parent5ec0ade4105d5d72f318b657bff1a628881cbf9d (diff)
downloadotp-6281020ef3ac85afbfbe811de662ae5e1f19901d.tar.gz
otp-6281020ef3ac85afbfbe811de662ae5e1f19901d.tar.bz2
otp-6281020ef3ac85afbfbe811de662ae5e1f19901d.zip
Add support for the format_status callback to gen_event
The gen_server and gen_fsm behaviors support the format_status callback to allow developers to specialize how callback module state appears within the return value of sys:get_status and within logged output resulting from abnormal process termination. This patch adds similar support to gen_event. Event handlers that export a format_status/2 function, which is an optional callback, and are registered with an event manager will now have their format_status callbacks invoked when sys:get_status is called on the event manager. The term returned from format_status for this case replaces the default handler state in the sys:get_status return value. This patch also extends gen_event to call an event handler's format_status function (if it exports one) should the handler terminate abnormally. The term returned from format_status is logged in place of the handler's state. This is intended to allow developers to control how much output is logged in the case of abnormal termination. The documentation is appropriately extended and new unit tests are added to cover the new gen_event format_status functionality.
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r--lib/stdlib/test/dummy1_h.erl5
-rw-r--r--lib/stdlib/test/gen_event_SUITE.erl59
2 files changed, 60 insertions, 4 deletions
diff --git a/lib/stdlib/test/dummy1_h.erl b/lib/stdlib/test/dummy1_h.erl
index 4377d774a3..8bbe729646 100644
--- a/lib/stdlib/test/dummy1_h.erl
+++ b/lib/stdlib/test/dummy1_h.erl
@@ -21,7 +21,7 @@
%% Test event handler for gen_event_SUITE.erl
-export([init/1, handle_event/2, handle_call/2, handle_info/2,
- terminate/2]).
+ terminate/2, format_status/2]).
init(make_error) ->
{error, my_error};
@@ -67,4 +67,5 @@ terminate(remove_handler, Parent) ->
terminate(_Reason, _State) ->
ok.
-
+format_status(_Opt, [_PDict, _State]) ->
+ "dummy1_h handler state".
diff --git a/lib/stdlib/test/gen_event_SUITE.erl b/lib/stdlib/test/gen_event_SUITE.erl
index 8cbffaca56..4f7de451e3 100644
--- a/lib/stdlib/test/gen_event_SUITE.erl
+++ b/lib/stdlib/test/gen_event_SUITE.erl
@@ -23,9 +23,11 @@
-export([all/1]).
-export([start/1, test_all/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]).
+ notify/1, sync_notify/1, call/1, info/1, hibernate/1,
+ call_format_status/1, error_format_status/1]).
-all(suite) -> {req, [stdlib], [start, test_all, hibernate]}.
+all(suite) -> {req, [stdlib], [start, test_all, hibernate,
+ call_format_status, error_format_status]}.
%% --------------------------------------
%% Start an event manager.
@@ -844,3 +846,56 @@ info(Config) when is_list(Config) ->
?line ok = gen_event:stop(my_dummy_handler),
ok.
+
+call_format_status(suite) ->
+ [];
+call_format_status(doc) ->
+ ["Test that sys:get_status/1,2 calls format_status/2"];
+call_format_status(Config) when is_list(Config) ->
+ ?line {ok, Pid} = gen_event:start({local, my_dummy_handler}),
+ %% State here intentionally differs from what we expect from format_status
+ State = self(),
+ FmtState = "dummy1_h handler state",
+ ?line ok = gen_event:add_handler(my_dummy_handler, dummy1_h, [State]),
+ ?line Status1 = sys:get_status(Pid),
+ ?line Status2 = sys:get_status(Pid, 5000),
+ ?line ok = gen_event:stop(Pid),
+ ?line {status, Pid, _, [_, _, Pid, [], Data1]} = Status1,
+ ?line HandlerInfo1 = proplists:get_value(items, Data1),
+ ?line {"Installed handlers", [{_,dummy1_h,_,FmtState,_}]} = HandlerInfo1,
+ ?line {status, Pid, _, [_, _, Pid, [], Data2]} = Status2,
+ ?line HandlerInfo2 = proplists:get_value(items, Data2),
+ ?line {"Installed handlers", [{_,dummy1_h,_,FmtState,_}]} = HandlerInfo2,
+ ok.
+
+error_format_status(suite) ->
+ [];
+error_format_status(doc) ->
+ ["Test that a handler error calls format_status/2"];
+error_format_status(Config) when is_list(Config) ->
+ ?line error_logger_forwarder:register(),
+ OldFl = process_flag(trap_exit, true),
+ State = self(),
+ ?line {ok, Pid} = gen_event:start({local, my_dummy_handler}),
+ ?line ok = gen_event:add_sup_handler(my_dummy_handler, dummy1_h, [State]),
+ ?line ok = gen_event:notify(my_dummy_handler, do_crash),
+ ?line receive
+ {gen_event_EXIT,dummy1_h,{'EXIT',_}} -> ok
+ after 5000 ->
+ ?t:fail(exit_gen_event)
+ end,
+ FmtState = "dummy1_h handler state",
+ receive
+ {error,_GroupLeader, {Pid,
+ "** gen_event handler"++_,
+ [dummy1_h,my_dummy_handler,do_crash,
+ FmtState, _]}} ->
+ ok;
+ Other ->
+ ?line io:format("Unexpected: ~p", [Other]),
+ ?line ?t:fail()
+ end,
+ ?t:messages_get(),
+ ?line ok = gen_event:stop(Pid),
+ process_flag(trap_exit, OldFl),
+ ok.