proc_lib
Functions for asynchronous and synchronous start of processes adhering to the OTP design principles.
This module is used to start processes adhering to
the OTP Design Principles. Specifically, the functions in this
module are used by the OTP standard behaviors (gen_server
,
gen_fsm
, ...) when starting new processes. The functions
can also be used to start special processes, user
defined processes which comply to the OTP design principles. See
Sys and Proc_Lib in OTP Design Principles for an example.
Some useful information is initialized when a process starts. The registered names, or the process identifiers, of the parent process, and the parent ancestors, are stored together with information about the function initially called in the process.
While in "plain Erlang" a process is said to terminate normally
only for the exit reason normal
, a process started
using proc_lib
is also said to terminate normally if it
exits with reason shutdown
or {shutdown,Term}
.
shutdown
is the reason used when
an application (supervision tree) is stopped.
When a process started using proc_lib
terminates
abnormally -- that is, with another exit reason than normal
,
shutdown
, or {shutdown,Term}
-- a crash report
is generated, which is written to terminal by the default SASL
event handler. That is, the crash report is normally only visible
if the SASL application is started. See
sasl(6) and
SASL User's Guide.
The crash report contains the previously stored information such as ancestors and initial function, the termination reason, and information regarding other processes which terminate as a result of this process terminating.
Functions
spawn/1
spawn/2
spawn/3
spawn/4
Spawns a new process and initializes it as described above. The process is spawned using the spawn BIFs.
spawn_link/1
spawn_link/2
spawn_link/3
spawn_link/4
Spawns a new process and initializes it as described above. The process is spawned using the spawn_link BIFs.
spawn_opt/2
spawn_opt/3
spawn_opt/4
spawn_opt/5
Spawns a new process and initializes it as described above. The process is spawned using the spawn_opt BIFs.
Note!
Using the spawn option monitor
is currently not
allowed, but will cause the function to fail with reason
badarg
.
start/3
start/4
start/5
start_link/3
start_link/4
start_link/5
Starts a new process synchronously. Spawns the process and
waits for it to start. When the process has started, it
must call
init_ack(Parent,Ret)
or init_ack(Ret),
where Parent
is the process that evaluates this
function. At this time, Ret
is returned.
If the start_link/3,4,5
function is used and
the process crashes before it has called init_ack/1,2
,
{error,
is returned if the calling process
traps exits.
If
is specified as an integer, this function
waits for
milliseconds for the new process to call
init_ack
, or {error, timeout}
is returned, and
the process is killed.
The
argument, if given, will be passed
as the last argument to the spawn_opt/2,3,4,5
BIF.
Note!
Using the spawn option monitor
is currently not
allowed, but will cause the function to fail with reason
badarg
.
init_ack/1
init_ack/2
This function must used by a process that has been started by
a start[_link]/3,4,5
function. It tells
that the process has
initialized itself, has started, or has failed to initialize
itself.
The init_ack/1
function uses the parent value
previously stored by the start function used.
If this function is not called, the start function will return an error tuple (if a link and/or a timeout is used) or hang otherwise.
The following example illustrates how this function and
proc_lib:start_link/3
are used.
-module(my_proc). -export([start_link/0]). -export([init/1]). start_link() -> proc_lib:start_link(my_proc, init, [self()]). init(Parent) -> case do_initialization() of ok -> proc_lib:init_ack(Parent, {ok, self()}); {error, Reason} -> exit(Reason) end, loop(). ...
format/1
Equivalent to format(
.
format/2
This function can be used by a user defined event handler to
format a crash report. The crash report is sent using
error_logger:error_report(crash_report,
.
That is, the event to be handled is of the format
{error_report, GL, {Pid, crash_report,
where GL
is the group leader pid of the process
Pid
which sent the crash report.
initial_call/1
Extracts the initial call of a process that was started
using one of the spawn or start functions described above.
can either be a pid, an integer tuple (from
which a pid can be created), or the process information of a
process Pid
fetched through an
erlang:process_info(Pid)
function call.
Note!
The list
no longer contains the actual arguments,
but the same number of atoms as the number of arguments; the first atom
is always 'Argument__1'
, the second 'Argument__2'
, and
so on. The reason is that the argument list could waste a significant
amount of memory, and if the argument list contained funs, it could
be impossible to upgrade the code for the module.
If the process was spawned using a fun, initial_call/1
no
longer returns the actual fun, but the module, function for the local
function implementing the fun, and the arity, for instance
{some_module,-work/3-fun-0-,0}
(meaning that the fun was
created in the function some_module:work/3
).
The reason is that keeping the fun would prevent code upgrade for the
module, and that a significant amount of memory could be wasted.
translate_initial_call/1
This function is used by the c:i/0
and
c:regs/0
functions in order to present process
information.
Extracts the initial call of a process that was started
using one of the spawn or start functions described above,
and translates it to more useful information.
can either be a pid, an integer tuple (from which a pid can
be created), or the process information of a process
Pid
fetched through an erlang:process_info(Pid)
function call.
If the initial call is to one of the system defined behaviors
such as gen_server
or gen_event
, it is
translated to more useful information. If a gen_server
is spawned, the returned
is the name of
the callback module and
is init
(the function that initiates the new server).
A supervisor
and a supervisor_bridge
are also
gen_server
processes. In order to return information
that this process is a supervisor and the name of the
call-back module,
is supervisor
and
is the name of the supervisor callback
module.
is 1
since the init/1
function is called initially in the callback module.
By default, {proc_lib,init_p,5}
is returned if no
information about the initial call can be found. It is
assumed that the caller knows that the process has been
spawned with the proc_lib
module.
hibernate/3
This function does the same as (and does call) the BIF
hibernate/3,
but ensures that exception handling and logging continues to
work as expected when the process wakes up. Always use this
function instead of the BIF for processes started using
proc_lib
functions.