aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src/sys.erl
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/src/sys.erl')
-rw-r--r--lib/stdlib/src/sys.erl236
1 files changed, 174 insertions, 62 deletions
diff --git a/lib/stdlib/src/sys.erl b/lib/stdlib/src/sys.erl
index f34201604c..a6ecf03716 100644
--- a/lib/stdlib/src/sys.erl
+++ b/lib/stdlib/src/sys.erl
@@ -1,18 +1,19 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2011. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2016. All Rights Reserved.
%%
-%% The contents of this file are subject to the Erlang Public License,
-%% Version 1.1, (the "License"); you may not use this file except in
-%% compliance with the License. You should have received a copy of the
-%% Erlang Public License along with this software. If not, it can be
-%% retrieved online at http://www.erlang.org/.
-%%
-%% Software distributed under the License is distributed on an "AS IS"
-%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
-%% the License for the specific language governing rights and limitations
-%% under the License.
+%% 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%
%%
@@ -21,7 +22,10 @@
%% External exports
-export([suspend/1, suspend/2, resume/1, resume/2,
get_status/1, get_status/2,
+ get_state/1, get_state/2,
+ replace_state/2, replace_state/3,
change_code/4, change_code/5,
+ terminate/2, terminate/3,
log/2, log/3, trace/2, trace/3, statistics/2, statistics/3,
log_to_file/2, log_to_file/3, no_debug/1, no_debug/2,
install/2, install/3, remove/2, remove/3]).
@@ -32,37 +36,52 @@
%% Types
%%-----------------------------------------------------------------
+-export_type([dbg_opt/0]).
+
-type name() :: pid() | atom() | {'global', atom()}.
-type system_event() :: {'in', Msg :: _}
| {'in', Msg :: _, From :: _}
| {'out', Msg :: _, To :: _}
| term().
--opaque dbg_opt() :: list().
+-opaque dbg_opt() :: {'trace', 'true'}
+ | {'log',
+ {N :: non_neg_integer(),
+ [{Event :: system_event(),
+ FuncState :: _,
+ FormFunc :: format_fun()}]}}
+ | {'statistics', {file:date_time(),
+ {'reductions', non_neg_integer()},
+ MessagesIn :: non_neg_integer(),
+ MessagesOut :: non_neg_integer()}}
+ | {'log_to_file', file:io_device()}
+ | {Func :: dbg_fun(), FuncState :: term()}.
-type dbg_fun() :: fun((FuncState :: _,
Event :: system_event(),
ProcState :: _) -> 'done' | (NewFuncState :: _)).
+-type format_fun() :: fun((Device :: io:device() | file:io_device(),
+ Event :: system_event(),
+ Extra :: term()) -> any()).
+
%%-----------------------------------------------------------------
%% System messages
%%-----------------------------------------------------------------
--spec suspend(Name) -> Void when
- Name :: name(),
- Void :: term().
+-spec suspend(Name) -> 'ok' when
+ Name :: name().
suspend(Name) -> send_system_msg(Name, suspend).
--spec suspend(Name, Timeout) -> Void when
+
+-spec suspend(Name, Timeout) -> 'ok' when
Name :: name(),
- Timeout :: timeout(),
- Void :: term().
+ Timeout :: timeout().
suspend(Name, Timeout) -> send_system_msg(Name, suspend, Timeout).
--spec resume(Name) -> Void when
- Name :: name(),
- Void :: term().
+-spec resume(Name) -> 'ok' when
+ Name :: name().
resume(Name) -> send_system_msg(Name, resume).
--spec resume(Name, Timeout) -> Void when
+
+-spec resume(Name, Timeout) -> 'ok' when
Name :: name(),
- Timeout :: timeout(),
- Void :: term().
+ Timeout :: timeout().
resume(Name, Timeout) -> send_system_msg(Name, resume, Timeout).
-spec get_status(Name) -> Status when
@@ -71,9 +90,10 @@ resume(Name, Timeout) -> send_system_msg(Name, resume, Timeout).
SItem :: (PDict :: [{Key :: term(), Value :: term()}])
| (SysState :: 'running' | 'suspended')
| (Parent :: pid())
- | (Dbg :: dbg_opt())
+ | (Dbg :: [dbg_opt()])
| (Misc :: term()).
get_status(Name) -> send_system_msg(Name, get_status).
+
-spec get_status(Name, Timeout) -> Status when
Name :: name(),
Timeout :: timeout(),
@@ -81,10 +101,50 @@ get_status(Name) -> send_system_msg(Name, get_status).
SItem :: (PDict :: [{Key :: term(), Value :: term()}])
| (SysState :: 'running' | 'suspended')
| (Parent :: pid())
- | (Dbg :: dbg_opt())
+ | (Dbg :: [dbg_opt()])
| (Misc :: term()).
get_status(Name, Timeout) -> send_system_msg(Name, get_status, Timeout).
+-spec get_state(Name) -> State when
+ Name :: name(),
+ State :: term().
+get_state(Name) ->
+ case send_system_msg(Name, get_state) of
+ {error, Reason} -> error(Reason);
+ State -> State
+ end.
+
+-spec get_state(Name, Timeout) -> State when
+ Name :: name(),
+ Timeout :: timeout(),
+ State :: term().
+get_state(Name, Timeout) ->
+ case send_system_msg(Name, get_state, Timeout) of
+ {error, Reason} -> error(Reason);
+ State -> State
+ end.
+
+-spec replace_state(Name, StateFun) -> NewState when
+ Name :: name(),
+ StateFun :: fun((State :: term()) -> NewState :: term()),
+ NewState :: term().
+replace_state(Name, StateFun) ->
+ case send_system_msg(Name, {replace_state, StateFun}) of
+ {error, Reason} -> error(Reason);
+ State -> State
+ end.
+
+-spec replace_state(Name, StateFun, Timeout) -> NewState when
+ Name :: name(),
+ StateFun :: fun((State :: term()) -> NewState :: term()),
+ Timeout :: timeout(),
+ NewState :: term().
+replace_state(Name, StateFun, Timeout) ->
+ case send_system_msg(Name, {replace_state, StateFun}, Timeout) of
+ {error, Reason} -> error(Reason);
+ State -> State
+ end.
+
-spec change_code(Name, Module, OldVsn, Extra) -> 'ok' | {error, Reason} when
Name :: name(),
Module :: module(),
@@ -93,6 +153,7 @@ get_status(Name, Timeout) -> send_system_msg(Name, get_status, Timeout).
Reason :: term().
change_code(Name, Mod, Vsn, Extra) ->
send_system_msg(Name, {change_code, Mod, Vsn, Extra}).
+
-spec change_code(Name, Module, OldVsn, Extra, Timeout) ->
'ok' | {error, Reason} when
Name :: name(),
@@ -104,6 +165,19 @@ change_code(Name, Mod, Vsn, Extra) ->
change_code(Name, Mod, Vsn, Extra, Timeout) ->
send_system_msg(Name, {change_code, Mod, Vsn, Extra}, Timeout).
+-spec terminate(Name, Reason) -> 'ok' when
+ Name :: name(),
+ Reason :: term().
+terminate(Name, Reason) ->
+ send_system_msg(Name, {terminate, Reason}).
+
+-spec terminate(Name, Reason, Timeout) -> 'ok' when
+ Name :: name(),
+ Reason :: term(),
+ Timeout :: timeout().
+terminate(Name, Reason, Timeout) ->
+ send_system_msg(Name, {terminate, Reason}, Timeout).
+
%%-----------------------------------------------------------------
%% Debug commands
%%-----------------------------------------------------------------
@@ -189,35 +263,33 @@ no_debug(Name) -> send_system_msg(Name, {debug, no_debug}).
Timeout :: timeout().
no_debug(Name, Timeout) -> send_system_msg(Name, {debug, no_debug}, Timeout).
--spec install(Name, FuncSpec) -> Void when
+-spec install(Name, FuncSpec) -> 'ok' when
Name :: name(),
FuncSpec :: {Func, FuncState},
Func :: dbg_fun(),
- FuncState :: term(),
- Void :: term().
+ FuncState :: term().
install(Name, {Func, FuncState}) ->
send_system_msg(Name, {debug, {install, {Func, FuncState}}}).
--spec install(Name, FuncSpec, Timeout) -> Void when
+
+-spec install(Name, FuncSpec, Timeout) -> 'ok' when
Name :: name(),
FuncSpec :: {Func, FuncState},
Func :: dbg_fun(),
FuncState :: term(),
- Timeout :: timeout(),
- Void :: term().
+ Timeout :: timeout().
install(Name, {Func, FuncState}, Timeout) ->
send_system_msg(Name, {debug, {install, {Func, FuncState}}}, Timeout).
--spec remove(Name, Func) -> Void when
+-spec remove(Name, Func) -> 'ok' when
Name :: name(),
- Func :: dbg_fun(),
- Void :: term().
+ Func :: dbg_fun().
remove(Name, Func) ->
send_system_msg(Name, {debug, {remove, Func}}).
--spec remove(Name, Func, Timeout) -> Void when
+
+-spec remove(Name, Func, Timeout) -> 'ok' when
Name :: name(),
Func :: dbg_fun(),
- Timeout :: timeout(),
- Void :: term().
+ Timeout :: timeout().
remove(Name, Func, Timeout) ->
send_system_msg(Name, {debug, {remove, Func}}, Timeout).
@@ -241,39 +313,36 @@ mfa(Name, {debug, {Func, Arg2}}) ->
{sys, Func, [Name, Arg2]};
mfa(Name, {change_code, Mod, Vsn, Extra}) ->
{sys, change_code, [Name, Mod, Vsn, Extra]};
+mfa(Name, {terminate, Reason}) ->
+ {sys, terminate, [Name, Reason]};
mfa(Name, Atom) ->
{sys, Atom, [Name]}.
+
mfa(Name, Req, Timeout) ->
{M, F, A} = mfa(Name, Req),
{M, F, A ++ [Timeout]}.
%%-----------------------------------------------------------------
%% Func: handle_system_msg/6
-%% Args: Msg ::= term()
-%% From ::= {pid(),Ref} but don't count on that
-%% Parent ::= pid()
-%% Module ::= atom()
-%% Debug ::= [debug_opts()]
-%% Misc ::= term()
%% Purpose: Used by a process module that wishes to take care of
%% system messages. The process receives a {system, From,
%% Msg} message, and passes the Msg to this function.
%% Returns: This function *never* returns! It calls the function
%% Module:system_continue(Parent, NDebug, Misc)
%% there the process continues the execution or
-%% Module:system_terminate(Raeson, Parent, Debug, Misc) if
+%% Module:system_terminate(Reason, Parent, Debug, Misc) if
%% the process should terminate.
%% The Module must export system_continue/3, system_terminate/4
%% and format_status/2 for status information.
%%-----------------------------------------------------------------
--spec handle_system_msg(Msg, From, Parent, Module, Debug, Misc) -> Void when
+-spec handle_system_msg(Msg, From, Parent, Module, Debug, Misc) ->
+ no_return() when
Msg :: term(),
From :: {pid(), Tag :: _},
Parent :: pid(),
Module :: module(),
Debug :: [dbg_opt()],
- Misc :: term(),
- Void :: term().
+ Misc :: term().
handle_system_msg(Msg, From, Parent, Module, Debug, Misc) ->
handle_system_msg(running, Msg, From, Parent, Module, Debug, Misc, false).
@@ -283,26 +352,25 @@ handle_system_msg(Msg, From, Parent, Mod, Debug, Misc, Hib) ->
handle_system_msg(SysState, Msg, From, Parent, Mod, Debug, Misc, Hib) ->
case do_cmd(SysState, Msg, Parent, Mod, Debug, Misc) of
{suspended, Reply, NDebug, NMisc} ->
- gen:reply(From, Reply),
+ _ = gen:reply(From, Reply),
suspend_loop(suspended, Parent, Mod, NDebug, NMisc, Hib);
{running, Reply, NDebug, NMisc} ->
- gen:reply(From, Reply),
- Mod:system_continue(Parent, NDebug, NMisc)
+ _ = gen:reply(From, Reply),
+ Mod:system_continue(Parent, NDebug, NMisc);
+ {{terminating, Reason}, Reply, NDebug, NMisc} ->
+ _ = gen:reply(From, Reply),
+ Mod:system_terminate(Reason, Parent, NDebug, NMisc)
end.
%%-----------------------------------------------------------------
%% Func: handle_debug/4
-%% Args: Debug ::= [debug_opts()]
-%% Func ::= {M,F} | fun() arity 3
-%% State ::= term()
-%% Event ::= {in, Msg} | {in, Msg, From} | {out, Msg, To} | term()
%% Purpose: Called by a process that wishes to debug an event.
%% Func is a formatting function, called as Func(Device, Event).
%% Returns: [debug_opts()]
%%-----------------------------------------------------------------
-spec handle_debug(Debug, FormFunc, Extra, Event) -> [dbg_opt()] when
Debug :: [dbg_opt()],
- FormFunc :: dbg_fun(),
+ FormFunc :: format_fun(),
Extra :: term(),
Event :: system_event().
handle_debug([{trace, true} | T], FormFunc, State, Event) ->
@@ -360,12 +428,19 @@ do_cmd(_, suspend, _Parent, _Mod, Debug, Misc) ->
{suspended, ok, Debug, Misc};
do_cmd(_, resume, _Parent, _Mod, Debug, Misc) ->
{running, ok, Debug, Misc};
+do_cmd(SysState, get_state, _Parent, Mod, Debug, Misc) ->
+ {SysState, do_get_state(Mod, Misc), Debug, Misc};
+do_cmd(SysState, {replace_state, StateFun}, _Parent, Mod, Debug, Misc) ->
+ {Res, NMisc} = do_replace_state(StateFun, Mod, Misc),
+ {SysState, Res, Debug, NMisc};
do_cmd(SysState, get_status, Parent, Mod, Debug, Misc) ->
Res = get_status(SysState, Parent, Mod, Debug, Misc),
{SysState, Res, Debug, Misc};
do_cmd(SysState, {debug, What}, _Parent, _Mod, Debug, Misc) ->
{Res, NDebug} = debug_cmd(What, Debug),
{SysState, Res, NDebug, Misc};
+do_cmd(_, {terminate, Reason}, _Parent, _Mod, Debug, Misc) ->
+ {{terminating, Reason}, ok, Debug, Misc};
do_cmd(suspended, {change_code, Module, Vsn, Extra}, _Parent,
Mod, Debug, Misc) ->
{Res, NMisc} = do_change_code(Mod, Module, Vsn, Extra, Misc),
@@ -373,6 +448,40 @@ do_cmd(suspended, {change_code, Module, Vsn, Extra}, _Parent,
do_cmd(SysState, Other, _Parent, _Mod, Debug, Misc) ->
{SysState, {error, {unknown_system_msg, Other}}, Debug, Misc}.
+do_get_state(Mod, Misc) ->
+ case erlang:function_exported(Mod, system_get_state, 1) of
+ true ->
+ try
+ {ok, State} = Mod:system_get_state(Misc),
+ State
+ catch
+ Cl:Exc ->
+ {error, {callback_failed,{Mod,system_get_state},{Cl,Exc}}}
+ end;
+ false ->
+ Misc
+ end.
+
+do_replace_state(StateFun, Mod, Misc) ->
+ case erlang:function_exported(Mod, system_replace_state, 2) of
+ true ->
+ try
+ {ok, State, NMisc} = Mod:system_replace_state(StateFun, Misc),
+ {State, NMisc}
+ catch
+ Cl:Exc ->
+ {{error, {callback_failed,{Mod,system_replace_state},{Cl,Exc}}}, Misc}
+ end;
+ false ->
+ try
+ NMisc = StateFun(Misc),
+ {NMisc, NMisc}
+ catch
+ Cl:Exc ->
+ {{error, {callback_failed,StateFun,{Cl,Exc}}}, Misc}
+ end
+ end.
+
get_status(SysState, Parent, Mod, Debug, Misc) ->
PDict = get(),
FmtMisc =
@@ -451,6 +560,7 @@ print_event(Dev, {Event, State, FormFunc}) ->
FormFunc(Dev, Event, State).
init_stat() -> {erlang:localtime(), process_info(self(), reductions), 0, 0}.
+
get_stat({Time, {reductions, Reds}, In, Out}) ->
{reductions, Reds2} = process_info(self(), reductions),
[{start_time, Time}, {current_time, erlang:localtime()},
@@ -490,9 +600,8 @@ get_debug2(Item, Debug, Default) ->
_ -> Default
end.
--spec print_log(Debug) -> Void when
- Debug :: [dbg_opt()],
- Void :: term().
+-spec print_log(Debug) -> 'ok' when
+ Debug :: [dbg_opt()].
print_log(Debug) ->
{_N, Logs} = get_debug(log, Debug, {0, []}),
lists:foreach(fun print_event/1,
@@ -509,8 +618,6 @@ close_log_file(Debug) ->
%%-----------------------------------------------------------------
%% Func: debug_options/1
-%% Args: [trace|log|{log,N}|statistics|{log_to_file, FileName}|
-%% {install, {Func, FuncState}}]
%% Purpose: Initiate a debug structure. Called by a process that
%% wishes to initiate the debug structure without the
%% system messages.
@@ -519,7 +626,11 @@ close_log_file(Debug) ->
-spec debug_options(Options) -> [dbg_opt()] when
Options :: [Opt],
- Opt :: 'trace' | 'log' | 'statistics' | {'log_to_file', FileName}
+ Opt :: 'trace'
+ | 'log'
+ | {'log', pos_integer()}
+ | 'statistics'
+ | {'log_to_file', FileName}
| {'install', FuncSpec},
FileName :: file:name(),
FuncSpec :: {Func, FuncState},
@@ -527,6 +638,7 @@ close_log_file(Debug) ->
FuncState :: term().
debug_options(Options) ->
debug_options(Options, []).
+
debug_options([trace | T], Debug) ->
debug_options(T, install_debug(trace, true, Debug));
debug_options([log | T], Debug) ->