summaryrefslogtreecommitdiff
path: root/lib/stdlib/src
diff options
context:
space:
mode:
authorRickard Green <rickard@erlang.org>2020-07-30 14:00:31 +0200
committerRickard Green <rickard@erlang.org>2020-11-12 18:19:17 +0100
commit7f4faa03a0fac9e841d16f4e3a47e66a4668b58e (patch)
tree8ec298b22c9ac2e39ba6d23108d3f8402fef3ca5 /lib/stdlib/src
parent9362aa5e226954ddadcde3bd41c4e0441a4d56c1 (diff)
downloaderlang-7f4faa03a0fac9e841d16f4e3a47e66a4668b58e.tar.gz
Use alias in gen behaviours
Diffstat (limited to 'lib/stdlib/src')
-rw-r--r--lib/stdlib/src/gen.erl81
-rw-r--r--lib/stdlib/src/gen_event.erl13
-rw-r--r--lib/stdlib/src/gen_fsm.erl6
-rw-r--r--lib/stdlib/src/gen_server.erl11
-rw-r--r--lib/stdlib/src/gen_statem.erl30
-rw-r--r--lib/stdlib/src/stdlib.app.src2
6 files changed, 122 insertions, 21 deletions
diff --git a/lib/stdlib/src/gen.erl b/lib/stdlib/src/gen.erl
index be14665d80..b2f2a0ff4e 100644
--- a/lib/stdlib/src/gen.erl
+++ b/lib/stdlib/src/gen.erl
@@ -29,7 +29,8 @@
-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, check_response/2,
+ send_request/3, wait_response/2,
+ receive_response/2, check_response/2,
stop/1, stop/3]).
-export([init_it/6, init_it/7]).
@@ -198,17 +199,41 @@ call(Process, Label, Request, Timeout)
Fun = fun(Pid) -> do_call(Pid, Label, Request, Timeout) end,
do_for_proc(Process, Fun).
-do_call(Process, Label, Request, Timeout) when is_atom(Process) =:= false ->
+-dialyzer({no_improper_lists, do_call/4}).
+
+do_call(Process, Label, Request, infinity)
+ when (is_pid(Process)
+ andalso (node(Process) == node()))
+ orelse (element(2, Process) == node()
+ andalso is_atom(element(1, Process))
+ andalso (tuple_size(Process) =:= 2)) ->
Mref = erlang:monitor(process, Process),
+ %% Local without timeout; no need to use alias since we unconditionally
+ %% will wait for either a reply or a down message which corresponds to
+ %% the process being terminated (as opposed to 'noconnection')...
+ Process ! {Label, {self(), Mref}, Request},
+ receive
+ {Mref, Reply} ->
+ erlang:demonitor(Mref, [flush]),
+ {ok, Reply};
+ {'DOWN', Mref, _, _, Reason} ->
+ exit(Reason)
+ end;
+do_call(Process, Label, Request, Timeout) when is_atom(Process) =:= false ->
+ Mref = erlang:monitor(process, Process, [{alias,demonitor}]),
+
+ Tag = [alias | Mref],
- %% OTP-21:
- %% Auto-connect is asynchronous. But we still use 'noconnect' to make sure
- %% we send on the monitored connection, and not trigger a new auto-connect.
+ %% OTP-24:
+ %% Using alias to prevent responses after 'noconnection' and timeouts.
+ %% We however still may call nodes responding via process identifier, so
+ %% we still use 'noconnect' on send in order to try to send on the
+ %% monitored connection, and not trigger a new auto-connect.
%%
- erlang:send(Process, {Label, {self(), Mref}, Request}, [noconnect]),
+ erlang:send(Process, {Label, {self(), Tag}, Request}, [noconnect]),
receive
- {Mref, Reply} ->
+ {[alias | Mref], Reply} ->
erlang:demonitor(Mref, [flush]),
{ok, Reply};
{'DOWN', Mref, _, _, noconnection} ->
@@ -218,7 +243,12 @@ do_call(Process, Label, Request, Timeout) when is_atom(Process) =:= false ->
exit(Reason)
after Timeout ->
erlang:demonitor(Mref, [flush]),
- exit(timeout)
+ receive
+ {[alias | Mref], Reply} ->
+ {ok, Reply}
+ after 0 ->
+ exit(timeout)
+ end
end.
get_node(Process) ->
@@ -246,9 +276,11 @@ send_request(Process, Label, Request) ->
Mref
end.
+-dialyzer({no_improper_lists, do_send_request/3}).
+
do_send_request(Process, Label, Request) ->
- Mref = erlang:monitor(process, Process),
- erlang:send(Process, {Label, {self(), {'$gen_request_id', Mref}}, Request}, [noconnect]),
+ Mref = erlang:monitor(process, Process, [{alias, demonitor}]),
+ erlang:send(Process, {Label, {self(), [alias|Mref]}, Request}, [noconnect]),
Mref.
%%
@@ -257,10 +289,9 @@ do_send_request(Process, Label, Request) ->
-spec wait_response(RequestId::request_id(), timeout()) ->
{reply, Reply::term()} | 'timeout' | {error, {term(), server_ref()}}.
-wait_response(Mref, Timeout)
- when is_reference(Mref) ->
+wait_response(Mref, Timeout) when is_reference(Mref) ->
receive
- {{'$gen_request_id', Mref}, Reply} ->
+ {[alias|Mref], Reply} ->
erlang:demonitor(Mref, [flush]),
{reply, Reply};
{'DOWN', Mref, _, Object, Reason} ->
@@ -269,12 +300,30 @@ wait_response(Mref, Timeout)
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) ->
+ receive
+ {[alias|Mref], Reply} ->
+ erlang:demonitor(Mref, [flush]),
+ {reply, Reply};
+ {'DOWN', Mref, _, Object, Reason} ->
+ {error, {Reason, Object}}
+ after Timeout ->
+ erlang:demonitor(Mref, [flush]),
+ receive
+ {[alias|Mref], 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) ->
+check_response(Msg, Mref) when is_reference(Mref) ->
case Msg of
- {{'$gen_request_id', Mref}, Reply} ->
+ {[alias|Mref], Reply} ->
erlang:demonitor(Mref, [flush]),
{reply, Reply};
{'DOWN', Mref, _, Object, Reason} ->
diff --git a/lib/stdlib/src/gen_event.erl b/lib/stdlib/src/gen_event.erl
index 8024221cab..0d069119c9 100644
--- a/lib/stdlib/src/gen_event.erl
+++ b/lib/stdlib/src/gen_event.erl
@@ -43,7 +43,7 @@
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, check_response/2,
+ send_request/3, wait_response/2, receive_response/2, check_response/2,
wake_hib/5]).
-export([init_it/6,
@@ -248,6 +248,14 @@ wait_response(RequestId, Timeout) ->
Return -> Return
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
+ {reply, {error, _} = Err} -> Err;
+ Return -> Return
+ end.
+
-spec check_response(Msg::term(), RequestId::request_id()) ->
{reply, Reply::term()} | 'no_reply' | {error, {Reason::term(), emgr_ref()}}.
check_response(Msg, RequestId) ->
@@ -396,6 +404,9 @@ terminate_server(Reason, Parent, MSL, ServerName) ->
do_unlink(Parent, MSL),
exit(Reason).
+reply({To, [alias|Alias] = Tag}, Reply) when is_pid(To), is_reference(Alias) ->
+ Alias ! {Tag, Reply},
+ ok;
reply({From, Ref}, Msg) ->
From ! {Ref, Msg},
ok.
diff --git a/lib/stdlib/src/gen_fsm.erl b/lib/stdlib/src/gen_fsm.erl
index f4752c37d4..9ff58584eb 100644
--- a/lib/stdlib/src/gen_fsm.erl
+++ b/lib/stdlib/src/gen_fsm.erl
@@ -564,8 +564,12 @@ from({'$gen_sync_all_state_event', From, _Event}) -> From;
from(_) -> undefined.
%% Send a reply to the client.
+reply({To, [alias|Alias] = Tag}, Reply) when is_pid(To), is_reference(Alias) ->
+ Alias ! {Tag, Reply},
+ ok;
reply({To, Tag}, Reply) ->
- catch To ! {Tag, Reply}.
+ catch To ! {Tag, Reply},
+ ok.
reply(Name, From, Reply, Debug, StateName) ->
reply(From, Reply),
diff --git a/lib/stdlib/src/gen_server.erl b/lib/stdlib/src/gen_server.erl
index e49961a5f0..86196eaf2a 100644
--- a/lib/stdlib/src/gen_server.erl
+++ b/lib/stdlib/src/gen_server.erl
@@ -97,7 +97,8 @@
start_monitor/3, start_monitor/4,
stop/1, stop/3,
call/2, call/3,
- send_request/2, wait_response/2, check_response/2,
+ send_request/2, wait_response/2,
+ receive_response/2, check_response/2,
cast/2, reply/2,
abcast/2, abcast/3,
multi_call/2, multi_call/3, multi_call/4,
@@ -260,6 +261,11 @@ send_request(Name, Request) ->
wait_response(RequestId, Timeout) ->
gen:wait_response(RequestId, Timeout).
+-spec receive_response(RequestId::request_id(), timeout()) ->
+ {reply, Reply::term()} | 'timeout' | {error, {Reason::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, {Reason::term(), server_ref()}}.
check_response(Msg, RequestId) ->
@@ -290,6 +296,9 @@ cast_msg(Request) -> {'$gen_cast',Request}.
%% -----------------------------------------------------------------
%% Send a reply to the client.
%% -----------------------------------------------------------------
+reply({To, [alias|Alias] = Tag}, Reply) when is_pid(To), is_reference(Alias) ->
+ Alias ! {Tag, Reply},
+ ok;
reply({To, Tag}, Reply) ->
catch To ! {Tag, Reply},
ok.
diff --git a/lib/stdlib/src/gen_statem.erl b/lib/stdlib/src/gen_statem.erl
index adf1a82a08..9b73a919c8 100644
--- a/lib/stdlib/src/gen_statem.erl
+++ b/lib/stdlib/src/gen_statem.erl
@@ -32,7 +32,8 @@
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,check_response/2,
+ send_request/2,wait_response/1,wait_response/2,
+ receive_response/1,receive_response/2,check_response/2,
enter_loop/4,enter_loop/5,enter_loop/6,
reply/1,reply/2]).
@@ -596,6 +597,16 @@ wait_response(RequestId) ->
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) ->
@@ -610,6 +621,9 @@ reply(Replies) when is_list(Replies) ->
%%
-compile({inline, [reply/2]}).
-spec reply(From :: from(), Reply :: term()) -> ok.
+reply({To, [alias|Alias] = Tag}, Reply) when is_pid(To), is_reference(Alias) ->
+ Alias ! {Tag, Reply},
+ ok;
reply({To,Tag}, Reply) when is_pid(To) ->
Msg = {Tag,Reply},
try To ! Msg of
@@ -679,8 +693,22 @@ call_dirty(ServerRef, Request, Timeout, T) ->
Stacktrace)
end.
+call_clean(ServerRef, Request, Timeout, T)
+ when (is_pid(ServerRef)
+ andalso (node(ServerRef) == node()))
+ orelse (element(2, ServerRef) == node()
+ andalso is_atom(element(1, ServerRef))
+ andalso (tuple_size(ServerRef) =:= 2)) ->
+ %% No need to use a proxy locally since we know alias will be
+ %% used as of OTP 24 which will prevent garbage responses...
+ call_dirty(ServerRef, Request, Timeout, T);
call_clean(ServerRef, Request, Timeout, T) ->
%% Call server through proxy process to dodge any late reply
+ %%
+ %% We still need a proxy in the distributed case since we may
+ %% communicate with a node that does not understand aliases.
+ %% This can be removed when alias support is mandatory.
+ %% Probably in OTP 26.
Ref = make_ref(),
Self = self(),
Pid = spawn(
diff --git a/lib/stdlib/src/stdlib.app.src b/lib/stdlib/src/stdlib.app.src
index b59e3b28c0..60ddb64640 100644
--- a/lib/stdlib/src/stdlib.app.src
+++ b/lib/stdlib/src/stdlib.app.src
@@ -109,6 +109,6 @@
dets]},
{applications, [kernel]},
{env, []},
- {runtime_dependencies, ["sasl-3.0","kernel-7.0","erts-11.0","crypto-3.3",
+ {runtime_dependencies, ["sasl-3.0","kernel-7.0","erts-@OTP-16718@","crypto-3.3",
"compiler-5.0"]}
]}.