File 1111-Don-t-throw-exceptions-from-rpc-call-and-rpc-block_c.patch of Package erlang
From cccf762d93640b707f8e1515604cebcfbe379c04 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Fri, 11 Mar 2016 13:13:59 +0100
Subject: [PATCH] Don't throw exceptions from rpc:call() and rpc:block_call()
The documentation for rpc:call() says:
Evaluates apply(Module, Function, Args) on the node Node and
returns the corresponding value Res, or {badrpc, Reason} if
the call fails.
What is not said that rpc:call() can generate an exception if the
'rex' process on the other node is killed:
(kalle@host)1> Rex = rpc:call(arne@host, erlang, whereis, [rex]).
<6937.14.0>
(kalle@host)2> rpc:call(arne@host, erlang, exit, [Rex,kill]).
** exception exit: {killed,
{gen_server,call,
[{rex,arne@host},
{call,erlang,exit,[<6937.14.0>,kill],<0.33.0>},
infinity]}}
in function rpc:rpc_check/1 (rpc.erl, line 361)
On the other hand, if the other node shuts down for some other reason,
we'll get a {badrpc,nodedown} result:
(kalle@host)5> rpc:call(arne@host, erlang, halt, []).
{badrpc,nodedown}
There does not seem to be any reason to handle the two cases
differently. If the 'rex' process is terminated on the other node,
it will shut down shortly thereafter.
Therefore, change rpc:call() and rpc:block_call() to always return
{badrpc,Reason} is the call fails:
(kalle@host)1> Rex = rpc:call(arne@host, erlang, whereis, [rex]).
<6937.14.0>
(kalle@host)2> rpc:call(arne@host, erlang, exit, [Rex,kill]).
{badrpc,{'EXIT',{killed,{gen_server,call,
[{rex,arne@host},
{call,erlang,exit,[<7126.14.0>,kill],<0.33.0>},
infinity]}}}}
---
lib/kernel/src/rpc.erl | 8 ++++++--
lib/kernel/test/rpc_SUITE.erl | 26 +++++++++++---------------
2 files changed, 17 insertions(+), 17 deletions(-)
diff --git a/lib/kernel/src/rpc.erl b/lib/kernel/src/rpc.erl
index d3db8eb..b928448 100644
--- a/lib/kernel/src/rpc.erl
+++ b/lib/kernel/src/rpc.erl
@@ -357,8 +357,12 @@ do_call(Node, Request, Timeout) ->
rpc_check_t({'EXIT', {timeout,_}}) -> {badrpc, timeout};
rpc_check_t(X) -> rpc_check(X).
-rpc_check({'EXIT', {{nodedown,_},_}}) -> {badrpc, nodedown};
-rpc_check({'EXIT', X}) -> exit(X);
+rpc_check({'EXIT', {{nodedown,_},_}}) ->
+ {badrpc, nodedown};
+rpc_check({'EXIT', _}=Exit) ->
+ %% Should only happen if the rex process on the other node
+ %% died.
+ {badrpc, Exit};
rpc_check(X) -> X.
diff --git a/lib/kernel/test/rpc_SUITE.erl b/lib/kernel/test/rpc_SUITE.erl
index 0e9068f..101cff7 100644
--- a/lib/kernel/test/rpc_SUITE.erl
+++ b/lib/kernel/test/rpc_SUITE.erl
@@ -372,30 +372,27 @@
?line PA = filename:dirname(code:which(?MODULE)),
%%
?line node_rep(
- fun (Tag, Call, Args) ->
- {Tag,{badrpc,nodedown}} =
- {Tag,apply(rpc, Call, Args)}
+ fun (Call, Args) ->
+ {badrpc,nodedown}} = apply(rpc, Call, Args)
end, "rpc_SUITE_called_node_dies_1",
PA, ?MODULE, suicide, [erlang,halt,[]]),
?line node_rep(
- fun (Tag, Call, Args) ->
- {Tag,{badrpc,nodedown}} =
- {Tag,apply(rpc, Call, Args)}
+ fun (Call, Args) ->
+ {badrpc,nodedown}} = apply(rpc, Call, Args)
end, "rpc_SUITE_called_node_dies_2",
PA, ?MODULE, suicide, [init,stop,[]]),
?line node_rep(
- fun (Tag, Call, Args=[_|_]) ->
- {Tag,{'EXIT',{killed,_}}} =
- {Tag,catch {noexit,apply(rpc, Call, Args)}}
+ fun (Call, Args=[_|_]) ->
+ {'EXIT',{killed,_}}} = apply(rpc, Call, Args)
end, "rpc_SUITE_called_node_dies_3",
PA, ?MODULE, suicide, [erlang,exit,[rex,kill]]),
?line node_rep(
- fun %% Cannot block call rpc - will hang
- (_Tag, block_call, _Args) -> ok;
+ fun (block_call, _Args) ->
+ %% Cannot block call rpc - will hang
+ ok;
(Tag, Call, Args=[_|_]) ->
- {Tag,{'EXIT',{normal,_}}} =
- {Tag,catch {noexit,apply(rpc, Call, Args)}}
- end, "rpc_SUITE_called_node_dies_4",
+ {'EXIT',{normal,_}}} = apply(rpc, Call, Args)
+ end, "rpc_SUITE_called_node_dies_4",
PA, ?MODULE, suicide, [rpc,stop,[]]),
%%
?t:timetrap_cancel(Timetrap),
@@ -404,28 +401,28 @@
node_rep(Fun, Name, PA, M, F, A) ->
{ok, Na} = ?t:start_node(list_to_atom(Name++"_a"), slave,
[{args, "-pa " ++ PA}]),
- Fun(a, call, [Na, M, F, A]),
+ Fun(call, [Na, M, F, A]),
catch ?t:stop_node(Na),
{ok, Nb} = ?t:start_node(list_to_atom(Name++"_b"), slave,
[{args, "-pa " ++ PA}]),
- Fun(b, call, [Nb, M, F, A, infinity]),
+ Fun(call, [Nb, M, F, A, infinity]),
catch ?t:stop_node(Nb),
{ok, Nc} = ?t:start_node(list_to_atom(Name++"_c"), slave,
[{args, "-pa " ++ PA}]),
- Fun(c, call, [Nc, M, F, A, infinity]),
+ Fun(call, [Nc, M, F, A, infinity]),
catch ?t:stop_node(Nc),
%%
{ok, Nd} = ?t:start_node(list_to_atom(Name++"_d"), slave,
[{args, "-pa " ++ PA}]),
- Fun(d, block_call, [Nd, M, F, A]),
+ Fun(block_call, [Nd, M, F, A]),
catch ?t:stop_node(Nd),
{ok, Ne} = ?t:start_node(list_to_atom(Name++"_e"), slave,
[{args, "-pa " ++ PA}]),
- Fun(e, block_call, [Ne, M, F, A, infinity]),
+ Fun(block_call, [Ne, M, F, A, infinity]),
catch ?t:stop_node(Ne),
{ok, Nf} = ?t:start_node(list_to_atom(Name++"_f"), slave,
[{args, "-pa " ++ PA}]),
- Fun(f, block_call, [Nf, M, F, A, infinity]),
+ Fun(block_call, [Nf, M, F, A, infinity]),
catch ?t:stop_node(Nf),
ok.
--
2.1.4