Module supervisor
An implementation of the Erlang/OTP supervisor interface.
Description
This module implements a strict subset of the Erlang/OTP supervisor interface, supporting operations for local creation and management of supervisor instances.
This module is designed to be API-compatible with supervisor, with exceptions noted below.
Caveats:
Support only for locally named procs
No support for simple_one_for_one or one_for_rest strategies
No support for hibernate
No support for automatic shutdown
Data Types
child()
child() = undefined | pid()
child_id()
child_id() = term()
child_spec()
child_spec() = #{id => any(), start => {module(), atom(), [any()]}, restart => restart(), shutdown => shutdown(), type => worker(), modules => [module()] | dynamic} | {Id::any(), StartFunc::{module(), atom(), [any()]}, Restart::restart(), Shutdown::shutdown(), Type::worker(), Modules::[module()] | dynamic}
restart()
restart() = permanent | transient | temporary | {terminating, permanent | transient | temporary, gen_server:from()}
shutdown()
shutdown() = brutal_kill | timeout()
startchild_err()
startchild_err() = already_present | {already_started, Child::child()} | term()
startchild_ret()
startchild_ret() = {ok, Child::child()} | {ok, Child::child(), Info::term()} | {error, startchild_err()}
startlink_err()
startlink_err() = {already_started, pid()} | {shutdown, term()} | term()
startlink_ret()
startlink_ret() = {ok, pid()} | ignore | {error, startlink_err()}
strategy()
strategy() = one_for_all | one_for_one
sup_flags()
sup_flags() = #{strategy => strategy(), intensity => non_neg_integer(), period => pos_integer()} | {RestartStrategy::strategy(), Intensity::non_neg_integer(), Period::pos_integer()}
sup_name()
sup_name() = {local, Name::atom()}
sup_ref()
sup_ref() = (Name::atom()) | {Name::atom(), Node::node()} | pid()
worker()
worker() = worker | supervisor
Function Index
| count_children/1 | |
| delete_child/2 | |
| restart_child/2 | |
| start_child/2 | |
| start_link/2 | |
| start_link/3 | |
| terminate_child/2 | |
| which_children/1 |
Function Details
count_children/1
count_children(Supervisor::sup_ref()) -> [{specs, ChildSpecCount::non_neg_integer()} | {active, ActiveProcessCount::non_neg_integer()} | {supervisors, ChildSupervisorCount::non_neg_integer()} | {workers, ChildWorkerCount::non_neg_integer()}]
delete_child/2
delete_child(Supervisor::sup_ref(), ChildId::any()) -> ok | {error, Reason::running | restarting | not_found}
restart_child/2
restart_child(Supervisor::sup_ref(), ChildId::any()) -> {ok, Child::child()} | {ok, Child::child(), Info::term()} | {error, Reason::running | restarting | not_found | term()}
start_child/2
start_child(Supervisor::sup_ref(), ChildSpec::child_spec()) -> startchild_ret()
start_link/2
start_link(Module::module(), Args::[any()]) -> startlink_ret()
start_link/3
start_link(SupName::sup_name(), Module::module(), Args::[any()]) -> startlink_ret()
terminate_child/2
terminate_child(Supervisor::sup_ref(), ChildId::any()) -> ok | {error, not_found}
which_children/1
which_children(Supervisor::sup_ref()) -> [{Id::child_id() | undefined, Child::child() | restarting, Type::worker(), Modules::[module()]}]