summaryrefslogtreecommitdiff
path: root/lib/stdlib/src/gen.erl
diff options
context:
space:
mode:
authorDan Gudmundsson <dgud@erlang.org>2017-09-21 13:43:52 +0200
committerDan Gudmundsson <dgud@erlang.org>2017-09-22 09:42:29 +0200
commit34814fd2f9fc6337f1333115e9bd36042acf9222 (patch)
treeb0a12598c8c51efbc3195b34e5577c2645d65065 /lib/stdlib/src/gen.erl
parent99876dd2dd9150ec4b15220c7fd46ed0b8200a19 (diff)
downloaderlang-34814fd2f9fc6337f1333115e9bd36042acf9222.tar.gz
stdlib: Add 'async_call' and 'yield' to generic behaviors
Simplify and encourage users to do more async work, the usage pattern is already available in 'rpc' module and similar usages are available in other languages and standards. Async calls can be implemented via cast or regular messages, but then the user need to implement it both in client and server. In this implementation the server does not need to know that the client are making async calls. This deliberately opens up and exposes the monitor reference, so that the user can choose not call 'yield' and instead do: Promise = gen:async_call(..), ... receive {Promise, Reply} -> erlang:demonitor(Promise, [flush]), Reply; {'DOWN', Promise, _, _, Reason} -> error(Reason) end, Or use async_call(..) from an gen_server to another gen behavior while not blocking the invoking server and handle the reply when it arrives in handle_info(..). This implies that systems that do can not handle monitors are not allowed to be used as target in async_call(). yield/[1|2] returns {reply, Reply} instead of {ok, Reply} since Reply may be positive or negative answer i.e.: {reply, {ok, Value}} and {reply, {error, Reason}} looks better than {ok, {error, Reason}} or {ok, {ok, Value}}. And we need to encapsulate the return value to differ between client timeouts and server response which may be the atom timeout, e.g. timeout vs {reply, timeout} We don't want do exit(timeout) since then you can't do non_blocking yields without catching the call to yield(Promise, 0).
Diffstat (limited to 'lib/stdlib/src/gen.erl')
-rw-r--r--lib/stdlib/src/gen.erl72
1 files changed, 70 insertions, 2 deletions
diff --git a/lib/stdlib/src/gen.erl b/lib/stdlib/src/gen.erl
index 33af0aed8f..bb40798ba1 100644
--- a/lib/stdlib/src/gen.erl
+++ b/lib/stdlib/src/gen.erl
@@ -28,7 +28,9 @@
%%%-----------------------------------------------------------------
-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, stop/1, stop/3]).
+ call/3, call/4, reply/2,
+ async_call/3, yield/1, yield/2,
+ stop/1, stop/3]).
-export([init_it/6, init_it/7]).
@@ -52,6 +54,11 @@
| {'spawn_opt', [proc_lib:spawn_option()]}.
-type options() :: [option()].
+-type server_ref() :: pid() | atom() | {atom(), node()}
+ | {global, term()} | {via, module(), term()}.
+
+-type promise() :: reference().
+
%%-----------------------------------------------------------------
%% Starts a generic process.
%% start(GenMod, LinkP, Mod, Args, Options)
@@ -138,7 +145,7 @@ init_it2(GenMod, Starter, Parent, Name, Mod, Args, Options) ->
%%-----------------------------------------------------------------
%% Makes a synchronous call to a generic process.
%% Request is sent to the Pid, and the response must be
-%% {Tag, _, Reply}.
+%% {Tag, Reply}.
%%-----------------------------------------------------------------
%%% New call function which uses the new monitor BIF
@@ -225,6 +232,67 @@ wait_resp(Node, Tag, Timeout) ->
exit(timeout)
end.
+-spec async_call(Name::server_ref(), Label::term(), Request::term()) -> promise().
+async_call(Process, Label, Request) when is_pid(Process); is_atom(Process) ->
+ do_async_call(Process, Label, Request);
+async_call({Name, _}=Process, Label, Request)
+ when is_atom(Name), Name =/= global ->
+ do_async_call(Process, Label, Request);
+async_call(Process, Label, Request) ->
+ try where(Process) of
+ Pid when is_pid(Pid) ->
+ do_async_call(Pid, Label, Request);
+ undefined ->
+ Ref = erlang:make_ref(),
+ self() ! {'DOWN', Ref, process, Process, noproc},
+ Ref
+ catch _:_ ->
+ error({badarg,Process})
+ end.
+
+do_async_call(Process, Label, Request) ->
+ try erlang:monitor(process, Process) of
+ Mref ->
+ %% If the monitor/2 call failed to set up a connection to a
+ %% remote node, we don't want the '!' operator to attempt
+ %% to set up the connection again. (If the monitor/2 call
+ %% failed due to an expired timeout, '!' too would probably
+ %% have to wait for the timeout to expire.) Therefore,
+ %% use erlang:send/3 with the 'noconnect' option so that it
+ %% will fail immediately if there is no connection to the
+ %% remote node.
+ catch erlang:send(Process, {Label, {self(), Mref}, Request},
+ [noconnect]),
+ Mref
+ catch
+ %% Do not support erl_interface or other systems which
+ %% non don't have monitor supported
+ error:_ -> error({badarg, Process})
+ end.
+
+%%
+%% Wait for a reply to the client.
+%% Note: if timeout is returned monitors are kept.
+
+-spec yield(Key::promise()) -> {ok, Reply::term()}.
+yield(Key) ->
+ yield(Key, infinity).
+
+-spec yield(Key::promise(), timeout()) -> {reply, Reply::term()} | 'timeout'.
+yield(Mref, Timeout) ->
+ receive
+ {Mref, Reply} ->
+ erlang:demonitor(Mref, [flush]),
+ {reply, Reply};
+ {'DOWN', Mref, _, Pid, noconnection} when is_pid(Pid) ->
+ exit({nodedown, node(Pid)});
+ {'DOWN', Mref, _, {_, Node}, noconnection} ->
+ exit({nodedown, Node});
+ {'DOWN', Mref, _, _, Reason} ->
+ exit(Reason)
+ after Timeout -> timeout
+ end.
+
%%
%% Send a reply to the client.
%%