supervisor_bridge
Generic Supervisor Bridge Behaviour.
A behaviour module for implementing a supervisor_bridge, a process which connects a subsystem not designed according to the OTP design principles to a supervision tree. The supervisor_bridge sits between a supervisor and the subsystem. It behaves like a real supervisor to its own supervisor, but has a different interface than a real supervisor to the subsystem. Refer to OTP Design Principles for more information.
A supervisor_bridge assumes the functions for starting and stopping the subsystem to be located in a callback module exporting a pre-defined set of functions.
The sys
module can be used for debugging a
supervisor_bridge.
Unless otherwise stated, all functions in this module will fail if the specified supervisor_bridge does not exist or if bad arguments are given.
Functions
start_link/2
start_link/3
Creates a supervisor_bridge process, linked to the calling
process, which calls
to start the subsystem.
To ensure a synchronized start-up procedure, this function does
not return until
has returned.
If
the supervisor_bridge is
registered locally as
using register/2
.
If
the supervisor_bridge is
registered globally as
using
global:register_name/2
.
If
the supervisor_bridge is
registered as
using a registry represented
by Module
callback should export
the functions register_name/2
, unregister_name/1
and send/2
, which should behave like the
corresponding functions in global
. Thus,
{via,global,GlobalName}
is a valid reference.
If no name is provided, the supervisor_bridge is not registered.
If there already exists a process with the specified
the function returns
{error,{already_started,
, where
is the pid
of that process.
is the name of the callback module.
is an arbitrary term which is passed as the argument
to
.
If the supervisor_bridge and the subsystem are successfully
started the function returns {ok,
, where
is
is the pid of the supervisor_bridge.
If
returns ignore
, this function
returns ignore
as well and the supervisor_bridge terminates
with reason normal
.
If
fails or returns an error tuple or an
incorrect value, this function returns {error,
where
is a term with information about the error, and
the supervisor_bridge terminates with reason
.
CALLBACK FUNCTIONS
The following functions should be exported from a
supervisor_bridge
callback module.
Functions
Module:init(Args) -> Result
Args = term()
Result = {ok,Pid,State} | ignore | {error,Error}
Pid = pid()
State = term()
Error = term()
Whenever a supervisor_bridge is started using
supervisor_bridge:start_link/2,3
, this function is called
by the new process to start the subsystem and initialize.
Args
is the Args
argument provided to the start
function.
The function should return {ok,Pid,State}
where Pid
is the pid of the main process in the subsystem and State
is any term.
If later Pid
terminates with a reason Reason
,
the supervisor bridge will terminate with reason Reason
as
well.
If later the supervisor_bridge is stopped by its supervisor with
reason Reason
, it will call
Module:terminate(Reason,State)
to terminate.
If something goes wrong during the initialization the function
should return {error,Error}
where Error
is any
term, or ignore
.
Module:terminate(Reason, State)
Reason = shutdown | term()
State = term()
This function is called by the supervisor_bridge when it is about
to terminate. It should be the opposite of Module:init/1
and stop the subsystem and do any necessary cleaning up.
The return value is ignored.
Reason
is shutdown
if the supervisor_bridge is
terminated by its supervisor. If the supervisor_bridge terminates
because a a linked process (apart from the main process of
the subsystem) has terminated with reason Term
,
Reason
will be Term
.
State
is taken from the return value of
Module:init/1
.