Generic state machine behavior.
gen_statem
provides a generic state machine behaviour
and replaces its predecessor
gen_fsm
since Erlang/OTP 20.0.
This reference manual describes types generated from the types
in the gen_statem
source code, so they are correct.
However, the generated descriptions also reflect the type hiearchy,
which makes them kind of hard to read.
To get an overview of the concepts and operation of gen_statem
,
do read the
gen_statem
Behaviour
in
OTP Design Principles
which frequently links back to this reference manual to avoid
containing detailed facts that may rot by age.
Note!
This behavior appeared in Erlang/OTP 19.0.
In OTP 19.1 a backwards incompatible change of
the return tuple from
Module:init/1
was made and the mandatory callback function
Module:callback_mode/0
was introduced. In OTP 20.0 the
generic timeouts
were added.
gen_statem
has got the same features that
gen_fsm
had and adds some really useful:
- Co-located state code
- Arbitrary term state
- Event postponing
- Self-generated events
- State time-out
- Multiple generic named time-outs
- Absolute time-out time
- Automatic state enter calls
-
Reply from other state than the request,
sys
traceable - Multiple
sys
traceable replies
Two callback modes are supported:
-
One for finite-state machines (
gen_fsm
like), which requires the state to be an atom and uses that state as the name of the current callback function -
One without restriction on the state data type that uses one callback function for all states
The callback model(s) for gen_statem
differs from
the one for gen_fsm
,
but it is still fairly easy to
rewrite from
gen_fsm
to gen_statem
.
A generic state machine process (gen_statem
) implemented
using this module has a standard set of interface functions
and includes functionality for tracing and error reporting.
It also fits into an OTP supervision tree. For more information, see
OTP Design Principles.
A gen_statem
assumes all specific parts to be located in a
callback module exporting a predefined set of functions.
The relationship between the behavior functions and the callback
functions is as follows:
gen_statem module Callback module ----------------- --------------- gen_statem:start gen_statem:start_link -----> Module:init/1 Server start or code change -----> Module:callback_mode/0 gen_statem:stop -----> Module:terminate/3 gen_statem:call gen_statem:cast erlang:send erlang:'!' -----> Module:StateName/3 Module:handle_event/4 - -----> Module:terminate/3 - -----> Module:code_change/4
Events are of different types, so the callback functions can know the origin of an event and how to respond.
If a callback function fails or returns a bad value,
the gen_statem
terminates, unless otherwise stated.
However, an exception of class
throw
is not regarded as an error but as a valid return
from all callback functions.
The state callback for a specific
state
in a gen_statem
is the callback function that is called
for all events in this state. It is selected depending on which
callback mode
that the callback module defines with the callback function
Module:callback_mode/0
.
When the
callback mode
is state_functions
, the state must be an atom and
is used as the state callback name; see
Module:StateName/3
.
This co-locates all code for a specific state
in one function as the gen_statem
engine
branches depending on state name.
Note the fact that the callback function
Module:terminate/3
makes the state name terminate
unusable in this mode.
When the
callback mode
is handle_event_function
, the state can be any term
and the state callback name is
Module:handle_event/4
.
This makes it easy to branch depending on state or event as you desire.
Be careful about which events you handle in which
states so that you do not accidentally postpone an event
forever creating an infinite busy loop.
When gen_statem
receives a process message it is
converted into an event and the
state callback
is called with the event as two arguments: type and content.
When the
state callback
has processed the event it returns to gen_statem
which does a state transition.
If this state transition is to a different state,
that is: NextState =/= State
, it is a state change.
The
state callback
may return
transition actions
for gen_statem
to execute during the state transition,
for example to reply to a
gen_statem:call/2,3
.
One of the possible transition actions
is to postpone the current event.
Then it is not retried in the current state.
The gen_statem
engine keeps a queue of events
divided into the postponed events
and the events still to process.
After a state change the queue restarts
with the postponed events.
The gen_statem
event queue model is sufficient
to emulate the normal process message queue with selective receive.
Postponing an event corresponds to not matching it
in a receive statement, and changing states corresponds
to entering a new receive statement.
The
state callback
can insert events using the
transition actions
next_event
and such an event is inserted in the event queue
as the next to call the
state callback
with.
That is, as if it is the oldest incoming event.
A dedicated
event_type()
internal
can be used for such events making them impossible
to mistake for external events.
Inserting an event replaces the trick of calling your own
state handling functions that you often would have to
resort to in, for example,
gen_fsm
to force processing an inserted event before others.
The gen_statem
engine can automatically
make a specialized call to the
state callback
whenever a new state is entered; see
state_enter()
.
This is for writing code common to all state entries.
Another way to do it is to explicitly insert an event
at the state transition,
and/or to use a dedicated state transition function,
but that is something you will have to remember
at every state transition to the state(s) that need it.
Note!
If you in gen_statem
, for example, postpone
an event in one state and then call another state callback
of yours, you have not done a state change
and hence the postponed event is not retried,
which is logical but can be confusing.
For the details of a state transition, see type
transition_option()
.
A gen_statem
handles system messages as described in
sys
.
The sys
module can be used for debugging a gen_statem
.
Notice that a gen_statem
does not trap exit signals
automatically, this must be explicitly initiated in
the callback module (by calling
process_flag(trap_exit, true)
.
Unless otherwise stated, all functions in this module fail if
the specified gen_statem
does not exist or
if bad arguments are specified.
The gen_statem
process can go into hibernation; see
proc_lib:hibernate/3
.
It is done when a
state callback
or
Module:init/1
specifies hibernate
in the returned
Actions
list. This feature can be useful to reclaim process heap memory
while the server is expected to be idle for a long time.
However, use this feature with care,
as hibernation can be too costly
to use after every event; see
erlang:hibernate/3
.
There is also a server start option
{hibernate_after, Timeout}
for
start/3,4
,
start_link/3,4
or
enter_loop/4,5,6
,
that may be used to automatically hibernate the server.
Example
The following example shows a simple pushbutton model
for a toggling pushbutton implemented with
callback mode
state_functions
.
You can push the button and it replies if it went on or off,
and you can ask for a count of how many times it has been
pushed to switch on.
The following is the complete callback module file
pushbutton.erl
:
-module(pushbutton).
-behaviour(gen_statem).
-export([start/0,push/0,get_count/0,stop/0]).
-export([terminate/3,code_change/4,init/1,callback_mode/0]).
-export([on/3,off/3]).
name() -> pushbutton_statem. % The registered server name
%% API. This example uses a registered name name()
%% and does not link to the caller.
start() ->
gen_statem:start({local,name()}, ?MODULE, [], []).
push() ->
gen_statem:call(name(), push).
get_count() ->
gen_statem:call(name(), get_count).
stop() ->
gen_statem:stop(name()).
%% Mandatory callback functions
terminate(_Reason, _State, _Data) ->
void.
code_change(_Vsn, State, Data, _Extra) ->
{ok,State,Data}.
init([]) ->
%% Set the initial state + data. Data is used only as a counter.
State = off, Data = 0,
{ok,State,Data}.
callback_mode() -> state_functions.
%%% state callback(s)
off({call,From}, push, Data) ->
%% Go to 'on', increment count and reply
%% that the resulting status is 'on'
{next_state,on,Data+1,[{reply,From,on}]};
off(EventType, EventContent, Data) ->
handle_event(EventType, EventContent, Data).
on({call,From}, push, Data) ->
%% Go to 'off' and reply that the resulting status is 'off'
{next_state,off,Data,[{reply,From,off}]};
on(EventType, EventContent, Data) ->
handle_event(EventType, EventContent, Data).
%% Handle events common to all states
handle_event({call,From}, get_count, Data) ->
%% Reply with the current count
{keep_state,Data,[{reply,From,Data}]};
handle_event(_, _, Data) ->
%% Ignore all other events
{keep_state,Data}.
The following is a shell session when running it:
1> pushbutton:start(). {ok,<0.36.0>} 2> pushbutton:get_count(). 0 3> pushbutton:push(). on 4> pushbutton:get_count(). 1 5> pushbutton:push(). off 6> pushbutton:get_count(). 1 7> pushbutton:stop(). ok 8> pushbutton:push(). ** exception exit: {noproc,{gen_statem,call,[pushbutton_statem,push,infinity]}} in function gen:do_for_proc/2 (gen.erl, line 261) in call from gen_statem:call/3 (gen_statem.erl, line 386)
To compare styles, here follows the same example using
callback mode
handle_event_function
, or rather the code to replace
after function init/1
of the pushbutton.erl
example file above:
callback_mode() -> handle_event_function.
%%% state callback(s)
handle_event({call,From}, push, off, Data) ->
%% Go to 'on', increment count and reply
%% that the resulting status is 'on'
{next_state,on,Data+1,[{reply,From,on}]};
handle_event({call,From}, push, on, Data) ->
%% Go to 'off' and reply that the resulting status is 'off'
{next_state,off,Data,[{reply,From,off}]};
%%
%% Event handling common to all states
handle_event({call,From}, get_count, State, Data) ->
%% Reply with the current count
{next_state,State,Data,[{reply,From,Data}]};
handle_event(_, _, State, Data) ->
%% Ignore all other events
{next_state,State,Data}.
Types
server_name() =
{global, GlobalName :: term()} |
{via, RegMod :: module(), Name :: term()} |
{local, atom()}
Name specification to use when starting
a gen_statem
server. See
start_link/3
and
server_ref()
below.
server_ref() =
pid() |
(LocalName :: atom()) |
{Name :: atom(), Node :: atom()} |
{global, GlobalName :: term()} |
{via, RegMod :: module(), ViaName :: term()}
Server specification to use when addressing
a gen_statem
server.
See call/2
and
server_name()
above.
It can be:
pid() | LocalName
The gen_statem
is locally registered.
{Name,Node}
The gen_statem
is locally registered
on another node.
{global,GlobalName}
The gen_statem
is globally registered in
global
.
{via,RegMod,ViaName}
The gen_statem
is registered in
an alternative process registry.
The registry callback module RegMod
is to export functions
register_name/2
, unregister_name/1
,
whereis_name/1
, and send/2
,
which are to behave like the corresponding functions in
global
.
Thus, {via,global,GlobalName}
is the same as
{global,GlobalName}
.
start_opt() =
{timeout, Time :: timeout()} |
{spawn_opt, [proc_lib:spawn_option()]} |
enter_loop_opt()
Options that can be used when starting
a gen_statem
server through, for example,
start_link/3
.
start_ret() = {ok, pid()} | ignore | {error, term()}
Return value from the start functions, for example,
start_link/3
.
enter_loop_opt() =
{hibernate_after, HibernateAfterTimeout :: timeout()} |
{debug, Dbgs :: [sys:debug_option()]}
Options that can be used when starting
a gen_statem
server through,
enter_loop/4-6
.
hibernate_after
HibernateAfterTimeout
specifies that the gen_statem
process awaits
any message for HibernateAfterTimeout
milliseconds and
if no message is received, the process goes into hibernation
automatically (by calling
proc_lib:hibernate/3
).
debug
For every entry in
,
the corresponding function in
sys
is called.
from() = {To :: pid(), Tag :: term()}
state() = state_name() | term()
If the
callback mode
is handle_event_function
,
the state can be any term.
After a state change (NextState =/= State
),
all postponed events are retried.
state_name() = atom()
If the
callback mode
is state_functions
,
the state must be of this type.
After a state change (NextState =/= State
),
all postponed events are retried.
data() = term()
A term in which the state machine implementation
is to store any server data it needs. The difference between
this and the state()
itself is that a change in this data does not cause
postponed events to be retried. Hence, if a change
in this data would change the set of events that
are handled, then that data item is to be made
a part of the state.
event_type() =
external_event_type() | timeout_event_type() | internal
There are 3 categories of events:
external,
timeout,
and internal
.
internal
events can only be generated by the
state machine itself through the transition action
next_event
.
external_event_type() = {call, From :: from()} | cast | info
timeout_event_type() =
timeout | {timeout, Name :: term()} | state_timeout
There are 3 types of timeout events that the state machine can generate for itself with the corresponding timeout_action()s.
callback_mode_result() =
callback_mode() | [callback_mode() | state_enter()]
This is the return type from
Module:callback_mode/0
and selects
callback mode
and whether to do
state enter calls,
or not.
callback_mode() = state_functions | handle_event_function
The callback mode is selected when starting the
gen_statem
and after code change
using the return value from
Module:callback_mode/0
.
state_functions
The state must be of type
state_name()
and one callback function per state, that is,
Module:StateName/3
,
is used.
handle_event_function
The state can be any term and the callback function
Module:handle_event/4
is used for all states.
state_enter() = state_enter
Whether the state machine should use state enter calls
or not is selected when starting the gen_statem
and after code change using the return value from
Module:callback_mode/0
.
If
Module:callback_mode/0
returns a list containing state_enter
,
the gen_statem
engine will, at every state change,
call the
state callback
with arguments (enter, OldState, Data)
.
This may look like an event but is really a call
performed after the previous
state callback
returned and before any event is delivered to the new
state callback.
See
Module:StateName/3
and
Module:handle_event/4
.
Such a call can be repeated by returning a
repeat_state
or
repeat_state_and_data
tuple from the state callback.
If
Module:callback_mode/0
does not return such a list, no state enter calls are done.
If
Module:code_change/4
should transform the state,
it is regarded as a state rename and not a state change,
which will not cause a state enter call.
Note that a state enter call will be done
right before entering the initial state even though this
actually is not a state change.
In this case OldState =:= State
,
which cannot happen for a subsequent state change,
but will happen when repeating the state enter call.
transition_option() =
postpone() |
hibernate() |
event_timeout() |
generic_timeout() |
state_timeout()
Transition options can be set by actions and modify the state transition. The state transition takes place when the state callback has processed an event and returns. Here are the sequence of steps for a state transition:
-
If state enter calls are used, and either: the state changes, it is the initial state, or one of the callback results
repeat_state
orrepeat_state_and_data
is used; thegen_statem
calls the new state callback with arguments(enter, OldState, Data)
.Any actions returned from this call are handled as if they were appended to the actions returned by the state callback that caused the state entry.
Should this state enter call return any of the mentioned
repeat_*
callback results it is repeated again, with the updatedData
. -
All actions are processed in order of appearance.
-
If
postpone()
istrue
, the current event is postponed. -
If this is a state change, the queue of incoming events is reset to start with the oldest postponed.
-
All events stored with
action()
next_event
are inserted to be processed before previously queued events. -
Time-out timers
event_timeout()
,generic_timeout()
andstate_timeout()
are handled. Time-outs with zero time are guaranteed to be delivered to the state machine before any external not yet received event so if there is such a time-out requested, the corresponding time-out zero event is enqueued as the newest received event; that is after already queued events such as inserted and postponed events.Any event cancels an
event_timeout()
so a zero time event time-out is only generated if the event queue is empty.A state change cancels a
state_timeout()
and any new transition option of this type belongs to the new state. -
If there are enqueued events the state callback for the possibly new state is called with the oldest enqueued event, and we start again from the top of this list.
-
Otherwise the
gen_statem
goes intoreceive
or hibernation (ifhibernate()
istrue
) to wait for the next message. In hibernation the next non-system event awakens thegen_statem
, or rather the next incoming message awakens thegen_statem
, but if it is a system event it goes right back into hibernation. When a new message arrives the state callback is called with the corresponding event, and we start again from the top of this sequence.
postpone() = boolean()
If true
, postpones the current event and retries
it after a state change
(NextState =/= State
).
hibernate() = boolean()
If true
, hibernates the gen_statem
by calling
proc_lib:hibernate/3
before going into receive
to wait for a new external event.
Note!
If there are enqueued events to process
when hibrnation is requested,
this is optimized by not hibernating but instead calling
erlang:garbage_collect/0
to simulate that the gen_statem
entered hibernation
and immediately got awakened by an enqueued event.
event_timeout() = timeout() | integer()
Starts a timer set by
enter_action()
timeout
.
When the timer expires an event of
event_type()
timeout
will be generated.
See
erlang:start_timer/4
for how Time
and
Options
are interpreted. Future erlang:start_timer/4
Options
will not necessarily be supported.
Any event that arrives cancels this time-out. Note that a retried or inserted event counts as arrived. So does a state time-out zero event, if it was generated before this time-out is requested.
If Time
is infinity
,
no timer is started, as it never would expire anyway.
If Time
is relative and 0
no timer is actually started,
instead the the time-out event is enqueued to ensure
that it gets processed before any not yet
received external event, but after already queued events.
Note that it is not possible nor needed to cancel this time-out, as it is cancelled automatically by any other event.
generic_timeout() = timeout() | integer()
Starts a timer set by
enter_action()
{timeout,Name}
.
When the timer expires an event of
event_type()
{timeout,Name}
will be generated.
See
erlang:start_timer/4
for how Time
and
Options
are interpreted. Future erlang:start_timer/4
Options
will not necessarily be supported.
If Time
is infinity
,
no timer is started, as it never would expire anyway.
If Time
is relative and 0
no timer is actually started,
instead the the time-out event is enqueued to ensure
that it gets processed before any not yet
received external event.
Setting a timer with the same Name
while it is running
will restart it with the new time-out value.
Therefore it is possible to cancel
a specific time-out by setting it to infinity
.
state_timeout() = timeout() | integer()
Starts a timer set by
enter_action()
state_timeout
.
When the timer expires an event of
event_type()
state_timeout
will be generated.
See
erlang:start_timer/4
for how Time
and
Options
are interpreted. Future erlang:start_timer/4
Options
will not necessarily be supported.
If Time
is infinity
,
no timer is started, as it never would expire anyway.
If Time
is relative and 0
no timer is actually started,
instead the the time-out event is enqueued to ensure
that it gets processed before any not yet
received external event.
Setting this timer while it is running will restart it with
the new time-out value. Therefore it is possible to cancel
this time-out by setting it to infinity
.
timeout_option() = {abs, Abs :: boolean()}
If Abs
is true
an absolute timer is started,
and if it is false
a relative, which is the default.
See
erlang:start_timer/4
for details.
action() =
postpone |
{postpone, Postpone :: postpone()} |
{next_event,
EventType :: event_type(),
EventContent :: term()} |
enter_action()
These transition actions can be invoked by
returning them from the
state callback
when it is called with an
event,
from
Module:init/1
or by giving them to
enter_loop/5,6
.
Actions are executed in the containing list order.
Actions that set
transition options
override any previous of the same type,
so the last in the containing list wins.
For example, the last
postpone()
overrides any previous postpone()
in the list.
postpone
Sets the
transition_option()
postpone()
for this state transition.
This action is ignored when returned from
Module:init/1
or given to
enter_loop/5,6
,
as there is no event to postpone in those cases.
next_event
This action does not set any
transition_option()
but instead stores the specified
and
for insertion after all
actions have been executed.
The stored events are inserted in the queue as the next to process
before any already queued events. The order of these stored events
is preserved, so the first next_event
in the containing
list becomes the first to process.
An event of type
internal
is to be used when you want to reliably distinguish
an event inserted this way from any external event.
enter_action() =
hibernate |
{hibernate, Hibernate :: hibernate()} |
timeout_action() |
reply_action()
These transition actions can be invoked by
returning them from the
state callback, from
Module:init/1
or by giving them to
enter_loop/5,6
.
Actions are executed in the containing list order.
Actions that set
transition options
override any previous of the same type,
so the last in the containing list wins.
For example, the last
event_timeout()
overrides any previous event_timeout()
in the list.
hibernate
Sets the
transition_option()
hibernate()
for this state transition.
timeout_action() =
(Time :: event_timeout()) |
{timeout, Time :: event_timeout(), EventContent :: term()} |
{timeout,
Time :: event_timeout(),
EventContent :: term(),
Options :: timeout_option() | [timeout_option()]} |
{{timeout, Name :: term()},
Time :: generic_timeout(),
EventContent :: term()} |
{{timeout, Name :: term()},
Time :: generic_timeout(),
EventContent :: term(),
Options :: timeout_option() | [timeout_option()]} |
{state_timeout,
Time :: state_timeout(),
EventContent :: term()} |
{state_timeout,
Time :: state_timeout(),
EventContent :: term(),
Options :: timeout_option() | [timeout_option()]}
These transition actions can be invoked by
returning them from the
state callback, from
Module:init/1
or by giving them to
enter_loop/5,6
.
These timeout actions sets timeout transition options.
Time
Short for {timeout,Time,Time}
, that is,
the time-out message is the time-out time.
This form exists to make the
state callback
return value {next_state,NextState,NewData,Time}
allowed like for gen_fsm
.
timeout
Sets the
transition_option()
event_timeout()
to
with
and time-out options
.
{timeout,Name }
Sets the
transition_option()
generic_timeout()
to
for
with
and time-out options
.
state_timeout
Sets the
transition_option()
state_timeout()
to
with
and time-out options
.
reply_action() = {reply, From :: from(), Reply :: term()}
This transition action can be invoked by
returning it from the
state callback, from
Module:init/1
or by giving it to
enter_loop/5,6
.
It does not set any
transition_option()
but instead replies to a caller waiting for a reply in
call/2
.
must be the term from argument
{call,
in a call to a
state callback.
Note that using this action from
Module:init/1
or
enter_loop/5,6
would be weird on the border of witchcraft
since there has been no earlier call to a
state callback
in this server.
init_result/0
For a succesful initialization,
is the initial
state()
and
the initial server
data()
of the gen_statem
.
The Actions
are executed when entering the first
state just as for a
state callback,
except that the action postpone
is forced to
false
since there is no event to postpone.
For an unsuccesful initialization,
{stop,
or ignore
should be used; see
start_link/3,4
.
state_enter_result/0
is the current state
and it cannot be changed since the state callback
was called with a
state enter call.
next_state
The gen_statem
does a state transition to
, which has to be
the current state,
sets
,
and executes all
.
event_handler_result/0
is
state_name()
if
callback mode
is state_functions
, or
state()
if
callback mode
is handle_event_function
.
next_state
The gen_statem
does a state transition to
(which can be the same as the current state),
sets
,
and executes all
.
If
the state transition is a state change.
state_callback_result/0
is
enter_action()
if the state callback was called with a
state enter call
and
action()
if the state callback was called with an event.
keep_state
The same as
{next_state,CurrentState,
.
keep_state_and_data
The same as
{keep_state,CurrentData,
.
repeat_state
If the gen_statem
runs with
state enter calls,
the state enter call is repeated, see type
transition_option()
,
other than that repeat_state
is the same as
keep_state
.
repeat_state_and_data
The same as
{repeat_state,CurrentData,
.
stop
Terminates the gen_statem
by calling
Module:terminate/3
with Reason
and
, if specified.
stop_and_reply
Sends all
,
then terminates the gen_statem
by calling
Module:terminate/3
with Reason
and
, if specified.
All these terms are tuples or atoms and this property
will hold in any future version of gen_statem
.
Functions
call(ServerRef :: server_ref(), Request :: term()) ->
Reply :: term()
call(ServerRef :: server_ref(),
Request :: term(),
Timeout ::
timeout() |
{clean_timeout, T :: timeout()} |
{dirty_timeout, T :: timeout()}) ->
Reply :: term()
Makes a synchronous call to the gen_statem
by sending a request
and waiting until its reply arrives.
The gen_statem
calls the
state callback
with
event_type()
{call,From}
and event content
.
A
is generated when a
state callback
returns with
{reply,From,
as one
action()
,
and that
becomes the return value
of this function.
is an integer > 0,
which specifies how many milliseconds to wait for a reply,
or the atom infinity
to wait indefinitely,
which is the default. If no reply is received within
the specified time, the function call fails.
Note!
For
,
to avoid getting a late reply in the caller's
inbox if the caller should catch exceptions,
this function spawns a proxy process that
does the call. A late reply gets delivered to the
dead proxy process, hence gets discarded. This is
less efficient than using
.
can also be a tuple
{clean_timeout,
or
{dirty_timeout,
, where
is the time-out time.
{clean_timeout,
works like
just T
described in the note above
and uses a proxy process
while {dirty_timeout,
bypasses the proxy process which is more lightweight.
Note!
If you combine catching exceptions from this function
with {dirty_timeout,
to avoid that the calling process dies when the call
times out, you will have to be prepared to handle
a late reply. Note that there is an odd chance
to get a late reply even with
{dirty_timeout,infinity}
or infinity
for example in the event of network problems.
So why not just let the calling process die
by not catching the exception?
The call can also fail, for example, if the gen_statem
dies before or during this function call.
cast(ServerRef :: server_ref(), Msg :: term()) -> ok
Sends an asynchronous event to the gen_statem
and returns ok
immediately,
ignoring if the destination node or gen_statem
does not exist.
The gen_statem
calls the
state callback
with
event_type()
cast
and event content
.
enter_loop(Module :: module(),
Opts :: [enter_loop_opt()],
State :: state(),
Data :: data()) ->
no_return()
The same as
enter_loop/6
with Actions = []
except that no
server_name()
must have been registered. This creates an anonymous server.
enter_loop(Module :: module(),
Opts :: [enter_loop_opt()],
State :: state(),
Data :: data(),
Server_or_Actions :: server_name() | pid() | [action()]) ->
no_return()
If
is a list()
,
the same as
enter_loop/6
except that no
server_name()
must have been registered and
Actions =
.
This creates an anonymous server.
Otherwise the same as
enter_loop/6
with
Server =
and
Actions = []
.
enter_loop(Module :: module(),
Opts :: [enter_loop_opt()],
State :: state(),
Data :: data(),
Server :: server_name() | pid(),
Actions :: [action()] | action()) ->
no_return()
Makes the calling process become a gen_statem
.
Does not return, instead the calling process enters
the gen_statem
receive loop and becomes
a gen_statem
server.
The process must have been started
using one of the start functions in
proc_lib
.
The user is responsible for any initialization of the process,
including registering a name for it.
This function is useful when a more complex initialization
procedure is needed than
the gen_statem
behavior provides.
,
have the same meaning as when calling
start[_link]/3,4
.
If
is self()
an anonymous
server is created just as when using
start[_link]/3
.
If
is a
server_name()
a named server is created just as when using
start[_link]/4
.
However, the
server_name()
name must have been registered accordingly
before this function is called.
,
,
and
have the same meanings as in the return value of
Module:init/1
.
Also, the callback module does not need to export a
Module:init/1
function.
The function fails if the calling process was not started by a
proc_lib
start function, or if it is not registered
according to
server_name()
.
reply(Replies :: [reply_action()] | reply_action()) -> ok
reply(From :: from(), Reply :: term()) -> ok
This function can be used by a gen_statem
to explicitly send a reply to a process that waits in
call/2
when the reply cannot be defined in
the return value of a
state callback.
must be the term from argument
{call,
to the
state callback.
A reply or multiple replies canalso be sent
using one or several
reply_action()
s
from a
state callback.
Note!
A reply sent with this function is not visible
in sys
debug output.
start(Module :: module(), Args :: term(), Opts :: [start_opt()]) ->
start_ret()
start(ServerName :: server_name(),
Module :: module(),
Args :: term(),
Opts :: [start_opt()]) ->
start_ret()
Creates a standalone gen_statem
process according to
OTP design principles (using
proc_lib
primitives).
As it does not get linked to the calling process,
this start function cannot be used by a supervisor
to start a child.
For a description of arguments and return values, see
start_link/3,4
.
start_link(Module :: module(),
Args :: term(),
Opts :: [start_opt()]) ->
start_ret()
start_link(ServerName :: server_name(),
Module :: module(),
Args :: term(),
Opts :: [start_opt()]) ->
start_ret()
Creates a gen_statem
process according
to OTP design principles
(using
proc_lib
primitives)
that is linked to the calling process.
This is essential when the gen_statem
must be part of
a supervision tree so it gets linked to its supervisor.
The gen_statem
process calls
Module:init/1
to initialize the server. To ensure a synchronized startup
procedure, start_link/3,4
does not return until
Module:init/1
has returned.
specifies the
server_name()
to register for the gen_statem
.
If the gen_statem
is started with start_link/3
,
no
is provided and
the gen_statem
is not registered.
is the name of the callback module.
is an arbitrary term that is passed as
the argument to
Module:init/1
.
-
If option
{timeout,Time}
is present in
, theOpts gen_statem
is allowed to spendTime
milliseconds initializing or it terminates and the start function returns{error,timeout}
. -
If option
{hibernate_after,HibernateAfterTimeout}
is present, thegen_statem
process awaits any message forHibernateAfterTimeout
milliseconds and if no message is received, the process goes into hibernation automatically (by callingproc_lib:hibernate/3
). -
If option
{debug,Dbgs}
is present in
, debugging throughOpts sys
is activated. -
If option
{spawn_opt,SpawnOpts}
is present in
,Opts SpawnOpts
is passed as option list toerlang:spawn_opt/2
, which is used to spawn thegen_statem
process.
Note!
Using spawn option monitor
is not
allowed, it causes this function to fail with reason
badarg
.
If the gen_statem
is successfully created
and initialized, this function returns
{ok,Pid}
,
where Pid
is the pid()
of the gen_statem
.
If a process with the specified
exists already, this function returns
{error,{already_started,Pid}}
,
where Pid
is the pid()
of that process.
If Module:init/1
fails with Reason
,
this function returns
{error,Reason}
.
If Module:init/1
returns
{stop,Reason}
or
ignore
,
the process is terminated and this function
returns
{error,Reason}
or
ignore
,
respectively.
stop(ServerRef :: server_ref()) -> ok
The same as
stop(
.
stop(ServerRef :: server_ref(),
Reason :: term(),
Timeout :: timeout()) ->
ok
Orders the gen_statem
to exit with the specified
and waits for it to terminate.
The gen_statem
calls
Module:terminate/3
before exiting.
This function returns ok
if the server terminates
with the expected reason. Any other reason than normal
,
shutdown
, or {shutdown,Term}
causes an
error report to be issued through
logger(3)
.
The default
is normal
.
is an integer > 0,
which specifies how many milliseconds to wait for the server to
terminate, or the atom infinity
to wait indefinitely.
Defaults to infinity
.
If the server does not terminate within the specified time,
a timeout
exception is raised.
If the process does not exist, a noproc
exception
is raised.
Callback Functions
The following functions are to be exported from a
gen_statem
callback module.
Functions
CallbackMode = callback_mode() | [ callback_mode() | state_enter() ]
This function is called by a gen_statem
when it needs to find out the
callback mode
of the callback module. The value is cached by gen_statem
for efficiency reasons, so this function is only called
once after server start and after code change,
but before the first
state callback
in the current code version is called.
More occasions may be added in future versions
of gen_statem
.
Server start happens either when
Module:init/1
returns or when
enter_loop/4-6
is called. Code change happens when
Module:code_change/4
returns.
The CallbackMode
is either just
callback_mode()
or a list containing
callback_mode()
and possibly the atom
state_enter
.
Note!
If this function's body does not return an inline constant value the callback module is doing something strange.
OldVsn = Vsn | {down,Vsn}
Vsn = term()
OldState = NewState = term()
Extra = term()
Result = {ok,NewState,NewData} | Reason
OldState = NewState = state()
OldData = NewData = data()
Reason = term()
Note!
This callback is optional, so callback modules need not export it.
If a release upgrade/downgrade with
Change = {advanced,Extra}
specified in the .appup
file is made
when code_change/4
is not implemented
the process will crash with exit reason undef
.
This function is called by a gen_statem
when it is to
update its internal state during a release upgrade/downgrade,
that is, when the instruction {update,Module,Change,...}
,
where Change = {advanced,Extra}
, is specified in the
appup
file. For more information, see
OTP Design Principles.
For an upgrade, OldVsn
is Vsn
, and
for a downgrade, OldVsn
is
{down,Vsn}
. Vsn
is defined by the vsn
attribute(s) of the old version of the callback module
Module
. If no such attribute is defined, the version
is the checksum of the Beam file.
OldState
and OldData
is the internal state
of the gen_statem
.
Extra
is passed "as is" from the {advanced,Extra}
part of the update instruction.
If successful, the function must return the updated
internal state in an
{ok,NewState,NewData}
tuple.
If the function returns a failure Reason
, the ongoing
upgrade fails and rolls back to the old release.
Note that Reason
cannot be an {ok,_,_}
tuple
since that will be regarded as a
{ok,NewState,NewData}
tuple,
and that a tuple matching {ok,_}
is an also invalid failure Reason
.
It is recommended to use an atom as Reason
since
it will be wrapped in an {error,Reason}
tuple.
Also note when upgrading a gen_statem
,
this function and hence
the Change = {advanced,Extra}
parameter in the
appup
file
is not only needed to update the internal state
or to act on the Extra
argument.
It is also needed if an upgrade or downgrade should change
callback mode,
or else the callback mode after the code change
will not be honoured,
most probably causing a server crash.
Args = term()
Result(StateType) = init_result(StateType)
Whenever a gen_statem
is started using
start_link/3,4
or
start/3,4
,
this function is called by the new process to initialize
the implementation state and server data.
Args
is the Args
argument provided to that start
function.
Note!
Note that if the gen_statem
is started through
proc_lib
and
enter_loop/4-6
,
this callback will never be called.
Since this callback is not optional it can
in that case be implemented as:
init(Args) -> erlang:error(not_implemented, [Args]).
Opt = normal | terminate
PDict = [{Key, Value}]
State = state()
Data = data()
Key = term()
Value = term()
Status = term()
Note!
This callback is optional, so a callback module does not need
to export it. The gen_statem
module provides a default
implementation of this function that returns
{State,Data}
.
If this callback is exported but fails,
to hide possibly sensitive data,
the default function will instead return {State,Info}
,
where Info
says nothing but the fact that
format_status/2
has crashed.
This function is called by a gen_statem
process when
any of the following apply:
-
One of
sys:get_status/1,2
is invoked to get thegen_statem
status.Opt
is set to the atomnormal
for this case. -
The
gen_statem
terminates abnormally and logs an error.Opt
is set to the atomterminate
for this case.
This function is useful for changing the form and
appearance of the gen_statem
status for these cases. A
callback module wishing to change the
sys:get_status/1,2
return value and how
its status appears in termination error logs exports an
instance of format_status/2
, which returns a term
describing the current status of the gen_statem
.
PDict
is the current value of the process dictionary
of the gen_statem
.
State
is the internal state of the gen_statem
.
Data
is the internal server data of the gen_statem
.
The function is to return Status
, a term that
contains the appropriate details
of the current state and status of
the gen_statem
. There are no restrictions on the
form Status
can take, but for the
sys:get_status/1,2
case (when Opt
is normal
), the recommended form for
the Status
value is [{data, [{"State",
Term}]}]
, where Term
provides relevant details of
the gen_statem
state. Following this recommendation is not
required, but it makes the callback module status
consistent with the rest of the
sys:get_status/1,2
return value.
One use for this function is to return compact alternative state representations to avoid having large state terms printed in log files. Another use is to hide sensitive data from being written to the error log.
EventType = event_type()
EventContent = term()
State = state()
Data = NewData = data()
StateEnterResult(StateName) = state_enter_result(StateName)
StateFunctionResult = event_handler_result(state_name())
StateEnterResult(State) = state_enter_result(State)
HandleEventResult = event_handler_result(state())
Whenever a gen_statem
receives an event from
call/2
,
cast/2
, or
as a normal process message, one of these functions is called. If
callback mode
is state_functions
, Module:StateName/3
is called,
and if it is handle_event_function
,
Module:handle_event/4
is called.
If EventType
is
{call,From}
,
the caller waits for a reply. The reply can be sent
from this or from any other
state callback
by returning with {reply,From,Reply}
in
Actions
, in
Replies
,
or by calling
reply(From, Reply)
.
If this function returns with a next state that
does not match equal (=/=
) to the current state,
all postponed events are retried in the next state.
The only difference between StateFunctionResult
and
HandleEventResult
is that for StateFunctionResult
the next state must be an atom, but for HandleEventResult
there is no restriction on the next state.
For options that can be set and actions that can be done
by gen_statem
after returning from this function,
see action()
.
When the gen_statem
runs with
state enter calls,
these functions are also called with arguments
(enter, OldState, ...)
during every state change.
In this case there are some restrictions on the
actions
that may be returned:
postpone()
is not allowed since a state enter call is not
an event so there is no event to postpone, and
{next_event,_,_}
is not allowed since using state enter calls
should not affect how events are consumed and produced.
You may also not change states from this call.
Should you return {next_state,NextState, ...}
with NextState =/= State
the gen_statem
crashes.
Note that it is actually allowed to use
{repeat_state, NewData, ...}
although it makes little
sense since you immediately will be called again with a new
state enter call making this just a weird way
of looping, and there are better ways to loop in Erlang.
If you do not update NewData
and have some
loop termination condition, or if you use
{repeat_state_and_data, _}
or
repeat_state_and_data
you have an infinite loop!
You are advised to use {keep_state,...}
,
{keep_state_and_data,_}
or
keep_state_and_data
since changing states from a state enter call
is not possible anyway.
Note the fact that you can use
throw
to return the result, which can be useful.
For example to bail out with throw(keep_state_and_data)
from deep within complex code that cannot
return {next_state,State,Data}
because
State
or Data
is no longer in scope.
Reason = normal | shutdown | {shutdown,term()} | term()
State = state()
Data = data()
Ignored = term()
Note!
This callback is optional, so callback modules need not
export it. The gen_statem
module provides a default
implementation without cleanup.
This function is called by a gen_statem
when it is about to terminate. It is to be the opposite of
Module:init/1
and do any necessary cleaning up. When it returns,
the gen_statem
terminates with Reason
. The return
value is ignored.
Reason
is a term denoting the stop reason and
State
is the internal state of the gen_statem
.
Reason
depends on why the gen_statem
is terminating.
If it is because another callback function has returned, a
stop tuple {stop,Reason}
in
Actions
,
Reason
has the value specified in that tuple.
If it is because of a failure, Reason
is the error reason.
If the gen_statem
is part of a supervision tree and is
ordered by its supervisor to terminate, this function is
called with Reason = shutdown
if both the following
conditions apply:
-
The
gen_statem
has been set to trap exit signals. -
The shutdown strategy as defined in the supervisor's child specification is an integer time-out value, not
brutal_kill
.
Even if the gen_statem
is not
part of a supervision tree, this function is called
if it receives an 'EXIT'
message from its parent.
Reason
is the same as
in the 'EXIT'
message.
Otherwise, the gen_statem
is immediately terminated.
Notice that for any other reason than normal
,
shutdown
, or {shutdown,Term}
,
the gen_statem
is assumed to terminate because of an error
and an error report is issued using
logger(3)
.
See Also
gen_event(3)
,
gen_fsm(3)
,
gen_server(3)
,
proc_lib(3)
,
supervisor(3)
,
sys(3)
.