gen_statem

Generic state machine behavior.

This behavior module provides a state machine. 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

Note!

This is a new behavior in Erlang/OTP 19.0. It has been thoroughly reviewed, is stable enough to be used by at least two heavy OTP applications, and is here to stay. Depending on user feedback, we do not expect but can find it necessary to make minor not backward compatible changes into Erlang/OTP 20.0.

The gen_statem behavior is intended to replace gen_fsm for new code. It has the same features and adds some really useful:

State code is gathered. The state can be any term. Events can be postponed. Events can be self-generated. A reply can be sent from a later state. There can be multiple sys traceable replies.

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

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. However, an exception of class throw is not regarded as an error but as a valid return.

The "state function" 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 implementation specifies when the server starts.

When the callback mode is state_functions, the state must be an atom and is used as the state function name; see Module:StateName/3. This gathers all code for a specific state in one function as the gen_statem engine branches depending on state name. Notice that in this mode the mandatory callback function Module:terminate/3 makes the state name terminate unusable.

When the callback mode is handle_event_function, the state can be any term and the state function 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.

The gen_statem enqueues incoming events in order of arrival and presents these to the state function in that order. The state function can postpone an event so it is not retried in the current state. 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 function can insert events using the action() next_event and such an event is inserted as the next to present to the state function. 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.

Note!

If you in gen_statem, for example, postpone an event in one state and then call another state function of yours, you have not changed states 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 function 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.

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]). -export([on/3,off/3]). name() -> pushbutton_statem. % The registered server name callback_mode() -> state_functions. %% 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) -> {callback_mode(),State,Data}. init([]) -> %% Set the callback mode and initial state + data. %% Data is used only as a counter. State = off, Data = 0, {callback_mode(),State,Data}. %%% State functions 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 state_functions, or rather the code to replace from function init/1 of the pushbutton.erl example file above:

init([]) -> %% Set the callback mode and initial state + data. %% Data is used only as a counter. State = off, Data = 0, {handle_event_function,State,Data}. %%% Event handling 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}.

debug_opt() =
            {debug,
             Dbgs ::
                 [trace | log | statistics | debug | {logfile, string()}]}

Debug option that can be used when starting a gen_statem server through, for example, enter_loop/5.

For every entry in Dbgs, the corresponding function in sys is called.

start_opt() =
            debug_opt() |
            {timeout, Time :: timeout()} |
            {spawn_opt, [proc_lib:spawn_option()]}

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.

from() = {To :: pid(), Tag :: term()}

Destination to use when replying through, for example, the action() {reply,From,Reply} to a process that has called the gen_statem server using call/2.

state() = state_name() | 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.

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() =
            {call, From :: from()} | cast | info | timeout | internal

External events are of three types: {call,From}, cast, or info. Calls (synchronous) and casts originate from the corresponding API functions. For calls, the event contains whom to reply to. Type info originates from regular process messages sent to the gen_statem. Also, the state machine implementation can generate events of types timeout and internal to itself.

callback_mode() = state_functions | handle_event_function

The callback mode is selected when starting the gen_statem using the return value from Module:init/1 or when calling enter_loop/5,6,7, and with the return value from Module:code_change/4.

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.

transition_option() =
            postpone() | hibernate() | event_timeout()

Transition options can be set by actions and they modify the following in how the state transition is done:

All actions are processed in order of appearance.

If postpone() is true, the current event is postponed.

If the state changes, the queue of incoming events is reset to start with the oldest postponed.

All events stored with action() next_event are inserted in the queue to be processed before all other events.

If an event_timeout() is set through action() timeout, an event timer can be started or a time-out zero event can be enqueued.

The (possibly new) state function is called with the oldest enqueued event if there is any, otherwise the gen_statem goes into receive or hibernation (if hibernate() is true) to wait for the next message. In hibernation the next non-system event awakens the gen_statem, or rather the next incoming message awakens the gen_statem, but if it is a system event it goes right back into hibernation.

postpone() = boolean()

If true, postpones the current event and retries it when the state changes (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. If there are enqueued events, to prevent receiving any new event, an erlang:garbage_collect/0 is done instead to simulate that the gen_statem entered hibernation and immediately got awakened by the oldest enqueued event.

event_timeout() = timeout()

Generates an event of event_type() timeout after this time (in milliseconds) unless another event arrives in which case this time-out is cancelled. Notice that a retried or inserted event counts like a new in this respect.

If the value is infinity, no timer is started, as it never triggers anyway.

If the value is 0, the time-out event is immediately enqueued unless there already are enqueued events, as the time-out is then immediately cancelled. This is a feature ensuring that a time-out 0 event is processed before any not yet received external event.

Notice that it is not possible or needed to cancel this time-out, as it is cancelled automatically by any other event.

action() =
            postpone |
            {postpone, Postpone :: postpone()} |
            hibernate |
            {hibernate, Hibernate :: hibernate()} |
            (Timeout :: event_timeout()) |
            {timeout, Time :: event_timeout(), EventContent :: term()} |
            reply_action() |
            {next_event,
             EventType :: event_type(),
             EventContent :: term()}

These state transition actions can be invoked by returning them from the state function, from Module:init/1 or by giving them to enter_loop/6,7.

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 other event_timeout() 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.

hibernate

Sets the transition_option() hibernate() for this state transition.

Timeout

Short for {timeout,Timeout,Timeout}, that is, the time-out message is the time-out time. This form exists to make the state function return value {next_state,NextState,NewData,Timeout} allowed like for gen_fsm's Module:StateName/2.

timeout

Sets the transition_option() event_timeout() to Time with EventContent.

reply_action()

Replies to a caller.

next_event

Stores the specified EventType and EventContent 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.

reply_action() = {reply, From :: from(), Reply :: term()}

Replies to a caller waiting for a reply in call/2. From must be the term from argument {call,From} to the state function.

state_function_result() =
            {next_state, NextStateName :: state_name(), NewData :: data()} |
            {next_state,
             NextStateName :: state_name(),
             NewData :: data(),
             Actions :: [action()] | action()} |
            common_state_callback_result()

next_state

The gen_statem does a state transition to NextStateName (which can be the same as the current state), sets NewData, and executes all Actions.

All these terms are tuples or atoms and this property will hold in any future version of gen_statem.

handle_event_result() =
            {next_state, NextState :: state(), NewData :: data()} |
            {next_state,
             NextState :: state(),
             NewData :: data(),
             Actions :: [action()] | action()} |
            common_state_callback_result()

next_state

The gen_statem does a state transition to NextState (which can be the same as the current state), sets NewData, and executes all Actions.

All these terms are tuples or atoms and this property will hold in any future version of gen_statem.

common_state_callback_result() =
            stop |
            {stop, Reason :: term()} |
            {stop, Reason :: term(), NewData :: data()} |
            {stop_and_reply,
             Reason :: term(),
             Replies :: [reply_action()] | reply_action()} |
            {stop_and_reply,
             Reason :: term(),
             Replies :: [reply_action()] | reply_action(),
             NewData :: data()} |
            {keep_state, NewData :: data()} |
            {keep_state,
             NewData :: data(),
             Actions :: [action()] | action()} |
            keep_state_and_data |
            {keep_state_and_data, Actions :: [action()] | action()}

stop

Terminates the gen_statem by calling Module:terminate/3 with Reason and NewData, if specified.

stop_and_reply

Sends all Replies, then terminates the gen_statem by calling Module:terminate/3 with Reason and NewData, if specified.

keep_state

The gen_statem keeps the current state, or does a state transition to the current state if you like, sets NewData, and executes all Actions. This is the same as {next_state,CurrentState,NewData,Actions}.

keep_state_and_data

The gen_statem keeps the current state or does a state transition to the current state if you like, keeps the current server data, and executes all Actions. This is the same as {next_state,CurrentState,CurrentData,Actions}.

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()) ->
        Reply :: term()

Makes a synchronous call to the gen_statem ServerRef by sending a request and waiting until its reply arrives. The gen_statem calls the state function with event_type() {call,From} and event content Request.

A Reply is generated when a state function returns with {reply,From,Reply} as one action(), and that Reply becomes the return value of this function.

Timeout 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!

To avoid getting a late reply in the caller's inbox, 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 Timeout =:= infinity.

The call can 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 ServerRef and returns ok immediately, ignoring if the destination node or gen_statem does not exist. The gen_statem calls the state function with event_type() cast and event content Msg.

enter_loop(Module :: module(),
           Opts :: [debug_opt()],
           CallbackMode :: callback_mode(),
           State :: state(),
           Data :: data()) ->
              no_return()

The same as enter_loop/7 except that no server_name() must have been registered.

enter_loop(Module :: module(),
           Opts :: [debug_opt()],
           CallbackMode :: callback_mode(),
           State :: state(),
           Data :: data(),
           Server_or_Actions :: server_name() | pid() | [action()]) ->
              no_return()

If Server_or_Actions is a list(), the same as enter_loop/7 except that no server_name() must have been registered and Actions = Server_or_Actions.

Otherwise the same as enter_loop/7 with Server = Server_or_Actions and Actions = [].

enter_loop(Module :: module(),
           Opts :: [debug_opt()],
           CallbackMode :: callback_mode(),
           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.

Module, Opts, and Server have the same meanings as when calling start[_link]/3,4. However, the server_name() name must have been registered accordingly before this function is called.

CallbackMode, State, Data, and Actions have the same meanings as in the return value of Module:init/1. Also, the callback module Module does not need to export an 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 function.

From must be the term from argument {call,From} to the state function. From and Reply can also be specified using a reply_action() and multiple replies with a list of them.

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.

ServerName specifies the server_name() to register for the gen_statem. If the gen_statem is started with start_link/3, no ServerName is provided and the gen_statem is not registered.

Module is the name of the callback module.

Args is an arbitrary term that is passed as the argument to Module:init/1.

If option {timeout,Time} is present in Opts, the gen_statem is allowed to spend Time milliseconds initializing or it terminates and the start function returns {error,timeout}.

If option {debug,Dbgs} is present in Opts, debugging through sys is activated.

If option {spawn_opt,SpawnOpts} is present in Opts, SpawnOpts is passed as option list to erlang:spawn_opt/2, which is used to spawn the gen_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 ServerName 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

stop(ServerRef :: server_ref(),
     Reason :: term(),
     Timeout :: timeout()) ->
        ok

Orders the gen_statem ServerRef to exit with the specified Reason 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 error_logger:format/2. The default Reason is normal.

Timeout 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


Module:code_change(OldVsn, OldState, OldData, Extra) -> Result

  • OldVsn = Vsn | {down,Vsn}
  •   Vsn = term()
  • OldState = NewState = term()
  • Extra = term()
  • Result = {NewCallbackMode,NewState,NewData} | Reason
  • NewCallbackMode = callback_mode()
  • OldState = NewState = state()
  • OldData = NewData = data()
  • Reason = term()

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.

Note!

If you would dare to change callback mode during release upgrade/downgrade, the upgrade is no problem, as the new code surely knows what callback mode it needs. However, for a downgrade this function must know from argument Extra that comes from the sasl:appup file what callback mode the old code did use. It can also be possible to figure this out from argument {down,Vsn}, as Vsn in effect defines the old callback module version.

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 {NewCallbackMode,NewState,NewData} tuple.

If the function returns Reason, the ongoing upgrade fails and rolls back to the old release.

This function can use erlang:throw/1 to return Result or Reason.

Module:init(Args) -> Result

  • Args = term()
  • Result = {CallbackMode,State,Data}
  •  | {CallbackMode,State,Data,Actions}
  •  | {stop,Reason} | ignore
  • CallbackMode = callback_mode()
  • State = state()
  • Data = data()
  • Actions = [action()] | action()
  • Reason = term()

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 the start function.

If the initialization is successful, the function is to return {CallbackMode,State,Data} or {CallbackMode,State,Data,Actions}. CallbackMode selects the callback mode of the gen_statem. State is the initial state() and Data the initial server data().

The Actions are executed when entering the first state just as for a state function.

If the initialization fails, the function is to return {stop,Reason} or ignore; see start_link/3,4.

This function can use erlang:throw/1 to return Result.

Module:format_status(Opt, [PDict,State,Data]) -> Status

  • 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 fails, the default function returns {State,Info}, where Info informs of the crash but no details, to hide possibly sensitive data.

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 the gen_statem status. Opt is set to the atom normal for this case. The gen_statem terminates abnormally and logs an error. Opt is set to the atom terminate 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 changes the 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.

This function can use erlang:throw/1 to return Status.

Module:StateName(EventType, EventContent, Data) -> StateFunctionResult

Module:handle_event(EventType, EventContent, State, Data) -> HandleEventResult

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 function 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().

These functions can use erlang:throw/1, to return the result.

Module:terminate(Reason, State, Data) -> Ignored

  • Reason = normal | shutdown | {shutdown,term()} | term()
  • State = state()
  • Data = data()
  • Ignored = term()

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 error_logger:format/2.

This function can use erlang:throw/1 to return Ignored, which is ignored anyway.