diff --git a/lib/stdlib/src/gen_event.erl b/lib/stdlib/src/gen_event.erl index 76e0b8dfbc13..d69e648c2514 100644 --- a/lib/stdlib/src/gen_event.erl +++ b/lib/stdlib/src/gen_event.erl @@ -21,18 +21,18 @@ -moduledoc """ Generic event handling behavior. -This behavior module provides event handling functionality. It consists of a -generic event manager process with any number of event handlers that are added -and deleted dynamically. +This behavior module provides event handling functionality. +It consists of a generic event manager process with any number of +event handlers that are added and deleted dynamically. -An event manager 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](`e:system:events.md`). +An event manager 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](`e:system:events.md`). -Each event handler is implemented as a callback module exporting a predefined -set of functions. The relationship between the behavior functions and the -callback functions is as follows: +Each event handler is implemented as a callback module +exporting a predefined set of functions. The relationship between +the behavior functions and the callback functions is as follows: ```text gen_event module Callback module @@ -65,53 +65,58 @@ gen_event:stop -----> Module:terminate/2 - -----> Module:code_change/3 ``` -As each event handler is one callback module, an event manager has many callback -modules that are added and deleted dynamically. `gen_event` is therefore more -tolerant of callback module errors than the other behaviors. If a callback -function for an installed event handler fails with `Reason`, or returns a bad -value `Term`, the event manager does not fail. It deletes the event handler by -calling callback function [`Module:terminate/2`](`c:terminate/2`), giving as -argument `{error,{'EXIT',Reason}}` or `{error,Term}`, respectively. No other -event handler is affected. +As each event handler is one callback module, an event manager +has many callback modules that are added and deleted dynamically. +`gen_event` is therefore more tolerant of callback module errors +than the other behaviors. If a callback function for an installed +event handler fails with `Reason`, or returns a bad value `Term`, +the event manager does not fail. It deletes the event handler +by calling callback function [`Module:terminate/2`](`c:terminate/2`), +giving as argument `{error, {'EXIT', Reason}}` or `{error, Term}`, +respectively. No other event handler is affected. -A `gen_event` process handles system messages as described in `m:sys`. The `sys` -module can be used for debugging an event manager. +A `gen_event` process handles system messages as described in `m:sys`. +The `sys` module can be used for debugging an event manager. Notice that an event manager _does_ trap exit signals automatically. -The `gen_event` process can go into hibernation (see `erlang:hibernate/3`) if a -callback function in a handler module specifies `hibernate` in its return value. -This can be useful if the server is expected to be idle for a long time. -However, use this feature with care, as hibernation implies at least two garbage -collections (when hibernating and shortly after waking up) and is not something -you want to do between each event handled by a busy event manager. +The `gen_event` process can go into hibernation +(see `erlang:hibernate/3`) if a callback function in a handler module +specifies `hibernate` in its return value. This can be useful +if the server is expected to be idle for a long time. +However, use this feature with care, as hibernation implies +at least two garbage collections (when hibernating +and shortly after waking up) and is not something you want to do +between each event handled by a busy event manager. -Notice that when multiple event handlers are invoked, it is sufficient that one -single event handler returns a `hibernate` request for the whole event manager -to go into hibernation. +Notice that when multiple event handlers are invoked, +it is sufficient that one single event handler returns a `hibernate` +request for the whole event manager to go into hibernation. -Unless otherwise stated, all functions in this module fail if the specified -event manager does not exist or if bad arguments are specified. +Unless otherwise stated, all functions in this module fail +if the specified event manager does not exist +or if bad arguments are specified. > #### Note {: .info } > > For some important information about distributed signals, see the -> [_Blocking Signaling Over Distribution_](`e:system:ref_man_processes.md#blocking-signaling-over-distribution`) -> section in the _Processes_ chapter of the _Erlang Reference Manual_. Blocking -> signaling can, for example, cause call timeouts in `gen_event` to be -> significantly delayed. +> [_Blocking Signaling Over Distribution_ +> ](`e:system:ref_man_processes.md#blocking-signaling-over-distribution`) +> section in the _Processes_ chapter of the _Erlang Reference Manual_. +> Blocking signaling can, for example, cause call timeouts in `gen_event` +> to be significantly delayed. ## See Also `m:supervisor`, `m:sys` """. -%%% +%%% %%% A general event handler. %%% Several handlers (functions) can be added. %%% Each handler holds a state and will be called %%% for every event received of the handler. -%%% +%%% %%% Modified by Magnus. %%% Take care of fault situations and made notify asynchronous. @@ -173,56 +178,67 @@ event manager does not exist or if bad arguments are specified. %% gen_event:delete_handler(Handler, Mod, Args) -> Val %% gen_event:swap_handler(Handler, {OldMod, Args1}, {NewMod, Args2}) -> ok %% gen_event:which_handler(Handler) -> [Mod] -%% gen_event:stop(Handler) -> ok +%% gen_event:stop(Handler) -> ok -doc """ -Whenever a new event handler is added to an event manager, this function is -called to initialize the event handler. +Initialize the event handler. + +Whenever a new event handler is added to an event manager, +this function is called to initialize the event handler. If the event handler is added because of a call to `add_handler/3` or `add_sup_handler/3`, `InitArgs` is the `Args` argument of these functions. -If the event handler replaces another event handler because of a call to -`swap_handler/3` or `swap_sup_handler/3`, or because of a `swap` return tuple -from one of the other callback functions, `InitArgs` is a tuple `{Args,Term}`, -where `Args` is the argument provided in the function call/return tuple and -`Term` is the result of terminating the old event handler, see `swap_handler/3`. +If the event handler replaces another event handler because of +a call to `swap_handler/3` or `swap_sup_handler/3`, or because of +a `swap` return tuple from one of the other callback functions, +`InitArgs` is a tuple `{Args, Term}`, where `Args` is the argument +provided in the function call/return tuple and `Term` is the result +of terminating the old event handler, see `swap_handler/3`. -If successful, the function returns `{ok,State}` or `{ok,State,hibernate}`, -where `State` is the initial internal state of the event handler. +If successful, the function returns `{ok, State}` or +`{ok, State, hibernate}`, where `State` is the initial internal state +of the event handler. -If `{ok,State,hibernate}` is returned, the event manager goes into hibernation -(by calling `proc_lib:hibernate/3`), waiting for the next event to occur. +If `{ok, State, hibernate}` is returned, the event manager +goes into hibernation (by calling `proc_lib:hibernate/3`), +waiting for the next event to occur. """. -callback init(InitArgs :: term()) -> {ok, State :: term()} | {ok, State :: term(), hibernate} | {error, Reason :: term()}. + -doc """ +Handle an event. + Whenever an event manager receives an event sent using `notify/2` or -`sync_notify/2`, this function is called for each installed event handler to -handle the event. +`sync_notify/2`, this function is called for each installed event handler +to handle the event. -`Event` is the `Event` argument of -[`notify/2`](`notify/2`)/[`sync_notify/2`](`sync_notify/2`). +`Event` is the `Event` argument of `notify/2` / `sync_notify/2`. `State` is the internal state of the event handler. -- If `{ok,NewState}` or `{ok,NewState,hibernate}` is returned, the event handler - remains in the event manager with the possible updated internal state - `NewState`. -- If `{ok,NewState,hibernate}` is returned, the event manager also goes into - hibernation (by calling `proc_lib:hibernate/3`), waiting for the next event to - occur. It is sufficient that one of the event handlers return - `{ok,NewState,hibernate}` for the whole event manager process to hibernate. -- If `{swap_handler,Args1,NewState,Handler2,Args2}` is returned, the event - handler is replaced by `Handler2` by first calling - [`Module:terminate(Args1,NewState)`](`c:terminate/2`) and then - [`Module2:init({Args2,Term})`](`c:init/1`), where `Term` is the return value - of [`Module:terminate/2`](`c:terminate/2`). For more information, see - `swap_handler/3`. +- If `{ok, NewState}` or `{ok, NewState, hibernate}` is returned, + the event handler remains in the event manager with the possibly + updated internal state `NewState`. + +- If `{ok, NewState, hibernate}` is returned, the event manager + also goes into hibernation (by calling `proc_lib:hibernate/3`), + waiting for the next event to occur. It is sufficient + that one of the event handlers return `{ok, NewState, hibernate}` + for the whole event manager process to hibernate. + +- If `{swap_handler, Args1, NewState, Handler2, Args2}` is returned, + the event handler is replaced by `Handler2` by first calling + [`Module:terminate(Args1, NewState)`](`c:terminate/2`) and then + [`Module2:init({Args2, Term})`](`c:init/1`), where `Term` + is the return value of [`Module:terminate/2`](`c:terminate/2`). + For more information, see `swap_handler/3`. + - If `remove_handler` is returned, the event handler is deleted by calling - [`Module:terminate(remove_handler,State)`](`c:terminate/2`). + [`Module:terminate(remove_handler, State)`](`c:terminate/2`). """. -callback handle_event(Event :: term(), State :: term()) -> {ok, NewState :: term()} | @@ -230,18 +246,22 @@ handle the event. {swap_handler, Args1 :: term(), NewState :: term(), Handler2 :: (atom() | {atom(), Id :: term()}), Args2 :: term()} | remove_handler. + -doc """ -Whenever an event manager receives a request sent using [`call/3,4`](`call/3`), -this function is called for the specified event handler to handle the request. +Handle a call. + +Whenever an event manager receives a request sent using +[`call/3,4`](`call/3`), this function is called +for the specified event handler to handle the request. `Request` is the `Request` argument of `call/3,4`. `State` is the internal state of the event handler. The return values are the same as for -[`Module:handle_event/2`](`c:handle_event/2`) except that they also contain a -term `Reply`, which is the reply to the client as the return value of -`call/3,4`. +[`Module:handle_event/2`](`c:handle_event/2`) except that +they also contain a term `Reply`, which is the reply to the client +as the return value of `call/3,4`. """. -callback handle_call(Request :: term(), State :: term()) -> {ok, Reply :: term(), NewState :: term()} | @@ -249,26 +269,31 @@ term `Reply`, which is the reply to the client as the return value of {swap_handler, Reply :: term(), Args1 :: term(), NewState :: term(), Handler2 :: (atom() | {atom(), Id :: term()}), Args2 :: term()} | {remove_handler, Reply :: term()}. + -doc """ -This function is called for each installed event handler when an event manager -receives any other message than an event or a synchronous request (or a system -message). +Handle an info message (regular process message). + +This function is called for each installed event handler when +an event manager receives any other message than an event +or a synchronous request (or a system message). `Info` is the received message. -In particular, this callback will be made when a process terminated after -calling `add_sup_handler/3`. Any event handler attached to an event manager -which in turn has a supervised handler should expect callbacks of the shape -[`Module:handle_info({'EXIT', Pid, Reason}, State)`](`c:handle_info/2`). +In particular, this callback will be made when a process terminated +after calling `add_sup_handler/3`. Any event handler attached to +an event manager which in turn has a supervised handler +should expect callbacks of the shape +[`Module:handle_info({'EXIT', Pid, Reason}, State)`](`c:handle_info/2`). -For a description of `State` and possible return values, see -[`Module:handle_event/2`](`c:handle_event/2`). +For a description of `State` and possible return values, +see [`Module:handle_event/2`](`c:handle_event/2`). > #### Note {: .info } > -> This callback is optional, so callback modules need not export it. The -> `gen_event` module provides a default implementation of this function that -> logs about the unexpected `Info` message, drops it and returns `{ok, State}`. +> This callback is optional, so callback modules need not export it. +> The `gen_event` module provides a default implementation +> of this function that logs about the unexpected `Info` message, +> drops it and returns `{ok, State}`. """. -callback handle_info(Info :: term(), State :: term()) -> {ok, NewState :: term()} | @@ -276,45 +301,52 @@ For a description of `State` and possible return values, see {swap_handler, Args1 :: term(), NewState :: term(), Handler2 :: (atom() | {atom(), Id :: term()}), Args2 :: term()} | remove_handler. + -doc """ -Whenever an event handler is deleted from an event manager, this function is -called. It is to be the opposite of [`Module:init/1`](`c:init/1`) and do any -necessary cleaning up. +Handle event handler termination. + +Whenever an event handler is deleted from an event manager, +this function is called. It is to be the opposite +of [`Module:init/1`](`c:init/1`) and do any necessary cleaning up. If the event handler is deleted because of a call to `delete_handler/3`, -`swap_handler/3`, or `swap_sup_handler/3`, `Arg` is the `Args` argument of this -function call. +`swap_handler/3`, or `swap_sup_handler/3`, `Arg` is +the `Args` argument of this function call. -`Arg={stop,Reason}` if the event handler has a supervised connection to a -process that has terminated with reason `Reason`. +`Arg = {stop, Reason}` if the event handler has a supervised connection +to a process that has terminated with reason `Reason`. -`Arg=stop` if the event handler is deleted because the event manager is -terminating. +`Arg = stop` if the event handler is deleted because +the event manager is terminating. -The event manager terminates if it is part of a supervision tree and it is -ordered by its supervisor to terminate. Even if it is _not_ part of a -supervision tree, it terminates if it receives an `'EXIT'` message from its -parent. +The event manager terminates if it is part of a supervision tree +and it is ordered by its supervisor to terminate. Even if +it is _not_ part of a supervision tree, it terminates if it receives +an `'EXIT'` message from its parent. -`Arg=remove_handler` if the event handler is deleted because another callback -function has returned `remove_handler` or `{remove_handler,Reply}`. +`Arg = remove_handler` if the event handler is deleted +because another callback function has returned `remove_handler` +or `{remove_handler, Reply}`. -`Arg={error,Term}` if the event handler is deleted because a callback function -returned an unexpected value `Term`, or `Arg={error,{'EXIT',Reason}}` if a -callback function failed. +`Arg = {error, Term}` if the event handler is deleted because +a callback function returned an unexpected value `Term`, +or `Arg = {error, {'EXIT', Reason}}` if a callback function failed. `State` is the internal state of the event handler. -The function can return any term. If the event handler is deleted because of a -call to `gen_event:delete_handler/3`, the return value of that function becomes -the return value of this function. If the event handler is to be replaced with -another event handler because of a swap, the return value is passed to the -`init` function of the new event handler. Otherwise the return value is ignored. +The function can return any term. If the event handler +is deleted because of a call to `gen_event:delete_handler/3`, +the return value of that function becomes the return value +of this function. If the event handler is to be replaced with +another event handler because of a swap, the return value +is passed to the `init` function of the new event handler. +Otherwise the return value is ignored. > #### Note {: .info } > -> This callback is optional, so callback modules need not export it. The -> `gen_event` module provides a default implementation without cleanup. +> This callback is optional, so callback modules need not export it. +> The `gen_event` module provides a default implementation +> without cleanup. """. -callback terminate(Args :: (term() | {stop, Reason :: term()} | stop | remove_handler | @@ -322,73 +354,86 @@ another event handler because of a swap, the return value is passed to the {error, term()}), State :: term()) -> term(). + -doc """ -This function is called for an installed event handler that is to update its -internal state during a release upgrade/downgrade, that is, when the instruction -`{update,Module,Change,...}`, is specified in the [`appup`](`e:sasl:appup.md`) file. +Update the event handler state after code change. + +This function is called for an installed event handler +that is to update its internal state during a release upgrade/downgrade, +that is, when the instruction `{update, Module, Change,...}`, +is specified in the [`appup`](`e:sasl:appup.md`) file. For more information, see [OTP Design Principles](`e:system:index.html`). -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. +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. `State` is the internal state of the event handler. -`Extra` is passed "as is" from the `{advanced,Extra}` part of the update -instruction. +`Extra` is passed "as is" from the `{advanced, Extra}` part +of the update instruction. The function is to return the updated internal state. > #### Note {: .info } > -> If a release upgrade/downgrade with `Change={advanced,Extra}` specified in the -> [`.appup`](`e:sasl:appup.md`) file is made when `c:code_change/3` isn't -> implemented the event handler will crash with an `undef` error reason. +> If a release upgrade/downgrade with `Change={advanced, Extra}` +> specified in the [`.appup`](`e:sasl:appup.md`) file is made +> when `c:code_change/3` is not implemented the event handler will crash +> with an `undef` error reason. """. -callback code_change(OldVsn :: (term() | {down, term()}), State :: term(), Extra :: term()) -> {ok, NewState :: term()}. + -doc """ -This function is called by a `gen_event` process in order to format/limit the -server state for debugging and logging purposes. +Format/limit the status value. + +This function is called by a `gen_event` process in in order to +format/limit the server state for debugging and logging purposes. It is called in the following situations: -- One of [`sys:get_status/1,2`](`sys:get_status/1`) is invoked to get the - `gen_event` status. `Opt` is set to the atom `normal` for this case. -- The event handler terminates abnormally and `gen_event` logs an error. `Opt` - is set to the atom `terminate` for this case. +- One of [`sys:get_status/1,2`](`sys:get_status/1`) is invoked + to get the `gen_event` status. `Opt` is set to the atom `normal` + for this case. + +- The event handler terminates abnormally and `gen_event` 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 event -handler state for these cases. An event handler callback module wishing to -change the `sys:get_status/1,2` return value as well as how its state appears in -termination error logs, exports an instance of -[`format_status/2`](`c:format_status/2`) that returns a term describing the -current state of the event handler. +handler state for these cases. An event handler callback module +wishing to change the `sys:get_status/1,2` return value as well as +how its state appears in termination error logs, exports an instance of +[`format_status/2`](`c:format_status/2`) that returns a term +describing the current state of the event handler. `PDict` is the current value of the process dictionary of `gen_event`. `State` is the internal state of the event handler. -The function is to return `Status`, a term that change the details of the -current state of the event handler. Any term is allowed for `Status`. The -`gen_event` module uses `Status` as follows: +The function is to return `Status`, a term that change the details of +the current state of the event handler. Any term is allowed for `Status`. +The `gen_event` module uses `Status` as follows: + +- When `sys:get_status/1,2` is called, `gen_event` ensures that + its return value contains `Status` in place of the state term + of the event handler. -- When `sys:get_status/1,2` is called, `gen_event` ensures that its return value - contains `Status` in place of the state term of the event handler. -- When an event handler terminates abnormally, `gen_event` logs `Status` in - place of the state term of the event handler. +- When an event handler terminates abnormally, `gen_event` logs `Status` + in place of the state term of the event handler. -One use for this function is to return compact alternative state representations -to avoid that large state terms are printed in log files. +One use for this function is to return compact alternative +state representations to avoid that large state terms +are printed in log files. > #### Note {: .info } > -> This callback is optional, so event handler modules need not export it. If a -> handler does not export this function, the `gen_event` module uses the handler -> state directly for the purposes described below. +> This callback is optional, so event handler modules need not export it. +> If a handler does not export this function, the `gen_event` module +> uses the handler state directly for the purposes described below. """. -deprecated_callback({format_status, 2, "use format_status/1 instead"}). -doc(#{since => <<"OTP R14B">>}). @@ -398,17 +443,14 @@ to avoid that large state terms are printed in log files. PDict :: [{Key :: term(), Value :: term()}], State :: term(), Status :: term(). + -doc """ A map that describes the `gen_event` process status. The keys are: - - **`state`** - The internal state of the event handler. - - **`message`** - The message that caused the event handler to terminate. - - **`reason`** - The reason that caused the event handler to terminate. - - **`log`** - The [sys log](`sys:log/2`) of the server. New associations may be added into the status map without prior notice. @@ -418,25 +460,31 @@ New associations may be added into the status map without prior notice. message => term(), reason => term(), log => [sys:system_event()] }. + -doc """ -This function is called by a `gen_event` process in order to format/limit the -server state for debugging and logging purposes. +Format/limit the status value. + +This function is called by a `gen_event` process in in order to +format/limit the server state for debugging and logging purposes. It is called in the following situations: -- One of [`sys:get_status/1,2`](`sys:get_status/1`) is invoked to get the - `gen_event` status. +- One of [`sys:get_status/1,2`](`sys:get_status/1`) is invoked + to get the `gen_event` status. + - The event handler terminates abnormally and `gen_event` logs an error. This callback is used to limit the status of the event handler returned by [`sys:get_status/1,2`](`sys:get_status/1`) or sent to `m:logger`. -The callback gets a map `Status` describing the current status and shall return -a map `NewStatus` with the same keys, but it may transform some values. +The callback gets a map `Status` describing the current status +and shall return a map `NewStatus` with the same keys, +but it may transform some values. -Two possible use cases for this callback is to remove sensitive information from -the state to prevent it from being printed in log files, or to compact large -irrelevant status items that would only clutter the logs. +Two possible use cases for this callback is to remove +sensitive information from the state to prevent it from being printed +in log files, or to compact large irrelevant status items +that would only clutter the logs. _Example_: @@ -454,12 +502,12 @@ format_status(Status) -> > #### Note {: .info } > -> This callback is optional, so event handler modules need not export it. If a -> handler does not export this function, the `gen_event` module uses the handler -> state directly for the purposes described below. +> This callback is optional, so event handler modules need not export it. +> If a handler does not export this function, the `gen_event` module +> uses the handler state directly for the purposes described below. > -> If this callback is exported but fails, to hide possibly sensitive data, the -> default function will instead return the fact that +> If this callback is exported but fails, to hide possibly sensitive data, +> the default function will instead return the fact that > [`format_status/1`](`c:format_status/1`) has crashed. """. -doc(#{since => <<"OTP 25.0">>}). @@ -478,28 +526,34 @@ format_status(Status) -> -type del_handler_ret() :: ok | term() | {'EXIT',term()}. -doc """ -The name given to an event manager when starting it. +Event manager name specification: `local`, `global`, or `via` registered. -- *`{local,Name}`* - the event manager is registered locally as +- *`{local, Name}`* - the event manager is registered locally as `Name` using [`register/2`](`register/2`). -- *`{global,GlobalName}`* - The event manager is registered - globally as `GlobalName` using `global:register_name/2`. If no name is - provided, the event manager is not registered. -- *`{via,Module,ViaName}`*, the event manager registers with the - registry represented by `Module`. The `Module` callback is to export the - functions `register_name/2`, `unregister_name/1`, `whereis_name/1`, and - `send/2`, which are to behave as the corresponding functions in `m:global`. - Thus, `{via,global,GlobalName}` is a valid reference. +- *`{global, GlobalName}`* - The event manager is registered + globally as `GlobalName` using `global:register_name/2`. + If no name is provided, the event manager is not registered. +- *`{via, Module, ViaName}`*, the event manager registers with the + registry represented by `Module`. The `Module` callback is to export + the functions `register_name/2`, `unregister_name/1`, `whereis_name/1`, + and `send/2`, which are to behave as the corresponding functions + in `m:global`. Thus, `{via, global, GlobalName}` is a valid reference. """. -type emgr_name() :: {'local', atom()} | {'global', term()} | {'via', atom(), term()}. + -type debug_flag() :: 'trace' | 'log' | 'statistics' | 'debug' | {'logfile', string()}. --doc "Options that can be used to configure an event handler when it is started.". + +-doc """ +Options that can be used to configure an event handler +when it is started. +""". -type options() :: [{'timeout', timeout()} | {'debug', [debug_flag()]} | {'spawn_opt', [proc_lib:start_spawn_option()]} | {'hibernate_after', timeout()}]. + -doc """ A reference used to locate an event manager. @@ -507,10 +561,11 @@ The reference can be any of the following: - The pid of the event manager - `Name`, if the event manager is locally registered -- `{Name,Node}`, if the event manager is locally registered at another node -- `{global,GlobalName}`, if the event manager is globally registered -- `{via,Module,ViaName}`, if the event manager is registered through an - alternative process registry +- `{Name, Node}`, if the event manager is locally registered + at another node +- `{global, GlobalName}`, if the event manager is globally registered +- `{via, Module, ViaName}`, if the event manager is registered through + an alternative process registry """. -type emgr_ref() :: atom() | {atom(), node()} | {'global', term()} | {'via', atom(), term()} | pid(). @@ -521,31 +576,37 @@ The reference can be any of the following: -opaque request_id() :: gen:request_id(). -doc """ -An opaque collection of request identifiers (`t:request_id/0`) where each -request identifier can be associated with a label chosen by the user. For more -information see `reqids_new/0`. +An opaque collection of request identifiers (`t:request_id/0`). + +Each request identifier can be associated with a label +chosen by the user. For more information see `reqids_new/0`. """. -opaque request_id_collection() :: gen:request_id_collection(). -doc """ +Response time-out for an asynchronous call. + Used to set a time limit on how long to wait for a response using either `receive_response/2`, `receive_response/3`, `wait_response/2`, or -`wait_response/3`. The time unit used is `millisecond`. Currently valid values: +`wait_response/3`. The time unit used is `millisecond`. +Currently valid values: - **`0..4294967295`** - Timeout relative to current time in milliseconds. -- **`infinity`** - Infinite timeout. That is, the operation will never time out. +- **`infinity`** - Infinite timeout. That is, the operation + will never time out. - **`{abs, Timeout}`** - An absolute - [Erlang monotonic time](`erlang:monotonic_time/1`) timeout in milliseconds. - That is, the operation will time out when - [`erlang:monotonic_time(millisecond)`](`erlang:monotonic_time/1`) returns a - value larger than or equal to `Timeout`. `Timeout` is not allowed to identify - a time further into the future than `4294967295` milliseconds. Identifying the - timeout using an absolute timeout value is especially handy when you have a - deadline for responses corresponding to a complete collection of requests - (`t:request_id_collection/0`) , since you do not have to recalculate the - relative time until the deadline over and over again. + [Erlang monotonic time](`erlang:monotonic_time/1`) timeout + in milliseconds. That is, the operation will time out when + [`erlang:monotonic_time(millisecond)`](`erlang:monotonic_time/1`) + returns a value larger than or equal to `Timeout`. + `Timeout` is not allowed to identify a time further into the future + than `4294967295` milliseconds. Identifying the timeout using + an absolute timeout value is especially handy when you have a + deadline for responses corresponding to a complete collection + of requests (`t:request_id_collection/0`) , since you do not have to + recalculate the relative time until the deadline over and over again. """. -type response_timeout() :: timeout() | {abs, integer()}. @@ -577,13 +638,18 @@ start() -> gen:start(?MODULE, nolink, ?NO_CALLBACK, [], []). -doc """ -Creates a stand-alone event manager process, that is, an event manager that is -not part of a supervision tree and thus has no supervisor. +Create a stand-alone event manager process, possibly nameless. -For a description of the arguments and return values, see -[`start_link/1`](`start_link/1`). +Equivalent to [`start(EventMgrName, Options)`](`start/2`). + +With argument `EventMgrName`, `Options` is `[]`. + +With argument `Options` a nameless event manager is created. + +For a description of the arguments and return values, see `start_link/2`. """. --spec start(EventMgrNameOrOptions :: emgr_name() | options()) -> start_ret(). +-spec start(EventMgrName :: emgr_name()) -> start_ret(); + (Options :: options()) -> start_ret(). start(Name) when is_tuple(Name) -> gen:start(?MODULE, nolink, Name, ?NO_CALLBACK, [], []); start(Options) when is_list(Options) -> @@ -592,11 +658,12 @@ start(Arg) -> error(badarg, [Arg]). -doc """ -Creates a stand-alone event manager process, that is, an event manager that is -not part of a supervision tree and thus has no supervisor. +Create a stand-alone event manager process. -For a description of the arguments and return values, see -[`start_link/2`](`start_link/2`). +The created event manager process is not part of a supervision tree +and thus has no supervisor. + +For a description of the arguments and return values, see `start_link/2`. """. -doc(#{since => <<"OTP 20.0">>}). -spec start(EventMgrName :: emgr_name(), Options :: options()) -> start_ret(). @@ -611,16 +678,19 @@ start_link() -> gen:start(?MODULE, link, ?NO_CALLBACK, [], []). -doc """ -Creates an event manager process as part of a supervision tree. +Create an event manager process as part of a supervision tree, +possibly nameless. -If called with `t:emgr_name/0`, then it is equivalent to [`start(EventMgrName, [])`](`start/2`). +Equivalent to [`start_link(EventMgrName, Options)`](`start_link/2`). -If called with `t:options/0`, then a nameless event manager is created using `Options`. +With argument `EventMgrName`, `Options` is `[]`. -For a description of the arguments and return values, see -[`start_link/2`](`start_link/2`). +With argument `Options` a nameless event manager is created. + +For a description of the arguments and return values, see `start_link/2`. """. --spec start_link(EventMgrNameOrOptions :: emgr_name() | options()) -> start_ret(). +-spec start_link(EventMgrName :: emgr_name()) -> start_ret(); + (Options :: options()) -> start_ret(). start_link(Name) when is_tuple(Name) -> gen:start(?MODULE, link, Name, ?NO_CALLBACK, [], []); start_link(Options) when is_list(Options) -> @@ -629,47 +699,54 @@ start_link(Arg) -> error(badarg, [Arg]). -doc """ -Creates an event manager process as part of a supervision tree. +Create an event manager process as part of a supervision tree. The function is to be called, directly or indirectly, by the supervisor. -For example, it ensures that the event manager is linked to the caller (supervisor). +For example, it ensures that the event manager is linked +to the caller (supervisor). -- If option `{hibernate_after,HibernateAfterTimeout}` is present, the +- If option `{hibernate_after, HibernateAfterTimeout}` is present, the `gen_event` 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`). + milliseconds and if no message is received, the process + goes into hibernation automatically (by calling `proc_lib:hibernate/3`). -If the event manager is successfully created, the function returns `{ok,Pid}`, -where `Pid` is the pid of the event manager. +If the event manager is successfully created, +the function returns `{ok, Pid}` where `Pid` is the `t:pid/0` +of the event manager. -If a process with the specified `EventMgrName` exists already, the function -returns `{error,{already_started,OtherPid}}`, where `OtherPid` is the pid of -that process, and the event manager process exits with reason `normal`. +If a process with the specified `EventMgrName` exists already, +the function returns `{error,{already_started,OtherPid}}`, +where `OtherPid` is the pid of that process, and the event manager process +exits with reason `normal`. If the event manager fails to start within the specified start timeout -`{timeout,Time}`, which is very unlikely since the start does not interact with -other processes, the function returns `{error,timeout}` and the failed event -manager is killed with [`exit(_, kill)`](`erlang:exit/2`). +`{timeout, Time}`, which is very unlikely since the start +does not interact with other processes, the function returns +`{error, timeout}` and the failed event manager is killed with +[`exit(_, kill)`](`erlang:exit/2`). -If `start_link/1,2` returns `{error,_}`, the started event manager process has -terminated. If an `'EXIT'` message was delivered to the calling process (due to -the process link), that message has been consumed. +If `start_link/1,2` returns `{error, _}`, the started event manager process +has terminated. If an `'EXIT'` message was delivered +to the calling process (due to the process link), that message +has been consumed. > #### Warning {: .warning } > -> Before OTP 26.0, if the started event manager failed to register its name, -> this founction could return `{error,{already_started,OtherPid}}` _before_ the -> started event manager process had terminated so starting again might fail -> because the registered name was not yet unregistered, and an `'EXIT'` message -> could arrive later to the process calling this function. +> Before OTP 26.0, if the started event manager failed to register +> its name, this founction could return +> `{error, {already_started, OtherPid}}` _before_ +> the started event manager process had terminated, +> so starting again might fail because the registered name +> was not yet unregistered, and an `'EXIT'` message could arrive later +> to the process calling this function. > -> But if the start timed out, this function killed the started event manager -> process and returned `{error,timeout}`, and then the process link -> `{'EXIT',Pid,killed}` message _was_ consumed. +> But if the start timed out, this function killed +> the started event manager process and returned `{error, timeout}`, +> and then the process link `{'EXIT', Pid, killed}` message _was_ consumed. > -> The start was made synchronous in OTP 26.0 and the guarantee was implemented -> that no process link `'EXIT'` message from a failed start will linger in the -> caller's inbox. +> The start was made synchronous in OTP 26.0 and a guarantee +> was implemented that no process link `'EXIT'` message +> from a failed start will linger in the caller's inbox. """. -doc(#{since => <<"OTP 20.0">>}). -spec start_link(EventMgrName :: emgr_name(), Options :: options()) -> start_ret(). @@ -685,12 +762,17 @@ start_monitor() -> gen:start(?MODULE, monitor, ?NO_CALLBACK, [], []). -doc """ -Creates a stand-alone event manager process, that is, an event manager that is -not part of a supervision tree (and thus has no supervisor) and atomically sets -up a monitor to the newly created process. +Creates a stand-alone event manager process, +monitored, possibly nameless. -For a description of the arguments and return values, see `start_monitor/2` and -`start_link/1`. +Equivalent to [`start_monitor(EventMgrName, Options)`](`start_monitor/2`). + +With argument `EventMgrName`, `Options` is `[]`. + +With argument `Options` a nameless event manager is created. + +For a description of the arguments and return values, +see `start_monitor/2` and `start_link/1`. """. -doc(#{since => <<"OTP 23.0">>}). -spec start_monitor(EventMgrNameOrOptions :: emgr_name() | options()) -> start_mon_ret(). @@ -702,17 +784,21 @@ start_monitor(Arg) -> error(badarg, [Arg]). -doc """ -Creates a stand-alone event manager process, that is, an event manager that is -not part of a supervision tree (and thus has no supervisor) and atomically sets -up a monitor to the newly created process. +Creates a stand-alone event manager process, monitored. + +The created event manager process is not part of a supervision tree +and thus has no supervisor. A monitor is atomically set up +to the newly created process. For a description of the arguments and return values, see -[`start_link/2`](`start_link/2`). Note that the return value on successful -start differs from `start_link/2`. `start_monitor/0,1,2` will return -`{ok,{Pid,Mon}}` where `Pid` is the process identifier of the process, and `Mon` -is a reference to the monitor set up to monitor the process. If the start is not -successful, the caller will be blocked until the `DOWN` message has been -received and removed from the message queue. +[`start_link/2`](`start_link/2`). Note that the return value +for a successful start differs from `start_link/2`. +`start_monitor/0,1,2` will return `{ok, {Pid, Mon}}` +where `Pid` is the process identifier of the process, +and `Mon` is a reference to the monitor set up to monitor the process. +If the start is not successful, the caller will be blocked +until the `DOWN` message has been received and removed +from the message queue. """. -doc(#{since => <<"OTP 23.0">>}). -spec start_monitor(EventMgtName :: emgr_name(), Options :: options()) -> start_mon_ret(). @@ -721,7 +807,7 @@ start_monitor(Name, Options) when is_tuple(Name), is_list(Options) -> start_monitor(Name, Options) -> error(badarg, [Name, Options]). -%% -spec init_it(pid(), 'self' | pid(), emgr_name(), module(), [term()], [_]) -> +%% -spec init_it(pid(), 'self' | pid(), emgr_name(), module(), [term()], [_]) -> -doc false. init_it(Starter, self, Name, Mod, Args, Options) -> init_it(Starter, self(), Name, Mod, Args, Options); @@ -734,49 +820,58 @@ init_it(Starter, Parent, Name0, _, _, Options) -> loop(Parent, Name, [], HibernateAfterTimeout, Debug, false). -doc """ -Adds a new event handler to event manager `EventMgrRef`. The event manager calls -[`Module:init/1`](`c:init/1`) to initiate the event handler and its internal -state. +Add a new event handler to an event manager. + +The new event handler is added to event manager `EventMgrRef`. +The event manager calls [`Module:init/1`](`c:init/1`) +to initiate the event handler and its internal state. -`Handler` is the name of the callback module `Module` or a tuple `{Module,Id}`, -where `Id` is any term. The `{Module,Id}` representation makes it possible to -identify a specific event handler when many event handlers use the same callback -module. +`Handler` is the name of the callback module `Module` +or a tuple `{Module, Id}`, where `Id` is any term. +The `{Module, Id}` representation makes it possible to +identify a specific event handler, when many event handlers +use the same callback module. `Args` is any term that is passed as the argument to [`Module:init/1`](`c:init/1`). -If [`Module:init/1`](`c:init/1`) returns a correct value indicating successful -completion, the event manager adds the event handler and this function returns -`ok`. If [`Module:init/1`](`c:init/1`) fails with `Reason` or returns -`{error,Reason}`, the event handler is ignored and this function returns -`{'EXIT',Reason}` or `{error,Reason}`, respectively. +If [`Module:init/1`](`c:init/1`) returns a correct value +indicating successful completion, the event manager +adds the event handler and this function returns `ok`. +If [`Module:init/1`](`c:init/1`) fails with `Reason` or returns +`{error,Reason}`, the event handler is ignored and this function +returns `{'EXIT',Reason}` or `{error,Reason}`, respectively. """. -spec add_handler(EventMgrRef :: emgr_ref(), Handler :: handler(), Args :: term()) -> term(). add_handler(M, Handler, Args) -> rpc(M, {add_handler, Handler, Args}). -doc """ -Adds a new event handler in the same way as `add_handler/3`, but also supervises -the connection by linking the event handler and the calling process. +Add a new event handler to an event manager, supervised. -- If the calling process later terminates with `Reason`, the event manager - deletes any supervised event handlers by calling +The new event handler is added as for `add_handler/3`, +but the event manager also supervises the connection +by linking the event handler and the calling process. + +- If the calling process later terminates with `Reason`, + the event manager deletes any supervised event handlers by calling [`Module:terminate/2`](`c:terminate/2`), then calls [`Module:handle_info/2`](`c:handle_info/2`) for each remaining handler. -- If the event handler is deleted later, the event manager sends a message - `{gen_event_EXIT,Handler,Reason}` to the calling process. `Reason` is one of - the following: - - - `normal`, if the event handler has been removed because of a call to - [`delete_handler/3`](`delete_handler/3`), or `remove_handler` has been - returned by a callback function (see below). - - `shutdown`, if the event handler has been removed because the event manager - is terminating. - - `{swapped,NewHandler,Pid}`, if the process `Pid` has replaced the event - handler with another event handler `NewHandler` using a call to - `swap_handler/3` or `swap_sup_handler/3`. - - A term, if the event handler is removed because of an error. Which term - depends on the error. + +- If the event handler is deleted later, the event manager + sends a message `{gen_event_EXIT,Handler,Reason}` + to the calling process. `Reason` is one of the following: + + + `normal`, if the event handler has been removed because of + a call to [`delete_handler/3`](`delete_handler/3`), + or `remove_handler` has been returned by a callback function + (see below). + + `shutdown`, if the event handler has been removed + because the event manager is terminating. + + `{swapped, NewHandler, Pid}`, if the process `Pid` has replaced + the event handler with another event handler `NewHandler`, + through a call to `swap_handler/3` or `swap_sup_handler/3`. + + Other `t:term/0`, if the event handler is removed + because of an error. Which term depends on the error. For a description of the arguments and return values, see `add_handler/3`. """. @@ -785,25 +880,29 @@ add_sup_handler(M, Handler, Args) -> rpc(M, {add_sup_handler, Handler, Args, self()}). -doc """ -Sends an asynchronous event notification to event manager `EventMgrRef`. The event -manager calls [`Module:handle_event/2`](`c:handle_event/2`) for each installed +Send an asynchronous event notification to an event manager. + +The event is sent to `EventMgrRef`, that calls +[`Module:handle_event/2`](`c:handle_event/2`) for each installed event handler to handle the event. `Event` is any term that is passed as one of the arguments to [`Module:handle_event/2`](`c:handle_event/2`). -`notify/1` does not fail even if the specified event manager does not exist, -unless it is specified as `Name`. +`notify/1` does not fail even if the specified event manager +does not exist, unless it is specified as `Name`. """. -spec notify(EventMgrRef :: emgr_ref(), Event :: term()) -> 'ok'. notify(M, Event) -> send(M, {notify, Event}). -doc """ -Sends a synchronous event notification to event manager `EventMgrRef`. The event -manager calls [`Module:handle_event/2`](`c:handle_event/2`) for each installed event -handler to handle the event. This function will return `ok` after the event has -been handled by all event handlers. +Send a synchronous event notification to an event manager. + +The event is sent to `EventMgrRef` that callsr calls +[`Module:handle_event/2`](`c:handle_event/2`) for each installed +event handler to handle the event. This function will return `ok` +after the event has been handled by all event handlers. `Event` is any term that is passed as one of the arguments to [`Module:handle_event/2`](`c:handle_event/2`). @@ -816,60 +915,66 @@ sync_notify(M, Event) -> rpc(M, {sync_notify, Event}). call(M, Handler, Query) -> call1(M, Handler, Query). -doc """ -Makes a synchronous call to event handler `Handler` installed in event manager -`EventMgrRef` by sending a request and waiting until a reply arrives or a -time-out occurs. The event manager calls +Make a synchronous call to an event handler. + +The call is sent to `Handler`, installed in event manager `EventMgrRef`, +by sending a request and waiting until a reply arrives, +or a time-out occurs. The event manager calls [`Module:handle_call/2`](`c:handle_call/2`) to handle the request. `Request` is any term that is passed as one of the arguments to [`Module:handle_call/2`](`c:handle_call/2`). -`Timeout` is an integer greater than zero that specifies how many milliseconds -to wait for a reply, or the atom `infinity` to wait indefinitely. Defaults -to 5000. If no reply is received within the specified time, the function call -fails. +`Timeout` is an integer greater than zero that specifies +how many milliseconds to wait for a reply, or the atom `infinity` +to wait indefinitely. Defaults to 5000. If no reply is received +within the specified time, the function call fails. The return value `Reply` is defined in the return value of -[`Module:handle_call/2`](`c:handle_call/2`). If the specified event handler is -not installed, the function returns `{error,bad_module}`. If the callback -function fails with `Reason` or returns an unexpected value `Term`, this -function returns `{error,{'EXIT',Reason}}` or `{error,Term}`, respectively. - -When this call fails it [exits](`erlang:exit/1`) the calling process. The exit -term is on the form `{Reason, Location}` where -`Location = {gen_event,call,ArgList}`. See -[`gen_server:call/3` ](`gen_server:call/3`)that has a description of relevant -values for the `Reason` in the exit term. +[`Module:handle_call/2`](`c:handle_call/2`). If the specified +event handler is not installed, the function returns +`{error, bad_module}`. If the callback function fails with `Reason`, +or returns an unexpected value `Term`, this function returns +`{error, {'EXIT', Reason}}` or `{error, Term}`, respectively. + +When this call fails it [exits](`erlang:exit/1`) the calling process. +The exit term is on the form `{Reason, Location}` where +`Location = {gen_event, call, ArgList}`. See `gen_server:call/3` +that has a description of relevant values for the `Reason` +in the exit term. """. -spec call(EventMgrRef :: emgr_ref(), Handler :: handler(), Request :: term(), Timeout :: timeout()) -> term(). call(M, Handler, Query, Timeout) -> call1(M, Handler, Query, Timeout). -doc """ -Sends an asynchronous `call` request `Request` to event handler `Handler` -installed in the event manager identified by `EventMgrRef` and returns a request -identifier `ReqId`. The return value `ReqId` shall later be used with -`receive_response/2`, `wait_response/2`, or `check_response/2` to fetch the -actual result of the request. - -Besides passing the request identifier directly to these functions, it can also -be saved in a request identifier collection using `reqids_add/3`. Such a -collection of request identifiers can later be used in -order to get one response corresponding to a request in the collection by -passing the collection as argument to `receive_response/3`, `wait_response/3`, -or `check_response/3`. If you are about to save the request identifier in a -request identifier collection, you may want to consider using `send_request/5` -instead. - -The call -`gen_event:receive_response(gen_event:send_request(EventMgrRef, Handler, Request), Timeout)` +Send an asynchronous `call` request to an event handler. + +This function sends the call request `Request` to the event handler +`Handler` installed in the event manager identified by `EventMgrRef`, +and returns a request identifier `ReqId`. The return value `ReqId` +shall later be used with `receive_response/2`, `wait_response/2`, +or `check_response/2` to fetch the actual result of the request. + +Besides passing the request identifier directly to these functions, +it can also be stored in a request identifier collection +using `reqids_add/3`. Such a collection of request identifiers +can later be used in order to get one response corresponding to +a request in the collection by passing the collection as argument to +`receive_response/3`, `wait_response/3`, or `check_response/3`. +If you are about to store the request identifier in a collection, +you may want to consider using `send_request/5` instead. + +The calls +`gen_event:receive_response(gen_event:send_request(EventMgrRef, +Handler, Request), Timeout)` can be seen as equivalent to -[`gen_event:call(EventMgrRef, Handler, Request, Timeout)`](`call/3`), ignoring -the error handling. +[`gen_event:call(EventMgrRef, Handler, Request, Timeout)`](`call/3`), +ignoring the error handling. -The event manager calls [`Module:handle_call/2`](`c:handle_call/2`) to handle -the request. +The event manager calls [`Module:handle_call/2`](`c:handle_call/2`) +to handle the request. -`Request` is any term that is passed as one of the arguments to +`Request` may be any term and is passed as one of the arguments to [`Module:handle_call/2`](`c:handle_call/2`). """. -doc(#{since => <<"OTP 23.0">>}). @@ -884,18 +989,23 @@ send_request(M, Handler, Request) -> end. -doc """ -Sends an asynchronous `call` request `Request` to event handler `Handler` -installed in the event manager identified by `EventMgrRef`. The `Label` will be -associated with the request identifier of the operation and added to the returned +Send an asynchronous `call` request to an event handler, +storing it in a request identifier collection. + +This function sends the call request `Request` to the event handler +`Handler` installed in the event manager identified by `EventMgrRef`. +The `Label` will be associated with the request identifier +of the operation and added to the returned request identifier collection `NewReqIdCollection`. -The collection can later be used in order to get one response corresponding to a -request in the collection by passing the collection as argument to `receive_response/3`, -`wait_response/3`, or `check_response/3`. +The collection can later be used in order to get one response +corresponding to a request in the collection by passing the collection +as argument to `receive_response/3`, `wait_response/3`, +or `check_response/3`. The same as calling [`gen_event:reqids_add`](`reqids_add/3`)`(`[`gen_event:send_request`](`send_request/3`)`(EventMgrRef, Handler, Request), Label, ReqIdCollection)`, -but calling [`send_request/5`](`send_request/5`) is slightly more efficient. +but slightly more efficient. """. -doc(#{since => <<"OTP 25.0">>}). -spec send_request(EventMgrRef::emgr_ref(), @@ -913,29 +1023,31 @@ send_request(M, Handler, Request, Label, ReqIdCol) -> end. -doc """ -Wait for a response corresponding to the request identifier `ReqId`. The request -must have been made by `send_request/3` to the `gen_statem` process. This -function must be called from the same process from which `send_request/3` was -made. +Wait for a request resonse. + +Wait for the response to the request identifier `ReqId`. The request +must have been made by `send_request/3`, from the same process +that called `send_request/3`. -`WaitTime` specifies how long to wait for a response. If no response is received -within the specified time, the function returns `timeout` and no cleanup is -done, and thus the function can be invoked repeatedly until a reply is returned. +`WaitTime` specifies how long to wait for a response. +If no response is received within the specified time, +the function returns `timeout` and no cleanup is done, +Thus the function can be invoked repeatedly until a reply is returned. The return value `Reply` is defined in the return value of [`Module:handle_call/2`](`c:handle_call/2`). If the specified event handler is not installed, the function returns -`{error,bad_module}`. If the callback function fails with `Reason` or returns an -unexpected value `Term`, this function returns `{error,{'EXIT',Reason}}` or -`{error,Term}`, respectively. If the event manager dies before or during the -request this function returns `{error,{Reason, EventMgrRef}}`. +`{error, bad_module}`. If the callback function fails with `Reason`, +or returns an unexpected value `Term`, this function returns +`{error,{'EXIT',Reason}}` or `{error,Term}`, respectively. +If the event manager dies before or during the request +this function returns `{error, {Reason, EventMgrRef}}`. The difference between `receive_response/2` and -[`wait_response/2`](`wait_response/2`) is that -[`receive_response/2`](`receive_response/2`) abandons the request at timeout so -that a potential future response is ignored, while -[`wait_response/2`](`wait_response/2`) does not. +`wait_response/2` is that `receive_response/2` abandons the request +at timeout so that a potential future response is ignored, +while [`wait_response/2`](`wait_response/2`) does not. """. -doc(#{since => <<"OTP 23.0">>}). -spec wait_response(ReqId, WaitTime) -> Result when @@ -955,49 +1067,57 @@ wait_response(ReqId, WaitTime) -> end. -doc """ -Wait for a response corresponding to a request identifier saved in -`ReqIdCollection`. All request identifiers of `ReqIdCollection` must correspond -to requests that have been made using `send_request/3` or `send_request/5`, and -all requests must have been made by the process calling this function. - -The `Label` in the response equals the `Label` associated with the request -identifier that the response corresponds to. The `Label` of a request identifier -is associated when [saving the request id](`reqids_add/3`) in a request -identifier collection, or when sending the request using `send_request/5`. - -Compared to `wait_response/2`, the returned result associated with a specific -request identifier or an exception associated with a specific request identifier -will be wrapped in a 3-tuple. The first element of this tuple equals the value -that would have been produced by [`wait_response/2`](`wait_response/2`), the -second element equals the `Label` associated with the specific request -identifier, and the third element `NewReqIdCollection` is a possibly modified +Wait for any request response in a collection. + +Wait for a response in a `ReqIdCollection`. All request identifiers +of `ReqIdCollection` must correspond to requests that have been made +using `send_request/3` or `send_request/5`, and all requests +must have been made by the process calling this function. + +The `Label` in the response is the `Label` associated with +the request identifier that the response corresponds to. +The `Label` of a request identifier is associated +when [adding the request id](`reqids_add/3`) to a collection, +or when sending the request using `send_request/5`. + +Compared to `wait_response/2`, the returned result or exception +associated with a specific request identifier will be wrapped +in a 3-tuple `{Response, Label, NewReqIdCollection}`. +`Response` is the value that would have been produced +by `wait_response/2`, `Label` is the value associated with +the specific [request identifier](`t:request_id/0`) +and `NewReqIdCollection` is a possibly modified request identifier collection. -If `ReqIdCollection` is empty, `no_request` will be returned. If no response is -received before the `WaitTime` timeout has triggered, the atom `timeout` is -returned. It is valid to continue waiting for a response as many times as needed -up until a response has been received and completed by `check_response()`, +If `ReqIdCollection` is empty, `no_request` will be returned. + +If no response is received before the `WaitTime` has expired, +`timeout` is returned. It is valid to continue waiting +for a response as many times as needed up until a response +has been received and completed by `check_response()`, `receive_response()`, or `wait_response()`. -The difference between `receive_response/3` and -[`wait_response/3`](`wait_response/3`) is that -[`receive_response/3`](`receive_response/3`) abandons requests at timeout so -that potential future responses are ignored, while +The difference between `receive_response/3` and `wait_response/3` +is that `receive_response/3` abandons requests at time-out +so that potential future responses are ignored, while [`wait_response/3`](`wait_response/3`) does not. -If `Delete` equals `true`, the association with `Label` will have been deleted -from `ReqIdCollection` in the resulting `NewReqIdCollection`. If `Delete` equals -`false`, `NewReqIdCollection` will equal `ReqIdCollection`. Note that deleting -an association is not for free and that a collection containing already handled +If `Delete` is `true`, the association with `Label` +has been deleted from `ReqIdCollection` in the resulting +`NewReqIdCollection`. If `Delete` is`false`, `NewReqIdCollection` +will equal `ReqIdCollection`. Note that deleting an association +is not for free and that a collection containing already handled requests can still be used by subsequent calls to -[`wait_response/3`](`wait_response/3`), `check_response/3`, and -`receive_response/3`. However, without deleting handled associations, the above -calls will not be able to detect when there are no more outstanding requests to -handle, so you will have to keep track of this some other way than relying on a -`no_request` return. Note that if you pass a collection only containing -associations of already handled or abandoned requests to -[`wait_response/3`](`wait_response/3`), it will always block until a timeout -determined by `WaitTime` is triggered and then return `no_reply`. +`wait_response/3`, `check_response/3`, and `receive_response/3`. + +However, without deleting handled associations, the above +calls will not be able to detect when there are +no more outstanding requests to handle, so you will have to keep track +of this some other way than relying on a `no_request` return. +Note that if you pass a collection only containing +associations of already handled or abandoned requests +to this function, it will always block until `WaitTime` expires +and then return `timeout`. """. -doc(#{since => <<"OTP 25.0">>}). -spec wait_response(ReqIdCollection, WaitTime, Delete) -> Result when @@ -1024,31 +1144,34 @@ wait_response(ReqIdCol, WaitTime, Delete) -> end. -doc """ -Receive a response corresponding to the request identifier `ReqId`. The request -must have been made by `send_request/3` to the `gen_statem` process. This -function must be called from the same process from which `send_request/3` was -made. - -`Timeout` specifies how long to wait for a response. If no response is received -within the specified time, the function returns `timeout`. Assuming that the -server executes on a node supporting aliases (introduced in OTP 24) the request -will also be abandoned. That is, no response will be received after a timeout. +Receive a request response. + +Receive a response corresponding to the request identifier `ReqId`. +The request must have been made by `send_request/3`, +and it must have been made from the same process calling this function. + +`Timeout` specifies how long to wait for a response. +If no response is received within the specified time, +this function returns `timeout`. Assuming that the +server executes on a node supporting aliases (introduced in OTP 24) +the request will also be abandoned. That is, +no response will be received after a timeout. Otherwise, a stray response might be received at a later time. The return value `Reply` is defined in the return value of [`Module:handle_call/2`](`c:handle_call/2`). -If the specified event handler is not installed, the function returns -`{error,bad_module}`. If the callback function fails with `Reason` or returns an -unexpected value `Term`, this function returns `{error,{'EXIT',Reason}}` or -`{error,Term}`, respectively. If the event manager dies before or during the -request this function returns `{error,{Reason, EventMgrRef}}`. - -The difference between `wait_response/2` and -[`receive_response/2`](`receive_response/2`) is that -[`receive_response/2`](`receive_response/2`) abandons the request at timeout so -that a potential future response is ignored, while -[`wait_response/2`](`wait_response/2`) does not. +If the specified event handler is not installed, this function returns +`{error, bad_module}`. If the callback function fails +with `Reason` or returns an unexpected value `Term`, +this function returns `{error, {'EXIT', Reason}}` or`{error,Term}`, +respectively. If the event manager dies before or during the +request this function returns `{error, {Reason, EventMgrRef}}`. + +The difference between `wait_response/2` and `receive_response/2` +is that `receive_response/2` abandons the request at time-out +so that a potential future response is ignored, +while [`wait_response/2`](`wait_response/2`) does not. """. -doc(#{since => <<"OTP 24.0">>}). -spec receive_response(ReqId, Timeout) -> Result when @@ -1068,50 +1191,59 @@ receive_response(ReqId, Timeout) -> end. -doc """ -Receive a response corresponding to a request identifier saved in -`ReqIdCollection`. All request identifiers of `ReqIdCollection` must correspond -to requests that have been made using `send_request/3` or `send_request/5`, and -all requests must have been made by the process calling this function. - -The `Label` in the response equals the `Label` associated with the request -identifier that the response corresponds to. The `Label` of a request identifier -is associated when [adding the request id](`reqids_add/3`) in a request -identifier collection, or when sending the request using `send_request/5`. - -Compared to `receive_response/2`, the returned result associated with a specific -request identifier will be wrapped in a 3-tuple. The first element of this tuple -equals the value that would have been produced by -[`receive_response/2`](`receive_response/2`), the second element equals the -`Label` associated with the specific request identifier, and the third element -`NewReqIdCollection` is a possibly modified request identifier collection. - -If `ReqIdCollection` is empty, the atom `no_request` will be returned. - -`Timeout` specifies how long to wait for a response. If no response is received -within the specified time, the function returns `timeout`. Assuming that the -server executes on a node supporting aliases (introduced in OTP 24) all requests -identified by `ReqIdCollection` will also be abandoned. That is, no responses -will be received after a timeout. Otherwise, stray responses might be received +Receive a request response in a collection. + +Receive a response in `ReqIdCollection`. All request identifiers +of `ReqIdCollection` must correspond to requests that have been +made using `send_request/3` or `send_request/5`, and all requests +must have been made by the process calling this function. + +The `Label` in the response is the `Label` associated with +the request identifier that the response corresponds to. +The `Label` of a request identifier is associated +when [adding the request id](`reqids_add/3`) to a collection, +or when sending the request using `send_request/5`. + +Compared to `receive_response/2`, the returned result or exception +associated with a specific request identifier will be wrapped +in a 3-tuple `{Response, Label, NewReqIdCollection}`. +`Response` is the value that would have been produced +by `receive_response/2`, `Label` is the value associated with +the specific [request identifier](`t:request_id/0`) +and `NewReqIdCollection` is a possibly modified +request identifier collection. + +If `ReqIdCollection` is empty, `no_request` will be returned. + +`Timeout` specifies how long to wait for a response. If no response +is received within the specified time, the function returns `timeout`. +Assuming that the server executes on a node supporting aliases +(introduced in OTP 24) all requests identified by `ReqIdCollection` +will also be abandoned. That is, no responses will be received +after a time-out. Otherwise, stray responses might be received at a later time. -The difference between [`receive_response/3`](`receive_response/3`) and -`wait_response/3` is that [`receive_response/3`](`receive_response/3`) abandons -the requests at timeout so that potential future responses are ignored, while -[`wait_response/3`](`wait_response/3`) does not. +The difference between `receive_response/3` and `wait_response/3` +is that `receive_response/3` abandons the requests at time-out +so that potential future responses are ignored, +while `wait_response/3` does not. -If `Delete` equals `true`, the association with `Label` will have been deleted -from `ReqIdCollection` in the resulting `NewReqIdCollection`. If `Delete` equals -`false`, `NewReqIdCollection` will equal `ReqIdCollection`. Note that deleting -an association is not for free and that a collection containing already handled +If `Delete` is `true`, the association with `Label` +is deleted from `ReqIdCollection` in the resulting +`NewReqIdCollection`. If `Delete` is `false`, `NewReqIdCollection` +will equal `ReqIdCollection`. Note that deleting an association +is not for free and that a collection containing already handled requests can still be used by subsequent calls to -[`receive_response/3`](`receive_response/3`), `check_response/3`, and -`wait_response/3`. However, without deleting handled associations, the above -calls will not be able to detect when there are no more outstanding requests to -handle, so you will have to keep track of this some other way than relying on a -`no_request` return. Note that if you pass a collection only containing +`receive_response/3`, `check_response/3`, and `wait_response/3`. + +However, without deleting handled associations, +the above calls will not be able to detect when there are +no more outstanding requests to handle, so you will have to keep track +of this some other way than relying on a `no_request` return. +Note that if you pass a collection only containing associations of already handled or abandoned requests to -[`receive_response/3`](`receive_response/3`), it will always block until a -timeout determined by `Timeout` is triggered. +`receive_response/3`, it will always block until `Timeout` expires +and then return `timeout`. """. -doc(#{since => <<"OTP 25.0">>}). -spec receive_response(ReqIdCollection, Timeout, Delete) -> Result when @@ -1138,18 +1270,24 @@ receive_response(ReqIdCol, Timeout, Delete) -> end. -doc """ -Check if `Msg` is a response corresponding to the request identifier `ReqId`. -The request must have been made by `send_request/3`. +Check if a received message is a request response. + +Check if `Msg` is a response corresponding to +the request identifier `ReqId`. The request must have been made +by `send_request/3`, and by the same process calling this function. -If `Msg` is a response corresponding to `ReqId` the response is returned; -otherwise, `no_reply` is returned and no cleanup is done, and thus the function -must be invoked repeatedly until a response is returned. +If `Msg` is a response corresponding to `ReqId` the response is returned +in `Reply`. Otherwise this function returns `no_reply` +and no cleanup is done. Thus this function must be invoked repeatedly +until a response is returned. If the specified event handler is not installed, the function returns -`{error,bad_module}`. If the callback function fails with `Reason` or returns an -unexpected value `Term`, this function returns `{error,{'EXIT',Reason}}` or -`{error,Term}`, respectively. If the event manager dies before or during the -request this function returns `{error,{Reason, EventMgrRef}}`. +`{error, bad_module}`. If the callback function fails with `Reason` +or returns an unexpected value `Term`, this function returns +`{error, {'EXIT', Reason}}` or `{error, Term}`, respectively. +If the event manager has died before this function is called, +that is; `Msg` reports the server's death, this function returns +`{error,{Reason, EventMgrRef}}` where `Reason` is the exit reason. """. -doc(#{since => <<"OTP 23.0">>}). -spec check_response(Msg, ReqId) -> Result when @@ -1169,40 +1307,49 @@ check_response(Msg, ReqId) -> end. -doc """ -Check if `Msg` is a response corresponding to a request identifier saved in -`ReqIdCollection`. All request identifiers of `ReqIdCollection` must correspond -to requests that have been made using `send_request/3` or `send_request/5`, and -all requests must have been made by the process calling this function. - -The `Label` in the response equals the `Label` associated with the request -identifier that the response corresponds to. The `Label` of a request identifier -is associated when [saving the request id](`reqids_add/3`) in a request -identifier collection, or when sending the request using `send_request/5`. - -Compared to `check_response/2`, the returned result associated with a specific -request identifier or an exception associated with a specific request identifier -will be wrapped in a 3-tuple. The first element of this tuple equals the value -that would have been produced by [`check_response/2`](`check_response/2`), the -second element equals the `Label` associated with the specific request -identifier, and the third element `NewReqIdCollection` is a possibly modified +Check if a received message is a request response in a collection. + +Check if `Msg` is a response corresponding to a request identifier +stored in `ReqIdCollection`. All request identifiers of `ReqIdCollection` +must correspond to requests that have been made using `send_request/3` +or `send_request/5`, and all requests must have been made +by the process calling this function. + +The `Label` in the response is the `Label` associated with +the request identifier that the response corresponds to. +The `Label` of a request identifier is associated +when [storing the request id](`reqids_add/3`) in a collection, +or when sending the request using `send_request/5`. + +Compared to `check_response/2`, the returned result or exception +associated with a specific request identifier will be wrapped +in a 3-tuple `{Response, Label, NewReqIdCollection}`. +`Response` is the value that would have been produced +by `check_response/2`, `Label` is the value associated with +the specific [request identifier](`t:request_id/0`) +and `NewReqIdCollection` is a possibly modified request identifier collection. -If `ReqIdCollection` is empty, the atom `no_request` will be returned. If `Msg` -does not correspond to any of the request identifiers in `ReqIdCollection`, the -atom `no_reply` is returned. - -If `Delete` equals `true`, the association with `Label` will have been deleted -from `ReqIdCollection` in the resulting `NewReqIdCollection`. If `Delete` equals -`false`, `NewReqIdCollection` will equal `ReqIdCollection`. Note that deleting -an association is not for free and that a collection containing already handled -requests can still be used by subsequent calls to -[`check_response/3`](`check_response/3`), `receive_response/3`, and -`wait_response/3`. However, without deleting handled associations, the above -calls will not be able to detect when there are no more outstanding requests to -handle, so you will have to keep track of this some other way than relying on a -`no_request` return. Note that if you pass a collection only containing -associations of already handled or abandoned requests to -[`check_response/3`](`check_response/3`), it will always return `no_reply`. +If `ReqIdCollection` is empty, `no_request` will be returned. + +If `Msg` does not correspond to any of the request identifiers +in `ReqIdCollection`, `no_reply` is returned. + +If `Delete` is `true`, the association with `Label` has been deleted +from `ReqIdCollection` in the resulting `NewReqIdCollection`. +If `Delete` is `false`, `NewReqIdCollection` will equal `ReqIdCollection`. +Note that deleting an association is not for free and that +a collection containing already handled requests +can still be used by subsequent calls to `check_response/3`), +`receive_response/3`, and `wait_response/3`. + +However, without deleting handled associations, the above calls +will not be able to detect when there are no more outstanding requests +to handle, so you will have to keep track of this some other way +than relying on a `no_request` return. Note that if you pass +a collection only containing associations of already handled +or abandoned requests to `check_response/3`, +it will always return `no_reply`. """. -doc(#{since => <<"OTP 25.0">>}). -spec check_response(Msg, ReqIdCollection, Delete) -> Result when @@ -1229,17 +1376,21 @@ check_response(Msg, ReqIdCol, Delete) -> end. -doc """ -Returns a new empty request identifier collection. A request identifier -collection can be utilized in order the handle multiple outstanding requests. +Create an empty request identifier collection. -Request identifiers of requests made by `send_request/3` can be saved in a -request identifier collection using `reqids_add/3`. Such a collection of request -identifiers can later be used in order to get one response corresponding to a -request in the collection by passing the collection as argument to +Returns a new empty request identifier collection. +A request identifier collection can be utilized to handle +multiple outstanding requests. + +Request identifiers of requests made by `send_request/3` +can be saved in a request identifier collection using `reqids_add/3`. +Such a collection of request identifiers can later be used +in order to get one response corresponding to a request +in the collection by passing the collection as argument to `receive_response/3`, `wait_response/3`, or, `check_response/3`. -`reqids_size/1` can be used to determine the amount of request identifiers in a -request identifier collection. +`reqids_size/1` can be used to determine the number of +request identifiers in a collection. """. -doc(#{since => <<"OTP 25.0">>}). -spec reqids_new() -> @@ -1248,7 +1399,7 @@ request identifier collection. reqids_new() -> gen:reqids_new(). --doc "Returns the amount of request identifiers saved in `ReqIdCollection`.". +-doc "Returns the number of request identifiers in `ReqIdCollection`.". -doc(#{since => <<"OTP 25.0">>}). -spec reqids_size(ReqIdCollection::request_id_collection()) -> non_neg_integer(). @@ -1261,9 +1412,11 @@ reqids_size(ReqIdCollection) -> end. -doc """ -Saves `ReqId` and associates a `Label` with the request identifier by adding -this information to `ReqIdCollection` and returning the resulting request -identifier collection. +Store a request identifier in a colletion. + +Stores `ReqId` and associates a `Label` with the request identifier +by adding this information to `ReqIdCollection` and returning +the resulting request identifier collection. """. -doc(#{since => <<"OTP 25.0">>}). -spec reqids_add(ReqId::request_id(), Label::term(), @@ -1278,9 +1431,11 @@ reqids_add(ReqId, Label, ReqIdCollection) -> end. -doc """ -Returns a list of `{ReqId, Label}` tuples which corresponds to all request -identifiers with their associated labels present in the `ReqIdCollection` -collection. +Convert a request identifier collection to a list. + +Returns a list of `{ReqId, Label}` tuples which corresponds to +all request identifiers with their associated labels +in [`ReqIdCollection`](`t:request_id_collection/0`). """. -doc(#{since => <<"OTP 25.0">>}). -spec reqids_to_list(ReqIdCollection::request_id_collection()) -> @@ -1294,49 +1449,56 @@ reqids_to_list(ReqIdCollection) -> end. -doc """ -Deletes an event handler from event manager `EventMgrRef`. The event manager -calls [`Module:terminate/2`](`c:terminate/2`) to terminate the event handler. +Deletes an event handler from an event manager. + +This function deletes event handler `Handler` from event manager +`EventMgrRef`. The event manager calls +[`Module:terminate/2`](`c:terminate/2`) to terminate the event handler. `Args` is any term that is passed as one of the arguments to [`Module:terminate/2`](`c:terminate/2`). -The return value is the return value of [`Module:terminate/2`](`c:terminate/2`). -If the specified event handler is not installed, the function returns -`{error,module_not_found}`. If the callback function fails with `Reason`, the -function returns `{'EXIT',Reason}`. +The return value is the return value of +[`Module:terminate/2`](`c:terminate/2`). If the specified +event handler is not installed, the function returns +`{error, module_not_found}`. If the callback function fails +with `Reason`, the function returns `{'EXIT', Reason}`. """. -spec delete_handler(EventMgrRef :: emgr_ref(), Handler :: handler(), Args :: term()) -> term(). delete_handler(M, Handler, Args) -> rpc(M, {delete_handler, Handler, Args}). -doc """ -Replaces an old event handler with a new event handler in event manager -`EventMgrRef`. +Replace an event handler. + +This function replaces an event handler in event manager `EventMgrRef`. For a description of `OldHandler` and `NewHandler`, see `add_handler/3`. -First the old event handler `OldHandler` is deleted. The event manager calls -`OldModule:terminate(Args1, ...)`, where `OldModule` is the callback module of -`OldHandler`, and collects the return value. +First the old event handler `OldHandler` is deleted. The event manager +calls `OldModule:terminate(Args1, ...)`, where `OldModule` +is the callback module of `OldHandler`, and collects the return value. -Then the new event handler `NewHandler` is added and initiated by calling -[`NewModule:init({Args2,Term})`](`c:init/1`), where `NewModule` is the callback -module of `OldHandler` and `Term` is the return value of -[`OldModule:terminate/2`](`c:terminate/2`). This makes it possible to transfer -information from `OldHandler` to `NewHandler`. +Then the new event handler `NewHandler` is added and initiated +by calling [`NewModule:init({Args2,Term})`](`c:init/1`), where `NewModule` +is the callback module of `NewHandler`, and `Term` is the return value +of [`OldModule:terminate/2`](`c:terminate/2`). This makes it possible +to transfer information from `OldHandler` to `NewHandler`. -The new handler is added even if the the specified old event handler is not -installed, in which case `Term=error`, or if -[`OldModule:terminate/2`](`c:terminate/2`) fails with `Reason`, in which case -`Term={'EXIT',Reason}`. The old handler is deleted even if -[`NewModule:init/1`](`c:init/1`) fails. +The new handler is added even if the the specified old event handler +is not installed, in which case `Term = error`, or if +[`OldModule:terminate/2`](`c:terminate/2`) fails with `Reason`, +in which case `Term = {'EXIT', Reason}`. The old handler +is deleted even if [`NewModule:init/1`](`c:init/1`) fails. -If there was a supervised connection between `OldHandler` and a process `Pid`, +If there was a supervised connection +between `OldHandler` and a process `Pid`, there is a supervised connection between `NewHandler` and `Pid` instead. -If [`NewModule:init/1`](`c:init/1`) returns a correct value, this function returns -`ok`. If [`NewModule:init/1`](`c:init/1`) fails with `Reason` or returns an -unexpected value `Term`, this function returns `{error,{'EXIT',Reason}}` or -`{error,Term}`, respectively. +If [`NewModule:init/1`](`c:init/1`) returns a correct value, +this function returns `ok`. If [`NewModule:init/1`](`c:init/1`) fails +with `Reason` or returns an unexpected value `Term`, +this function returns `{error, {'EXIT', Reason}}` or +`{error, Term}`, respectively. """. -spec swap_handler(EventMgrRef :: emgr_ref(), OldHandler :: {handler(), term()}, @@ -1345,9 +1507,12 @@ unexpected value `Term`, this function returns `{error,{'EXIT',Reason}}` or swap_handler(M, {H1, A1}, {H2, A2}) -> rpc(M, {swap_handler, H1, A1, H2, A2}). -doc """ -Replaces an event handler in event manager `EventMgrRef` in the same way as -[`swap_handler/3`](`swap_handler/3`), but also supervises the connection between -`NewHandler` and the calling process. +Replace an event handler, and supervise it. + +Replaces an event handler in event manager `EventMgrRef` +in the same way as [`swap_handler/3`](`swap_handler/3`), +but also supervises the connection between `NewHandler` +and the calling process. For a description of the arguments and return values, see `swap_handler/3`. """. @@ -1359,7 +1524,10 @@ swap_sup_handler(M, {H1, A1}, {H2, A2}) -> rpc(M, {swap_sup_handler, H1, A1, H2, A2, self()}). -doc """ -Returns a list of all event handlers installed in event manager `EventMgrRef`. +Return all event handlers in an event manager. + +This function returns a list of all event handlers +installed in event manager `EventMgrRef`. For a description of `Handler`, see `add_handler/3`. """. @@ -1372,24 +1540,28 @@ stop(M) -> gen:stop(M). -doc """ -Orders event manager `EventMgrRef` to exit with the specifies `Reason` and waits -for it to terminate. Before terminating, `gen_event` calls -[`Module:terminate(stop,...)`](`c:terminate/2`) for each installed event -handler. - -The function returns `ok` if the event manager terminates with the expected -reason. Any other reason than `normal`, `shutdown`, or `{shutdown,Term}` causes -an error report to be issued using `m:logger`. - -`Timeout` is an integer greater than zero that specifies how many milliseconds -to wait for the event manager to terminate, or the atom `infinity` to wait -indefinitely. If the event manager has not terminated -within the specified time, the call exits the calling process with reason -`timeout`. - -If the process does not exist, the call exits the calling process with reason -`noproc`, and with reason `{nodedown,Node}` if the connection fails to the -remote `Node` where the server runs. +Stop an event manager. + +Orders event manager `EventMgrRef` to exit with the specifies `Reason`, +and waits for it to terminate. Before terminating, `gen_event` calls +[`Module:terminate(stop,...)`](`c:terminate/2`) +for each installed event handler. + +The function returns `ok` if the event manager terminates +with the expected reason. Any other reason than `normal`, +`shutdown`, or `{shutdown, Term}` causes an error report +to be issued using `m:logger`. + +`Timeout` is an integer greater than zero that specifies +how many milliseconds to wait for the event manager to terminate, +or the atom `infinity` to wait indefinitely. If the event manager +has not terminated within the specified time, the call exits +the calling process with reason `timeout`. + +If the process does not exist, +the call exits the calling process with reason `noproc`, +and with reason `{nodedown, Node}` if the connection fails +to the remote `Node` where the server runs. """. -doc(#{since => <<"OTP 18.0">>}). -spec stop(EventMgrRef :: emgr_ref(), Reason :: term(), Timeout :: timeout()) -> 'ok'. diff --git a/lib/stdlib/src/gen_fsm.erl b/lib/stdlib/src/gen_fsm.erl index 7a944ba7d823..c1f53841bade 100644 --- a/lib/stdlib/src/gen_fsm.erl +++ b/lib/stdlib/src/gen_fsm.erl @@ -18,13 +18,15 @@ %% %CopyrightEnd% %% -module(gen_fsm). + -moduledoc """ -Deprecated and replaced by `m:gen_statem`. +Deprecated and replaced by `m:gen_statem` in OTP 20. -## Migration to gen_statem +Migration to gen_statem +----------------------- -Here follows a simple example of turning a gen_fsm into a `m:gen_statem`. The -example comes from the previous Users Guide for `gen_fsm` +Here follows a simple example of turning a gen_fsm into a `m:gen_statem`. +The example comes from the previous User's Guide for `gen_fsm` ```erlang -module(code_lock). @@ -41,9 +43,10 @@ example comes from the previous Users Guide for `gen_fsm` -ifdef(BEFORE_REWRITE). -export([init/1, locked/2, open/2, handle_sync_event/4, handle_event/3, - handle_info/3, terminate/3, code_change/4]). + handle_info/3, terminate/3, code_change/4]). -else. --export([init/1, callback_mode/0, locked/3, open/3, terminate/3, code_change/4]). +-export([init/1, callback_mode/0, locked/3, open/3, + terminate/3, code_change/4]). %% Add callback__mode/0 %% Change arity of the state functions %% Remove handle_info/3 @@ -93,18 +96,18 @@ callback_mode() -> -ifdef(BEFORE_REWRITE). locked({button, Digit}, Data0) -> case analyze_lock(Digit, Data0) of - {open = StateName, Data} -> - {next_state, StateName, Data, 10000}; - {StateName, Data} -> - {next_state, StateName, Data} + {open = StateName, Data} -> + {next_state, StateName, Data, 10000}; + {StateName, Data} -> + {next_state, StateName, Data} end. -else. locked(cast, {button,Digit}, Data0) -> case analyze_lock(Digit, Data0) of - {open = StateName, Data} -> - {next_state, StateName, Data, 10000}; - {StateName, Data} -> - {next_state, StateName, Data} + {open = StateName, Data} -> + {next_state, StateName, Data, 10000}; + {StateName, Data} -> + {next_state, StateName, Data} end; locked({call, From}, Msg, Data) -> handle_call(From, Msg, Data); @@ -171,8 +174,8 @@ handle_info(Info, StateName, Data) -> analyze_lock(Digit, #{code := Code, remaining := Remaining} = Data) -> case Remaining of [Digit] -> - do_unlock(), - {open, Data#{remaining := Code}}; + do_unlock(), + {open, Data#{remaining := Code}}; [Digit|Rest] -> % Incomplete {locked, Data#{remaining := Rest}}; _Wrong -> @@ -184,10 +187,94 @@ do_lock() -> do_unlock() -> io:format("Unlock~n", []). ``` + +OTP 19 Documentation +-------------------- + +### Module + +`gen_fsm` + +### Module Summary + +Generic finite state machine behavior. + +### Description + +This behavior module provides a finite state machine. +A generic finite state machine process (`gen_fsm`) 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](`e:system:design_principles`). + +A `gen_fsm` process 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: + +``` text +gen_fsm module Callback module +-------------- --------------- +gen_fsm:start +gen_fsm:start_link -----> Module:init/1 + +gen_fsm:stop -----> Module:terminate/3 + +gen_fsm:send_event -----> Module:StateName/2 + +gen_fsm:send_all_state_event -----> Module:handle_event/3 + +gen_fsm:sync_send_event -----> Module:StateName/3 + +gen_fsm:sync_send_all_state_event -----> Module:handle_sync_event/4 + +- -----> Module:handle_info/3 + +- -----> Module:terminate/3 + +- -----> Module:code_change/4 +``` + +If a callback function fails or returns a bad value, +the `gen_fsm` process terminates. + +A `gen_fsm` process handles system messages as described +in [sys(3)](`m:sys`). The sys module can be used for +debugging a `gen_fsm` process. + +Notice that a `gen_fsm` process does not trap exit signals automatically, +this must be explicitly initiated in the callback module. + +Unless otherwise stated, all functions in this module fail +if the specified `gen_fsm` process does not exist +or if bad arguments are specified. + +The gen_fsm process can go into hibernation (see `erlang:hibernate/3`) +if a callback function specifies `hibernate` instead of a time-out value. +This can be useful if the server is expected to be idle for a long time. +However, use this feature with care, as hibernation implies at least +two garbage collections (when hibernating and shortly after waking up) +and is not something you want to do between each call +to a busy state machine. + +### Callback Functions + +See the [Callback Functions](#callbacks-deprecated) section +for the functions to be exported from a `gen_fsm` callback module. + +[]() {: #state-name } +**State name** denotes a state of the state machine. + +[]() {: #state-data } +**State data** denotes the internal state of the Erlang process +that implements the state machine. """. +-moduledoc #{titles => + [{callback, ~"deprecated"}]}. %%%----------------------------------------------------------------- -%%% +%%% %%% This state machine is somewhat more pure than state_lib. It is %%% still based on State dispatching (one function per state), but %%% allows a function handle_event to take care of events in all states. @@ -297,52 +384,440 @@ do_unlock() -> -export([format_log/1, format_log/2]). -deprecated({'_','_', "use the 'gen_statem' module instead"}). +-deprecated_callback({'_','_', "use the 'gen_statem' module instead"}). %%% --------------------------------------------------- %%% Interface functions. %%% --------------------------------------------------- --callback init(Args :: term()) -> - {ok, StateName :: atom(), StateData :: term()} | - {ok, StateName :: atom(), StateData :: term(), timeout() | hibernate} | - {stop, Reason :: term()} | ignore. --callback handle_event(Event :: term(), StateName :: atom(), - StateData :: term()) -> - {next_state, NextStateName :: atom(), NewStateData :: term()} | - {next_state, NextStateName :: atom(), NewStateData :: term(), - timeout() | hibernate} | - {stop, Reason :: term(), NewStateData :: term()}. --callback handle_sync_event(Event :: term(), From :: {pid(), Tag :: term()}, - StateName :: atom(), StateData :: term()) -> - {reply, Reply :: term(), NextStateName :: atom(), NewStateData :: term()} | - {reply, Reply :: term(), NextStateName :: atom(), NewStateData :: term(), - timeout() | hibernate} | - {next_state, NextStateName :: atom(), NewStateData :: term()} | - {next_state, NextStateName :: atom(), NewStateData :: term(), - timeout() | hibernate} | - {stop, Reason :: term(), Reply :: term(), NewStateData :: term()} | - {stop, Reason :: term(), NewStateData :: term()}. --callback handle_info(Info :: term(), StateName :: atom(), - StateData :: term()) -> - {next_state, NextStateName :: atom(), NewStateData :: term()} | - {next_state, NextStateName :: atom(), NewStateData :: term(), - timeout() | hibernate} | - {stop, Reason :: normal | term(), NewStateData :: term()}. --callback terminate(Reason :: normal | shutdown | {shutdown, term()} - | term(), StateName :: atom(), StateData :: term()) -> - term(). --callback code_change(OldVsn :: term() | {down, term()}, StateName :: atom(), - StateData :: term(), Extra :: term()) -> - {ok, NextStateName :: atom(), NewStateData :: term()}. --callback format_status(Opt, StatusData) -> Status when +-doc "Reply destination. See `reply/2`". +-type from() :: {To :: pid(), Tag :: term()}. + +-doc #{ title => ~"deprecated" }. +-doc """ +Initialize process and internal [*state name*](#state-name) +and [*state data*](#state-data). + +Whenever a `gen_fsm` process is started using +[`start/3,4`](`start/4`) or [`start_link/3,4`](`start_link/4`), +this function is called by the new process to initialize. + +`Args` is the `Args` argument provided to the start function. + +If initialization is successful, the function is to return +{ok, StateName, StateData}, {ok, StateName, StateData, Timeout}, +or {ok, StateName, StateData, hibernate}, where `StateName` +is the initial [*state name*](#state-name) and `StateData` +the initial [*state data*](#state-data) of the `gen_fsm` process. + +If an `t:integer/0` time-out value is provided, a time-out occurs +unless an event or a message is received within `Timeout` milliseconds. +A time-out is represented by the atom `timeout` and is to be handled +by the [`Module:StateName/2`](`c:'StateName'/2`) callback functions. +The atom `infinity` can be used to wait indefinitely, this is +the default value. + +If `hibernate` is specified instead of a time-out value, +the process goes into hibernation when waiting for the next message +to arrive (by calling `proc_lib:hibernate/3`). + +If the initialization fails, the function returns `{stop, Reason}`, +where `Reason` is any term, or `ignore`. +""". +-callback init(Args) -> Result when + Args :: term(), + Result :: {ok, StateName, StateData} + | {ok, StateName, StateData, Timeout} + | {ok, StateName, StateData, hibernate} + | {stop, Reason} + | ignore, + StateName :: atom(), + StateData :: term(), + Timeout :: timeout(), + Reason :: term(). + +-doc #{ title => ~"deprecated" }. +-doc """ +Handle an asynchronous event. + +There is to be one instance of this function +for each possible [*state name*](#state-name). +Whenever a `gen_fsm` process receives an event sent using `send_event/2`, +the instance of this function with the same name as the current +[*state name*](#state-name) `StateName` is called to handle the event. +It is also called if a time-out occurs. + +`Event` is either the atom `timeout`, if a time-out has occurred, +or the `Event` argument provided to `send_event/2`. + +`StateData` is the [*state data*](#state-data) of the `gen_fsm` process. + +If the function returns `{next_state, NextStateName, NewStateData}, +{next_state, NextStateName, NewStateData, Timeout}, +or {next_state, NextStateName, NewStateData, hibernate}, +the `gen_fsm` process continues executing with +the current [*state name*](#state-name) set to `NextStateName` +and with the possibly updated [*state data*](#state-data) +`NewStateData`. For a description of `Timeout` and `hibernate`, +see [`Module:init/1`](`c:init/1`). + +If the function returns `{stop ,Reason, NewStateData}, +the `gen_fsm` process calls +[`Module:terminate(Reason, StateName, NewStateData)`](`c:terminate/3`) +and terminates. +""". +-callback 'StateName'(Event, StateData) -> Result when + Event :: 'timeout' | term(), + StateData :: term(), + Result :: {next_state, NextStateName, NewStateData} + | {next_state, NextStateName, NewStateData, Timeout} + | {next_state, NextStateName, NewStateData, 'hibernate'} + | {stop, Reason, NewStateData}, + NextStateName :: atom(), + NewStateData :: term(), + Timeout :: timeout(), + Reason :: term(). + +-doc #{ title => ~"deprecated" }. +-doc """ +Handle a synchronous event. + +There is to be one instance of this function +for each possible [*state name*](#state-name). +Whenever a `gen_fsm` process receives an event sent using +[`sync_send_event/2,3`](`sync_send_event/3`), +the instance of this function with the same name +as the current [*state name*](#state-name) `StateName` is called +to handle the event. + +`Event` is the `Event` argument provided to +[`sync_send_event/2,3`](`sync_send_event/3`). + +`From` is a tuple `{Pid, Tag}` where `Pid` is the `t:pid/0` +of the process that called [`sync_send_event/2,3`](`sync_send_event/3`), +`Tag` is a unique tag. + +`StateData` is the [*state data*](#state-data) of the `gen_fsm` process. + +- If `{reply, Reply, NextStateName, NewStateData}`, + `{reply, Reply, NextStateName, NewStateData, Timeout}`, + or `{reply, Reply, NextStateName, NewStateData, hibernate}` is returned, + `Reply` is given back to `From` as the return value of + [`sync_send_event/2,3`](`sync_send_event/3`). + The `gen_fsm` process then continues executing + with the current [*state name*](#state-name) set to `NextStateName` + and with the possibly updated [*state data*](#state-data) `NewStateData`. + For a description of `Timeout` and `hibernate`, + see [`Module:init/1`](`c:init/1`). + +- If `{next_state, NextStateName, NewStateData}`, + `{next_state, NextStateName, NewStateData, Timeout}`, + or `{next_state, NextStateName, NewStateData, hibernate}` is returned, + the `gen_fsm` process continues executing in `NextStateName` + with `NewStateData`. Any reply to `From` + must be specified explicitly using `reply/2`. + +- If the function returns `{stop, Reason, Reply, NewStateData}`, + `Reply` is given back to `From`. If the function returns + {stop, Reason, NewStateData}, any reply to `From` must be specified + explicitly using `reply/2`. The `gen_fsm` process then calls + [`Module:terminate(Reason, StateName, NewStateData)`](`c:terminate/3`) + and terminates. +""". +-callback 'StateName'(Event, From, StateData) -> Result when + Event :: term(), + From :: from(), + StateData :: term(), + Result :: {reply, Reply, NextStateName, NewStateData} + | {reply, Reply, NextStateName, NewStateData, Timeout} + | {reply, Reply, NextStateName, NewStateData, 'hibernate'} + | {next_state, NextStateName, NewStateData} + | {next_state, NextStateName, NewStateData, Timeout} + | {next_state, NextStateName, NewStateData, 'hibernate'} + | {stop, Reason, Reply, NewStateData} + | {stop, Reason, NewStateData}, + Reply :: term(), + NextStateName :: atom(), + NewStateData :: term(), + Timeout :: timeout(), + Reason :: 'normal' | term(). + +-doc #{ title => ~"deprecated" }. +-doc """ +Handle an asynchronous event. + +Whenever a `gen_fsm` process receives an event sent using +`send_all_state_event/2`, this function is called to handle the event. + +`StateName` is the current [*state name*](#state-name) +of the `gen_fsm` process. + +For a description of the other arguments and possible return values, +see [`Module:StateName/2`](`c:'StateName'/2`). +""". +-callback handle_event(Event, StateName, StateData) -> Result when + Event :: term(), + StateName :: atom(), + StateData :: term(), + Result :: {next_state, NextStateName, NewStateData} + | {next_state, NextStateName, NewStateData, Timeout} + | {next_state, NextStateName, NewStateData, 'hibernate'} + | {stop, Reason, NewStateData}, + NextStateName :: atom(), + NewStateData :: term(), + Timeout :: timeout(), + Reason :: term(). + +-doc #{ title => ~"deprecated" }. +-doc """ +Handle a synchronous event. + +Whenever a `gen_fsm` process receives an event sent using +[`sync_send_all_state_event/2,3`](`sync_send_all_state_event/3`), +this function is called to handle the event. + +`StateName` is the current [*state name*](#state-name) +of the `gen_fsm` process. + +For a description of the other arguments and possible return values, +see [`Module:StateName/3`](`c:'StateName'/3`). +""". +-callback handle_sync_event(Event, From, StateName, StateData) -> Result when + Event :: term(), + From :: from(), + StateName :: atom(), + StateData :: term(), + Result :: {reply, Reply, NextStateName, NewStateData} + | {reply, Reply, NextStateName, NewStateData, Timeout} + | {reply, Reply, NextStateName, NewStateData, 'hibernate'} + | {next_state, NextStateName, NewStateData} + | {next_state, NextStateName, NewStateData, Timeout} + | {next_state, NextStateName, NewStateData, 'hibernate'} + | {stop, Reason, Reply, NewStateData} + | {stop, Reason, NewStateData}, + Reply :: term(), + NextStateName :: atom(), + NewStateData :: term(), + Timeout :: timeout(), + Reason :: term(). +-doc #{ title => ~"deprecated" }. +-doc """ +Handle an incoming message + +This function is called by a `gen_fsm` process when it receives +any other message than a synchronous or asynchronous event +(or a system message). + +`Info` is the received message. + +For a description of the other arguments and possible return values, +see [`Module:StateName/2`](`c:'StateName'/2`). +""". +-callback handle_info(Info, StateName, StateData) -> Result when + Info :: term(), + StateName :: atom(), + StateData :: term(), + Result :: {next_state, NextStateName, NewStateData} + | {next_state, NextStateName, NewStateData, Timeout} + | {next_state, NextStateName, NewStateData, 'hibernate'} + | {stop, Reason, NewStateData}, + NextStateName :: atom(), + NewStateData :: term(), + Timeout :: timeout(), + Reason :: normal | term(). +-doc #{ title => ~"deprecated" }. +-doc """ +Clean up before termination. + +This function is called by a `gen_fsm` process +when it is about to terminate. It is to be the opposite of +[`Module:init/1`](`c:init/1`) and do any necessary cleaning up. +When it returns, the `gen_fsm` process terminates with `Reason`. +The return value is ignored. + +`Reason` is a term denoting the stop reason, `StateName` is +the current [*state name*](#state-name), +and `StateData` is the [*state data*](#state-data) +of the `gen_fsm` process. + +`Reason` depends on why the `gen_fsm` process is terminating. +If it is because another callback function has returned a stop tuple +`{stop, ...}`, `Reason` has the value specified in that tuple. +If it is because of a failure, `Reason` is the error reason. + +If the `gen_fsm` process is part of a supervision tree +and is ordered by its supervisor to terminate, this function +is called with `Reason = shutdown` if the following conditions apply: + +- The gen_fsm process has been set to trap exit signals. + +- The shutdown strategy as defined in the child specification + of the supervisor is an integer time-out value, not brutal_kill. + +Even if the gen_fsm process 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_fsm process terminates immediately. + +Notice that for any other reason than `normal`, `shutdown`, +or `{shutdown, Term}` the `gen_fsm` process is assumed to terminate +because of an error and an error report is issued +using `error_logger:format/2`. +""". +-callback terminate(Reason, StateName, StateData) -> _ when + Reason :: normal | shutdown | {shutdown, term()} | term(), + StateName :: atom(), + StateData :: term(). + +-doc #{ title => ~"deprecated" }. +-doc """ +Update the internal [*state data*](#state-data) during upgrade/downgrade. + +This function is called by a `gen_fsm` process when it is to update +its internal [*state data*](#state-data) +during a release upgrade/downgrade, that is, +when instruction `{update, Module, Change, ...}`, +where `Change = {advanced, Extra}`, is given in the appup file; +see section Release Handling Instructions in OTP Design Principles. +[OTP Design Principles](`e:system:release_handling.md#instr`). + +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. + +`StateName` is the current [*state name*](#state-name) + and `StateData` the internal [*state data*](#state-data) + of the `gen_fsm` process. + +`Extra` is passed "as is" from the `{advanced, Extra}` part + of the update instruction. + +The function is to return the new current [*state name*](#state-name) +and updated internal data. +""". +-callback code_change(OldVsn, StateName, StateData, Extra) -> + {ok, NextStateName, NewStateData} when + OldVsn :: Vsn | {'down', Vsn}, + Vsn :: term(), + StateName :: atom(), + NextStateName :: atom(), + StateData :: term(), + NewStateData :: term(), + Extra :: term(). + +-doc #{ title => ~"deprecated" }. +-doc """ +Optional function for providing a term describing +the current `gen_fsm` process status. + +The second argument is `[PDict, StateData]`, that is, a list +with the 2 elements, in that order. + +> #### Note {: .info } +> +> This callback is optional, so callback modules need not export it. +> The `gen_fsm` module provides a default implementation +> of this function that returns the callback module +> [*state data*](#state-data). + +This function is called by a `gen_fsm` process +in the following situations: + +- One of [`sys:get_status/1,2`](`sys:get_status/1`) is invoked to get + the `gen_fsm` status. `Opt` is set to the atom `normal` for this case. +- The `gen_fsm` process 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_fsm` status for these cases. A callback module +wishing to change the [`sys:get_status/1,2`](`sys:get_status/1`) +return value as well as how its status appears in termination error logs, +exports an instance of `c:format_status/2` that returns a term +describing the current status of the `gen_fsm` process. + +`PDict` is the current value of the process dictionary +of the `gen_fsm` process. + +`StateData` is the internal [*state data*](#state-data) +of the `gen_fsm` process. + +The function is to return `Status`, a term that change the details +of the current state and status of the `gen_fsm` process. +There are no restrictions on the form `Status` can take, +but for the [`sys:get_status/1,2`](`sys:get_status/1`) case +(when `Opt` is `normal`), the recommended form for the `Status` value +is `[{data, [{"StateData", Term}]}]`, where `Term` provides +relevant details of the `gen_fsm` [*state data*](#state-data). +Following this recommendation is not required, but it makes +the callback module status consistent with the rest of +the [`sys:get_status/1,2`](`sys:get_status/1`) return value. + +One use for this function is to return compact alternative +[*state data*](#state-data) representations to avoid +that large state terms are printed in log files. +""". +-callback format_status(Opt, nonempty_improper_list(PDict, [StateData])) -> + Status when Opt :: 'normal' | 'terminate', - StatusData :: [PDict | State], PDict :: [{Key :: term(), Value :: term()}], - State :: term(), + StateData :: term(), Status :: term(). -optional_callbacks( - [handle_info/3, terminate/3, code_change/4, format_status/2]). + ['StateName'/2, 'StateName'/3, + handle_info/3, terminate/3, code_change/4, format_status/2]). + + + +-doc """ +[FSM name](#fsm-name) specification: +`local`, `global`, or `via` registered. + +To be used when starting a `gen_fsm`. See `start_link/4`. +""". +-type fsm_name() :: % Duplicate of gen:emgr_name() + {'local', LocalName :: atom()} + | {'global', GlobalName :: term()} + | {'via', RegMod :: module(), ViaName :: term()}. + +-doc """ +[FSM reference](#fsm-ref) `t:pid/0` or registered `t:fsm_name/0`. + +To be used in for example `send_event/2` to specify the server. +""". +-type fsm_ref() :: % What gen:call/3,4 and gen:stop/1,3 accepts + pid() + | (LocalName :: atom()) + | {Name :: atom(), Node :: atom()} + | {'global', GlobalName :: term()} + | {'via', RegMod :: module(), ViaName :: term()}. + + +-doc """ +[Start options](#start-options) for the [`start/3,4`](`start/3`), +and [`start_link/3,4`](`start_link/3`) functions. + +See `start_link/4`. +""". +-type start_opt() :: % Duplicate of gen:option() + {'timeout', Time :: timeout()} + | {'spawn_opt', [proc_lib:start_spawn_option()]} + | enter_loop_opt(). + +%%---------------------- +-doc """ +[Start options](#start-options) for the +[`enter_loop/4,5,6`](`enter_loop/6`), [`start/3,4`](`start/3`), +and [`start_link/3,4`](`start_link/3`) functions. + +See `start_link/4`. +""". +-type enter_loop_opt() :: % Some gen:option()s works for enter_loop/* + {'debug', Dbgs :: [sys:debug_option()]}. + + %%% --------------------------------------------------- %%% Starts a generic state machine. @@ -360,31 +835,192 @@ do_unlock() -> %%% {error, {already_started, Pid}} | %%% {error, Reason} %%% --------------------------------------------------- --doc false. +-doc """ +Create a standalone `gen_fsm` process, not registered. + +Equivalent to [`start(Name, Mod, Args, Options)`](`start/4`) +without registering a `Name`. + +For a description of arguments and return values, +see [`start_link/3,4`](`start_link/3`). +""". +-spec start(Module, Args, Options) -> Result when + Module :: module(), % + Args :: term(), + Options :: [start_opt()], + Result :: {ok, Pid} | ignore | {error, Reason}, + Pid :: pid(), + Reason :: term(). start(Mod, Args, Options) -> gen:start(?MODULE, nolink, Mod, Args, Options). --doc false. +-doc """ +Create a standalone `gen_fsm` process. + +The created process is not part of a supervision tree +and thus has no supervisor. + +For a description of arguments and return values, +see [`start_link/3,4`](`start_link/4`). +""". +-spec start(FsmName, Module, Args, Options) -> Result when + FsmName :: fsm_name(), + Module :: module(), + Args :: term(), + Options :: [start_opt()], + Result :: {ok, Pid} | ignore | {error, Reason}, + Pid :: pid(), + Reason :: {'already_started', Pid} | term(). start(Name, Mod, Args, Options) -> gen:start(?MODULE, nolink, Name, Mod, Args, Options). --doc false. +-doc """ +Create a `gen_fsm` process in a supervision tree, not registered. + +Equivalent to [`start_link(Name, Mod, Args, Options)`](`start_link/4`) +without registering a `Name`. +""". +-spec start_link(Module, Args, Options) -> Result when + Module :: module(), + Args :: term(), + Options :: [start_opt()], + Result :: {ok, Pid} | ignore | {error, Reason}, + Pid :: pid(), + Reason :: term(). start_link(Mod, Args, Options) -> gen:start(?MODULE, link, Mod, Args, Options). --doc false. +-doc """ +Create a `gen_fsm` process in a supervision tree. + +The process is created as part of a supervision tree. The function +is to be called, directly or indirectly, by the supervisor. +For example, it ensures that the `gen_fsm` process +is linked to the supervisor. + +The `gen_fsm` process calls [`Module:init/1`](`c:init/1`) to initialize. +To ensure a synchronized startup procedure, +[`start_link/3,4`](`start_link/4`) does not return +until `Module:init/1` has returned. + +[]() {: #fsm-name } + +- If **`FsmName = {local, Name}`**, the `gen_fsm` process + is registered locally as `Name` using `register/2`. + +- If **`FsmName = {global, GlobalName}`**, the `gen_fsm` process + is registered globally as `GlobalName` using `global:register_name/2`. + +- If **`FsmName = {via, Module, ViaName}`**, + the `gen_fsm` process registers with the registry + represented by `Module`. The `Module` callback is to export + the functions `register_name/2`, `unregister_name/1`, + `whereis_name/1`, and `send/2`, which are to behave like + the corresponding functions in `m:global`. + Thus, `{via, global, GlobalName}` is a valid reference. + +`Module` is the name of the callback module. + +`Args` is any term that is passed as the argument to `Module:init/1`. + +[]() {: #start-options } + +If option **`{timeout, Time}`** is present, the `gen_fsm` process +is allowed to spend `Time` milliseconds initializing or it terminates +and the start function returns `{error, timeout}`. + +If option **`{debug, Dbgs}`** is present, the corresponding `sys` function +is called for each item in `Dbgs`; see [`sys(3)`](`m:sys`). + +If option **`{spawn_opt, SOpts}`** is present, `SOpts` is passed +as option list to the `spawn_opt` BIF that is used +to spawn the `gen_fsm` process; see `spawn_opt/2`. + +> #### Note {: .info } +> Using spawn option `monitor` is not allowed, it causes +> the function to fail with reason `badarg`. + +If the `gen_fsm` process is successfully created and initialized, +the function returns `{ok, Pid}`, where `Pid` is the pid +of the `gen_fsm` process. If a process with the specified `FsmName` +exists already, the function returns `{error, {already_started, Pid}}`, +where `Pid` is the pid of that process. + +If `Module:init/1` fails with `Reason`, the function returns +`{error, Reason}`. If `Module:init/1` returns `{stop, Reason}` +or `ignore`, the process is terminated and the function returns +`{error, Reason}` or `ignore`, respectively. +""". +-spec start_link(FsmName, Module, Args, Options) -> Result when + FsmName :: fsm_name(), + Module :: module(), + Args :: term(), + Options :: [start_opt()], + Result :: {ok, Pid} | ignore | {error, Reason}, + Pid :: pid(), + Reason :: {'already_started', Pid} | term(). start_link(Name, Mod, Args, Options) -> gen:start(?MODULE, link, Name, Mod, Args, Options). --doc false. +-doc #{ equiv => stop(FsmRef, normal, infinity) }. +-spec stop(FsmRef) -> ok when + FsmRef :: fsm_ref(). stop(Name) -> gen:stop(Name). --doc false. +-doc """ +Synchronously stop a generic FSM. + +Orders a generic finite state machine to exit with the specified `Reason` +and waits for it to terminate. The `gen_fsm` process calls +[`Module:terminate/3`](`c:terminate/3`) before exiting. + +The function returns `ok` if the generic finite state machine terminates +with the expected reason. Any other reason than `normal`, `shutdown`, +or `{shutdown, Term}` causes an error report to be issued using +`error_logger:format/2`. + +`Timeout` is an integer greater than zero that specifies +how many milliseconds to wait for the generic FSM to terminate, +or the atom `infinity` to wait indefinitely. +If the generic finite state machine has not terminated +within the specified time, a `timeout` exception is raised. + +If the process does not exist, a `noproc` exception is raised. +""". +-spec stop(FsmRef, Reason, Timeout) -> ok when + FsmRef :: fsm_ref(), + Reason :: term(), + Timeout :: timeout(). stop(Name, Reason, Timeout) -> gen:stop(Name, Reason, Timeout). --doc false. +-doc """ +Send an event asynchronously to a generic FSM. + +Sends `Event` to the `FsmRef` of the `gen_fsm` process +and returns `ok` immediately. The `gen_fsm` process calls +[`Module:StateName/2`](`c:'StateName'/2`) to handle the event, +where `StateName` is the name of the current state +of the `gen_fsm` process. + +[](){: #fsm-ref } +`FsmRef` can be any of the following: + +- The `t:pid/0` +- `Name`, if the `gen_fsm` process is locally registered +- `{Name, Node}`, if the `gen_fsm` process is locally registered + at another node +- `{global, GlobalName}`, if the `gen_fsm` process is globally registered +- `{via, Module, ViaName}`, if the `gen_fsm` process is registered + through an alternative process registry + +`Event` is any term that is passed as one of the arguments +to `Module:StateName/2`. +""". +-spec send_event(FsmRef, Event) -> ok when + FsmRef :: fsm_ref(), + Event :: term(). send_event({global, Name}, Event) -> catch global:send(Name, {'$gen_event', Event}), ok; @@ -395,7 +1031,11 @@ send_event(Name, Event) -> Name ! {'$gen_event', Event}, ok. --doc false. +-doc #{ equiv => sync_send_event(FsmRef, Event, 5000) }. +-spec sync_send_event(FsmRef, Event) -> Reply when + FsmRef :: fsm_ref(), + Event :: term(), + Reply :: term(). sync_send_event(Name, Event) -> case catch gen:call(Name, '$gen_sync_event', Event) of {ok,Res} -> @@ -404,7 +1044,35 @@ sync_send_event(Name, Event) -> exit({Reason, {?MODULE, sync_send_event, [Name, Event]}}) end. --doc false. +-doc """ +Send an event synchronously to a generic FSM. + +Sends an event to the `FsmRef` of the `gen_fsm` process +and waits until a reply arrives or a time-out occurs. +The `gen_fsm` process calls [`Module:StateName/3`](`c:'StateName'/3`) +to handle the event, where `'StateName'` is the name +of the current state of the `gen_fsm` process. + +For a description of `FsmRef` and `Event`, see `send_event/2`. + +`Timeout` is an integer greater than zero that specifies +how many milliseconds to wait for a reply, or the atom `infinity` +to wait indefinitely. If no reply is received within the specified time, +the function call fails. + +Return value `Reply` is defined in the return value of +[`Module:StateName/3`](`c:'StateName'/3`) + +> #### Note {: .info } +> The ancient behavior of sometimes consuming the server exit message +> if the server died during the call while linked to the client +> was removed in Erlang 5.6/OTP R12B. +""". +-spec sync_send_event(FsmRef, Event, Timeout) -> Reply when + FsmRef :: fsm_ref(), + Event :: term(), + Timeout :: timeout(), + Reply :: term(). sync_send_event(Name, Event, Timeout) -> case catch gen:call(Name, '$gen_sync_event', Event, Timeout) of {ok,Res} -> @@ -413,7 +1081,25 @@ sync_send_event(Name, Event, Timeout) -> exit({Reason, {?MODULE, sync_send_event, [Name, Event, Timeout]}}) end. --doc false. +-doc """ +Send an event asynchronously to a generic FSM. + +Sends an event asynchronously to the `FsmRef` of the `gen_fsm` process +and returns `ok` immediately. The `gen_fsm` process calls +[`Module:handle_event/3`](`c:handle_event/3`) to handle the event. + +For a description of the arguments, see `send_event/2`. + +The difference between `send_event/2` and `send_all_state_event/2` +is which callback function is used to handle the event. +This function is useful when sending events that are handled +the same way in every state, as only one `handle_event` clause +is needed to handle the event instead of one clause +in each state name function. +""". +-spec send_all_state_event(FsmRef, Event) -> ok when + FsmRef :: fsm_ref(), + Event :: term(). send_all_state_event({global, Name}, Event) -> catch global:send(Name, {'$gen_all_state_event', Event}), ok; @@ -424,7 +1110,11 @@ send_all_state_event(Name, Event) -> Name ! {'$gen_all_state_event', Event}, ok. --doc false. +-doc #{ equiv => sync_send_all_state_event(FsmRef, Event, 5000) }. +-spec sync_send_all_state_event(FsmRef, Event) -> Reply when + FsmRef :: fsm_ref(), + Event :: term, + Reply :: term(). sync_send_all_state_event(Name, Event) -> case catch gen:call(Name, '$gen_sync_all_state_event', Event) of {ok,Res} -> @@ -433,7 +1123,25 @@ sync_send_all_state_event(Name, Event) -> exit({Reason, {?MODULE, sync_send_all_state_event, [Name, Event]}}) end. --doc false. +-doc """ +Send an event synchronously to a generic FSM. + +Sends an event to the `FsmRef` of the `gen_fsm` process and waits +until a reply arrives or a time-out occurs. The `gen_fsm` process calls +[`Module:handle_sync_event/4`](`c:handle_sync_event/4`) +to handle the event. + +For a description of `FsmRef` and `Event`, see `send_event/2`. +For a description of `Timeout` and `Reply`, see `sync_send_event/3`. + +For a discussion about the difference between `sync_send_event` +and `sync_send_all_state_event`, see `send_all_state_event/2`. +""". +-spec sync_send_all_state_event(FsmRef, Event, Timeout) -> Reply when + FsmRef :: fsm_ref(), + Event :: term(), + Timeout :: timeout(), + Reply :: term(). sync_send_all_state_event(Name, Event, Timeout) -> case catch gen:call(Name, '$gen_sync_all_state_event', Event, Timeout) of {ok,Res} -> @@ -449,25 +1157,83 @@ sync_send_all_state_event(Name, Event, Timeout) -> %% e.g. when straddling a failover, or turn up in a restarted %% instance of the process. -%% Returns Ref, sends event {timeout,Ref,Msg} after Time +%% Returns Ref, sends event {timeout,Ref,Msg} after Time %% to the (then) current state. --doc false. +-doc """ +Send a time-out event internally in a generic FSM. + +Sends a time-out event internally in the `gen_fsm process` +that calls this function after `Time` milliseconds. +Returns immediately a reference that can be used to cancel the timer +using `cancel_timer/1`. + +The `gen_fsm` process calls [`Module:StateName/2`](`c:'StateName'/2`) +to handle the event, where `'StateName'` is the name +of the current state of the `gen_fsm` process at the time +the time-out message is delivered. + +`Msg` is any term that is passed in the time-out message, +`{timeout, Ref, Msg}`, as one of the arguments +to [`Module:StateName/2`](`c:'StateName'/2`). +""". +-spec start_timer(Time, Msg) -> Ref when + Time :: non_neg_integer(), + Msg :: term(), + Ref :: reference(). start_timer(Time, Msg) -> erlang:start_timer(Time, self(), {'$gen_timer', Msg}). %% Returns Ref, sends Event after Time to the (then) current state. --doc false. +-doc """ +Send a delayed event internally in a generic FSM. + +Sends a delayed event internally in the `gen_fsm` process +that calls this function after `Time` milliseconds. +Returns immediately a reference that can be used to cancel +the delayed send using `cancel_timer/1`. + +The `gen_fsm` process calls [`Module:StateName/2`](`c:'StateName'/2`) +to handle the event, where `'StateName'` is the name of +the current state of the `gen_fsm` process at the time +the delayed event is delivered. + +`Event` is any term that is passed as one of the arguments +to [`Module:StateName/2`](`c:'StateName'/2`). +""". +-spec send_event_after(Time, Event) -> Ref when + Time :: non_neg_integer(), + Event :: term(), + Ref :: reference(). send_event_after(Time, Event) -> erlang:start_timer(Time, self(), {'$gen_event', Event}). %% Returns the remaining time for the timer if Ref referred to %% an active timer/send_event_after, false otherwise. --doc false. +-doc """ +Cancel an internal timer in a generic FSM. + +Cancels an internal timer referred by `Ref` in the `gen_fsm` process +that calls this function. + +`Ref` is a reference returned from `send_event_after/2` +or `start_timer/2`. + +If the timer has already timed out, but the event not yet been delivered, +it is cancelled as if it had not timed out, so there is no false +timer event after returning from this function. + +Returns the remaining time in milliseconds until the timer +would have expired if `Ref` referred to an active timer, +otherwise `false`. +""". +-spec cancel_timer(Ref) -> RemainingTime | 'false' when + Ref :: reference(), + RemainingTime :: non_neg_integer(). cancel_timer(Ref) -> case erlang:cancel_timer(Ref) of false -> receive {timeout, Ref, _} -> 0 - after 0 -> false + after 0 -> false end; RemainingTime -> RemainingTime @@ -481,20 +1247,86 @@ cancel_timer(Ref) -> %% in proc_lib, see proc_lib(3). %% The user is responsible for any initialization of the process, %% including registering a name for it. --doc false. +-doc """ +Enter the `gen_fsm` receive loop. + +Equivalent to `enter_loop/6` with `Timeout = infinity` +but the started server is not registered as for `start_link/3`. +""". +-spec enter_loop(Module, Options, StateName, StateData) -> + no_return() when + Module :: module(), + Options :: [enter_loop_opt()], + StateName :: atom(), + StateData :: term(). enter_loop(Mod, Options, StateName, StateData) -> enter_loop(Mod, Options, StateName, StateData, self(), infinity). --doc false. +-doc """ +Enter the `gen_fsm` receive loop. + +With argument `FsmName` equivalent to `enter_loop/6` +with `Timeout = infinity`. + +With argument `Timeout` equivalent to `enter_loop/6` +but the started server is not registered as for `start_link/3`. +""". +-spec enter_loop(Module, Options, StateName, StateData, FsmName) -> + no_return() when + Module :: module(), + Options :: [enter_loop_opt()], + StateName :: atom(), + StateData :: term(), + FsmName :: fsm_name(); + (Module, Options, StateName, StateData, Timeout) -> + no_return() when + Module :: module(), + Options :: enter_loop_opt(), + StateName :: atom(), + StateData :: term(), + Timeout :: timeout(). enter_loop(Mod, Options, StateName, StateData, {Scope,_} = ServerName) when Scope == local; Scope == global -> - enter_loop(Mod, Options, StateName, StateData, ServerName,infinity); + enter_loop(Mod, Options, StateName, StateData, ServerName, infinity); enter_loop(Mod, Options, StateName, StateData, {via,_,_} = ServerName) -> - enter_loop(Mod, Options, StateName, StateData, ServerName,infinity); + enter_loop(Mod, Options, StateName, StateData, ServerName, infinity); enter_loop(Mod, Options, StateName, StateData, Timeout) -> enter_loop(Mod, Options, StateName, StateData, self(), Timeout). --doc false. +-doc """ +Enter the `gen_fsm` receive loop. + +Makes an existing process into a `gen_fsm` process. Does not return, +instead the calling process enters the `gen_fsm` receive loop +and becomes a `gen_fsm` process. The process must have been started +using one of the start functions in `m: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_fsm` behavior provides. + +`Module`, `Options`, and `FsmName` have the same meanings +as when calling [`start[_link]/3,4`](`start_link/4`). +However, the process must have been registered according to +`FsmName` before this function is called. + +`StateName`, `StateData`, and `Timeout` have the same meanings +as in the return value of [`Module:init/1`](`c:init/1`). +The callback module `Module` does not need to export +an `c:init/1` function. + +The function fails if the calling process was not started +by a `m:proc_lib` start function, or if it is not registered +according to `FsmName`. +""". +-spec enter_loop(Module, Options, StateName, StateData, FsmName, Timeout) -> + no_return() when + Module :: module(), + Options :: [enter_loop_opt()], + StateName :: atom(), + StateData :: term(), + FsmName :: fsm_name() | pid(), + Timeout :: timeout(). enter_loop(Mod, Options, StateName, StateData, ServerName, Timeout) -> Name = gen:get_proc_name(ServerName), Parent = gen:get_parent(), @@ -665,7 +1497,7 @@ print_event(Dev, {noreply, StateName}, Name) -> handle_msg(Msg, Parent, Name, StateName, StateData, Mod, _Time, HibernateAfterTimeout) -> %No debug here From = from(Msg), case catch dispatch(Msg, Mod, StateName, StateData) of - {next_state, NStateName, NStateData} -> + {next_state, NStateName, NStateData} -> loop(Parent, Name, NStateName, NStateData, Mod, infinity, HibernateAfterTimeout, []); {next_state, NStateName, NStateData, Time1} -> loop(Parent, Name, NStateName, NStateData, Mod, Time1, HibernateAfterTimeout, []); @@ -752,7 +1584,28 @@ from({'$gen_sync_all_state_event', From, _Event}) -> From; from(_) -> undefined. %% Send a reply to the client. --doc false. +-doc """ +Send a reply to a caller. + +This function can be used by a `gen_fsm` process to explicitly send +a reply to a client process that called +[`sync_send_event/2,3`](`sync_send_event/3`) or +[`sync_send_all_state_event/2,3`](`sync_send_all_state_event/3`) +when the reply cannot be defined in the return value of +[`Module:StateName/3`](`c:'StateName'/3`) or +[`Module:handle_sync_event/4`](`c:handle_sync_event/4`). + +`Caller` must be the `From` argument provided to the callback function. +`Reply` is any term given back to the client as the return value of +[`sync_send_event/2,3`](`sync_send_event/3`) or +[`sync_send_all_state_event/2,3`](`sync_send_all_state_event/3`). + +Return value `Result` is not further defined, and is always to be ignored. +""". +-spec reply(Caller, Reply) -> Result when + Caller :: from(), + Reply :: term(), + Result :: term(). reply(From, Reply) -> gen:reply(From, Reply). diff --git a/lib/stdlib/src/gen_server.erl b/lib/stdlib/src/gen_server.erl index 08a349296e32..b01df7555f9d 100644 --- a/lib/stdlib/src/gen_server.erl +++ b/lib/stdlib/src/gen_server.erl @@ -21,16 +21,18 @@ -moduledoc """ Generic server behavior. -This behavior module provides the server of a client-server relation. A generic -server process (`gen_server`) 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 -section [gen_server Behaviour](`e:system:gen_server_concepts.md`) in OTP Design -Principles. - -A `gen_server` process 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: +This behavior module provides the server in a client-server relation. +A generic server process (`gen_server`) 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 section +[gen_server Behaviour](`e:system:gen_server_concepts.md`) +in OTP Design Principles. + +A `gen_server` process 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: ```text gen_server module Callback module @@ -57,44 +59,51 @@ gen_server:abcast -----> Module:handle_cast/2 - -----> Module:code_change/3 ``` -If a callback function fails or returns a bad value, the `gen_server` process -terminates. - -A `gen_server` process handles system messages as described in `m:sys`. The -`m:sys` module can be used for debugging a `gen_server` process. - -Notice that a `gen_server` process does not trap exit signals automatically, -this must be explicitly initiated in the callback module. - -Unless otherwise stated, all functions in this module fail if the specified -`gen_server` process does not exist or if bad arguments are specified. - -The `gen_server` process can go into hibernation (see `erlang:hibernate/3`) if a -callback function specifies `'hibernate'` instead of a time-out value. This can -be useful if the server is expected to be idle for a long time. However, use -this feature with care, as hibernation implies at least two garbage collections -(when hibernating and shortly after waking up) and is not something you want to -do between each call to a busy server. - -If the `gen_server` process needs to perform an action immediately after -initialization or to break the execution of a callback into multiple steps, it -can return `{continue,Continue}` in place of the time-out or hibernation value, -which will immediately invoke the [`handle_continue/2`](`c:handle_continue/2`) -callback. - -If the `gen_server` process terminates, e.g. as a result of a function in the -callback module returning `{stop,Reason,NewState}`, an exit signal with this -`Reason` is sent to linked processes and ports. See -[Processes](`e:system:ref_man_processes.md#errors`) in the Reference Manual for -details regarding error handling using exit signals. +If a callback function fails or returns a bad value, +the `gen_server` process terminates. However, an exception of class +[`throw`](`erlang:throw/1`) is not regarded as an error +but as a valid return, from all callback functions. + +A `gen_server` process handles system messages as described in `m:sys`. +The `m:sys` module can be used for debugging a `gen_server` process. + +Notice that a `gen_server` process does not trap exit signals +automatically, this must be explicitly initiated in the callback module. + +Unless otherwise stated, all functions in this module fail +if the specified `gen_server` process does not exist +or if bad arguments are specified. + +The `gen_server` process can go into hibernation (see `erlang:hibernate/3`) +if a callback function specifies `'hibernate'` instead of a time-out value. +This can be useful if the server is expected to be idle for a long time. +However, use this feature with care, as hibernation implies at least +two garbage collections (when hibernating and shortly after waking up) +and is not something you want to do between each call to a busy server. + +If the `gen_server` process needs to perform an action after +initialization or to break the execution of a callback into multiple steps, +it can return `{continue, Continue}` in place of +the time-out or hibernation value, which will invoke +the [`Module:handle_continue/2`](`c:handle_continue/2`) callback, +before receiving any external message / request. + +If the `gen_server` process terminates, e.g. as a result of a function +in the callback module returning `{stop,Reason,NewState}`, +an exit signal with this `Reason` is sent to linked processes and ports. +See [Processes](`e:system:ref_man_processes.md#errors`) +in the Reference Manual for details regarding error handling +using exit signals. > #### Note {: .info } > > For some important information about distributed signals, see the -> [_Blocking Signaling Over Distribution_](`e:system:ref_man_processes.md#blocking-signaling-over-distribution`) -> section in the _Processes_ chapter of the _Erlang Reference Manual_. Blocking -> signaling can, for example, cause call timeouts in `gen_server` to be -> significantly delayed. +> [_Blocking Signaling Over Distribution_][1] +> section in the _Processes_ chapter of the _Erlang Reference Manual_. +> Blocking signaling can, for example, cause call time-outs +> in `gen_server` to be significantly delayed. + +[1]: `e:system:ref_man_processes.md#blocking-signaling-over-distribution` ## See Also @@ -110,13 +119,13 @@ details regarding error handling using exit signals. %%% %%% The idea behind THIS server is that the user module %%% provides (different) functions to handle different -%%% kind of inputs. +%%% kind of inputs. %%% If the Parent process terminates the Module:terminate/2 %%% function is called. %%% %%% The user module should export: %%% -%%% init(Args) +%%% init(Args) %%% ==> {ok, State} %%% {ok, State, Timeout} %%% ignore @@ -128,21 +137,21 @@ details regarding error handling using exit signals. %%% {reply, Reply, State, Timeout} %%% {noreply, State} %%% {noreply, State, Timeout} -%%% {stop, Reason, Reply, State} +%%% {stop, Reason, Reply, State} %%% Reason = normal | shutdown | Term terminate(State) is called %%% %%% handle_cast(Msg, State) %%% %%% ==> {noreply, State} %%% {noreply, State, Timeout} -%%% {stop, Reason, State} +%%% {stop, Reason, State} %%% Reason = normal | shutdown | Term terminate(State) is called %%% %%% handle_info(Info, State) Info is e.g. {'EXIT', P, R}, {nodedown, N}, ... %%% %%% ==> {noreply, State} %%% {noreply, State, Timeout} -%%% {stop, Reason, State} +%%% {stop, Reason, State} %%% Reason = normal | shutdown | Term, terminate(State) is called %%% %%% terminate(Reason, State) Let the user module clean up @@ -252,94 +261,98 @@ details regarding error handling using exit signals. %%%========================================================================= -doc """ +Initialize the server. + Whenever a `gen_server` process is started using [`start/3,4`](`start/3`), -[`start_monitor/3,4`](`start_monitor/3`), or [`start_link/3,4`](`start_link/3`), -this function is called by the new process to initialize. +[`start_monitor/3,4`](`start_monitor/3`), +or [`start_link/3,4`](`start_link/3`), this function is called +by the new process to initialize the server. `Args` is the `Args` argument provided to the start function. The return value `Result` is interpreted as follows: -- **`{ok,State}` - `{ok,State,_}`** - Initialization was succesful and `State` is the internal state of the - `gen_server` process. - -- **`{ok,_,Timeout}` - `{ok,_,hibernate}` - `{ok,_,{continue,Continue}}`** - See the corresponding return values from - [`Module:handle_call/3`](`c:handle_call/3`) for a description of this tuple - member. +- **`{ok,State}`\ + `{ok,State,_}`** - Initialization was succesful + and `State` is the internal state of the `gen_server` process. -- **`{stop,Reason}` - ** - Initialization failed. The `gen_server` process exits with reason `Reason`. +- **`{ok,_,Timeout}`\ + `{ok,_,hibernate}`\ + `{ok,_,{continue,Continue}}`** - See the corresponding return values from + [`Module:handle_call/3`](`c:handle_call/3`) for a description + of this tuple member. -- **`{error,Reason}` - `ignore`** - Initialization failed. The `gen_server` process exits with reason `normal`. +- **`{stop,Reason}`** - Initialization failed. The `gen_server` + process exits with reason `Reason`. - `{error,Reason}` was introduced in OTP 26.0. +- **`{error,Reason}` _since OTP 26.0_\ + `ignore`** - Initialization failed. The `gen_server` process exits + with reason `normal`. -See function [`start_link/3,4`](`start_link/3`)'s return value `t:start_ret/0` -in these different cases. +See function [`start_link/3,4`](`start_link/3`)'s return value +`t:start_ret/0` in these different cases. """. -callback init(Args :: term()) -> - {ok, State :: term()} | {ok, State :: term(), timeout() | hibernate | {continue, term()}} | - {stop, Reason :: term()} | ignore | {error, Reason :: term()}. + {ok, State :: term()} | + {ok, State :: term(), timeout() | hibernate | {continue, term()}} | + {stop, Reason :: term()} | + ignore | + {error, Reason :: term()}. + -doc """ +Handle a call. + Whenever a `gen_server` process receives a request sent using -[`call/2,3`](`call/3`), [`multi_call/2,3,4`](`multi_call/4`) or [`send_request/2,4`](`send_request/4`), -this function is called to handle the request. +[`call/2,3`](`call/3`), [`multi_call/2,3,4`](`multi_call/4`), +or [`send_request/2,4`](`send_request/4`), this function is called +to handle the request. -`State` is the internal state of the `gen_server` process, and `NewState` a -possibly updated one. +`State` is the internal state of the `gen_server` process, +and `NewState` a possibly updated one. -`Request` is passed from the same argument provided to `call` or `multi_call`. +`Request` is passed from the same argument provided +to `call` or `multi_call`. The return value `Result` is interpreted as follows: -- **`{reply,Reply,NewState}` - `{reply,Reply,NewState,_}`** - The `Reply` value is sent back to the client request and there becomes its - return value. +- **`{reply,Reply,NewState}`\ + `{reply,Reply,NewState,_}`** - The `Reply` value is sent back + to the client request and there becomes its return value. The `gen_server` process continues executing with the possibly updated internal state `NewState`. -- **`{noreply,NewState}` - `{noreply,NewState,_}`** - The `gen_server` process continues executing with the possibly updated - internal state `NewState`. +- **`{noreply,NewState}`\ + `{noreply,NewState,_}`** - The `gen_server` process + continues executing with the possibly updated internal state `NewState`. A reply to the client request has to be created by calling - [`reply(From, Reply)`](`reply/2`), either in this or in a later callback. + [`reply(From, Reply)`](`reply/2`), either in this + or in a later callback. -- **`{reply,_,_,Timeout}` - `{noreply,_,Timeout}`** - If an integer `Timeout` is provided, a time-out occurs unless a request or a - message is received within that many milliseconds. A time-out is represented +- **`{reply,_,_,Timeout}`\ + `{noreply,_,Timeout}`** - If an integer `Timeout` is provided, + a time-out occurs unless a request or a message is received + within that many milliseconds. A time-out is represented by the atom `timeout` to be handled by the [`Module:handle_info/2`](`c:handle_info/2`) callback function. - `Timeout =:= infinity` can be used to wait indefinitely, which is the same as - returning a value without a `Timeout` member. + `Timeout =:= infinity` can be used to wait indefinitely, + which is the same as returning a value without a `Timeout` member. -- **`{reply,_,_,hibernate}` - `{noreply,_,hibernate}`** - The process goes into hibernation waiting for the next message to arrive (by - calling `proc_lib:hibernate/3`). +- **`{reply,_,_,hibernate}`\ + `{noreply,_,hibernate}`** - The process goes into hibernation, + by calling `proc_lib:hibernate/3`, waiting for + the next message to arrive -- **`{reply,_,_,{continue,Continue}}` - `{noreply,_,{continue,Continue}}`** - The process will execute the - [`Module:handle_continue/2`](`c:handle_continue/2`) callback function, with - `Continue` as the first argument. +- **`{reply,_,_,{continue,Continue}}`\ + `{noreply,_,{continue,Continue}}`** - The process will execute the + [`Module:handle_continue/2`](`c:handle_continue/2`) callback function, + with `Continue` as the first argument. -- **`{stop,Reason,NewState}` - `{stop,Reason,Reply,NewState}`** - The `gen_server` process will call - [`Module:terminate(Reason,NewState)`](`c:terminate/2`) and then terminate. +- **`{stop,Reason,NewState}`\ + `{stop,Reason,Reply,NewState}`** - The `gen_server` process will call + [`Module:terminate(Reason,NewState)`](`c:terminate/2`), + and then terminate. `{stop,_,Reply,_}` will create a reply to the client request just as `{reply,Reply,...}` while `{stop,_,_}` will not, so just as for @@ -349,186 +362,222 @@ The return value `Result` is interpreted as follows: -callback handle_call(Request :: term(), From :: from(), State :: term()) -> {reply, Reply :: term(), NewState :: term()} | - {reply, Reply :: term(), NewState :: term(), timeout() | hibernate | {continue, term()}} | + {reply, Reply :: term(), NewState :: term(), + timeout() | hibernate | {continue, term()}} | {noreply, NewState :: term()} | - {noreply, NewState :: term(), timeout() | hibernate | {continue, term()}} | + {noreply, NewState :: term(), + timeout() | hibernate | {continue, term()}} | {stop, Reason :: term(), Reply :: term(), NewState :: term()} | {stop, Reason :: term(), NewState :: term()}. + -doc """ -Whenever a `gen_server` process receives a request sent using `cast/2` or -[`abcast/2,3`](`abcast/2`), this function is called to handle the request. +Handle a cast message. -For a description of the arguments and possible return values, see -[`Module:handle_call/3`](`c:handle_call/3`). +Whenever a `gen_server` process receives a request sent using `cast/2` +or [`abcast/2,3`](`abcast/2`), this function is called +to handle the request. + +For a description of the arguments and possible return values, +see [`Module:handle_call/3`](`c:handle_call/3`). """. -callback handle_cast(Request :: term(), State :: term()) -> {noreply, NewState :: term()} | - {noreply, NewState :: term(), timeout() | hibernate | {continue, term()}} | + {noreply, NewState :: term(), + timeout() | hibernate | {continue, term()}} | {stop, Reason :: term(), NewState :: term()}. + -doc """ -This function is called by a `gen_server` process when a time-out occurs or when -it receives any other message than a synchronous or asynchronous request (or a -system message). +Handle an info message (regular process message). -`Info` is either the atom `timeout`, if a time-out has occurred, or the received -message. +This function is called by a `gen_server` process when a time-out occurs +or when it receives any other message than a synchronous +or asynchronous request (or a system message). -For a description of the other arguments and possible return values, see -[`Module:handle_call/3`](`c:handle_call/3`). +`Info` is either the atom `timeout`, if a time-out has occurred, +or the received message. + +For a description of the other arguments and possible return values, +see [`Module:handle_call/3`](`c:handle_call/3`). > #### Note {: .info } > -> This callback is optional, so callback modules need not export it. The -> `gen_server` module provides a default implementation of this function that -> logs about the unexpected `Info` message, drops it and returns -> `{noreply, State}`. +> This callback is optional, so callback modules need not export it. +> The `gen_server` module provides a default implementation +> of this function that logs about the unexpected `Info` message, +> drops it and returns `{noreply, State}`. """. -callback handle_info(Info :: timeout | term(), State :: term()) -> {noreply, NewState :: term()} | {noreply, NewState :: term(), timeout() | hibernate | {continue, term()}} | {stop, Reason :: term(), NewState :: term()}. + -doc """ -This function is called by a `gen_server` process whenever a previous callback -returns one of the tuples containing `{continue, Continue}`. -[`handle_continue/2`](`c:handle_continue/2`) is invoked immediately after the -previous callback, which makes it useful for performing work after -initialization or for splitting the work in a callback in multiple steps, -updating the process state along the way. - -For a description of the other arguments and possible return values, see -[`Module:handle_call/3`](`c:handle_call/3`). +Handle a callback continuation. + +This function is called by a `gen_server` process whenever +a previous callback returns one of the tuples containing +`{continue, Continue}`. The call is invoked immediately after +the previous callback, which makes it useful for performing work +after initialization or, for splitting the work in a callback +into multiple steps, updating the process state along the way. + +For a description of the other arguments and possible return values, +see [`Module:handle_call/3`](`c:handle_call/3`). > #### Note {: .info } > -> This callback is optional, so callback modules need to export it only if they -> return one of the tuples containing `{continue,Continue}` from another -> callback. If such a `{continue,_}` tuple is used and the callback is not -> implemented, the process will exit with `undef` error. +> This callback is optional, so callback modules need to export it +> only if theyreturn one of the tuples containing `{continue,Continue}` +> from another callback. If such a `{continue,_}` tuple is used +> and the callback is not implemented, the process will exit +> with `undef` error. """. + -doc(#{since => <<"OTP 21.0">>}). -callback handle_continue(Info :: term(), State :: term()) -> {noreply, NewState :: term()} | - {noreply, NewState :: term(), timeout() | hibernate | {continue, term()}} | + {noreply, NewState :: term(), + timeout() | hibernate | {continue, term()}} | {stop, Reason :: term(), NewState :: term()}. + -doc """ -This function is called by a `gen_server` process when it is about to terminate. +Handle server termination. -It is to be the opposite of [`Module:init/1`](`c:init/1`) and do any necessary -cleaning up. When it returns, the `gen_server` process terminates with `Reason`. +This function is called by a `gen_server` process +when it is about to terminate. + +It is to be the opposite of [`Module:init/1`](`c:init/1`) +and do any necessary cleaning up. When it returns, +the `gen_server` process 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_server` process. +`Reason` is a term denoting the stop reason and `State` +is the internal state of the `gen_server` process. -`Reason` depends on why the `gen_server` process is terminating. If it is -because another callback function has returned a stop tuple `{stop,..}`, -`Reason` has the value specified in that tuple. If it is because of a failure, -`Reason` is the error reason. +`Reason` depends on why the `gen_server` process is terminating. +If it is because another callback function has returned a stop tuple +`{stop,..}`, `Reason` has the value specified in that tuple. +If it is because of a failure, `Reason` is the error reason. -If the `gen_server` process is part of a supervision tree and is ordered by its -supervisor to terminate, this function is called with `Reason=shutdown` if the -following conditions apply: +If the `gen_server` process is part of a supervision tree +and is ordered by its supervisor to terminate, this function is called +with `Reason=shutdown` if the following conditions apply: - The `gen_server` process has been set to trap exit signals. -- The shutdown strategy as defined in the child specification of the supervisor - is an integer time-out value, not `brutal_kill`. +- The shutdown strategy as defined in the child specification + of the supervisor is an integer time-out value, not `brutal_kill`. -Even if the `gen_server` process 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. +Even if the `gen_server` process 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_server` process terminates immediately. +If the `gen_server` process does not trap exits, +the `gen_server` process terminates immediately. Notice that for any other reason than `normal`, `shutdown`, or -`{shutdown,Term}`, see `stop/3`, the `gen_server` process is assumed to -terminate because of an error, and an error report is issued using `m:logger`. +`{shutdown,Term}`, see `stop/3`, the `gen_server` process is assumed +to terminate because of an error, and an error report is issued +using `m:logger`. -When the gen_server process exits, an exit signal with the same reason is sent -to linked processes and ports. +When the gen_server process exits, an exit signal with the same reason +is sent to linked processes and ports. > #### Note {: .info } > -> This callback is optional, so callback modules need not export it. The -> `gen_server` module provides a default implementation without cleanup. +> This callback is optional, so callback modules need not export it. +> The `gen_server` module provides a default implementation +> with no cleanup. """. -callback terminate(Reason :: (normal | shutdown | {shutdown, term()} | term()), State :: term()) -> term(). + -doc """ -This function is called by a `gen_server` process when it is to update its -internal state during a release upgrade/downgrade, that is, when the instruction -`{update,Module,Change,...}`, is specified in the [`appup`](`e:sasl:appup.md`) file. +Update the server state after code change. + +This function is called by a `gen_server` process when it is to update +its internal state during a release upgrade/downgrade, that is, +when the instruction `{update, Module, Change, ...}`, is specified +in the [`appup`](`e:sasl:appup.md`) file. For more information, see section -[Release Handling Instructions](`e:system:release_handling.md#instr`) in OTP -Design Principles. +[Release Handling Instructions](`e:system:release_handling.md#instr`) +in 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. +`{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. `State` is the internal state of the `gen_server` process. -`Extra` is passed "as is" from the `{advanced,Extra}` part of the update -instruction. +`Extra` is passed "as is" from the `{advanced,Extra}` part +of the update instruction. If successful, the function must return the updated internal state. -If the function returns `{error,Reason}`, the ongoing upgrade fails and rolls -back to the old release. +If the function returns `{error,Reason}`, +the ongoing upgrade fails and rolls back to the old release. > #### Note {: .info } > -> If a release upgrade/downgrade with `Change={advanced,Extra}` specified in the -> [`.appup`](`e:sasl:appup.md`) file is made when `c:code_change/3` isn't -> implemented the event handler will crash with an `undef` error reason. +> If a release upgrade/downgrade with `Change = {advanced, Extra}` +> specified in the [`.appup`](`e:sasl:appup.md`) file is made when +> [`Module:code_change/3`](`c:code_change/3`) is not implemented, +> the callback call will crash with an `undef` error reason. """. -callback code_change(OldVsn :: (term() | {down, term()}), State :: term(), Extra :: term()) -> {ok, NewState :: term()} | {error, Reason :: term()}. + -doc """ -This function is called by a `gen_server` process in order to format/limit the -server state for debugging and logging purposes. +Format/limit the status value. + +This function is called by a `gen_server` process +in in order to format/limit the server state +for debugging and logging purposes. It is called in the following situations: - One of [`sys:get_status/1,2`](`sys:get_status/1`) is invoked to get the `gen_server` status. `Opt` is set to the atom `normal`. -- The `gen_server` process terminates abnormally and logs an error. `Opt` is set - to the atom `terminate`. +- The `gen_server` process terminates abnormally and logs an error. + `Opt` is set to the atom `terminate`. -This function is useful for changing the form and appearance of the `gen_server` -status for these cases. A callback module wishing to change the -`sys:get_status/1,2` return value, as well as how its status appears in -termination error logs, exports an instance of -[`format_status/2`](`c:format_status/2`) that returns a term describing the -current status of the `gen_server` process. +This function is useful for changing the form and appearance +of the `gen_server` status for these cases. A callback module +wishing to change the `sys:get_status/1,2` return value, +as well as how its status appears in termination error logs, +exports an instance of [`Module:format_status/2`](`c:format_status/2`) +that returns a term describing the current status +of the `gen_server` process. -`PDict` is the current value of the process dictionary of the `gen_server` -process.. +`PDict` is the current value of the process dictionary +of the `gen_server` process.. `State` is the internal state of the `gen_server` process. -The function is to return `Status`, a term that changes the details of the -current state and status of the `gen_server` process. 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_server` 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. +The function is to return `Status`, a term that changes the details +of the current state and status of the `gen_server` process. +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_server` 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 that large state terms are printed in log files. +One use for this function is to return compact alternative +state representations to avoid that large state terms are printed +in log files. > #### Note {: .info } > -> This callback is optional, so callback modules need not export it. The -> `gen_server` module provides a default implementation of this function that -> returns the callback module state. +> This callback is optional, so callback modules need not export it. +> The `gen_server` module provides a default implementation +> of this function that returns the callback module state. """. -deprecated_callback({format_status, 2, "use format_status/1 instead"}). -doc(#{since => <<"OTP R13B04">>}). @@ -538,17 +587,14 @@ to avoid that large state terms are printed in log files. PDict :: [{Key :: term(), Value :: term()}], State :: term(), Status :: term(). + -doc """ A map that describes the `gen_server` status. The keys are: - - **`state`** - The internal state of the `gen_server` process. - - **`message`** - The message that caused the server to terminate. - - **`reason`** - The reason that caused the server to terminate. - - **`log`** - The [sys log](`sys:log/2`) of the server. New associations may be added to the status map without prior notice. @@ -558,25 +604,30 @@ New associations may be added to the status map without prior notice. message => term(), reason => term(), log => [sys:system_event()] }. + -doc """ -This function is called by a `gen_server` process in order to format/limit the -server state for debugging and logging purposes. +Format/limit the status value. + +This function is called by a `gen_server` process in in order to +format/limit the server state for debugging and logging purposes. It is called in the following situations: -- [`sys:get_status/1,2`](`sys:get_status/1`) is invoked to get the `gen_server` - status. +- [`sys:get_status/1,2`](`sys:get_status/1`) is invoked + to get the `gen_server` status. - The `gen_server` process terminates abnormally and logs an error. This callback is used to limit the status of the process returned by [`sys:get_status/1,2`](`sys:get_status/1`) or sent to `m:logger`. -The callback gets a map `Status` describing the current status and shall return -a map `NewStatus` with the same keys, but it may transform some values. +The callback gets a map `Status` describing the current status +and shall return a map `NewStatus` with the same keys, +but it may transform some values. -Two possible use cases for this callback is to remove sensitive information from -the state to prevent it from being printed in log files, or to compact large -irrelevant status items that would only clutter the logs. +Two possible use cases for this callback is to remove +sensitive information from the state to prevent it from being printed +in log files, or to compact large irrelevant status items +that would only clutter the logs. Example: @@ -595,13 +646,13 @@ format_status(Status) -> > #### Note {: .info } > > This callback is optional, so callback modules need not export it. The -> `gen_server` module provides a default implementation of this function that -> returns the callback module state. +> `gen_server` module provides a default implementation +> of this function that returns the callback module state. > -> If this callback is exported but fails, to hide possibly sensitive data, the -> default function will instead return the fact that -> [`format_status/1`](`c:format_status/1`) has crashed. - +> If this callback is exported but fails, +> to hide possibly sensitive data, +> the default function will instead return the fact that +> [`Module:format_status/1`](`c:format_status/1`) has crashed. """. -doc(#{since => <<"OTP 25.0">>}). -callback format_status(Status) -> NewStatus when @@ -615,12 +666,14 @@ format_status(Status) -> -doc """ -Destination, given to the `gen_server` as the first argument to the callback -function [`Module:handle_call/3`](`c:handle_call/3`), to be used by the when -replying through `reply/2` (instead of through the callback function's return -value) to the process `Client` that has called the `gen_server` using -[`call/2,3`](`call/2`). `Tag` is a term that is unique for this call/request -instance. +A call's reply destination. + +Destination, given to the `gen_server` as the first argument +to the callback function [`Module:handle_call/3`](`c:handle_call/3`), +to be used by the when replying through `reply/2` (instead of +through the callback function's return value), to the process `Client` +that has called the `gen_server` using [`call/2,3`](`call/2`). +`Tag` is a term that is unique for this call/request instance. """. -type from() :: {Client :: pid(), Tag :: reply_tag()}. -doc "A handle that associates a reply to the corresponding request.". @@ -630,33 +683,38 @@ instance. -opaque request_id() :: gen:request_id(). -doc """ -An opaque collection of request identifiers (`t:request_id/0`) where each -request identifier can be associated with a label chosen by the user. For more -information see `reqids_new/0`. +An opaque collection of request identifiers (`t:request_id/0`). + +Each request identifier can be associated with a label +chosen by the user. For more information see `reqids_new/0`. """. -opaque request_id_collection() :: gen:request_id_collection(). -doc """ +Response time-out for an asynchronous call. + Used to set a time limit on how long to wait for a response using either `receive_response/2`, `receive_response/3`, `wait_response/2`, or `wait_response/3`. The time unit used is `millisecond`. Currently valid values: -- **`0..4294967295`** - Timeout relative to current time in milliseconds. +- **`0..4294967295`** - Time-out relative to current time in milliseconds. -- **`infinity`** - Infinite timeout. That is, the operation will never time out. +- **`infinity`** - Infinite time-out. That is, + the operation will never time out. - **`{abs, Timeout}`** - An absolute - [Erlang monotonic time](`erlang:monotonic_time/1`) timeout in milliseconds. - That is, the operation will time out when - [`erlang:monotonic_time(millisecond)`](`erlang:monotonic_time/1`) returns a - value larger than or equal to `Timeout`. `Timeout` is not allowed to identify - a time further into the future than `4294967295` milliseconds. Identifying the - timeout using an absolute timeout value is especially handy when you have a - deadline for responses corresponding to a complete collection of requests - (`t:request_id_collection/0`) , since you do not have to recalculate the - relative time until the deadline over and over again. + [Erlang monotonic time](`erlang:monotonic_time/1`) + time-out in milliseconds. That is, the operation will time out when + [`erlang:monotonic_time(millisecond)`](`erlang:monotonic_time/1`) + returns a value larger than or equal to `Timeout`. + `Timeout` is not allowed to identify a time further into the future + than `4294967295` milliseconds. Specifying the time-out + using an absolute value is especially handy when you have + a deadline for responses corresponding to a complete collection + of requests (`t:request_id_collection/0`), since you do not have to + recalculate the relative time until the deadline over and over again. """. -type response_timeout() :: timeout() | {abs, integer()}. @@ -679,24 +737,27 @@ Currently valid values: %%% ----------------------------------------------------------------- -doc """ -Name specification to use when starting a `gen_server`. - -See functions [`start/3,4`](`start/3`), [`start_link/3,4`](`start_link/3`), -[`start_monitor/3,4`](`start_monitor/3`), [`enter_loop/3,4,5`](`enter_loop/3`), -and the type `t:server_ref/0`. - -- **`{local,LocalName}`** - Register the `gen_server` locally as `LocalName` - using [`register/2`](`erlang:register/2`). - -- **`{global,GlobalName}`** - Register the `gen_server` process id globally as - `GlobalName` using `global:register_name/2`. - -- **`{via,RegMod,ViaName}`** - Register the `gen_server` process with the - registry represented by `RegMod`. The `RegMod` callback is to export the - functions `register_name/2`, `unregister_name/1`, `whereis_name/1`, and - `send/2`, which are to behave like the corresponding functions in `m:global`. - Thus, `{via,global,GlobalName}` is a valid reference equivalent to - `{global,GlobalName}`. +Server name specification: `local`, `global`, or `via` registered. + +To be used when starting a `gen_server`. See functions +[`start/3,4`](`start/3`), +[`start_link/3,4`](`start_link/3`), +[`start_monitor/3,4`](`start_monitor/3`), +[`enter_loop/3,4,5`](`enter_loop/3`), and the type `t:server_ref/0`. + +- **`{local, LocalName}`** - Register the `gen_server` locally + as `LocalName` using [`register/2`](`erlang:register/2`). + +- **`{global, GlobalName}`** - Register the `gen_server` process id + globally as `GlobalName` using `global:register_name/2`. + +- **`{via, RegMod, ViaName}`** - Register the `gen_server` process + with the registry represented by `RegMod`. The `RegMod` callback + is to export the functions `register_name/2`, `unregister_name/1`, + `whereis_name/1`, and `send/2`, which are to behave like + the corresponding functions in `m:global`. + Thus, `{via, global, GlobalName}` is a valid reference + equivalent to `{global, GlobalName}`. """. -type server_name() :: % Duplicate of gen:emgr_name() {'local', LocalName :: atom()} @@ -704,28 +765,28 @@ and the type `t:server_ref/0`. | {'via', RegMod :: module(), ViaName :: term()}. -doc """ -Server specification to use when addressing a `gen_server`. +Server specification: `t:pid/0` or registered `t:server_name/0`. -See [`call/2,3`](`call/2`), `cast/2`, `send_request/2`, `check_response/2`, -`wait_response/2`, [`stop/2,3`](`stop/1`) and the type `t:server_name/0`. +To be used when addressing a `gen_server`. See [`call/2,3`](`call/2`), +`cast/2`, `send_request/2`, `check_response/2`, `wait_response/2`, +[`stop/2,3`](`stop/1`) and the type `t:server_name/0`. It can be: - **`t:pid/0`** - The `gen_server`'s process identifier. -- **`LocalName`** - The `gen_server` is locally registered as `LocalName` with - [`register/2`](`erlang:register/2`). +- **`LocalName`** - The `gen_server` is locally registered + as `LocalName` with [`register/2`](`erlang:register/2`). -- **`{Name,Node}`** - The `gen_server` is locally registered on another node. +- **`{Name,Node}`** - The `gen_server` is locally registered + on another node. -- **`{global,GlobalName}`** - The `gen_server` is globally registered in - `m:global`. +- **`{global, GlobalName}`** - The `gen_server` is globally registered + in `m:global`. -- **`{via,RegMod,ViaName}`** - The `gen_server` 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 `m:global`. Thus, - `{via,global,GlobalName}` is the same as `{global,GlobalName}`. +- **`{via, RegMod, ViaName}`** - The `gen_server` is registered + in an alternative process registry. See the same term + described for `t:server_name/0`. """. -type server_ref() :: % What gen:call/3,4 and gen:stop/1,3 accepts pid() @@ -735,41 +796,48 @@ It can be: | {'via', RegMod :: module(), ViaName :: term()}. -doc """ -Options that can be used when starting a `gen_server` server through, for -example, [`start_link/3,4`](`start_link/4`). +Server start options for the [`start` functions](`start_link/3`). -- **`{timeout,Timeout}`** - How many milliseconds the `gen_server` process is - allowed to spend initializing or it is terminated and the start function - returns `{error,timeout}`. +Options that can be used when starting a `gen_server` server through, +for example, [`start_link/3,4`](`start_link/4`). -- **`{spawn_opt,SpawnOptions}`** - The `SpawnOptions` option list is passed to - the function used to spawn the `gen_server`; see - [`spawn_opt/2`](`erlang:spawn_opt/2`). +- **`{timeout, Timeout}`** - How many milliseconds + the `gen_server` process is allowed to spend initializing + or it is terminated and the start function returns `{error, timeout}`. + +- **`{spawn_opt, SpawnOptions}`** - The `SpawnOptions` option list + is passed to the function used to spawn the `gen_server`; + see `t:proc_lib:start_spawn_option/0`). > #### Note {: .info } > - > Using spawn option `monitor` is not allowed, it causes a `badarg` failure. + > Using spawn option `monitor` is not allowed - + > it causes a `badarg` failure. -- **`t:enter_loop_opt/0`** - See the type `t:enter_loop_opt/0` below for more - start options that are also allowed by [`enter_loop/3,4,5`](`enter_loop/3`). +- **`t:enter_loop_opt/0`** - See the type `t:enter_loop_opt/0` + below for more start options that are also allowed + by [`enter_loop/3,4,5`](`enter_loop/3`). """. -type start_opt() :: % Duplicate of gen:option() {'timeout', Timeout :: timeout()} - | {'spawn_opt', SpawnOptions :: [proc_lib:spawn_option()]} + | {'spawn_opt', SpawnOptions :: [proc_lib:start_spawn_option()]} | enter_loop_opt(). %% -doc """ +Server start options for the [`start`](`start_link/4`) or +[`enter_loop`](`enter_loop/5`) functions. + Options that can be used when starting a `gen_server` server through -[`enter_loop/3-5`](`enter_loop/3`) or the start functions such as -[`start_link/3,4`](`start_link/3`). +[`enter_loop/3-5`](`enter_loop/5`) or the start functions such as +[`start_link/3,4`](`start_link/4`). -- **`{hibernate_after,HibernateAfterTimeout}`** - Specifies that the +- **`{hibernate_after, HibernateAfterTimeout}`** - Specifies that the `gen_server` 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`). + milliseconds and if no message is received, the process goes into + hibernation automatically (by calling `proc_lib:hibernate/3`). -- **`{debug,Dbgs}`** - For every entry in `Dbgs`, the corresponding function in - `m:sys` is called. +- **`{debug, Dbgs}`** - For every entry in `Dbgs`, + the corresponding function in `m:sys` is called. """. -type enter_loop_opt() :: % Some gen:option()s works for enter_loop/* {'hibernate_after', HibernateAfterTimeout :: timeout()} @@ -779,28 +847,28 @@ Options that can be used when starting a `gen_server` server through Return value from the [`start/3,4`](`start/3`) and [`start_link/3,4`](`start_link/3`) functions. -- **`{ok,Pid}`** - The `gen_server` process was succesfully created and +- **`{ok, Pid}`** - The `gen_server` process was succesfully created and initialized, with the process identifier `Pid`. -- **`{error,{already_started,OtherPid}}`** - A process with the specified - `ServerName` exists already with the process identifier `OtherPid`. This - `gen_server` was not started, or rather exited with reason `normal` before - calling [`Module:init/1`](`c:init/1`). +- **`{error, {already_started, OtherPid}}`** - A process with the specified + `ServerName` exists already with the process identifier `OtherPid`. + This function failed to start a `gen_server`. It exited with reason + `normal` before calling [`Module:init/1`](`c:init/1`). -- **`{error,timeout}`** - The `gen_server` process failed to initialize since - [`Module:init/1`](`c:init/1`) did not return within the - [start timeout](`t:start_opt/0`). The `gen_server` process was killed with - [`exit(_, kill)`](`erlang:exit/2`). +- **`{error, timeout}`** - The `gen_server` process failed to initialize + since [`Module:init/1`](`c:init/1`) did not return within the + [start time-out](`t:start_opt/0`). The `gen_server` process was killed + with [`exit(_, kill)`](`erlang:exit/2`). - **`ignore`** - The `gen_server` process failed to initialize since [`Module:init/1`](`c:init/1`) returned `ignore`. - **`{error,Reason}`** - The `gen_server` process failed to initialize since - [`Module:init/1`](`c:init/1`) returned `{stop,Reason}`, `{error,Reason}`, or - it failed with reason `Reason`. + [`Module:init/1`](`c:init/1`) returned `{stop,Reason}`, `{error,Reason}`, + or it failed with reason `Reason`. -See [`Module:init/1`](`c:init/1`) about the exit reason for the `gen_server` -process when it fails to initialize. +See [`Module:init/1`](`c:init/1`) about the exit reason +for the `gen_server` process when it fails to initialize. """. -type start_ret() :: % gen:start_ret() without monitor return {'ok', Pid :: pid()} @@ -808,10 +876,11 @@ process when it fails to initialize. | {'error', Reason :: term()}. -doc """ -Return value from the [`start_monitor/3,4`](`start_monitor/3`) functions. The -same as type `t:start_ret/0` except that for a succesful start it returns both -the process identifier `Pid` and a [`monitor/2,3`](`erlang:monitor/2`) -`t:reference/0` `MonRef`. +Return value from the [`start_monitor/3,4`](`start_monitor/3`) functions. + +The same as type `t:start_ret/0` except that for a succesful start +it returns both the process identifier `Pid` +and a [`monitor/2,3`](`erlang:monitor/2`) [`MonRef`](`t:reference/0`). """. -type start_mon_ret() :: % gen:start_ret() with only monitor return {'ok', {Pid :: pid(), MonRef :: reference()}} @@ -821,6 +890,8 @@ the process identifier `Pid` and a [`monitor/2,3`](`erlang:monitor/2`) %%% --------------------------------------------------- -doc """ +Start a server, neither linked nor registered. + Equivalent to `start/4` except that the `gen_server` process is not registered with any [name service](`t:server_name/0`). """. @@ -838,8 +909,11 @@ start(Module, Args, Options) -> error(badarg, [Module, Args, Options]). -doc """ -Creates a standalone `gen_server` process, that is, a `gen_server` process that -is not part of a supervision tree and thus has no supervisor. +Start a server, neither linked nor registered. + +Creates a standalone `gen_server` process, that is, +a `gen_server` process that is not part of a supervision tree, +and thus has no supervisor. Other than that see `start_link/4`. """. @@ -858,8 +932,10 @@ start(ServerName, Module, Args, Options) -> error(badarg, [ServerName, Module, Args, Options]). -doc """ -Equivalent to `start_link/4` except that the `gen_server` process is not -registered with any [name service](`t:server_name/0`). +Start a server, linked but not registered. + +Equivalent to `start_link/4` except that the `gen_server` process is +not registered with any [name service](`t:server_name/0`). """. -spec start_link( Module :: module(), @@ -875,52 +951,60 @@ start_link(Module, Args, Options) -> error(badarg, [Module, Args, Options]). -doc """ -Creates a `gen_server` process as part of a supervision tree. This function is -to be called, directly or indirectly, by the supervisor. For example, it ensures -that the `gen_server` process is spawned as linked to the caller (supervisor). +Start a server, linked but not registered. + +Creates a `gen_server` process as part of a supervision tree. +This function is to be called, directly or indirectly, by the supervisor. +For example, it ensures that the `gen_server` process is spawned +as linked to the caller (supervisor). -The `gen_server` process calls [`Module:init/1`](`c:init/1`) to initialize. To -ensure a synchronized startup procedure, `start_link/3,4` does not return until -[`Module:init/1`](`c:init/1`) has returned or failed. +The `gen_server` process calls [`Module:init/1`](`c:init/1`) +to initialize. To ensure a synchronized startup procedure, +`start_link/3,4` does not return until [`Module:init/1`](`c:init/1`) +has returned or failed. -Using the argument `ServerName` creates a `gen_server` with a registered name. -See type `t:server_name/0` for different name registrations. +[`ServerName`](`t:server_name/0`) specifies with what name +and now to register the server name. See type `t:server_name/0` +for different name registrations. `Module` is the name of the callback module. `Args` is any term that is passed as the argument to [`Module:init/1`](`c:init/1`). -See type `t:start_opt/0` for `Options` when starting the `gen_server` process. +See type `t:start_opt/0` for `Options` for starting +the `gen_server` process. See type `t:start_ret/0` for a description this function's return values. -If `start_link/3,4` returns `ignore` or `{error,_}`, the started `gen_server` -process has terminated. If an `'EXIT'` message was delivered to the calling -process (due to the process link), that message has been consumed. +If `start_link/3,4` returns `ignore` or `{error, _}`, +the started `gen_server` process has terminated. If an `'EXIT'` message +was delivered to the calling process (due to the process link), +that message has been consumed. > #### Warning {: .warning } > > Before OTP 26.0, if the started `gen_server` process returned e.g. -> `{stop,Reason}` from [`Module:init/1`](`c:init/1`), this function could return -> `{error,Reason}` _before_ the started `m:gen_server` process had terminated so -> starting again might fail because VM resources such as the registered name was -> not yet unregistered. An `'EXIT'` message could arrive later to the process -> calling this function. +> `{stop, Reason}` from [`Module:init/1`](`c:init/1`), this function +> could return `{error, Reason}` _before_ the started `m:gen_server` process +> had terminated so starting again might fail because VM resources +> such as the registered name was not yet unregistered. An `'EXIT'` message +> could arrive later to the process calling this function. > > But if the started `gen_server` process instead failed during -> [`Module:init/1`](`c:init/1`), a process link `{'EXIT',Pid,Reason}` message -> caused this function to return `{error,Reason}` so the `'EXIT'` message had -> been consumed and the started `m:gen_server` process had terminated. +> [`Module:init/1`](`c:init/1`), a process link `{'EXIT', Pid, Reason}` +> message caused this function to return `{error, Reason}`, +> so the `'EXIT'` message had been consumed and the started +> `m:gen_server` process had terminated. > -> Since it was impossible to tell the difference between these two cases from -> `start_link/3,4`'s return value, this inconsistency was cleaned up in OTP -> 26.0. - -The difference between returning `{stop,_}` and `{error,_}` from -[`Module:init/1`](`c:init/1`), is that `{error,_}` results in a graceful -("silent") termination since the `gen_server` process exits with reason -`normal`. +> Since it was impossible to tell the difference between these two cases +> from `start_link/3,4`'s return value, this inconsistency was cleaned up +> in OTP 26.0. + +The difference between returning `{stop, _}` and `{error, _}` from +[`Module:init/1`](`c:init/1`), is that `{error, _}` results in a graceful +("silent") termination since the `gen_server` process exits +with reason `normal`. """. -spec start_link( ServerName :: server_name(), @@ -937,8 +1021,10 @@ start_link(ServerName, Module, Args, Options) -> error(badarg, [ServerName, Module, Args, Options]). -doc """ -Equivalent to `start_monitor/4` except that the `gen_server` process is not -registered with any [name service](`t:server_name/0`). +Start a server, monitored but neither linked nor registered. + +Equivalent to `start_monitor/4` except that the `gen_server` process +is not registered with any [name service](`t:server_name/0`). """. -doc(#{since => <<"OTP 23.0">>}). -spec start_monitor( @@ -955,16 +1041,20 @@ start_monitor(Module, Args, Options) -> error(badarg, [Module, Args, Options]). -doc """ -Creates a standalone `gen_server` process, that is, a `gen_server` process that -is not part of a supervision tree (and thus has no supervisor) and atomically -sets up a monitor to the newly created server. +Start a server, monitored and registered, but not linked. -Other than that see [`start_link/3,4`](`start_link/3`). Note that the return -value for a successful start differs in that it returns a monitor `reference`. -See type `t:start_mon_ret/0`. +Creates a standalone `gen_server` process, that is, +a `gen_server` process that is not part of a supervision tree +(and thus has no supervisor) and atomically sets up a monitor +to the newly created server. -If the start is not successful, the caller will be blocked until the monitor's -`'DOWN'` message has been received and removed from the message queue. +Other than that see [`start_link/3,4`](`start_link/3`). +Note that the return value for a successful start differs in that +it returns a monitor `reference`. See type `t:start_mon_ret/0`. + +If the start is not successful, the caller will be blocked +until the monitor's `'DOWN'` message has been received +and removed from the message queue. """. -doc(#{since => <<"OTP 23.0">>}). -spec start_monitor( @@ -998,23 +1088,26 @@ stop(ServerRef) -> gen:stop(ServerRef). -doc """ -Orders the generic server specified by `ServerRef` to exit with the specified -`Reason` and waits for it to terminate. The `gen_server` -process calls [`Module:terminate/2`](`c:terminate/2`) before exiting. - -The 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 using `m:logger`. An exit signal with the same reason is -sent to linked processes and ports. - -`Timeout` is an integer that specifies how many milliseconds to wait for the -server to terminate, or the atom `infinity` to wait indefinitely. If the server -has not terminated within the specified time, the call exits the calling process -with reason `timeout`. - -If the process does not exist, the call exits the calling process with reason -`noproc`, and with reason `{nodedown,Node}` if the connection fails to the -remote `Node` where the server runs. +Stop a server. + +Orders the generic server specified by `ServerRef` to exit +with the specified `Reason` and waits for it to terminate. +The `gen_server` process calls [`Module:terminate/2`](`c:terminate/2`) +before exiting. + +The 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 using `m:logger`. +An exit signal with the same reason is sent to linked processes and ports. + +`Timeout` is an integer that specifies how many milliseconds to wait +for the server to terminate, or the atom `infinity` to wait indefinitely. +If the server has not terminated within the specified time, +the call exits the calling process with reason `timeout`. + +If the process does not exist, the call exits the calling process +with reason `noproc`, or with reason `{nodedown,Node}` +if the connection fails to the remote `Node` where the server runs. """. -doc(#{since => <<"OTP 18.0">>}). -spec stop( @@ -1031,8 +1124,8 @@ stop(ServerRef, Reason, Timeout) -> %% If the server is located at another node, that node will %% be monitored. %% If the client is trapping exits and is linked server termination -%% is handled here (? Shall we do that here (or rely on timeouts) ?). -%% ----------------------------------------------------------------- +%% is handled here (? Shall we do that here (or rely on time-outs) ?). +%% ----------------------------------------------------------------- -doc(#{equiv => call(ServerRef, Request, 5000)}). -spec call( @@ -1050,66 +1143,69 @@ call(ServerRef, Request) -> end. -doc """ -Makes a synchronous call to the `ServerRef` of the `gen_server` process by -sending a request and waiting until a reply arrives or a time-out occurs. The -`gen_server` process calls [`Module:handle_call/3`](`c:handle_call/3`) to handle -the request. +Call a server: send request and wait for response. + +Makes a synchronous call to the `ServerRef` of the `gen_server` process +by sending a request and waiting until a reply arrives +or a time-out occurs. The `gen_server` process calls +[`Module:handle_call/3`](`c:handle_call/3`) to handle the request. See also `ServerRef`'s type `t:server_ref/0`. `Request` is any term that is passed as the first argument to [`Module:handle_call/3`](`c:handle_call/3`). -`Timeout` is an integer that specifies how many milliseconds to wait for a -reply, or the atom `infinity` to wait indefinitely. If no -reply is received within the specified time, this function exits the calling +`Timeout` is an integer that specifies how many milliseconds to wait +for a reply, or the atom `infinity` to wait indefinitely. If no reply +is received within the specified time, this function exits the calling process with an exit term containing `Reason = timeout` as described below. > #### Note {: .info } > -> Before OTP 24, if the caller uses (`try`...)`catch` to avoid process exit, and -> the server happens to just be late with the reply, it may arrive to the -> process message queue any time later. The calling process must therefore after -> catching a time-out exit be prepared to receive garbage message(s) on the form -> `{reference(), _}` and deal with them appropriately (discard them) so they do -> not clog the process message queue or gets mistaken for other messages. +> Before OTP 24, if the caller uses (`try`...)`catch` +> to avoid process exit, and the server happens to just be late +> with the reply, it may arrive to the process message queue +> any time later. The calling process must therefore after +> catching a time-out exit be prepared to receive garbage message(s) +> on the form `{reference(), _}` and deal with them appropriately +> (discard them) so they do not clog the process message queue, +> or gets mistaken for other messages. > -> Starting with OTP 24, `gen_server:call` uses process aliases, so late replies -> will not be received. +> Starting with OTP 24, `gen_server:call` uses process aliases, +> so late replies will not be received. The return value `Reply` is passed from the return value of [`Module:handle_call/3`](`c:handle_call/3`). This call may exit the calling process with an exit term on the form -`{Reason, Location}` where `Location = {gen_server,call,ArgList}` and `Reason` -can be (at least) one of: +`{Reason, Location}` where `Location = {gen_server, call, ArgList}` +and `Reason` can be (at least) one of: -- **`timeout`** - The call was aborted after waiting `Timeout` milliseconds for - a reply, as described above. +- **`timeout`** - The call was aborted after waiting `Timeout` milliseconds + for a reply, as described above. - **`noproc`** - The `ServerRef` refers to a server by name (it is not a - `t:pid/0`) and looking up the server process failed, or the `t:pid/0` was - already terminated. + `t:pid/0`) and looking up the server process failed, or the `t:pid/0` + was already terminated. -- **`{nodedown,Node}`** - The `ServerRef` refers to a server on the remote node - `Node` and the connection to that node failed. +- **`{nodedown,Node}`** - The `ServerRef` refers to a server + on the remote node `Node` and the connection to that node failed. - **`calling_self`** - A call to `self/0` would hang indefinitely. -- **`shutdown` - ** - The server was stopped during the call by its supervisor. See also `stop/3`. +- **`shutdown`** - The server was stopped during the call + by its supervisor. See also `stop/3`. -- **`normal` - `{shutdown,Term}` - ** - The server stopped during the call by returning `{stop,Reason,_}` from one of - its callbacks without replying to this call. See also `stop/3`. +- **`normal`\ + `{shutdown,Term}`** - The server stopped during the call + by returning `{stop,Reason,_}` from one of its callbacks + without replying to this call. See also `stop/3`. -- **`_OtherTerm`** - The server process exited during the call, with reason - `Reason`. Either by returning `{stop,Reason,_}` from one of its callbacks - (without replying to this call), by raising an exception, or due to getting an - exit signal it did not trap. +- **`_OtherTerm`** - The server process exited during the call, + with reason `Reason`. Either by returning `{stop,Reason,_}` + from one of its callbacks (without replying to this call), + by raising an exception, or due to getting an exit signal + it did not trap. """. -spec call( ServerRef :: server_ref(), @@ -1132,24 +1228,28 @@ call(ServerRef, Request, Timeout) -> %% result of the request. -doc """ -Sends an asynchronous `call` request `Request` to the `gen_server` process -identified by `ServerRef` and returns a request identifier `ReqId`. - -The return value `ReqId` shall later be used with `receive_response/2`, `wait_response/2`, -or `check_response/2` to fetch the actual result of the request. Besides passing -the request identifier directly to these functions, it can also be saved in a -request identifier collection using `reqids_add/3`. Such a collection of request -identifiers can later be used in order to get one response corresponding to a -request in the collection by passing the collection as argument to -`receive_response/3`, `wait_response/3`, or `check_response/3`. If you are about -to save the request identifier in a request identifier collection, you may want -to consider using `send_request/4` instead. +Send an asynchronous `call` request. + +Sends `Request` to the `gen_server` process identified by `ServerRef` +and returns a request identifier `ReqId`. + +The return value `ReqId` shall later be used with `receive_response/2`, +`wait_response/2`, or `check_response/2` to fetch the actual result +of the request. Besides passing the request identifier directly +to these functions, it can also be stored in +a request identifier collection using `reqids_add/3`. +Such a collection of request identifiers can later be used +in order to get one response corresponding to a +request in the collection by passing the collection +as argument to `receive_response/3`, `wait_response/3`, +or `check_response/3`. If you are about to store the request identifier +in a collection, you may want to consider using `send_request/4` instead. The call -`gen_server:receive_response(gen_server:send_request(ServerRef, Request), Timeout)` +`gen_server:receive_response(gen_server:send_request(ServerRef, Request), Timeout)` can be seen as equivalent to -[`gen_server:call(ServerRef, Request, Timeout)`](`call/3`), ignoring the error -handling. +[`gen_server:call(ServerRef, Request, Timeout)`](`call/3`), +ignoring the error handling. The `gen_server` process calls [`Module:handle_call/3`](`c:handle_call/3`) to handle the request. @@ -1172,17 +1272,20 @@ send_request(ServerRef, Request) -> end. -doc """ -Sends an asynchronous `call` request `Request` to the `gen_server` process -identified by `ServerRef`. The `Label` will be associated with the request -identifier of the operation and added to the returned request identifier -collection `NewReqIdCollection`. The collection can later be used in order to -get one response corresponding to a request in the collection by passing the -collection as argument to `receive_response/3`, `wait_response/3`, or, -`check_response/3`. +Send an asynchronous `call` request and add it +to a request identifier collection. + +Sends `Request` to the `gen_server` process identified by `ServerRef`. +The `Label` will be associated with the request identifier +of the operation and added to the returned request identifier collection +`NewReqIdCollection`. The collection can later be used in order to +get one response corresponding to a request in the collection +by passing the collection as argument to `receive_response/3`, +`wait_response/3`, or `check_response/3`. The same as calling -[`gen_server:reqids_add`](`reqids_add/3`)([`gen_server:send_request`](`send_request/2`)`(ServerRef, Request), Label, ReqIdCollection)`, -but calling [`send_request/4`](`send_request/4`) is slightly more efficient. +[`reqids_add`](`reqids_add/3`)`(`[`send_request`](`send_request/2`)`(ServerRef, Request), Label, ReqIdCollection)`, +but slightly more efficient. """. -doc(#{since => <<"OTP 25.0">>}). -spec send_request(ServerRef::server_ref(), @@ -1200,24 +1303,27 @@ send_request(ServerRef, Request, Label, ReqIdCol) -> end. -doc """ -Wait for a response corresponding to the request identifier `ReqId`. The request -must have been made by `send_request/2`, and it must have been made by the same -process calling this function. +Wait for a request response. + +Wait for the response to the request identifier `ReqId`. The request +must have been made by `send_request/2`, and it must have been made +by the same process calling this function. -`WaitTime` specifies how long to wait for a reply. If no reply is received -within the specified time, the function returns `timeout` and no cleanup is -done, and thus the function can be invoked repeatedly until a reply is returned. +`WaitTime` specifies how long to wait for a reply. +If no reply is received within the specified time, +the function returns `timeout` and no cleanup is done. +Thus the function can be invoked repeatedly until a reply is returned. The return value `Reply` is passed from the return value of [`Module:handle_call/3`](`c:handle_call/3`). -The function returns an error if the `gen_server` died before a reply was sent. +The function returns an error if the `gen_server` +died before a reply was sent. The difference between `receive_response/2` and -[`wait_response/2`](`wait_response/2`) is that -[`receive_response/2`](`receive_response/2`) abandons the request at time-out so -that a potential future response is ignored, while -[`wait_response/2`](`wait_response/2`) does not. +`wait_response/2` is that `receive_response/2` abandons +the request at time-out so that a potential future response is ignored, +while [`wait_response/2`](`wait_response/2`) does not. """. -doc(#{since => <<"OTP 23.0">>}). -spec wait_response(ReqId, WaitTime) -> Result when @@ -1236,49 +1342,57 @@ wait_response(ReqId, WaitTime) -> end. -doc """ -Wait for a response corresponding to a request identifier saved in -`ReqIdCollection`. All request identifiers of `ReqIdCollection` must correspond -to requests that have been made using `send_request/2` or `send_request/4`, and -all requests must have been made by the process calling this function. - -The `Label` in the response equals the `Label` associated with the request -identifier that the response corresponds to. The `Label` of a request identifier -is associated when [saving the request id](`reqids_add/3`) in a request -identifier collection, or when sending the request using `send_request/4`. - -Compared to `wait_response/2`, the returned result associated with a specific -request identifier or an exception associated with a specific request identifier -will be wrapped in a 3-tuple. The first element of this tuple equals the value -that would have been produced by [`wait_response/2`](`wait_response/2`), the -second element equals the `Label` associated with the specific request -identifier, and the third element `NewReqIdCollection` is a possibly modified +Wait for any request response in a collection. + +Wait for a response in a `ReqIdCollection`. All request identifiers +of `ReqIdCollection` must correspond to requests that have been made +using `send_request/2` or `send_request/4`, and all requests +must have been made by the process calling this function. + +The `Label` in the response is the `Label` associated with +the request identifier that the response corresponds to. +The `Label` of a request identifier is associated +when [adding the request id](`reqids_add/3`) to a collection, +or when sending the request using `send_request/4`. + +Compared to `wait_response/2`, the returned result or exception +associated with a specific request identifier will be wrapped +in a 3-tuple `{Response, Label, NewReqIdCollection}`. +`Response` is the value that would have been produced +by `wait_response/2`, `Label` is the value associated with +the specific [request identifier](`t:request_id/0`) +and `NewReqIdCollection` is a possibly modified request identifier collection. -If `ReqIdCollection` is empty, `no_request` will be returned. If no response is -received before the `WaitTime` timeout has triggered, the atom `timeout` is -returned. It is valid to continue waiting for a response as many times as needed -up until a response has been received and completed by `check_response()`, +If `ReqIdCollection` is empty, `no_request` will be returned. + +If no response is received before `WaitTime` has expired, +`timeout` is returned. It is valid to continue waiting +for a response as many times as needed up until a response +has been received and completed by `check_response()`, `receive_response()`, or `wait_response()`. -The difference between `receive_response/3` and -[`wait_response/3`](`wait_response/3`) is that -[`receive_response/3`](`receive_response/3`) abandons requests at timeout so -that potential future responses are ignored, while -[`wait_response/3`](`wait_response/3`) does not. +The difference between `receive_response/3` and `wait_response/3` +is that `receive_response/3` abandons requests at time-out +so that potential future responses are ignored, while +`wait_response/3` does not. -If `Delete` equals `true`, the association with `Label` will have been deleted -from `ReqIdCollection` in the resulting `NewReqIdCollection`. If `Delete` equals -`false`, `NewReqIdCollection` will equal `ReqIdCollection`. Note that deleting -an association is not for free and that a collection containing already handled +If `Delete` is `true`, the association with `Label` +has been deleted from `ReqIdCollection` in the resulting +`NewReqIdCollection`. If `Delete` is `false`, `NewReqIdCollection` +will equal `ReqIdCollection`. Note that deleting an association +is not for free and that a collection containing already handled requests can still be used by subsequent calls to -[`wait_response/3`](`wait_response/3`), `check_response/3`, and -`receive_response/3`. However, without deleting handled associations, the above -calls will not be able to detect when there are no more outstanding requests to -handle, so you will have to keep track of this some other way than relying on a -`no_request` return. Note that if you pass a collection only containing -associations of already handled or abandoned requests to -[`wait_response/3`](`wait_response/3`), it will always block until a timeout -determined by `WaitTime` is triggered and then return `no_reply`. +`wait_response/3`, `check_response/3`, and `receive_response/3`. + +However, without deleting handled associations, the above +calls will not be able to detect when there are +no more outstanding requests to handle, so you will have to keep track +of this some other way than relying on a `no_request` return. +Note that if you pass a collection only containing +associations of already handled or abandoned requests +to this function, it will always block until `WaitTime` expires +and then return `timeout`. """. -doc(#{since => <<"OTP 25.0">>}). -spec wait_response(ReqIdCollection, WaitTime, Delete) -> Result when @@ -1302,25 +1416,30 @@ wait_response(ReqIdCol, WaitTime, Delete) -> end. -doc """ -Receive a response corresponding to the request identifier `ReqId`. The request -must have been made by `send_request/2`, and it must have been made by the same -process calling this function. - -`Timeout` specifies how long to wait for a response. If no response is received -within the specified time, the function returns `timeout`. Assuming that the -server executes on a node supporting aliases (introduced in OTP 24) the request -will also be abandoned. That is, no response will be received after a timeout. +Receive a request response. + +Receive a response corresponding to the request identifier `ReqId`. +The request must have been made by `send_request/2`, +and it must have been made by the same process calling this function. + +`Timeout` specifies how long to wait for a response. +If no response is received within the specified time, +this function returns `timeout`. Assuming that the +server executes on a node supporting aliases (introduced in OTP 24) +the request will also be abandoned. That is, +no response will be received after a time-out. Otherwise, a stray response might be received at a later time. The return value `Reply` is passed from the return value of [`Module:handle_call/3`](`c:handle_call/3`). -The function returns an error if the `gen_server` died before a reply was sent. +The function returns an error if the `gen_server` died +before a reply was sent. -The difference between [`receive_response/2`](`receive_response/2`) and -`wait_response/2` is that [`receive_response/2`](`receive_response/2`) abandons -the request at timeout so that a potential future response is ignored, while -[`wait_response/2`](`wait_response/2`) does not. +The difference between `receive_response/2` and `wait_response/2` +is that `receive_response/2` abandons the request at time-out +so that a potential future response is ignored, +while `wait_response/2` does not. """. -doc(#{since => <<"OTP 24.0">>}). -spec receive_response(ReqId, Timeout) -> Result when @@ -1339,50 +1458,59 @@ receive_response(ReqId, Timeout) -> end. -doc """ -Receive a response corresponding to a request identifier saved in -`ReqIdCollection`. All request identifiers of `ReqIdCollection` must correspond -to requests that have been made using `send_request/2` or `send_request/4`, and -all requests must have been made by the process calling this function. - -The `Label` in the response equals the `Label` associated with the request -identifier that the response corresponds to. The `Label` of a request identifier -is associated when [adding the request id](`reqids_add/3`) in a request -identifier collection, or when sending the request using `send_request/4`. - -Compared to `receive_response/2`, the returned result associated with a specific -request identifier will be wrapped in a 3-tuple. The first element of this tuple -equals the value that would have been produced by -[`receive_response/2`](`receive_response/2`), the second element equals the -`Label` associated with the specific request identifier, and the third element -`NewReqIdCollection` is a possibly modified request identifier collection. - -If `ReqIdCollection` is empty, the atom `no_request` will be returned. - -`Timeout` specifies how long to wait for a response. If no response is received -within the specified time, the function returns `timeout`. Assuming that the -server executes on a node supporting aliases (introduced in OTP 24) all requests -identified by `ReqIdCollection` will also be abandoned. That is, no responses -will be received after a timeout. Otherwise, stray responses might be received +Receive a request response in a collection. + +Receive a response in `ReqIdCollection`. All request identifiers +of `ReqIdCollection` must correspond to requests that have been made +using `send_request/2` or `send_request/4`, and all requests +must have been made by the process calling this function. + +The `Label` in the response is the `Label` associated with +the request identifier that the response corresponds to. +The `Label` of a request identifier is associated +when [adding the request id](`reqids_add/3`) to a collection, +or when sending the request using `send_request/4`. + +Compared to `receive_response/2`, the returned result or exception +associated with a specific request identifier will be wrapped +in a 3-tuple `{Response, Label, NewReqIdCollection}`. +`Response` is the value that would have been produced +by `receive_response/2`, `Label` is the value associated with +the specific [request identifier](`t:request_id/0`) +and `NewReqIdCollection` is a possibly modified +request identifier collection. + +If `ReqIdCollection` is empty, `no_request` will be returned. + +`Timeout` specifies how long to wait for a response. If no response +is received within the specified time, the function returns `timeout`. +Assuming that the server executes on a node supporting aliases +(introduced in OTP 24) all requests identified by `ReqIdCollection` +will also be abandoned. That is, no responses will be received +after a time-out. Otherwise, stray responses might be received at a later time. -The difference between [`receive_response/3`](`receive_response/3`) and -`wait_response/3` is that [`receive_response/3`](`receive_response/3`) abandons -the requests at timeout so that potential future responses are ignored, while -[`wait_response/3`](`wait_response/3`) does not. +The difference between `receive_response/3` and `wait_response/3` +is that `receive_response/3` abandons the requests at time-out +so that potential future responses are ignored, +while [`wait_response/3`](`wait_response/3`) does not. -If `Delete` equals `true`, the association with `Label` will have been deleted -from `ReqIdCollection` in the resulting `NewReqIdCollection`. If `Delete` equals -`false`, `NewReqIdCollection` will equal `ReqIdCollection`. Note that deleting -an association is not for free and that a collection containing already handled +If `Delete` is `true`, the association with `Label` +is deleted from `ReqIdCollection` in the resulting +`NewReqIdCollection`. If `Delete` is `false`, `NewReqIdCollection` +will equal `ReqIdCollection`. Note that deleting an association +is not for free and that a collection containing already handled requests can still be used by subsequent calls to -[`receive_response/3`](`receive_response/3`), `check_response/3`, and -`wait_response/3`. However, without deleting handled associations, the above -calls will not be able to detect when there are no more outstanding requests to -handle, so you will have to keep track of this some other way than relying on a -`no_request` return. Note that if you pass a collection only containing +`receive_response/3`, `check_response/3`, and `wait_response/3`. + +However, without deleting handled associations, +the above calls will not be able to detect when there are +no more outstanding requests to handle, so you will have to keep track +of this some other way than relying on a `no_request` return. +Note that if you pass a collection only containing associations of already handled or abandoned requests to -[`receive_response/3`](`receive_response/3`), it will always block until a -timeout determined by `Timeout` is triggered. +this function, it will always block until `Timeout` expires +and then return `timeout`. """. -doc(#{since => <<"OTP 25.0">>}). -spec receive_response(ReqIdCollection, Timeout, Delete) -> Result when @@ -1406,18 +1534,23 @@ receive_response(ReqIdCol, Timeout, Delete) -> end. -doc """ -Check if `Msg` is a response corresponding to the request identifier `ReqId`. -The request must have been made by `send_request/2`, and it must have been made -by the same process calling this function. +Check if a received message is a request response. + +Checks if `Msg` is a response corresponding to +the request identifier `ReqId`. The request must have been made +by `send_request/2`, and by the same process calling this function. -If `Msg` is a response corresponding to `ReqId` the response is returned; -otherwise, `no_reply` is returned and no cleanup is done, and thus the function -must be invoked repeatedly until a response is returned. +If `Msg` is a reply to the handle `ReqId` the result of the request +is returned in `Reply`. Otherwise this function returns `no_reply` +and no cleanup is done, and thus the function shall be invoked repeatedly +until the response is returned. The return value `Reply` is passed from the return value of [`Module:handle_call/3`](`c:handle_call/3`). -The function returns an error if the `gen_server` died before a reply was sent. +If the `gen_statem` server process has died when this function +is called, that is; `Msg` reports the server's death, +this function returns an `error` return with the exit `Reason`. """. -doc(#{since => <<"OTP 23.0">>}). -spec check_response(Msg, ReqId) -> Result when @@ -1436,40 +1569,48 @@ check_response(Msg, ReqId) -> end. -doc """ -Check if `Msg` is a response corresponding to a request identifier saved in -`ReqIdCollection`. All request identifiers of `ReqIdCollection` must correspond -to requests that have been made using `send_request/2` or `send_request/4`, and -all requests must have been made by the process calling this function. - -The `Label` in the response equals the `Label` associated with the request -identifier that the response corresponds to. The `Label` of a request identifier -is associated when [saving the request id](`reqids_add/3`) in a request -identifier collection, or when sending the request using `send_request/4`. - -Compared to `check_response/2`, the returned result associated with a specific -request identifier or an exception associated with a specific request identifier -will be wrapped in a 3-tuple. The first element of this tuple equals the value -that would have been produced by [`check_response/2`](`check_response/2`), the -second element equals the `Label` associated with the specific request -identifier, and the third element `NewReqIdCollection` is a possibly modified +Check if a received message is a request response in a collection. + +Check if `Msg` is a response corresponding to a request identifier +stored in `ReqIdCollection`. All request identifiers of `ReqIdCollection` +must correspond to requests that have been made using `send_request/2` +or `send_request/4`, by the process calling this function. + +The `Label` in the response equals the `Label` associated +with the request identifier that the response corresponds to. +The `Label` of a request identifier is associated +when [storing the request id](`reqids_add/3`) in a collection, +or when sending the request using `send_request/4`. + +Compared to `check_response/2`, the returned result or exception +associated with a specific request identifier will be wrapped +in a 3-tuple `{Response, Label, NewReqIdCollection}`. +`Response` is the value that would have been produced +by `check_response/2`, `Label` is the value associated with +the specific [request identifier](`t:request_id/0`) +and `NewReqIdCollection` is a possibly modified request identifier collection. -If `ReqIdCollection` is empty, the atom `no_request` will be returned. If `Msg` -does not correspond to any of the request identifiers in `ReqIdCollection`, the -atom `no_reply` is returned. +If `ReqIdCollection` is empty, `no_request` will be returned. -If `Delete` equals `true`, the association with `Label` will have been deleted -from `ReqIdCollection` in the resulting `NewReqIdCollection`. If `Delete` equals -`false`, `NewReqIdCollection` will equal `ReqIdCollection`. Note that deleting -an association is not for free and that a collection containing already handled +If `Msg` does not correspond to any of the request identifiers +in `ReqIdCollection`, `no_reply` is returned. + +If `Delete` is `true`, the association with `Label` +has been deleted from `ReqIdCollection` in the resulting +`NewReqIdCollection`. If `Delete` is `false`, `NewReqIdCollection` +will equal `ReqIdCollection`. Note that deleting an association +is not for free and that a collection containing already handled requests can still be used by subsequent calls to -[`check_response/3`](`check_response/3`), `receive_response/3`, and -`wait_response/3`. However, without deleting handled associations, the above -calls will not be able to detect when there are no more outstanding requests to -handle, so you will have to keep track of this some other way than relying on a -`no_request` return. Note that if you pass a collection only containing +`check_response/3`, `receive_response/3`, and `wait_response/3`. + +However, without deleting handled associations, +the above calls will not be able to detect when there are +no more outstanding requests to handle, so you will have to keep track +of this some other way than relying on a `no_request` return. +Note that if you pass a collection only containing associations of already handled or abandoned requests to -[`check_response/3`](`check_response/3`), it will always return `no_reply`. +this function, it will always return `no_reply`. """. -doc(#{since => <<"OTP 25.0">>}). -spec check_response(Msg, ReqIdCollection, Delete) -> Result when @@ -1493,17 +1634,21 @@ check_response(Msg, ReqIdCol, Delete) -> end. -doc """ -Returns a new empty request identifier collection. A request identifier -collection can be utilized in order the handle multiple outstanding requests. +Create an empty request identifier collection. -Request identifiers of requests made by `send_request/2` can be saved in a -request identifier collection using `reqids_add/3`. Such a collection of request -identifiers can later be used in order to get one response corresponding to a -request in the collection by passing the collection as argument to +Returns a new empty request identifier collection. +A request identifier collection can be utilized to handle +multiple outstanding requests. + +Request identifiers of requests made by `send_request/2` +can be stored in a collection using `reqids_add/3`. +Such a collection of request identifiers can later be used +in order to get one response corresponding to a request +in the collection by passing the collection as argument to `receive_response/3`, `wait_response/3`, or, `check_response/3`. -`reqids_size/1` can be used to determine the amount of request identifiers in a -request identifier collection. +`reqids_size/1` can be used to determine the number of +request identifiers in a collection. """. -doc(#{since => <<"OTP 25.0">>}). -spec reqids_new() -> @@ -1512,7 +1657,7 @@ request identifier collection. reqids_new() -> gen:reqids_new(). --doc "Returns the amount of request identifiers saved in `ReqIdCollection`.". +-doc "Returns the number of request identifiers in `ReqIdCollection`.". -doc(#{since => <<"OTP 25.0">>}). -spec reqids_size(ReqIdCollection::request_id_collection()) -> non_neg_integer(). @@ -1525,9 +1670,11 @@ reqids_size(ReqIdCollection) -> end. -doc """ -Saves `ReqId` and associates a `Label` with the request identifier by adding -this information to `ReqIdCollection` and returning the resulting request -identifier collection. +Store a request identifier in a colletion. + +Stores `ReqId` and associates a `Label` with the request identifier +by adding this information to `ReqIdCollection` and returning +the resulting request identifier collection. """. -doc(#{since => <<"OTP 25.0">>}). -spec reqids_add(ReqId::request_id(), Label::term(), @@ -1542,9 +1689,11 @@ reqids_add(ReqId, Label, ReqIdCollection) -> end. -doc """ -Returns a list of `{ReqId, Label}` tuples which corresponds to all request -identifiers with their associated labels present in the `ReqIdCollection` -collection. +Convert a request identifier collection to a list. + +Returns a list of `{ReqId, Label}` tuples which corresponds to +all request identifiers with their associated labels +in [`ReqIdCollection`](`t:request_id_collection/0`). """. -doc(#{since => <<"OTP 25.0">>}). -spec reqids_to_list(ReqIdCollection::request_id_collection()) -> @@ -1562,21 +1711,21 @@ reqids_to_list(ReqIdCollection) -> %% ----------------------------------------------------------------- -doc """ -Sends an asynchronous request to the `ServerRef` of the `gen_server` process and -returns `ok` immediately, ignoring if the destination node or `gen_server` -process does not exist. The `gen_server` process calls -[`Module:handle_cast/2`](`c:handle_cast/2`) to handle the request. +Cast a request to a server. -See also `ServerRef`'s type `t:server_ref/0`. +Sends an asynchronous request to the `gen_server` +[`ServerRef`](`t:server_ref/0`) and returns `ok` immediately, +ignoring if the destination node or `gen_server` +process does not exist. -`Request` is any term that is passed as the first argument to -[`Module:handle_cast/2`](`c:handle_cast/2`). +The `gen_server` process calls +[`Module:handle_cast(Request, _)`](`c:handle_cast/2`) +to handle the request. """. -spec cast( ServerRef :: server_ref(), - Request :: term() - ) -> - ok. + Request :: term()) -> + ok. %% cast({global,Name}, Request) -> catch global:send(Name, cast_msg(Request)), @@ -1584,17 +1733,17 @@ cast({global,Name}, Request) -> cast({via, Mod, Name}, Request) -> catch Mod:send(Name, cast_msg(Request)), ok; -cast({Name,Node}=Dest, Request) when is_atom(Name), is_atom(Node) -> +cast({Name,Node}=Dest, Request) when is_atom(Name), is_atom(Node) -> do_cast(Dest, Request); cast(Dest, Request) when is_atom(Dest) -> do_cast(Dest, Request); cast(Dest, Request) when is_pid(Dest) -> do_cast(Dest, Request). -do_cast(Dest, Request) -> +do_cast(Dest, Request) -> do_send(Dest, cast_msg(Request)), ok. - + cast_msg(Request) -> {'$gen_cast',Request}. %% ----------------------------------------------------------------- @@ -1602,14 +1751,16 @@ cast_msg(Request) -> {'$gen_cast',Request}. %% ----------------------------------------------------------------- -doc """ -This function can be used by a `gen_server` process to explicitly send a reply -to a client that called [`call/2,3`](`call/2`) or -[`multi_call/2,3,4`](`multi_call/2`), when the reply cannot be passed in the -return value of [`Module:handle_call/3`](`c:handle_call/3`). - -`Client` must be the `From` argument provided to the `handle_call` callback -function. `Reply` is any term passed back to the client as the return value of -`call/2,3` or `multi_call/2,3,4`. +Send a reply to a client. + +This function can be used by a `gen_server` process to explicitly send +a reply to a client that called [`call/2,3`](`call/2`) or +[`multi_call/2,3,4`](`multi_call/2`), when the reply cannot be passed +in the return value of [`Module:handle_call/3`](`c:handle_call/3`). + +`Client` must be the `From` argument provided to the `c:handle_call/3` +callback function. `Reply` is any term passed back to the client +as the return value of `call/2,3` or `multi_call/2,3,4`. """. -spec reply( Client :: from(), @@ -1620,13 +1771,16 @@ function. `Reply` is any term passed back to the client as the return value of reply(Client, Reply) -> gen:reply(Client, Reply). -%% ----------------------------------------------------------------- +%% ----------------------------------------------------------------- %% Asynchronous broadcast, returns nothing, it's just send 'n' pray -%%----------------------------------------------------------------- +%%----------------------------------------------------------------- -doc """ -Equivalent to [`abcast(Nodes, Name, Request)`](`abcast/3`) where `Nodes` -is all nodes connected to the calling node, including the calling node. +Cast a request to multiple nodes. + +Equivalent to [`abcast(Nodes, Name, Request)`](`abcast/3`) +where `Nodes` is all nodes connected to the calling node, +including the calling node itself. """. -spec abcast( Name :: atom(), @@ -1638,13 +1792,17 @@ abcast(Name, Request) when is_atom(Name) -> do_abcast([node() | nodes()], Name, cast_msg(Request)). -doc """ -Sends an asynchronous request to the `gen_server` processes locally registered -as `Name` at the specified nodes. The function returns immediately and ignores -nodes that do not exist, or where the `gen_server` `Name` does not exist. The -`gen_server` processes call [`Module:handle_cast/2`](`c:handle_cast/2`) to -handle the request. +Cast a request to multiple nodes. -For a description of the arguments, see [`multi_call/2,3,4`](`multi_call/2`). +Sends an asynchronous request to the `gen_server` processes +locally registered as `Name` at the specified nodes. +The function returns immediately and ignores nodes that do not exist, +or where the `gen_server` `Name` does not exist. The `gen_server` +processes call [`Module:handle_cast/2`](`c:handle_cast/2`) +to handle the request. + +For a description of the arguments, +see [`multi_call/2,3,4`](`multi_call/2`). """. -spec abcast( Nodes :: [node()], @@ -1664,17 +1822,20 @@ do_abcast([], _,_) -> abcast. %%% ----------------------------------------------------------------- %%% Make a call to servers at several nodes. %%% Returns: {[Replies],[BadNodes]} -%%% A Timeout can be given -%%% +%%% A time-out can be given +%%% %%% A middleman process is used in case late answers arrives after -%%% the timeout. If they would be allowed to glog the callers message -%%% queue, it would probably become confused. Late answers will +%%% the time-out. If they would be allowed to glog the callers message +%%% queue, it would probably become confused. Late answers will %%% now arrive to the terminated middleman and so be discarded. %%% ----------------------------------------------------------------- -doc """ -Equivalent to [`multi_call(Nodes, Name, Request)`](`multi_call/3`) where `Nodes` -is all nodes connected to the calling node, including the calling node. +Call servers on multiple nodes in parallel. + +Equivalent to [`multi_call(Nodes, Name, Request)`](`multi_call/3`) +where `Nodes` is all nodes connected to the calling node, +including the calling node itself. """. -spec multi_call( Name :: atom(), @@ -1705,15 +1866,19 @@ multi_call(Nodes, Name, Request) multi_call(Nodes, Name, Request, infinity). -doc """ -Makes a synchronous call to all `gen_server` processes locally registered as -`Name` at the specified nodes, by first sending the request to the nodes, and -then waiting for the replies. The `gen_server` processes on the nodes call +Call servers on multiple nodes in parallel. + +Makes a synchronous call to all `gen_server` processes +locally registered as `Name` at the specified nodes, +by first sending the request to the nodes, and then waiting +for the replies. The `gen_server` processes on the nodes call [`Module:handle_call/3`](`c:handle_call/3`) to handle the request. -The function returns a tuple `{Replies,BadNodes}`, where `Replies` is a list of -`{Node,Reply}` tuples, and `BadNodes` is a list of nodes that either did not -exist, where `Name` was not a registered `gen_server`, or where it did not -reply. +The function returns a tuple `{Replies, BadNodes}`, +where `Replies` is a list of `{Node, Reply}` tuples, +and `BadNodes` is a list of nodes that either did not exist, +where `Name` was not a registered `gen_server`, +or where it did not reply. `Nodes` is a list of node names to which the request is to be sent. @@ -1722,27 +1887,30 @@ reply. `Request` is any term that is passed as the first argument to [`Module:handle_call/3`](`c:handle_call/3`). -`Timeout` is an integer that specifies how many milliseconds to wait for all -replies, or the atom `infinity` to wait indefinitely. If -no reply is received from a node within the specified time, the node is added to -`BadNodes`. +`Timeout` is an integer that specifies how many milliseconds +to wait for all replies, or the atom `infinity` to wait indefinitely. +If no reply is received from a node within the specified time, +the node is added to `BadNodes`. -When a reply `Reply` is received from the `gen_server` process at a node `Node`, -`{Node,Reply}` is added to `Replies`. `Reply` is passed from the return value of +When a reply `Reply` is received from the `gen_server` process +at a node `Node`, `{Node,Reply}` is added to `Replies`. +`Reply` is passed from the return value of [`Module:handle_call/3`](`c:handle_call/3`). > #### Warning {: .warning } > -> If one of the nodes cannot process monitors, for example, C or Java nodes, and -> the `gen_server` process is not started when the requests are sent, but starts -> within 2 seconds, this function waits the whole `Timeout`, which may be -> infinity. +> If one of the nodes cannot process monitors, for example, +> C or Java nodes, and the `gen_server` process is not started +> when the requests are sent, but starts within 2 seconds, +> this function waits the whole `Timeout`, which may be infinity. > > This problem does not exist if all nodes are Erlang nodes. -To prevent late answers (after the time-out) from polluting the message queue of -the caller, a middleman process is used to do the calls. Late answers are then -discarded when they arrive to a terminated process. +To prevent late answers (after the time-out) +from polluting the message queue of the caller, +a middleman process is used to do the calls. +Late answers are then discarded when they arrive to +the terminated middleman process. """. -spec multi_call( Nodes :: [node()], @@ -1846,14 +2014,14 @@ mc_cancel_timer(Timer, Alias) -> end. %%----------------------------------------------------------------- -%% enter_loop(Mod, Options, State, , ) ->_ -%% -%% Description: Makes an existing process into a gen_server. -%% The calling process will enter the gen_server receive +%% enter_loop(Mod, Options, State, , ) ->_ +%% +%% Description: Makes an existing process into a gen_server. +%% The calling process will enter the gen_server receive %% loop and become a gen_server process. -%% The process *must* have been started using one of the -%% start functions in proc_lib, see proc_lib(3). -%% The user is responsible for any initialization of the +%% The process *must* have been started using one of the +%% start functions in proc_lib, see proc_lib(3). +%% The user is responsible for any initialization of the %% process, including registering a name for it. %%----------------------------------------------------------------- @@ -1870,15 +2038,14 @@ enter_loop(Mod, Options, State) enter_loop(Mod, Options, State, self(), infinity). -doc """ -enter_loop(Module, Options, State, How) - -Makes an existing process a `gen_server` process. +Make the calling process become a `gen_server` process. -Equivalent to [`enter_loop(Module, Options, State, ServerName, infinity)`](`enter_loop/5`) if -called as `enter_loop(Module, Options, State, ServerName)`. +With argument `ServerName` equivalent to +[`enter_loop(Module, Options, + State, ServerName, infinity)`](`enter_loop/5`). -Equivalent to [`enter_loop(Module, Options, State, self(), How)`](`enter_loop/5`) if -called as `enter_loop(Module, Options, State, How)`. +With argument `How` equivalent to +[`enter_loop(Module, Options, State, self(), How)`](`enter_loop/5`). """. -spec enter_loop( Module :: module(), @@ -1887,7 +2054,7 @@ called as `enter_loop(Module, Options, State, How)`. ServerName :: server_name() | pid() ) -> no_return(); -( + ( Module :: module(), Options :: [enter_loop_opt()], State :: term(), @@ -1914,37 +2081,42 @@ enter_loop(Mod, Options, State, {continue, _}=Continue) enter_loop(Mod, Options, State, self(), Continue). -doc """ -Makes an existing process a `gen_server` process. - -Does not return, instead the calling process enters the `gen_server` process -receive loop and becomes a `gen_server` process. The process _must_ have been -started using one of the start functions in `m: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_server` process behavior provides. - -`Module`, `Options`, and `ServerName` have the same meanings as when calling -[`start[_link|_monitor]/3,4`](`start_link/3`) or it can be `self/0` for an -anonymous server, which is the same as calling an `enter_loop/3,4` function -without a `ServerName` argument. However, if `ServerName` is specified (and not -as `self/0`), the process must have been registered accordingly _before_ this -function is called. - -`State`, `Timeout`, `Hibernate` and `Cont` have the same meanings as in the -return value of [`Module:init/1`](`c:init/1`), which is _not_ called when -`enter_loop/3,4,5` is used. Note that to adhere to the -[gen_server Behaviour](`e:system:gen_server_concepts.md`) such a callback -function needs to be defined, and it might as well be the one used when starting -the `gen_server` process through `proc_lib`, and then be the one that calls -`enter_loop/3,4,5`. But if such a [`Module:init/1`](`c:init/1`) function in for -example error cases cannot call `enter_loop/3,4,5`, it should return a value -that follows the type specification for [`Module:init/1`](`c:init/1`) such as -`ignore`, although that value will be lost when returning to the spawning -function. - -This function fails if the calling process was not started by a `proc_lib` start -function, or if it is not registered according to `ServerName`. +Make the calling process become a `gen_server` process. + +Does not return, instead the calling process enters the `gen_server` +process receive loop and becomes a `gen_server` process. +The process _must_ have been started using one of the start functions +in `m: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_server` [`Module:init/1`](`c:init/1`); +callback provides. + +`Module`, `Options`, and `ServerName` have the same meanings +as when calling [`start[_link|_monitor]/3,4`](`start_link/3`) +or `ServerName` can be `self/0` for an anonymous server, +which is the same as calling an `enter_loop/3,4` function +without a `ServerName` argument. However, if `ServerName` +is specified (and not as `self/0`), the process must have been registered +accordingly _before_ this function is called. + +`State`, `Timeout`, `Hibernate` and `Cont` have the same meanings +as in the return value of [`Module:init/1`](`c:init/1`), +which is _not_ called when `enter_loop/3,4,5` is used. Note that +to adhere to the [gen_server Behaviour](`e:system:gen_server_concepts.md`) +such a callback function needs to be defined, and it might as well +be the one used when starting the `gen_server` process +through `proc_lib`, and then be the one that calls `enter_loop/3,4,5`. +But if such a [`Module:init/1`](`c:init/1`) function, +in for example error cases, cannot call `enter_loop/3,4,5`, +it should return a value that follows the type specification +for [`Module:init/1`](`c:init/1`) such as `ignore`, +although that value will be lost when returning to the spawning function. + +This function fails if the calling process was not started +by a `proc_lib` start function, or if it is not registered +according to `ServerName`. """. -spec enter_loop( Module :: module(), @@ -2447,7 +2619,7 @@ catch_result(error, Reason, Stacktrace) -> {Reason, Stacktrace}; catch_result(exit, Reason, _Stacktrace) -> Reason. error_info(_Reason, _ST, application_controller, _From, _Msg, _Mod, _State, _Debug) -> - %% OTP-5811 Don't send an error report if it's the system process + %% OTP-5811 Do not send an error report if it's the system process %% application_controller which is terminating - let init take care %% of it instead ok; diff --git a/lib/stdlib/src/gen_statem.erl b/lib/stdlib/src/gen_statem.erl index 9326709c6659..9b131ce2c54d 100644 --- a/lib/stdlib/src/gen_statem.erl +++ b/lib/stdlib/src/gen_statem.erl @@ -21,75 +21,67 @@ -moduledoc """ Generic state machine behavior. -`gen_statem` provides a generic state machine behaviour that for new code -replaces its predecessor `m:gen_fsm` since Erlang/OTP 20.0. The `gen_fsm` -behaviour remains in OTP "as is". +`gen_statem` provides a generic state machine behaviour +that since Erlang/OTP 20.0 replaces its predecessor `m:gen_fsm`, +and should be used for new code. The `gen_fsm` behaviour +remains in OTP "as is" to not break old code using it. -> #### Note {: .info } -> -> If you are new to `gen_statem` and want an overview of concepts and operation -> the section [`gen_statem` Behaviour ](`e:system:statem.md`)located in the -> User's Guide [OTP Design Principles ](`e:system:index.html`)is recommended to -> read before this reference manual, possibly after the Description section you -> are reading here. - -This reference manual contains type descriptions generated from types in the -`gen_statem` source code, so they are correct. However, the generated -descriptions also reflect the type hierarchy, which sometimes makes it hard to -get a good overview. If so, see the section -[`gen_statem` Behaviour ](`e:system:statem.md`)in the -[OTP Design Principles ](`e:system:index.html`)User's Guide. +A generic state machine server 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](`e:system:statem.md`). > #### Note {: .info } > -> - This behavior appeared in Erlang/OTP 19.0. -> - In OTP 19.1 a backwards incompatible change of the return tuple from -> [`Module:init/1`](`c:init/1`) was made and the mandatory callback function -> [`Module:callback_mode/0` ](`c:callback_mode/0`)was introduced. -> - In OTP 20.0 [generic time-outs ](`t:generic_timeout/0`)were added. -> - In OTP 22.1 time-out content [`update` ](`t:timeout_update_action/0`)and -> explicit time-out [`cancel` ](`t:timeout_cancel_action/0`)were added. -> - In OTP 22.3 the possibility to change the callback module with actions -> [`change_callback_module`](`t:action/0`), -> [`push_callback_module`](`t:action/0`) and -> [`pop_callback_module`](`t:action/0`), was added. - -`gen_statem` has got the same features that `m: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, `m:sys` traceable -- Multiple `m:sys` traceable replies -- Changing the callback module +> If you are new to `gen_statem` and want an overview +> of concepts and operation the section +> [`gen_statem` Behaviour](`e:system:statem.md`) located in +> the User's Guide [OTP Design Principles](`e:system:index.html`) +> is recommended to read. This reference manual focuses on +> being correct and complete, which might make it hard to see +> the forest for all the trees. + +#### Features + +`gen_statem` has got the same features that `m:gen_fsm` had +and adds some really useful: + +- [Co-located state code](#state_functions) +- [Arbitrary term state](#handle_event_function) +- [Event postponing](#event-postponing) +- [Self-generated events](#event-insertion) +- [State time-out](`t:state_timeout/0`) +- [Multiple generic named time-outs](`t:generic_timeout/0`) +- [Absolute time-out time](`t:timeout_option/0`) +- [Automatic state enter calls](#state-enter-calls) +- [Reply from other state than the request](#reply-to-a-call), + traceable with `m:sys` +- [Multiple replies](#reply-to-a-call), traceable with `m:sys` +- [Changing the callback module](#change_callback_module) Two [_callback modes_](`t:callback_mode/0`) are supported: -- One for finite-state machines (`m:gen_fsm` like), which requires the state to - be an atom and uses that state as the name of the current callback function. -- One that allows the state to be any term and that uses one callback function - for all states. +- `state_functions` - for finite-state machines (`m:gen_fsm` like), + which requires the state to be an atom and uses that state + as the name of the current callback function, arity 3. +- `handle_event_function` - that allows the state to be any term + and that uses `c:handle_event/4` as callback function for all states. -The callback model(s) for `gen_statem` differs from the one for `m:gen_fsm`, but -it is still fairly easy to -[rewrite from ](`m:gen_fsm#module-migration-to-gen_statem`)`gen_fsm` to `gen_statem`. +The callback modes for `gen_statem` differs from the one for +`gen_fsm`, but it is still fairly easy to +rewrite from `gen_fsm` to `gen_statem`. See the +[rewrite guide](`m:gen_fsm#module-migration-to-gen_statem`) +at the start of the `m:gen_fsm` documentation. -A generic state machine server 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](`e:system:statem.md`). +#### Callback module -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: +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: -```erlang +``` gen_statem module Callback module ----------------- --------------- gen_statem:start @@ -98,146 +90,229 @@ gen_statem:start_link -----> Module:init/1 Server start or code change -----> Module:callback_mode/0 + selects callback mode -gen_statem:stop -----> Module:terminate/3 +gen_statem:stop +Supervisor exit +Callback failure -----> Module:terminate/3 gen_statem:call gen_statem:cast gen_statem:send_request erlang:send erlang:'!' -----> Module:StateName/3 - Module:handle_event/4 - -- -----> Module:terminate/3 + or -----> Module:handle_event/4 + depending on callback mode -- -----> Module:code_change/4 +Release upgrade/downgrade +(code change) + -----> Module:code_change/4 ``` -Events are of different [types](`t:event_type/0`), so the callback functions can -know the origin of an event and how to respond. +#### State callback {: #state-callback } -If a callback function fails or returns a bad value, the `gen_statem` -terminates, unless otherwise stated. However, an exception of class -[`throw`](`erlang:throw/1`) is not regarded as an error but as a valid return -from all callback functions. - -[](){: #state-callback } - -The _state callback_ for a specific [state](`t:state/0`) 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_](`t:callback_mode/0`) that the -callback module defines with the callback function +The _state callback_ for a specific [state](`t:state/0`) 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_](`t:callback_mode/0`) +that the callback module defines with the callback function [`Module:callback_mode/0`](`c:callback_mode/0`). -When the [_callback mode_](`t:callback_mode/0`) is `state_functions`, the state -must be an atom and is used as the _state callback_ name; see -[`Module:StateName/3`](`c:'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 +[](){: #state_functions } +When the [_callback mode_](`t:callback_mode/0`) is `state_functions`, +the state must be an atom and is used as the _state callback_ name; +see [`Module:StateName/3`](`c:'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`](`c:terminate/3`) makes the state name `terminate` unusable in this mode. -When the [_callback mode_](`t:callback_mode/0`) is `handle_event_function`, the -state can be any term and the _state callback_ name is -[`Module:handle_event/4`](`c: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_](`m:gen_statem#state-callback`) is called with the event -as two arguments: type and content. When the -[_state callback_](`m:gen_statem#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_](`m:gen_statem#state-callback`) may return -[_transition actions_](`t:action/0`) for `gen_statem` to execute during the -_state transition_, for example to reply to a [`gen_statem:call/2,3`](`call/2`). - -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_](`m:gen_statem#state-callback`) can insert events using -the [_transition actions_](`t:action/0`) `next_event` and such an event is -inserted in the event queue as the next to call the -[_state callback_](`m:gen_statem#state-callback`) with. That is, as if it is the -oldest incoming event. A dedicated `t:event_type/0` `internal` can be used for -such events making them impossible to mistake for external events. +[](){: #handle_event_function } +When the [_callback mode_](`t:callback_mode/0`) is `handle_event_function`, +the state can be any term and the _state callback_ name is +[`Module:handle_event/4`](`c: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. + +#### Event types + +Events are of different [types](`t:event_type/0`), +therefore the callback functions can know the origin of an event +when handling it. [External events](`t:external_event_type/0`) are +`call`, `cast`, and `info`. Internal events are +[`timeout`](`t:timeout_event_type/0`) and `internal`. + +#### Event handling + +When `gen_statem` receives a process message it is transformed +into an event and the [_state callback_](#state-callback) +is called with the event as two arguments: type and content. When the +[_state callback_](#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_. + +#### Transition actions + +The [_state callback_](#state-callback) may return +[_transition actions_](`t:action/0`) for `gen_statem` to execute +during the _state transition_, for example to set a time-out +or reply to a call. + +#### Reply to a call {: #reply-to-a-call } + +See [`gen_statem:call/2,3`](#call-reply) about how to reply +to a call. A reply can be sent from any _state callback_, +not just the one that got the request event. + +#### Event postponing {: #event-postponing } + +One of the possible _transition actions_ is to postpone the current event. +Then it will not be handled in the current state. The `gen_statem` engine +keeps a queue of events divided into postponed events and +events still to process (not presented yet). 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. + +#### Event insertion {: #event-insertion } + +The [_state callback_](#state-callback) can insert +events using the [_transition action_](`t:action/0`) `next_event`, +and such an event is inserted in the event queue as the next to call the +[_state callback_](#state-callback) with. That is, +as if it is the oldest incoming event. A dedicated `t:event_type/0` +`internal` can be used for such events making it possible to +safely distinguish them from 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, `m:gen_fsm` to -force processing an inserted event before others. - -The `gen_statem` engine can automatically make a specialized call to the -[_state callback_](`m:gen_statem#state-callback`) whenever a new state is -entered; see `t:state_enter/0`. 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. +functions that you often would have to resort to in, for example, +`m:gen_fsm` to force processing an inserted event before others. > #### Note {: .info } > -> 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. +> If you postpone an event and (against good practice) directly call +> a different _state callback_, the postponed event is not retried, +> since there was no _state change_. +> +> Instead of directly calling a _state callback_, do a _state change_. +> This makes the `gen_statem` engine retry postponed events. +> +> Inserting an event in a _state change_ also triggers +> the new _state callback_ to be called with that event +> before receiving any external events. -For the details of a _state transition_, see type `t:transition_option/0`. +#### State enter calls {: #state-enter-calls } -A `gen_statem` handles system messages as described in `m:sys`. The `m:sys` module -can be used for debugging a `gen_statem`. +The `gen_statem` engine can automatically make a special call to the +[_state callback_](#state-callback) whenever a new state is +entered; see `t:state_enter/0`. 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. -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)`](`erlang:process_flag/2`). +For the details of a _state transition_, see type `t:transition_option/0`. -Unless otherwise stated, all functions in this module fail if the specified -`gen_statem` does not exist or if bad arguments are specified. +#### Hibernation -The `gen_statem` process can go into hibernation; see `proc_lib:hibernate/3`. It -is done when a [_state callback_](`m:gen_statem#state-callback`) or -[`Module:init/1`](`c:init/1`) specifies `hibernate` in the returned -[`Actions`](`t:action/0`) 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`. +The `gen_statem` process can go into hibernation; +see `proc_lib:hibernate/3`. It is done when +a [_state callback_](#state-callback) or +[`Module:init/1`](`c:init/1`) specifies `hibernate` +in the returned [`Actions`](`t:enter_action/0`) 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 it 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}` ](`t:enter_loop_opt/0`)for -[`start/3,4`](`start/3`), [`start_monitor/3,4`](`start_monitor/3`), -[`start_link/3,4`](`start_link/3`) or [`enter_loop/4,5,6`](`enter_loop/4`), that -may be used to automatically hibernate the server. +[`{hibernate_after, Timeout}`](`t:enter_loop_opt/0`) +for [`start/3,4`](`start/3`), [`start_link/3,4`](`start_link/3`), +[`start_monitor/3,4`](`start_monitor/3`), +or [`enter_loop/4,5,6`](`enter_loop/6`), that may be used +to automatically hibernate the server. + +#### Callback failure + +If a callback function fails or returns a bad value, +the `gen_statem` terminates. However, an exception of class +[`throw`](`erlang:throw/1`) is not regarded as an error +but as a valid return, from all callback functions. + +#### System messages and the `m:sys` module -If the `gen_statem` process terminates, e.g. as a result of a function in the -callback module returning `{stop,Reason}`, an exit signal with this `Reason` is -sent to linked processes and ports. See -[Processes](`e:system:ref_man_processes.md#errors`) in the Reference Manual for -details regarding error handling using exit signals. +A `gen_statem` handles system messages as described in `m:sys`. +The `m:sys` module can be used for debugging a `gen_statem`. +Replies sent through [_transition actions_](`t:action/0`) +gets logged, but not replies sent through [`reply/1,2`](`reply/2`). + +#### Trapping exit + +A `gen_statem` process, like all `gen_`\* behaviours, +does not trap exit signals automatically; +this must be explicitly initiated in the callback module +(by calling [`process_flag(trap_exit, true)`](`erlang:process_flag/2`) +preferably from `c:init/1`. + +#### Server termination + +If the `gen_statem` process terminates, e.g. as a result +of a callback function returning `{stop, Reason}`, an exit signal +with this `Reason` is sent to linked processes and ports. +See [Processes](`e:system:ref_man_processes.md#errors`) +in the Reference Manual for details regarding error handling +using exit signals. > #### Note {: .info } > > For some important information about distributed signals, see the -> [_Blocking Signaling Over Distribution_](`e:system:ref_man_processes.md#blocking-signaling-over-distribution`) -> section in the _Processes_ chapter of the _Erlang Reference Manual_. Blocking -> signaling can, for example, cause call timeouts in `gen_statem` to be -> significantly delayed. +> [_Blocking Signaling Over Distribution_ +> ](`e:system:ref_man_processes.md#blocking-signaling-over-distribution`) +> section in the _Processes_ chapter of the _Erlang Reference Manual_. +> Blocking signaling can, for example, cause call time-outs in `gen_statem` +> to be significantly delayed. + +#### Bad argument + +Unless otherwise stated, all functions in this module fail if the specified +`gen_statem` does not exist or if bad arguments are specified. ## Example -The following example shows a simple pushbutton model for a toggling pushbutton -implemented with [_callback mode_](`t:callback_mode/0`) `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 example shows a simple pushbutton model +for a toggling pushbutton implemented with +[_callback mode_](`t:callback_mode/0`) `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. + +### Pushbutton State Diagram + +```mermaid +--- +title: Pushbutton State Diagram +--- +stateDiagram-v2 + [*] --> off + off --> on : push\n* Increment count\n* Reply 'on' + on --> off : push\n* Reply 'off' +``` + +Not shown in the state diagram: +* The API function `push()` generates an event `push` of type `call`. +* The API function `get_count()` generates an event `get_count` + of type `call` that is handled in all states by replying with + the current count value. +* Unknown events are ignored and discarded. +* There is boilerplate code for start, stop, terminate, code change, + init, to set the callback mode to `state_functions`, etc... + +### Pushbutton Code The following is the complete callback module file `pushbutton.erl`: @@ -321,9 +396,9 @@ ok ``` To compare styles, here follows the same example using -[_callback mode_](`t:callback_mode/0`) `handle_event_function`, or rather the -code to replace after function [`init/1`](`c:init/1`) of the `pushbutton.erl` -example file above: +[_callback mode_](`t:callback_mode/0`) `handle_event_function`, +or rather, the code to replace after function [`init/1`](`c:init/1`) +of the `pushbutton.erl` example file above: ```erlang callback_mode() -> handle_event_function. @@ -347,6 +422,41 @@ handle_event(_, _, State, Data) -> {next_state,State,Data}. ``` +> #### Note {: .info } +> ## API changes +> - This behavior appeared in Erlang/OTP 19.0 as experimental. +> - In OTP 19.1 a backwards incompatible change of the return tuple from +> [`Module:init/1`](`c:init/1`) was made, +> the mandatory callback function +> [`Module:callback_mode/0`](`c:callback_mode/0`) was introduced, +> and `enter_loop/4` was added. +> - In OTP 19.2 [_state enter calls_](`t:state_enter/0`) were added. +> - In OTP 19.3 [state time-outs](`t:state_timeout/0`) were added. +> - In OTP 20.0 [generic time-outs](`t:generic_timeout/0`) were added +> and `gen_statem` was stated to be no longer experimental and +> preferred over `gen_fsm`. +> - In OTP 22.1 time-out content [`update`](`t:timeout_update_action/0`) +> and explicit time-out [`cancel`](`t:timeout_cancel_action/0`) +> were added. +> - In OTP 22.3 the possibility to change the callback module with actions +> [`change_callback_module`](#change_callback_module), +> [`push_callback_module`](#push_callback_module) and +> [`pop_callback_module`](#pop_callback_module), was added. +> - In OTP 23.0 [`start_monitor/3,4`](`start_monitor/3`) were added, +> as well as functions for asynchronous calls: `send_request/2`, +> [`wait_response/1,2`](`wait_response/2`), and `check_response/2`. +> - In OTP 24.0 [`receive_response/1,2`](`receive_response/2`) were added. +> - In OTP 25.0 [`Module:format_status/1`](`c:format_status/1`) +> was added to replace [`Module:format_status/1`](`c:format_status/1`), +> as well as functions for collections of asynchronous calls: +> `send_request/4`, `wait_response/3`, `receive_response/3`, +> `check_response/3`, `reqids_new/0`, `reqids_size/1`, +> `reqids_add/3`, `reqids_to_list/1`. +> - In OTP 26.0 the possibility to return `{error, Reason}` from +> [`Module:init/1`](`c:init/1`) was added. +> - In OTP 27.0 [`Module:format_status/1`](`c:format_status/1`) +> was deprecated. + ## See Also `m:gen_event`, `m:gen_fsm`, `m:gen_server`, `m:proc_lib`, `m:supervisor`, @@ -356,10 +466,8 @@ handle_event(_, _, State, Data) -> -include("logger.hrl"). -%%% -%%% NOTE: If init_ack() return values are modified, see comment -%%% above monitor_return() in gen.erl! -%%% +%%%========================================================================== +%%% Exports %% API -export( @@ -438,349 +546,552 @@ handle_event(_, _, State, Data) -> %%%========================================================================== -%%% Interface functions. +%%% Callback functions %%%========================================================================== -doc """ -Destination to use when replying through, for example, the `t:action/0` -`{reply,From,Reply}` to a process that has called the `gen_statem` server using -`call/2`. +A [`call`](`t:external_event_type/0`) event's reply destination. + +Destination to use when replying through, for example, +the action [`{reply, From, Reply}`](`t:reply_action/0`) +to a process that has called the `gen_statem` server +using [`call/2,3`](`call/3`). """. -type from() :: {To :: pid(), Tag :: reply_tag()}. % Reply-to specifier for call + +%%---------------------- -doc "A handle that associates a reply to the corresponding request.". -opaque reply_tag() :: gen:reply_tag(). +%%---------------------- -doc """ -If the [_callback mode_](`t:callback_mode/0`) is `handle_event_function`, the -state can be any term. After a _state change_ (`NextState =/= State`), all -postponed events are retried. +State name or state term. + +If the [_callback mode_](`t:callback_mode/0`) is `handle_event_function`, +the state can be any term. After a _state change_ (`NextState =/= State`), +all postponed events are retried. + +Comparing two states for strict equality is assumed to be a fast operation, +since for every _state transition_ the `gen_statem` engine has to deduce +if it is a _state change_. + +> #### Note {: .info } +> The smaller the state term, in general, the faster the comparison. +> +> Note that if the "same" state term is returned for a state transition +> (or a return action without a `NextState` field is used), +> the comparison for equality is always fast because that can be seen +> from the term handle. +> +> But if a newly constructed state term is returned, +> both the old and the new state terms will have to be traversed +> until an inequality is found, or until both terms +> have been fully traversed. +> +> So it is possible to use large state terms that are fast to compare, +> but very easy to accidentally mess up. Using small state terms is +> the safe choice. """. -type state() :: state_name() | % For StateName/3 callback functions term(). % For handle_event/4 callback function +%%---------------------- -doc """ -If the [_callback mode_](`t:callback_mode/0`) is `state_functions`, the state -must be an atom. After a _state change_ (`NextState =/= State`), all postponed -events are retried. Note that the state `terminate` is not possible to use since -it would collide with the optional callback function -[`Module:terminate/3`](`c:terminate/3`). +State name in [_callback mode_](`t:callback_mode/0`) `state_functions`. + +If the [_callback mode_](`t:callback_mode/0`) is `state_functions`, +the state must be an atom. After a _state change_ (`NextState =/= State`), +all postponed events are retried. Note that the state `terminate` +is not possible to use since it would collide with the optional +callback function [`Module:terminate/3`](`c:terminate/3`). """. -type state_name() :: atom(). +%%---------------------- -doc """ -A term in which the state machine implementation is to store any server data it -needs. The difference between this and the `t:state/0` 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. +Generic state data for the server. + +A term in which the state machine implementation is to store +any server data it needs. The difference between this and the `t:state/0` +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 +should be part of the `t:state/0` instead. """. -type data() :: term(). +%%---------------------- -doc """ -There are 3 categories of events: [external](`t:external_event_type/0`), -[timeout](`t:timeout_event_type/0`), and `internal`. +All event types: [external](`t:external_event_type/0`), +[time-out](`t:timeout_event_type/0`), or `internal`. -`internal` events can only be generated by the state machine itself through the -_transition action_ [`next_event`](`t:action/0`). +`internal` events can only be generated by the state machine itself +through the _transition action_ [`next_event`](`t:action/0`). """. -type event_type() :: external_event_type() | timeout_event_type() | 'internal'. + +%%---------------------- -doc """ -External events are of 3 types: `{call,From}`, `cast`, or `info`. Type `call` -originates from the API functions `call/2` and `send_request/2`. For calls, the -event contains whom to reply to. Type `cast` originates from the API function -`cast/2`. Type `info` originates from regular process messages sent to the -`gen_statem`. +Event from a [call](`call/3`), [cast](`cast/2`), +or regular process message; "info". + +Type `{call, From}` originates from the API functions +[`call/2,3`](`call/3`) or `send_request/2`. The event contains +[`From`](`t:from/0`), which is whom to reply to +by a `t:reply_action/0` or [`reply/2,3`](`reply/2`) call. + +Type `cast` originates from the API function `cast/2`. + +Type `info` originates from regular process messages +sent to the `gen_statem` process. """. -type external_event_type() :: {'call',From :: from()} | 'cast' | 'info'. + +%%---------------------- -doc """ -There are 3 types of time-out events that the state machine can generate for -itself with the corresponding `t:timeout_action/0`s. -""". +[Event time-out](`t:event_timeout/0`), +[generic time-out](`t:generic_timeout/0`), +or [state time-out](`t:state_timeout/0`). + +The time-out event types that the state machine can generate +for itself with the corresponding `t:timeout_action/0`s: + +| Time-out type | Action | Event type | +|-------------------|--------------------------------|-------------------| +| Event time-out | `{timeout, Time, ...}` | `timeout` | +| Generic time-out | `{{timeout, Name}, Time, ...}` | `{timeout, Name}` | +| State time-out | `{state_timeout, Time, ...}` | `state_timeout` | + +In short; the action to set a time-out with +[`EventType`](`t:timeout_event_type/0`) is `{EventType, Time, ...}`. +""" . -type timeout_event_type() :: 'timeout' | {'timeout', Name :: term()} | 'state_timeout'. +%%---------------------- -doc """ -Any event's content can be any term. +Event payload from the event's origin, delivered to +the [_state callback_](#state-callback). -See [`event_type`](`t:event_type/0`) that describes the origins of the different -event types, which is also where the event content comes from. +See [`event_type`](`t:event_type/0`) that describes the origins of +the different event types, which is also where the event's content +comes from. """. -type event_content() :: term(). +%%---------------------- -doc """ -This is the return type from [`Module:callback_mode/0`](`c:callback_mode/0`) and -selects [_callback mode_](`t:callback_mode/0`) and whether to do -[_state enter calls_](`t:state_enter/0`), or not. +Return value from [`Module:callback_mode/0`](`c:callback_mode/0`). + +This is the return type from +[`Module:callback_mode/0`](`c:callback_mode/0`) +which selects [_callback mode_](`t:callback_mode/0`) +and whether to do [_state enter calls_](`t:state_enter/0`), +or not. """. +-doc #{ since => ~"OTP 19.2" }. -type callback_mode_result() :: - callback_mode() | [callback_mode() | state_enter()]. + callback_mode() | [callback_mode() | state_enter()]. + +%%---------------------- -doc """ +One function per state or one common event handler. + The _callback mode_ is selected with the return value from [`Module:callback_mode/0`](`c:callback_mode/0`): -- **`state_functions`** - The state must be of type `t:state_name/0` and one - callback function per state, that is, [`Module:StateName/3`](`c:'StateName'/3`), - is used. +- **`state_functions`** - The state must be of type `t:state_name/0` + and one callback function per state, that is, + [`Module:StateName/3`](`c:'StateName'/3`), is used. - **`handle_event_function`** - The state can be any term and the callback - function [`Module:handle_event/4`](`c:handle_event/4`) is used for all states. - -The function [`Module:callback_mode/0`](`c:callback_mode/0`) is called when -starting the `gen_statem`, after code change and after changing the callback -module with any of the actions [`change_callback_module`](`t:action/0`), -[`push_callback_module`](`t:action/0`) or [`pop_callback_module`](`t:action/0`). + function [`Module:handle_event/4`](`c:handle_event/4`) + is used for all states. + +The function [`Module:callback_mode/0`](`c:callback_mode/0`) is called +when starting the `gen_statem`, after code change and after changing +the callback module with any of the actions +[`change_callback_module`](#change_callback_module), +[`push_callback_module`](#push_callback_module), +or [`pop_callback_module`](#pop_callback_module). The result is cached for subsequent calls to -[state callbacks](`m:gen_statem#state-callback`). +[_state callbacks_](#state-callback). """. +-doc #{ since => ~"OTP 19.1" }. -type callback_mode() :: 'state_functions' | 'handle_event_function'. + +%%---------------------- -doc """ -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 +[_Callback mode_](`t:callback_mode/0`) modifier +for _state enter calls_: the atom `state_enter`. + +Both _callback modes_ can use _state enter calls_, +and this is selected by adding this `state_enter` flag +to the [_callback mode_](`t:callback_mode/0`) return value from [`Module:callback_mode/0`](`c:callback_mode/0`). -If [`Module:callback_mode/0`](`c:callback_mode/0`) returns a list containing -`state_enter`, the `gen_statem` engine will, at every _state change_, call the -[state callback](`m:gen_statem#state-callback`) with arguments -`(enter, OldState, Data)` or `(enter, OldState, State, Data)`, depending on the -[_callback mode_](`t:callback_mode/0`). This may look like an event but is -really a call performed after the previous -[_state callback_](`m:gen_statem#state-callback`) returned and before any event -is delivered to the new [_state callback_](`m:gen_statem#state-callback`). See -[`Module:StateName/3`](`c:'StateName'/3`) and -[`Module:handle_event/4`](`c:handle_event/4`). Such a call can be repeated by -returning a [`repeat_state` ](`t:state_callback_result/1`)or -[`repeat_state_and_data` ](`t:state_callback_result/1`)tuple from the _state -callback_. - -If [`Module:callback_mode/0`](`c:callback_mode/0`) does not return such a list, -no _state enter calls_ are done. - -If [`Module:code_change/4`](`c: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_. +If [`Module:callback_mode/0`](`c:callback_mode/0`) returns +a list containing `state_enter`, the `gen_statem` engine will, +at every _state change_, that is; `NextState =/= CurrentState`, +call the [_state callback_](#state-callback) with arguments +`(enter, OldState, Data)` or `(enter, OldState, State, Data)`, +depending on the [_callback mode_](`t:callback_mode/0`). + +This may look like an event but is really a call performed +after the previous [_state callback_](#state-callback) returned, +and before any event is delivered to the new +[_state callback_](#state-callback). +See [`Module:StateName/3`](`c:'StateName'/3`) and +[`Module:handle_event/4`](`c:handle_event/4`). A _state enter call_ +may be repeated without doing a _state change_ by returning +a [`repeat_state`](`t:state_callback_result/2`) or +[`repeat_state_and_data`](`t:state_callback_result/2`) action +from the _state callback_. + +If [`Module:callback_mode/0`](`c:callback_mode/0`) does not return +a list containing `state_enter`, no _state enter calls_ are done. + +If [`Module:code_change/4`](`c: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, which may be seen as a state change from no state +to the initial state. In this case `OldState =:= State`, +which cannot happen for a subsequent state change, +but will happen when repeating the _state enter call_. """. +-doc #{ since => ~"OTP 19.2" }. -type state_enter() :: 'state_enter'. +%%---------------------- -doc """ -Transition options can be set by [actions](`t:action/0`) and modify the _state -transition_. The _state transition_ takes place when the -[_state callback_](`m:gen_statem#state-callback`) has processed an event and -returns. Here are the sequence of steps for a _state transition_: - -1. All returned [actions](`t:action/0`) are processed in order of appearance. In - this step all replies generated by any `t:reply_action/0` are sent. Other - actions set `t:transition_option/0`s that come into play in subsequent steps. -1. If [_state enter calls_ ](`t:state_enter/0`)are used, and either it is the - initial state or one of the callback results - [`repeat_state_and_data` ](`t:state_callback_result/1`)or - [`repeat_state_and_data` ](`t:state_callback_result/1`)is used the - `gen_statem` engine calls the current state callback with arguments - [`(enter, State, Data)`](`t:state_enter/0`) or - [`(enter, State, State, Data)`](`t:state_enter/0`) (depending on - [_callback mode_](`t:callback_mode/0`)) and when it returns starts again from - the top of this sequence. - -If [_state enter calls_ ](`t:state_enter/0`)are used, and the state changes the -`gen_statem` engine calls the new state callback with arguments -[`(enter, OldState, Data)`](`t:state_enter/0`) or -[`(enter, OldState, State, Data)`](`t:state_enter/0`) (depending on -[_callback mode_](`t:callback_mode/0`)) and when it returns starts again from -the top of this sequence. - -1. If `t:postpone/0` is `true`, the current event is postponed. -1. If this is a _state change_, the queue of incoming events is reset to start - with the oldest postponed. -1. All events stored with `t:action/0` `next_event` are inserted to be processed - before previously queued events. -1. Time-out timers `t:event_timeout/0`, `t:generic_timeout/0` and - `t:state_timeout/0` 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 `t:event_timeout/0` so a zero time event time-out is only -generated if the event queue is empty. - -A _state change_ cancels a `t:state_timeout/0` and any new transition option of -this type belongs to the new state, that is; a `t:state_timeout/0` applies to -the state the state machine enters. - -1. If there are enqueued events the - [_state callback_](`m:gen_statem#state-callback`) for the possibly new state - is called with the oldest enqueued event, and we start again from the top of - this sequence. -1. Otherwise the `gen_statem` goes into `receive` or hibernation (if - `t:hibernate/0` 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. When a new message arrives the - [_state callback_](`m:gen_statem#state-callback`) is called with the - corresponding event, and we start again from the top of this sequence. +_State transition_ options set by [actions](`t:action/0`). + +These determine what happens during the _state transition_. +The _state transition_ takes place when the +[_state callback_](#state-callback) has processed an event +and returns. Here are the sequence of steps for a _state transition_: + +1. All returned [actions](`t:action/0`) are processed + in order of appearance. In this step all replies generated + by any `t:reply_action/0` are sent. Other actions set + `t:transition_option/0`s that come into play in subsequent steps. + +2. If [_state enter calls_](`t:state_enter/0`) are used, + it is either the initial state or one of the callback results + [`repeat_state`](`t:state_callback_result/2`) or + [`repeat_state_and_data`](`t:state_callback_result/2`) is used the + `gen_statem` engine calls the current _state callback_ with arguments + [`(enter, State, Data)`](`t:state_enter/0`) or + [`(enter, State, State, Data)`](`t:state_enter/0`) (depending on + [_callback mode_](`t:callback_mode/0`)) and when it returns + starts again from the top of this sequence. + + If [_state enter calls_](`t:state_enter/0`) are used, + and the state changes, the `gen_statem` engine calls + the new _state callback_ with arguments + [`(enter, OldState, Data)`](`t:state_enter/0`) or + [`(enter, OldState, State, Data)`](`t:state_enter/0`) (depending on + [_callback mode_](`t:callback_mode/0`)) and when it returns + starts again from the top of this sequence. + +3. If `t:postpone/0` is `true`, the current event is postponed. + +4. If this is a _state change_, the queue of incoming events is reset + to start with the oldest postponed. + +5. All events stored with `t:action/0` `next_event` are inserted + to be processed before previously queued events. + +6. Time-out timers `t:event_timeout/0`, `t:generic_timeout/0` and + `t:state_timeout/0` 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 `t:event_timeout/0` so a zero time event time-out + is only generated if the event queue is empty. + + A _state change_ cancels a `t:state_timeout/0` and any new transition + option of this type belongs to the new state, that is; + a `t:state_timeout/0` applies to the state the state machine enters. + +7. If there are enqueued events the + [_state callback_](#state-callback) for the possibly + new state is called with the oldest enqueued event, and we start again + from the top of this sequence. + +8. Otherwise the `gen_statem` goes into `receive` or hibernation + (if `t:hibernate/0` 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. + When a new message arrives the + [_state callback_](#state-callback) is called with + the corresponding event, and we start again + from the top of this sequence. + +> #### Note {: .info } +> The behaviour of a zero time-out (a time-out with time `0`) +> differs subtly from Erlang's `receive ... after 0 ... end`. +> +> The latter receives one message if there is one, +> while using the `t:timeout_action/0` `{timeout, 0}` does not +> receive any external event. +> +> `m:gen_server`'s time-out works like Erlang's +> `receive ... after 0 ... end`, in contrast to `gen_statem`. """. -type transition_option() :: postpone() | hibernate() | event_timeout() | generic_timeout() | state_timeout(). + +%%---------------------- -doc """ -If `true`, postpones the current event and retries it after a _state change_ -(`NextState =/= State`). +Postpone an event to handle it later. + +If `true`, postpones the current event. +After a _state change_ (`NextState =/= State`), it is retried. """. -type postpone() :: %% If 'true' postpone the current event %% and retry it when the state changes (=/=) boolean(). + +%%---------------------- -doc """ -If `true`, hibernates the `gen_statem` by calling `proc_lib:hibernate/3` before -going into `receive` to wait for a new external event. +Hibernate the server process. + +If `true`, hibernates the `gen_statem` by calling `proc_lib:hibernate/3` +before going into `receive` to wait for a new external event. + +There is also a server start option +[`{hibernate_after, Timeout}`](`t:enter_loop_opt/0`) +for automatic hibernation. > #### Note {: .info } > -> If there are enqueued events to process when hibernation is requested, this is -> optimized by not hibernating but instead calling -> [`erlang:garbage_collect/0` ](`erlang:garbage_collect/0`)to simulate that the -> `gen_statem` entered hibernation and immediately got awakened by an enqueued -> event. +> If there are enqueued events to process when hibernation is requested, +> this is optimized by not hibernating but instead calling +> [`erlang:garbage_collect/0`](`erlang:garbage_collect/0`) to simulate, +> in a more effective way, that the `gen_statem` entered hibernation +> and immediately got awakened by an enqueued event. """. -type hibernate() :: %% If 'true' hibernate the server instead of going into receive boolean(). + +%%---------------------- -doc """ -Starts a timer set by `t:enter_action/0` `timeout`. When the timer expires an -event of `t:event_type/0` `timeout` will be generated. See -`erlang:start_timer/4` for how `Time` and [`Options`](`t:timeout_option/0`) are -interpreted. Future `erlang:start_timer/4` `Options` will not necessarily be -supported. +How long to wait for an event. + +Starts a timer set by `t:timeout_action/0` +`Time`, or `{timeout, Time, EventContent [, Options]}`. + +When the timer expires an event of `t:event_type/0` `timeout` +will be generated. See `erlang:start_timer/4` for how `Time` +and [`Options`](`t:timeout_option/0`) 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. -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 `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. -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, meaning that +whenever a callback is invoked that may want to cancel this time-out, +the timer is already cancelled or expired. -Note that it is not possible nor needed to cancel this time-out, as it is -cancelled automatically by any other event. +The timer `EventContent` can be updated with the +[`{timeout, update, NewEventContent}`](`t:timeout_update_action/0`) +action without affecting the time of expiry. """. -type event_timeout() :: %% Generate a ('timeout', EventContent, ...) event %% unless some other event is delivered Time :: timeout() | integer(). + +%%---------------------- -doc """ -Starts a timer set by `t:enter_action/0` `{timeout,Name}`. When the timer -expires an event of `t:event_type/0` `{timeout,Name}` will be generated. See -`erlang:start_timer/4` for how `Time` and [`Options`](`t:timeout_option/0`) are -interpreted. Future `erlang:start_timer/4` `Options` will not necessarily be -supported. +How long to wait for a named time-out event. + +Starts a timer set by `t:timeout_action/0` +`{{timeout, Name}, Time, EventContent [, Options]}`. + +When the timer expires an event of `t:event_type/0` `{timeout, Name}` +will be generated. See `erlang:start_timer/4` for how `Time` +and [`Options`](`t:timeout_option/0`) 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 `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. +If `Time` is relative and `0` no timer is actually started, +instead 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`. +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`. +It can also be cancelled more explicitly with the +[`{{timeout, Name}, cancel}`](`t:timeout_cancel_action/0`) action. + +The timer `EventContent` can be updated with the +[`{{timeout, Name}, update, NewEventContent}`](`t:timeout_update_action/0`) +action without affecting the time of expiry. """. +-doc #{ since => ~"OTP 20.0" }. -type generic_timeout() :: %% Generate a ({'timeout',Name}, EventContent, ...) event Time :: timeout() | integer(). --doc """ -Starts a timer set by `t:enter_action/0` `state_timeout`. When the timer expires -an event of `t:event_type/0` `state_timeout` will be generated. See -`erlang:start_timer/4` for how `Time` and [`Options`](`t:timeout_option/0`) 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`. +%%---------------------- +-doc """ +How long to wait in the current state. + +Starts a timer set by `t:timeout_action/0`, or +`{state_timeout, Time, EventContent [, Options]}`. + +When the timer expires an event of `t:event_type/0` `state_timeout` +will be generated. See `erlang:start_timer/4` for how `Time` +and [`Options`](`t:timeout_option/0`) are interpreted. Future +`erlang:start_timer/4` `Options` will not necessarily be supported. + +A _state change_ cancels this timer, if it is running. +That is, if the `t:timeout_action/0` that starts this timer +is part of a list of `t:action/0`s for a _state change_, +`NextState =/= CurrentState`, the timer runs in the **`NextState`**. + +If the state machine stays in that new state, now the current state, +the timer will run until it expires, which creates the time-out event. +If the state machine changes states from the now current state, +the timer is cancelled. During the _state change_ from +the now current state, a new _state time-out_ may be started +for the next **`NextState`**. + +If the `t:timeout_action/0` that starts this timer +is part of a list of `t:action/0`s for a _state transition_ +that is not a _state change_, the timer runs in the current state. + +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`. +It can also be cancelled more explicitly with +[`{state_timeout, cancel}`](`t:timeout_cancel_action/0`). + +The timer `EventContent` can be updated with the +[`{state_timeout, update, NewEventContent}`](`t:timeout_update_action/0`) +action without affecting the time of expiry. """. +-doc #{ since => ~"OTP 19.3" }. -type state_timeout() :: %% Generate a ('state_timeout', EventContent, ...) event %% unless the state is changed Time :: timeout() | integer(). + +%%---------------------- -doc """ -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` ](`erlang:start_timer/4`)for details. +Time-out timer start option, to select absolute time of expiry. + +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`](`erlang:start_timer/4`) for details. """. -type timeout_option() :: {abs,Abs :: boolean()}. +%%---------------------- -doc """ +Actions for a _state transition_, or when starting the server. + These _transition actions_ can be invoked by returning them from the -[_state callback_](`m:gen_statem#state-callback`) when it is called with an -[event](`t:event_type/0`), from [`Module:init/1`](`c:init/1`) or by giving them -to [`enter_loop/5,6`](`enter_loop/5`). +[_state callback_](#state-callback) when it is called +with an [event](`t:event_type/0`), from [`Module:init/1`](`c:init/1`) +or by passing them to [`enter_loop/4,5,6`](`enter_loop/6`). +They are **not allowed** from _state enter calls_. Actions are executed in the containing list order. -Actions that set [transition options ](`t:transition_option/0`)override any -previous of the same type, so the last in the containing list wins. For example, -the last `t:postpone/0` overrides any previous `t:postpone/0` in the list. +Actions that set [transition options](`t:transition_option/0`) +override any previous of the same type, so the last +in the containing list wins. For example, the last `t:postpone/0` +overrides any previous `t:postpone/0` in the list. + +- **`{postpone, Value}`** - Sets the + [`transition_option()` ](`t:transition_option/0`)`t:postpone/0` + for this _state transition_. This action is ignored when returned from + [`Module:init/1`](`c:init/1`) or passed to + [`enter_loop/4,5,6`](`enter_loop/6`), as there is no event to postpone + in those cases. -- **`postpone`** - Sets the - [`transition_option()` ](`t:transition_option/0`)`t:postpone/0` for this - _state transition_. This action is ignored when returned from - [`Module:init/1`](`c:init/1`) or given to [`enter_loop/5,6`](`enter_loop/5`), - as there is no event to postpone in those cases. + `postpone` is equivalent to `{postpone, true}`. -- **`next_event`** - This action does not set any - [`transition_option()` ](`t:transition_option/0`)but instead stores the - specified `EventType` and `EventContent` for insertion after all actions have - been executed. +- **`{next_event, EventType, EventContent}`** - This action + does not set any [`transition_option()`](`t:transition_option/0`) + but instead 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. + 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`](`t:event_type/0`) is to be used when you want to - reliably distinguish an event inserted this way from any external event. + An event of type [`internal`](`t:event_type/0`) should be used + when you want to reliably distinguish an event inserted this way + from any external event. -- **`change_callback_module`** - Changes the callback module to `NewModule` - which will be used when calling all subsequent - [state callbacks](`m:gen_statem#state-callback`). +- **`{change_callback_module, NewModule}`** {: #change_callback_module } - + Changes the callback module to `NewModule` which will be used + when calling all subsequent [state callbacks](#state-callback).\ + **Since OTP 22.3.** The `gen_statem` engine will find out the - [_callback mode_ ](`t:callback_mode/0`)of `NewModule` by calling - [`NewModule:callback_mode/0` ](`c:callback_mode/0`)before the next - [state callback](`m:gen_statem#state-callback`). - - Changing the callback module does not affect the _state transition_ in any - way, it only changes which module that handles the events. Be aware that all - relevant callback functions in `NewModule` such as the - [state callback](`m:gen_statem#state-callback`), + [_callback mode_](`t:callback_mode/0`) of `NewModule` by calling + [`NewModule:callback_mode/0`](`c:callback_mode/0`) before the next + [state callback](#state-callback). + + Changing the callback module does not affect the _state transition_ + in any way, it only changes which module that handles the events. + Be aware that all relevant callback functions in `NewModule` such as + the [state callback](#state-callback), [`NewModule:code_change/4`](`c:code_change/4`), - [`NewModule:format_status/1` ](`c:format_status/1`)and - [`NewModule:terminate/3` ](`c:terminate/3`)must be able to handle the state - and data from the old module. - -- **`push_callback_module`** - Pushes the current callback module to the top of - an internal stack of callback modules and changes the callback module to - `NewModule`. Otherwise like `{change_callback_module, NewModule}` above. - -- **`pop_callback_module`** - Pops the top module from the internal stack of - callback modules and changes the callback module to be the popped module. If - the stack is empty the server fails. Otherwise like - `{change_callback_module, NewModule}` above. + [`NewModule:format_status/1`](`c:format_status/1`) and + [`NewModule:terminate/3`](`c:terminate/3`) must be able to handle + the state and data from the old module. + +- **`{push_callback_module, NewModule}`** {: #push_callback_module } - + Pushes the current callback module to the top of an internal stack + of callback modules, and changes the callback module to `NewModule`. + Otherwise like `{change_callback_module, NewModule}` above.\ + **Since OTP 22.3.** + +- **`pop_callback_module`** {: #pop_callback_module } - + Pops the top module from the internal stack of callback modules + and changes the callback module to be the popped module. + If the stack is empty the server fails. + Otherwise like `{change_callback_module, NewModule}` above.\ + **Since OTP 22.3.** """. -type action() :: %% During a state change: @@ -788,7 +1099,7 @@ the last `t:postpone/0` overrides any previous `t:postpone/0` in the list. %% * All action()s are executed in order of apperance. %% * Postponing the current event is performed %% iff 'postpone' is 'true'. - %% * A state timeout is started iff 'timeout' is set. + %% * A state time-out is started iff 'timeout' is set. %% * Pending events are handled or if there are %% no pending events the server goes into receive %% or hibernate (iff 'hibernate' is 'true') @@ -810,51 +1121,69 @@ the last `t:postpone/0` overrides any previous `t:postpone/0` in the list. {'push_callback_module', NewModule :: module()} | 'pop_callback_module' | enter_action(). + +%%---------------------- -doc """ -These _transition actions_ can be invoked by returning them from the -[_state callback_](`m:gen_statem#state-callback`), from -[`Module:init/1`](`c:init/1`) or by giving them to -[`enter_loop/5,6`](`enter_loop/5`). +Actions for any callback: hibernate, time-outs or replies. + +These _transition actions_ are allowed when a `t:action/0` is allowed, +and also from a _state enter call_, and can be invoked +by returning them from the [_state callback_](#state-callback), from +[`Module:init/1`](`c:init/1`) or by passing them to +[`enter_loop/4,5,6`](`enter_loop/6`). Actions are executed in the containing list order. -Actions that set [transition options](`t:transition_option/0`) override any -previous of the same type, so the last in the containing list wins. For example, -the last `t:event_timeout/0` overrides any previous `t:event_timeout/0` in the -list. +Actions that set [transition options](`t:transition_option/0`) +override any previous of the same type, +so the last in the containing list wins. For example, +the last `t:event_timeout/0` overrides any previous +`t:event_timeout/0` in the list. -- **`hibernate`** - Sets the `t:transition_option/0` `t:hibernate/0` for this - _state transition_. +- **`{hibernate, Value}`** - Sets the `t:transition_option/0` + `t:hibernate/0` for this _state transition_. + + `hibernate` is equivalent to `{hibernate, true}`. """. -type enter_action() :: 'hibernate' | % Set the hibernate option {'hibernate', Hibernate :: hibernate()} | timeout_action() | reply_action(). + +%%---------------------- -doc """ + Event time-out, generic time-outs or state time-out. + These _transition actions_ can be invoked by returning them from the -[_state callback_](`m:gen_statem#state-callback`), from -[`Module:init/1`](`c:init/1`) or by giving them to -[`enter_loop/5,6`](`enter_loop/5`). +[_state callback_](#state-callback), from +[`Module:init/1`](`c:init/1`) or by passing them to +[`enter_loop/4,5,6`](`enter_loop/6`). These time-out actions sets time-out [transition options](`t:transition_option/0`). -- **`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_](`m:gen_statem#state-callback`) return value - `{next_state,NextState,NewData,Time}` allowed like for `gen_fsm`. +- **`Time`** - Short for `{timeout, Time, Time}`, that is, + the time-out message is the time-out time. This form exists to allow the + [_state callback_](#state-callback) return value + `{next_state, NextState, NewData, Time}` like in `gen_fsm`. -- **`timeout`** - Sets the `t:transition_option/0` `t:event_timeout/0` to `Time` - with `EventContent` and time-out options [`Options`](`t:timeout_option/0`). - -- **`{timeout,Name}`** - Sets the `t:transition_option/0` `t:generic_timeout/0` - to `Time` for `Name` with `EventContent` and time-out options +- **`{timeout, Time, EventContent [, Options]}`** - + Sets the `t:transition_option/0` `t:event_timeout/0` to `Time` + with `EventContent`, and time-out options [`Options`](`t:timeout_option/0`). -- **`state_timeout`** - Sets the `t:transition_option/0` `t:state_timeout/0` to - `Time` with `EventContent` and time-out options - [`Options`](`t:timeout_option/0`). +- **`{{timeout,Name}, Time, EventContent [, Options]}`** - + Sets the `t:transition_option/0` `t:generic_timeout/0` to `Time` + for time-out `Name` with `EventContent`, and time-out options + [`Options`](`t:timeout_option/0`).\ + **Since OTP 20.0**. + +- **`{state_timeout, Time, EventContent [, Options]}`** - + Sets the `t:transition_option/0` `t:state_timeout/0` to `Time` + with `EventContent`, and time-out options + [`Options`](`t:timeout_option/0`).\ + **Since OTP 19.3**. """. -type timeout_action() :: (Time :: event_timeout()) | % {timeout,Time,Time} @@ -880,61 +1209,89 @@ These time-out actions sets time-out Options :: (timeout_option() | [timeout_option()])} | timeout_cancel_action() | timeout_update_action(). + +%%---------------------- -doc """ -This is a shorter and clearer form of -[timeout_action() ](`t:timeout_action/0`)with `Time = infinity` which cancels a -time-out. +Clearer way to cancel a time-out than the original +setting it to 'infinity'. + +It has always been possible to cancel a time-out using +`t:timeout_action/0` with `Time = infinity`, since setting a new +time-out time overrides a running timer, and since setting the time +to `infinity` is optimized to not setting a timer (that never +will expire). Using this action shows the intention more clearly. """. +-doc #{ since => ~"OTP 22.1" }. -type timeout_cancel_action() :: {'timeout', 'cancel'} | {{'timeout', Name :: term()}, 'cancel'} | {'state_timeout', 'cancel'}. + +%%---------------------- -doc """ -Updates a time-out with a new `EventContent`. See -[timeout_action() ](`t:timeout_action/0`)for how to start a time-out. +Update the `EventContent` without affecting the time of expiry. + +Sets a new `EventContent` for a running time-out timer. +See [timeout_action()](`t:timeout_action/0`) for how to start a time-out. -If no time-out of the same type is active instead insert the time-out event just -like when starting a time-out with relative `Time = 0`. +If no time-out of this type is active, instead inserts +the time-out event just like when starting a time-out +with relative `Time = 0`. This is a time-out autostart with +immediate expiry, so there will be noise for example +if a generic time-out name was misspelled. """. +-doc #{ since => ~"OTP 22.1" }. -type timeout_update_action() :: {'timeout', 'update', EventContent :: event_content()} | {{'timeout', Name :: term()}, 'update', EventContent :: event_content()} | {'state_timeout', 'update', EventContent :: event_content()}. + +%%---------------------- -doc """ +Reply to a [`call/2,3`](`call/3`). + This _transition action_ can be invoked by returning it from the -[_state callback_](`m:gen_statem#state-callback`), from -[`Module:init/1`](`c:init/1`) or by giving it to -[`enter_loop/5,6`](`enter_loop/5`). +[_state callback_](#state-callback), from +[`Module:init/1`](`c:init/1`) or by passing it to +[`enter_loop/4,5,6`](`enter_loop/6`). -It does not set any [`transition_option()` ](`t:transition_option/0`)but instead -replies to a caller waiting for a reply in `call/2`. `From` must be the term -from argument [`{call,From}`](`t:event_type/0`) in a call to a -[_state callback_](`m:gen_statem#state-callback`). +It does not set any [`transition_option()`](`t:transition_option/0`) +but instead replies to a caller waiting for a reply in `call/3`. +`From` must be the term from argument [`{call, From}`](`t:event_type/0`) +in a call to a [_state callback_](#state-callback). Note that using this action from [`Module:init/1`](`c:init/1`) or -[`enter_loop/5,6`](`enter_loop/5`) would be weird on the border of witchcraft -since there has been no earlier call to a -[_state callback_](`m:gen_statem#state-callback`) in this server. +[`enter_loop/4,5,6`](`enter_loop/6`) would be weird +on the border of witchcraft since there has been no earlier call to a +[_state callback_](#state-callback) in this server. """. -type reply_action() :: {'reply', % Reply to a caller From :: from(), Reply :: term()}. -type init_result(StateType) :: init_result(StateType, term()). + +%%---------------------- -doc """ -For a succesful initialization, `State` is the initial `t:state/0` and `Data` -the initial server `t:data/0` of the `gen_statem`. +The return value from [`Module:init/1`](`c:init/1`). + +For a succesful initialization, `State` is the initial `t:state/0`, +and `Data` the initial server `t:data/0` of the `gen_statem`. The [`Actions`](`t:action/0`) are executed when entering the first [state](`t:state/0`) just as for a -[_state callback_](`m:gen_statem#state-callback`), except that the action +[_state callback_](#state-callback), except that the action `postpone` is forced to `false` since there is no event to postpone. -For an unsuccesful initialization, `{stop,Reason}`, `{error,Reason}` or `ignore` -should be used; see [`start_link/3,4`](`start_link/3`). +For an unsuccesful initialization, `{stop, Reason}`, `{error, Reason}`, +or `ignore` should be used; see [`start_link/3,4`](`start_link/3`). + +`{error, Reason}` has been allowed **since OTP 26.0**. -`{error,Reason}` was introduced in OTP 26.0. +The `{ok, ...}` tuples have existed **since OTP 19.1**, +before that they were not `ok` tagged. This was before +`gen_statem` replaced `gen_fsm` in OTP 20.0. """. -type init_result(StateType, DataType) :: {ok, State :: StateType, Data :: DataType} | @@ -945,18 +1302,27 @@ should be used; see [`start_link/3,4`](`start_link/3`). {'error', Reason :: term()}. %% Old, not advertised +-doc false. -type state_function_result() :: event_handler_result(state_name()). +-doc false. -type handle_event_result() :: event_handler_result(state()). -%% + -type state_enter_result(State) :: state_enter_result(State, term()). +%% +%%---------------------- -doc """ -`State` is the current state and it cannot be changed since the state callback -was called with a [_state enter call_](`t:state_enter/0`). +Return value from a [_state callback_](#state-callback) +after a _state enter call_. + +`State` is the current state and it cannot be changed +since the state callback was called with a +[_state enter call_](`t:state_enter/0`). -- **`next_state`** - The `gen_statem` does a state transition to `State`, which - has to be the current state, sets `NewData`, and executes all `Actions`. +- **`{next_state, State, NewData [, Actions]}`** - + The `gen_statem` does a state transition to `State`, which has to be + equal to the current state, sets `NewData`, and executes all `Actions`. """. -type state_enter_result(State, DataType) :: {'next_state', % {next_state,State,NewData,[]} @@ -966,18 +1332,27 @@ was called with a [_state enter call_](`t:state_enter/0`). State, NewData :: DataType, Actions :: [enter_action()] | enter_action()} | - state_callback_result(enter_action()). + state_callback_result(enter_action(), DataType). + -type event_handler_result(StateType) :: event_handler_result(StateType, term()). +%% +%%---------------------- -doc """ -`StateType` is `t:state_name/0` if [_callback mode_](`t:callback_mode/0`) is -`state_functions`, or `t:state/0` if [_callback mode_](`t:callback_mode/0`) is -`handle_event_function`. - -- **`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`. If `NextState =/= CurrentState` the _state transition_ is a _state - change_. +Return value from a [_state callback_](#state-callback) +after handling an event. + +`StateType` is `t:state_name/0` +if [_callback mode_](`t:callback_mode/0`) is `state_functions`, +or `t:state/0` +if [_callback mode_](`t:callback_mode/0`) is `handle_event_function`. + +- **`{next_state, NextState, NewData [, Actions]}`** - + The `gen_statem` does a _state transition_ to `NextState` + (which may be the same as the current state), sets `NewData` + as the current server `t:data/0`, and executes all `Actions`. + If `NextState =/= CurrentState` the _state transition_ + is a _state change_. """. -type event_handler_result(StateType, DataType) :: {'next_state', % {next_state,NextState,NewData,[]} @@ -987,38 +1362,45 @@ was called with a [_state enter call_](`t:state_enter/0`). NextState :: StateType, NewData :: DataType, Actions :: [action()] | action()} | - state_callback_result(action()). --type state_callback_result(ActionType) :: - state_callback_result(ActionType, term()). + state_callback_result(action(), DataType). + +%% +%%---------------------- -doc """ -`ActionType` is `t:enter_action/0` if the state callback was called with a -[_state enter call_](`t:state_enter/0`) and `t:action/0` if the state callback -was called with an event. +Return value from any [_state callback_](#state-callback). + +`ActionType` is `t:enter_action/0` if the state callback +was called with a [_state enter call_](`t:state_enter/0`), +and `t:action/0` if the state callback was called with an event. + +- **`{keep_state, NewData [, Actions]}`** - The same as + `{next_state, CurrentState, NewData [, Actions]}`. -- **`keep_state`** - The same as `{next_state,CurrentState,NewData,Actions}`. +- **`keep_state_and_data | {keep_state_and_data, Actions}`** - + The same as `{keep_state, CurrentData [, Actions]}`. -- **`keep_state_and_data`** - The same as `{keep_state,CurrentData,Actions}`. +- **`{repeat_state, NewData [, Actions]}`** - If the `gen_statem` + runs with [_state enter calls_](`t:state_enter/0`), + the _state enter call_ is repeated, see type `t:transition_option/0`. + Other than that `{repeat_state, NewData [, Actions]}` is the same as + `{keep_state, NewData [, Actions]}`. -- **`repeat_state`** - If the `gen_statem` runs with - [_state enter calls_](`t:state_enter/0`), the _state enter call_ is repeated, - see type `t:transition_option/0`, other than that `repeat_state` is the same - as `keep_state`. +- **`repeat_state_and_data | {repeat_state_and_data, Actions}`** - + The same as `{repeat_state, CurrentData [, Actions]}`. -- **`repeat_state_and_data`** - The same as - `{repeat_state,CurrentData,Actions}`. +- **`{stop, Reason [, NewData]}`** - Terminates the `gen_statem` + by calling [`Module:terminate/3`](`c:terminate/3`) + with `Reason` and `NewData`, if specified. An exit signal + with this reason is sent to linked processes and ports. -- **`stop`** - Terminates the `gen_statem` by calling - [`Module:terminate/3`](`c:terminate/3`) with `Reason` and `NewData`, if - specified. An exit signal with this reason is sent to linked processes and - ports. The default `Reason` is `normal`. +- **`stop`** - The same as `{stop, normal}`. -- **`stop_and_reply`** - Sends all `Replies`, then terminates the `gen_statem` - by calling [`Module:terminate/3`](`c:terminate/3`) with `Reason` and - `NewData`, if specified. An exit signal with this reason is sent to linked - processes and ports. +- **`{stop_and_reply, Reason, Replies [, NewData]}`** - + Sends all `Replies`, then terminates the `gen_statem` + like with `{stop, Reason [, NewData]}`. -All these terms are tuples or atoms and this property will hold in any future -version of `gen_statem`. +All these terms are tuples or atoms and will be so +in all future versions of `gen_statem`. """. -type state_callback_result(ActionType, DataType) :: {'keep_state', % {keep_state,NewData,[]} @@ -1054,35 +1436,45 @@ version of `gen_statem`. Replies :: [reply_action()] | reply_action(), NewData :: DataType}. +%%---------------------- -doc "An opaque request identifier. See `send_request/2` for details.". -opaque request_id() :: gen:request_id(). +%%---------------------- -doc """ -An opaque collection of request identifiers (`t:request_id/0`) where each -request identifier can be associated with a label chosen by the user. For more -information see `reqids_new/0`. +An opaque collection of request identifiers (`t:request_id/0`). + +Each request identifier can be associated with +a label chosen by the user. For more information see `reqids_new/0`. """. -opaque request_id_collection() :: gen:request_id_collection(). +%%---------------------- -doc """ +Response time-out for an asynchronous call. + Used to set a time limit on how long to wait for a response using either `receive_response/2`, `receive_response/3`, `wait_response/2`, or -`wait_response/3`. The time unit used is `millisecond`. Currently valid values: - -- **`0..4294967295`** - Timeout relative to current time in milliseconds. - -- **`infinity`** - Infinite timeout. That is, the operation will never time out. - -- **`{abs, Timeout}`** - An absolute - [Erlang monotonic time](`erlang:monotonic_time/1`) timeout in milliseconds. - That is, the operation will time out when - [`erlang:monotonic_time(millisecond)`](`erlang:monotonic_time/1`) returns a - value larger than or equal to `Timeout`. `Timeout` is not allowed to identify - a time further into the future than `4294967295` milliseconds. Identifying the - timeout using an absolute timeout value is especially handy when you have a - deadline for responses corresponding to a complete collection of requests - (`t:request_id_collection/0`) , since you do not have to recalculate the - relative time until the deadline over and over again. +`wait_response/3`. The time unit used is `millisecond`. + + Currently valid values: + +- **`0..4294967295`** - Time-out relative to current time in milliseconds. + +- **`infinity`** - Infinite time-out. That is, + the operation will never time out. + +- **`{abs, Timeout}`** - An absolute + [Erlang monotonic time](`erlang:monotonic_time/1`) + time-out in milliseconds. That is, the operation will time out when + [`erlang:monotonic_time(millisecond)`](`erlang:monotonic_time/1`) + returns a value larger than or equal to `Timeout`. + `Timeout` is not allowed to identify a time further into the future + than `4294967295` milliseconds. Specifying the time-out + using an absolute value is especially handy when you have + a deadline for responses corresponding to a complete collection + of requests (`t:request_id_collection/0`), since you do not have to + recalculate the relative time until the deadline over and over again. """. -type response_timeout() :: timeout() | {abs, integer()}. @@ -1091,61 +1483,74 @@ Used to set a time limit on how long to wait for a response using either %% the server is not running until this function has returned %% an {ok, ...} tuple. Thereafter the state callbacks are called %% for all events to this server. +%%---------------------- -doc """ -Whenever a `gen_statem` is started using [`start_link/3,4`](`start_link/3`), -[`start_monitor/3,4`](`start_monitor/3`), or [`start/3,4`](`start/3`), this -function is called by the new process to initialize the implementation state and -server data. +Initialize the state machine. + +Whenever a `gen_statem` is started using +[`start_link/3,4`](`start_link/3`), +[`start_monitor/3,4`](`start_monitor/3`), or +[`start/3,4`](`start/3`), 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 {: .info } > -> Note that if the `gen_statem` is started through `m:proc_lib` and -> [`enter_loop/4-6`](`enter_loop/4`), this callback will never be called. Since -> this callback is not optional it can in that case be implemented as: +> Note that if the `gen_statem` is started through `m:proc_lib` +> and [`enter_loop/4,5,6`](`enter_loop/6`), this callback +> will never be called. Since this callback is not optional +> it can in that case be implemented as: > > ```erlang > -spec init(_) -> no_return(). > init(Args) -> erlang:error(not_implemented, [Args]). > ``` """. --doc(#{since => <<"OTP 19.0">>}). +-doc #{ since => <<"OTP 19.0">> }. -callback init(Args :: term()) -> init_result(state()). %% This callback shall return the callback mode of the callback module. %% %% It is called once after init/0 and code_change/4 but before %% the first state callback StateName/3 or handle_event/4. +%%---------------------- -doc """ +Select the _callback mode_ and possibly +[_state enter calls_](`t:state_enter/0`). + This function is called by a `gen_statem` when it needs to find out the [_callback mode_](`t:callback_mode/0`) of the callback module. -The value is cached by `gen_statem` for efficiency reasons, so this function is only called -once after server start, after code change, and after changing the callback -module, but before the first [_state callback_](`m:gen_statem#state-callback`) -in the current callback module's code version is called. More occasions may be +The value is cached by `gen_statem` for efficiency reasons, +so this function is only called once after server start, +after code change, and after changing the callback module, +but before the first [_state callback_](#state-callback) +in the current callback module's code is called. More occasions may be added in future versions of `gen_statem`. -Server start happens either when [`Module:init/1`](`c:init/1`) returns or when -[`enter_loop/4-6`](`enter_loop/4`) is called. Code change happens when -[`Module:code_change/4`](`c:code_change/4`) returns. A change of the callback -module happens when a [_state callback_](`m:gen_statem#state-callback`) returns -any of the actions [`change_callback_module`](`t:action/0`), -[`push_callback_module`](`t:action/0`) or [`pop_callback_module`](`t:action/0`). +Server start happens either when [`Module:init/1`](`c:init/1`) +returns or when [`enter_loop/4,5,6`](`enter_loop/6`) is called. +Code change happens when [`Module:code_change/4`](`c:code_change/4`) +returns. A change of the callback module happens when +a [_state callback_](#state-callback) returns +any of the actions [`change_callback_module`](#push_callback_module), +[`push_callback_module`](#push_callback_module) or +[`pop_callback_module`](#pop_callback_module). -The `CallbackMode` is either just `t:callback_mode/0` or a list containing -`t:callback_mode/0` and possibly the atom [`state_enter`](`t:state_enter/0`). +The `CallbackMode` is either just `t:callback_mode/0` +or a list containing `t:callback_mode/0` and possibly +the atom [`state_enter`](`t:state_enter/0`). > #### Note {: .info } > -> If this function's body does not return an inline constant value the callback -> module is doing something strange. +> If this function's body does not return an inline constant value +> the callback module is doing something strange. """. --doc(#{since => <<"OTP 19.1">>}). +-doc #{ since => <<"OTP 19.1">> }. -callback callback_mode() -> callback_mode_result(). -%% Example state callback for StateName = 'state_name' +%% Example state callback for state name 'StateName' %% when callback_mode() =:= state_functions. %% %% In this mode all states has to be of type state_name() i.e atom(). @@ -1153,79 +1558,107 @@ The `CallbackMode` is either just `t:callback_mode/0` or a list containing %% Note that the only callbacks that have arity 3 are these %% StateName/3 callbacks and terminate/3, so the state name %% 'terminate' is unusable in this mode. --doc(#{equiv => handle_event/4, since => <<"OTP 19.0">>}). +%%---------------------- +-doc """ +[_State callback_](#state-callback) in +[_callback mode_](`t:callback_mode/0`) `state_functions`. + +State callback that handles all events in state `StateName`, where +[`StateName :: state_name()`](`t:state_name/0`) +has to be an `t:atom/0`. + +`StateName` cannot be `terminate` since that would collide +with the callback function [`Module:terminate/3`](`c:terminate/3`). + +Besides that when doing a [_state change_](#state-callback) +the next state always has to be an `t:atom/0`, +this function is equivalent to +[`Module:handle_event(​EventType, EventContent, +?FUNCTION_NAME, Data)`](`c:handle_event/4`), +which is the [_state callback_](#state-callback) in +[_callback mode_](`t:callback_mode/0`) `handle_event_function`. +""". +-doc #{ since => <<"OTP 19.0">> }. -callback 'StateName'( 'enter', OldStateName :: state_name(), data()) -> state_enter_result('state_name'); - (event_type(), - event_content(), - data()) -> + (EventType :: event_type(), + EventContent :: event_content(), + Data :: data()) -> event_handler_result(state_name()). -%% + %% State callback for all states %% when callback_mode() =:= handle_event_function. +%%---------------------- -doc """ -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_](`t:callback_mode/0`) is `state_functions`, -`Module:StateName/3` is called, and if it is `handle_event_function`, -[`Module:handle_event/4`](`c:handle_event/4`) is called. - -If `EventType` is [`{call,From}`](`t:event_type/0`), the caller waits for a -reply. The reply can be sent from this or from any other -[_state callback_](`m:gen_statem#state-callback`) by returning with -`{reply,From,Reply}` in [`Actions`](`t:action/0`), in -[`Replies`](`t:reply_action/0`), or by calling -[`reply(From, Reply)`](`reply/2`). - -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 `t:action/0`. - -When the `gen_statem` runs with [_state enter calls_](`t:state_enter/0`), these -functions are also called with arguments `(enter, OldState, ...)` during every -_state change_. In this case there are some restrictions on the -[actions](`t:enter_action/0`) that may be returned: `t:postpone/0` is not -allowed since a _state enter call_ is not an event so there is no event to -postpone, and [`{next_event,_,_}`](`t:action/0`) 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`](`erlang:throw/1`) to return the result, -which can be useful. For example to bail out with -[`throw(keep_state_and_data)`](`throw/1`) from deep within complex code that -cannot return `{next_state,State,Data}` because `State` or `Data` is no longer -in scope. +[_State callback_](#state-callback) in +[_callback mode_](`t:callback_mode/0`) `handle_event_function`. + +Whenever a `gen_statem` receives an event from [`call/2,3`](`call/3`), +`cast/2`, or as a normal process message, this function is called. + +If `EventType` is [`{call, From}`](`t:event_type/0`), +the caller waits for a reply. The reply can be sent from this +or from any other [_state callback_](#state-callback) +by returning with `{reply, From, Reply}` in [`Actions`](`t:action/0`), +in [`Replies`](`t:reply_action/0`), or by calling +[`reply(From, Reply)`](`reply/2`). + +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. + +For options that can be set and actions that can be done +by `gen_statem` after returning from this function, see `t:action/0`. + +When the `gen_statem` runs with [_state enter calls_](`t:state_enter/0`), +this function is also called with arguments `(enter, OldState, ...)` +during every _state change_. In this case there are some restrictions +on the [actions](`t:action/0`) that may be returned: + +- `t:postpone/0` is not allowed since a _state enter call_ + is not an event so there is no event to postpone. +- [`{next_event, _, _}`](`t:action/0`) is not allowed since + using _state enter calls_ should not affect how events + are consumed and produced. +- It is not allowed to 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`](`erlang:throw/1`) +to return the result, which can be useful. For example to bail out with +[`throw(keep_state_and_data)`](`throw/1`) from deep within complex code +that cannot return `{next_state, State, Data}` because `State` or `Data` +is no longer in scope. """. --doc(#{since => <<"OTP 19.0">>}). --callback handle_event( - 'enter', - OldState :: state(), - CurrentState, - data()) -> - state_enter_result(CurrentState); - (event_type(), - event_content(), - CurrentState :: state(), - data()) -> - event_handler_result(state()). % New state +-doc #{ since => <<"OTP 19.0">> }. +-callback handle_event('enter', OldState, CurrentState, Data) -> + state_enter_result(CurrentState) when + OldState :: state(), + CurrentState :: state(), + Data :: data(); + (EventType, EventContent, CurrentState, Data) -> + event_handler_result(state()) when + EventType :: event_type(), + EventContent :: event_content(), + CurrentState :: state(), + Data :: data(). +%% %% The following fun() should have the same type as the previous callback, %% but ... %% the type language cannot express a fun() with multiple clauses @@ -1244,42 +1677,48 @@ in scope. data()) -> term()). %% Clean up before the server terminates. +%%---------------------- -doc """ -This function is called by a `gen_statem` when it is about to terminate. It is -to be the opposite of [`Module:init/1`](`c:init/1`) and do any necessary -cleaning up. When it returns, the `gen_statem` terminates with `Reason`. The -return value is ignored. +Handle state machine termination. + +This function is called by a `gen_statem` when it is about to terminate. +It is to be the opposite of [`Module:init/1`](`c: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`](`t:state/0`) is the -internal state of the `gen_statem`. +`Reason` is a term denoting the stop reason and [`State`](`t:state/0`) +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`](`t:action/0`), `Reason` has the value specified in that tuple. If it -is because of a failure, `Reason` is the error reason. +`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`](`t:action/0`), `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: +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`. +- The `gen_statem` process 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. +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. +If the `gen_statem` process is not set up to trap +exit signals it is immediately terminated, just like any process, +and this function is not called. 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 `m:logger`. +`{shutdown, Term}`, the `gen_statem` is assumed to terminate +because of an error and an error report is issued using `m:logger`. -When the `gen_statem` process exits, an exit signal with the same reason is sent -to linked processes and ports. +When the `gen_statem` process exits, an exit signal +with the same reason is sent to linked processes and ports, +just as for any process. """. --doc(#{since => <<"OTP 19.0">>}). +-doc #{ since => <<"OTP 19.0">> }. -callback terminate( Reason :: 'normal' | 'shutdown' | {'shutdown', term()} | term(), @@ -1290,67 +1729,83 @@ to linked processes and ports. %% Note that the new code can expect to get an OldState from %% the old code version not only in code_change/4 but in the first %% state callback function called thereafter +%%---------------------- -doc """ -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`](`e:sasl:appup.md`) file. For more information, see +Update the [state](`t:state/0`) and [data](`t:data/0`) +after code change. + +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`](`e:sasl:appup.md`) file. For more information, see [OTP Design Principles](`e:system:release_handling.md#instr`). 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. +`{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. +`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 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. +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`](`e:sasl:appup.md`) 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_](`t:callback_mode/0`), or else the _callback mode_ after the -code change will not be honoured, most probably causing a server crash. +`Change = {advanced, Extra}` parameter +in the [`appup`](`e:sasl:appup.md`) 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_](`t:callback_mode/0`), or else the _callback mode_ +after the code change will not be honoured, most probably causing +a server crash. If the server changes callback module using any of the actions -[`change_callback_module`](`t:action/0`), [`push_callback_module`](`t:action/0`) -or [`pop_callback_module`](`t:action/0`), be aware that it is always the current -callback module that will get this callback call. That the current callback -module handles the current state and data update should be no surprise, but it -must be able to handle even parts of the state and data that it is not familiar -with, somehow. +[`change_callback_module`](#change_callback_module), +[`push_callback_module`](#push_callback_module), or +[`pop_callback_module`](#pop_callback_module), be aware that it is always +the current callback module that will get this callback call. +That the current callback module handles the current +state and data update should be no surprise, but it +must be able to handle even parts of the state and data +that it is not familiar with, somehow. In the supervisor -[child specification](`e:system:sup_princ.md#child-specification`) there is a -list of modules which is recommended to contain only the callback module. For a -`gen_statem` with multiple callback modules there is no real need to list all of -them, it may not even be possible since the list could change after code -upgrade. If this list would contain only the start callback module, as -recommended, what is important is to upgrade _that_ module whenever a -_synchronized code replacement_ is done. Then the release handler concludes that -an upgrade that upgrades _that_ module needs to suspend, code change, and resume -any server whose child specification declares that it is using _that_ module. +[child specification](`e:system:sup_princ.md#child-specification`) +there is a list of modules which is recommended to contain +only the callback module. For a `gen_statem` +with multiple callback modules there is no real need to list +all of them, it may not even be possible since the list could change +after code upgrade. If this list would contain only +the start callback module, as recommended, what is important +is to upgrade _that_ module whenever +a _synchronized code replacement_ is done. +Then the release handler concludes that +an upgrade that upgrades _that_ module needs to suspend, +code change, and resume any server whose child specification declares +that it is using _that_ module. And again; the _current_ callback module will get the [`Module:code_change/4`](`c:code_change/4`) call. > #### Note {: .info } > -> If a release upgrade/downgrade with `Change = {advanced,Extra}` specified in the -> `.appup` file is made when [`code_change/4`](`c:code_change/4`) is not -> implemented the process will crash with exit reason `undef`. +> If a release upgrade/downgrade with `Change = {advanced, Extra}` +> specified in the `.appup` file is made +> when [`Module:code_change/4`](`c:code_change/4`) is not implemented +> the process will crash with exit reason `undef`. """. --doc(#{since => <<"OTP 19.0">>}). +-doc #{ since => <<"OTP 19.0">> }. -callback code_change( OldVsn :: term() | {'down', term()}, OldState :: state(), @@ -1365,23 +1820,28 @@ And again; the _current_ callback module will get the %% StatusOption =:= 'terminate' it is just FormattedState. %% %% Deprecated +%%---------------------- -doc """ -This function is called by a `gen_statem` process in order to format/limit the -server state for debugging and logging purposes. +Format/limit the status value. + +This function is called by a `gen_statem` process +in in order to format/limit the server state +for debugging and logging purposes. It is called in the following situations: - One of [`sys:get_status/1,2`](`sys:get_status/1`) 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`](`sys:get_status/1`) return value and how its status -appears in termination error logs exports an instance of -[`format_status/2`](`c:format_status/2`), which returns a term describing the -current status of the `gen_statem`. +- 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`](`sys:get_status/1`) return value +and how its status appears in termination error logs, should export +an instance of [`Module:format_status/2`](`c:format_status/2`), +that returns a term describing the current status of the `gen_statem`. `PDict` is the current value of the process dictionary of the `gen_statem`. @@ -1389,32 +1849,35 @@ current status of the `gen_statem`. [`Data`](`t:data/0`) 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`](`sys:get_status/1`) 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`](`sys:get_status/1`) +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`](`sys:get_status/1`) 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`](`sys:get_status/1`) 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. +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. > #### Note {: .info } > -> 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}`. +> 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`](`c:format_status/2`) has crashed. +> 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 +> [`Module:format_status/2`](`c:format_status/2`) has crashed. """. -deprecated_callback({format_status, 2, "use format_status/1 instead"}). --doc(#{since => <<"OTP 19.0">>}). +-doc #{ since => <<"OTP 19.0">> }. -callback format_status( StatusOption, [ [{Key :: term(), Value :: term()}] | @@ -1423,25 +1886,17 @@ sensitive data from being written to the error log. Status :: term() when StatusOption :: 'normal' | 'terminate'. +%%---------------------- -doc """ -A map that describes the `gen_statem` status. +A map that describes the server's status. The keys are: - -- **`state`** - The current state of the `gen_statem` process. - -- **`data`** - The state data of the the `gen_statem` process. - -- **`reason`** - The reason that caused the state machine to terminate. - -- **`queue`** - The event queue of the `gen_statem` process. - -- **`postponed`** - The [postponed](`t:postpone/0`) events queue of the - `gen_statem` process. - -- **`timeouts`** - The active [time-outs](`t:timeout_action/0`) of the - `gen_statem` process. - +- **`state`** - The current state. +- **`data`** - The state data. +- **`reason`** - The reason that caused the process to terminate. +- **`queue`** - The event queue. +- **`postponed`** - The queue of [postponed](`t:postpone/0`) events. +- **`timeouts`** - The active [time-outs](`t:timeout_action/0`). - **`log`** - The [sys log](`sys:log/2`) of the server. New associations may be added to the status map without prior notice. @@ -1457,28 +1912,33 @@ New associations may be added to the status map without prior notice. %% Format the callback module status in some sensible that is %% often condensed way. +%%---------------------- -doc """ -This function is called by a `gen_statem` process in order to format/limit the -server state for debugging and logging purposes. +Format/limit the status value. + +This function is called by a `gen_statem` process +in order to format/limit the server status +for debugging and logging purposes. It is called in the following situations: -- [`sys:get_status/1,2`](`sys:get_status/1`) is invoked to get the `gen_statem` - status. +- [`sys:get_status/1,2`](`sys:get_status/1`) is invoked + to get the `gen_statem` status. - The `gen_statem` process terminates abnormally and logs an error. -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`](`sys:get_status/1`) return value and how its status -appears in termination error logs exports an instance of -[`format_status/1`](`c:format_status/1`), which will get a map `Status` that -describes the current states of the `gen_statem`, and shall return a map -`NewStatus` containing the same keys as the input map, but it may transform some -values. +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`](`sys:get_status/1`) +return value and how its status appears in termination error logs, +exports an instance of [`Module:format_status/1`](`c:format_status/1`), +which will get a map `Status` that describes the current state +of the `gen_statem`, and shall return a map `NewStatus` +containing the same keys as the input map, +but it may transform some values. One use case for this function is to return compact alternative state -representations to avoid having large state terms printed in log files. Another -is to hide sensitive data from being written to the error log. +representations to avoid having large state terms printed in log files. +Another is to hide sensitive data from being written to the error log. Example: @@ -1496,15 +1956,16 @@ format_status(Status) -> > #### Note {: .info } > -> 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}`. +> 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`](`c:format_status/2`) has crashed. +> 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 +> [`Module:format_status/2`](`c:format_status/2`) has crashed. """. --doc(#{since => <<"OTP 25.0">>}). +-doc #{ since => <<"OTP 25.0">> }. -callback format_status(Status) -> NewStatus when Status :: format_status(), NewStatus :: format_status(). @@ -1647,33 +2108,38 @@ event_type(Type) -> %%% API -doc """ -Name specification to use when starting a `gen_statem` server. See -`start_link/3` and `t:server_ref/0` below. +Server name specification: `local`, `global`, or `via` registered. + +Name specification to use when starting a `gen_statem` server. +See `start_link/3` and `t:server_ref/0` below. """. -type server_name() :: % Duplicate of gen:emgr_name() {'local', atom()} | {'global', GlobalName :: term()} | {'via', RegMod :: module(), Name :: term()}. +%%---------------------- -doc """ -Server specification to use when addressing a `gen_statem` server. +Server specification: `t:pid/0` or registered `t:server_name/0`. -See `call/2` and `t:server_name/0`. +To be used in [`call/2,3`](`call/3`) to specify the server. It can be: -- **`pid() | LocalName`** - The `gen_statem` is locally registered. +- **`pid() | LocalName`** - The `gen_statem` is locally registered. -- **`{Name,Node}`** - The `gen_statem` is locally registered on another node. +- **`{Name, Node}`** - The `gen_statem` is locally registered + on another node. -- **`{global,GlobalName}`** - The `gen_statem` is globally registered in - `m:global`. +- **`{global, GlobalName}`** - The `gen_statem` is globally registered + in `m: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 `m:global`. Thus, - `{via,global,GlobalName}` is the same as `{global,GlobalName}`. +- **`{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 `m:global`. + Thus, `{via, global, GlobalName}` is the same as `{global, GlobalName}`. """. -type server_ref() :: % What gen:call/3,4 and gen:stop/1,3 accepts pid() @@ -1682,41 +2148,53 @@ It can be: | {'global', GlobalName :: term()} | {'via', RegMod :: module(), ViaName :: term()}. +%%---------------------- -doc """ -Options that can be used when starting a `gen_statem` server through, for -example, `start_link/3`. +Server [start options](#start-options) for the +[`start/3,4`](`start/3`), [`start_link/3,4`](`start_link/3`), +and [`start_monitor/3,4`](`start_monitor/3`) functions. + +See [`start_link/4`](#start-options). """. -type start_opt() :: % Duplicate of gen:option() {'timeout', Time :: timeout()} - | {'spawn_opt', [proc_lib:spawn_option()]} + | {'spawn_opt', [proc_lib:start_spawn_option()]} | enter_loop_opt(). -%% --doc """ -Options that can be used when starting a `gen_statem` server through, -[`enter_loop/4-6`](`enter_loop/4`). -- **`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`). +%%---------------------- +-doc """ +Server [start options](#start-options) for the +[`enter_loop/4,5,6`](`enter_loop/6`), +[`start/3,4`](`start/3`), [`start_link/3,4`](`start_link/3`), +and [`start_monitor/3,4`](`start_monitor/3`), functions. -- **`debug`** - For every entry in `Dbgs`, the corresponding function in `m:sys` - is called. +See [`start_link/4`](#start-options). """. -type enter_loop_opt() :: % Some gen:option()s works for enter_loop/* {'hibernate_after', HibernateAfterTimeout :: timeout()} | {'debug', Dbgs :: [sys:debug_option()]}. +%%---------------------- -doc """ -Return value from the [`start/3,4`](`start/3`) and -[`start_link/3,4`](`start_link/3`) functions. +[Return value](#start-return-values) from the [`start/3,4`](`start/3`) +and [`start_link/3,4`](`start_link/3`) functions. + +See [`start_link/4`](#start-return-values). """. -type start_ret() :: % gen:start_ret() without monitor return {'ok', pid()} | 'ignore' | {'error', term()}. --doc "Return value from the [`start_monitor/3,4`](`start_monitor/3`) functions.". +%%---------------------- +-doc """ +Return value from the [`start_monitor/3,4`](`start_monitor/3`) functions. + +As for [`start_link/4`](#start-return-values) but a succesful return +wraps the process ID and the [monitor reference](`erlang:monitor/2`) in a +`{ok, {`[`pid()`](`t:pid/0`)`, `[`reference()`](`t:reference/0`)`}}` +tuple. +""". -type start_mon_ret() :: % gen:start_ret() with only monitor return {'ok', {pid(),reference()}} | 'ignore' @@ -1726,11 +2204,14 @@ Return value from the [`start/3,4`](`start/3`) and %% Start a state machine +%%---------------------- -doc """ -Equivalent to `start/4` except that the `gen_statem` process is not -registered with any [name service](`t:server_name/0`). +Start a server, neither linked nor registered. + +Equivalent to `start/4` except that the `gen_statem` process +is not registered with any [name service](`t:server_name/0`). """. --doc(#{since => <<"OTP 19.0">>}). +-doc #{ since => <<"OTP 19.0">> }. -spec start( Module :: module(), Args :: term(), Opts :: [start_opt()]) -> start_ret(). @@ -1740,15 +2221,19 @@ start(Module, Args, Opts) start(Module, Args, Opts) -> error(badarg, [Module, Args, Opts]). %% +%%---------------------- -doc """ -Creates a standalone `gen_statem` process according to OTP design principles -(using `m: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. +Start a server, registered but not linked. -For a description of arguments and return values, see -[`start_link/4`](`start_link/4`). +Creates a standalone `gen_statem` process according to +OTP design principles (using `m: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/4`](`start_link/4`). """. --doc(#{since => <<"OTP 19.0">>}). +-doc #{ since => <<"OTP 19.0">> }. -spec start( ServerName :: server_name(), Module :: module(), Args :: term(), Opts :: [start_opt()]) -> @@ -1760,11 +2245,14 @@ start(ServerName, Module, Args, Opts) -> error(badarg, [ServerName, Module, Args, Opts]). %% Start and link to a state machine +%%---------------------- -doc """ -Equivalent to `start_link/4` except that the `gen_statem` process is not -registered with any [name service](`t:server_name/0`). +Start a server, linked but not registered. + +Equivalent to `start_link/4` except that the `gen_statem` process +is not registered with any [name service](`t:server_name/0`). """. --doc(#{since => <<"OTP 19.0">>}). +-doc #{ since => <<"OTP 19.0">> }. -spec start_link( Module :: module(), Args :: term(), Opts :: [start_opt()]) -> start_ret(). @@ -1774,18 +2262,22 @@ start_link(Module, Args, Opts) start_link(Module, Args, Opts) -> error(badarg, [Module, Args, Opts]). %% +%%---------------------- -doc """ -Creates a `gen_statem` process according to OTP design principles (using -`m:proc_lib` primitives) that is spawned as 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. +Start a server, linked and registered. + +Creates a `gen_statem` process according to OTP design principles +(using `m:proc_lib` primitives) that is spawned 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`](`c:init/1`) to initialize the -server. To ensure a synchronized startup procedure, `start_link/3,4` does not -return until [`Module:init/1`](`c:init/1`) has returned or failed. +The spawned `gen_statem` process calls [`Module:init/1`](`c:init/1`) +to initialize the server. To ensure a synchronized startup procedure, +`start_link/3,4` does not return until [`Module:init/1`](`c:init/1`) +has returned or failed. -`ServerName` specifies the `t:server_name/0` to register for the `gen_statem` -process. If the `gen_statem` process is started with +`ServerName` specifies the `t:server_name/0` to register +for the `gen_statem` process. If the `gen_statem` process is started with [`start_link/3`](`start_link/3`), no `ServerName` is provided and the `gen_statem` process is not registered. @@ -1794,76 +2286,95 @@ process. If the `gen_statem` process is started with `Args` is an arbitrary term that is passed as the argument to [`Module:init/1`](`c:init/1`). -- If option [`{timeout,Time}` ](`t:start_opt/0`)is present in `Opts`, the - `gen_statem` process is allowed to spend `Time` milliseconds initializing or - it is terminated and the start function returns - [`{error,timeout}`](`t:start_ret/0`). -- If option [`{hibernate_after,HibernateAfterTimeout}` ](`t:enter_loop_opt/0`)is - present, 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`). -- If option [`{debug,Dbgs}` ](`t:enter_loop_opt/0`)is present in `Opts`, - debugging through `m:sys` is activated. -- If option [`{spawn_opt,SpawnOpts}` ](`t:start_opt/0`)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 {: .info } -> -> Using spawn option `monitor` is not allowed, it causes this function to fail -> with reason `badarg`. - -If the `gen_statem` process is successfully created and initialized, this -function returns [`{ok,Pid}`](`t:start_ret/0`), where `Pid` is the `t:pid/0` of -the `gen_statem` process. If a process with the specified `ServerName` exists -already, this function returns -[`{error,{already_started,OtherPid}}`](`t:start_ret/0`), where `OtherPid` is the -`t:pid/0` of that process, and the `gen_statem` process exits with reason -`normal` before calling [`Module:init/1`](`c:init/1`). - -If [`Module:init/1`](`c:init/1`) does not return within the -[start timeout](`t:start_opt/0`), the `gen_statem` process is killed with -[`exit(_, kill)`](`erlang:exit/2`), and this function returns -[`{error,timeout}`](`t:start_ret/0`). - -This function returns [`{error,Reason}`](`t:start_ret/0`) if -[`Module:init/1`](`c:init/1`) returns [`{stop,Reason}`](`t:init_result/1`) or -[`{error,Reason}`](`t:init_result/1`), or fails with reason `Reason`. This -function returns [`ignore`](`t:start_ret/0`) if [`Module:init/1`](`c:init/1`) -returns [`ignore`](`t:init_result/1`). In these cases the `gen_statem` process -exits with reason `Reason`, except when [`Module:init/1`](`c:init/1`) returns -`ignore` or `{error,_}`; then the `gen_statem` process exits with reason -`normal`. - -If `start_link/3,4` returns `ignore` or `{error,_}`, the started `gen_statem` -process has terminated. If an `'EXIT'` message was delivered to the calling -process (due to the process link), that message has been consumed. +#### Start options in `Opts` {: #start-options } + +- **[`{timeout, Time}`](`t:start_opt/0`)** - The `gen_statem` process + is allowed to spend `Time` milliseconds before returning + from [`Module:init/1`](`c:init/1`), or it is terminated + and this start function returns [`{error, timeout}`](`t:start_ret/0`). + +- **[`{spawn_opt, SpawnOpts}`](`t:start_opt/0`)** - + `SpawnOpts` is passed as option list to `erlang:spawn_opt/2`, + which is used to spawn the `gen_statem` process. + See `t:proc_lib:start_spawn_option/0`. + + > #### Note {: .info } + > + > Using spawn option `monitor` is not allowed, + > it causes a `badarg` failure. + +- **[`{hibernate_after, HibernateAfterTimeout}`](`t:enter_loop_opt/0`)** - + When the `gen_statem` process waits for a message, if no message + is received within `HibernateAfterTimeout` milliseconds, + the process goes into hibernation automatically + (by calling `proc_lib:hibernate/3`). This option is also + allowed for the [`enter_loop`](`enter_loop/6`) functions. + + Note that there is also a `t:transition_option/0` + to explicitly hibernate the server from a + [_state callback_](#state-callback). + +- **[`{debug, Dbgs}`](`t:enter_loop_opt/0`)** - Activates + debugging through `m:sys`. For every entry in `Dbgs`, + the corresponding function in `m:sys` is called. This option is also + allowed for the [`enter_loop`](`enter_loop/6`) functions. + +#### Return values {: #start-return-values } + +- **[`{ok, Pid}`](`t:start_ret/0`)** - + The `gen_statem` server process was successfully created and + initialized. `Pid` is the `t:pid/0` of the process. + +- **[`ignore`](`t:start_ret/0`)** - + [`Module:init/1`](`c:init/1`) returned [`ignore`](`t:init_result/1`). + The `gen_statem` process has exited with reason `normal`. + +- **[`{error, {already_started, OtherPid}}`](`t:start_ret/0`)** - + A process with the specified [`ServerName`](`t:server_name/0`) + already exists. `OtherPid` is the `t:pid/0` of that process. + The `gen_statem` process exited with reason `normal` + before calling [`Module:init/1`](`c:init/1`). + +- **[`{error, timeout}`](`t:start_ret/0`)** - + [`Module:init/1`](`c:init/1`) did not return within + the [start time-out](`t:start_opt/0`). The `gen_statem` process + has been killed with [`exit(_, kill)`](`erlang:exit/2`). + +- **[`{error, Reason}`](`t:start_ret/0`)** + + Either [`Module:init/1`](`c:init/1`) returned + [`{stop, Reason}`](`t:init_result/1`) or failed with reason `Reason`, + The `gen_statem` process exited with reason `Reason`. + + Or [`Module:init/1`](`c:init/1`) returned + [`{error, Reason}`](`t:init_result/1`). + The `gen_statem` process did a graceful exit with reason `normal`. + +If the return value is `ignore` or `{error, _}`, the started +`gen_statem` process has terminated. If an `'EXIT'` message +was delivered to the calling process (due to the process link), +that message has been consumed. > #### Warning {: .warning } > > Before OTP 26.0, if the started `gen_statem` process returned e.g. -> `{stop,Reason}` from [`Module:init/1`](`c:init/1`), this function could return -> `{error,Reason}` _before_ the started `gen_statem` process had terminated so -> starting again might fail because VM resources such as the registered name was -> not yet unregistered, and an `'EXIT'` message could arrive later to the +> `{stop, Reason}` from [`Module:init/1`](`c:init/1`), +> this function could return `{error, Reason}` +> _before_ the started `gen_statem` process had terminated, +> so starting again might fail because VM resources +> such as the registered name was not yet unregistered, +> and an `'EXIT'` message could arrive later to the > process calling this function. > > But if the started `gen_statem` process instead failed during -> [`Module:init/1`](`c:init/1`), a process link `{'EXIT',Pid,Reason}` message -> caused this function to return `{error,Reason}` so the `'EXIT'` message had -> been consumed and the started `gen_statem` process had terminated. +> [`Module:init/1`](`c:init/1`), a process link `{'EXIT', Pid, Reason}` +> message caused this function to return `{error, Reason}`, +> so the `'EXIT'` message had been consumed and +> the started `gen_statem` process had terminated. > -> Since it was impossible to tell the difference between these two cases from -> `start_link/3,4`'s return value, this inconsistency was cleaned up in OTP -> 26.0. - -The difference between returning `{stop,_}` and `{error,_}` from -[`Module:init/1`](`c:init/1`), is that `{error,_}` results in a graceful -("silent") termination since the `gen_statem` process exits with reason -`normal`. +> Since it was impossible to tell the difference between these two cases +> from `start_link/3,4`'s return value, this inconsistency +> was cleaned up in OTP 26.0. """. --doc(#{since => <<"OTP 19.0">>}). +-doc #{ since => <<"OTP 19.0">> }. -spec start_link( ServerName :: server_name(), Module :: module(), Args :: term(), Opts :: [start_opt()]) -> @@ -1875,11 +2386,14 @@ start_link(ServerName, Module, Args, Opts) -> error(badarg, [ServerName, Module, Args, Opts]). %% Start and monitor a state machine +%%---------------------- -doc """ -Equivalent to `start_monitor/4` except that the `gen_statem` process is not -registered with any [name service](`t:server_name/0`). +Start a server, monitored but neither linked nor registered. + +Equivalent to `start_monitor/4` except that the `gen_statem` +process is not registered with any [name service](`t:server_name/0`). """. --doc(#{since => <<"OTP 23.0">>}). +-doc #{ since => <<"OTP 23.0">> }. -spec start_monitor( Module :: module(), Args :: term(), Opts :: [start_opt()]) -> start_mon_ret(). @@ -1889,21 +2403,27 @@ start_monitor(Module, Args, Opts) start_monitor(Module, Args, Opts) -> error(badarg, [Module, Args, Opts]). %% +%%---------------------- -doc """ -Creates a standalone `gen_statem` process according to OTP design principles -(using `m:proc_lib` primitives) and atomically sets up a monitor to the newly -created process. As it does not get linked to the calling process, this start -function cannot be used by a supervisor to start a child. +Start a server, monitored and registered, but not linked. + +Creates a standalone `gen_statem` process according to +OTP design principles (using `m:proc_lib` primitives), +and atomically sets up a monitor to the newly created process. + +As the started process 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/3`). Note that the return value on successful -start differs from `start_link/3,4`. `start_monitor/3,4` will return -`{ok,{Pid,Mon}}` where `Pid` is the process identifier of the process, and `Mon` -is a reference to the monitor set up to monitor the process. If the start is not -successful, the caller will be blocked until the `DOWN` message has been -received and removed from the message queue. +[`start_link/4`](`start_link/4`), but note that for a succesful start +the return value differs since this function returns `{ok, {Pid, Mon}}`, +where `Pid` is the process identifier of the process, +and `Mon` is the monitor reference for the process. +If the start is not successful, the caller will be blocked +until the `DOWN` message has been received +and removed from the caller's message queue. """. --doc(#{since => <<"OTP 23.0">>}). +-doc #{ since => <<"OTP 23.0">> }. -spec start_monitor( ServerName :: server_name(), Module :: module(), Args :: term(), Opts :: [start_opt()]) -> @@ -1915,32 +2435,38 @@ start_monitor(ServerName, Module, Args, Opts) -> error(badarg, [ServerName, Module, Args, Opts]). %% Stop a state machine +%%---------------------- -doc #{ equiv => stop(ServerRef, normal, infinity) }. --doc(#{since => <<"OTP 19.0">>}). +-doc #{ since => <<"OTP 19.0">> }. -spec stop(ServerRef :: server_ref()) -> ok. stop(ServerRef) -> gen:stop(ServerRef). %% +%%---------------------- -doc """ +Stop a server. + Orders the `gen_statem` [`ServerRef`](`t:server_ref/0`) to exit with the specified `Reason` and waits for it to terminate. The `gen_statem` calls [`Module:terminate/3`](`c: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 `m:logger`. An exit signal with the same reason is +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 `m:logger`. An exit signal with the same reason is sent to linked processes and ports. 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, the -call exits the calling process with reason `timeout`. +`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, +the call exits the calling process with reason `timeout`. -If the process does not exist, the call exits the calling process with reason -`noproc`, and with reason `{nodedown,Node}` if the connection fails to the -remote `Node` where the server runs. +If the process does not exist, the call exits the calling process +with reason `noproc`, or with reason `{nodedown, Node}` +if the connection fails to the remote `Node` where the server runs. """. --doc(#{since => <<"OTP 19.0">>}). +-doc #{ since => <<"OTP 19.0">> }. -spec stop( ServerRef :: server_ref(), Reason :: term(), @@ -1949,16 +2475,19 @@ stop(ServerRef, Reason, Timeout) -> gen:stop(ServerRef, Reason, Timeout). %% Send an event to a state machine that arrives with type 'event' +%%---------------------- -doc """ -Sends an asynchronous event to the `gen_statem` [`ServerRef`](`t:server_ref/0`) -and returns `ok` immediately, ignoring if the destination node or `gen_statem` -does not exist. +Cast an event to a server. + +Sends an asynchronous `cast` event to the `gen_statem` +[`ServerRef`](`t:server_ref/0`) and returns `ok` immediately, +ignoring if the destination node or `gen_statem` does not exist. The `gen_statem` calls the -[_state callback_](`m:gen_statem#state-callback`) with `t:event_type/0` `cast` -and event content `Msg`. +[_state callback_](#state-callback) +with `t:event_type/0` `cast` and event content `Msg`. """. --doc(#{since => <<"OTP 19.0">>}). +-doc #{ since => <<"OTP 19.0">> }. -spec cast(ServerRef :: server_ref(), Msg :: term()) -> ok. cast(ServerRef, Msg) when is_pid(ServerRef) -> send(ServerRef, wrap_cast(Msg)); @@ -1981,44 +2510,54 @@ cast({Name,Node} = ServerRef, Msg) when is_atom(Name), is_atom(Node) -> %% Call a state machine (synchronous; a reply is expected) that %% arrives with type {call,From} --doc(#{equiv => call(ServerRef, Request, infinity)}). --doc(#{since => <<"OTP 19.0">>}). +%%---------------------- +-doc #{ equiv => call(ServerRef, Request, infinity) }. +-doc #{ since => <<"OTP 19.0">> }. -spec call(ServerRef :: server_ref(), Request :: term()) -> Reply :: term(). call(ServerRef, Request) -> call(ServerRef, Request, infinity). %% +%%---------------------- -doc """ -Makes a synchronous call to the `gen_statem` [`ServerRef`](`t:server_ref/0`) by -sending a request and waiting until its reply arrives. - -The `gen_statem` calls the [_state callback_](`m:gen_statem#state-callback`) -with `t:event_type/0` `{call,From}` and event content `Request`. - -A `Reply` is generated when a [_state callback_](`m:gen_statem#state-callback`) -returns with `{reply,From,Reply}` as one `t:action/0`, and that `Reply` becomes -the return value of this function. +Call a server: send request and wait for response. -`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. +Makes a synchronous call to the `gen_statem` +[`ServerRef`](`t:server_ref/0`) by sending a request +and waiting until the response arrives. -Previous issue with late replies that could occur when having network issues or -using `dirty_timeout` is now prevented by use of +[](){: #call-reply } +The `gen_statem` calls the +[_state callback_](#state-callback) +with `t:event_type/0` `{call, From}` and event content `Request`. + +The server's reply is sent from a [_state callback_](#state-callback), +by returning a [_transition action_](`t:action/0`) `{reply, From, Reply}`, +calling [`reply(Replies)`](`reply/1`) with such a reply action +in the `Replies` list, or calling [`reply(From, Reply)`](`reply/2`). + +`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. + +Previous issue with late replies that could occur +when having network issues or using `dirty_timeout` +is now prevented by use of [_process aliases_](`e:system:ref_man_processes.md#process-aliases`). -`{clean_timeout, T}` and `{dirty_timeout, T}` therefore no longer serves any -purpose and will work the same as `Timeout` while all of them also being equally -efficient. - -The call can also fail, for example, if the `gen_statem` dies before or during -this function call. - -When this call fails it [exits](`erlang:exit/1`) the calling process. The exit -term is on the form `{Reason, Location}` where -`Location = {gen_statem,call,ArgList}`. See -[`gen_server:call/3` ](`gen_server:call/3`)that has a description of relevant -values for the `Reason` in the exit term. +`{clean_timeout, T}` and `{dirty_timeout, T}` therefore +no longer serves any purpose and will work the same as `Timeout` +while all of them also being equally efficient. + +The call can also fail, for example, if the `gen_statem` +dies before or during this function call. + +When this call fails it [exits](`erlang:exit/1`) +the calling process. The exit term is on the form +`{Reason, Location}` where `Location = {gen_statem, call, ArgList}`. +See [`gen_server:call/3`](`gen_server:call/3`) that has a description +of relevant values for the `Reason` in the exit term. """. --doc(#{since => <<"OTP 19.0">>}). +-doc #{ since => <<"OTP 19.0">> }. -spec call( ServerRef :: server_ref(), Request :: term(), @@ -2038,59 +2577,69 @@ call(ServerRef, Request, {_, _} = Timeout) -> call(ServerRef, Request, Timeout) -> call(ServerRef, Request, Timeout, Timeout). +%%---------------------- -doc """ -Sends an asynchronous `call` request `Request` to the `gen_statem` process -identified by `ServerRef` and returns a request identifier `ReqId`. - -The return value `ReqId` shall later be used with `receive_response/2`, `wait_response/2`, -or `check_response/2` to fetch the actual result of the request. Besides passing -the request identifier directly to these functions, it can also be saved in a -request identifier collection using `reqids_add/3`. Such a collection of request -identifiers can later be used in order to get one response corresponding to a -request in the collection by passing the collection as argument to -`receive_response/3`, `wait_response/3`, or `check_response/3`. If you are about -to save the request identifier in a request identifier collection, you may want -to consider using `send_request/4` instead. +Send an asynchronous `call` request. + +Sends `Request` to the `gen_statem` process identified by `ServerRef` +and returns a request identifier `ReqId`. + +The return value `ReqId` shall later be used with `receive_response/2`, +`wait_response/2`, or `check_response/2` to fetch the actual result +of the request. Besides passing the request identifier directly +to these functions, it can also be stored in +a request identifier collection using `reqids_add/3`. +Such a collection of request identifiers can later be used +in order to get one response corresponding to a +request in the collection by passing the collection +as argument to `receive_response/3`, `wait_response/3`, +or `check_response/3`. If you are about to store the request identifier +in a collection, you may want to consider using `send_request/4` instead. The call -`gen_statem:wait_response(gen_statem:send_request(ServerRef,Request), Timeout)` -can be seen as equivalent to -[`gen_statem:call(Server,Request,Timeout)`](`call/3`), ignoring the error -handling. - -The `gen_statem` calls the [_state callback_](`m:gen_statem#state-callback`) -with `t:event_type/0` `{call,From}` and event content `Request`. - -A `Reply` is generated when a [_state callback_](`m:gen_statem#state-callback`) -returns with `{reply,From,Reply}` as one `t:action/0`, and that `Reply` becomes -the return value of [`receive_response/1,2`](`receive_response/2`), -[`wait_response/1,2`](`wait_response/2`), or `check_response/2` function. +`gen_statem:wait_response(gen_statem:send_request(ServerRef, +Request), Timeout)` can be seen as equivalent to +[`gen_statem:call(Server, Request, Timeout)`](`call/3`), +ignoring the error handling. + +See [`call/3`](#call-reply) about how the request is handled +and the `Reply` is sent by the `gen_statem` server. + +The server's `Reply` is returned by one of the +[`receive_response/1,2`](`receive_response/2`), +[`wait_response/1,2`](`wait_response/2`), +or `check_response/2` functions. """. --doc(#{since => <<"OTP 23.0">>}). +-doc #{ since => <<"OTP 23.0">> }. -spec send_request(ServerRef::server_ref(), Request::term()) -> ReqId::request_id(). -send_request(Name, Request) -> +send_request(ServerRef, Request) -> try - gen:send_request(Name, '$gen_call', Request) + gen:send_request(ServerRef, '$gen_call', Request) catch error:badarg -> - error(badarg, [Name, Request]) + error(badarg, [ServerRef, Request]) end. +%%---------------------- -doc """ -Sends an asynchronous `call` request `Request` to the `gen_statem` process -identified by `ServerRef`. The `Label` will be associated with the request -identifier of the operation and added to the returned request identifier -collection `NewReqIdCollection`. The collection can later be used in order to -get one response corresponding to a request in the collection by passing the -collection as argument to `receive_response/3`, `wait_response/3`, or, -`check_response/3`. +Send an asynchronous `call` request and add it +to a request identifier collection. + +Sends `Request` to the `gen_statem` process identified by `ServerRef`. +The `Label` will be associated with the request identifier +of the operation and added to the returned request identifier collection +`NewReqIdCollection`. The collection can later be used in order to +get one response corresponding to a request in the collection +by passing the collection as argument to `receive_response/3`, +`wait_response/3`, or `check_response/3`. The same as calling -[`gen_statem:reqids_add`](`reqids_add/3`)([`statem:send_request`](`send_request/2`)`(ServerRef, Request), Label, ReqIdCollection)`, -but calling [`send_request/4`](`send_request/4`) is slightly more efficient. +[`reqids_add(​`](`reqids_add/3`)[`send_request(ServerRef, Request), +`](`send_request/2`)[`Label, ReqIdCollection)`](`reqids_add/3`), +but slightly more efficient. """. --doc(#{since => <<"OTP 25.0">>}). +-doc #{ since => <<"OTP 25.0">> }. -spec send_request(ServerRef::server_ref(), Request::term(), Label::term(), @@ -2106,8 +2655,9 @@ send_request(ServerRef, Request, Label, ReqIdCol) -> end. --doc #{ equiv => receive_response(ReqId, infinity) }. --doc(#{since => <<"OTP 23.0">>}). +%%---------------------- +-doc #{ equiv => wait_response(ReqId, infinity) }. +-doc #{ since => <<"OTP 23.0">> }. -spec wait_response(ReqId) -> Result when ReqId :: request_id(), Response :: {reply, Reply::term()} @@ -2117,31 +2667,33 @@ send_request(ServerRef, Request, Label, ReqIdCol) -> wait_response(ReqId) -> wait_response(ReqId, infinity). +%%---------------------- -doc """ -Wait for a response corresponding to the request identifier `ReqId`. The request -must have been made by `send_request/2` to the `gen_statem` process. This -function must be called from the same process from which `send_request/2` was -made. +Wait for a request response. -`WaitTime` specifies how long to wait for a reply. If no reply is received -within the specified time, the function returns `timeout` and no cleanup is -done, and thus the function can be invoked repeatedly until a reply is returned. +Waits for the response to the request identifier `ReqId`. The request +must have been made by `send_request/2` to the `gen_statem` process. +This function must be called from the same process from which +`send_request/2` was called. -The return value `Reply` is generated when a -[_state callback_](`m:gen_statem#state-callback`) returns with -`{reply,From,Reply}` as one `t:action/0`, and that `Reply` becomes the return -value of this function. +`WaitTime` specifies how long to wait for a reply. +If no reply is received within the specified time, +the function returns `timeout` and no cleanup is done, +Thus the function can be invoked repeatedly until a reply is returned. -The function returns an error if the `gen_statem` dies before or during this -function call. +See [`call/3`](#call-reply) about how the request is handled +and the `Reply` is sent by the `gen_statem` server. + +If the `gen_statem` server process is dead or dies while +this function waits for the reply, it returns an `error` return +with the exit `Reason`. The difference between `receive_response/2` and -[`wait_response/2`](`wait_response/2`) is that -[`receive_response/2`](`receive_response/2`) abandons the request at timeout so -that a potential future response is ignored, while -[`wait_response/2`](`wait_response/2`) does not. +`wait_response/2` is that `receive_response/2` abandons +the request at time-out so that a potential future response is ignored, +while `wait_response/2` does not. """. --doc(#{since => <<"OTP 23.0">>}). +-doc #{ since => <<"OTP 23.0">> }. -spec wait_response(ReqId, WaitTime) -> Result when ReqId :: request_id(), WaitTime :: response_timeout(), @@ -2157,52 +2709,61 @@ wait_response(ReqId, WaitTime) -> error(badarg, [ReqId, WaitTime]) end. +%%---------------------- -doc """ -Wait for a response corresponding to a request identifier saved in -`ReqIdCollection`. All request identifiers of `ReqIdCollection` must correspond -to requests that have been made using `send_request/2` or `send_request/4`, and -all requests must have been made by the process calling this function. - -The `Label` in the response equals the `Label` associated with the request -identifier that the response corresponds to. The `Label` of a request identifier -is associated when [saving the request id](`reqids_add/3`) in a request -identifier collection, or when sending the request using `send_request/4`. - -Compared to `wait_response/2`, the returned result associated with a specific -request identifier or an exception associated with a specific request identifier -will be wrapped in a 3-tuple. The first element of this tuple equals the value -that would have been produced by [`wait_response/2`](`wait_response/2`), the -second element equals the `Label` associated with the specific request -identifier, and the third element `NewReqIdCollection` is a possibly modified +Wait for any request response in a collection. + +Waits for a response in `ReqIdCollection`. All request identifiers +of `ReqIdCollection` must correspond to requests that have been made +using `send_request/2` or `send_request/4`, and all requests +must have been made by the process calling this function. + +The `Label` in the response is the `Label` associated with +the request identifier that the response corresponds to. +The `Label` of a request identifier is associated +when [adding the request id](`reqids_add/3`) to a collection, +or when sending the request using `send_request/4`. + +Compared to `wait_response/2`, the returned result or exception +associated with a specific request identifier will be wrapped +in a 3-tuple `{Response, Label, NewReqIdCollection}`. +`Response` is the value that would have been produced +by `wait_response/2`, `Label` is the value associated with +the specific [request identifier](`t:request_id/0`) +and `NewReqIdCollection` is a possibly modified request identifier collection. -If `ReqIdCollection` is empty, `no_request` will be returned. If no response is -received before the `WaitTime` timeout has triggered, the atom `timeout` is -returned. It is valid to continue waiting for a response as many times as needed -up until a response has been received and completed by `check_response()`, +If `ReqIdCollection` is empty, `no_request` is returned. + +If no response is received before `WaitTime` has expired, +`timeout` is returned. It is valid to continue waiting +for a response as many times as needed up until a response +has been received and completed by `check_response()`, `receive_response()`, or `wait_response()`. -The difference between `receive_response/3` and -[`wait_response/3`](`wait_response/3`) is that -[`receive_response/3`](`receive_response/3`) abandons requests at timeout so -that potential future responses are ignored, while -[`wait_response/3`](`wait_response/3`) does not. +The difference between `receive_response/3` and `wait_response/3` +is that `receive_response/3` abandons requests at time-out +so that potential future responses are ignored, +while `wait_response/3` does not. -If `Delete` equals `true`, the association with `Label` will have been deleted -from `ReqIdCollection` in the resulting `NewReqIdCollection`. If `Delete` equals -`false`, `NewReqIdCollection` will equal `ReqIdCollection`. Note that deleting -an association is not for free and that a collection containing already handled +If `Delete` is `true`, the association with `Label` +has been deleted from `ReqIdCollection` in the resulting +`NewReqIdCollection`. If `Delete` is `false`, `NewReqIdCollection` +will equal`ReqIdCollection`. Note that deleting an association +is not for free and that a collection containing already handled requests can still be used by subsequent calls to -[`wait_response/3`](`wait_response/3`), `check_response/3`, and -`receive_response/3`. However, without deleting handled associations, the above -calls will not be able to detect when there are no more outstanding requests to -handle, so you will have to keep track of this some other way than relying on a -`no_request` return. Note that if you pass a collection only containing -associations of already handled or abandoned requests to -[`wait_response/3`](`wait_response/3`), it will always block until a timeout -determined by `WaitTime` is triggered and then return `no_reply`. +`wait_response/3`, `check_response/3`, and `receive_response/3`. + +However, without deleting handled associations, +the above calls will not be able to detect when there are +no more outstanding requests to handle, so you will have to keep track +of this some other way than relying on a `no_request` return. +Note that if you pass a collection only containing +associations of already handled or abandoned requests +to this function, it will always block until `WaitTime` expires +and then return `timeout`. """. --doc(#{since => <<"OTP 25.0">>}). +-doc #{ since => <<"OTP 25.0">> }. -spec wait_response(ReqIdCollection, WaitTime, Delete) -> Result when ReqIdCollection :: request_id_collection(), WaitTime :: response_timeout(), @@ -2223,8 +2784,9 @@ wait_response(ReqIdCol, WaitTime, Delete) -> error(badarg, [ReqIdCol, WaitTime, Delete]) end. +%%---------------------- -doc #{ equiv => receive_response(ReqId, infinity) }. --doc(#{since => <<"OTP 24.0">>}). +-doc #{ since => <<"OTP 24.0">> }. -spec receive_response(ReqId) -> Result when ReqId :: request_id(), Response :: {reply, Reply::term()} | @@ -2234,33 +2796,36 @@ wait_response(ReqIdCol, WaitTime, Delete) -> receive_response(ReqId) -> receive_response(ReqId, infinity). +%%---------------------- -doc """ -Receive a response corresponding to the request identifier `ReqId`\- The request -must have been made by `send_request/2` to the `gen_statem` process. This -function must be called from the same process from which `send_request/2` was -made. - -`Timeout` specifies how long to wait for a response. If no response is received -within the specified time, the function returns `timeout`. Assuming that the -server executes on a node supporting aliases (introduced in OTP 24) the request -will also be abandoned. That is, no response will be received after a timeout. +Receive a request response. + +Receive a response corresponding to the request identifier `ReqId`. +The request must have been made by `send_request/2` +to the `gen_statem` process. This function must be called +from the same process from which `send_request/2` was made. + +`Timeout` specifies how long to wait for a response. +If no response is received within the specified time, +this function returns `timeout`. Assuming that the server executes +on a node supporting aliases (introduced in OTP 24) +the request will also be abandoned. That is, +no response will be received after a time-out. Otherwise, a stray response might be received at a later time. -The return value `Reply` is generated when a -[_state callback_](`m:gen_statem#state-callback`) returns with -`{reply,From,Reply}` as one `t:action/0`, and that `Reply` becomes the return -value of this function. +See [`call/3`](#call-reply) about how the request is handled +and the `Reply` is sent by the `gen_statem` server. -The function returns an error if the `gen_statem` dies before or during this -function call. +If the `gen_statem` server process is dead or dies while +this function waits for the reply, it returns an `error` return +with the exit `Reason`. -The difference between `wait_response/2` and -[`receive_response/2`](`receive_response/2`) is that -[`receive_response/2`](`receive_response/2`) abandons the request at timeout so -that a potential future response is ignored, while -[`wait_response/2`](`wait_response/2`) does not. +The difference between `wait_response/2` and `receive_response/2` +is that `receive_response/2` abandons the request at time-out +so that a potential future response is ignored, +while `wait_response/2` does not. """. --doc(#{since => <<"OTP 24.0">>}). +-doc #{ since => <<"OTP 24.0">> }. -spec receive_response(ReqId, Timeout) -> Result when ReqId :: request_id(), Timeout :: response_timeout(), @@ -2276,53 +2841,63 @@ receive_response(ReqId, Timeout) -> error(badarg, [ReqId, Timeout]) end. +%%---------------------- -doc """ -Receive a response corresponding to a request identifier saved in -`ReqIdCollection`. All request identifiers of `ReqIdCollection` must correspond -to requests that have been made using `send_request/2` or `send_request/4`, and -all requests must have been made by the process calling this function. - -The `Label` in the response equals the `Label` associated with the request -identifier that the response corresponds to. The `Label` of a request identifier -is associated when [adding the request id](`reqids_add/3`) in a request -identifier collection, or when sending the request using `send_request/4`. - -Compared to `receive_response/2`, the returned result associated with a specific -request identifier will be wrapped in a 3-tuple. The first element of this tuple -equals the value that would have been produced by -[`receive_response/2`](`receive_response/2`), the second element equals the -`Label` associated with the specific request identifier, and the third element -`NewReqIdCollection` is a possibly modified request identifier collection. - -If `ReqIdCollection` is empty, the atom `no_request` will be returned. - -`Timeout` specifies how long to wait for a response. If no response is received -within the specified time, the function returns `timeout`. Assuming that the -server executes on a node supporting aliases (introduced in OTP 24) all requests -identified by `ReqIdCollection` will also be abandoned. That is, no responses -will be received after a timeout. Otherwise, stray responses might be received +Receive a request response in a collection. + +Receive a response in `ReqIdCollection`. All request identifiers +of `ReqIdCollection` must correspond to requests that have been made +using `send_request/2` or `send_request/4`, and all requests +must have been made by the process calling this function. + +The `Label` in the response is the `Label` associated with +the request identifier that the response corresponds to. +The `Label` of a request identifier is associated +when [adding the request id](`reqids_add/3`) to a collection, +or when sending the request using `send_request/4`. + +Compared to `receive_response/2`, the returned result or exception +associated with a specific request identifier will be wrapped +in a 3-tuple `{Response, Label, NewReqIdCollection}`. +`Response` is the value that would have been produced +by `receive_response/2`, `Label` is the value associated with +the specific [request identifier](`t:request_id/0`) +and `NewReqIdCollection` is a possibly modified +request identifier collection. + +If `ReqIdCollection` is empty, `no_request` will be returned. + +`Timeout` specifies how long to wait for a response. If no response +is received within the specified time, the function returns `timeout`. +Assuming that the server executes on a node supporting aliases +(introduced in OTP 24) all requests identified by `ReqIdCollection` +will also be abandoned. That is, no responses will be received +after a time-out. Otherwise, stray responses might be received at a later time. -The difference between [`receive_response/3`](`receive_response/3`) and -`wait_response/3` is that [`receive_response/3`](`receive_response/3`) abandons -the requests at timeout so that potential future responses are ignored, while -[`wait_response/3`](`wait_response/3`) does not. +The difference between `receive_response/3` and `wait_response/3` +is that `receive_response/3` abandons requests at time-out +so that potential future responses are ignored, +while `wait_response/3` does not. -If `Delete` equals `true`, the association with `Label` will have been deleted -from `ReqIdCollection` in the resulting `NewReqIdCollection`. If `Delete` equals -`false`, `NewReqIdCollection` will equal `ReqIdCollection`. Note that deleting -an association is not for free and that a collection containing already handled +If `Delete` is `true`, the association with `Label` +is deleted from `ReqIdCollection` in the resulting +`NewReqIdCollection`. If `Delete` is `false`, `NewReqIdCollection` +will equal`ReqIdCollection`. Note that deleting an association +is not for free and that a collection containing already handled requests can still be used by subsequent calls to -[`receive_response/3`](`receive_response/3`), `check_response/3`, and -`wait_response/3`. However, without deleting handled associations, the above -calls will not be able to detect when there are no more outstanding requests to -handle, so you will have to keep track of this some other way than relying on a -`no_request` return. Note that if you pass a collection only containing +`wait_response/3`, `check_response/3`, and `receive_response/3`. + +However, without deleting handled associations, +the above calls will not be able to detect when there are +no more outstanding requests to handle, so you will have to keep track +of this some other way than relying on a `no_request` return. +Note that if you pass a collection only containing associations of already handled or abandoned requests to -[`receive_response/3`](`receive_response/3`), it will always block until a -timeout determined by `Timeout` is triggered. +this function, it will always block until `Timeout` expires +and then return `timeout`. """. --doc(#{since => <<"OTP 25.0">>}). +-doc #{ since => <<"OTP 25.0">> }. -spec receive_response(ReqIdCollection, Timeout, Delete) -> Result when ReqIdCollection :: request_id_collection(), Timeout :: response_timeout(), @@ -2343,23 +2918,27 @@ receive_response(ReqIdCol, Timeout, Delete) -> error(badarg, [ReqIdCol, Timeout, Delete]) end. +%%---------------------- -doc """ -Check if `Msg` is a response corresponding to the request identifier `ReqId`. +Check if a received message is a request response. + +Checks if `Msg` is a response corresponding to +the request identifier `ReqId`. The request must have been made +by `send_request/2` and by the same process calling this function. -The request must have been made by `send_request/2`. If `Msg` is a reply to the -handle `ReqId` the result of the request is returned in `Reply`. Otherwise -returns `no_reply` and no cleanup is done, and thus the function shall be -invoked repeatedly until a reply is returned. +If `Msg` is a reply to the handle `ReqId` the result of the request +is returned in `Reply`. Otherwise this function returns `no_reply` +and no cleanup is done, and thus the function shall be invoked repeatedly +until the response is returned. -The return value `Reply` is generated when a -[_state callback_](`m:gen_statem#state-callback`) returns with -`{reply,From,Reply}` as one `t:action/0`, and that `Reply` becomes the return -value of this function. +See [`call/3`](#call-reply) about how the request is handled +and the `Reply` is sent by the `gen_statem` server. -The function returns an error if the `gen_statem` dies before or during this -request. +If the `gen_statem` server process has died when this function +is called, that is; `Msg` reports the server's death, +this function returns an `error` return with the exit `Reason`. """. --doc(#{since => <<"OTP 23.0">>}). +-doc #{ since => <<"OTP 23.0">> }. -spec check_response(Msg, ReqId) -> Result when Msg :: term(), ReqId :: request_id(), @@ -2375,43 +2954,52 @@ check_response(Msg, ReqId) -> error(badarg, [Msg, ReqId]) end. +%%---------------------- -doc """ -Check if `Msg` is a response corresponding to a request identifier saved in -`ReqIdCollection`. All request identifiers of `ReqIdCollection` must correspond -to requests that have been made using `send_request/2` or `send_request/4`, and -all requests must have been made by the process calling this function. - -The `Label` in the response equals the `Label` associated with the request -identifier that the response corresponds to. The `Label` of a request identifier -is associated when [saving the request id](`reqids_add/3`) in a request -identifier collection, or when sending the request using `send_request/4`. - -Compared to `check_response/2`, the returned result associated with a specific -request identifier or an exception associated with a specific request identifier -will be wrapped in a 3-tuple. The first element of this tuple equals the value -that would have been produced by [`check_response/2`](`check_response/2`), the -second element equals the `Label` associated with the specific request -identifier, and the third element `NewReqIdCollection` is a possibly modified +Check if a received message is a request response in a collection. + +Check if `Msg` is a response corresponding to a request identifier +stored in `ReqIdCollection`. All request identifiers of `ReqIdCollection` +must correspond to requests that have been made using `send_request/2` +or `send_request/4`, by the process calling this function. + +The `Label` in the response equals the `Label` associated +with the request identifier that the response corresponds to. +The `Label` of a request identifier is associated +when [storing the request id](`reqids_add/3`) in a collection, +or when sending the request using `send_request/4`. + +Compared to `check_response/2`, the returned result or exception +associated with a specific request identifier will be wrapped +in a 3-tuple `{Response, Label, NewReqIdCollection}`. +`Response` is the value that would have been produced +by `check_response/2`, `Label` is the value associated with +the specific [request identifier](`t:request_id/0`) +and `NewReqIdCollection` is a possibly modified request identifier collection. -If `ReqIdCollection` is empty, the atom `no_request` will be returned. If `Msg` -does not correspond to any of the request identifiers in `ReqIdCollection`, the -atom `no_reply` is returned. +If `ReqIdCollection` is empty, `no_request` is returned. + +If `Msg` does not correspond to any of the request identifiers +in `ReqIdCollection`, `no_reply` is returned. -If `Delete` equals `true`, the association with `Label` will have been deleted -from `ReqIdCollection` in the resulting `NewReqIdCollection`. If `Delete` equals -`false`, `NewReqIdCollection` will equal `ReqIdCollection`. Note that deleting -an association is not for free and that a collection containing already handled +If `Delete` equals `true`, the association with `Label` +has been deleted from `ReqIdCollection` in the resulting +`NewReqIdCollection`. If `Delete` is `false`, `NewReqIdCollection` +will equal `ReqIdCollection`. Note that deleting an association +is not for free and that a collection containing already handled requests can still be used by subsequent calls to -[`check_response/3`](`check_response/3`), `receive_response/3`, and -`wait_response/3`. However, without deleting handled associations, the above -calls will not be able to detect when there are no more outstanding requests to -handle, so you will have to keep track of this some other way than relying on a -`no_request` return. Note that if you pass a collection only containing +`wait_response/3`, `check_response/3`, and `receive_response/3`. + +However, without deleting handled associations, +the above calls will not be able to detect when there are +no more outstanding requests to handle, so you will have to keep track +of this some other way than relying on a `no_request` return. +Note that if you pass a collection only containing associations of already handled or abandoned requests to -[`check_response/3`](`check_response/3`), it will always return `no_reply`. +this function, it will always return `no_reply`. """. --doc(#{since => <<"OTP 25.0">>}). +-doc #{ since => <<"OTP 25.0">> }. -spec check_response(Msg, ReqIdCollection, Delete) -> Result when Msg :: term(), ReqIdCollection :: request_id_collection(), @@ -2432,28 +3020,34 @@ check_response(Msg, ReqIdCol, Delete) -> error(badarg, [Msg, ReqIdCol, Delete]) end. +%%---------------------- -doc """ -Returns a new empty request identifier collection. A request identifier -collection can be utilized in order the handle multiple outstanding requests. +Create an empty request identifier collection. + +Returns a new empty request identifier collection. +A request identifier collection can be used to handle +multiple outstanding requests. -Request identifiers of requests made by `send_request/2` can be saved in a -request identifier collection using `reqids_add/3`. Such a collection of request -identifiers can later be used in order to get one response corresponding to a -request in the collection by passing the collection as argument to +Request identifiers of requests made by `send_request/2` +can be stored in a collection using `reqids_add/3`. +Such a collection of request identifiers can later be used +in order to get one response corresponding to a request +in the collection by passing the collection as argument to `receive_response/3`, `wait_response/3`, or, `check_response/3`. -`reqids_size/1` can be used to determine the amount of request identifiers in a -request identifier collection. +`reqids_size/1` can be used to determine the number of +request identifiers in a collection. """. --doc(#{since => <<"OTP 25.0">>}). +-doc #{ since => <<"OTP 25.0">> }. -spec reqids_new() -> NewReqIdCollection::request_id_collection(). reqids_new() -> gen:reqids_new(). --doc "Returns the amount of request identifiers saved in `ReqIdCollection`.". --doc(#{since => <<"OTP 25.0">>}). +%%---------------------- +-doc "Return the number of request identifiers in `ReqIdCollection`.". +-doc #{ since => <<"OTP 25.0">> }. -spec reqids_size(ReqIdCollection::request_id_collection()) -> non_neg_integer(). @@ -2464,12 +3058,15 @@ reqids_size(ReqIdCollection) -> error:badarg -> error(badarg, [ReqIdCollection]) end. +%%---------------------- -doc """ -Saves `ReqId` and associates a `Label` with the request identifier by adding -this information to `ReqIdCollection` and returning the resulting request -identifier collection. +Store a request identifier in a colletion. + +Stores `ReqId` and associates a `Label` with the request identifier +by adding this information to `ReqIdCollection` and returning +the resulting request identifier collection. """. --doc(#{since => <<"OTP 25.0">>}). +-doc #{ since => <<"OTP 25.0">> }. -spec reqids_add(ReqId::request_id(), Label::term(), ReqIdCollection::request_id_collection()) -> NewReqIdCollection::request_id_collection(). @@ -2481,12 +3078,15 @@ reqids_add(ReqId, Label, ReqIdCollection) -> error:badarg -> error(badarg, [ReqId, Label, ReqIdCollection]) end. +%%---------------------- -doc """ -Returns a list of `{ReqId, Label}` tuples which corresponds to all request -identifiers with their associated labels present in the `ReqIdCollection` -collection. +Convert a request identifier collection to a list. + +Returns a list of `{ReqId, Label}` tuples which corresponds to +all request identifiers with their associated labels +in [`ReqIdCollection`](`t:request_id_collection/0`). """. --doc(#{since => <<"OTP 25.0">>}). +-doc #{ since => <<"OTP 25.0">> }. -spec reqids_to_list(ReqIdCollection::request_id_collection()) -> [{ReqId::request_id(), Label::term()}]. @@ -2498,19 +3098,20 @@ reqids_to_list(ReqIdCollection) -> end. %% Reply from a state machine callback to whom awaits in call/2 +%%---------------------- -doc """ -Send a reply or multiple replies using one or several `t:reply_action/0`s from a -[_state callback_](`m:gen_statem#state-callback`). +Send one or multiple `call` replies. -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_](`m:gen_statem#state-callback`). +This funcion can be used by a `gen_statem` callback to explicitly send +one or multiple replies to processes waiting for `call` requests' replies, +when it is impractical or impossible to return `t:reply_action/0`s +from a [_state callback_](#state-callback). > #### Note {: .info } > > A reply sent with this function is not visible in `m:sys` debug output. """. --doc(#{since => <<"OTP 19.0">>}). +-doc #{ since => <<"OTP 19.0">> }. -spec reply(Replies :: [reply_action()] | reply_action()) -> ok. reply({reply,From,Reply}) -> reply(From, Reply); @@ -2518,21 +3119,20 @@ reply(Replies) when is_list(Replies) -> replies(Replies). %% -compile({inline, [reply/2]}). +%%---------------------- -doc """ -Send a `Reply` to `From`. - -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_](`m:gen_statem#state-callback`). +Send a `call` `Reply` to `From`. -`From` must be the term from argument [`{call,From}`](`t:event_type/0`) to the -[_state callback_](`m:gen_statem#state-callback`). +This funcion can be used by a `gen_statem` callback to explicitly send +a reply to a process waiting for a `call` requests' reply, +when it is impractical or impossible to return a `t:reply_action/0` +from a [_state callback_](#state-callback). > #### Note {: .info } > > A reply sent with this function is not visible in `m:sys` debug output. """. --doc(#{since => <<"OTP 19.0">>}). +-doc #{ since => <<"OTP 19.0">> }. -spec reply(From :: from(), Reply :: term()) -> ok. reply(From, Reply) -> gen:reply(From, Reply). @@ -2541,33 +3141,36 @@ reply(From, Reply) -> %% or start_link/3,4 turn the current process presumably %% started by proc_lib into a state machine using %% the same arguments as you would have returned from init/1 --doc """ -The same as `enter_loop/6` with `Actions = []` except that no `t:server_name/0` -must have been registered. This creates an anonymous server. -""". --doc(#{since => <<"OTP 19.1">>}). +%%---------------------- +-doc #{ equiv => enter_loop(Module, Opts, State, Data, self(), []) }. +-doc #{ since => <<"OTP 19.1">> }. -spec enter_loop( - Module :: module(), Opts :: [enter_loop_opt()], - State :: state(), Data :: data()) -> - no_return(). + Module :: term(), Opts :: term(), State :: term(), Data :: term()) -> + no_return(). enter_loop(Module, Opts, State, Data) -> enter_loop(Module, Opts, State, Data, self()). %% +%%---------------------- -doc """ -If `Server_or_Actions` is a `t:list/0`, the same as `enter_loop/6` except that -no `t:server_name/0` must have been registered and -`Actions = Server_or_Actions`. This creates an anonymous server. +Make the calling process become a `gen_statem` server. + +With argument `Actions`, equivalent to +[`enter_loop(Module, Opts, State, Data, self(), Actions)`](`enter_loop/6`). -Otherwise the same as `enter_loop/6` with `Server = Server_or_Actions` and -`Actions = []`. +Otherwise equivalent to +[`enter_loop(Module, Opts, State, Data, Server, [])`](`enter_loop/6`). """. --doc(#{since => <<"OTP 19.0">>}). --spec enter_loop( - Module :: module(), Opts :: [enter_loop_opt()], - State :: state(), Data :: data(), - Server_or_Actions :: - server_name() | pid() | [action()]) -> - no_return(). +-doc #{ since => <<"OTP 19.0">> }. +-spec enter_loop(Module :: term(), Opts :: term(), + State :: term(), Data :: term(), + Actions) -> + no_return() when + Actions :: list(); + (Module :: term(), Opts :: term(), + State :: term(), Data :: term(), + Server) -> + no_return() when + Server :: server_name() | pid(). enter_loop(Module, Opts, State, Data, Server_or_Actions) -> if is_list(Server_or_Actions) -> @@ -2576,35 +3179,40 @@ enter_loop(Module, Opts, State, Data, Server_or_Actions) -> enter_loop(Module, Opts, State, Data, Server_or_Actions, []) end. %% +%%---------------------- -doc """ -Makes the calling process become a `gen_statem`. +Make the calling process become a `gen_statem` server. -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 -`m:proc_lib`. The user is responsible for any initialization of the process, -including registering a name for it. +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 `m: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. +This function is useful when a more complex initialization procedure +is needed than the `gen_statem` [`Module:init/1`](`c:init/1`) +callback offers. -`Module`, `Opts` have the same meaning as when calling -[`start[_link|_monitor]/3,4`](`start_link/3`). +`Module` and `Opts` have the same meanings as when calling +[`start[link | monitor]/3,4`](`start_link/3`). If `Server` is `self/0` an anonymous server is created just as when using -[`start[_link|_monitor]/3`](`start_link/3`). If `Server` is a `t:server_name/0` -a named server is created just as when using -[`start[_link|_monitor]/4`](`start_link/4`). However, the `t:server_name/0` name -must have been registered accordingly _before_ this function is called. - -`State`, `Data`, and `Actions` have the same meanings as in the return value of -[`Module:init/1`](`c:init/1`). Also, the callback module does not need to export +[`start[link |_monitor]/3`](`start_link/3`). If `Server` +is a `t:server_name/0` a named server is created just as when using +[`start[link |_monitor]/4`](`start_link/4`). However, +the `t:server_name/0` name must have been registered accordingly +_before_ this function is called. + +`State`, `Data`, and `Actions` have the same meanings +as in the return value of [`Module:init/1`](`c:init/1`). +Also, the callback module does not need to export a [`Module:init/1`](`c:init/1`) function. -The function fails if the calling process was not started by a `m:proc_lib` -start function, or if it is not registered according to `t:server_name/0`. +The function fails if the calling process was not started +by a `m:proc_lib` start function, or if it is not registered +according to `t:server_name/0`. """. --doc(#{since => <<"OTP 19.0">>}). +-doc #{ since => <<"OTP 19.0">> }. -spec enter_loop( Module :: module(), Opts :: [enter_loop_opt()], State :: state(), Data :: data(), @@ -2657,7 +3265,7 @@ send(Proc, Msg) -> end, ok. -%% Here the init_it/6 and enter_loop/5,6,7 functions converge +%% Here the init_it/6 and enter_loop/4,5,6 functions converge enter( Parent, Debug, Module, Name, HibernateAfterTimeout, State, Data, Actions) -> @@ -2715,6 +3323,11 @@ init_it(Starter, Parent, ServerRef, Module, Args, Opts) -> %%--------------------------------------------------------------------------- %% gen callbacks helpers +%%% +%%% NOTE: If init_ack() return values are modified, see comment +%%% above monitor_return() in gen.erl! +%%% + init_result( Starter, Parent, ServerRef, Module, Result, Name, Debug, HibernateAfterTimeout) -> @@ -2844,7 +3457,7 @@ format_status( maps:get('$status',NewStatusMap)]. %% Update #params.parent only if it differs. This should not -%% be possible today (OTP-22.0), but could happen for example +%% be possible today (OTP 22.0), but could happen for example %% if someone implements changing a server's parent %% in a new sys call. -compile({inline, update_parent/2}). @@ -2952,7 +3565,7 @@ loop(P, Debug, S) -> %% loop_hibernate(P, Debug, S) -> %% - %% Does not return but restarts process at + %% does not return but restarts process at %% wakeup_from_hibernate/3 that jumps to loop_receive/3 %% proc_lib:hibernate(?MODULE, wakeup_from_hibernate, [P, Debug, S]), @@ -2990,7 +3603,7 @@ loop_receive( end; %% {system,Pid,Req} -> - %% Does not return but tail recursively calls + %% does not return but tail recursively calls %% system_continue/3 that jumps to loop/3 sys:handle_system_msg( Req, Pid, P#params.parent, ?MODULE, Debug, @@ -4397,7 +5010,7 @@ client_stacktrace([_|_]) -> %% error_logger only. It is kept for backwards compatibility with %% legacy error_logger event handlers. This function must always %% return {Format,Args} compatible with the arguments in this module's -%% calls to error_logger prior to OTP-21.0. +%% calls to error_logger prior to OTP 21.0. -doc false. format_log(Report) -> Depth = error_logger:get_format_depth(), diff --git a/lib/stdlib/test/erl_internal_SUITE.erl b/lib/stdlib/test/erl_internal_SUITE.erl index b25c455dbcff..0aadb3baf7a8 100644 --- a/lib/stdlib/test/erl_internal_SUITE.erl +++ b/lib/stdlib/test/erl_internal_SUITE.erl @@ -82,7 +82,8 @@ callbacks(gen_server) -> {handle_info,2}, {terminate,2}, {code_change,3}, {format_status,1}, {format_status,2}, {handle_continue, 2}]; callbacks(gen_fsm) -> - [{init,1}, {handle_event,3}, {handle_sync_event,4}, + [{init,1}, {'StateName',2}, {'StateName',3}, + {handle_event,3}, {handle_sync_event,4}, {handle_info,3}, {terminate,3}, {code_change,4}, {format_status,2}]; callbacks(gen_event) -> @@ -103,7 +104,8 @@ optional_callbacks(application) -> optional_callbacks(gen_server) -> [{handle_info, 2}, {handle_continue, 2}, {terminate, 2}, {code_change, 3}, {format_status, 1}, {format_status, 2}]; optional_callbacks(gen_fsm) -> - [{handle_info, 3}, {terminate, 3}, {code_change, 4}, {format_status, 2}]; + [{'StateName', 2}, {'StateName', 3}, + {handle_info, 3}, {terminate, 3}, {code_change, 4}, {format_status, 2}]; optional_callbacks(gen_event) -> [{handle_info, 2}, {terminate, 2}, {code_change, 3}, {format_status, 1}, {format_status, 2}]; optional_callbacks(gen_statem) -> diff --git a/make/ex_doc.exs b/make/ex_doc.exs index 606ccac3a6ea..6803d758366f 100644 --- a/make/ex_doc.exs +++ b/make/ex_doc.exs @@ -98,14 +98,24 @@ groups_for_docs = ) ++ [Types: &(&1[:kind] == :type)] ++ Enum.map( - Access.get(titles, :function, []), - fn {:function, title} -> - {"#{title}", + Access.get(titles, :callback, []), + fn {:callback, title} -> + {"Callbacks: #{title}", fn a -> - a[:kind] == :function && String.equivalent?(Access.get(a, :title, ""), title) + a[:kind] == :callback && String.equivalent?(Access.get(a, :title, ""), title) end} end - ) + ) ++ + [Callbacks: &(&1[:kind] == :callback)] ++ + Enum.map( + Access.get(titles, :function, []), + fn {:function, title} -> + {"#{title}", + fn a -> + a[:kind] == :function && String.equivalent?(Access.get(a, :title, ""), title) + end} + end + ) ## Create the correct source url to github base_url = "https://github.com/" <> System.get_env("BASE_URL", "erlang/otp/blob/master/") diff --git a/system/doc/design_principles/assets/ballpoint-pen.odg b/system/doc/design_principles/assets/ballpoint-pen.odg new file mode 100644 index 000000000000..5f4a35c81874 Binary files /dev/null and b/system/doc/design_principles/assets/ballpoint-pen.odg differ diff --git a/system/doc/design_principles/assets/ballpoint-pen.svg b/system/doc/design_principles/assets/ballpoint-pen.svg new file mode 100644 index 000000000000..9db3fd474f9e --- /dev/null +++ b/system/doc/design_principles/assets/ballpoint-pen.svg @@ -0,0 +1,107 @@ + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + \ No newline at end of file diff --git a/system/doc/design_principles/gen_server_concepts.md b/system/doc/design_principles/gen_server_concepts.md index e5c960605803..d30eca8c9dfd 100644 --- a/system/doc/design_principles/gen_server_concepts.md +++ b/system/doc/design_principles/gen_server_concepts.md @@ -17,18 +17,19 @@ limitations under the License. %CopyrightEnd% --> -# gen_server Behaviour -[](){: #gen_server } +[](){: #gen_server }gen_server Behaviour +======================================== It is recommended to read this section alongside `m:gen_server` in STDLIB. -## Client-Server Principles +Client-Server Principles +------------------------ The client-server model is characterized by a central server and an arbitrary number of clients. The client-server model is used for resource management -operations, where several different clients want to share a common resource. The -server is responsible for managing this resource. +operations, where several different clients want to share a common resource. +The server is responsible for managing this resource. [](){: #clientserver } @@ -65,7 +66,8 @@ flowchart LR end ``` -## Example +Example +------- An example of a simple server written in plain Erlang is provided in [Overview](design_principles.md#ch1). The server can be reimplemented using @@ -104,7 +106,8 @@ handle_cast({free, Ch}, Chs) -> The code is explained in the next sections. -## Starting a Gen_Server +Starting a Gen_Server +--------------------- In the example in the previous section, `gen_server` is started by calling `ch3:start_link()`: @@ -114,11 +117,11 @@ start_link() -> gen_server:start_link({local, ch3}, ch3, [], []) => {ok, Pid} ``` -`start_link/0` calls function `gen_server:start_link/4`. This function spawns and -links to a new process, a `gen_server`. +`start_link/0` calls function `gen_server:start_link/4`. This function +spawns and links to a new process, a `gen_server`. -- The first argument, `{local, ch3}`, specifies the name. The gen_server is then - locally registered as `ch3`. +- The first argument, `{local, ch3}`, specifies the name. + The gen_server is then locally registered as `ch3`. If the name is omitted, the `gen_server` is not registered. Instead its pid must be used. The name can also be given as `{global, Name}`, in which case @@ -157,7 +160,8 @@ a supervision tree, meaning that it was started by a supervisor. There is another function, `gen_server:start/4`, to start a standalone `gen_server` that is not part of a supervision tree. -## Synchronous Requests - Call +Synchronous Requests - Call +--------------------------- The synchronous request `alloc()` is implemented using `gen_server:call/2`: @@ -166,14 +170,14 @@ alloc() -> gen_server:call(ch3, alloc). ``` -`ch3` is the name of the `gen_server` and must agree with the name used to start -it. `alloc` is the actual request. +`ch3` is the name of the `gen_server` and must agree with the name +used to start it. `alloc` is the actual request. -The request is made into a message and sent to the `gen_server`. When the -request is received, the `gen_server` calls `handle_call(Request, From, State)`, -which is expected to return a tuple `{reply,Reply,State1}`. `Reply` is the reply -that is to be sent back to the client, and `State1` is a new value for the state -of the `gen_server`. +The request is made into a message and sent to the `gen_server`. +When the request is received, the `gen_server` calls +`handle_call(Request, From, State)`, which is expected to return +a tuple `{reply,Reply,State1}`. `Reply` is the reply that is to be sent back +to the client, and `State1` is a new value for the state of the `gen_server`. ```erlang handle_call(alloc, _From, Chs) -> @@ -185,10 +189,11 @@ In this case, the reply is the allocated channel `Ch` and the new state is the set of remaining available channels `Chs2`. Thus, the call `ch3:alloc()` returns the allocated channel `Ch` and the -`gen_server` then waits for new requests, now with an updated list of available -channels. +`gen_server` then waits for new requests, now with an updated list of +available channels. -## Asynchronous Requests - Cast +Asynchronous Requests - Cast +---------------------------- The asynchronous request `free(Ch)` is implemented using `gen_server:cast/2`: @@ -199,8 +204,8 @@ free(Ch) -> `ch3` is the name of the `gen_server`. `{free, Ch}` is the actual request. -The request is made into a message and sent to the `gen_server`. `cast`, and -thus `free`, then returns `ok`. +The request is made into a message and sent to the `gen_server`. +`cast`, and thus `free`, then returns `ok`. When the request is received, the `gen_server` calls `handle_cast(Request, State)`, which is expected to return a tuple @@ -215,19 +220,20 @@ handle_cast({free, Ch}, Chs) -> In this case, the new state is the updated list of available channels `Chs2`. The `gen_server` is now ready for new requests. -## Stopping +Stopping +-------- ### In a Supervision Tree If the `gen_server` is part of a supervision tree, no stop function is needed. -The `gen_server` is automatically terminated by its supervisor. Exactly how this -is done is defined by a [shutdown strategy](sup_princ.md#shutdown) set in the -supervisor. +The `gen_server` is automatically terminated by its supervisor. Exactly how +this is done is defined by a [shutdown strategy](sup_princ.md#shutdown) +set in the supervisor. -If it is necessary to clean up before termination, the shutdown strategy must be -a time-out value and the `gen_server` must be set to trap exit signals in -function `init`. When ordered to shutdown, the `gen_server` then calls the -callback function `terminate(shutdown, State)`: +If it is necessary to clean up before termination, the shutdown strategy +must be a time-out value and the `gen_server` must be set to trap exit signals +in function `init`. When ordered to shutdown, the `gen_server` then calls +the callback function `terminate(shutdown, State)`: ```erlang init(Args) -> @@ -246,8 +252,8 @@ terminate(shutdown, State) -> ### Standalone Gen_Servers -If the `gen_server` is not part of a supervision tree, a stop function can be -useful, for example: +If the `gen_server` is not part of a supervision tree, a stop function +can be useful, for example: ```erlang ... @@ -270,17 +276,19 @@ terminate(normal, State) -> ``` The callback function handling the `stop` request returns a tuple -`{stop,normal,State1}`, where `normal` specifies that it is a normal termination -and `State1` is a new value for the state of the `gen_server`. This causes the -`gen_server` to call `terminate(normal, State1)` and then it terminates -gracefully. - -## Handling Other Messages - -If the `gen_server` is to be able to receive other messages than requests, the -callback function `handle_info(Info, State)` must be implemented to handle them. -Examples of other messages are exit messages, if the `gen_server` is linked to -other processes than the supervisor and it is trapping exit signals. +`{stop,normal,State1}`, where `normal` specifies that it is +a normal termination and `State1` is a new value for the state +of the `gen_server`. This causes the `gen_server` to call +`terminate(normal, State1)` and then it terminates gracefully. + +Handling Other Messages +----------------------- + +If the `gen_server` is to be able to receive other messages than requests, +the callback function `handle_info(Info, State)` must be implemented +to handle them. Examples of other messages are exit messages, +if the `gen_server` is linked to other processes than the supervisor +and it is trapping exit signals. ```erlang handle_info({'EXIT', Pid, Reason}, State) -> diff --git a/system/doc/design_principles/statem.md b/system/doc/design_principles/statem.md index 9c965beb0eb5..9b9fcdff2b18 100644 --- a/system/doc/design_principles/statem.md +++ b/system/doc/design_principles/statem.md @@ -17,28 +17,34 @@ limitations under the License. %CopyrightEnd% --> -# gen_statem Behaviour -It is recommended to read this section alongside `m:gen_statem` in STDLIB. +`gen_statem` Behaviour +====================== -## Event-Driven State Machines +It is recommended to read this section alongside +the `m:gen_statem` reference manual in STDLIB. -Established Automata Theory does not deal much with how a _state transition_ is -triggered, but assumes that the output is a function of the input (and the -state) and that they are some kind of values. +Event-Driven State Machines +--------------------------- -For an Event-Driven State Machine, the input is an event that triggers a _state -transition_ and the output is actions executed during the _state transition_. -Analogously to the mathematical model of a Finite State Machine, it can be -described as a set of relations of the following form: +Established Automata Theory does not deal much with how a _state transition_ +is triggered, but assumes that the output is a function of the input +(and the state) and that they are some kind of values. + +For an Event-Driven State Machine, the input is an _event_ that triggers +a _state transition_ and the output is actions executed during +the _state transition_. Analogously to the mathematical model +of a Finite State Machine, it can be described as a set of relations +of the following form: ```erlang State(S) x Event(E) -> Actions(A), State(S') ``` -These relations are interpreted as follows: if we are in state `S` and event `E` -occurs, we are to perform actions `A`, and make a transition to state `S'`. -Notice that `S'` can be equal to `S`, and that `A` can be empty. +These relations are interpreted as follows: if we are in state `S`, +and event `E` occurs, we are to perform actions `A`, and make a transition +to state `S'`. Notice that `S'` can be equal to `S`, +and that `A` can be empty. In `gen_statem` we define a _state change_ as a _state transition_ in which the new state `S'` is different from the current state `S`, where "different" means @@ -56,24 +62,52 @@ machine memory), or on the number of distinct input events, a state machine implemented with this behaviour is Turing complete. But it feels mostly like an Event-Driven Mealy machine. -## When to use gen_statem +### Everyday State Machine + +An example of an everyday device that can be modelled as a state machine +is a classic ballpoint pen, the retractable type where you push the end +to expose the tip and push the side to retract it. (A push-push pen +would also be an example but that type has only one event, so it is +less interesting) + +![Ballpoint Pen](assets/ballpoint-pen.svg "Ballpoint Pen") + +```mermaid +--- +title: Ballpoint Pen State Diagram +--- +stateDiagram-v2 + [*] --> Retracted + Retracted --> Retracted : push-side + Retracted --> Exposed : push-end\n* Expose tip + Exposed --> Retracted : push-side\n* Retract tip + Exposed --> Exposed : push-end +``` + +The state diagram shows the states, events, and state transitions +with transition actions. Note that pushing the end when the tip is exposed, +or pushing the side when the tip is retracted, does not change the state +nor cause any actions, which is modeled by an arrow back to the same state. + +When to use gen_statem +---------------------- You should consider using `m:gen_statem` over `m:gen_server` if your process logic is convenient to describe as a state machine and you need any of these `m:gen_statem` key features: - Co-located callback code for each state, for all - [_Event Types_ ](statem.md#event-types-and-event-content), such as _call_, + [_event types_](#event-types-and-event-content), such as _call_, _cast_, and _info_ -- [Postponing Events](statem.md#postponing-events) - a substitute for selective +- [_Postponing events_](#postponing-events) - a substitute for selective receive -- [Inserted Events](statem.md#inserted-events) - events from the state +- [_Inserted events_](#inserted-events) - events from the state machine to itself; for purely internal events in particular -- [_State Enter Calls_](statem.md#state-enter-calls) - callback on state entry +- [_State enter calls_](#state-enter-calls) - callback on state entry co-located with the rest of each state's callback code -- Easy-to-use time-outs - [State Time-Outs](statem.md#state-time-outs), - [Event Time-Outs](statem.md#event-time-outs), and - [Generic Time-Outs](statem.md#generic-time-outs) (named time-outs) +- Easy-to-use time-outs - [_state time-outs_](#state-time-outs), + [_event time-outs_](#event-time-outs), and + [_generic time-outs_](#generic-time-outs) (named time-outs) For simple state machines not needing these features, `m:gen_server` is perfectly suitable. It also has a smaller call overhead, but we are @@ -82,7 +116,8 @@ here, so if the server callback does just a little bit more than just replying, or if calls are not extremely frequent, that difference will be hard to notice. -## Callback Module +Callback Module +--------------- The _callback module_ contains functions that implement the state machine. When an event occurs, the `gen_statem` behaviour engine calls @@ -94,10 +129,10 @@ be performed by the behaviour engine. The behaviour engine holds the state machine state, server data, timer references, a queue of postponed messages, and other metadata. It receives all process messages, handles the system messages, and calls the _callback module_ -with machine specific events. +with state machine specific events. The _callback module_ can be changed for a running server using any of the -[transition actions](statem.md#transition-actions) +[_transition actions_](#transition-actions) [`{change_callback_module, NewModule}`](`t:gen_statem:action/0`), [`{push_callback_module, NewModule}`](`t:gen_statem:action/0`), or [`pop_callback_module`](`t:gen_statem:action/0`). @@ -113,7 +148,8 @@ The _callback module_ can be changed for a running server using any of the > module, so all relevant callback functions have to handle the state > and data from the previous callback module. -## Callback Modes +Callback Modes +-------------- The `gen_statem` behaviour supports two _callback modes_: @@ -127,17 +163,17 @@ The _callback mode_ is a property of the _callback module_ and is set at server start. It may be changed due to a code upgrade/downgrade, or when changing the _callback module_. -See the section [_State Callback_](statem.md#state-callback) that describes the +See the section [_State Callback_](#state-callback) that describes the event handling callback function(s). The _callback mode_ is selected by implementing a mandatory callback function -[`Module:callback_mode()` ](`c:gen_statem:callback_mode/0`)that returns one of +[`Module:callback_mode()`](`c:gen_statem:callback_mode/0`) that returns one of the _callback modes_. -The [`Module:callback_mode()` ](`c:gen_statem:callback_mode/0`)function may also -return a list containing the _callback mode_ and the atom `state_enter` in which -case [_state enter calls_ ](statem.md#state-enter-calls)are activated for the -_callback mode_. +The [`Module:callback_mode()`](`c:gen_statem:callback_mode/0`) function +may also return a list containing the _callback mode_ and the atom +`state_enter` in which case [_state enter calls_](#state-enter-calls) +are activated for the _callback mode_. ### Choosing the Callback Mode @@ -146,201 +182,195 @@ The short version: choose `state_functions` - it is the one most like atom, or if you do not want to write one _state callback_ function per state, please read on... -The two [_callback modes_](statem.md#callback-modes) give different +The two [_callback modes_](#callback-modes) give different possibilities and restrictions, with one common goal: to handle all possible combinations of events and states. This can be done, for example, by focusing on one state at the time and for -every state ensure that all events are handled. Alternatively, you can focus on -one event at the time and ensure that it is handled in every state. You can also -use a mix of these strategies. +every state ensure that all events are handled. Alternatively, you can focus +on one event at the time and ensure that it is handled in every state. +You can also use a mix of these strategies. With `state_functions`, you are restricted to use atom-only states, and the -`m:gen_statem` engine branches depending on state name for you. This encourages -the _callback module_ to co-locate the implementation of all event actions -particular to one state in the same place in the code, hence to focus on one -state at the time. - -This mode fits well when you have a regular state diagram, like the ones in this -chapter, which describes all events and actions belonging to a state visually -around that state, and each state has its unique name. - -With `handle_event_function`, you are free to mix strategies, as all events and -states are handled in the same callback function. - -This mode works equally well when you want to focus on one event at the time or -on one state at the time, but function -[`Module:handle_event/4` ](`c:gen_statem:handle_event/4`)quickly grows too large -to handle without branching to helper functions. - -The mode enables the use of non-atom states, for example, complex states or even -hierarchical states. See section [Complex State](statem.md#complex-state). If, -for example, a state diagram is largely alike for the client side and the server -side of a protocol, you can have a state `{StateName,server}` or -`{StateName,client}`, and make `StateName` determine where in the code to handle -most events in the state. The second element of the tuple is then used to select -whether to handle special client-side or server-side events. - -## State Callback +`m:gen_statem` engine branches depending on state name for you. +This encourages the _callback module_ to co-locate the implementation +of all event actions particular to one state in the same place in the code, +hence to focus on one state at the time. + +This mode fits well when you have a regular state diagram, like the ones +in this chapter, which describes all events and actions belonging to a state +visually around that state, and each state has its unique name. + +With `handle_event_function`, you are free to mix strategies, as all events +and states are handled in the same callback function. + +This mode works equally well when you want to focus on one event +at the time or on one state at the time, but function +[`Module:handle_event/4`](`c:gen_statem:handle_event/4`) quickly grows +too large to handle without branching to helper functions. + +The mode enables the use of non-atom states, for example, complex states, +or even hierarchical states. See section [_Complex State_](#complex-state). +If, for example, a state diagram is largely alike for the client side +and the server side of a protocol, you can have a state `{StateName, server}`, +or `{StateName, client}`, and make `StateName` determine where in the code +to handle most events in the state. The second element of the tuple +is then used to select whether to handle special client-side +or server-side events. + +State Callback +-------------- The _state callback_ is the callback function that handles an event in the current state, and which function that is depends on the _callback mode_: - **`state_functions`** - The event is handled by: - [`Module:StateName(EventType, EventContent, Data)`](`c:gen_statem:'StateName'/3`) + [`Module:StateName(EventType, EventContent, + Data)`](`c:gen_statem:'StateName'/3`) - This form is the one mostly used in the [Example](statem.md#example) section. + This form is the one mostly used in the [_Example_](#example) section. - **`handle_event_function`** - The event is handled by: - [`Module:handle_event(EventType, EventContent, State, Data)`](`c:gen_statem:handle_event/4`) + [`Module:handle_event(EventType, EventContent, State, + Data)`](`c:gen_statem:handle_event/4`) - See section [_One State Callback_ ](statem.md#one-state-callback)for an - example. + See section [_One State Callback_](#one-state-callback) for an example. -The state is either the name of the function itself or an argument to it. The -other arguments are the `EventType` and the event dependent `EventContent`, both -described in section -[Event Types and Event Content](statem.md#event-types-and-event-content), and -the current server `Data`. +The state is either the name of the state callback itself, or an argument +to the [`handle_event()`](`c:gen_statem:handle_event/4`) callback. The +other arguments are the `EventType` and the event dependent `EventContent`, +both described in section +[_Event Types and Event Content_](#event-types-and-event-content), +and the the last argument is the current server `Data`. -_State enter calls_ are also handled by the event handler and have slightly -different arguments. See section -[State Enter Calls](statem.md#state-enter-calls). +[_State Enter Calls_](#state-enter-calls) (see that section) +are also handled by the event handler and have slightly different arguments. The _state callback_ return values are defined in the description of -[`Module:StateName/3` ](`c:gen_statem:'StateName'/3`) in `m:gen_statem`, -but here is a more readable list: +[`Module:StateName/3`](`c:gen_statem:'StateName'/3`) in `m:gen_statem`. +Here is a maybe more readable list: -- **`{next_state, NextState, NewData, Actions}` - `{next_state, NextState, NewData}`** +- **`{next_state, NextState, NewData [, Actions]}`** Set next state and update the server data. If the `Actions` field is used, - execute _transition actions_. An empty `Actions` list is equivalent to not + execute [_Transition Actions_](#transition-actions) + (see that section). An empty `Actions` list is equivalent to not returning the field. - See section [_Transition Actions_ ](statem.md#transition-actions)for a list of - possible _transition actions_. - - If `NextState =/= State` this is a _state change_ so the extra things - `gen_statem` does are: the event queue is restarted from the oldest - [postponed event](statem.md#postponing-events), any current - [state time-out](statem.md#state-time-outs) is canceled, and a - [state enter call](statem.md#state-enter-calls) is performed, if enabled. + If `NextState =/= State` it's a _state change_ and `gen_statem` + does some extra things: the event queue is restarted from the oldest + [postponed event](#postponing-events), any current + [_state time-out_](#state-time-outs) is canceled, and a + [_state enter call_](#state-enter-calls) is performed, if enabled. + The current `State` becomes `OldState` in a _state enter call_. -- **`{keep_state, NewData, Actions}` - `{keep_state, NewData}`** - Same as the `next_state` values with `NextState =:= State`, that is, no _state - change_. +- **`{keep_state, NewData [, Actions]}`** + Same as the `next_state` values with `NextState =:= State`, that is, + no _state change_. -- **`{keep_state_and_data, Actions}` - `keep_state_and_data`** - Same as the `keep_state` values with `NextData =:= Data`, that is, no change +- **`keep_state_and_data | {keep_state_and_data, Actions}`** + Same as the `keep_state` values with `NextData =:= Data`, that is, no change in server data. -- **`{repeat_state, NewData, Actions}` - `{repeat_state, NewData}` - `{repeat_state_and_data, Actions}` - `repeat_state_and_data`** - Same as the `keep_state` or `keep_state_and_data` values, and if - [State Enter Calls ](statem.md#state-enter-calls)are enabled, repeat the - _state enter call_ as if this state was entered again. - - If these return values are used from a _state enter call_ the `OldState` does - not change, but if used from an event handling _state callback_ the new _state - enter call's_ `OldState` will be the current state. - -- **`{stop, Reason, NewData}` - `{stop, Reason}`** - Stop the server with reason `Reason`. If the `NewData` field is used, first - update the server data. - -- **`{stop_and_reply, Reason, NewData, ReplyActions}` - `{stop_and_reply, Reason, ReplyActions}`** +- **`{repeat_state, NewData [, Actions]} | + repeat_state_and_data |{repeat_state_and_data, Actions}`** + Same as the `keep_state` or `keep_state_and_data` values, but if + [_state enter calls_](#state-enter-calls) are enabled; + repeat it as if this state was entered again. In this case `State` + and `OldState` becomes equal in the repeated _state enter call_ + since the state is re-entered from itself. + +- **`{stop, Reason [, NewData]}`** + Stop the server with reason `Reason`. If the `NewData` field is used, + first update the server data. + +- **`{stop_and_reply, Reason, [NewData, ] ReplyActions}`** Same as the `stop` values, but first execute the given - [_transition actions_ ](statem.md#transition-actions)that may only be reply - actions. + [_transition actions_](#transition-actions) + that may only be reply actions. ### The First State To decide the first state the -[`Module:init(Args)` ](`c:gen_statem:init/1`)callback function is called before -any [_state callback_](statem.md#state-callback) is called. This function -behaves like a _state callback_ function, but gets its only argument `Args` from -the `gen_statem` [`start/3,4` ](`gen_statem:start/3`)or -[`start_link/3,4` ](`gen_statem:start_link/3`)function, and returns -`{ok, State, Data}` or `{ok, State, Data, Actions}`. If you use the -[`postpone`](statem.md#postponing-events) action from this function, that action +[`Module:init(Args)`](`c:gen_statem:init/1`) callback function is called +before any [_state callback_](#state-callback) is called. This function +behaves like a _state callback_ function, but gets its only argument `Args` +from the `gen_statem` [`start/3,4`](`gen_statem:start/3`) or +[`start_link/3,4`](`gen_statem:start_link/3`) function, and returns +`{ok, State, Data}` or `{ok, State, Data, Actions}`. If you use the +[`postpone`](#postponing-events) action from this function, that action is ignored, since there is no event to postpone. -## Transition Actions +Transition Actions +------------------ In the first section -([Event-Driven State Machines](statem.md#event-driven-state-machines)), actions +([_Event-Driven State Machines_](#event-driven-state-machines)), actions were mentioned as a part of the general state machine model. These general actions are implemented with the code that _callback module_ `gen_statem` executes in an event-handling callback function before returning to the `m:gen_statem` engine. There are more specific _transition actions_ that a callback function can -command the `gen_statem` engine to do after the callback function return. These -are commanded by returning a list of [actions](`t:gen_statem:action/0`) in the -[return value ](`t:gen_statem:state_callback_result/1`)from the -[callback function](`c:gen_statem:'StateName'/3`). These are the possible +command the `gen_statem` engine to do after the callback function return. +These are commanded by returning a list of [_actions_](`t:gen_statem:action/0`) +in the [return value](`t:gen_statem:state_callback_result/2`) from the +[_callback function_](`c:gen_statem:'StateName'/3`). These are the possible _transition actions_: -- **[`postpone`](`t:gen_statem:postpone/0`) - `{postpone, Boolean}`** - - If set postpone the current event, see section - [Postponing Events](statem.md#postponing-events). - -- **[`hibernate`](`t:gen_statem:hibernate/0`) - `{hibernate, Boolean}`** - - If set hibernate the `gen_statem`, treated in section - [Hibernation](statem.md#hibernation). - -- **[`{state_timeout, Time, EventContent}`](`t:gen_statem:state_timeout/0`) - `{state_timeout, Time, EventContent, Opts}` - [`{state_timeout, update, EventContent}`](`t:gen_statem:timeout_update_action/0`) - [`{state_timeout, cancel}`](`t:gen_statem:timeout_cancel_action/0`)** - - Start, update or cancel a state time-out, read more in sections - [Time-Outs](statem.md#time-outs) and - [State Time-Outs](statem.md#state-time-outs). - -- **[`{{timeout, Name}, Time, EventContent}`](`t:gen_statem:generic_timeout/0`) - `{{timeout, Name}, Time, EventContent, Opts}` - [`{{timeout, Name}, update, EventContent}`](`t:gen_statem:timeout_update_action/0`) - [`{{timeout, Name}, cancel}`](`t:gen_statem:timeout_cancel_action/0`)** - - Start, update or cancel a generic time-out, read more in sections - [Time-Outs](statem.md#time-outs) and - [Generic Time-Outs](statem.md#generic-time-outs). - -- **[`{timeout, Time, EventContent}`](`t:gen_statem:event_timeout/0`) - `{timeout, Time, EventContent, Opts}` - `Time`** - - Start an event time-out, see more in sections [Time-Outs](statem.md#time-outs) - and [Event Time-Outs](statem.md#event-time-outs). +- **[`{postpone, Boolean}`](`t:gen_statem:postpone/0`)** - + If `true` postpone the current event, see section + [_Postponing Events_](#postponing-events). + +- **[`{hibernate, Boolean`](`t:gen_statem:hibernate/0`)** - + If `true` hibernate the `gen_statem`, treated in section + [_Hibernation_](#hibernation). + +- **[`{state_timeout, Time, EventContent + [, Opts]}`](`t:gen_statem:state_timeout/0`)` |`**\ + **[`{state_timeout, update, + EventContent}`](`t:gen_statem:timeout_update_action/0`)` |`**\ + **[`{state_timeout, cancel}`](`t:gen_statem:timeout_cancel_action/0`)** - + Start, update, or cancel a _state time-out_, read more in sections + [_Time-Outs_](#time-outs) and + [_State Time-Outs_](#state-time-outs). + +- **[`{{timeout, Name}, Time, EventContent + [, Opts]}`](`t:gen_statem:generic_timeout/0`)` |`**\ + **[`{{timeout, Name}, update, + EventContent}`](`t:gen_statem:timeout_update_action/0`)` |`**\ + **[`{{timeout, Name}, cancel}`](`t:gen_statem:timeout_cancel_action/0`)** - + Start, update, or cancel a _generic time-out_, read more in sections + [_Time-Outs_](#time-outs) and + [_Generic Time-Outs_](#generic-time-outs). + +- **[`{timeout, Time, EventContent + [, Opts]}`](`t:gen_statem:event_timeout/0`)** - + Start an _event time-out_, see more in sections [_Time-Outs_](#time-outs) + and [_Event Time-Outs_](#event-time-outs). - **[`{reply, From, Reply}`](`t:gen_statem:reply_action/0`)** - Reply to a caller, mentioned at the end of section - [All State Events](statem.md#all-state-events). + [_All State Events_](#all-state-events). - **[`{next_event, EventType, EventContent}`](`t:gen_statem:action/0`)** - Generate the next event to handle, see section - [Inserted Events](statem.md#inserted-events). - -- **[`{change_callback_module, NewModule}`](`t:gen_statem:action/0`)** - Change - the [_callback module_ ](statem.md#callback-module)for the running server. - This can be done during any _state transition_, whether it is a _state change_ - or not, but it can _not_ be done from a - [_state enter call_](statem.md#state-enter-calls). - -- **[`{push_callback_module, NewModule}`](`t:gen_statem:action/0`)** - Push the - current _callback module_ to the top of an internal stack of callback modules - and set the new [_callback module_ ](statem.md#callback-module)for the running - server. Otherwise like `{change_callback_module, NewModule}` above. - -- **[`pop_callback_module`](`t:gen_statem:action/0`)** - Pop the top module from - the internal stack of callback modules and set it to be the new - [_callback module_ ](statem.md#callback-module)for the running server. If the + [_Inserted Events_](#inserted-events). + +- **[`{change_callback_module, NewModule}`](`t:gen_statem:action/0`)** - + Change the [_callback module_](#callback-module) for the running server. + This can be done during any _state transition_, whether it is + a _state change_ or not, but it _cannot_ be done from a + [_state enter call_](#state-enter-calls). + +- **[`{push_callback_module, NewModule}`](`t:gen_statem:action/0`)** - + Push the current _callback module_ to the top of an internal stack + of callback modules and set the new [_callback module_](#callback-module) + for the running server. Otherwise like + `{change_callback_module, NewModule}` above. + +- **[`pop_callback_module`](`t:gen_statem:action/0`)** - Pop the top module + from the internal stack of callback modules and set it to be the new + [_callback module_](#callback-module) for the running server. If the stack is empty the server fails. Otherwise like `{change_callback_module, NewModule}` above. @@ -351,19 +381,20 @@ instead of relative time (using the `Opts` field). Out of these _transition actions_, the only immediate action is `reply` for replying to a caller. The other actions are collected and -handled later during the _state transition_. [Inserted -Events](statem.md#inserted-events) are stored and inserted all +handled later during the _state transition_. +[_Inserted events_](#inserted-events) are stored and inserted all together, and the rest set transition options where the last of a specific type override the previous. See the description of a _state transition_ in module `m:gen_statem` for type [`transition_option()`](`t:gen_statem:transition_option/0`). -The different [Time-Outs](statem.md#time-outs) and -[`next_event`](statem.md#inserted-events) actions generate new events with +The different [_Time-Outs_](#time-outs) and +[`next_event`](#inserted-events) actions generate new events with corresponding -[Event Types and Event Content ](statem.md#event-types-and-event-content). +[_event types and event content_](#event-types-and-event-content). -## Event Types and Event Content +Event Types and Event Content +----------------------------- Events are categorized in different [_event types_](`t:gen_statem:event_type/0`). Events of all types are for a @@ -374,51 +405,55 @@ depends on the `EventType`. The following is a complete list of _event types_ and from where they come: - **[`cast`](`t:gen_statem:external_event_type/0`)** - Generated by - [`gen_statem:cast(ServerRef, Msg)` ](`gen_statem:cast/2`)where `Msg` becomes + [`gen_statem:cast(ServerRef, Msg)`](`gen_statem:cast/2`) where `Msg` becomes the `EventContent`. -- **[`{call,From}`](`t:gen_statem:external_event_type/0`)** - Generated by - [`gen_statem:call(ServerRef, Request)` ](`gen_statem:call/2`)where `Request` - becomes the `EventContent`. `From` is the reply address to use when replying - either through the _transition action_ `{reply,From,Reply}` or by calling - [`gen_statem:reply(From, Reply)` ](`gen_statem:reply/1`)from the _callback - module_. - -- **[`info`](`t:gen_statem:external_event_type/0`)** - Generated by any regular - process message sent to the `gen_statem` process. The process message becomes - the `EventContent`. +- **[`{call, From}`](`t:gen_statem:external_event_type/0`)** - Generated by + [`gen_statem:call(ServerRef, Request)`](`gen_statem:call/2`), + [`gen_statem:send_request(ServerRef, + Request)`](`gen_statem:send_request/2`), or + [`gen_statem:send_request(ServerRef, Request, + _, _)`](`gen_statem:send_request/4`) where `Request` becomes + the `EventContent`. `From` is the reply address to use when replying + either through the _transition action_ `{reply, From, Reply}`, + or by calling [`gen_statem:reply(From, Reply)`](`gen_statem:reply/1`) + from the _callback module_. + +- **[`info`](`t:gen_statem:external_event_type/0`)** - Generated by + any regular process message sent to the `gen_statem` process. + The process message becomes the `EventContent`. - **[`state_timeout`](`t:gen_statem:timeout_event_type/0`)** - Generated by _transition action_ - [`{state_timeout,Time,EventContent}` ](`t:gen_statem:timeout_action/0`)state - timer timing out. Read more in sections [Time-Outs](statem.md#time-outs) and - [State Time-Outs](statem.md#state-time-outs). + [`{state_timeout, Time, EventContent}`](`t:gen_statem:timeout_action/0`) + when the time-out expires. Read more in sections [_Time-Outs_](#time-outs) + and [_State Time-Outs_](#state-time-outs). -- **[`{timeout,Name}`](`t:gen_statem:timeout_event_type/0`)** - Generated by +- **[`{timeout, Name}`](`t:gen_statem:timeout_event_type/0`)** - Generated by _transition action_ - [`{{timeout,Name},Time,EventContent}` ](`t:gen_statem:timeout_action/0`)generic - timer timing out. Read more in sections [Time-Outs](statem.md#time-outs) and - [Generic Time-Outs](statem.md#generic-time-outs). + [`{{timeout, Name},Time, EventContent}`](`t:gen_statem:timeout_action/0`) + when the time-out expires. Read more in sections [_Time-Outs_](#time-outs) + and [_Generic Time-Outs_](#generic-time-outs). - **[`timeout`](`t:gen_statem:timeout_event_type/0`)** - Generated by _transition action_ - [`{timeout,Time,EventContent}` ](`t:gen_statem:timeout_action/0`)(or its short - form `Time`) event timer timing out. Read more in sections - [Time-Outs](statem.md#time-outs) and - [Event Time-Outs](statem.md#event-time-outs). + [`{timeout, Time, EventContent}`](`t:gen_statem:timeout_action/0`) + (or its short form `Time`) when the time-out expires. Read more in sections + [_Time-Outs_](#time-outs) and [_Event Time-Outs_](#event-time-outs). - **[`internal`](`t:gen_statem:event_type/0`)** - Generated by _transition - action_ [`{next_event,internal,EventContent}`](`t:gen_statem:action/0`). All - _event types_ above can also be generated using the `next_event` action: - `{next_event,EventType,EventContent}`. + action_ [`{next_event, internal, EventContent}`](`t:gen_statem:action/0`). + All _event types_ above can also be generated using the `next_event` action: + `{next_event, EventType, EventContent}`. -## State Enter Calls +State Enter Calls +----------------- -The `gen_statem` behaviour can if this is enabled, regardless of _callback -mode_, automatically -[call the state callback ](`t:gen_statem:state_enter/0`)with special arguments -whenever the state changes so you can write state enter actions near the rest of -the _state transition_ rules. It typically looks like this: +The `gen_statem` behaviour can, if this is enabled, regardless of _callback +mode_, automatically call the [_state callback_](`t:gen_statem:state_enter/0`) +with special arguments whenever the state changes, so you can write +state enter actions near the rest of the _state transition_ rules. +It typically looks like this: ```erlang StateName(enter, OldState, Data) -> @@ -430,88 +465,91 @@ StateName(EventType, EventContent, Data) -> ``` Since the _state enter call_ is not an event there are restrictions on the -allowed return value and -[State Transition Actions](statem.md#transition-actions). You must not change the -state, [postpone](statem.md#postponing-events) this non-event, -[insert any events](statem.md#inserted-events), or change the -[_callback module_](statem.md#callback-module). +allowed return value and state [_transition actions_](#transition-actions). +You must not change the state, [postpone](#postponing-events) this non-event, +[insert any events](#inserted-events), or change the +[_callback module_](#callback-module). -The first state that is entered will get a _state enter call_ with `OldState` -equal to the current state. +The first state that is entered after `c:gen_statem:init/1` will get +a _state enter call_ with `OldState` equal to the current state. You may repeat the _state enter call_ using the `{repeat_state,...}` return -value from the [state callback](statem.md#state-callback). In this case +value from the [_state callback_](#state-callback). In this case `OldState` will also be equal to the current state. Depending on how your state machine is specified, this can be a very useful -feature, but it forces you to handle the _state enter calls_ in all states. See -also the [State Enter Actions ](statem.md#state-enter-actions)section. +feature, but it forces you to handle the _state enter calls_ in all states. +See also the [_State Enter Actions_](#state-enter-actions) section. -## Time-Outs +Time-Outs +--------- Time-outs in `gen_statem` are started from a -[_transition action_ ](statem.md#transition-actions)during a state transition -that is when exiting from the [_state callback_](statem.md#state-callback). +[_transition action_](#transition-actions) during a state transition +that is when exiting from the [_state callback_](#state-callback). There are 3 types of time-outs in `gen_statem`: - **[`state_timeout`](`t:gen_statem:state_timeout/0`)** - There is one - [State Time-Out](statem.md#state-time-outs) that is automatically canceled by + [_state time-out_](#state-time-outs) that is automatically canceled by a _state change_. - **[`{timeout, Name}`](`t:gen_statem:generic_timeout/0`)** - There are any - number of [Generic Time-Outs](statem.md#generic-time-outs) differing by their + number of [_generic time-outs_](#generic-time-outs) differing by their `Name`. They have no automatic canceling. - **[`timeout`](`t:gen_statem:event_timeout/0`)** - There is one - [Event Time-Out](statem.md#event-time-outs) that is automatically canceled by - any event. Note that [postponed ](statem.md#postponing-events)and - [inserted](statem.md#inserted-events) events cancel this time-out just as + [_event time-out_](#event-time-outs) that is automatically canceled by + any event. Note that [postponed](#postponing-events) and + [inserted](#inserted-events) events cancel this time-out just as external events do. -When a time-out is started any running time-out of the same type -(`state_timeout`, `{timeout, Name}`, or `timeout`) is canceled, that is, the -time-out is restarted with the new time. +When a time-out is started, any running time-out of the same type +(`state_timeout`, `{timeout, Name}`, or `timeout`) is canceled, that is, +the time-out is restarted with the new time and event content. -All time-outs has an `EventContent` that is part of the -[_transition action_ ](statem.md#transition-actions)that starts the time-out. +All time-outs have an `EventContent` that is part of the +[_transition action_](#transition-actions) that starts the time-out. Different `EventContent`s does not create different time-outs. The -`EventContent` is delivered to the [_state callback_](statem.md#state-callback) +`EventContent` is delivered to the [_state callback_](#state-callback) when the time-out expires. ### Canceling a Time-Out -Starting a time-out with the `infinity` time value ensures it never times -out, essentially preventing it from even starting, and any running +Starting a time-out with the `infinity` time value would never time out, +which is optimized by not even starting it, and any running time-out with the same tag will be canceled. The `EventContent` will in this case be ignored, so it makes sense to set it to `undefined`. -A more explicit way to cancel a timer is to use a -[_transition action_ ](statem.md#transition-actions)on the form -[`{TimeoutType, cancel}` ](`t:gen_statem:timeout_cancel_action/0`). +A more explicit way to cancel a time-out is to use a +[_transition action_](#transition-actions) on the form +[`{TimeoutType, cancel}`](`t:gen_statem:timeout_cancel_action/0`). ### Updating a Time-Out While a time-out is running, its `EventContent` can be updated using a -[_transition action_ ](statem.md#transition-actions)on the form -[`{TimeoutType, update, NewEventContent}` ](`t:gen_statem:timeout_update_action/0`). +[_transition action_](#transition-actions) on the form +[`{TimeoutType, update, +NewEventContent}`](`t:gen_statem:timeout_update_action/0`). If this feature is used while no such `TimeoutType` is running, a time-out event is immediately delivered as when starting a -[Time-Out Zero](statem.md#time-out-zero). +[zero time-out](#zero-time-out). -### Time-Out Zero +### Zero Time-Out If a time-out is started with the time `0` it will actually not be started. Instead the time-out event will immediately be inserted to be processed after any events already enqueued, and before any not yet received external events. + Note that some time-outs are automatically canceled so if you for example -combine [postponing](statem.md#postponing-events) an event in a _state change_ -with starting an [event time-out](statem.md#event-time-outs) with time `0` there -will be no time-out event inserted since the event time-out is canceled by the -postponed event that is delivered due to the state change. +combine [postponing](#postponing-events) an event in a _state change_ +with starting an [_event time-out_](#event-time-outs) with time `0` there +will be no time-out event inserted since the _event time-out_ is canceled by +the postponed event that is delivered due to the state change. -## Example +Example +------- A door with a code lock can be seen as a state machine. Initially, the door is locked. When someone presses a button, a `{button, Button}` @@ -537,8 +575,8 @@ stateDiagram-v2 open --> locked : state_timeout\n* do_lock() ``` -This code lock state machine can be implemented using `m:gen_statem` with the -following _callback module_: +This code lock state machine can be implemented using `m:gen_statem` with +the following _callback module_: ```erlang -module(code_lock). @@ -607,7 +645,8 @@ terminate(_Reason, State, _Data) -> The code is explained in the next sections. -## Starting gen_statem +Starting gen_statem +------------------- In the example in the previous section, `gen_statem` is started by calling `code_lock:start_link(Code)`: @@ -617,38 +656,39 @@ start_link(Code) -> gen_statem:start_link({local,?NAME}, ?MODULE, Code, []). ``` -`start_link/1` calls function `gen_statem:start_link/4`, which spawns and links to -a new process, a `gen_statem`. +`start_link/1` calls function `gen_statem:start_link/4`, +which spawns and links to a new process, a `gen_statem`. - The first argument, `{local,?NAME}`, specifies the name. In this case, the `gen_statem` is locally registered as `code_lock` through the macro `?NAME`. If the name is omitted, the `gen_statem` is not registered. Instead its pid - must be used. The name can also be specified as `{global,Name}`, then the + must be used. The name can also be specified as `{global, Name}`, then the `gen_statem` is registered using `global:register_name/2` in Kernel. -- The second argument, `?MODULE`, is the name of the _callback module_, that is, - the module where the callback functions are located, which is this module. +- The second argument, `?MODULE`, is the name of the _callback module_, + that is, the module where the callback functions are located, + which is this module. The interface functions (`start_link/1` and `button/1`) are located in the - same module as the callback functions (`init/1`, `locked/3`, and `open/3`). It - is normally good programming practice to have the client-side code and the - server-side code contained in the same module. + same module as the callback functions (`init/1`, `locked/3`, and `open/3`). + It is normally good programming practice to have the client-side code + and the server-side code contained in the same module. -- The third argument, `Code`, is a list of digits, which is the correct unlock - code that is passed to callback function `init/1`. +- The third argument, `Code`, is a list of digits, which is the correct + unlock code that is passed to callback function `init/1`. - The fourth argument, `[]`, is a list of options. For the available options, see `gen_statem:start_link/3`. If name registration succeeds, the new `gen_statem` process calls callback function `code_lock:init(Code)`. This function is expected to return -`{ok, State, Data}`, where `State` is the initial state of the `gen_statem`, in -this case `locked`; assuming that the door is locked to begin with. `Data` is -the internal server data of the `gen_statem`. Here the server data is a -[map](`m:maps`) with key `code` that stores the correct button sequence, key -`length` store its length, and key `buttons` that stores the collected buttons -up to the same length. +`{ok, State, Data}`, where `State` is the initial state of the `gen_statem`, +in this case `locked`; assuming that the door is locked to begin with. +`Data` is the internal server data of the `gen_statem`. Here the server data +is a [`map()`](`m:maps`) with key `code` that stores the correct +button sequence, key `length` store its length, and key `buttons` +that stores the collected buttons up to the same length. ```erlang init(Code) -> @@ -657,27 +697,28 @@ init(Code) -> {ok, locked, Data}. ``` -Function [`gen_statem:start_link/3,4`](`gen_statem:start_link/3`) is synchronous. It -does not return until the `gen_statem` is initialized and is ready to receive -events. +Function [`gen_statem:start_link/3,4`](`gen_statem:start_link/3`) +is synchronous. It does not return until the `gen_statem` is initialized +and is ready to receive events. -Function [`gen_statem:start_link/3,4`](`gen_statem:start_link/3`) must be used if -the `gen_statem` is part of a supervision tree, that is, started by a -supervisor. Another function, [`gen_statem:start/3,4`](`gen_statem:start/3`) can be -used to start a standalone `gen_statem`, meaning it is not part of a supervision -tree. +Function [`gen_statem:start_link/3,4`](`gen_statem:start_link/3`) +must be used if the `gen_statem` is part of a supervision tree, that is, +started by a supervisor. Function, +[`gen_statem:start/3,4`](`gen_statem:start/3`) can be used to start +a standalone `gen_statem`, meaning it is not part of a supervision tree. -Function [`Module:callback_mode/0`](`c:gen_statem:callback_mode/0`) selects the -[`CallbackMode`](statem.md#callback-modes) for the _callback module_, in this -case [`state_functions`](`t:gen_statem:callback_mode/0`). That is, each state -has its own handler function: +Function [`Module:callback_mode/0`](`c:gen_statem:callback_mode/0`) selects +the [`CallbackMode`](#callback-modes) for the _callback module_, +in this case [`state_functions`](`t:gen_statem:callback_mode/0`). +That is, each state has its own handler function: ```erlang callback_mode() -> state_functions. ``` -## Handling Events +Handling Events +--------------- The function notifying the code lock about a button event is implemented using `gen_statem:cast/2`: @@ -687,17 +728,17 @@ button(Button) -> gen_statem:cast(?NAME, {button,Button}). ``` -The first argument is the name of the `gen_statem` and must agree with the name -used to start it. So, we use the same macro `?NAME` as when starting. -`{button,Button}` is the event content. +The first argument is the name of the `gen_statem` and must agree with +the name used to start it. So, we use the same macro `?NAME` as when starting. +`{button, Button}` is the event content. The event is sent to the `gen_statem`. When the event is received, the -`gen_statem` calls `StateName(cast, Event, Data)`, which is expected to return a -tuple `{next_state, NewStateName, NewData}`, or -`{next_state, NewStateName, NewData, Actions}`. `StateName` is the name of the -current state and `NewStateName` is the name of the next state to go to. -`NewData` is a new value for the server data of the `gen_statem`, and `Actions` -is a list of actions to be performed by the `gen_statem` engine. +`gen_statem` calls `StateName(cast, Event, Data)`, which is expected +to return a tuple `{next_state, NewStateName, NewData}`, or +`{next_state, NewStateName, NewData, Actions}`. `StateName` is the name +of the current state and `NewStateName` is the name of the next state. +`NewData` is a new value for the server data of the `gen_statem`, +and `Actions` is a list of actions to be performed by the `gen_statem` engine. ```erlang locked( @@ -727,31 +768,32 @@ either unlocked and the `gen_statem` goes to state `open`, or the door remains in state `locked`. When changing to state `open`, the collected buttons are reset, the lock -unlocked, and a state timer for 10 seconds is started. +unlocked, and a _state time-out_ for 10 seconds is started. ```erlang open(cast, {button,_}, Data) -> {next_state, open, Data}. ``` -In state `open`, a button event is ignored by staying in the same state. This -can also be done by returning `{keep_state, Data}`, or in this case since `Data` -is unchanged, by returning `keep_state_and_data`. +In state `open`, a button event is ignored by staying in the same state. +This can also be done by returning `{keep_state, Data}`, or in this case +since `Data` is unchanged, by returning `keep_state_and_data`. -## State Time-Outs +State Time-Outs +--------------- -When a correct code has been given, the door is unlocked and the following tuple -is returned from `locked/2`: +When a correct code has been given, the door is unlocked and the following +tuple is returned from `locked/2`: ```erlang {next_state, open, Data#{buttons := []}, [{state_timeout,10_000,lock}]}; % Time in milliseconds ``` -10,000 is a time-out value in milliseconds. After this time (10 seconds), a -time-out occurs. Then, `StateName(state_timeout, lock, Data)` is called. The -time-out occurs when the door has been in state `open` for 10 seconds. After -that the door is locked again: +10,000 is a time-out value in milliseconds. After this time (10 seconds), +a time-out occurs. Then, `StateName(state_timeout, lock, Data)` is called. +The time-out occurs when the door has been in state `open` for 10 seconds. +After that the door is locked again: ```erlang open(state_timeout, lock, Data) -> @@ -759,21 +801,22 @@ open(state_timeout, lock, Data) -> {next_state, locked, Data}; ``` -The timer for a state time-out is automatically canceled when the state machine -does a _state change_. +The timer for a _state time-out_ is automatically canceled when +the state machine does a _state change_. -You can restart, cancel or update a state time-out. See section -[Time-Outs](statem.md#time-outs) for details. +You can restart, cancel, or update a _state time-out_. See section +[_Time-Outs_](#time-outs) for details. -## All State Events +All State Events +---------------- Sometimes events can arrive in any state of the `gen_statem`. It is convenient -to handle these in a common state handler function that all state functions call -for events not specific to the state. +to handle these in a common state handler function that all state functions +call for events not specific to the state. -Consider a `code_length/0` function that returns the length of the correct code. -We dispatch all events that are not state-specific to the common function -`handle_common/3`: +Consider a `code_length/0` function that returns the length +of the correct code. We dispatch all events that are not state-specific +to the common function `handle_common/3`: ```erlang ... @@ -825,7 +868,7 @@ open(...) -> ... ; ``` This example uses `gen_statem:call/2`, which waits for a reply from the server. -The reply is sent with a `{reply,From,Reply}` tuple in an action list in the +The reply is sent with a `{reply, From, Reply}` tuple in an action list in the `{keep_state, ...}` tuple that retains the current state. This return form is convenient when you want to stay in the current state but do not know or care about what it is. @@ -838,13 +881,14 @@ If the common _state callback_ needs to know the current state a function ?FUNCTION_NAME(T, C, D) -> handle_common(T, C, ?FUNCTION_NAME, D)). ``` -## One State Callback +One State Callback +------------------ -If [_callback mode_ ](statem.md#callback-modes)`handle_event_function` is used, +If [_callback mode_](#callback-modes) `handle_event_function` is used, all events are handled in -[`Module:handle_event/4`](`c:gen_statem:handle_event/4`) and we can (but do not -have to) use an event-centered approach where we first branch depending on event -and then depending on state: +[`Module:handle_event/4`](`c:gen_statem:handle_event/4`) and we can +(but do not have to) use an event-centered approach where we first branch +depending on event and then depending on state: ```erlang ... @@ -887,18 +931,19 @@ handle_event( ... ``` -## Stopping +Stopping +-------- ### In a Supervision Tree If the `gen_statem` is part of a supervision tree, no stop function is needed. -The `gen_statem` is automatically terminated by its supervisor. Exactly how this -is done is defined by a [shutdown strategy](sup_princ.md#shutdown) set in the -supervisor. +The `gen_statem` is automatically terminated by its supervisor. Exactly how +this is done is defined by a [shutdown strategy](sup_princ.md#shutdown) +set in the supervisor. -If it is necessary to clean up before termination, the shutdown strategy must be -a time-out value and the `gen_statem` must in function `init/1` set itself to -trap exit signals by calling +If it is necessary to clean up before termination, the shutdown strategy +must be a time-out value and the `gen_statem` must in function `init/1` +set itself to trap exit signals by calling [`process_flag(trap_exit, true)`](`erlang:process_flag/2`): ```erlang @@ -911,8 +956,9 @@ init(Args) -> When ordered to shut down, the `gen_statem` then calls callback function `terminate(shutdown, State, Data)`. -In this example, function `terminate/3` locks the door if it is open, so we do -not accidentally leave the door open when the supervision tree terminates: +In this example, function `terminate/3` locks the door if it is open, +so we do not accidentally leave the door open +when the supervision tree terminates: ```erlang terminate(_Reason, State, _Data) -> @@ -922,8 +968,9 @@ terminate(_Reason, State, _Data) -> ### Standalone gen_statem -If the `gen_statem` is not part of a supervision tree, it can be stopped using -[`gen_statem:stop/1`](`gen_statem:stop/1`), preferably through an API function: +If the `gen_statem` is not part of a supervision tree, it can be stopped +using [`gen_statem:stop/1`](`gen_statem:stop/1`), preferably through +an API function: ```erlang ... @@ -934,22 +981,23 @@ stop() -> gen_statem:stop(?NAME). ``` -This makes the `gen_statem` call callback function `terminate/3` just like for a -supervised server and waits for the process to terminate. +This makes the `gen_statem` call callback function `terminate/3` just like +for a supervised server and waits for the process to terminate. -## Event Time-Outs +Event Time-Outs +--------------- -A time-out feature inherited from `gen_statem`'s predecessor `m:gen_fsm`, is an -event time-out, that is, if an event arrives the timer is canceled. You get -either an event or a time-out, but not both. +A time-out feature inherited from `gen_statem`'s predecessor `m:gen_fsm`, +is an _event time-out_, that is, if an event arrives the timer is canceled. +You get either an event or a time-out, but not both. It is ordered by the -[_transition action_ ](statem.md#transition-actions)`{timeout,Time,EventContent}`, +[_transition action_](#transition-actions) `{timeout, Time, EventContent}`, or just an integer `Time`, even without the enclosing actions list (the latter is a form inherited from `gen_fsm`). -This type of time-out is useful, for example, to act on inactivity. Let us restart -the code sequence if no button is pressed for say 30 seconds: +This type of time-out is useful, for example, to act on inactivity. +Let's restart the code sequence if no button is pressed for say 30 seconds: ```erlang ... @@ -962,40 +1010,43 @@ locked( ... true -> % Incomplete | Incorrect {next_state, locked, Data#{buttons := NewButtons}, - 30000} % Time in milliseconds + 30_000} % Time in milliseconds ... ``` -Whenever we receive a button event we start an event time-out of 30 seconds, and -if we get an _event type_ of `timeout` we reset the remaining code sequence. +Whenever we receive a button event we start an _event time-out_ of 30 seconds, +and if we get an _event type_ of `timeout` we reset the remaining +code sequence. -An event time-out is canceled by any other event so you either get +An _event time-out_ is canceled by any other event so you either get some other event or the time-out event. Therefore, canceling, -restarting, or updating an event time-out is neither possible nor -necessary. Whatever event you act on has already canceled the event -time-out, so there is never a running event time-out while the _state -callback_ executes. +restarting, or updating an _event time-out_ is neither possible nor +necessary. Whatever event you act on has already canceled +the _event time-out_, so there is never a running _event time-out_ +while the _state callback_ executes. -Note that an event time-out does not work well when you have for example a -status call as in section [All State Events](statem.md#all-state-events), or -handle unknown events, since all kinds of events will cancel the event time-out. +Note that an _event time-out_ does not work well when you have for example a +status call as in section [_All State Events_](#all-state-events), or +handle unknown events, since all kinds of events will cancel +the _event time-out_. -## Generic Time-Outs +Generic Time-Outs +----------------- -The previous example of state time-outs only work if the state machine stays in -the same state during the time-out time. And event time-outs only work if no -disturbing unrelated events occur. +The previous example of _state time-outs_ only work if the state machine stays +in the same state during the time-out time. And _event time-outs_ only work +if no disturbing unrelated events occur. You may want to start a timer in one state and respond to the time-out in another, maybe cancel the time-out without changing states, or perhaps run multiple time-outs in parallel. All this can be accomplished with -[generic time-outs](`t:gen_statem:generic_timeout/0`). They may look a little -bit like [event time-outs](`t:gen_statem:event_timeout/0`) but contain a name to -allow for any number of them simultaneously and they are not automatically -canceled. +[_generic time-outs_](`t:gen_statem:generic_timeout/0`). They may look a little +bit like [_event time-outs_](`t:gen_statem:event_timeout/0`) but contain +a name to allow for any number of them simultaneously and they are +not automatically canceled. -Here is how to accomplish the state time-out in the previous example by instead -using a generic time-out named for example `open`: +Here is how to accomplish the _state time-out_ in the previous example +by instead using a _generic time-out_ named for example `open`: ```erlang ... @@ -1018,31 +1069,32 @@ open(cast, {button,_}, Data) -> ... ``` -Specific generic time-outs can just as -[state time-outs](statem.md#state-time-outs) be restarted or canceled by -setting it to a new time or `infinity`. +Specific _generic time-outs_ can just as [_state time-outs_](#state-time-outs) +be restarted or canceled by setting it to a new time or `infinity`. -In this particular case we do not need to cancel the time-out since the time-out -event is the only possible reason to do a _state change_ from `open` to -`locked`. +In this particular case we do not need to cancel the time-out since +the time-out event is the only possible reason to do a _state change_ +from `open` to `locked`. -Instead of bothering with when to cancel a time-out, a late time-out event can -be handled by ignoring it if it arrives in a state where it is known to be late. +Instead of bothering with when to cancel a time-out, a late time-out event +can be handled by ignoring it if it arrives in a state +where it is known to be late. -You can restart, cancel, or update a generic time-out. See section -[Time-Outs](statem.md#time-outs) for details. +You can restart, cancel, or update a _generic time-out_. +See section [_Time-Outs_](#time-outs) for details. -## Erlang Timers +Erlang Timers +------------- The most versatile way to handle time-outs is to use Erlang Timers; see -[`erlang:start_timer/3,4`](`erlang:start_timer/4`). Most time-out tasks can be -performed with the time-out features in `m:gen_statem`, but an example of one that -cannot is if you should need the return value from -[`erlang:cancel_timer(Tref)`](`erlang:cancel_timer/2`), that is, the remaining -time of the timer. +[`erlang:start_timer/3,4`](`erlang:start_timer/4`). Most time-out tasks +can be performed with the time-out features in `m:gen_statem`, +but an example of one that cannot is if you should need the return value +from [`erlang:cancel_timer(Tref)`](`erlang:cancel_timer/2`), that is, +the remaining time of the timer. -Here is how to accomplish the state time-out in the previous example by instead -using an Erlang Timer: +Here is how to accomplish the _state time-out_ in the previous example +by instead using an Erlang Timer: ```erlang ... @@ -1067,34 +1119,36 @@ open(cast, {button,_}, Data) -> ... ``` -Removing the `timer` key from the map when we do a _state change_ to `locked` is -not strictly necessary since we can only get into state `open` with an updated -`timer` map value. But it can be nice to not have outdated values in the state -`Data`. +Removing the `timer` key from the map when we do a _state change_ to `locked` +is not strictly necessary since we can only get into state `open` +with an updated `timer` map value. But it can be nice to not have +outdated values in the state `Data`. If you need to cancel a timer because of some other event, you can use [`erlang:cancel_timer(Tref)`](`erlang:cancel_timer/2`). Note that no time-out -message will arrive after this (because the timer has been explicitly canceled), -unless you have already postponed one earlier (see the next section), so ensure -that you do not accidentally postpone such messages. Also note that a time-out -message may arrive during a _state callback_ that is canceling the timer, so -you may have to read out such a message from the process mailbox, depending on +message will arrive after this (because the timer has been +explicitly canceled), unless you have already postponed one earlier +(see the next section), so ensure that you do not accidentally +postpone such messages. Also note that a time-out message may arrive +during a _state callback_ that is canceling the timer, so you may have to +read out such a message from the process mailbox, depending on the return value from [`erlang:cancel_timer(Tref)`](`erlang:cancel_timer/2`). Another way to handle a late time-out can be to not cancel it, but to ignore it if it arrives in a state where it is known to be late. -## Postponing Events +Postponing Events +----------------- -If you want to ignore a particular event in the current state and handle it in a -future state, you can postpone the event. A postponed event is retried after a -_state change_, that is, `OldState =/= NewState`. +If you want to ignore a particular event in the current state and handle it +in a future state, you can postpone the event. A postponed event +is retried after a _state change_, that is, `OldState =/= NewState`. Postponing is ordered by the -[_transition action_ ](statem.md#transition-actions)`postpone`. +[_transition action_](#transition-actions) `postpone`. -In this example, instead of ignoring button events while in the `open` state, we -can postpone them and they are queued and later handled in the `locked` state: +In this example, instead of ignoring button events while in the `open` state, +we can postpone them handle them later in the `locked` state: ```erlang ... @@ -1107,25 +1161,25 @@ Since a postponed event is only retried after a _state change_, you have to think about where to keep a state data item. You can keep it in the server `Data` or in the `State` itself, for example by having two more or less identical states to keep a boolean value, or by using a complex state (see -section [Complex State](statem.md#complex-state)) with -[_callback mode_](statem.md#callback-modes) -[`handle_event_function`](`t:gen_statem:callback_mode/0`). If a change in the -value changes the set of events that is handled, the value should be kept -in the State. Otherwise no postponed events will be retried since only the -server `Data` changes. +section [_Complex State_](#complex-state)) with +[_callback mode_](#callback-modes) +[`handle_event_function`](`t:gen_statem:callback_mode/0`). If a change +in the value changes the set of events that is handled, the value +should be in the State. Otherwise no postponed events will be retried +since only the server `Data` changes. -This is not important if you do not postpone events. But if you later decide to -start postponing some events, the design flaw of not having separate states -when they should be, could become a hard-to-find bug. +This is important if events are postponed. But remember that an incorrect +design decision of what belongs in the state, may become a hard to find bug +some time later, when event postponing is introduced. ### Fuzzy State Diagrams It is not uncommon that a state diagram does not specify how to handle events -that are not illustrated in a particular state in the diagram. Hopefully this is -described in an associated text or from the context. +that are not illustrated in a particular state in the diagram. +Hopefully this is described in an associated text or from the context. -Possible actions: ignore as in drop the event (maybe log it) or deal with the -event in some other state as in postpone it. +Possible actions: ignore as in drop the event (maybe log it) or deal with +the event in some other state as in postpone it. ### Selective Receive @@ -1188,18 +1242,19 @@ do_unlock() -> The selective receive in this case causes `open` to implicitly postpone any events to the `locked` state. -A catch-all receive should never be used from a `gen_statem` behaviour (or from -any `gen_*` behaviour), as the receive statement is within the `gen_*` engine -itself. `m:sys`-compatible behaviours must respond to system messages and -therefore do that in their engine receive loop, passing non-system messages to -the _callback module_. Using a catch-all receive can result in system messages -being discarded, which in turn can lead to unexpected behaviour. If a selective -receive must be used, great care should be taken to ensure that only -messages pertinent to the operation are received. Likewise, a callback must -return in due time to let the engine receive loop handle system messages, or -they might time out, also leading to unexpected behaviour. - -The [_transition action_ ](statem.md#transition-actions)`postpone` is +A catch-all receive should never be used from a `gen_statem` behaviour +(or from any `gen_*` behaviour), as the receive statement is within +the `gen_*` engine itself. `m:sys`-compatible behaviours must respond to +system messages and therefore do that in their engine receive loop, +passing non-system messages to the _callback module_. Using a catch-all +receive can result in system messages being discarded, which in turn +can lead to unexpected behaviour. If a selective receive must be used, +great care should be taken to ensure that only messages pertinent +to the operation are received. Likewise, a callback must return +in due time to let the engine receive loop handle system messages, +or they might time out, also leading to unexpected behaviour. + +The [_transition action_](#transition-actions) `postpone` is designed to model selective receives. A selective receive implicitly postpones any events not yet received, but the `postpone` _transition action_ explicitly postpones a single received event. @@ -1208,19 +1263,20 @@ Both mechanisms have the same theoretical time and memory complexity, but note that the selective receive language construct has smaller constant factors. -## State Enter Actions +State Enter Actions +------------------- Say you have a state machine specification that uses state enter actions. Although you can code this using inserted events (described in the next section), especially if only one or a few states have state enter actions, this is a perfect use case for the built in -[_state enter calls_](statem.md#state-enter-calls). +[_state enter calls_](#state-enter-calls). You return a list containing `state_enter` from your -[`callback_mode/0` ](`c:gen_statem:callback_mode/0`)function and the +[`callback_mode/0`](`c:gen_statem:callback_mode/0`) function and the `gen_statem` engine will call your _state callback_ once with an event -`(enter, OldState, ...)` whenever it does a _state change_. Then you just need -to handle these event-like calls in all states. +`(enter, OldState, ...)` whenever it does a _state change_. Then you +just need to handle these event-like calls in all states. ```erlang ... @@ -1253,22 +1309,25 @@ open(state_timeout, lock, Data) -> ... ``` -You can repeat the state enter code by returning one of `{repeat_state, ...}`, -`{repeat_state_and_data,_}`, or `repeat_state_and_data` that otherwise behaves -exactly like their `keep_state` siblings. See the type -[`state_callback_result()` ](`t:gen_statem:state_callback_result/1`) in the -Reference Manual. +You can repeat the state enter code by returning one of +`{repeat_state, ...}`,`{repeat_state_and_data, _}`, +or `repeat_state_and_data` that otherwise behaves exactly like their +`keep_state` siblings. See the type +[`state_callback_result()`](`t:gen_statem:state_callback_result/2`) +in the Reference Manual. -## Inserted Events +Inserted Events +--------------- -It can sometimes be beneficial to be able to generate events to your own state -machine. This can be done with the -[_transition action_ ](statem.md#transition-actions)[`{next_event,EventType,EventContent}`](`t:gen_statem:action/0`). +It can sometimes be beneficial to be able to generate events to your own +state machine. This can be done with the +[_transition action_](#transition-actions) +[`{next_event, EventType, EventContent}`](`t:gen_statem:action/0`). -You can generate events of any existing [type](`t:gen_statem:action/0`), but the -`internal` type can only be generated through action `next_event`. Hence, it -cannot come from an external source, so you can be certain that an `internal` -event is an event from your state machine to itself. +You can generate events of any existing [type](`t:gen_statem:action/0`), +but the`internal` type can only be generated through action `next_event`. +Hence, it cannot come from an external source, so you can be certain +that an `internal` event is an event from your state machine to itself. One example for this is to pre-process incoming data, for example decrypting chunks or collecting characters up to a line break. @@ -1285,13 +1344,13 @@ machine. Using internal events also can make it easier to synchronize the state machines. -A variant of this is to use a [complex state](statem.md#complex-state) with -[_one state callback_](statem.md#one-state-callback), modeling the state -with, for example, a tuple `{MainFSMState,SubFSMState}`. +A variant of this is to use a [complex state](#complex-state) with +[one state callback](#one-state-callback), modeling the state +with, for example, a tuple `{MainFSMState, SubFSMState}`. -To illustrate this we make up an example where the buttons instead generate down -and up (press and release) events, and the lock responds to an up event only -after the corresponding down event. +To illustrate this we make up an example where the buttons instead generate +down and up (press and release) events, and the lock responds +to an up event only after the corresponding down event. ```erlang ... @@ -1335,10 +1394,11 @@ open(internal, {button,_}, Data) -> If you start this program with `code_lock:start([17])` you can unlock with `code_lock:down(17), code_lock:up(17).` -## Example Revisited +Example Revisited +----------------- -This section includes the example after most of the mentioned modifications and -some more using _state enter calls_, which deserves a new state diagram: +This section includes the example after most of the mentioned modifications +and some more using _state enter calls_, which deserves a new state diagram: ```mermaid --- @@ -1361,11 +1421,11 @@ stateDiagram-v2 open --> enter_locked : state_timeout ``` -Notice that this state diagram does not specify how to handle a button event in -the state `open`. So, you need to read in some side notes, that is, here: that -unspecified events shall be postponed (handled in some later state). Also, the -state diagram does not show that the `code_length/0` call must be handled in -every state. +Notice that this state diagram does not specify how to handle a button event +in the state `open`. So, you need to read in some side notes, that is, here: +that unspecified events shall be postponed (handled in some later state). +Also, the state diagram does not show that the `code_length/0` call +must be handled in every state. ### Callback Mode: state_functions @@ -1442,7 +1502,7 @@ locked( {next_state, open, Data}; true -> % Incomplete | Incorrect {keep_state, Data#{buttons := NewButtons}, - [{state_timeout,30000,button}]} % Time in milliseconds + [{state_timeout,30_000,button}]} % Time in milliseconds end; ?HANDLE_COMMON. ``` @@ -1470,10 +1530,10 @@ terminate(_Reason, State, _Data) -> ### Callback Mode: handle_event_function -This section describes what to change in the example to use one `handle_event/4` -function. The previously used approach to first branch depending on event does -not work that well here because of the _state enter calls_, so this example -first branches depending on state: +This section describes what to change in the example to use one +`handle_event/4` function. The previously used approach to first branch +depending on event does not work that well here because of +the _state enter calls_, so this example first branches depending on state: ```erlang -export([handle_event/4]). @@ -1507,7 +1567,7 @@ handle_event( {next_state, open, Data}; true -> % Incomplete | Incorrect {keep_state, Data#{buttons := NewButtons}, - [{state_timeout,30000,button}]} % Time in milliseconds + [{state_timeout,30_000,button}]} % Time in milliseconds end; ``` @@ -1533,7 +1593,7 @@ handle_event(cast, {up,Button}, _State, Data) -> #{button := Button} -> {keep_state, maps:remove(button, Data), [{next_event,internal,{button,Button}}, - {state_timeout,30000,button}]}; % Time in milliseconds + {state_timeout,30_000,button}]}; % Time in milliseconds #{} -> keep_state_and_data end; @@ -1542,27 +1602,29 @@ handle_event({call,From}, code_length, _State, #{length := Length}) -> [{reply,From,Length}]}. ``` -Notice that postponing buttons from the `open` state to the `locked` state feels -like a strange thing to do for a code lock, but it at least illustrates event -postponing. +Notice that postponing buttons from the `open` state to the `locked` state +seems like a strange thing to do for a code lock, but it at least +illustrates event postponing. -## Filter the State +Filter the State +---------------- -The example servers so far in this chapter print the full internal state in the -error log, for example, when killed by an exit signal or because of an internal -error. This state contains both the code lock code and which digits that remain -to unlock. +The example servers so far in this chapter print the full internal state +in the error log, for example, when killed by an exit signal or because of +an internal error. The state contains both the code lock code +and which digits that remain to unlock. -This state data can be regarded as sensitive, and maybe not what you want in the -error log because of some unpredictable event. +This state data can be regarded as sensitive, and maybe not what you want +in the error log because of some unpredictable event. Another reason to filter the state can be that the state is too large to print, as it fills the error log with uninteresting details. -To avoid this, you can format the internal state that gets in the error log and -gets returned from [`sys:get_status/1,2`](`sys:get_status/1`) by implementing -function [`Module:format_status/2`](`c:gen_statem:format_status/2`), for example -like this: +To avoid this, you can format the internal state that gets in the error log +and gets returned from [`sys:get_status/1,2`](`sys:get_status/1`) +by implementing function +[`Module:format_status/2`](`c:gen_statem:format_status/2`), +for example like this: ```erlang ... @@ -1586,27 +1648,29 @@ format_status(Opt, [_PDict,State,Data]) -> ``` It is not mandatory to implement a -[`Module:format_status/2`](`c:gen_statem:format_status/2`) function. If you do -not, a default implementation is used that does the same as this example -function without filtering the `Data` term, that is, `StateData = {State,Data}`, -in this example containing sensitive information. +[`Module:format_status/2`](`c:gen_statem:format_status/2`) function. +If you do not, a default implementation is used that does the same +as this example function without filtering the `Data` term, that is, +`StateData = {State, Data}`, in this example containing sensitive information. -## Complex State +Complex State +------------- The _callback mode_ [`handle_event_function`](`t:gen_statem:callback_mode/0`) enables using a non-atom state as described in section -[Callback Modes](statem.md#callback-modes), for example, a complex state term +[_Callback Modes_](#callback-modes), for example, a complex state term like a tuple. -One reason to use this is when you have a state item that when changed should -cancel the [state time-out](statem.md#state-time-outs), or one that affects the -event handling in combination with postponing events. We will go for the latter -and complicate the previous example by introducing a configurable lock button -(this is the state item in question), which in the `open` state immediately -locks the door, and an API function `set_lock_button/1` to set the lock button. +One reason to use this is when you have a state item that when changed +should cancel the [_state time-out_](#state-time-outs), or one that affects +the event handling in combination with postponing events. We will go for +the latter and complicate the previous example by introducing +a configurable lock button (this is the state item in question), +which in the `open` state immediately locks the door, and an API function +`set_lock_button/1` to set the lock button. -Suppose now that we call `set_lock_button` while the door is open, and we have -already postponed a button event that was the new lock button: +Suppose now that we call `set_lock_button` while the door is open, +and we have already postponed a button event that was the new lock button: ```erlang 1> code_lock:start_link([a,b,c], x). @@ -1625,14 +1689,14 @@ x % What should happen here? Immediate lock or nothing? ``` -We could say that the button was pressed too early so it is not to be recognized -as the lock button. Or we can make the lock button part of the state so when we -then change the lock button in the locked state, the change becomes a _state -change_ and all postponed events are retried, therefore the lock is immediately -locked\! +We could say that the button was pressed too early so it should not be +recognized as the lock button. Or we can make the lock button part of +the state so when we then change the lock button in the locked state, +the change becomes a _state change_ and all postponed events are retried, +therefore the lock is immediately locked\! -We define the state as `{StateName,LockButton}`, where `StateName` is as before -and `LockButton` is the current lock button: +We define the state as `{StateName, LockButton}`, where `StateName` +is as before and `LockButton` is the current lock button: ```erlang -module(code_lock). @@ -1686,7 +1750,7 @@ handle_event( {next_state, {open,LockButton}, Data}; true -> % Incomplete | Incorrect {keep_state, Data#{buttons := NewButtons}, - [{state_timeout,30000,button}]} % Time in milliseconds + [{state_timeout,30_000,button}]} % Time in milliseconds end; ``` @@ -1726,7 +1790,8 @@ terminate(_Reason, State, _Data) -> ok. ``` -## Hibernation +Hibernation +----------- If you have many servers in one node and they have some state(s) in their lifetime in which the servers can be expected to idle for a while, and the @@ -1739,9 +1804,9 @@ footprint of a server can be minimized by hibernating it through > It is rather costly to hibernate a process; see `erlang:hibernate/3`. It is > not something you want to do after every event. -We can in this example hibernate in the `{open,_}` state, because what normally -occurs in that state is that the state time-out after a while triggers a -transition to `{locked,_}`: +We can in this example hibernate in the `{open, _}` state, +because what normally occurs in that state is that the _state time-out_ +after a while triggers a transition to `{locked, _}`: ```erlang ... @@ -1756,21 +1821,22 @@ handle_event(enter, _OldState, {open,_}, _Data) -> ``` The atom [`hibernate`](`t:gen_statem:hibernate/0`) in the action list on the -last line when entering the `{open,_}` state is the only change. If any event -arrives in the `{open,_},` state, we do not bother to rehibernate, so the server -stays awake after any event. +last line when entering the `{open, _}` state is the only change. If any event +arrives in the `{open, _},` state, we do not bother to rehibernate, +so the server stays awake after any event. -To change that we would need to insert action `hibernate` in more places. For -example, the state-independent `set_lock_button` operation would have to use -`hibernate` but only in the `{open,_}` state, which would clutter the code. +To change that we would need to insert action `hibernate` in more places. +For example, the state-independent `set_lock_button` operation +would have to use `hibernate` but only in the `{open, _}` state, +which would clutter the code. Another not uncommon scenario is to use the -[event time-out](statem.md#event-time-outs) to trigger hibernation after a +[_event time-out_](#event-time-outs) to trigger hibernation after a certain time of inactivity. There is also a server start option -[`{hibernate_after, Timeout}` ](`t:gen_statem:enter_loop_opt/0`)for +[`{hibernate_after, Timeout}`](`t:gen_statem:enter_loop_opt/0`) for [`start/3,4`](`gen_statem:start/3`), -[`start_link/3,4` ](`gen_statem:start_link/3`)or -[`enter_loop/4,5,6` ](`gen_statem:enter_loop/4`)that may be used to +[`start_link/3,4`](`gen_statem:start_link/3`), or +[`enter_loop/4,5,6`](`gen_statem:enter_loop/4`) that may be used to automatically hibernate the server. This particular server probably does not use heap memory worth hibernating for.