summaryrefslogtreecommitdiff
path: root/lib/stdlib/src/gen.erl
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/src/gen.erl')
-rw-r--r--lib/stdlib/src/gen.erl97
1 files changed, 94 insertions, 3 deletions
diff --git a/lib/stdlib/src/gen.erl b/lib/stdlib/src/gen.erl
index a7f743bd4c..be14665d80 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,
+ send_request/3, wait_response/2, check_response/2,
+ stop/1, stop/3]).
-export([init_it/6, init_it/7]).
@@ -38,7 +40,7 @@
%%-----------------------------------------------------------------
--type linkage() :: 'link' | 'nolink'.
+-type linkage() :: 'monitor' | 'link' | 'nolink'.
-type emgr_name() :: {'local', atom()}
| {'global', term()}
| {'via', Module :: module(), Name :: term()}.
@@ -53,6 +55,11 @@
| {'spawn_opt', [proc_lib:spawn_option()]}.
-type options() :: [option()].
+-type server_ref() :: pid() | atom() | {atom(), node()}
+ | {global, term()} | {via, module(), term()}.
+
+-type request_id() :: term().
+
%%-----------------------------------------------------------------
%% Starts a generic process.
%% start(GenMod, LinkP, Mod, Args, Options)
@@ -95,6 +102,13 @@ do_spawn(GenMod, link, Mod, Args, Options) ->
[GenMod, self(), self(), Mod, Args, Options],
Time,
spawn_opts(Options));
+do_spawn(GenMod, monitor, Mod, Args, Options) ->
+ Time = timeout(Options),
+ Ret = proc_lib:start_monitor(?MODULE, init_it,
+ [GenMod, self(), self(), Mod, Args, Options],
+ Time,
+ spawn_opts(Options)),
+ monitor_return(Ret);
do_spawn(GenMod, _, Mod, Args, Options) ->
Time = timeout(Options),
proc_lib:start(?MODULE, init_it,
@@ -108,6 +122,13 @@ do_spawn(GenMod, link, Name, Mod, Args, Options) ->
[GenMod, self(), self(), Name, Mod, Args, Options],
Time,
spawn_opts(Options));
+do_spawn(GenMod, monitor, Name, Mod, Args, Options) ->
+ Time = timeout(Options),
+ Ret = proc_lib:start_monitor(?MODULE, init_it,
+ [GenMod, self(), self(), Name, Mod, Args, Options],
+ Time,
+ spawn_opts(Options)),
+ monitor_return(Ret);
do_spawn(GenMod, _, Name, Mod, Args, Options) ->
Time = timeout(Options),
proc_lib:start(?MODULE, init_it,
@@ -115,6 +136,26 @@ do_spawn(GenMod, _, Name, Mod, Args, Options) ->
Time,
spawn_opts(Options)).
+
+%%
+%% Adjust monitor returns for OTP gen behaviours...
+%%
+%% If an OTP behaviour is introduced that 'init_ack's
+%% other results, this has code has to be moved out
+%% into all behaviours as well as adjusted...
+%%
+monitor_return({{ok, Pid}, Mon}) when is_pid(Pid), is_reference(Mon) ->
+ %% Successful start_monitor()...
+ {ok, {Pid, Mon}};
+monitor_return({Error, Mon}) when is_reference(Mon) ->
+ %% Failure; wait for spawned process to terminate
+ %% and release resources, then return the error...
+ receive
+ {'DOWN', Mon, process, _Pid, _Reason} ->
+ ok
+ end,
+ Error.
+
%%-----------------------------------------------------------------
%% Initiate the new process.
%% Register the name using the Rfunc function
@@ -139,7 +180,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
@@ -192,6 +233,56 @@ 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,
+ try do_for_proc(Process, Fun)
+ catch exit:Reason ->
+ %% Make send_request async and fake a down message
+ Mref = erlang:make_ref(),
+ self() ! {'DOWN', Mref, process, Process, Reason},
+ Mref
+ end.
+
+do_send_request(Process, Label, Request) ->
+ Mref = erlang:monitor(process, Process),
+ erlang:send(Process, {Label, {self(), {'$gen_request_id', Mref}}, Request}, [noconnect]),
+ Mref.
+
+%%
+%% 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) ->
+ receive
+ {{'$gen_request_id', Mref}, Reply} ->
+ erlang:demonitor(Mref, [flush]),
+ {reply, Reply};
+ {'DOWN', Mref, _, Object, Reason} ->
+ {error, {Reason, Object}}
+ after Timeout ->
+ timeout
+ 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) ->
+ case Msg of
+ {{'$gen_request_id', Mref}, Reply} ->
+ erlang:demonitor(Mref, [flush]),
+ {reply, Reply};
+ {'DOWN', Mref, _, Object, Reason} ->
+ {error, {Reason, Object}};
+ _ ->
+ no_reply
+ end.
+
%%
%% Send a reply to the client.
%%