Skip to content

Commit

Permalink
Merge branch 'sverker/dist-ctrl-shutdown-reason' into maint
Browse files Browse the repository at this point in the history
OTP-17838
  • Loading branch information
sverker committed Feb 28, 2022
2 parents e30cfc7 + add7bfb commit 0441e42
Show file tree
Hide file tree
Showing 3 changed files with 57 additions and 0 deletions.
1 change: 1 addition & 0 deletions erts/emulator/beam/atom.names
Expand Up @@ -629,6 +629,7 @@ atom set_on_spawn
atom set_seq_token
atom set_tcw
atom set_tcw_fake
atom shutdown
atom sighup
atom sigterm
atom sigusr1
Expand Down
13 changes: 13 additions & 0 deletions erts/emulator/beam/dist.c
Expand Up @@ -965,6 +965,19 @@ int erts_do_net_exits(DistEntry *dep, Eterm reason)
if (erts_port_task_is_scheduled(&dep->dist_cmd))
erts_port_task_abort(&dep->dist_cmd);
}
else {
ASSERT(is_internal_pid(dep->cid));
/*
* Supervised distribution controllers may exit "normally" with
* {shutdown,Reason}. Unwrap such shutdown tuple to get a correct
* documented 'nodedown_reason' from net_kernel:montitor_nodes.
*/
if (is_tuple_arity(reason, 2)) {
Eterm* tpl = tuple_val(reason);
if (tpl[1] == am_shutdown)
reason = tpl[2];
}
}

if (dep->state == ERTS_DE_STATE_EXITING) {
ASSERT(erts_atomic32_read_nob(&dep->qflgs) & ERTS_DE_QFLG_EXIT);
Expand Down
43 changes: 43 additions & 0 deletions lib/ssl/test/ssl_dist_SUITE.erl
Expand Up @@ -37,6 +37,7 @@
%% Test cases
-export([basic/0,
basic/1,
monitor_nodes/1,
payload/0,
payload/1,
dist_port_overload/0,
Expand Down Expand Up @@ -65,6 +66,7 @@

%% Apply export
-export([basic_test/3,
monitor_nodes_test/3,
payload_test/3,
plain_options_test/3,
plain_verify_options_test/3,
Expand Down Expand Up @@ -100,6 +102,7 @@ start_ssl_node_name(Name, Args) ->
%%--------------------------------------------------------------------
all() ->
[basic,
monitor_nodes,
payload,
dist_port_overload,
plain_options,
Expand Down Expand Up @@ -170,6 +173,11 @@ basic() ->
basic(Config) when is_list(Config) ->
gen_dist_test(basic_test, Config).

%%--------------------------------------------------------------------
%% Test net_kernel:monitor_nodes with nodedown_reason (OTP-17838)
monitor_nodes(Config) when is_list(Config) ->
gen_dist_test(monitor_nodes_test, Config).

%%--------------------------------------------------------------------
payload() ->
[{doc,"Test that send a lot of data between the ssl distributed nodes"}].
Expand Down Expand Up @@ -530,6 +538,41 @@ basic_test(NH1, NH2, _) ->
end)
end.

monitor_nodes_test(NH1, NH2, _) ->
Node2 = NH2#node_handle.nodename,

Ref = make_ref(),
MonitorNodesFun =
fun() ->
tstsrvr_format("Hi from ~p!~n", [node()]),
ok = net_kernel:monitor_nodes(true, [nodedown_reason]),
send_to_tstcntrl({self(), ready, Ref}),
NodeUp = receive_any(),
send_to_tstcntrl({self(), got, NodeUp}),
NodeDown = receive_any(),
send_to_tstcntrl({self(), got, NodeDown}),
ok = net_kernel:monitor_nodes(false, [nodedown_reason])
end,
spawn_link(fun () ->
ok = apply_on_ssl_node(NH1, MonitorNodesFun)
end),
{SslPid, ready, Ref} = receive_any(),

%% Setup connection and expect 'nodeup'
pong = apply_on_ssl_node(NH1, fun () -> net_adm:ping(Node2) end),
{SslPid, got, {nodeup, Node2, []}} = receive_any(),

%% Disconnect and expect 'nodedown' with correct reason
true = apply_on_ssl_node(NH1, fun () ->
net_kernel:disconnect(Node2)
end),
{SslPid, got, {nodedown, Node2, [{nodedown_reason, disconnect}]}} = receive_any(),
ok.


receive_any() ->
receive M -> M end.

payload_test(NH1, NH2, _) ->
Node1 = NH1#node_handle.nodename,
Node2 = NH2#node_handle.nodename,
Expand Down

0 comments on commit 0441e42

Please sign in to comment.