File 2617-pg-fix-doubling-for-local-processes-with-dynamic-dis.patch of Package erlang

From 653b1773e655a77b664d3db0541ca3ac09b69e8c Mon Sep 17 00:00:00 2001
From: Maxim Fedorov <dane@whatsapp.com>
Date: Wed, 2 Sep 2020 17:59:57 -0700
Subject: [PATCH] pg: fix doubling for local processes with dynamic
 distribution

When distribution is started dynamically (via net_kernel:start/1),
pg incorrectly forms an overlay network with local node. Then,
every local process is counted twice (once as local, once as
remote).
This commit also contains tests for the case above, and test
case for local process check.
---
 lib/kernel/src/pg.erl        |  2 ++
 lib/kernel/test/pg_SUITE.erl | 42 ++++++++++++++++++++++++++++++++++--
 2 files changed, 42 insertions(+), 2 deletions(-)

diff --git a/lib/kernel/src/pg.erl b/lib/kernel/src/pg.erl
index 7d733f4493..580759a9bf 100644
--- a/lib/kernel/src/pg.erl
+++ b/lib/kernel/src/pg.erl
@@ -342,6 +342,8 @@ handle_info({nodedown, _Node}, State) ->
     {noreply, State};
 
 %% nodeup: discover if remote node participates in the overlay network
+handle_info({nodeup, Node}, State) when Node =:= node() ->
+    {noreply, State};
 handle_info({nodeup, Node}, #state{scope = Scope} = State) ->
     {Scope, Node} ! {discover, self()},
     {noreply, State};
diff --git a/lib/kernel/test/pg_SUITE.erl b/lib/kernel/test/pg_SUITE.erl
index 8a670e0823..725169cda5 100644
--- a/lib/kernel/test/pg_SUITE.erl
+++ b/lib/kernel/test/pg_SUITE.erl
@@ -38,6 +38,8 @@
     pg/0, pg/1,
     errors/0, errors/1,
     leave_exit_race/0, leave_exit_race/1,
+    dyn_distribution/0, dyn_distribution/1,
+    process_owner_check/0, process_owner_check/1,
     overlay_missing/0, overlay_missing/1,
     single/0, single/1,
     two/1,
@@ -92,13 +94,13 @@ end_per_testcase(TestCase, _Config) ->
     ok.
 
 all() ->
-    [{group, basic}, {group, cluster}, {group, performance}].
+    [dyn_distribution, {group, basic}, {group, cluster}, {group, performance}].
 
 groups() ->
     [
         {basic, [parallel], [errors, pg, leave_exit_race, single, overlay_missing]},
         {performance, [sequential], [thundering_herd]},
-        {cluster, [parallel], [two, initial, netsplit, trisplit, foursplit,
+        {cluster, [parallel], [process_owner_check, two, initial, netsplit, trisplit, foursplit,
             exchange, nolocal, double, scope_restart, missing_scope_join,
             disconnected_start, forced_sync, group_leave]}
     ].
@@ -172,6 +174,42 @@ single(Config) when is_list(Config) ->
     ?assertEqual(ok, pg:leave(?FUNCTION_NAME, ?FUNCTION_NAME, self())),
     ok.
 
+dyn_distribution() ->
+    [{doc, "Tests that local node when distribution is started dynamically is not treated as remote node"}].
+
+dyn_distribution(Config) when is_list(Config) ->
+    %% When distribution is started or stopped dynamically,
+    %%  there is a nodeup/nodedown message delivered to pg
+    %% It is possible but non-trivial to simulate this
+    %%  behaviour with starting slave nodes being not
+    %%  distributed, and calling net_kernel:start/1, however
+    %%  the effect is still the same as simply sending nodeup,
+    %%  which is also documented.
+    ?FUNCTION_NAME ! {nodeup, node()},
+    %%
+    ?assertEqual(ok, pg:join(?FUNCTION_NAME, ?FUNCTION_NAME, self())),
+    ?assertEqual([self()], pg:get_members(?FUNCTION_NAME, ?FUNCTION_NAME)),
+    ok.
+
+process_owner_check() ->
+    [{doc, "Tests that process owner is local node"}].
+
+process_owner_check(Config) when is_list(Config) ->
+    {TwoPeer, Socket} = spawn_node(?FUNCTION_NAME, ?FUNCTION_NAME),
+    %% spawn remote process
+    LocalPid = erlang:spawn(forever()),
+    RemotePid = erlang:spawn(TwoPeer, forever()),
+    %% check they can't be joined locally
+    ?assertException(error, {nolocal, _}, pg:join(?FUNCTION_NAME, ?FUNCTION_NAME, RemotePid)),
+    ?assertException(error, {nolocal, _}, pg:join(?FUNCTION_NAME, ?FUNCTION_NAME, [RemotePid, RemotePid])),
+    ?assertException(error, {nolocal, _}, pg:join(?FUNCTION_NAME, ?FUNCTION_NAME, [LocalPid, RemotePid])),
+    %% check that non-pid also triggers error
+    ?assertException(error, function_clause, pg:join(?FUNCTION_NAME, ?FUNCTION_NAME, undefined)),
+    ?assertException(error, {nolocal, _}, pg:join(?FUNCTION_NAME, ?FUNCTION_NAME, [undefined])),
+    %% stop the peer
+    stop_node(TwoPeer, Socket),
+    ok.
+
 overlay_missing() ->
     [{doc, "Tests that scope process that is not a part of overlay network does not change state"}].
 
-- 
2.26.2

openSUSE Build Service is sponsored by