diff --git a/lib/kernel/doc/src/erpc.xml b/lib/kernel/doc/src/erpc.xml index 26d1ec4aadac..ecb3949eb969 100644 --- a/lib/kernel/doc/src/erpc.xml +++ b/lib/kernel/doc/src/erpc.xml @@ -64,12 +64,55 @@

- An opaque type of call request identifiers. For more - information see + An opaque request identifier. For more information see send_request/4.

+ + + +

+ An opaque collection of request identifiers + (request_id()) + where each request identifier can be associated with a label + chosen by the user. For more information see + reqids_new/0. +

+
+
+ + + + + 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 + timeout in milliseconds. That is, the operation will time out when + erlang:monotonic_time(millisecond) + 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 + (request_id_collection()) +, + since you do not have to recalculate the relative time until the deadline + over and over again. +

+
+
+
+ @@ -81,8 +124,9 @@

The same as calling - erpc:call(Node,erlang,apply,[Fun,[]],Timeout). - May raise all the same exceptions as erpc:call/5 + erpc:call(Node, + erlang, apply, [Fun,[]], Timeout). + May raise all the same exceptions as call/5 plus an {erpc, badarg} error exception if Fun is not a fun of zero arity. @@ -104,9 +148,8 @@ Evaluates apply(Module, Function, Args) on node Node and returns the corresponding value Result. - Timeout is an integer representing - the timeout in milliseconds or the atom infinity - which prevents the operation from ever timing out. + Timeout sets an upper time limit + for the call operation to complete.

The call erpc:call(Node, Module, Function, Args) is equivalent @@ -118,7 +161,7 @@ exceptions, the operation did not time out, and no failures occurred. In all other cases an exception is raised. The following exceptions, listed by exception class, can - currently be raised by erpc:call(): + currently be raised by call():

throw @@ -158,7 +201,7 @@ {exception, ErrorReason, StackTrace}

- A runtime error occurred which raised and error + A runtime error occurred which raised an error exception while applying the function, and the applied function did not catch the exception. The error reason ErrorReason @@ -186,9 +229,8 @@

Args is not a list. Note that the list is not verified to be a proper list at the client side.

-

Timeout is not the - atom infinity or an integer in valid - range.

+

Timeout is + invalid.

@@ -256,7 +298,7 @@ The same as calling erpc:cast(Node,erlang,apply,[Fun,[]]).

-

erpc:cast/2 fails with an {erpc, badarg} +

cast/2 fails with an {erpc, badarg} error exception if:

Node is not an atom.

@@ -273,11 +315,11 @@ Evaluates apply(Module, Function, Args) on node Node. No response is delivered to the - calling process. erpc:cast() returns immediately + calling process. cast() returns immediately after the cast request has been sent. Any failures beside bad arguments are silently ignored.

-

erpc:cast/4 fails with an {erpc, badarg} +

cast/4 fails with an {erpc, badarg} error exception if:

Node is not an atom.

@@ -305,13 +347,13 @@

Check if a message is a response to a call request previously made by the calling process using - erpc:send_request/4. + send_request/4. RequestId should be the value returned - from the previously made erpc:send_request() call, + from the previously made send_request/4 call, and the corresponding response should not already have been - received and handled to completion by erpc:check_response(), - erpc:receive_response(), or - erpc:wait_response(). + received and handled to completion by check_response/2, + receive_response/2, or + wait_response/2. Message is the message to check.

@@ -323,9 +365,9 @@ corresponds to the value returned from the applied function or an exception is raised. The exceptions that can be raised corresponds to the same exceptions as can be raised by - erpc:call/4. + call/4. That is, no {erpc, timeout} error exception - can be raised. erpc:check_response() will fail with + can be raised. check_response() will fail with an {erpc, badarg} exception if/when an invalid RequestId is detected.

@@ -340,6 +382,80 @@
+ + + Check if a message is a response corresponding to a + previously sent call request. + +

+ Check if a message is a response to a call request corresponding + to a request identifier saved in RequestIdCollection. + All request identifiers of RequestIdCollection must + correspond to requests that have been made using + send_request/4 or + send_request/6, + and all requests must have been made by the process calling this + function. +

+

+ Label is the label associated with the request + identifier of the request that the response corresponds to. + A request identifier is associated with a label when + adding a request identifier + in a request identifier + collection, or when sending the request using + send_request/6. +

+

+ 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, + the second element equals the Label associated + with the specific request identifier, and the third element + NewRequestIdCollection is a possibly modified + request identifier collection. The error exception {erpc, + badarg} is not associated with any specific request identifier, + and will hence not be wrapped. +

+

+ If RequestIdCollection is empty, the atom + no_request will be returned. If Message + does not correspond to any of the request identifiers in + RequestIdCollection, the atom + no_response is returned. +

+

+ If Delete equals true, the association + with Label will have been deleted from + RequestIdCollection in the resulting + NewRequestIdCollection. If + Delete equals false, + NewRequestIdCollection will equal + RequestIdCollection. 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_response. +

+

+ Note that a response might have been consumed uppon an {erpc, + badarg} exception and if so, will be lost for ever. +

+
+
+ @@ -347,8 +463,9 @@

The same as calling - erpc:multicall(Nodes,erlang,apply,[Fun,[]],Timeout). - May raise all the same exceptions as erpc:multicall/5 + erpc:multicall(Nodes, + erlang, apply, [Fun,[]], Timeout). + May raise all the same exceptions as multicall/5 plus an {erpc, badarg} error exception if Fun is not a fun of zero arity. @@ -372,15 +489,13 @@ Performs multiple call operations in parallel on multiple nodes. That is, evaluates apply(Module, Function, - Args) on the nodes - Nodes in parallel. - Timeout is an integer representing - the timeout in milliseconds or the atom infinity - which prevents the operation from ever timing out. - The result is returned as a list where - the result from each node is placed at the same position - as the node name is placed in Nodes. - Each item in the resulting list is formatted as either: + Args) on the nodes Nodes + in parallel. Timeout sets an upper time + limit for all call operations to complete. The result + is returned as a list where the result from each node is placed + at the same position as the node name is placed in + Nodes. Each item in the resulting list is + formatted as either:

{ok, Result} @@ -394,11 +509,11 @@ raised an exception of class Class with exception reason ExceptionReason. These corresponds the the exceptions that - erpc:call/5 + call/5 can raise.

-

erpc:multicall/5 fails with an {erpc, badarg} +

multicall/5 fails with an {erpc, badarg} error exception if:

Nodes is not a proper list of @@ -416,8 +531,12 @@ to the call erpc:multicall(Nodes, Module, Function, Args, infinity). These calls are also equivalent to calling my_multicall(Nodes, Module, - Function, Args) if one disregard performance and failure - behavior: + Function, Args) below if one disregard performance and failure + behavior. multicall() can utilize a selective receive + optimization which removes the need to scan the message queue from + the beginning in order to find a matching message. The + send_request()/receive_response() combination can, + however, not utilize this optimization.

 my_multicall(Nodes, Module, Function, Args) ->
@@ -436,12 +555,6 @@ my_multicall(Nodes, Module, Function, Args) ->
             ReqIds).
 
-

- The Timeout value in milliseconds - sets an upper time limit for all call operations - to complete. -

-

If an erpc operation fails, but it is unknown if the function is/will be applied (that is, a timeout, @@ -473,7 +586,7 @@ my_multicall(Nodes, Module, Function, Args) -> The same as calling erpc:multicast(Nodes,erlang,apply,[Fun,[]]).

-

erpc:multicast/2 fails with an {erpc, badarg} +

multicast/2 fails with an {erpc, badarg} error exception if:

Nodes is not a proper list of atoms.

@@ -490,11 +603,11 @@ my_multicall(Nodes, Module, Function, Args) -> Evaluates apply(Module, Function, Args) on the nodes Nodes. No response is delivered to the - calling process. erpc:multicast() returns immediately + calling process. multicast() returns immediately after the cast requests have been sent. Any failures beside bad arguments are silently ignored.

-

erpc:multicast/4 fails with an {erpc, badarg} +

multicast/4 fails with an {erpc, badarg} error exception if:

Nodes is not a proper list of @@ -515,9 +628,21 @@ my_multicall(Nodes, Module, Function, Args) -> - + + Receive a call response corresponding to a + previously sent call request. + +

+ The same as calling + erpc:receive_response(RequestId, + infinity). +

+
+
+ + Receive a call response corresponding to a previously sent call request. @@ -525,34 +650,41 @@ my_multicall(Nodes, Module, Function, Args) ->

Receive a response to a call request previously made by the calling process using - erpc:send_request/4. + send_request/4. RequestId should be the value returned from - the previously made erpc:send_request() call, and + the previously made send_request/4 call, and the corresponding response should not already have been received - and handled to completion by - erpc:check_response(), - erpc:receive_response(), or - erpc:wait_response(). - Timeout is an integer representing - the timeout in milliseconds or the atom infinity - which prevents the operation from ever timing out. The call - operation is completed once the erpc:receive_response() call - returns or raise an exception. -

-

- The call erpc:receive_response(RequestId) is - equivalent to the call - erpc:receive_response(RequestId, infinity). + and handled to completion by receive_response(), + check_response/4, + or + wait_response/4. +

+

+ Timeout sets an upper time limit on how + long to wait for a response. If the operation times out, the request + identified by RequestId will be abandoned, then an + {erpc, timeout} error exception will be raised. That is, + no response corresponding to the request will ever be received after a + timeout. If a response is received, the call operation is + completed and either the result is returned or an exception is raised. The + exceptions that can be raised corresponds to the same exceptions as can + be raised by call/5. + receive_response/2 will fail with an {erpc, badarg} + exception if/when an invalid RequestId is detected + or if an invalid Timeout is passed.

+

A call to the function my_call(Node, Module, Function, Args, Timeout) below is equivalent to the call erpc:call(Node, Module, Function, Args, - Timeout) if one disregards performance. erpc:call() - can utilize a message queue optimization which removes the need to scan - the whole message queue which the combination - erpc:send_request()/erpc:receive_response() cannot. + Timeout) if one disregards performance. call() + can utilize a selective receive optimization which removes + the need to scan the message queue from the beginning in + order to find a matching message. The + send_request()/receive_response() combination can, + however, not utilize this optimization.

 my_call(Node, Module, Function, Args, Timeout) ->
@@ -568,15 +700,157 @@ my_call(Node, Module, Function, Args, Timeout) ->
 	  communicates with the calling process, such communication
 	  may, of course, reach the calling process.
         

- -

- erpc:receive_response() will return or raise exceptions the - same way as erpc:call/5 - does with the exception of {erpc, badarg}. An - {erpc, badarg} exception will be raised if/when an invalid - RequestId is detected or if an invalid - Timeout is passed. + + + + + + Receive a call response corresponding to a + previously sent call request. + +

+ Receive a response to a call request corresponding to a request + identifier saved in RequestIdCollection. All + request identifiers of RequestIdCollection must + correspond to requests that have been made using + send_request/4 or + send_request/6, + and all requests must have been made by the process calling this + function.

+

+ Label is the label associated with the request + identifier of the request that the response corresponds to. + A request identifier is associated with a label when + adding a request identifier + in a request identifier + collection, or when sending the request using + send_request/6. +

+

+ Compared to + receive_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 receive_response/2, + the second element equals the Label associated + with the specific request identifier, and the third element + NewRequestIdCollection is a possibly modified + request identifier collection. The error exceptions {erpc, + badarg} and {erpc, timeout} are not associated with any + specific request identifiers, and will hence not be wrapped. +

+

+ If RequestIdCollection is empty, the atom + no_request will be returned. +

+

+ If the operation times out, all requests identified by + RequestIdCollection will be abandoned, then an + {erpc, timeout} error exception will be raised. That is, + no responses corresponding to any of the request identifiers in + RequestIdCollection will ever be received after a + timeout. The difference between receive_response/3 and + wait_response/3 + is that receive_response/3 abandons the requests at timeout + so that any potential future responses are ignored, while + wait_response/3 does not. +

+

+ If Delete equals true, the association + with Label will have been deleted from + RequestIdCollection in the resulting + NewRequestIdCollection. If + Delete equals false, + NewRequestIdCollection will equal + RequestIdCollection. 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, + 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, it will always block + until a timeout determined by Timeout is + triggered. +

+

+ Note that a response might have been consumed uppon an {erpc, + badarg} exception and if so, will be lost for ever. +

+ + + + + + Save a request identifier. + +

+ Saves RequestId and associates a + Label with the request identifier by adding this + information to RequestIdCollection and returning + the resulting request identifier collection. +

+
+
+ + + + Create a new empty request identifier collection. + +

+ Returns a new empty request identifier collection. A + request identifier collection can be utilized in order + the handle multiple outstanding requests. +

+

+ Request identifiers of requests made by + send_request/4 + 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 + check_response/3, + receive_response/3, + and + wait_response/3. +

+

+ reqids_size/1 + can be used to determine the amount of request identifiers in a + request identifier collection. +

+
+
+ + + + Get size of a request identifier collection. + +

+ Returns the amount of request identifiers saved in + RequestIdCollection. +

+
+
+ + + + Get a list a request identifier/label associations in a collection. + +

+ Returns a list of {RequestId, Label} + tuples which corresponds to all request identifiers with their + associated labels present in the RequestIdCollection + collection. +

@@ -586,10 +860,10 @@ my_call(Node, Module, Function, Args, Timeout) ->

The same as calling - erpc:send_request(Node,erlang,apply,[Fun,[]]). + erpc:send_request(Node, + erlang, apply, [Fun, []]).

-

erpc:send_request/2 fails with an {erpc, badarg} - error exception if:

+

Fails with an {erpc, badarg} error exception if:

Node is not an atom.

Fun is not a fun of @@ -606,34 +880,158 @@ my_call(Node, Module, Function, Args, Timeout) -> - + Send a request to evaluate a function call on a node.

Send an asynchronous call request to the node - Node. erpc:send_request() + Node. send_request/4 returns a request identifier that later is to be passed - as argument to either - erpc:receive_response(), - erpc:wait_response(), + to either + receive_response/2, + wait_response/2, + or, + check_response/2 + in order to get the response of the call request. Besides passing + the request identifier directly to these functions, it can also be + added 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, - erpc:check_response() - in order to get the response of the call request. + 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/6 + instead. +

+

+ A call to the function + my_call(Node, Module, Function, Args, Timeout) + below is equivalent to the call + erpc:call(Node, Module, Function, Args, + Timeout) if one disregards performance. call() + can utilize a selective receive optimization which removes + the need to scan the message queue from the beginning in + order to find a matching message. The + send_request()/receive_response() combination can, + however, not utilize this optimization.

-

erpc:send_request() fails with an {erpc, badarg} - error exception if:

+
+my_call(Node, Module, Function, Args, Timeout) ->
+  RequestId = erpc:send_request(Node, Module, Function, Args),
+  erpc:receive_response(RequestId, Timeout).
+
+

Fails with an {erpc, badarg} error exception if:

+ +

Node is not an atom.

+

Module is not an atom.

+

Function is not an atom.

+

Args is not a list. Note that the + list is not verified to be a proper list at the client side.

+
+ +

+ You cannot make any assumptions about the + process that will perform the apply(). It may + be a server, or a freshly spawned process. +

+
+
+ + + + + Send a request to evaluate a function call on a node. + +

+ The same as calling + erpc:send_request(Node, + erlang, apply, [Fun,[]]), Label, + RequestIdCollection). +

+

Fails with an {erpc, badarg} error exception if:

+ +

Node is not an atom.

+

Fun is not a fun of zero arity.

+

RequestIdCollection is detected not to + be request identifier collection.

+
+ +

+ You cannot make any assumptions about the + process that will perform the apply(). It may + be a server, or a freshly spawned process. +

+
+
+
+ + + + Send a request to evaluate a function call on a node. + +

+ Send an asynchronous call request to the node + Node. The Label will be + associated with the request identifier of the operation and + added to the returned request identifier collection + NewRequestIdCollection. 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 + erpc:reqids_add(erpc:send_request(Node, + Module, Function, Args), + Label, RequestIdCollection), but + calling send_request/6 is slightly more efficient. +

+ +

Fails with an {erpc, badarg} error exception if:

Node is not an atom.

Module is not an atom.

Function is not an atom.

Args is not a list. Note that the list is not verified to be a proper list at the client side.

+

RequestIdCollection is detected not to + be request identifier collection.

+ +

+ You cannot make any assumptions about the + process that will perform the apply(). It may + be a server, or a freshly spawned process. +

+
+
+
+ + + + Poll for a call response corresponding to a previously + sent call request. + +

+ The same as calling + erpc:wait_response(RequestId, + 0). That is, poll for a response message to a call + request previously made by the calling process. +

- Wait or poll for a call response corresponding to a previously sent call request. @@ -641,40 +1039,30 @@ my_call(Node, Module, Function, Args, Timeout) ->

Wait or poll for a response message to a call request previously made by the calling process using - erpc:send_request/4. + send_request/4. RequestId should be the value returned from - the previously made erpc:send_request() call, and the + the previously made send_request() call, and the corresponding response should not already have been received and handled to completion by - erpc:check_response(), - erpc:receive_response(), - or erpc:wait_response(). WaitTime equals the - time to wait in milliseconds (or the atom infinity) during the wait. - WaitTime is an integer representing time to wait - in milliseconds or the atom infinity which will cause - wait_response/2 to wait for a response until it appears - regardless of how long time that is. + check_response/2, + receive_response/2, + or wait_response().

- The call erpc:wait_response(RequestId) is equivalent - to the call erpc:wait_response(RequestId, 0). That is, - poll for a response message to a call request previously made by - the calling process. -

-

- If no response is received before WaitTime milliseconds, - the atom no_response 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 erpc:check_response(), - erpc:receive_response(), or erpc:wait_response(). If a - response is received, the call operation is completed and either - the result is returned as {response, Result} where Result - corresponds to the value returned from the applied function or an - exception is raised. The exceptions that can be raised corresponds to the - same exceptions as can be raised by - erpc:call/4. + WaitTime sets an upper time limit on how long to wait + for a response. If no response is received before the + WaitTime timeout has triggered, the atom + no_response 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(). If a response is received, the call + operation is completed and either the result is returned as + {response, Result} where Result corresponds to the value + returned from the applied function or an exception is raised. The + exceptions that can be raised corresponds to the same exceptions as can + be raised by call/4. That is, no {erpc, timeout} error exception can be raised. - erpc:wait_response() will fail with an {erpc, badarg} + wait_response/2 will fail with an {erpc, badarg} exception if/when an invalid RequestId is detected or if an invalid WaitTime is passed.

@@ -690,6 +1078,87 @@ my_call(Node, Module, Function, Args, Timeout) ->
+ + + Wait or poll for a call response corresponding to a previously + sent call request. + +

+ Wait or poll for a response to a call request corresponding + to a request identifier saved in RequestIdCollection. All + request identifiers of RequestIdCollection must + correspond to requests that have been made using + send_request/4 or + send_request/6, + and all requests must have been made by the process calling this + function. +

+

+ Label is the label associated with the request + identifier of the request that the response corresponds to. + A request identifier is associated with a label when + adding a request identifier + in a request identifier + collection, or when sending the request using + send_request/6. +

+

+ 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, + the second element equals the Label associated + with the specific request identifier, and the third element + NewRequestIdCollection is a possibly modified + request identifier collection. The error exception {erpc, + badarg} is not associated with any specific request identifier, + and will hence not be wrapped. +

+

+ If RequestIdCollection is empty, no_request + will be returned. If no response is received before the + WaitTime timeout has triggered, the atom + no_response 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 is that receive_response/3 + abandons requests at timeout so that any potential future + responses are ignored, while wait_response/3 does not. +

+

+ If Delete equals true, the association + with Label will have been deleted from + RequestIdCollection in the resulting + NewRequestIdCollection. If + Delete equals false, + NewRequestIdCollection will equal + RequestIdCollection. 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, + 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, it will always block + until a timeout determined by WaitTime is + triggered and then return no_response. +

+

+ Note that a response might have been consumed uppon an {erpc, + badarg} exception and if so, will be lost for ever. +

+
+
+ diff --git a/lib/kernel/src/erpc.erl b/lib/kernel/src/erpc.erl index c93b0f7ca86e..be5d2b1942ca 100644 --- a/lib/kernel/src/erpc.erl +++ b/lib/kernel/src/erpc.erl @@ -32,19 +32,27 @@ cast/4, send_request/2, send_request/4, + send_request/6, receive_response/1, receive_response/2, + receive_response/3, wait_response/1, wait_response/2, + wait_response/3, check_response/2, + check_response/3, multicall/2, multicall/3, multicall/4, multicall/5, multicast/2, - multicast/4]). + multicast/4, + reqids_new/0, + reqids_size/1, + reqids_add/3, + reqids_to_list/1]). --export_type([request_id/0]). +-export_type([request_id/0, request_id_collection/0, timeout_time/0]). %% Internal exports (also used by the 'rpc' module) @@ -57,14 +65,15 @@ %%------------------------------------------------------------------------ --compile({inline,[{result,4}]}). %% Nicer error stack trace... +%% Nicer error stack trace... +-compile({inline,[{result,4},{collection_result,6},{timeout_value,1}]}). -define(MAX_INT_TIMEOUT, 4294967295). --define(TIMEOUT_TYPE, 0..?MAX_INT_TIMEOUT | 'infinity'). -define(IS_VALID_TMO_INT(TI_), (is_integer(TI_) andalso (0 =< TI_) andalso (TI_ =< ?MAX_INT_TIMEOUT))). --define(IS_VALID_TMO(T_), ((T_ == infinity) orelse ?IS_VALID_TMO_INT(T_))). + +-type timeout_time() :: 0..?MAX_INT_TIMEOUT | 'infinity' | {abs, integer()}. %%------------------------------------------------------------------------ %% Exported API @@ -81,7 +90,7 @@ call(N, Fun) -> -spec call(Node, Fun, Timeout) -> Result when Node :: node(), Fun :: function(), - Timeout :: ?TIMEOUT_TYPE, + Timeout :: timeout_time(), Result :: term(). call(N, Fun, Timeout) when is_function(Fun, 0) -> @@ -106,7 +115,7 @@ call(N, M, F, A) -> Module :: atom(), Function :: atom(), Args :: [term()], - Timeout :: ?TIMEOUT_TYPE, + Timeout :: timeout_time(), Result :: term(). call(N, M, F, A, infinity) when node() =:= N, %% Optimize local call @@ -131,8 +140,8 @@ call(N, M, F, A, infinity) when node() =:= N, %% Optimize local call call(N, M, F, A, T) when is_atom(N), is_atom(M), is_atom(F), - is_list(A), - ?IS_VALID_TMO(T) -> + is_list(A) -> + Timeout = timeout_value(T), Res = make_ref(), ReqId = spawn_request(N, ?MODULE, execute_call, [Res, M, F, A], [{reply, error_only}, monitor]), @@ -141,7 +150,7 @@ call(N, M, F, A, T) when is_atom(N), result(spawn_reply, ReqId, Res, Reason); {'DOWN', ReqId, process, _Pid, Reason} -> result(down, ReqId, Res, Reason) - after T -> + after Timeout -> result(timeout, ReqId, Res, undefined) end; call(_N, _M, _F, _A, _T) -> @@ -149,24 +158,34 @@ call(_N, _M, _F, _A, _T) -> %% Asynchronous call --opaque request_id() :: {reference(), reference()}. +-opaque request_id() :: nonempty_improper_list(reference(), reference()). +-opaque request_id_collection() :: #{ reference() => [reference() | term()] }. -spec send_request(Node, Fun) -> RequestId when Node :: node(), Fun :: function(), RequestId :: request_id(). -send_request(N, F) when is_function(F, 0) -> +send_request(N, F) when is_atom(N), is_function(F, 0) -> send_request(N, erlang, apply, [F, []]); send_request(_N, _F) -> error({?MODULE, badarg}). +-dialyzer({no_improper_lists, send_request/4}). + -spec send_request(Node, Module, Function, Args) -> RequestId when Node :: node(), Module :: atom(), Function :: atom(), Args :: [term()], - RequestId :: request_id(). + RequestId :: request_id(); + (Node, Fun, Label, RequestIdCollection) -> + NewRequestIdCollection when + Node :: node(), + Fun :: function(), + Label :: term(), + RequestIdCollection :: request_id_collection(), + NewRequestIdCollection :: request_id_collection(). send_request(N, M, F, A) when is_atom(N), is_atom(M), @@ -175,16 +194,43 @@ send_request(N, M, F, A) when is_atom(N), Res = make_ref(), ReqId = spawn_request(N, ?MODULE, execute_call, [Res, M, F, A], [{reply, error_only}, monitor]), - {Res, ReqId}; -send_request(_N, _M, _F, _A) -> + [Res|ReqId]; +send_request(N, F, L, C) when is_atom(N), is_function(F, 0), is_map(C) -> + send_request(N, erlang, apply, [F, []], L, C); +send_request(_, _, _, _) -> + error({?MODULE, badarg}). + +-dialyzer({no_improper_lists, send_request/6}). + +-spec send_request(Node, Module, Function, Args, + Label, RequestIdCollection) -> + NewRequestIdCollection when + Node :: node(), + Module :: atom(), + Function :: atom(), + Args :: [term()], + Label :: term(), + RequestIdCollection :: request_id_collection(), + NewRequestIdCollection :: request_id_collection(). + +send_request(N, M, F, A, L, C) when is_atom(N), + is_atom(M), + is_atom(F), + is_list(A), + is_map(C) -> + Res = make_ref(), + ReqId = spawn_request(N, ?MODULE, execute_call, [Res, M, F, A], + [{reply, error_only}, monitor]), + maps:put(ReqId, [Res|L], C); +send_request(_N, _M, _F, _A, _L, _C) -> error({?MODULE, badarg}). -spec receive_response(RequestId) -> Result when RequestId :: request_id(), Result :: term(). -receive_response({Res, ReqId} = RId) when is_reference(Res), - is_reference(ReqId) -> +receive_response([Res|ReqId] = RId) when is_reference(Res), + is_reference(ReqId) -> receive_response(RId, infinity); receive_response(_) -> error({?MODULE, badarg}). @@ -193,53 +239,118 @@ receive_response(_) -> -spec receive_response(RequestId, Timeout) -> Result when RequestId :: request_id(), - Timeout :: ?TIMEOUT_TYPE, + Timeout :: timeout_time(), Result :: term(). -receive_response({Res, ReqId}, Tmo) when is_reference(Res), - is_reference(ReqId), - ?IS_VALID_TMO(Tmo) -> +receive_response([Res|ReqId], Tmo) when is_reference(Res), + is_reference(ReqId) -> + Timeout = timeout_value(Tmo), receive {spawn_reply, ReqId, error, Reason} -> result(spawn_reply, ReqId, Res, Reason); {'DOWN', ReqId, process, _Pid, Reason} -> result(down, ReqId, Res, Reason) - after Tmo -> + after Timeout -> result(timeout, ReqId, Res, undefined) end; receive_response(_, _) -> error({?MODULE, badarg}). --spec wait_response(RequestId) -> {'response', Result} | 'no_response' when +-dialyzer([{nowarn_function, receive_response/3}, no_return]). + +-spec receive_response(RequestIdCollection, Timeout, Delete) -> + {Result, Label, NewRequestIdCollection} | 'no_request' when + RequestIdCollection :: request_id_collection(), + Timeout :: timeout_time(), + Delete :: boolean(), + Result :: term(), + Label :: term(), + NewRequestIdCollection :: request_id_collection(). + +receive_response(ReqIdCol, WT, Del) when map_size(ReqIdCol) == 0, + is_boolean(Del) -> + _ = timeout_value(WT), + no_request; +receive_response(ReqIdCol, Tmo, Del) when is_map(ReqIdCol), + is_boolean(Del) -> + Timeout = timeout_value(Tmo), + receive + {spawn_reply, ReqId, error, Reason} + when is_map_key(ReqId, ReqIdCol), is_reference(ReqId) -> + collection_result(spawn_reply, ReqId, Reason, ReqIdCol, false, Del); + {'DOWN', ReqId, process, _Pid, Reason} + when is_map_key(ReqId, ReqIdCol), is_reference(ReqId) -> + collection_result(down, ReqId, Reason, ReqIdCol, false, Del) + after Timeout -> + collection_result(timeout, ok, ok, ReqIdCol, false, Del) + end; +receive_response(_, _, _) -> + error({?MODULE, badarg}). + +-spec wait_response(RequestId) -> + {'response', Result} | 'no_response' when RequestId :: request_id(), Result :: term(). -wait_response({Res, ReqId} = RId) when is_reference(Res), - is_reference(ReqId) -> - wait_response(RId, 0). +wait_response([Res|ReqId] = RId) when is_reference(Res), + is_reference(ReqId) -> + wait_response(RId, 0); +wait_response(_) -> + error({?MODULE, badarg}). -dialyzer([{nowarn_function, wait_response/2}, no_return]). -spec wait_response(RequestId, WaitTime) -> {'response', Result} | 'no_response' when RequestId :: request_id(), - WaitTime :: ?TIMEOUT_TYPE, + WaitTime :: timeout_time(), Result :: term(). -wait_response({Res, ReqId}, WT) when is_reference(Res), - is_reference(ReqId), - ?IS_VALID_TMO(WT) -> +wait_response([Res|ReqId], WT) when is_reference(Res), + is_reference(ReqId) -> + Timeout = timeout_value(WT), receive {spawn_reply, ReqId, error, Reason} -> result(spawn_reply, ReqId, Res, Reason); {'DOWN', ReqId, process, _Pid, Reason} -> {response, result(down, ReqId, Res, Reason)} - after WT -> + after Timeout -> no_response end; wait_response(_, _) -> error({?MODULE, badarg}). +-spec wait_response(RequestIdCollection, WaitTime, Delete) -> + {{'response', Result}, Label, NewRequestIdCollection} | + 'no_response' | + 'no_request' when + RequestIdCollection :: request_id_collection(), + WaitTime :: timeout_time(), + Delete :: boolean(), + Label :: term(), + NewRequestIdCollection :: request_id_collection(), + Result :: term(). + +wait_response(ReqIdCol, WT, Del) when map_size(ReqIdCol) == 0, + is_boolean(Del) -> + _ = timeout_value(WT), + no_request; +wait_response(ReqIdCol, WT, Del) when is_map(ReqIdCol), + is_boolean(Del) -> + Timeout = timeout_value(WT), + receive + {spawn_reply, ReqId, error, Reason} + when is_map_key(ReqId, ReqIdCol), is_reference(ReqId) -> + collection_result(spawn_reply, ReqId, Reason, ReqIdCol, true, Del); + {'DOWN', ReqId, process, _Pid, Reason} + when is_map_key(ReqId, ReqIdCol), is_reference(ReqId) -> + collection_result(down, ReqId, Reason, ReqIdCol, true, Del) + after Timeout -> + no_response + end; +wait_response(_, _, _) -> + error({?MODULE, badarg}). + -dialyzer([{nowarn_function, check_response/2}, no_return]). -spec check_response(Message, RequestId) -> @@ -247,21 +358,106 @@ wait_response(_, _) -> Message :: term(), RequestId :: request_id(), Result :: term(). - + check_response({spawn_reply, ReqId, error, Reason}, - {Res, ReqId}) when is_reference(Res), - is_reference(ReqId) -> + [Res|ReqId]) when is_reference(Res), + is_reference(ReqId) -> result(spawn_reply, ReqId, Res, Reason); check_response({'DOWN', ReqId, process, _Pid, Reason}, - {Res, ReqId}) when is_reference(Res), - is_reference(ReqId) -> + [Res|ReqId]) when is_reference(Res), + is_reference(ReqId) -> {response, result(down, ReqId, Res, Reason)}; -check_response(_Msg, {Res, ReqId}) when is_reference(Res), - is_reference(ReqId) -> +check_response(_Msg, [Res|ReqId]) when is_reference(Res), + is_reference(ReqId) -> no_response; check_response(_, _) -> error({?MODULE, badarg}). +-spec check_response(Message, RequestIdCollection, Delete) -> + {{'response', Result}, Label, NewRequestIdCollection} | + 'no_response' | + 'no_request' when + Message :: term(), + RequestIdCollection :: request_id_collection(), + Delete :: boolean(), + Result :: term(), + Label :: term(), + NewRequestIdCollection :: request_id_collection(). + +check_response(_Msg, ReqIdCol, Del) when map_size(ReqIdCol) == 0, + is_boolean(Del) -> + no_request; +check_response({spawn_reply, ReqId, error, Reason}, + ReqIdCol, Del) when is_reference(ReqId), + is_map_key(ReqId, ReqIdCol), + is_boolean(Del) -> + collection_result(spawn_reply, ReqId, Reason, ReqIdCol, true, Del); +check_response({'DOWN', ReqId, process, _Pid, Reason}, + ReqIdCol, Del) when is_reference(ReqId), + is_map_key(ReqId, ReqIdCol), + is_boolean(Del) -> + collection_result(down, ReqId, Reason, ReqIdCol, true, Del); +check_response(_Msg, ReqIdCol, Del) when is_map(ReqIdCol), + is_boolean(Del) -> + no_response; +check_response(_, _, _) -> + error({?MODULE, badarg}). + +-spec reqids_new() -> + NewRequestIdCollection::request_id_collection(). + +reqids_new() -> + maps:new(). + +-spec reqids_size(RequestIdCollection::request_id_collection()) -> + non_neg_integer(). +reqids_size(ReqIdCollection) -> + try + maps:size(ReqIdCollection) + catch + _:_ -> + error({?MODULE, badarg}) + end. + +-dialyzer({no_improper_lists, reqids_add/3}). + +-spec reqids_add(RequestId::request_id(), Label::term(), + RequestIdCollection::request_id_collection()) -> + NewRequestIdCollection::request_id_collection(). + +reqids_add([_|ReqId], _, ReqIdCollection) when is_reference(ReqId), + is_map_key(ReqId, + ReqIdCollection) -> + error({?MODULE, badarg}); +reqids_add([Res|ReqId], Label, ReqIdCollection) when is_reference(Res), + is_reference(ReqId), + is_map(ReqIdCollection) -> + maps:put(ReqId, [Res|Label], ReqIdCollection); +reqids_add(_, _, _) -> + error({?MODULE, badarg}). + +-dialyzer({no_improper_lists, reqids_to_list/1}). + +-spec reqids_to_list(RequestIdCollection::request_id_collection()) -> + [{RequestId::request_id(), Label::term()}]. + +reqids_to_list(ReqIdCollection) when is_map(ReqIdCollection) -> + try + maps:fold(fun (ReqId, [Res|Label], Acc) when is_reference(ReqId), + is_reference(Res) -> + [{[Res|ReqId], Label}|Acc]; + (_, _, _) -> + throw(badarg) + end, + [], + ReqIdCollection) + catch + throw:badarg -> + error({?MODULE, badarg}) + end; +reqids_to_list(_) -> + error({?MODULE, badarg}). + -type stack_item() :: {Module :: atom(), Function :: atom(), @@ -288,7 +484,7 @@ multicall(Ns, Fun) -> -spec multicall(Nodes, Fun, Timeout) -> Result when Nodes :: [atom()], Fun :: function(), - Timeout :: ?TIMEOUT_TYPE, + Timeout :: timeout_time(), Result :: term(). multicall(Ns, Fun, Timeout) when is_function(Fun, 0) -> @@ -311,7 +507,7 @@ multicall(Ns, M, F, A) -> Module :: atom(), Function :: atom(), Args :: [term()], - Timeout :: ?TIMEOUT_TYPE, + Timeout :: timeout_time(), Result :: [{ok, ReturnValue :: term()} | caught_call_exception()]. multicall(Ns, M, F, A, T) -> @@ -320,7 +516,8 @@ multicall(Ns, M, F, A, T) -> true = is_atom(F), true = is_list(A), Tag = make_ref(), - SendState = mcall_send_requests(Tag, Ns, M, F, A, T), + Timeout = timeout_value(T), + SendState = mcall_send_requests(Tag, Ns, M, F, A, Timeout), mcall_receive_replies(Tag, SendState) catch error:NotIErr when NotIErr /= internal_error -> @@ -531,6 +728,74 @@ result(timeout, ReqId, Res, _Reason) -> end end. +collection_result(timeout, _, _, ReqIdCollection, _, _) -> + Abandon = fun (ReqId, [Res|_Label]) when is_reference(ReqId), + is_reference(Res) -> + case call_abandon(ReqId) of + true -> + ok; + false -> + %% Spawn error or DOWN has arrived if + %% ReqId corresponds to an outstanding + %% request; fetch and drop it... + receive + {spawn_reply, ReqId, error, _} -> + ok; + {'DOWN', ReqId, process, _, _} -> + ok + after + 0 -> + ok %% Already handled... + end + end; + (_, _) -> + %% Invalid request id collection... + throw(badarg) + end, + try + maps:foreach(Abandon, ReqIdCollection) + catch + throw:badarg -> error({?MODULE, badarg}) + end, + error({?MODULE, timeout}); +collection_result(Type, ReqId, ResultReason, ReqIdCol, WrapResponse, Delete) -> + ReqIdInfo = case Delete of + true -> maps:take(ReqId, ReqIdCol); + false -> {maps:get(ReqId, ReqIdCol), ReqIdCol} + end, + case ReqIdInfo of + {[Res|Label], NewReqIdCol} when is_reference(Res) -> + try + Result = result(Type, ReqId, Res, ResultReason), + Response = if WrapResponse -> {response, Result}; + true -> Result + end, + {Response, Label, NewReqIdCol} + catch + Class:Reason -> + erlang:Class({Reason, Label, NewReqIdCol}) + end; + _ -> + %% Invalid request id collection... + error({?MODULE, badarg}) + end. + +timeout_value(infinity) -> + infinity; +timeout_value(Timeout) when ?IS_VALID_TMO_INT(Timeout) -> + Timeout; +timeout_value({abs, Timeout}) when is_integer(Timeout) -> + case Timeout - erlang:monotonic_time(millisecond) of + TMO when TMO < 0 -> + 0; + TMO when TMO > ?MAX_INT_TIMEOUT -> + error({?MODULE, badarg}); + TMO -> + TMO + end; +timeout_value(_) -> + error({?MODULE, badarg}). + deadline(infinity) -> infinity; deadline(?MAX_INT_TIMEOUT) -> diff --git a/lib/kernel/test/erpc_SUITE.erl b/lib/kernel/test/erpc_SUITE.erl index 9d295eefef91..265131b20cf8 100644 --- a/lib/kernel/test/erpc_SUITE.erl +++ b/lib/kernel/test/erpc_SUITE.erl @@ -29,6 +29,9 @@ send_request_wait_reqtmo/1, send_request_check_reqtmo/1, send_request_against_ei_node/1, + send_request_receive_reqid_collection/1, + send_request_wait_reqid_collection/1, + send_request_check_reqid_collection/1, multicall/1, multicall_reqtmo/1, multicall_recv_opt/1, multicall_recv_opt2/1, @@ -56,7 +59,7 @@ suite() -> [{ct_hooks,[ts_install_cth]}, {timetrap,{minutes,2}}]. -all() -> +all() -> [call, call_against_old_node, call_from_old_node, @@ -69,6 +72,9 @@ all() -> send_request_wait_reqtmo, send_request_check_reqtmo, send_request_against_ei_node, + send_request_receive_reqid_collection, + send_request_wait_reqid_collection, + send_request_check_reqid_collection, multicall, multicall_reqtmo, multicall_recv_opt, @@ -937,6 +943,327 @@ send_request_against_ei_node(Config) when is_list(Config) -> ok = stop_ei_node(EiNode). +send_request_receive_reqid_collection(Config) when is_list(Config) -> + {ok, _P, N} = ?CT_PEER(#{connection => 0}), + send_request_receive_reqid_collection_success(N), + send_request_receive_reqid_collection_timeout(N), + send_request_receive_reqid_collection_error(N), + ok. + +send_request_receive_reqid_collection_success(N) -> + + ReqId0 = erpc:send_request(N, fun () -> 0 end), + + ReqIdC0 = erpc:reqids_new(), + + ReqId1 = erpc:send_request(N, fun () -> receive after 400 -> 400 end end), + ReqIdC1 = erpc:reqids_add(ReqId1, req1, ReqIdC0), + 1 = erpc:reqids_size(ReqIdC1), + + ReqIdC2 = erpc:send_request(N, fun () -> receive after 1 -> 1 end end, req2, ReqIdC1), + 2 = erpc:reqids_size(ReqIdC2), + + ReqIdC3 = erpc:send_request(N, fun () -> receive after 200 -> 200 end end, req3, ReqIdC2), + 3 = erpc:reqids_size(ReqIdC3), + + {1, req2, ReqIdC4} = erpc:receive_response(ReqIdC3, infinity, true), + 2 = erpc:reqids_size(ReqIdC4), + + {200, req3, ReqIdC5} = erpc:receive_response(ReqIdC4, 7654, true), + 1 = erpc:reqids_size(ReqIdC5), + + {400, req1, ReqIdC6} = erpc:receive_response(ReqIdC5, 5000, true), + 0 = erpc:reqids_size(ReqIdC6), + + no_request = erpc:receive_response(ReqIdC6, 5000, true), + + 0 = erpc:receive_response(ReqId0), + + ok. + +send_request_receive_reqid_collection_timeout(N) -> + + ReqId0 = erpc:send_request(N, fun () -> 0 end), + + ReqIdC0 = erpc:reqids_new(), + + ReqId1 = erpc:send_request(N, fun () -> receive after 1000 -> 1000 end end), + ReqIdC1 = erpc:reqids_add(ReqId1, req1, ReqIdC0), + + ReqIdC2 = erpc:send_request(N, fun () -> receive after 1 -> 1 end end, req2, ReqIdC1), + + ReqId3 = erpc:send_request(N, fun () -> receive after 500 -> 500 end end), + ReqIdC3 = erpc:reqids_add(ReqId3, req3, ReqIdC2), + + Deadline = erlang:monotonic_time(millisecond) + 100, + + {1, req2, ReqIdC4} = erpc:receive_response(ReqIdC3, {abs, Deadline}, true), + 2 = erpc:reqids_size(ReqIdC4), + + try not_valid = erpc:receive_response(ReqIdC4, {abs, Deadline}, true) + catch error:{erpc, timeout} -> ok + end, + + Abandoned = lists:sort([{ReqId1, req1}, {ReqId3, req3}]), + Abandoned = lists:sort(erpc:reqids_to_list(ReqIdC4)), + + %% Make sure requests were abandoned... + try not_valid = erpc:receive_response(ReqIdC4, {abs, Deadline+1000}, false) + catch error:{erpc, timeout} -> ok + end, + + 0 = erpc:receive_response(ReqId0, infinity), + + ok. + +send_request_receive_reqid_collection_error(N) -> + + ReqId0 = erpc:send_request(N, fun () -> 0 end), + + ReqIdC0 = erpc:reqids_new(), + + ReqId1 = erpc:send_request(N, fun () -> receive after 600 -> 600 end end), + ReqIdC1 = erpc:reqids_add(ReqId1, req1, ReqIdC0), + try + nope = erpc:reqids_add(ReqId1, req2, ReqIdC1) + catch + error:{erpc, badarg} -> ok + end, + + ReqIdC2 = erpc:send_request(N, fun () -> receive after 800 -> erlang:halt() end end, req2, ReqIdC1), + ReqIdC3 = erpc:send_request(N, fun () -> receive after 200 -> error(errored) end end, req3, ReqIdC2), + ReqIdC4 = erpc:send_request(N, fun () -> exit(exited) end, req4, ReqIdC3), + ReqIdC5 = erpc:send_request(N, fun () -> receive after 400 -> throw(thrown) end end, req5, ReqIdC4), + + 5 = erpc:reqids_size(ReqIdC5), + + ReqIdC6 = try not_valid = erpc:receive_response(ReqIdC5, infinity, true) + catch exit:{{exception, exited}, req4, RIC6} -> RIC6 + end, + + 4 = erpc:reqids_size(ReqIdC6), + + try not_valid = erpc:receive_response(ReqIdC6, 2000, false) + catch error:{{exception, errored, _Stk}, req3, _} -> ok + end, + + try not_valid = erpc:receive_response(ReqIdC6, infinity, false) + catch throw:{thrown, req5, _} -> ok + end, + + {600, req1, ReqIdC6} = erpc:receive_response(ReqIdC6, infinity, false), + + try not_valid = erpc:receive_response(ReqIdC6, 5000, false) + catch error:{{erpc, noconnection}, req2, ReqIdC6} -> ok + end, + + 0 = erpc:receive_response(ReqId0), + + ok. + +send_request_wait_reqid_collection(Config) when is_list(Config) -> + {ok, _P, N} = ?CT_PEER(#{connection => 0}), + send_request_wait_reqid_collection_success(N), + send_request_wait_reqid_collection_timeout(N), + send_request_wait_reqid_collection_error(N), + ok. + +send_request_wait_reqid_collection_success(N) -> + + ReqId0 = erpc:send_request(N, fun () -> 0 end), + + ReqIdC0 = erpc:reqids_new(), + + ReqId1 = erpc:send_request(N, fun () -> receive after 400 -> 400 end end), + ReqIdC1 = erpc:reqids_add(ReqId1, req1, ReqIdC0), + 1 = erpc:reqids_size(ReqIdC1), + + ReqIdC2 = erpc:send_request(N, fun () -> receive after 1 -> 1 end end, req2, ReqIdC1), + 2 = erpc:reqids_size(ReqIdC2), + + ReqIdC3 = erpc:send_request(N, fun () -> receive after 200 -> 200 end end, req3, ReqIdC2), + 3 = erpc:reqids_size(ReqIdC3), + + {{response, 1}, req2, ReqIdC4} = erpc:wait_response(ReqIdC3, infinity, true), + 2 = erpc:reqids_size(ReqIdC4), + + {{response, 200}, req3, ReqIdC5} = erpc:wait_response(ReqIdC4, 7654, true), + 1 = erpc:reqids_size(ReqIdC5), + + {{response, 400}, req1, ReqIdC6} = erpc:wait_response(ReqIdC5, 5000, true), + 0 = erpc:reqids_size(ReqIdC6), + + no_request = erpc:wait_response(ReqIdC6, 5000, true), + + {response, 0} = erpc:wait_response(ReqId0), + + ok. + +send_request_wait_reqid_collection_timeout(N) -> + + ReqId0 = erpc:send_request(N, fun () -> 0 end), + + ReqIdC0 = erpc:reqids_new(), + + ReqIdC0 = erpc:reqids_new(), + + ReqId1 = erpc:send_request(N, fun () -> receive after 1000 -> 1000 end end), + ReqIdC1 = erpc:reqids_add(ReqId1, req1, ReqIdC0), + + ReqIdC2 = erpc:send_request(N, fun () -> receive after 1 -> 1 end end, req2, ReqIdC1), + + ReqId3 = erpc:send_request(N, fun () -> receive after 500 -> 500 end end), + ReqIdC3 = erpc:reqids_add(ReqId3, req3, ReqIdC2), + + Deadline = erlang:monotonic_time(millisecond) + 100, + + {{response, 1}, req2, ReqIdC4} = erpc:wait_response(ReqIdC3, {abs, Deadline}, true), + 2 = erpc:reqids_size(ReqIdC4), + + no_response = erpc:wait_response(ReqIdC4, {abs, Deadline}, true), + + Unhandled = lists:sort([{ReqId1, req1}, {ReqId3, req3}]), + Unhandled = lists:sort(erpc:reqids_to_list(ReqIdC4)), + + %% Make sure requests were not abandoned... + {{response, 500}, req3, ReqIdC4} = erpc:wait_response(ReqIdC4, {abs, Deadline+1500}, false), + {{response, 1000}, req1, ReqIdC4} = erpc:wait_response(ReqIdC4, {abs, Deadline+1500}, false), + + {response, 0} = erpc:wait_response(ReqId0, infinity), + + ok. + +send_request_wait_reqid_collection_error(N) -> + + ReqId0 = erpc:send_request(N, fun () -> 0 end), + + ReqIdC0 = erpc:reqids_new(), + + ReqId1 = erpc:send_request(N, fun () -> receive after 600 -> 600 end end), + ReqIdC1 = erpc:reqids_add(ReqId1, req1, ReqIdC0), + try + nope = erpc:reqids_add(ReqId1, req2, ReqIdC1) + catch + error:{erpc, badarg} -> ok + end, + + ReqIdC2 = erpc:send_request(N, fun () -> receive after 800 -> erlang:halt() end end, req2, ReqIdC1), + ReqIdC3 = erpc:send_request(N, fun () -> receive after 200 -> error(errored) end end, req3, ReqIdC2), + ReqIdC4 = erpc:send_request(N, fun () -> exit(exited) end, req4, ReqIdC3), + ReqIdC5 = erpc:send_request(N, fun () -> receive after 400 -> throw(thrown) end end, req5, ReqIdC4), + + 5 = erpc:reqids_size(ReqIdC5), + + ReqIdC6 = try not_valid = erpc:wait_response(ReqIdC5, infinity, true) + catch exit:{{exception, exited}, req4, RIC6} -> RIC6 + end, + + 4 = erpc:reqids_size(ReqIdC6), + + try not_valid = erpc:wait_response(ReqIdC6, 2000, false) + catch error:{{exception, errored, _Stk}, req3, _} -> ok + end, + + try not_valid = erpc:wait_response(ReqIdC6, infinity, false) + catch throw:{thrown, req5, _} -> ok + end, + + {{response, 600}, req1, ReqIdC6} = erpc:wait_response(ReqIdC6, infinity, false), + + try not_valid = erpc:wait_response(ReqIdC6, 5000, false) + catch error:{{erpc, noconnection}, req2, ReqIdC6} -> ok + end, + + {response, 0} = erpc:wait_response(ReqId0), + + ok. + +send_request_check_reqid_collection(Config) when is_list(Config) -> + {ok, _P, N} = ?CT_PEER(#{connection => 0}), + send_request_check_reqid_collection_success(N), + send_request_check_reqid_collection_error(N), + ok. + +send_request_check_reqid_collection_success(N) -> + + ReqId0 = erpc:send_request(N, fun () -> 0 end), + + ReqIdC0 = erpc:reqids_new(), + + ReqIdC1 = erpc:send_request(N, fun () -> receive after 600 -> 600 end end, req1, ReqIdC0), + 1 = erpc:reqids_size(ReqIdC1), + + ReqId2 = erpc:send_request(N, fun () -> receive after 200 -> 200 end end), + ReqIdC2 = erpc:reqids_add(ReqId2, req2, ReqIdC1), + 2 = erpc:reqids_size(ReqIdC2), + + ReqIdC3 = erpc:send_request(N, fun () -> receive after 400 -> 400 end end, req3, ReqIdC2), + 3 = erpc:reqids_size(ReqIdC3), + + Msg0 = next_msg(), + + no_response = erpc:check_response(Msg0, ReqIdC3, true), + + {{response, 200}, req2, ReqIdC4} = erpc:check_response(next_msg(), ReqIdC3, true), + 2 = erpc:reqids_size(ReqIdC4), + + {{response, 400}, req3, ReqIdC5} = erpc:check_response(next_msg(), ReqIdC4, true), + 1 = erpc:reqids_size(ReqIdC5), + + {{response, 600}, req1, ReqIdC6} = erpc:check_response(next_msg(), ReqIdC5, true), + 0 = erpc:reqids_size(ReqIdC6), + + no_request = erpc:check_response(Msg0, ReqIdC6, true), + + {response, 0} = erpc:check_response(Msg0, ReqId0), + + ok. + +send_request_check_reqid_collection_error(N) -> + + ReqId0 = erpc:send_request(N, fun () -> 0 end), + + ReqIdC0 = erpc:reqids_new(), + + ReqId1 = erpc:send_request(N, fun () -> receive after 600 -> 600 end end), + ReqIdC1 = erpc:reqids_add(ReqId1, req1, ReqIdC0), + + ReqIdC2 = erpc:send_request(N, fun () -> receive after 800 -> erlang:halt() end end, req2, ReqIdC1), + + ReqIdC3 = erpc:send_request(N, fun () -> receive after 200 -> error(errored) end end, req3, ReqIdC2), + + ReqIdC4 = erpc:send_request(N, fun () -> exit(exited) end, req4, ReqIdC3), + + ReqIdC5 = erpc:send_request(N, fun () -> receive after 400 -> throw(thrown) end end, req5, ReqIdC4), + + 5 = erpc:reqids_size(ReqIdC5), + + Msg0 = next_msg(), + + no_response = erpc:check_response(Msg0, ReqIdC5, true), + + ReqIdC6 = try not_valid = erpc:check_response(next_msg(), ReqIdC5, true) + catch exit:{{exception, exited}, req4, RIC6} -> RIC6 + end, + + try not_valid = erpc:check_response(next_msg(), ReqIdC6, false) + catch error:{{exception, errored, _Stk}, req3, ReqIdC6} -> ok + end, + + try not_valid = erpc:check_response(next_msg(), ReqIdC6, false) + catch throw:{thrown, req5, ReqIdC6} -> ok + end, + + {{response, 600}, req1, ReqIdC6} = erpc:check_response(next_msg(), ReqIdC6, false), + + try not_valid = erpc:check_response(next_msg(), ReqIdC6, false) + catch error:{{erpc, noconnection}, req2, ReqIdC6} -> ok + end, + + {response, 0} = erpc:check_response(Msg0, ReqId0), + + ok. + multicall(Config) -> {ok, _Peer1, Node1} = ?CT_PEER(#{connection => 0}), {ok, Peer2, Node2} = ?CT_PEER(#{connection => 0}), @@ -1743,6 +2070,9 @@ f2() -> timer:sleep(500), halt(). +next_msg() -> + receive M -> M end. + flush_msgq() -> flush_msgq(0). flush_msgq(N) -> diff --git a/lib/stdlib/doc/src/gen_event.xml b/lib/stdlib/doc/src/gen_event.xml index bb891fce56fd..676d6430720d 100644 --- a/lib/stdlib/doc/src/gen_event.xml +++ b/lib/stdlib/doc/src/gen_event.xml @@ -119,24 +119,89 @@ gen_event:stop -----> Module:terminate/2 + + + + + + + +

- A request handle, see send_request/3 + An opaque request identifier. See + send_request/3 for details.

+ + + + +

+ An opaque collection of request identifiers + (request_id()) + where each request identifier can be associated with a label + chosen by the user. For more information see + reqids_new/0. +

+
+
+ + + + +

+ 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 + timeout in milliseconds. That is, the operation will time out when + erlang:monotonic_time(millisecond) + 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 + (request_id_collection()) +, + since you do not have to recalculate the relative time until the deadline + over and over again. +

+
+
+
+ @@ -312,28 +377,24 @@ gen_event:stop -----> Module:terminate/2 - - check_response(Msg, RequestId) -> Result - Check if a message is a reply from a server. - - Msg = term() - RequestId = request_id() - Result = {reply, Reply} | no_reply | {error, Error} - Reply = Error = term() - + + Check if a message is a response to an asynchronous call request + to a generic event manager.

- This function is used to check if a previously received - message, for example by receive or - handle_info/2, is a result of a request made with + Check if Msg is a response corresponding + to the request identifier ReqId. The request + must have been made by send_request/3. - If Msg is a reply to the handle RequestId - 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 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 the specified event handler is not installed, the function returns {error,bad_module}. If @@ -346,6 +407,74 @@ gen_event:stop -----> Module:terminate/2 + + + Check if a message is a response to an asynchronous call request + to a generic event manager. + +

+ 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 request 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 + 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, + 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. 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, + 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. +

+
+
+ delete_handler(EventMgrRef, Handler, Args) -> Result Delete an event handler from a generic event manager. @@ -409,34 +538,29 @@ gen_event:stop -----> Module:terminate/2 does not exist, unless it is specified as Name.

- + - receive_response(RequestId, Timeout) -> Result - Receive for a reply from a server. - - RequestId = request_id() - Reply = term() - Timeout = timeout() - Result = {reply, Reply} | timeout | {error, Error} - Reply = Error = term() - + + Receive a response to an asynchronous call request + to a generic event manager.

- This function is used to receive for a reply of a request made with - send_request/3 - to the event manager. This function must be called from the same - process from which send_request/3 - was made. + 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 is an integer greater then or equal to zero - that specifies how many milliseconds to wait for an reply, or - the atom infinity to wait indefinitely. - If no reply is received within the specified - time, the function returns timeout. Assuming that the + 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) no response will be received after a timeout. Otherwise, - a garbage response might be received at a later time. + 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 @@ -453,44 +577,197 @@ gen_event:stop -----> Module:terminate/2

The difference between - wait_response() - and receive_response() is that receive_response() + wait_response/2 + and receive_response/2 is that receive_response/2 abandons the request at timeout so that a potential future - response is ignored, while wait_response() does not. + response is ignored, while wait_response/2 does not.

- send_request(EventMgrRef, Handler, Request) -> RequestId - Send a request to a generic event manager. - - EventMgrRef = Name | {Name,Node} | {global,GlobalName} -   | {via,Module,ViaName} | pid() -  Node = atom() -  GlobalName = ViaName = term() - Handler = Module | {Module,Id} -  Module = atom() -  Id = term() - Request = term() - RequestId = request_id() - + + Receive a response to an asynchronous call request + to a generic event manager. + +

+ 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 request 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 + 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, + 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 + at a later time. +

+

+ The difference between receive_response/3 and + wait_response/3 + is that receive_response/3 abandons the requests at timeout + 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 requests can still be used by subsequent calls to + 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, it will always block + until a timeout determined by Timeout is + triggered. +

+
+
+ + + + Save a request identifier. + +

+ Saves ReqId and associates a Label + with the request identifier by adding this information to + ReqIdCollection and returning the + resulting request identifier collection. +

+
+
+ + + + Create a new empty request identifier collection. +

+ Returns a new empty request identifier collection. A + request identifier collection can be utilized in order + the 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. +

- Sends a request to event handler Handler installed in - event manager EventMgrRef and returns a handle - RequestId. The return value RequestId shall - later be used with - receive_response/2, - wait_response/2, or - check_response/2 in the same process to - fetch the actual result of the request. + reqids_size/1 + can be used to determine the amount of request identifiers in a + request identifier collection. +

+
+
+ + + + Get size of a request identifier collection. + +

+ Returns the amount of request identifiers saved in + ReqIdCollection. +

+
+
+ + + + List a request identifiers. + +

+ Returns a list of {ReqId, Label} + tuples which corresponds to all request identifiers with their + associated labels present in the ReqIdCollection + collection. +

+
+
+ + + + Send an asyncronous call request to a generic event manager. + +

+ 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:wait_response(gen_event:send_request(EventMgrRef,Handler,Request), Timeout) + The call 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), + gen_event:call(EventMgrRef, + Handler, Request, Timeout), ignoring the error handling.

@@ -504,6 +781,38 @@ gen_event:stop -----> Module:terminate/2 + + + + Sends a request to a generic server. + +

+ 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 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_event:reqids_add(gen_event:send_request(EventMgrRef, + Handler, Request), Label, + ReqIdCollection), but calling send_request/5 + is slightly more efficient. +

+
+
+ start() -> Result start(EventMgrName | Options) -> Result @@ -742,30 +1051,24 @@ gen_event:stop -----> Module:terminate/2 - wait_response(RequestId, Timeout) -> Result - Wait for a reply from a server. - - RequestId = request_id() - Reply = term() - Timeout = timeout() - Result = {reply, Reply} | timeout | {error, Error} - Reply = Error = term() - + + Wait or poll for a response to an asynchronous call request + to a generic event manager.

- This function is used to wait for a reply of a request made with - send_request/3 - to the event manager. This function must be called from the same - process from which send_request/3 - was made. + 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.

- Timeout is an integer greater then or equal to zero - that specifies how many milliseconds to wait for an reply, or - the atom infinity to wait indefinitely. - If no reply is received within the specified + 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 must be invoked repeatedly until a + done, and thus the function can be invoked repeatedly until a reply is returned.

@@ -783,11 +1086,89 @@ gen_event:stop -----> Module:terminate/2

The difference between - receive_response() - and wait_response() is that receive_response() + receive_response/2 + and wait_response/2 is that receive_response/2 abandons the request at timeout so that a potential future - response is ignored, while wait_response() does not. + response is ignored, while wait_response/2 does not. +

+
+
+ + + + Wait or poll for a response to an asynchronous call request + to a generic event manager. + +

+ 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 request 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 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, + 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, 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(), receive_response(), + or wait_response(). +

+

+ The difference between + receive_response/3 + and wait_response/3 is that receive_response/3 + abandons requests at timeout so that a 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 requests can still be used by subsequent calls to + 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, it will always block + until a timeout determined by WaitTime is + triggered and then return no_reply. +

diff --git a/lib/stdlib/doc/src/gen_server.xml b/lib/stdlib/doc/src/gen_server.xml index f9c7419ade4a..6f5a650acccd 100644 --- a/lib/stdlib/doc/src/gen_server.xml +++ b/lib/stdlib/doc/src/gen_server.xml @@ -412,12 +412,67 @@ gen_server:abcast -----> Module:handle_cast/2

- A request handle, see - send_request/2 + An opaque request identifier. See + send_request/2 for details.

+ + + + +

+ An opaque collection of request identifiers + (request_id()) + where each request identifier can be associated with a label + chosen by the user. For more information see + reqids_new/0. +

+
+
+ + + + +

+ 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 + timeout in milliseconds. That is, the operation will time out when + erlang:monotonic_time(millisecond) + 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 + (request_id_collection()) +, + since you do not have to recalculate the relative time until the deadline + over and over again. +

+
+
+
@@ -607,31 +662,101 @@ gen_server:abcast -----> Module:handle_cast/2 - - Check if a message is a reply from a server. + + Check if a message is a response from a server.

- This function is used to check if a previously received - message, for example by receive or - handle_info/2, is a result of a request made with - send_request/2. - If Msg is a reply - to the handle RequestId - the result of the request is returned in Reply. - Otherwise returns no_reply and no cleanup is done, and - thus the function must be invoked repeatedly until a reply - is returned. + 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.

+

+ 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. +

- The return value Reply is passed from the return value - of Module:handle_call/3. + The return value Reply is passed from the + return value of Module:handle_call/3.

The function returns an error if the gen_server - dies before or during this request. + died before a reply was sent.

+ + + + Check if a message is a response from a server. + +

+ 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 request 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 + 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, + 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. 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, + 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. +

+
+
@@ -786,45 +911,123 @@ gen_server:abcast -----> Module:handle_cast/2 - Receive a reply from a server. + Receive a response from a server.

- This function is used to receive a reply to a request made with - send_request/2 - to a gen_server process. - This function must be called by the same process that called - send_request/2. + 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 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, - the function returns timeout. - If the server executes on a node supporting aliases - (introduced in OTP 24) no response will be received - after a time-out. Otherwise, a garbage response - might be received at a later time. + 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. Otherwise, a + stray response might be received at a later time.

- A returned Reply is passed from - the return value of Module:handle_call/3. + The return value Reply is passed from the + return value of Module:handle_call/3.

The function returns an error if the gen_server - dies before or during this request. + died before a reply was sent.

- The difference between - wait_response() - and receive_response() is that receive_response() - abandons the request at time-out so that a potential late - response is ignored, while wait_response() does not. + The difference between receive_response/2 and + 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 does not.

+ + + Receive a response from a server. + +

+ 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 request 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 + 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, + 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 + at a later time. +

+

+ The difference between receive_response/3 and + wait_response/3 + is that receive_response/3 abandons the requests at timeout + 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 requests can still be used by subsequent calls to + 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, it will always block + until a timeout determined by Timeout is + triggered. +

+
+
+ Send a reply to a client. @@ -848,29 +1051,105 @@ gen_server:abcast -----> Module:handle_cast/2 + + + Save a request identifier. + +

+ Saves ReqId and associates a Label + with the request identifier by adding this information to + ReqIdCollection and returning the + resulting request identifier collection. +

+
+
+ + + + Create a new empty request identifier collection. + +

+ Returns a new empty request identifier collection. A + request identifier collection can be utilized in order + the 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 + 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. +

+
+
+ + + + Get size of a request identifier collection. + +

+ Returns the amount of request identifiers saved in + ReqIdCollection. +

+
+
+ + + + List a request identifiers. + +

+ Returns a list of {ReqId, Label} + tuples which corresponds to all request identifiers with their + associated labels present in the ReqIdCollection + collection. +

+
+
+ Sends a request to a generic server.

- Sends a request to the ServerRef - of the gen_server process - and returns a handle RequestId. - The returned handle shall later be used with - receive_response/2, - wait_response/2, or - check_response/2 - to fetch the actual result of the request. + 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.

- The call - - gen_server:wait_response(gen_server:send_request(ServerRef, - Request), Timeout) - - can be seen as equivalent to - gen_server:call(ServerRef, Request, Timeout), - ignoring the error handling. + The call gen_server:receive_response(gen_server:send_request(ServerRef, + Request), Timeout) can be seen as equivalent to + gen_server:call(ServerRef, Request, + Timeout), ignoring the error handling.

The gen_server process calls @@ -891,6 +1170,36 @@ gen_server:abcast -----> Module:handle_cast/2 + + + Sends a request to a generic server. + +

+ 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. +

+ +

+ The same as calling + gen_server:reqids_add(gen_server:send_request(ServerRef, + Request), Label, + ReqIdCollection), but calling send_request/4 + is slightly more efficient. +

+
+
+ @@ -1033,41 +1342,116 @@ gen_server:abcast -----> Module:handle_cast/2 - Wait for a reply from a server. + Wait or poll for a response from a server.

- This function is used to wait for a reply of a request made with - send_request/2 - from the gen_server process. - This function must be called from the same process that called - send_request/2. + 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.

- 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, - the function returns timeout and no cleanup is done; - thus the function can be invoked repeatedly until a + 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.

- The return value Reply is passed from - the return value of Module:handle_call/3. + The return value Reply is passed from the + return value of Module:handle_call/3.

The function returns an error if the gen_server - dies before or during this request. + died before a reply was sent.

The difference between - receive_response() - and wait_response() is that receive_response() + 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() does not. + response is ignored, while wait_response/2 does not.

+ + + + Wait or poll for a response from a server. + +

+ 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 request 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 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, + 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, 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(), receive_response(), + or wait_response(). +

+

+ The difference between + receive_response/3 + and wait_response/3 is that receive_response/3 + abandons requests at timeout so that a 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 requests can still be used by subsequent calls to + 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, it will always block + until a timeout determined by WaitTime is + triggered and then return no_reply. +

+
+
diff --git a/lib/stdlib/doc/src/gen_statem.xml b/lib/stdlib/doc/src/gen_statem.xml index c1a2b1e52926..6711addc1c58 100644 --- a/lib/stdlib/doc/src/gen_statem.xml +++ b/lib/stdlib/doc/src/gen_statem.xml @@ -1624,11 +1624,67 @@ handle_event(_, _, State, Data) ->

- A request handle, see send_request/2 + An opaque request identifier. See + send_request/2 for details.

+ + + + +

+ An opaque collection of request identifiers + (request_id()) + where each request identifier can be associated with a label + chosen by the user. For more information see + reqids_new/0. +

+
+
+ + + + +

+ 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 + timeout in milliseconds. That is, the operation will time out when + erlang:monotonic_time(millisecond) + 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 + (request_id_collection()) +, + since you do not have to recalculate the relative time until the deadline + over and over again. +

+
+
+
@@ -1744,15 +1800,15 @@ handle_event(_, _, State, Data) -> - + Check if a message is a reply from a server.

- This function is used to check if a previously received - message, for example by receive or - handle_info/2, is a result of a request made with + Check if Msg is a response corresponding + to the request identifier ReqId. The request + must have been made by send_request/2. - If Msg is a reply to the handle RequestId + 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 @@ -1774,6 +1830,73 @@ handle_event(_, _, State, Data) -> + + + Check if a message is a reply from a server. + +

+ 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 request 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 + 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, + 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. 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, + 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. +

+
+
+ Enter the gen_statem receive loop. @@ -1871,11 +1994,23 @@ handle_event(_, _, State, Data) -> - Receive for a reply from a server.

- This function is used to receive for a reply of a request made with + The same as calling + gen_statem:receive_response(ReqId, + infinity). +

+
+
+ + + + Receive for a reply from a server. + +

+ 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 @@ -1883,15 +2018,13 @@ handle_event(_, _, State, Data) -> was made.

- Timeout is an integer - that specifies how many milliseconds to wait for an reply, or - the atom infinity to wait indefinitely. Defaults to - infinity. - If no reply is received within the specified - time, the function returns timeout. Assuming that the + 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) no response will be received after a timeout. Otherwise, - a garbage response might be received at a later time. + 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 generated when a @@ -1908,13 +2041,94 @@ handle_event(_, _, State, Data) ->

The difference between - wait_response() - and receive_response() is that receive_response() + wait_response/2 + and receive_response/2 is that receive_response/2 abandons the request at timeout so that a potential future - response is ignored, while wait_response() does not. + response is ignored, while wait_response/2 does not.

+ + + + Receive a response from a server. + +

+ 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 request 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 + 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, + 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 + at a later time. +

+

+ The difference between receive_response/3 and + wait_response/3 + is that receive_response/3 abandons the requests at timeout + 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 requests can still be used by subsequent calls to + 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, it will always block + until a timeout determined by Timeout is + triggered. +

+
+
@@ -1950,20 +2164,98 @@ handle_event(_, _, State, Data) -> - - Send a request to a gen_statem. + + Save a request identifier. +

+ Saves ReqId and associates a Label + with the request identifier by adding this information to + ReqIdCollection and returning the + resulting request identifier collection. +

+
+
+ + + + Create a new empty request identifier collection. + +

+ Returns a new empty request identifier collection. A + request identifier collection can be utilized in order + the handle multiple outstanding requests. +

- Sends a request to the gen_statem - ServerRef - and returns a handle RequestId. -

+ 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 + 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. +

+
+
+ + + + Get size of a request identifier collection. +

- The return value RequestId shall later be used with - receive_response/1,2, - wait_response/1,2, or + Returns the amount of request identifiers saved in + ReqIdCollection. +

+
+
+ + + + List a request identifiers. + +

+ Returns a list of {ReqId, Label} + tuples which corresponds to all request identifiers with their + associated labels present in the ReqIdCollection + collection. +

+
+
+ + + + Send a request to a gen_statem. + +

+ 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. + 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.

The call gen_statem:wait_response(gen_statem:send_request(ServerRef,Request), Timeout) @@ -1993,6 +2285,36 @@ handle_event(_, _, State, Data) -> + + + Sends a request to a generic server. + +

+ 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. +

+ +

+ The same as calling + gen_statem:reqids_add(statem:send_request(ServerRef, + Request), Label, + ReqIdCollection), but calling send_request/4 + is slightly more efficient. +

+
+
+ @@ -2222,12 +2544,24 @@ handle_event(_, _, State, Data) -> - - + Wait for a reply from a server.

- This function is used to wait for a reply of a request made with + The same as calling + gen_statem:receive_response(ReqId, + infinity). +

+
+
+ + + + Wait or poll for a reply from a server. + +

+ 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 @@ -2235,11 +2569,8 @@ handle_event(_, _, State, Data) -> was made.

- Timeout is an integer - that specifies how many milliseconds to wait for an reply, or - the atom infinity to wait indefinitely. Defaults to - infinity. - If no reply is received within the specified + 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. @@ -2259,13 +2590,90 @@ handle_event(_, _, State, Data) ->

The difference between - receive_response() - and wait_response() is that receive_response() + receive_response/2 + and wait_response/2 is that receive_response/2 abandons the request at timeout so that a potential future - response is ignored, while wait_response() does not. + response is ignored, while wait_response/2 does not.

+ + + + Wait or poll for a response from a server. + +

+ 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 request 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 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, + 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, 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(), receive_response(), + or wait_response(). +

+

+ The difference between + receive_response/3 + and wait_response/3 is that receive_response/3 + abandons requests at timeout so that a 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 requests can still be used by subsequent calls to + 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, it will always block + until a timeout determined by WaitTime is + triggered and then return no_reply. +

+
+
diff --git a/lib/stdlib/src/gen.erl b/lib/stdlib/src/gen.erl index 1ebd4ac8686d..363094fb154d 100644 --- a/lib/stdlib/src/gen.erl +++ b/lib/stdlib/src/gen.erl @@ -29,23 +29,27 @@ -export([start/5, start/6, debug_options/2, hibernate_after/1, name/1, unregister_name/1, get_proc_name/1, get_parent/0, call/3, call/4, reply/2, - send_request/3, wait_response/2, - receive_response/2, check_response/2, + send_request/3, send_request/5, + wait_response/2, receive_response/2, check_response/2, + wait_response/3, receive_response/3, check_response/3, + reqids_new/0, reqids_size/1, + reqids_add/3, reqids_to_list/1, stop/1, stop/3]). -export([init_it/6, init_it/7]). -export([format_status_header/2, format_status/4]). +-define(MAX_INT_TIMEOUT, 4294967295). -define(default_timeout, 5000). -include("logger.hrl"). %%----------------------------------------------------------------- --export_type( - [reply_tag/0, - request_id/0]). +-export_type([reply_tag/0, + request_id/0, + request_id_collection/0]). -type linkage() :: 'monitor' | 'link' | 'nolink'. -type emgr_name() :: {'local', atom()} @@ -73,6 +77,10 @@ -opaque request_id() :: reference(). +-opaque request_id_collection() :: map(). + +-type response_timeout() :: + 0..?MAX_INT_TIMEOUT | 'infinity' | {abs, integer()}. %%----------------------------------------------------------------- %% Starts a generic process. @@ -278,11 +286,12 @@ get_node(Process) -> node(Process) end. --spec send_request(Name::server_ref(), Label::term(), Request::term()) -> request_id(). -send_request(Process, Label, Request) when is_pid(Process) -> - do_send_request(Process, Label, Request); -send_request(Process, Label, Request) -> - Fun = fun(Pid) -> do_send_request(Pid, Label, Request) end, +-spec send_request(Name::server_ref(), Tag::term(), Request::term()) -> + request_id(). +send_request(Process, Tag, Request) when is_pid(Process) -> + do_send_request(Process, Tag, Request); +send_request(Process, Tag, Request) -> + Fun = fun(Pid) -> do_send_request(Pid, Tag, Request) end, try do_for_proc(Process, Fun) catch exit:Reason -> %% Make send_request async and fake a down message @@ -291,62 +300,232 @@ send_request(Process, Label, Request) -> Mref end. +-spec send_request(Name::server_ref(), Tag::term(), Request::term(), + Label::term(), ReqIdCol::request_id_collection()) -> + request_id_collection(). +send_request(Process, Tag, Request, Label, ReqIdCol) when is_map(ReqIdCol) -> + maps:put(send_request(Process, Tag, Request), Label, ReqIdCol). + -dialyzer({no_improper_lists, do_send_request/3}). -do_send_request(Process, Label, Request) -> - Mref = erlang:monitor(process, Process, [{alias, demonitor}]), - erlang:send(Process, {Label, {self(), [alias|Mref]}, Request}, [noconnect]), - Mref. +do_send_request(Process, Tag, Request) -> + ReqId = erlang:monitor(process, Process, [{alias, demonitor}]), + _ = erlang:send(Process, {Tag, {self(), [alias|ReqId]}, Request}, [noconnect]), + ReqId. %% %% Wait for a reply to the client. %% Note: if timeout is returned monitors are kept. --spec wait_response(RequestId::request_id(), timeout()) -> - {reply, Reply::term()} | 'timeout' | {error, {term(), server_ref()}}. -wait_response(Mref, Timeout) when is_reference(Mref) -> +-spec wait_response(ReqId, Timeout) -> Result when + ReqId :: request_id(), + Timeout :: response_timeout(), + Resp :: {reply, Reply::term()} | {error, {Reason::term(), server_ref()}}, + Result :: Resp | 'timeout'. + +wait_response(ReqId, Timeout) -> + TMO = timeout_value(Timeout), receive - {[alias|Mref], Reply} -> - erlang:demonitor(Mref, [flush]), + {[alias|ReqId], Reply} -> + erlang:demonitor(ReqId, [flush]), {reply, Reply}; - {'DOWN', Mref, _, Object, Reason} -> + {'DOWN', ReqId, _, Object, Reason} -> {error, {Reason, Object}} - after Timeout -> + after TMO -> timeout end. --spec receive_response(RequestId::request_id(), timeout()) -> - {reply, Reply::term()} | 'timeout' | {error, {term(), server_ref()}}. -receive_response(Mref, Timeout) when is_reference(Mref) -> +-spec wait_response(ReqIdCol, Timeout, Delete) -> Result when + ReqIdCol :: request_id_collection(), + Timeout :: response_timeout(), + Delete :: boolean(), + Resp :: {reply, Reply::term()} | {error, {Reason::term(), server_ref()}}, + Result :: {Resp, Label::term(), NewReqIdCol::request_id_collection()} | + 'no_request' | 'timeout'. + +wait_response(ReqIdCol, Timeout, Delete) when map_size(ReqIdCol) == 0, + is_boolean(Delete) -> + _ = timeout_value(Timeout), + no_request; +wait_response(ReqIdCol, Timeout, Delete) when is_map(ReqIdCol), + is_boolean(Delete) -> + TMO = timeout_value(Timeout), receive - {[alias|Mref], Reply} -> - erlang:demonitor(Mref, [flush]), + {[alias|ReqId], _} = Msg when is_map_key(ReqId, ReqIdCol) -> + collection_result(Msg, ReqIdCol, Delete); + {'DOWN', ReqId, _, _, _} = Msg when is_map_key(ReqId, ReqIdCol) -> + collection_result(Msg, ReqIdCol, Delete) + after TMO -> + timeout + end. + +-spec receive_response(ReqId, Timeout) -> Result when + ReqId :: request_id(), + Timeout :: response_timeout(), + Resp :: {reply, Reply::term()} | {error, {Reason::term(), server_ref()}}, + Result :: Resp | 'timeout'. + +receive_response(ReqId, Timeout) -> + TMO = timeout_value(Timeout), + receive + {[alias|ReqId], Reply} -> + erlang:demonitor(ReqId, [flush]), {reply, Reply}; - {'DOWN', Mref, _, Object, Reason} -> + {'DOWN', ReqId, _, Object, Reason} -> {error, {Reason, Object}} - after Timeout -> - erlang:demonitor(Mref, [flush]), + after TMO -> + erlang:demonitor(ReqId, [flush]), receive - {[alias|Mref], Reply} -> + {[alias|ReqId], Reply} -> {reply, Reply} after 0 -> timeout end end. --spec check_response(RequestId::term(), Key::request_id()) -> - {reply, Reply::term()} | 'no_reply' | {error, {term(), server_ref()}}. -check_response(Msg, Mref) when is_reference(Mref) -> +-spec receive_response(ReqIdCol, Timeout, Delete) -> Result when + ReqIdCol :: request_id_collection(), + Timeout :: response_timeout(), + Delete :: boolean(), + Resp :: {reply, Reply::term()} | {error, {Reason::term(), server_ref()}}, + Result :: {Resp, Label::term(), NewReqIdCol::request_id_collection()} + | 'no_request' | 'timeout'. + +receive_response(ReqIdCol, Timeout, Delete) when map_size(ReqIdCol) == 0, + is_boolean(Delete) -> + _ = timeout_value(Timeout), + no_request; +receive_response(ReqIdCol, Timeout, Delete) when is_map(ReqIdCol), + is_boolean(Delete) -> + TMO = timeout_value(Timeout), + receive + {[alias|ReqId], _} = Msg when is_map_key(ReqId, ReqIdCol) -> + collection_result(Msg, ReqIdCol, Delete); + {'DOWN', Mref, _, _, _} = Msg when is_map_key(Mref, ReqIdCol) -> + collection_result(Msg, ReqIdCol, Delete) + after TMO -> + maps:foreach(fun (ReqId, _Label) when is_reference(ReqId) -> + erlang:demonitor(ReqId, [flush]); + (_, _) -> + error(badarg) + end, ReqIdCol), + flush_responses(ReqIdCol), + timeout + end. + +-spec check_response(Msg::term(), ReqIdOrReqIdCol) -> Result when + ReqIdOrReqIdCol :: request_id() | request_id_collection(), + ReqIdResp :: {reply, Reply::term()} | + {error, {Reason::term(), server_ref()}}, + ReqIdColResp :: {{reply, Reply::term()}, Label::term()} | + {{error, {Reason::term(), server_ref()}}, Label::term()}, + Result :: ReqIdResp | ReqIdColResp | 'no_reply'. + +check_response(Msg, ReqId) when is_reference(ReqId) -> case Msg of - {[alias|Mref], Reply} -> - erlang:demonitor(Mref, [flush]), + {[alias|ReqId], Reply} -> + erlang:demonitor(ReqId, [flush]), {reply, Reply}; - {'DOWN', Mref, _, Object, Reason} -> + {'DOWN', ReqId, _, Object, Reason} -> {error, {Reason, Object}}; _ -> no_reply + end; +check_response(_, _) -> + error(badarg). + +-spec check_response(Msg, ReqIdCol, Delete) -> Result when + Msg :: term(), + ReqIdCol :: request_id_collection(), + Delete :: boolean(), + Resp :: {reply, Reply::term()} | {error, {Reason::term(), server_ref()}}, + Result :: {Resp, Label::term(), NewReqIdCol::request_id_collection()} + | 'no_request' | 'no_reply'. + +check_response(_Msg, ReqIdCol, Delete) when map_size(ReqIdCol) == 0, + is_boolean(Delete) -> + no_request; +check_response(Msg, ReqIdCol, Delete) when is_map(ReqIdCol), + is_boolean(Delete) -> + case Msg of + {[alias|ReqId], _} = Msg when is_map_key(ReqId, ReqIdCol) -> + collection_result(Msg, ReqIdCol, Delete); + {'DOWN', Mref, _, _, _} = Msg when is_map_key(Mref, ReqIdCol) -> + collection_result(Msg, ReqIdCol, Delete); + _ -> + no_reply end. +collection_result({[alias|ReqId], Reply}, ReqIdCol, Delete) -> + _ = erlang:demonitor(ReqId, [flush]), + collection_result({reply, Reply}, ReqId, ReqIdCol, Delete); +collection_result({'DOWN', ReqId, _, Object, Reason}, ReqIdCol, Delete) -> + collection_result({error, {Reason, Object}}, ReqId, ReqIdCol, Delete). + +collection_result(Resp, ReqId, ReqIdCol, false) -> + {Resp, maps:get(ReqId, ReqIdCol), ReqIdCol}; +collection_result(Resp, ReqId, ReqIdCol, true) -> + {Label, NewReqIdCol} = maps:take(ReqId, ReqIdCol), + {Resp, Label, NewReqIdCol}. + +flush_responses(ReqIdCol) -> + receive + {[alias|Mref], _Reply} when is_map_key(Mref, ReqIdCol) -> + flush_responses(ReqIdCol) + after 0 -> + ok + end. + +timeout_value(infinity) -> + infinity; +timeout_value(Timeout) when 0 =< Timeout, Timeout =< ?MAX_INT_TIMEOUT -> + Timeout; +timeout_value({abs, Timeout}) when is_integer(Timeout) -> + case Timeout - erlang:monotonic_time(millisecond) of + TMO when TMO < 0 -> + 0; + TMO when TMO > ?MAX_INT_TIMEOUT -> + error(badarg); + TMO -> + TMO + end; +timeout_value(_) -> + error(badarg). + +-spec reqids_new() -> + NewReqIdCol::request_id_collection(). + +reqids_new() -> + maps:new(). + +-spec reqids_size(request_id_collection()) -> + non_neg_integer(). +reqids_size(ReqIdCol) when is_map(ReqIdCol) -> + maps:size(ReqIdCol); +reqids_size(_) -> + error(badarg). + +-spec reqids_add(ReqId::request_id(), Label::term(), + ReqIdCol::request_id_collection()) -> + NewReqIdCol::request_id_collection(). + +reqids_add(ReqId, _, ReqIdCol) when is_reference(ReqId), + is_map_key(ReqId, ReqIdCol) -> + error(badarg); +reqids_add(ReqId, Label, ReqIdCol) when is_reference(ReqId), + is_map(ReqIdCol) -> + maps:put(ReqId, Label, ReqIdCol); +reqids_add(_, _, _) -> + error(badarg). + +-spec reqids_to_list(ReqIdCol::request_id_collection()) -> + [{ReqId::request_id(), Label::term()}]. + +reqids_to_list(ReqIdCol) when is_map(ReqIdCol) -> + maps:to_list(ReqIdCol); +reqids_to_list(_) -> + error(badarg). + %% %% Send a reply to the client. %% diff --git a/lib/stdlib/src/gen_event.erl b/lib/stdlib/src/gen_event.erl index afb63c5b28fa..3f5737f304c2 100644 --- a/lib/stdlib/src/gen_event.erl +++ b/lib/stdlib/src/gen_event.erl @@ -43,7 +43,11 @@ notify/2, sync_notify/2, add_handler/3, add_sup_handler/3, delete_handler/3, swap_handler/3, swap_sup_handler/3, which_handlers/1, call/3, call/4, - send_request/3, wait_response/2, receive_response/2, check_response/2, + send_request/3, send_request/5, + wait_response/2, receive_response/2, check_response/2, + wait_response/3, receive_response/3, check_response/3, + reqids_new/0, reqids_size/1, + reqids_add/3, reqids_to_list/1, wake_hib/5]). -export([init_it/6, @@ -58,7 +62,7 @@ -export([format_log/1, format_log/2]). -export_type([handler/0, handler_args/0, add_handler_ret/0, - del_handler_ret/0, request_id/0]). + del_handler_ret/0, request_id/0, request_id_collection/0]). -record(handler, {module :: atom(), id = false, @@ -150,6 +154,11 @@ -opaque request_id() :: gen:request_id(). +-opaque request_id_collection() :: gen:request_id_collection(). + +-type response_timeout() :: + timeout() | {abs, integer()}. + %%--------------------------------------------------------------------------- -define(NO_CALLBACK, 'no callback module'). @@ -243,32 +252,182 @@ call(M, Handler, Query) -> call1(M, Handler, Query). -spec call(emgr_ref(), handler(), term(), timeout()) -> term(). call(M, Handler, Query, Timeout) -> call1(M, Handler, Query, Timeout). --spec send_request(emgr_ref(), handler(), term()) -> request_id(). -send_request(M, Handler, Query) -> - gen:send_request(M, self(), {call, Handler, Query}). +-spec send_request(EventMgrRef::emgr_ref(), Handler::handler(), Request::term()) -> + ReqId::request_id(). +send_request(M, Handler, Request) -> + try + gen:send_request(M, self(), {call, Handler, Request}) + catch + error:badarg -> + error(badarg, [M, Handler, Request]) + end. --spec wait_response(RequestId::request_id(), timeout()) -> - {reply, Reply::term()} | 'timeout' | {error, {Reason::term(), emgr_ref()}}. -wait_response(RequestId, Timeout) -> - case gen:wait_response(RequestId, Timeout) of +-spec send_request(EventMgrRef::emgr_ref(), + Handler::handler(), + Request::term(), + Label::term(), + ReqIdCollection::request_id_collection()) -> + NewReqIdCollection::request_id_collection(). +send_request(M, Handler, Request, Label, ReqIdCol) -> + try + gen:send_request(M, self(), {call, Handler, Request}, Label, ReqIdCol) + catch + error:badarg -> + error(badarg, [M, Handler, Request, Label, ReqIdCol]) + end. + +-spec wait_response(ReqId, WaitTime) -> Result when + ReqId :: request_id(), + WaitTime :: response_timeout(), + Response :: {reply, Reply::term()} + | {error, {Reason::term(), emgr_ref()}}, + Result :: Response | 'timeout'. + +wait_response(ReqId, WaitTime) -> + try gen:wait_response(ReqId, WaitTime) of {reply, {error, _} = Err} -> Err; Return -> Return + catch + error:badarg -> + error(badarg, [ReqId, WaitTime]) end. --spec receive_response(RequestId::request_id(), timeout()) -> - {reply, Reply::term()} | 'timeout' | {error, {Reason::term(), emgr_ref()}}. -receive_response(RequestId, Timeout) -> - case gen:receive_response(RequestId, Timeout) of +-spec wait_response(ReqIdCollection, WaitTime, Delete) -> Result when + ReqIdCollection :: request_id_collection(), + WaitTime :: response_timeout(), + Delete :: boolean(), + Response :: {reply, Reply::term()} | + {error, {Reason::term(), emgr_ref()}}, + Result :: {Response, + Label::term(), + NewReqIdCollection::request_id_collection()} | + 'no_request' | + 'timeout'. + +wait_response(ReqIdCol, WaitTime, Delete) -> + try gen:wait_response(ReqIdCol, WaitTime, Delete) of + {{reply, {error, _} = Err}, Label, NewReqIdCol} -> + {Err, Label, NewReqIdCol}; + Return -> + Return + catch + error:badarg -> + error(badarg, [ReqIdCol, WaitTime, Delete]) + end. + +-spec receive_response(ReqId, Timeout) -> Result when + ReqId :: request_id(), + Timeout :: response_timeout(), + Response :: {reply, Reply::term()} | + {error, {Reason::term(), emgr_ref()}}, + Result :: Response | 'timeout'. + +receive_response(ReqId, Timeout) -> + try gen:receive_response(ReqId, Timeout) of {reply, {error, _} = Err} -> Err; Return -> Return + catch + error:badarg -> + error(badarg, [ReqId, Timeout]) end. --spec check_response(Msg::term(), RequestId::request_id()) -> - {reply, Reply::term()} | 'no_reply' | {error, {Reason::term(), emgr_ref()}}. -check_response(Msg, RequestId) -> - case gen:check_response(Msg, RequestId) of +-spec receive_response(ReqIdCollection, Timeout, Delete) -> Result when + ReqIdCollection :: request_id_collection(), + Timeout :: response_timeout(), + Delete :: boolean(), + Response :: {reply, Reply::term()} | + {error, {Reason::term(), emgr_ref()}}, + Result :: {Response, + Label::term(), + NewReqIdCollection::request_id_collection()} | + 'no_request' | + 'timeout'. + +receive_response(ReqIdCol, Timeout, Delete) -> + try gen:receive_response(ReqIdCol, Timeout, Delete) of + {{reply, {error, _} = Err}, Label, NewReqIdCol} -> + {Err, Label, NewReqIdCol}; + Return -> + Return + catch + error:badarg -> + error(badarg, [ReqIdCol, Timeout, Delete]) + end. + +-spec check_response(Msg, ReqId) -> Result when + Msg :: term(), + ReqId :: request_id(), + Response :: {reply, Reply::term()} | + {error, {Reason::term(), emgr_ref()}}, + Result :: Response | 'no_reply'. + +check_response(Msg, ReqId) -> + try gen:check_response(Msg, ReqId) of {reply, {error, _} = Err} -> Err; Return -> Return + catch + error:badarg -> + error(badarg, [Msg, ReqId]) + end. + +-spec check_response(Msg, ReqIdCollection, Delete) -> Result when + Msg :: term(), + ReqIdCollection :: request_id_collection(), + Delete :: boolean(), + Response :: {reply, Reply::term()} | + {error, {Reason::term(), emgr_ref()}}, + Result :: {Response, + Label::term(), + NewReqIdCollection::request_id_collection()} | + 'no_request' | + 'no_reply'. + +check_response(Msg, ReqIdCol, Delete) -> + try gen:check_response(Msg, ReqIdCol, Delete) of + {{reply, {error, _} = Err}, Label, NewReqIdCol} -> + {Err, Label, NewReqIdCol}; + Return -> + Return + catch + error:badarg -> + error(badarg, [Msg, ReqIdCol, Delete]) + end. + +-spec reqids_new() -> + NewReqIdCollection::request_id_collection(). + +reqids_new() -> + gen:reqids_new(). + +-spec reqids_size(ReqIdCollection::request_id_collection()) -> + non_neg_integer(). + +reqids_size(ReqIdCollection) -> + try + gen:reqids_size(ReqIdCollection) + catch + error:badarg -> error(badarg, [ReqIdCollection]) + end. + +-spec reqids_add(ReqId::request_id(), Label::term(), + ReqIdCollection::request_id_collection()) -> + NewReqIdCollection::request_id_collection(). + +reqids_add(ReqId, Label, ReqIdCollection) -> + try + gen:reqids_add(ReqId, Label, ReqIdCollection) + catch + error:badarg -> error(badarg, [ReqId, Label, ReqIdCollection]) + end. + +-spec reqids_to_list(ReqIdCollection::request_id_collection()) -> + [{ReqId::request_id(), Label::term()}]. + +reqids_to_list(ReqIdCollection) -> + try + gen:reqids_to_list(ReqIdCollection) + catch + error:badarg -> error(badarg, [ReqIdCollection]) end. -spec delete_handler(emgr_ref(), handler(), term()) -> term(). diff --git a/lib/stdlib/src/gen_server.erl b/lib/stdlib/src/gen_server.erl index ef9dd43e0091..14858e3eb5ed 100644 --- a/lib/stdlib/src/gen_server.erl +++ b/lib/stdlib/src/gen_server.erl @@ -97,8 +97,11 @@ start_monitor/3, start_monitor/4, stop/1, stop/3, call/2, call/3, - send_request/2, wait_response/2, - receive_response/2, check_response/2, + send_request/2, send_request/4, + wait_response/2, receive_response/2, check_response/2, + wait_response/3, receive_response/3, check_response/3, + reqids_new/0, reqids_size/1, + reqids_add/3, reqids_to_list/1, cast/2, reply/2, abcast/2, abcast/3, multi_call/2, multi_call/3, multi_call/4, @@ -123,7 +126,8 @@ -export_type( [from/0, reply_tag/0, - request_id/0]). + request_id/0, + request_id_collection/0]). -export_type( [server_name/0, @@ -200,6 +204,11 @@ -opaque request_id() :: gen:request_id(). +-opaque request_id_collection() :: gen:request_id_collection(). + +-type response_timeout() :: + timeout() | {abs, integer()}. + %%% ----------------------------------------------------------------- %%% Starts a generic server. %%% start(Mod, Args, Options) @@ -378,45 +387,172 @@ call(ServerRef, Request, Timeout) -> %% used with wait_response/2 or check_response/2 to fetch the %% result of the request. --spec send_request( - ServerRef :: server_ref(), - Request :: term() - ) -> - RequestId :: request_id(). +-spec send_request(ServerRef::server_ref(), Request::term()) -> + ReqId::request_id(). + send_request(ServerRef, Request) -> - gen:send_request(ServerRef, '$gen_call', Request). - --spec wait_response( - RequestId :: request_id(), - Timeout :: timeout()) -> - {reply, Reply :: term()} | - 'timeout' | - {error, - {Reason :: term(), ServerRef :: server_ref()}}. -wait_response(RequestId, Timeout) -> - gen:wait_response(RequestId, Timeout). - --spec receive_response( - RequestId :: request_id(), - Timeout :: timeout() - ) -> - {reply, Reply :: term()} | - 'timeout' | - {error, - {Reason :: term(), ServerRef :: server_ref()}}. -receive_response(RequestId, Timeout) -> - gen:receive_response(RequestId, Timeout). - --spec check_response( - Msg :: term(), - RequestId :: request_id() - ) -> - {reply, Reply :: term()} | - 'no_reply' | - {error, - {Reason :: term(), ServerRef :: server_ref()}}. -check_response(Msg, RequestId) -> - gen:check_response(Msg, RequestId). + try + gen:send_request(ServerRef, '$gen_call', Request) + catch + error:badarg -> + error(badarg, [ServerRef, Request]) + end. + +-spec send_request(ServerRef::server_ref(), + Request::term(), + Label::term(), + ReqIdCollection::request_id_collection()) -> + NewReqIdCollection::request_id_collection(). + +send_request(ServerRef, Request, Label, ReqIdCol) -> + try + gen:send_request(ServerRef, '$gen_call', Request, Label, ReqIdCol) + catch + error:badarg -> + error(badarg, [ServerRef, Request, Label, ReqIdCol]) + end. + +-spec wait_response(ReqId, WaitTime) -> Result when + ReqId :: request_id(), + WaitTime :: response_timeout(), + Response :: {reply, Reply::term()} + | {error, {Reason::term(), server_ref()}}, + Result :: Response | 'timeout'. + +wait_response(ReqId, WaitTime) -> + try + gen:wait_response(ReqId, WaitTime) + catch + error:badarg -> + error(badarg, [ReqId, WaitTime]) + end. + +-spec wait_response(ReqIdCollection, WaitTime, Delete) -> Result when + ReqIdCollection :: request_id_collection(), + WaitTime :: response_timeout(), + Delete :: boolean(), + Response :: {reply, Reply::term()} | + {error, {Reason::term(), server_ref()}}, + Result :: {Response, + Label::term(), + NewReqIdCollection::request_id_collection()} | + 'no_request' | + 'timeout'. + +wait_response(ReqIdCol, WaitTime, Delete) -> + try + gen:wait_response(ReqIdCol, WaitTime, Delete) + catch + error:badarg -> + error(badarg, [ReqIdCol, WaitTime, Delete]) + end. + +-spec receive_response(ReqId, Timeout) -> Result when + ReqId :: request_id(), + Timeout :: response_timeout(), + Response :: {reply, Reply::term()} | + {error, {Reason::term(), server_ref()}}, + Result :: Response | 'timeout'. + +receive_response(ReqId, Timeout) -> + try + gen:receive_response(ReqId, Timeout) + catch + error:badarg -> + error(badarg, [ReqId, Timeout]) + end. + +-spec receive_response(ReqIdCollection, Timeout, Delete) -> Result when + ReqIdCollection :: request_id_collection(), + Timeout :: response_timeout(), + Delete :: boolean(), + Response :: {reply, Reply::term()} | + {error, {Reason::term(), server_ref()}}, + Result :: {Response, + Label::term(), + NewReqIdCollection::request_id_collection()} | + 'no_request' | + 'timeout'. + +receive_response(ReqIdCol, Timeout, Delete) -> + try + gen:receive_response(ReqIdCol, Timeout, Delete) + catch + error:badarg -> + error(badarg, [ReqIdCol, Timeout, Delete]) + end. + +-spec check_response(Msg, ReqId) -> Result when + Msg :: term(), + ReqId :: request_id(), + Response :: {reply, Reply::term()} | + {error, {Reason::term(), server_ref()}}, + Result :: Response | 'no_reply'. + +check_response(Msg, ReqId) -> + try + gen:check_response(Msg, ReqId) + catch + error:badarg -> + error(badarg, [Msg, ReqId]) + end. + +-spec check_response(Msg, ReqIdCollection, Delete) -> Result when + Msg :: term(), + ReqIdCollection :: request_id_collection(), + Delete :: boolean(), + Response :: {reply, Reply::term()} | + {error, {Reason::term(), server_ref()}}, + Result :: {Response, + Label::term(), + NewReqIdCollection::request_id_collection()} | + 'no_request' | + 'no_reply'. + +check_response(Msg, ReqIdCol, Delete) -> + try + gen:check_response(Msg, ReqIdCol, Delete) + catch + error:badarg -> + error(badarg, [Msg, ReqIdCol, Delete]) + end. + +-spec reqids_new() -> + NewReqIdCollection::request_id_collection(). + +reqids_new() -> + gen:reqids_new(). + +-spec reqids_size(ReqIdCollection::request_id_collection()) -> + non_neg_integer(). + +reqids_size(ReqIdCollection) -> + try + gen:reqids_size(ReqIdCollection) + catch + error:badarg -> error(badarg, [ReqIdCollection]) + end. + +-spec reqids_add(ReqId::request_id(), Label::term(), + ReqIdCollection::request_id_collection()) -> + NewReqIdCollection::request_id_collection(). + +reqids_add(ReqId, Label, ReqIdCollection) -> + try + gen:reqids_add(ReqId, Label, ReqIdCollection) + catch + error:badarg -> error(badarg, [ReqId, Label, ReqIdCollection]) + end. + +-spec reqids_to_list(ReqIdCollection::request_id_collection()) -> + [{ReqId::request_id(), Label::term()}]. + +reqids_to_list(ReqIdCollection) -> + try + gen:reqids_to_list(ReqIdCollection) + catch + error:badarg -> error(badarg, [ReqIdCollection]) + end. %% ----------------------------------------------------------------- %% Make a cast to a generic server. diff --git a/lib/stdlib/src/gen_statem.erl b/lib/stdlib/src/gen_statem.erl index 51ac904ee9d8..f82965d925a6 100644 --- a/lib/stdlib/src/gen_statem.erl +++ b/lib/stdlib/src/gen_statem.erl @@ -32,8 +32,12 @@ start_monitor/3,start_monitor/4, stop/1,stop/3, cast/2,call/2,call/3, - send_request/2,wait_response/1,wait_response/2, - receive_response/1,receive_response/2,check_response/2, + send_request/2, send_request/4, + wait_response/1, wait_response/2, wait_response/3, + receive_response/1, receive_response/2, receive_response/3, + check_response/2, check_response/3, + reqids_new/0, reqids_size/1, + reqids_add/3, reqids_to_list/1, enter_loop/4,enter_loop/5,enter_loop/6, reply/1,reply/2]). @@ -72,7 +76,8 @@ reply_action/0, enter_action/0, action/0, - request_id/0 + request_id/0, + request_id_collection/0 ]). %% Old types, not advertised -export_type( @@ -284,6 +289,11 @@ -opaque request_id() :: gen:request_id(). +-opaque request_id_collection() :: gen:request_id_collection(). + +-type response_timeout() :: + timeout() | {abs, integer()}. + %% The state machine init function. It is called only once and %% the server is not running until this function has returned %% an {ok, ...} tuple. Thereafter the state callbacks are called @@ -625,34 +635,189 @@ call(ServerRef, Request, Timeout) -> call_clean(ServerRef, Request, Timeout, Timeout). -spec send_request(ServerRef::server_ref(), Request::term()) -> - RequestId::request_id(). + ReqId::request_id(). send_request(Name, Request) -> - gen:send_request(Name, '$gen_call', Request). - --spec wait_response(RequestId::request_id()) -> - {reply, Reply::term()} | {error, {term(), server_ref()}}. -wait_response(RequestId) -> - gen:wait_response(RequestId, infinity). - --spec wait_response(RequestId::request_id(), timeout()) -> - {reply, Reply::term()} | 'timeout' | {error, {term(), server_ref()}}. -wait_response(RequestId, Timeout) -> - gen:wait_response(RequestId, Timeout). - --spec receive_response(RequestId::request_id()) -> - {reply, Reply::term()} | {error, {term(), server_ref()}}. -receive_response(RequestId) -> - gen:receive_response(RequestId, infinity). - --spec receive_response(RequestId::request_id(), timeout()) -> - {reply, Reply::term()} | 'timeout' | {error, {term(), server_ref()}}. -receive_response(RequestId, Timeout) -> - gen:receive_response(RequestId, Timeout). - --spec check_response(Msg::term(), RequestId::request_id()) -> - {reply, Reply::term()} | 'no_reply' | {error, {term(), server_ref()}}. -check_response(Msg, RequestId) -> - gen:check_response(Msg, RequestId). + try + gen:send_request(Name, '$gen_call', Request) + catch + error:badarg -> + error(badarg, [Name, Request]) + end. + +-spec send_request(ServerRef::server_ref(), + Request::term(), + Label::term(), + ReqIdCollection::request_id_collection()) -> + NewReqIdCollection::request_id_collection(). + +send_request(ServerRef, Request, Label, ReqIdCol) -> + try + gen:send_request(ServerRef, '$gen_call', Request, Label, ReqIdCol) + catch + error:badarg -> + error(badarg, [ServerRef, Request, Label, ReqIdCol]) + end. + + +-spec wait_response(ReqId) -> Result when + ReqId :: request_id(), + Response :: {reply, Reply::term()} + | {error, {Reason::term(), server_ref()}}, + Result :: Response | 'timeout'. + +wait_response(ReqId) -> + wait_response(ReqId, infinity). + +-spec wait_response(ReqId, WaitTime) -> Result when + ReqId :: request_id(), + WaitTime :: response_timeout(), + Response :: {reply, Reply::term()} + | {error, {Reason::term(), server_ref()}}, + Result :: Response | 'timeout'. + +wait_response(ReqId, WaitTime) -> + try + gen:wait_response(ReqId, WaitTime) + catch + error:badarg -> + error(badarg, [ReqId, WaitTime]) + end. + +-spec wait_response(ReqIdCollection, WaitTime, Delete) -> Result when + ReqIdCollection :: request_id_collection(), + WaitTime :: response_timeout(), + Delete :: boolean(), + Response :: {reply, Reply::term()} | + {error, {Reason::term(), server_ref()}}, + Result :: {Response, + Label::term(), + NewReqIdCollection::request_id_collection()} | + 'no_request' | + 'timeout'. + +wait_response(ReqIdCol, WaitTime, Delete) -> + try + gen:wait_response(ReqIdCol, WaitTime, Delete) + catch + error:badarg -> + error(badarg, [ReqIdCol, WaitTime, Delete]) + end. + +-spec receive_response(ReqId) -> Result when + ReqId :: request_id(), + Response :: {reply, Reply::term()} | + {error, {Reason::term(), server_ref()}}, + Result :: Response | 'timeout'. + +receive_response(ReqId) -> + receive_response(ReqId, infinity). + +-spec receive_response(ReqId, Timeout) -> Result when + ReqId :: request_id(), + Timeout :: response_timeout(), + Response :: {reply, Reply::term()} | + {error, {Reason::term(), server_ref()}}, + Result :: Response | 'timeout'. + +receive_response(ReqId, Timeout) -> + try + gen:receive_response(ReqId, Timeout) + catch + error:badarg -> + error(badarg, [ReqId, Timeout]) + end. + +-spec receive_response(ReqIdCollection, Timeout, Delete) -> Result when + ReqIdCollection :: request_id_collection(), + Timeout :: response_timeout(), + Delete :: boolean(), + Response :: {reply, Reply::term()} | + {error, {Reason::term(), server_ref()}}, + Result :: {Response, + Label::term(), + NewReqIdCollection::request_id_collection()} | + 'no_request' | + 'timeout'. + +receive_response(ReqIdCol, Timeout, Delete) -> + try + gen:receive_response(ReqIdCol, Timeout, Delete) + catch + error:badarg -> + error(badarg, [ReqIdCol, Timeout, Delete]) + end. + +-spec check_response(Msg, ReqId) -> Result when + Msg :: term(), + ReqId :: request_id(), + Response :: {reply, Reply::term()} | + {error, {Reason::term(), server_ref()}}, + Result :: Response | 'no_reply'. + +check_response(Msg, ReqId) -> + try + gen:check_response(Msg, ReqId) + catch + error:badarg -> + error(badarg, [Msg, ReqId]) + end. + +-spec check_response(Msg, ReqIdCollection, Delete) -> Result when + Msg :: term(), + ReqIdCollection :: request_id_collection(), + Delete :: boolean(), + Response :: {reply, Reply::term()} | + {error, {Reason::term(), server_ref()}}, + Result :: {Response, + Label::term(), + NewReqIdCollection::request_id_collection()} | + 'no_request' | + 'no_reply'. + +check_response(Msg, ReqIdCol, Delete) -> + try + gen:check_response(Msg, ReqIdCol, Delete) + catch + error:badarg -> + error(badarg, [Msg, ReqIdCol, Delete]) + end. + +-spec reqids_new() -> + NewReqIdCollection::request_id_collection(). + +reqids_new() -> + gen:reqids_new(). + +-spec reqids_size(ReqIdCollection::request_id_collection()) -> + non_neg_integer(). + +reqids_size(ReqIdCollection) -> + try + gen:reqids_size(ReqIdCollection) + catch + error:badarg -> error(badarg, [ReqIdCollection]) + end. + +-spec reqids_add(ReqId::request_id(), Label::term(), + ReqIdCollection::request_id_collection()) -> + NewReqIdCollection::request_id_collection(). + +reqids_add(ReqId, Label, ReqIdCollection) -> + try + gen:reqids_add(ReqId, Label, ReqIdCollection) + catch + error:badarg -> error(badarg, [ReqId, Label, ReqIdCollection]) + end. + +-spec reqids_to_list(ReqIdCollection::request_id_collection()) -> + [{ReqId::request_id(), Label::term()}]. + +reqids_to_list(ReqIdCollection) -> + try + gen:reqids_to_list(ReqIdCollection) + catch + error:badarg -> error(badarg, [ReqIdCollection]) + end. %% Reply from a state machine callback to whom awaits in call/2 -spec reply([reply_action()] | reply_action()) -> ok. diff --git a/lib/stdlib/test/dummy_h.erl b/lib/stdlib/test/dummy_h.erl index f75c580be115..4fffcd86d8c2 100644 --- a/lib/stdlib/test/dummy_h.erl +++ b/lib/stdlib/test/dummy_h.erl @@ -63,6 +63,9 @@ handle_call(hibernate, _State) -> handle_call(hibernate_later, _State) -> timer:send_after(1000,sleep), {ok,later,[]}; +handle_call({delayed_answer, T}, State) -> + receive after T -> ok end, + {ok, delayed, State}; handle_call(_Query, State) -> {ok, ok, State}. diff --git a/lib/stdlib/test/gen_event_SUITE.erl b/lib/stdlib/test/gen_event_SUITE.erl index 6dbadd3602f6..65c5a83c9ea2 100644 --- a/lib/stdlib/test/gen_event_SUITE.erl +++ b/lib/stdlib/test/gen_event_SUITE.erl @@ -32,7 +32,9 @@ start_opt/1, undef_init/1, undef_handle_call/1, undef_handle_event/1, undef_handle_info/1, undef_code_change/1, undef_terminate/1, - undef_in_terminate/1, format_log_1/1, format_log_2/1]). + undef_in_terminate/1, format_log_1/1, format_log_2/1, + send_request_receive_reqid_collection/1, send_request_wait_reqid_collection/1, + send_request_check_reqid_collection/1]). suite() -> [{ct_hooks,[ts_install_cth]}]. @@ -41,7 +43,9 @@ all() -> call_format_status, call_format_status_anon, error_format_status, get_state, replace_state, start_opt, {group, undef_callbacks}, undef_in_terminate, - format_log_1, format_log_2]. + format_log_1, format_log_2, + send_request_receive_reqid_collection, send_request_wait_reqid_collection, + send_request_check_reqid_collection]. groups() -> [{test_all, [], @@ -1522,3 +1526,324 @@ format_log_2(_Config) -> flatten_format_log(Report, Format) -> lists:flatten(gen_event:format_log(Report, Format)). + + +send_request_receive_reqid_collection(Config) when is_list(Config) -> + {ok, Pid1} = gen_event:start(), + ok = gen_event:add_handler(Pid1, dummy_h, [self()]), + [dummy_h] = gen_event:which_handlers(Pid1), + {ok, Pid2} = gen_event:start(), + ok = gen_event:add_handler(Pid2, dummy_h, [self()]), + [dummy_h] = gen_event:which_handlers(Pid2), + {ok, Pid3} = gen_event:start(), + ok = gen_event:add_handler(Pid3, dummy_h, [self()]), + [dummy_h] = gen_event:which_handlers(Pid3), + send_request_receive_reqid_collection(Pid1, Pid2, Pid3), + send_request_receive_reqid_collection_timeout(Pid1, Pid2, Pid3), + send_request_receive_reqid_collection_error(Pid1, Pid2, Pid3), + ok = gen_event:stop(Pid1), + try gen_event:stop(Pid2) catch exit:noproc -> ok end, + ok = gen_event:stop(Pid3). + +send_request_receive_reqid_collection(Pid1, Pid2, Pid3) -> + + ReqId0 = gen_event:send_request(Pid1, dummy_h, hejsan), + + ReqIdC0 = gen_event:reqids_new(), + + ReqId1 = gen_event:send_request(Pid1, dummy_h, {delayed_answer,400}), + ReqIdC1 = gen_event:reqids_add(ReqId1, req1, ReqIdC0), + 1 = gen_event:reqids_size(ReqIdC1), + + ReqIdC2 = gen_event:send_request(Pid2, dummy_h, {delayed_answer,1}, req2, ReqIdC1), + 2 = gen_event:reqids_size(ReqIdC2), + + ReqIdC3 = gen_event:send_request(Pid3, dummy_h, {delayed_answer,200}, req3, ReqIdC2), + 3 = gen_event:reqids_size(ReqIdC3), + + {{reply, delayed}, req2, ReqIdC4} = gen_event:receive_response(ReqIdC3, infinity, true), + 2 = gen_event:reqids_size(ReqIdC4), + + {{reply, delayed}, req3, ReqIdC5} = gen_event:receive_response(ReqIdC4, 5678, true), + 1 = gen_event:reqids_size(ReqIdC5), + + {{reply, delayed}, req1, ReqIdC6} = gen_event:receive_response(ReqIdC5, 5000, true), + 0 = gen_event:reqids_size(ReqIdC6), + + no_request = gen_event:receive_response(ReqIdC6, 5000, true), + + {reply, {ok, hejhopp}} = gen_event:receive_response(ReqId0, infinity), + + ok. + +send_request_receive_reqid_collection_timeout(Pid1, Pid2, Pid3) -> + + ReqId0 = gen_event:send_request(Pid1, dummy_h, hejsan), + + ReqIdC0 = gen_event:reqids_new(), + + ReqId1 = gen_event:send_request(Pid1, dummy_h, {delayed_answer,1000}), + ReqIdC1 = gen_event:reqids_add(ReqId1, req1, ReqIdC0), + + ReqIdC2 = gen_event:send_request(Pid2, dummy_h, {delayed_answer,1}, req2, ReqIdC1), + + ReqId3 = gen_event:send_request(Pid3, dummy_h, {delayed_answer,500}), + ReqIdC3 = gen_event:reqids_add(ReqId3, req3, ReqIdC2), + + Deadline = erlang:monotonic_time(millisecond) + 100, + + {{reply, delayed}, req2, ReqIdC4} = gen_event:receive_response(ReqIdC3, {abs, Deadline}, true), + 2 = gen_event:reqids_size(ReqIdC4), + + timeout = gen_event:receive_response(ReqIdC4, {abs, Deadline}, true), + + Abandoned = lists:sort([{ReqId1, req1}, {ReqId3, req3}]), + Abandoned = lists:sort(gen_event:reqids_to_list(ReqIdC4)), + + %% Make sure requests were abandoned... + timeout = gen_event:receive_response(ReqIdC4, {abs, Deadline+1000}, true), + + {reply, {ok, hejhopp}} = gen_event:receive_response(ReqId0, infinity), + + ok. + +send_request_receive_reqid_collection_error(Pid1, Pid2, Pid3) -> + + ReqId0 = gen_event:send_request(Pid1, dummy_h, hejsan), + + ReqIdC0 = gen_event:reqids_new(), + + ReqId1 = gen_event:send_request(Pid1, dummy_h, {delayed_answer,400}), + ReqIdC1 = gen_event:reqids_add(ReqId1, req1, ReqIdC0), + try + nope = gen_event:reqids_add(ReqId1, req2, ReqIdC1) + catch + error:badarg -> ok + end, + + unlink(Pid2), + exit(Pid2, kill), + ReqIdC2 = gen_event:send_request(Pid2, dummy_h, {delayed_answer,1}, req2, ReqIdC1), + ReqIdC3 = gen_event:send_request(Pid3, dummy_h, {delayed_answer,200}, req3, ReqIdC2), + ReqIdC4 = gen_event:send_request(Pid1, bad_h, hejsan, req4, ReqIdC3), + 4 = gen_event:reqids_size(ReqIdC4), + + {{error, {noproc, _}}, req2, ReqIdC5} = gen_event:receive_response(ReqIdC4, 2000, true), + 3 = gen_event:reqids_size(ReqIdC5), + + {{reply, delayed}, req3, ReqIdC5} = gen_event:receive_response(ReqIdC5, infinity, false), + {{reply, delayed}, req1, ReqIdC5} = gen_event:receive_response(ReqIdC5, infinity, false), + {{error, bad_module}, req4, ReqIdC5} = gen_event:wait_response(ReqIdC5, infinity, false), + + {reply, {ok, hejhopp}} = gen_event:receive_response(ReqId0, infinity), + + ok. + +send_request_wait_reqid_collection(Config) when is_list(Config) -> + {ok, Pid1} = gen_event:start(), + ok = gen_event:add_handler(Pid1, dummy_h, [self()]), + [dummy_h] = gen_event:which_handlers(Pid1), + {ok, Pid2} = gen_event:start(), + ok = gen_event:add_handler(Pid2, dummy_h, [self()]), + [dummy_h] = gen_event:which_handlers(Pid2), + {ok, Pid3} = gen_event:start(), + ok = gen_event:add_handler(Pid3, dummy_h, [self()]), + [dummy_h] = gen_event:which_handlers(Pid3), + send_request_wait_reqid_collection(Pid1, Pid2, Pid3), + send_request_wait_reqid_collection_timeout(Pid1, Pid2, Pid3), + send_request_wait_reqid_collection_error(Pid1, Pid2, Pid3), + ok = gen_event:stop(Pid1), + try gen_event:stop(Pid2) catch exit:noproc -> ok end, + ok = gen_event:stop(Pid3). + +send_request_wait_reqid_collection(Pid1, Pid2, Pid3) -> + + ReqId0 = gen_event:send_request(Pid1, dummy_h, hejsan), + + ReqIdC0 = gen_event:reqids_new(), + + ReqId1 = gen_event:send_request(Pid1, dummy_h, {delayed_answer,400}), + ReqIdC1 = gen_event:reqids_add(ReqId1, req1, ReqIdC0), + 1 = gen_event:reqids_size(ReqIdC1), + + ReqIdC2 = gen_event:send_request(Pid2, dummy_h, {delayed_answer,1}, req2, ReqIdC1), + 2 = gen_event:reqids_size(ReqIdC2), + + ReqIdC3 = gen_event:send_request(Pid3, dummy_h, {delayed_answer,200}, req3, ReqIdC2), + 3 = gen_event:reqids_size(ReqIdC3), + + {{reply, delayed}, req2, ReqIdC4} = gen_event:wait_response(ReqIdC3, infinity, true), + 2 = gen_event:reqids_size(ReqIdC4), + + {{reply, delayed}, req3, ReqIdC5} = gen_event:wait_response(ReqIdC4, 5678, true), + 1 = gen_event:reqids_size(ReqIdC5), + + {{reply, delayed}, req1, ReqIdC6} = gen_event:wait_response(ReqIdC5, 5000, true), + 0 = gen_event:reqids_size(ReqIdC6), + + no_request = gen_event:wait_response(ReqIdC6, 5000, true), + + {reply, {ok, hejhopp}} = gen_event:receive_response(ReqId0, infinity), + + ok. + +send_request_wait_reqid_collection_timeout(Pid1, Pid2, Pid3) -> + + ReqId0 = gen_event:send_request(Pid1, dummy_h, hejsan), + + ReqIdC0 = gen_event:reqids_new(), + + ReqId1 = gen_event:send_request(Pid1, dummy_h, {delayed_answer,1000}), + ReqIdC1 = gen_event:reqids_add(ReqId1, req1, ReqIdC0), + + ReqIdC2 = gen_event:send_request(Pid2, dummy_h, {delayed_answer,1}, req2, ReqIdC1), + + ReqId3 = gen_event:send_request(Pid3, dummy_h, {delayed_answer,500}), + ReqIdC3 = gen_event:reqids_add(ReqId3, req3, ReqIdC2), + + Deadline = erlang:monotonic_time(millisecond) + 100, + + {{reply, delayed}, req2, ReqIdC4} = gen_event:wait_response(ReqIdC3, {abs, Deadline}, true), + 2 = gen_event:reqids_size(ReqIdC4), + + timeout = gen_event:wait_response(ReqIdC4, {abs, Deadline}, true), + + Unhandled = lists:sort([{ReqId1, req1}, {ReqId3, req3}]), + Unhandled = lists:sort(gen_event:reqids_to_list(ReqIdC4)), + + %% Make sure requests were not abandoned... + {{reply, delayed}, req3, ReqIdC4} = gen_event:wait_response(ReqIdC4, {abs, Deadline+1500}, false), + {{reply, delayed}, req1, ReqIdC4} = gen_event:wait_response(ReqIdC4, {abs, Deadline+1500}, false), + + {reply, {ok, hejhopp}} = gen_event:receive_response(ReqId0, infinity), + + ok. + +send_request_wait_reqid_collection_error(Pid1, Pid2, Pid3) -> + + ReqId0 = gen_event:send_request(Pid1, dummy_h, hejsan), + + ReqIdC0 = gen_event:reqids_new(), + + ReqId1 = gen_event:send_request(Pid1, dummy_h, {delayed_answer,400}), + ReqIdC1 = gen_event:reqids_add(ReqId1, req1, ReqIdC0), + try + nope = gen_event:reqids_add(ReqId1, req2, ReqIdC1) + catch + error:badarg -> ok + end, + + unlink(Pid2), + exit(Pid2, kill), + ReqIdC2 = gen_event:send_request(Pid2, dummy_h, {delayed_answer,1}, req2, ReqIdC1), + ReqIdC3 = gen_event:send_request(Pid3, dummy_h, {delayed_answer,200}, req3, ReqIdC2), + ReqIdC4 = gen_event:send_request(Pid1, bad_h, hejsan, req4, ReqIdC3), + 4 = gen_event:reqids_size(ReqIdC4), + + {{error, {noproc, _}}, req2, ReqIdC5} = gen_event:wait_response(ReqIdC4, 2000, true), + 3 = gen_event:reqids_size(ReqIdC5), + + {{reply, delayed}, req3, ReqIdC5} = gen_event:wait_response(ReqIdC5, infinity, false), + {{reply, delayed}, req1, ReqIdC5} = gen_event:wait_response(ReqIdC5, infinity, false), + {{error, bad_module}, req4, ReqIdC5} = gen_event:wait_response(ReqIdC5, infinity, false), + + {reply, {ok, hejhopp}} = gen_event:receive_response(ReqId0, infinity), + + ok. + +send_request_check_reqid_collection(Config) when is_list(Config) -> + {ok, Pid1} = gen_event:start(), + ok = gen_event:add_handler(Pid1, dummy_h, [self()]), + [dummy_h] = gen_event:which_handlers(Pid1), + {ok, Pid2} = gen_event:start(), + ok = gen_event:add_handler(Pid2, dummy_h, [self()]), + [dummy_h] = gen_event:which_handlers(Pid2), + {ok, Pid3} = gen_event:start(), + ok = gen_event:add_handler(Pid3, dummy_h, [self()]), + [dummy_h] = gen_event:which_handlers(Pid3), + send_request_check_reqid_collection(Pid1, Pid2, Pid3), + send_request_check_reqid_collection_error(Pid1, Pid2, Pid3), + ok = gen_event:stop(Pid1), + try gen_event:stop(Pid2) catch exit:noproc -> ok end, + ok = gen_event:stop(Pid3). + +send_request_check_reqid_collection(Pid1, Pid2, Pid3) -> + + ReqId0 = gen_event:send_request(Pid1, dummy_h, hejsan), + + receive after 100 -> ok end, + + ReqIdC0 = gen_event:reqids_new(), + + ReqIdC1 = gen_event:send_request(Pid1, dummy_h, {delayed_answer,400}, req1, ReqIdC0), + 1 = gen_event:reqids_size(ReqIdC1), + + ReqId2 = gen_event:send_request(Pid2, dummy_h, {delayed_answer,1}), + ReqIdC2 = gen_event:reqids_add(ReqId2, req2, ReqIdC1), + 2 = gen_event:reqids_size(ReqIdC2), + + ReqIdC3 = gen_event:send_request(Pid3, dummy_h, {delayed_answer,200}, req3, ReqIdC2), + 3 = gen_event:reqids_size(ReqIdC3), + + Msg0 = next_msg(), + no_reply = gen_event:check_response(Msg0, ReqIdC3, true), + + {{reply, delayed}, req2, ReqIdC4} = gen_event:check_response(next_msg(), ReqIdC3, true), + 2 = gen_event:reqids_size(ReqIdC4), + + {{reply, delayed}, req3, ReqIdC5} = gen_event:check_response(next_msg(), ReqIdC4, true), + 1 = gen_event:reqids_size(ReqIdC5), + + {{reply, delayed}, req1, ReqIdC6} = gen_event:check_response(next_msg(), ReqIdC5, true), + 0 = gen_event:reqids_size(ReqIdC6), + + no_request = gen_event:check_response(Msg0, ReqIdC6, true), + + {reply, {ok, hejhopp}} = gen_event:check_response(Msg0, ReqId0), + + ok. + +send_request_check_reqid_collection_error(Pid1, Pid2, Pid3) -> + + ReqId0 = gen_event:send_request(Pid1, dummy_h, hejsan), + + receive after 100 -> ok end, + + ReqIdC0 = gen_event:reqids_new(), + + ReqId1 = gen_event:send_request(Pid1, dummy_h, {delayed_answer,400}), + ReqIdC1 = gen_event:reqids_add(ReqId1, req1, ReqIdC0), + try + nope = gen_event:reqids_add(ReqId1, req2, ReqIdC1) + catch + error:badarg -> ok + end, + + unlink(Pid2), + exit(Pid2, kill), + ReqIdC2 = gen_event:send_request(Pid2, dummy_h, {delayed_answer,1}, req2, ReqIdC1), + + ReqIdC3 = gen_event:send_request(Pid3, dummy_h, {delayed_answer,200}, req3, ReqIdC2), + + ReqIdC4 = gen_event:send_request(Pid1, bad_h, hejsan, req4, ReqIdC3), + 4 = gen_event:reqids_size(ReqIdC4), + + Msg0 = next_msg(), + + no_reply = gen_event:check_response(Msg0, ReqIdC3, true), + + {{error, {noproc, _}}, req2, ReqIdC5} = gen_event:check_response(next_msg(), ReqIdC4, true), + 3 = gen_event:reqids_size(ReqIdC5), + + {{reply, delayed}, req3, ReqIdC5} = gen_event:check_response(next_msg(), ReqIdC5, false), + {{reply, delayed}, req1, ReqIdC5} = gen_event:check_response(next_msg(), ReqIdC5, false), + {{error, bad_module}, req4, ReqIdC5} = gen_event:check_response(next_msg(), ReqIdC5, false), + + no_reply = gen_event:check_response(Msg0, ReqIdC3, false), + + {reply, {ok, hejhopp}} = gen_event:check_response(Msg0, ReqId0), + + ok. + +next_msg() -> + receive M -> M end. diff --git a/lib/stdlib/test/gen_server_SUITE.erl b/lib/stdlib/test/gen_server_SUITE.erl index 652bff2a519b..5fa604d4fd1a 100644 --- a/lib/stdlib/test/gen_server_SUITE.erl +++ b/lib/stdlib/test/gen_server_SUITE.erl @@ -26,7 +26,11 @@ -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, init_per_group/2,end_per_group/2]). --export([start/1, crash/1, call/1, send_request/1, cast/1, cast_fast/1, +-export([start/1, crash/1, call/1, send_request/1, + send_request_receive_reqid_collection/1, + send_request_wait_reqid_collection/1, + send_request_check_reqid_collection/1, + cast/1, cast_fast/1, continue/1, info/1, abcast/1, multicall/1, multicall_down/1, call_remote1/1, call_remote2/1, call_remote3/1, calling_self/1, call_remote_n1/1, call_remote_n2/1, call_remote_n3/1, spec_init/1, @@ -65,7 +69,9 @@ suite() -> {timetrap,{minutes,1}}]. all() -> - [start, {group,stop}, crash, call, send_request, cast, cast_fast, info, abcast, + [start, {group,stop}, crash, call, send_request, + send_request_receive_reqid_collection, send_request_wait_reqid_collection, + send_request_check_reqid_collection, cast, cast_fast, info, abcast, continue, multicall, multicall_down, call_remote1, call_remote2, calling_self, call_remote3, call_remote_n1, call_remote_n2, call_remote_n3, spec_init, @@ -598,6 +604,323 @@ send_request(Config) when is_list(Config) -> process_flag(trap_exit, OldFl), ok. +send_request_receive_reqid_collection(Config) when is_list(Config) -> + {ok, Pid1} = gen_server:start_link({local, my_test_name1}, + gen_server_SUITE, [], []), + {ok, Pid2} = gen_server:start_link({local, my_test_name2}, + gen_server_SUITE, [], []), + {ok, Pid3} = gen_server:start_link({local, my_test_name3}, + gen_server_SUITE, [], []), + send_request_receive_reqid_collection(Pid1, Pid2, Pid3), + send_request_receive_reqid_collection_timeout(Pid1, Pid2, Pid3), + send_request_receive_reqid_collection_error(Pid1, Pid2, Pid3), + unlink(Pid1), + exit(Pid1, kill), + unlink(Pid2), + exit(Pid2, kill), + unlink(Pid3), + exit(Pid3, kill), + false = is_process_alive(Pid1), + false = is_process_alive(Pid2), + false = is_process_alive(Pid3), + ok. + +send_request_receive_reqid_collection(Pid1, Pid2, Pid3) -> + + ReqId0 = gen_server:send_request(Pid1, started_p), + + ReqIdC0 = gen_server:reqids_new(), + + ReqId1 = gen_server:send_request(Pid1, {delayed_answer,400}), + ReqIdC1 = gen_server:reqids_add(ReqId1, req1, ReqIdC0), + 1 = gen_server:reqids_size(ReqIdC1), + + ReqIdC2 = gen_server:send_request(Pid2, {delayed_answer,1}, req2, ReqIdC1), + 2 = gen_server:reqids_size(ReqIdC2), + + ReqIdC3 = gen_server:send_request(Pid3, {delayed_answer,200}, req3, ReqIdC2), + 3 = gen_server:reqids_size(ReqIdC3), + + {{reply, delayed}, req2, ReqIdC4} = gen_server:receive_response(ReqIdC3, infinity, true), + 2 = gen_server:reqids_size(ReqIdC4), + + {{reply, delayed}, req3, ReqIdC5} = gen_server:receive_response(ReqIdC4, 5678, true), + 1 = gen_server:reqids_size(ReqIdC5), + + {{reply, delayed}, req1, ReqIdC6} = gen_server:receive_response(ReqIdC5, 5000, true), + 0 = gen_server:reqids_size(ReqIdC6), + + no_request = gen_server:receive_response(ReqIdC6, 5000, true), + + {reply, ok} = gen_server:receive_response(ReqId0, infinity), + + ok. + +send_request_receive_reqid_collection_timeout(Pid1, Pid2, Pid3) -> + + ReqId0 = gen_server:send_request(Pid1, started_p), + + ReqIdC0 = gen_server:reqids_new(), + + ReqId1 = gen_server:send_request(Pid1, {delayed_answer,1000}), + ReqIdC1 = gen_server:reqids_add(ReqId1, req1, ReqIdC0), + + ReqIdC2 = gen_server:send_request(Pid2, {delayed_answer,1}, req2, ReqIdC1), + + ReqId3 = gen_server:send_request(Pid3, {delayed_answer,500}), + ReqIdC3 = gen_server:reqids_add(ReqId3, req3, ReqIdC2), + + Deadline = erlang:monotonic_time(millisecond) + 100, + + {{reply, delayed}, req2, ReqIdC4} = gen_server:receive_response(ReqIdC3, {abs, Deadline}, true), + 2 = gen_server:reqids_size(ReqIdC4), + + timeout = gen_server:receive_response(ReqIdC4, {abs, Deadline}, true), + + Abandoned = lists:sort([{ReqId1, req1}, {ReqId3, req3}]), + Abandoned = lists:sort(gen_server:reqids_to_list(ReqIdC4)), + + %% Make sure requests were abandoned... + timeout = gen_server:receive_response(ReqIdC4, {abs, Deadline+1000}, true), + + {reply, ok} = gen_server:receive_response(ReqId0, infinity), + + ok. + +send_request_receive_reqid_collection_error(Pid1, Pid2, Pid3) -> + + ReqId0 = gen_server:send_request(Pid1, started_p), + + ReqIdC0 = gen_server:reqids_new(), + + ReqId1 = gen_server:send_request(Pid1, {delayed_answer,400}), + ReqIdC1 = gen_server:reqids_add(ReqId1, req1, ReqIdC0), + try + nope = gen_server:reqids_add(ReqId1, req2, ReqIdC1) + catch + error:badarg -> ok + end, + + unlink(Pid2), + ReqIdC2 = gen_server:send_request(Pid2, stop_shutdown, req2, ReqIdC1), + ReqIdC3 = gen_server:send_request(Pid3, {delayed_answer,200}, req3, ReqIdC2), + 3 = gen_server:reqids_size(ReqIdC3), + + {{error, {shutdown, _}}, req2, ReqIdC4} = gen_server:receive_response(ReqIdC3, 2000, true), + 2 = gen_server:reqids_size(ReqIdC4), + + {{reply, delayed}, req3, ReqIdC4} = gen_server:receive_response(ReqIdC4, infinity, false), + + {{reply, delayed}, req1, ReqIdC4} = gen_server:receive_response(ReqIdC4, infinity, false), + + {reply, ok} = gen_server:receive_response(ReqId0, infinity), + + ok. + +send_request_wait_reqid_collection(Config) when is_list(Config) -> + {ok, Pid1} = gen_server:start_link({local, my_test_name1}, + gen_server_SUITE, [], []), + {ok, Pid2} = gen_server:start_link({local, my_test_name2}, + gen_server_SUITE, [], []), + {ok, Pid3} = gen_server:start_link({local, my_test_name3}, + gen_server_SUITE, [], []), + send_request_wait_reqid_collection(Pid1, Pid2, Pid3), + send_request_wait_reqid_collection_timeout(Pid1, Pid2, Pid3), + send_request_wait_reqid_collection_error(Pid1, Pid2, Pid3), + unlink(Pid1), + exit(Pid1, kill), + unlink(Pid2), + exit(Pid2, kill), + unlink(Pid3), + exit(Pid3, kill), + false = is_process_alive(Pid1), + false = is_process_alive(Pid2), + false = is_process_alive(Pid3), + ok. + +send_request_wait_reqid_collection(Pid1, Pid2, Pid3) -> + + ReqId0 = gen_server:send_request(Pid1, started_p), + + ReqIdC0 = gen_server:reqids_new(), + + ReqId1 = gen_server:send_request(Pid1, {delayed_answer,400}), + ReqIdC1 = gen_server:reqids_add(ReqId1, req1, ReqIdC0), + 1 = gen_server:reqids_size(ReqIdC1), + + ReqIdC2 = gen_server:send_request(Pid2, {delayed_answer,1}, req2, ReqIdC1), + 2 = gen_server:reqids_size(ReqIdC2), + + ReqIdC3 = gen_server:send_request(Pid3, {delayed_answer,200}, req3, ReqIdC2), + 3 = gen_server:reqids_size(ReqIdC3), + + {{reply, delayed}, req2, ReqIdC4} = gen_server:wait_response(ReqIdC3, infinity, true), + 2 = gen_server:reqids_size(ReqIdC4), + + {{reply, delayed}, req3, ReqIdC5} = gen_server:wait_response(ReqIdC4, 5678, true), + 1 = gen_server:reqids_size(ReqIdC5), + + {{reply, delayed}, req1, ReqIdC6} = gen_server:wait_response(ReqIdC5, 5000, true), + 0 = gen_server:reqids_size(ReqIdC6), + + no_request = gen_server:wait_response(ReqIdC6, 5000, true), + + {reply, ok} = gen_server:wait_response(ReqId0, infinity), + + ok. + +send_request_wait_reqid_collection_timeout(Pid1, Pid2, Pid3) -> + + ReqId0 = gen_server:send_request(Pid1, started_p), + + ReqIdC0 = gen_server:reqids_new(), + + ReqId1 = gen_server:send_request(Pid1, {delayed_answer,1000}), + ReqIdC1 = gen_server:reqids_add(ReqId1, req1, ReqIdC0), + + ReqIdC2 = gen_server:send_request(Pid2, {delayed_answer,1}, req2, ReqIdC1), + + ReqId3 = gen_server:send_request(Pid3, {delayed_answer,500}), + ReqIdC3 = gen_server:reqids_add(ReqId3, req3, ReqIdC2), + + Deadline = erlang:monotonic_time(millisecond) + 100, + + {{reply, delayed}, req2, ReqIdC4} = gen_server:wait_response(ReqIdC3, {abs, Deadline}, true), + 2 = gen_server:reqids_size(ReqIdC4), + + timeout = gen_server:wait_response(ReqIdC4, {abs, Deadline}, true), + + Unhandled = lists:sort([{ReqId1, req1}, {ReqId3, req3}]), + Unhandled = lists:sort(gen_server:reqids_to_list(ReqIdC4)), + + %% Make sure requests were not abandoned... + {{reply, delayed}, req3, ReqIdC4} = gen_server:wait_response(ReqIdC4, {abs, Deadline+1500}, false), + {{reply, delayed}, req1, ReqIdC4} = gen_server:wait_response(ReqIdC4, {abs, Deadline+1500}, false), + + {reply, ok} = gen_server:receive_response(ReqId0, infinity), + + ok. + +send_request_wait_reqid_collection_error(Pid1, Pid2, Pid3) -> + + ReqId0 = gen_server:send_request(Pid1, started_p), + + ReqIdC0 = gen_server:reqids_new(), + + ReqId1 = gen_server:send_request(Pid1, {delayed_answer,400}), + ReqIdC1 = gen_server:reqids_add(ReqId1, req1, ReqIdC0), + try + nope = gen_server:reqids_add(ReqId1, req2, ReqIdC1) + catch + error:badarg -> ok + end, + + unlink(Pid2), + ReqIdC2 = gen_server:send_request(Pid2, stop_shutdown, req2, ReqIdC1), + ReqIdC3 = gen_server:send_request(Pid3, {delayed_answer,200}, req3, ReqIdC2), + 3 = gen_server:reqids_size(ReqIdC3), + + {{error, {shutdown, _}}, req2, ReqIdC4} = gen_server:wait_response(ReqIdC3, 2000, true), + 2 = gen_server:reqids_size(ReqIdC4), + + {{reply, delayed}, req3, ReqIdC4} = gen_server:wait_response(ReqIdC4, infinity, false), + + {{reply, delayed}, req1, ReqIdC4} = gen_server:wait_response(ReqIdC4, infinity, false), + + {reply, ok} = gen_server:wait_response(ReqId0, infinity), + + ok. + +send_request_check_reqid_collection(Config) when is_list(Config) -> + {ok, Pid1} = gen_server:start_link({local, my_test_name1}, + gen_server_SUITE, [], []), + {ok, Pid2} = gen_server:start_link({local, my_test_name2}, + gen_server_SUITE, [], []), + {ok, Pid3} = gen_server:start_link({local, my_test_name3}, + gen_server_SUITE, [], []), + send_request_check_reqid_collection(Pid1, Pid2, Pid3), + send_request_check_reqid_collection_error(Pid1, Pid2, Pid3), + unlink(Pid1), + exit(Pid1, kill), + unlink(Pid2), + exit(Pid2, kill), + unlink(Pid3), + exit(Pid3, kill), + false = is_process_alive(Pid1), + false = is_process_alive(Pid2), + false = is_process_alive(Pid3), + ok. + +send_request_check_reqid_collection(Pid1, Pid2, Pid3) -> + + ReqId0 = gen_server:send_request(Pid1, started_p), + + receive after 100 -> ok end, + + ReqIdC0 = gen_server:reqids_new(), + + ReqIdC1 = gen_server:send_request(Pid1, {delayed_answer,400}, req1, ReqIdC0), + 1 = gen_server:reqids_size(ReqIdC1), + + ReqId2 = gen_server:send_request(Pid2, {delayed_answer,1}), + ReqIdC2 = gen_server:reqids_add(ReqId2, req2, ReqIdC1), + 2 = gen_server:reqids_size(ReqIdC2), + + ReqIdC3 = gen_server:send_request(Pid3, {delayed_answer,200}, req3, ReqIdC2), + 3 = gen_server:reqids_size(ReqIdC3), + + Msg0 = next_msg(), + no_reply = gen_server:check_response(Msg0, ReqIdC3, true), + + {{reply, delayed}, req2, ReqIdC4} = gen_server:check_response(next_msg(), ReqIdC3, true), + 2 = gen_server:reqids_size(ReqIdC4), + + {{reply, delayed}, req3, ReqIdC5} = gen_server:check_response(next_msg(), ReqIdC4, true), + 1 = gen_server:reqids_size(ReqIdC5), + + {{reply, delayed}, req1, ReqIdC6} = gen_server:check_response(next_msg(), ReqIdC5, true), + 0 = gen_server:reqids_size(ReqIdC6), + + no_request = gen_server:check_response(Msg0, ReqIdC6, true), + + {reply, ok} = gen_server:check_response(Msg0, ReqId0), + + ok. + +send_request_check_reqid_collection_error(Pid1, Pid2, Pid3) -> + + ReqId0 = gen_server:send_request(Pid1, started_p), + + receive after 100 -> ok end, + + ReqIdC0 = gen_server:reqids_new(), + + ReqId1 = gen_server:send_request(Pid1, {delayed_answer,400}), + ReqIdC1 = gen_server:reqids_add(ReqId1, req1, ReqIdC0), + + unlink(Pid2), + ReqIdC2 = gen_server:send_request(Pid2, stop_shutdown, req2, ReqIdC1), + + ReqIdC3 = gen_server:send_request(Pid3, {delayed_answer,200}, req3, ReqIdC2), + 3 = gen_server:reqids_size(ReqIdC3), + + Msg0 = next_msg(), + + no_reply = gen_server:check_response(Msg0, ReqIdC3, true), + + {{error, {shutdown, _}}, req2, ReqIdC4} = gen_server:check_response(next_msg(), ReqIdC3, true), + 2 = gen_server:reqids_size(ReqIdC4), + + {{reply, delayed}, req3, ReqIdC4} = gen_server:check_response(next_msg(), ReqIdC4, false), + + {{reply, delayed}, req1, ReqIdC4} = gen_server:check_response(next_msg(), ReqIdC4, false), + + {reply, ok} = gen_server:check_response(Msg0, ReqId0), + + ok. + +next_msg() -> + receive M -> M end. %% -------------------------------------- %% Test handle_continue. diff --git a/lib/stdlib/test/gen_statem_SUITE.erl b/lib/stdlib/test/gen_statem_SUITE.erl index 9ddffcbb72ca..a34cb55e52ec 100644 --- a/lib/stdlib/test/gen_statem_SUITE.erl +++ b/lib/stdlib/test/gen_statem_SUITE.erl @@ -43,7 +43,9 @@ all() -> {group, sys}, hibernate, auto_hibernate, enter_loop, {group, undef_callbacks}, undef_in_terminate, {group, format_log}, - reply_by_alias_with_payload]. + reply_by_alias_with_payload, + send_request_receive_reqid_collection, send_request_wait_reqid_collection, + send_request_check_reqid_collection]. groups() -> [{start, [], tcs(start)}, @@ -2305,6 +2307,311 @@ reply_by_alias_with_payload(Config) when is_list(Config) -> ok end. +send_request_receive_reqid_collection(Config) when is_list(Config) -> + {ok,Pid1} = gen_statem:start(?MODULE, start_arg(Config, []), []), + {ok,Pid2} = gen_statem:start(?MODULE, start_arg(Config, []), []), + {ok,Pid3} = gen_statem:start(?MODULE, start_arg(Config, []), []), + send_request_receive_reqid_collection(Pid1, Pid2, Pid3), + send_request_receive_reqid_collection_timeout(Pid1, Pid2, Pid3), + send_request_receive_reqid_collection_error(Pid1, Pid2, Pid3), + stopped = gen_statem:call(Pid1, {stop,shutdown}), + stopped = gen_statem:call(Pid3, {stop,shutdown}), + check_stopped(Pid1), + check_stopped(Pid2), + check_stopped(Pid3), + ok. + +send_request_receive_reqid_collection(Pid1, Pid2, Pid3) -> + + ReqId0 = gen_statem:send_request(Pid1, 'alive?'), + + ReqIdC0 = gen_statem:reqids_new(), + + ReqId1 = gen_statem:send_request(Pid1, {delayed_answer,400}), + ReqIdC1 = gen_statem:reqids_add(ReqId1, req1, ReqIdC0), + 1 = gen_statem:reqids_size(ReqIdC1), + + ReqIdC2 = gen_statem:send_request(Pid2, {delayed_answer,1}, req2, ReqIdC1), + 2 = gen_statem:reqids_size(ReqIdC2), + + ReqIdC3 = gen_statem:send_request(Pid3, {delayed_answer,200}, req3, ReqIdC2), + 3 = gen_statem:reqids_size(ReqIdC3), + + {{reply, delayed}, req2, ReqIdC4} = gen_statem:receive_response(ReqIdC3, infinity, true), + 2 = gen_statem:reqids_size(ReqIdC4), + + {{reply, delayed}, req3, ReqIdC5} = gen_statem:receive_response(ReqIdC4, 5678, true), + 1 = gen_statem:reqids_size(ReqIdC5), + + {{reply, delayed}, req1, ReqIdC6} = gen_statem:receive_response(ReqIdC5, 5000, true), + 0 = gen_statem:reqids_size(ReqIdC6), + + no_request = gen_statem:receive_response(ReqIdC6, 5000, true), + + {reply, yes} = gen_statem:receive_response(ReqId0, infinity), + + ok. + +send_request_receive_reqid_collection_timeout(Pid1, Pid2, Pid3) -> + + ReqId0 = gen_statem:send_request(Pid1, 'alive?'), + + ReqIdC0 = gen_statem:reqids_new(), + + ReqId1 = gen_statem:send_request(Pid1, {delayed_answer,1000}), + ReqIdC1 = gen_statem:reqids_add(ReqId1, req1, ReqIdC0), + + ReqIdC2 = gen_statem:send_request(Pid2, {delayed_answer,1}, req2, ReqIdC1), + + ReqId3 = gen_statem:send_request(Pid3, {delayed_answer,500}), + ReqIdC3 = gen_statem:reqids_add(ReqId3, req3, ReqIdC2), + + Deadline = erlang:monotonic_time(millisecond) + 100, + + {{reply, delayed}, req2, ReqIdC4} = gen_statem:receive_response(ReqIdC3, {abs, Deadline}, true), + 2 = gen_statem:reqids_size(ReqIdC4), + + timeout = gen_statem:receive_response(ReqIdC4, {abs, Deadline}, true), + + Abandoned = lists:sort([{ReqId1, req1}, {ReqId3, req3}]), + Abandoned = lists:sort(gen_statem:reqids_to_list(ReqIdC4)), + + %% Make sure requests were abandoned... + timeout = gen_statem:receive_response(ReqIdC4, {abs, Deadline+1000}, true), + + {reply, yes} = gen_statem:receive_response(ReqId0, infinity), + + ok. + +send_request_receive_reqid_collection_error(Pid1, Pid2, Pid3) -> + + ReqId0 = gen_statem:send_request(Pid1, 'alive?'), + + ReqIdC0 = gen_statem:reqids_new(), + + ReqId1 = gen_statem:send_request(Pid1, {delayed_answer,400}), + ReqIdC1 = gen_statem:reqids_add(ReqId1, req1, ReqIdC0), + try + nope = gen_statem:reqids_add(ReqId1, req2, ReqIdC1) + catch + error:badarg -> ok + end, + + unlink(Pid2), + exit(Pid2, kill), + ReqIdC2 = gen_statem:send_request(Pid2, {delayed_answer,1}, req2, ReqIdC1), + ReqIdC3 = gen_statem:send_request(Pid3, {delayed_answer,200}, req3, ReqIdC2), + 3 = gen_statem:reqids_size(ReqIdC3), + + {{error, {noproc, _}}, req2, ReqIdC4} = gen_statem:receive_response(ReqIdC3, 2000, true), + 2 = gen_statem:reqids_size(ReqIdC4), + + {{reply, delayed}, req3, ReqIdC4} = gen_statem:receive_response(ReqIdC4, infinity, false), + + {{reply, delayed}, req1, ReqIdC4} = gen_statem:receive_response(ReqIdC4, infinity, false), + + {reply, yes} = gen_statem:receive_response(ReqId0, infinity), + + ok. + +send_request_wait_reqid_collection(Config) when is_list(Config) -> + {ok,Pid1} = gen_statem:start(?MODULE, start_arg(Config, []), []), + {ok,Pid2} = gen_statem:start(?MODULE, start_arg(Config, []), []), + {ok,Pid3} = gen_statem:start(?MODULE, start_arg(Config, []), []), + send_request_wait_reqid_collection(Pid1, Pid2, Pid3), + send_request_wait_reqid_collection_timeout(Pid1, Pid2, Pid3), + send_request_wait_reqid_collection_error(Pid1, Pid2, Pid3), + stopped = gen_statem:call(Pid1, {stop,shutdown}), + stopped = gen_statem:call(Pid3, {stop,shutdown}), + check_stopped(Pid1), + check_stopped(Pid2), + check_stopped(Pid3), + ok. + +send_request_wait_reqid_collection(Pid1, Pid2, Pid3) -> + + ReqId0 = gen_statem:send_request(Pid1, 'alive?'), + + ReqIdC0 = gen_statem:reqids_new(), + + ReqId1 = gen_statem:send_request(Pid1, {delayed_answer,400}), + ReqIdC1 = gen_statem:reqids_add(ReqId1, req1, ReqIdC0), + 1 = gen_statem:reqids_size(ReqIdC1), + + ReqIdC2 = gen_statem:send_request(Pid2, {delayed_answer,1}, req2, ReqIdC1), + 2 = gen_statem:reqids_size(ReqIdC2), + + ReqIdC3 = gen_statem:send_request(Pid3, {delayed_answer,200}, req3, ReqIdC2), + 3 = gen_statem:reqids_size(ReqIdC3), + + {{reply, delayed}, req2, ReqIdC4} = gen_statem:wait_response(ReqIdC3, infinity, true), + 2 = gen_statem:reqids_size(ReqIdC4), + + {{reply, delayed}, req3, ReqIdC5} = gen_statem:wait_response(ReqIdC4, 5678, true), + 1 = gen_statem:reqids_size(ReqIdC5), + + {{reply, delayed}, req1, ReqIdC6} = gen_statem:wait_response(ReqIdC5, 5000, true), + 0 = gen_statem:reqids_size(ReqIdC6), + + no_request = gen_statem:wait_response(ReqIdC6, 5000, true), + + {reply, yes} = gen_statem:receive_response(ReqId0, infinity), + + ok. + +send_request_wait_reqid_collection_timeout(Pid1, Pid2, Pid3) -> + + ReqId0 = gen_statem:send_request(Pid1, 'alive?'), + + ReqIdC0 = gen_statem:reqids_new(), + + ReqId1 = gen_statem:send_request(Pid1, {delayed_answer,1000}), + ReqIdC1 = gen_statem:reqids_add(ReqId1, req1, ReqIdC0), + + ReqIdC2 = gen_statem:send_request(Pid2, {delayed_answer,1}, req2, ReqIdC1), + + ReqId3 = gen_statem:send_request(Pid3, {delayed_answer,500}), + ReqIdC3 = gen_statem:reqids_add(ReqId3, req3, ReqIdC2), + + Deadline = erlang:monotonic_time(millisecond) + 100, + + {{reply, delayed}, req2, ReqIdC4} = gen_statem:wait_response(ReqIdC3, {abs, Deadline}, true), + 2 = gen_statem:reqids_size(ReqIdC4), + + timeout = gen_statem:wait_response(ReqIdC4, {abs, Deadline}, true), + + Unhandled = lists:sort([{ReqId1, req1}, {ReqId3, req3}]), + Unhandled = lists:sort(gen_statem:reqids_to_list(ReqIdC4)), + + %% Make sure requests were not abandoned... + {{reply, delayed}, req3, ReqIdC4} = gen_statem:wait_response(ReqIdC4, {abs, Deadline+1500}, false), + {{reply, delayed}, req1, ReqIdC4} = gen_statem:wait_response(ReqIdC4, {abs, Deadline+1500}, false), + + {reply, yes} = gen_statem:receive_response(ReqId0), + + ok. + +send_request_wait_reqid_collection_error(Pid1, Pid2, Pid3) -> + + ReqId0 = gen_statem:send_request(Pid1, 'alive?'), + + ReqIdC0 = gen_statem:reqids_new(), + + ReqId1 = gen_statem:send_request(Pid1, {delayed_answer,400}), + ReqIdC1 = gen_statem:reqids_add(ReqId1, req1, ReqIdC0), + try + nope = gen_statem:reqids_add(ReqId1, req2, ReqIdC1) + catch + error:badarg -> ok + end, + + unlink(Pid2), + exit(Pid2, kill), + ReqIdC2 = gen_statem:send_request(Pid2, {delayed_answer,1}, req2, ReqIdC1), + ReqIdC3 = gen_statem:send_request(Pid3, {delayed_answer,200}, req3, ReqIdC2), + 3 = gen_statem:reqids_size(ReqIdC3), + + {{error, {noproc, _}}, req2, ReqIdC4} = gen_statem:wait_response(ReqIdC3, 2000, true), + 2 = gen_statem:reqids_size(ReqIdC4), + + {{reply, delayed}, req3, ReqIdC4} = gen_statem:wait_response(ReqIdC4, infinity, false), + + {{reply, delayed}, req1, ReqIdC4} = gen_statem:wait_response(ReqIdC4, infinity, false), + + {reply, yes} = gen_statem:receive_response(ReqId0, infinity), + + ok. + +send_request_check_reqid_collection(Config) when is_list(Config) -> + {ok,Pid1} = gen_statem:start(?MODULE, start_arg(Config, []), []), + {ok,Pid2} = gen_statem:start(?MODULE, start_arg(Config, []), []), + {ok,Pid3} = gen_statem:start(?MODULE, start_arg(Config, []), []), + send_request_check_reqid_collection(Pid1, Pid2, Pid3), + send_request_check_reqid_collection_error(Pid1, Pid2, Pid3), + stopped = gen_statem:call(Pid1, {stop,shutdown}), + stopped = gen_statem:call(Pid3, {stop,shutdown}), + check_stopped(Pid1), + check_stopped(Pid2), + check_stopped(Pid3), + ok. + +send_request_check_reqid_collection(Pid1, Pid2, Pid3) -> + + ReqId0 = gen_statem:send_request(Pid1, 'alive?'), + + receive after 100 -> ok end, + + ReqIdC0 = gen_statem:reqids_new(), + + ReqIdC1 = gen_statem:send_request(Pid1, {delayed_answer,400}, req1, ReqIdC0), + 1 = gen_statem:reqids_size(ReqIdC1), + + ReqId2 = gen_statem:send_request(Pid2, {delayed_answer,1}), + ReqIdC2 = gen_statem:reqids_add(ReqId2, req2, ReqIdC1), + 2 = gen_statem:reqids_size(ReqIdC2), + + ReqIdC3 = gen_statem:send_request(Pid3, {delayed_answer,200}, req3, ReqIdC2), + 3 = gen_statem:reqids_size(ReqIdC3), + + Msg0 = next_msg(), + no_reply = gen_statem:check_response(Msg0, ReqIdC3, true), + + {{reply, delayed}, req2, ReqIdC4} = gen_statem:check_response(next_msg(), ReqIdC3, true), + 2 = gen_statem:reqids_size(ReqIdC4), + + {{reply, delayed}, req3, ReqIdC5} = gen_statem:check_response(next_msg(), ReqIdC4, true), + 1 = gen_statem:reqids_size(ReqIdC5), + + {{reply, delayed}, req1, ReqIdC6} = gen_statem:check_response(next_msg(), ReqIdC5, true), + 0 = gen_statem:reqids_size(ReqIdC6), + + no_request = gen_statem:check_response(Msg0, ReqIdC6, true), + + {reply, yes} = gen_statem:check_response(Msg0, ReqId0), + + ok. + +send_request_check_reqid_collection_error(Pid1, Pid2, Pid3) -> + + ReqId0 = gen_statem:send_request(Pid1, 'alive?'), + + receive after 100 -> ok end, + + ReqIdC0 = gen_statem:reqids_new(), + + ReqId1 = gen_statem:send_request(Pid1, {delayed_answer,400}), + ReqIdC1 = gen_statem:reqids_add(ReqId1, req1, ReqIdC0), + try + nope = gen_statem:reqids_add(ReqId1, req2, ReqIdC1) + catch + error:badarg -> ok + end, + + unlink(Pid2), + exit(Pid2, kill), + ReqIdC2 = gen_statem:send_request(Pid2, {delayed_answer,1}, req2, ReqIdC1), + + ReqIdC3 = gen_statem:send_request(Pid3, {delayed_answer,200}, req3, ReqIdC2), + 3 = gen_statem:reqids_size(ReqIdC3), + + Msg0 = next_msg(), + + no_reply = gen_statem:check_response(Msg0, ReqIdC3, true), + + {{error, {noproc, _}}, req2, ReqIdC4} = gen_statem:check_response(next_msg(), ReqIdC3, true), + 2 = gen_statem:reqids_size(ReqIdC4), + + {{reply, delayed}, req3, ReqIdC4} = gen_statem:check_response(next_msg(), ReqIdC4, false), + + {{reply, delayed}, req1, ReqIdC4} = gen_statem:check_response(next_msg(), ReqIdC4, false), + + {reply, yes} = gen_statem:check_response(Msg0, ReqId0), + + ok. + +next_msg() -> + receive M -> M end. + %% %% Functionality check %%