diff options
Diffstat (limited to 'lib/stdlib/src/supervisor.erl')
-rw-r--r-- | lib/stdlib/src/supervisor.erl | 98 |
1 files changed, 69 insertions, 29 deletions
diff --git a/lib/stdlib/src/supervisor.erl b/lib/stdlib/src/supervisor.erl index 09a01a9aea..e60706ed05 100644 --- a/lib/stdlib/src/supervisor.erl +++ b/lib/stdlib/src/supervisor.erl @@ -35,19 +35,28 @@ %%-------------------------------------------------------------------------- --export_type([child_spec/0, del_err/0, startchild_ret/0, strategy/0]). +-export_type([child_spec/0, startchild_ret/0, strategy/0]). %%-------------------------------------------------------------------------- --type child_id() :: pid() | 'undefined'. --type mfargs() :: {module(), atom(), [term()] | undefined}. +-type child() :: pid() | 'undefined'. +-type child_id() :: term(). +-type mfargs() :: {M :: module(), F :: atom(), A :: [term()] | undefined}. -type modules() :: [module()] | 'dynamic'. -type restart() :: 'permanent' | 'transient' | 'temporary'. -type shutdown() :: 'brutal_kill' | timeout(). -type worker() :: 'worker' | 'supervisor'. --type sup_name() :: {'local', atom()} | {'global', atom()}. --type sup_ref() :: atom() | {atom(), atom()} | {'global', atom()} | pid(). --type child_spec() :: {term(),mfargs(),restart(),shutdown(),worker(),modules()}. +-type sup_name() :: {'local', Name :: atom()} | {'global', Name :: atom()}. +-type sup_ref() :: (Name :: atom()) + | {Name :: atom(), Node :: node()} + | {'global', Name :: atom()} + | pid(). +-type child_spec() :: {Id :: child_id(), + StartFunc :: mfargs(), + Restart :: restart(), + Shutdown :: shutdown(), + Type :: worker(), + Modules :: modules()}. -type strategy() :: 'one_for_all' | 'one_for_one' | 'rest_for_one' | 'simple_one_for_one'. @@ -55,14 +64,14 @@ %%-------------------------------------------------------------------------- -record(child, {% pid is undefined when child is not running - pid = undefined :: child_id(), + pid = undefined :: child(), name, mfargs :: mfargs(), restart_type :: restart(), shutdown :: shutdown(), child_type :: worker(), modules = [] :: modules()}). --type child() :: #child{}. +-type child_rec() :: #child{}. -define(DICT, dict). -define(SETS, sets). @@ -70,7 +79,7 @@ -record(state, {name, strategy :: strategy(), - children = [] :: [child()], + children = [] :: [child_rec()], dynamics :: ?DICT() | ?SET(), intensity :: non_neg_integer(), period :: pos_integer(), @@ -99,11 +108,16 @@ behaviour_info(_Other) -> -type startlink_err() :: {'already_started', pid()} | 'shutdown' | term(). -type startlink_ret() :: {'ok', pid()} | 'ignore' | {'error', startlink_err()}. --spec start_link(module(), term()) -> startlink_ret(). +-spec start_link(Module, Args) -> startlink_ret() when + Module :: module(), + Args :: term(). start_link(Mod, Args) -> gen_server:start_link(supervisor, {self, Mod, Args}, []). --spec start_link(sup_name(), module(), term()) -> startlink_ret(). +-spec start_link(SupName, Module, Args) -> startlink_ret() when + SupName :: sup_name(), + Module :: module(), + Args :: term(). start_link(SupName, Mod, Args) -> gen_server:start_link(SupName, supervisor, {SupName, Mod, Args}, []). @@ -111,24 +125,33 @@ start_link(SupName, Mod, Args) -> %%% Interface functions. %%% --------------------------------------------------- --type info() :: term(). -type startchild_err() :: 'already_present' - | {'already_started', child_id()} | term(). --type startchild_ret() :: {'ok', child_id()} | {'ok', child_id(), info()} + | {'already_started', Child :: child()} | term(). +-type startchild_ret() :: {'ok', Child :: child()} + | {'ok', Child :: child(), Info :: term()} | {'error', startchild_err()}. --spec start_child(sup_ref(), child_spec() | [term()]) -> startchild_ret(). +-spec start_child(SupRef, ChildSpec) -> startchild_ret() when + SupRef :: sup_ref(), + ChildSpec :: child_spec() | (List :: [term()]). start_child(Supervisor, ChildSpec) -> call(Supervisor, {start_child, ChildSpec}). --type restart_err() :: 'running' | 'not_found' | 'simple_one_for_one' | term(). --spec restart_child(sup_ref(), term()) -> - {'ok', child_id()} | {'ok', child_id(), info()} | {'error', restart_err()}. +-spec restart_child(SupRef, Id) -> Result when + SupRef :: sup_ref(), + Id :: child_id(), + Result :: {'ok', Child :: child()} + | {'ok', Child :: child(), Info :: term()} + | {'error', Error}, + Error :: 'running' | 'not_found' | 'simple_one_for_one' | term(). restart_child(Supervisor, Name) -> call(Supervisor, {restart_child, Name}). --type del_err() :: 'running' | 'not_found' | 'simple_one_for_one'. --spec delete_child(sup_ref(), term()) -> 'ok' | {'error', del_err()}. +-spec delete_child(SupRef, Id) -> Result when + SupRef :: sup_ref(), + Id :: child_id(), + Result :: 'ok' | {'error', Error}, + Error :: 'running' | 'not_found' | 'simple_one_for_one'. delete_child(Supervisor, Name) -> call(Supervisor, {delete_child, Name}). @@ -139,22 +162,39 @@ delete_child(Supervisor, Name) -> %% way (maybe killed). %%----------------------------------------------------------------- --type term_err() :: 'not_found' | 'simple_one_for_one'. --spec terminate_child(sup_ref(), pid() | term()) -> 'ok' | {'error', term_err()}. +-spec terminate_child(SupRef, Id) -> Result when + SupRef :: sup_ref(), + Id :: pid() | child_id(), + Result :: 'ok' | {'error', Error}, + Error :: 'not_found' | 'simple_one_for_one'. terminate_child(Supervisor, Name) -> call(Supervisor, {terminate_child, Name}). --spec which_children(sup_ref()) -> [{term(), child_id(), worker(), modules()}]. +-spec which_children(SupRef) -> [{Id,Child,Type,Modules}] when + SupRef :: sup_ref(), + Id :: child_id() | undefined, + Child :: child(), + Type :: worker(), + Modules :: modules(). which_children(Supervisor) -> call(Supervisor, which_children). +-spec count_children(SupRef) -> PropListOfCounts when + SupRef :: sup_ref(), + PropListOfCounts :: [Count], + Count :: {specs, ChildSpecCount :: non_neg_integer()} + | {active, ActiveProcessCount :: non_neg_integer()} + | {supervisors, ChildSupervisorCount :: non_neg_integer()} + |{workers, ChildWorkerCount :: non_neg_integer()}. count_children(Supervisor) -> call(Supervisor, count_children). call(Supervisor, Req) -> gen_server:call(Supervisor, Req, infinity). --spec check_childspecs([child_spec()]) -> 'ok' | {'error', term()}. +-spec check_childspecs(ChildSpecs) -> Result when + ChildSpecs :: [child_spec()], + Result :: 'ok' | {'error', Error :: term()}. check_childspecs(ChildSpecs) when is_list(ChildSpecs) -> case check_startspec(ChildSpecs) of {ok, _} -> ok; @@ -222,12 +262,12 @@ init_dynamic(_State, StartSpec) -> %%----------------------------------------------------------------- %% Func: start_children/2 -%% Args: Children = [child()] in start order +%% Args: Children = [child_rec()] in start order %% SupName = {local, atom()} | {global, atom()} | {pid(), Mod} %% Purpose: Start all children. The new list contains #child's %% with pids. %% Returns: {ok, NChildren} | {error, NChildren} -%% NChildren = [child()] in termination order (reversed +%% NChildren = [child_rec()] in termination order (reversed %% start order) %%----------------------------------------------------------------- start_children(Children, SupName) -> start_children(Children, [], SupName). @@ -687,9 +727,9 @@ restart(one_for_all, Child, State) -> %%----------------------------------------------------------------- %% Func: terminate_children/2 -%% Args: Children = [child()] in termination order +%% Args: Children = [child_rec()] in termination order %% SupName = {local, atom()} | {global, atom()} | {pid(),Mod} -%% Returns: NChildren = [child()] in +%% Returns: NChildren = [child_rec()] in %% startup order (reversed termination order) %%----------------------------------------------------------------- terminate_children(Children, SupName) -> @@ -958,7 +998,7 @@ supname(N, _) -> N. %%% Shutdown = integer() | infinity | brutal_kill %%% ChildType = supervisor | worker %%% Modules = [atom()] | dynamic -%%% Returns: {ok, [child()]} | Error +%%% Returns: {ok, [child_rec()]} | Error %%% ------------------------------------------------------ check_startspec(Children) -> check_startspec(Children, []). |