Skip to content

Commit

Permalink
Teach sys:get_status/1,2 to call Mod:format_status/2
Browse files Browse the repository at this point in the history
Restore the ability for gen_server and gen_fsm callback
modules to format their own state for display under the
sys:get_status/1,2 calls.

This ability is extremely useful for new behavior modules
based on gen_server or gen_fsm, so that they can display
their status in a more meaningful way than just dumping
the state record. It is also generally useful for applications
wanting to display their gen_server or gen_fsm callback module
state in something other than the default manner.

Also document the previously undocumented the
gen_server:format_status/2 and gen_fsm:format_status/2 optional
callback functions that, if exported by the callback module, are
invoked when sys:get_status/1,2 are called.

Add unit tests to ensure that format_status/2 functions exported
from a gen_fsm callback module and a gen_server callback module
are called when sys:get_status/1,2 are called.
  • Loading branch information
vinoski committed Dec 2, 2009
1 parent 2a9b7a1 commit 88b530e
Show file tree
Hide file tree
Showing 6 changed files with 117 additions and 9 deletions.
30 changes: 30 additions & 0 deletions lib/stdlib/doc/src/gen_fsm.xml
Original file line number Diff line number Diff line change
Expand Up @@ -729,6 +729,36 @@ gen_fsm:sync_send_all_state_event -----> Module:handle_sync_event/4
updated internal data.</p>
</desc>
</func>
<func>
<name>Module:format_status(normal, [PDict, StateData]) -> Status</name>
<fsummary>Optional function for providing a term describing the
current gen_fsm status.</fsummary>
<type>
<v>PDict = [{Key, Value}]</v>
<v>StateData = term()</v>
<v>Status = [term()]</v>
</type>
<desc>
<p><em>This callback is optional, so callback modules need not
export it. The gen_fsm module provides a default
implementation of this function that returns the callback
module state data.</em></p>
<p>This function is called by a gen_fsm process when one
of <seealso marker="sys#get_status/1">sys:get_status/1,2</seealso>
is invoked to get the gen_fsm status. A callback module
wishing to customise the <c>sys:get_status/1,2</c> return
value exports an instance of <c>format_status/2</c> that
returns a term describing the current status of the
gen_fsm.</p>
<p><c>PDict</c> is the current value of the gen_fsm's
process dictionary.</p>
<p><c>StateData</c> is the internal state data of the
gen_fsm.</p>
<p>The function should return <c>Status</c>, a list of one or
more terms that customise the details of the current state
and status of the gen_fsm.</p>
</desc>
</func>
</funcs>

<section>
Expand Down
29 changes: 29 additions & 0 deletions lib/stdlib/doc/src/gen_server.xml
Original file line number Diff line number Diff line change
Expand Up @@ -598,6 +598,35 @@ gen_server:abcast -----> Module:handle_cast/2
<p>The function should return the updated internal state.</p>
</desc>
</func>
<func>
<name>Module:format_status(normal, [PDict, State]) -> Status</name>
<fsummary>Optional function for providing a term describing the
current gen_server status.</fsummary>
<type>
<v>PDict = [{Key, Value}]</v>
<v>State = term()</v>
<v>Status = [term()]</v>
</type>
<desc>
<p><em>This callback is optional, so callback modules need not
export it. The gen_server module provides a default
implementation of this function that returns the callback
module state.</em></p>
<p>This function is called by a gen_server process when one
of <seealso marker="sys#get_status/1">sys:get_status/1,2</seealso>
is invoked to get the gen_server status. A callback module
wishing to customise the <c>sys:get_status/1,2</c> return
value exports an instance of <c>format_status/2</c> that
returns a term describing the current status of the
gen_server.</p>
<p><c>PDict</c> is the current value of the gen_server's
process dictionary.</p>
<p><c>State</c> is the internal state of the gen_server.</p>
<p>The function should return <c>Status</c>, a list of one or
more terms that customise the details of the current state
and status of the gen_server.</p>
</desc>
</func>
</funcs>

<section>
Expand Down
11 changes: 11 additions & 0 deletions lib/stdlib/doc/src/sys.xml
Original file line number Diff line number Diff line change
Expand Up @@ -237,6 +237,17 @@
</type>
<desc>
<p>Gets the status of the process.</p>
<p>The value of <c>Misc</c> varies for different types of
processes. For example, a <c>gen_server</c> process returns
the callback module's state, and a <c>gen_fsm</c> process
returns information such as its current state name. Callback
modules for <c>gen_server</c> and <c>gen_fsm</c> can also
customise the value of <c>Misc</c> by exporting
a <c>format_status/2</c> function that contributes
module-specific information;
see <seealso marker="gen_server#format_status/2">gen_server:format_status/2</seealso>
and <seealso marker="gen_fsm#format_status/2">gen_fsm:format_status/2</seealso>
for more details.</p>
</desc>
</func>
<func>
Expand Down
11 changes: 10 additions & 1 deletion lib/stdlib/src/sys.erl
Original file line number Diff line number Diff line change
Expand Up @@ -245,8 +245,17 @@ do_cmd(SysState, Other, _Parent, _Mod, Debug, Misc) ->
{SysState, {error, {unknown_system_msg, Other}}, Debug, Misc}.

get_status(SysState, Parent, Mod, Debug, Misc) ->
PDict = get(),
FmtMisc =
case erlang:function_exported(Mod, format_status, 2) of
true ->
FmtArgs = [PDict, SysState, Parent, Debug, Misc],
Mod:format_status(normal, FmtArgs);
_ ->
Misc
end,
{status, self(), {module, Mod},
[get(), SysState, Parent, Debug, Misc]}.
[PDict, SysState, Parent, Debug, FmtMisc]}.

%%-----------------------------------------------------------------
%% These are the system debug commands.
Expand Down
16 changes: 13 additions & 3 deletions lib/stdlib/test/gen_fsm_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,7 @@

-export([shutdown/1]).

-export([sys/1, sys1/1]).
-export([sys/1, sys1/1, call_format_status/1]).

-export([hibernate/1,hiber_idle/3,hiber_wakeup/3,hiber_idle/2,hiber_wakeup/2]).

Expand All @@ -42,7 +42,7 @@

% The gen_fsm behaviour
-export([init/1, handle_event/3, handle_sync_event/4, terminate/3,
handle_info/3]).
handle_info/3, format_status/2]).
-export([idle/2, idle/3,
timeout/2,
wfor_conf/2, wfor_conf/3,
Expand Down Expand Up @@ -305,7 +305,7 @@ shutdown(Config) when is_list(Config) ->
ok.


sys(suite) -> [sys1].
sys(suite) -> [sys1, call_format_status].

sys1(Config) when is_list(Config) ->
?line {ok, Pid} =
Expand All @@ -317,6 +317,13 @@ sys1(Config) when is_list(Config) ->
?line sys:resume(Pid),
?line stop_it(Pid).

call_format_status(Config) when is_list(Config) ->
?line {ok, Pid} = gen_fsm:start(gen_fsm_SUITE, [], []),
?line Status = sys:get_status(Pid),
?line {status, Pid, _Mod, [_PDict, running, _Parent, _, Data]} = Status,
?line [format_status_called | _] = lists:reverse(Data),
?line stop_it(Pid).


%% Hibernation
hibernate(suite) -> [];
Expand Down Expand Up @@ -836,3 +843,6 @@ handle_sync_event(stop_shutdown_reason, _From, _State, Data) ->
{stop, {shutdown,reason}, {shutdown,reason}, Data};
handle_sync_event({get, _Pid}, _From, State, Data) ->
{reply, {state, State, Data}, State, Data}.

format_status(_Opt, [_Pdict, _StateData]) ->
[format_status_called].
29 changes: 24 additions & 5 deletions lib/stdlib/test/gen_server_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,7 @@
call_remote_n1/1, call_remote_n2/1, call_remote_n3/1, spec_init/1,
spec_init_local_registered_parent/1,
spec_init_global_registered_parent/1,
otp_5854/1, hibernate/1, otp_7669/1
otp_5854/1, hibernate/1, otp_7669/1, call_format_status/1
]).

% spawn export
Expand All @@ -42,7 +42,7 @@

% The gen_server behaviour
-export([init/1, handle_call/3, handle_cast/2,
handle_info/2, terminate/2]).
handle_info/2, terminate/2, format_status/2]).

all(suite) ->
[start, crash, call, cast, cast_fast, info,
Expand All @@ -51,7 +51,7 @@ all(suite) ->
call_remote_n2, call_remote_n3, spec_init,
spec_init_local_registered_parent,
spec_init_global_registered_parent,
otp_5854,hibernate,otp_7669].
otp_5854, hibernate, otp_7669, call_format_status].

-define(default_timeout, ?t:minutes(1)).

Expand Down Expand Up @@ -851,7 +851,7 @@ otp_5854(Config) when is_list(Config) ->
ok.

%% If initialization fails (with ignore or {stop,Reason}),
%% make sure that the process is not registered when gen_sever:start()
%% make sure that the process is not registered when gen_server:start()
%% returns.

otp_7669(Config) when is_list(Config) ->
Expand Down Expand Up @@ -887,6 +887,24 @@ do_otp_7669_stop() ->
?MODULE, stop, []),
?line undefined = global:whereis_name(?MODULE).

%% Verify that sys:get_status correctly calls our format_status/2 fun
%%
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_server:start_link({local, call_format_status},
gen_server_SUITE, [], []),
?line Status1 = sys:get_status(call_format_status),
?line {status, Pid, _Mod, [_PDict, running, _Parent, _, Data1]} = Status1,
?line [format_status_called | _] = lists:reverse(Data1),
?line Status2 = sys:get_status(call_format_status, 5000),
?line {status, Pid, _Mod, [_PDict, running, _Parent, _, Data2]} = Status2,
?line [format_status_called | _] = lists:reverse(Data2),
ok.


%%--------------------------------------------------------------
%% Help functions to spec_init_*
start_link(Init, Options) ->
Expand Down Expand Up @@ -1046,4 +1064,5 @@ terminate({From, stopped_info}, _State) ->
terminate(_Reason, _State) ->
ok.


format_status(_Opt, [_PDict, _State]) ->
[format_status_called].

0 comments on commit 88b530e

Please sign in to comment.