Skip to content

Commit 330b119

Browse files
committed
[erts] ensure no mix of external and internal identifiers
Silently reject proposed creation and select another one when a node goes alive if there are external identifiers in the system with the proposed creation and the same node name that are to be used. Such identifiers would not work as expected in various situations, and are not from the instance of the node that are about to go alive.
1 parent 3002f55 commit 330b119

File tree

4 files changed

+154
-2
lines changed

4 files changed

+154
-2
lines changed

erts/emulator/beam/dist.c

Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -4636,6 +4636,19 @@ BIF_RETTYPE setnode_2(BIF_ALIST_2)
46364636
success = (!ERTS_PROC_IS_EXITING(net_kernel)
46374637
& !ERTS_PROC_GET_DIST_ENTRY(net_kernel));
46384638
if (success) {
4639+
/*
4640+
* Ensure we don't use a nodename-creation pair with
4641+
* external identifiers existing in the system.
4642+
*/
4643+
while (!0) {
4644+
ErlNode *nep;
4645+
if (creation < 4)
4646+
creation = 4;
4647+
nep = erts_find_node(BIF_ARG_1, creation);
4648+
if (!nep || erts_node_refc(nep) == 0)
4649+
break;
4650+
creation++;
4651+
}
46394652
inc_no_nodes();
46404653
erts_set_this_node(BIF_ARG_1, (Uint32) creation);
46414654
erts_this_dist_entry->creation = creation;

erts/emulator/beam/erl_node_tables.c

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -881,6 +881,18 @@ erts_node_table_info(fmtfn_t to, void *to_arg)
881881
erts_rwmtx_runlock(&erts_node_table_rwmtx);
882882
}
883883

884+
ErlNode *erts_find_node(Eterm sysname, Uint32 creation)
885+
{
886+
ErlNode *res;
887+
ErlNode ne;
888+
ne.sysname = sysname;
889+
ne.creation = creation;
890+
891+
erts_rwmtx_rlock(&erts_node_table_rwmtx);
892+
res = hash_get(&erts_node_table, (void *) &ne);
893+
erts_rwmtx_runlock(&erts_node_table_rwmtx);
894+
return res;
895+
}
884896

885897
ErlNode *erts_find_or_insert_node(Eterm sysname, Uint32 creation, Eterm book)
886898
{

erts/emulator/beam/erl_node_tables.h

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -258,6 +258,7 @@ void erts_set_dist_entry_not_connected(DistEntry *);
258258
void erts_set_dist_entry_pending(DistEntry *);
259259
void erts_set_dist_entry_connected(DistEntry *, Eterm, Uint64);
260260
ErlNode *erts_find_or_insert_node(Eterm, Uint32, Eterm);
261+
ErlNode *erts_find_node(Eterm, Uint32);
261262
void erts_schedule_delete_node(ErlNode *);
262263
void erts_set_this_node(Eterm, Uint32);
263264
Uint erts_node_table_size(void);
@@ -285,6 +286,7 @@ ERTS_GLB_INLINE void erts_deref_node_entry__(ErlNode *np, Eterm term, char *file
285286
ERTS_GLB_INLINE erts_aint_t erts_ref_node_entry(ErlNode *np, int min_val, Eterm term);
286287
ERTS_GLB_INLINE void erts_deref_node_entry(ErlNode *np, Eterm term);
287288
#endif
289+
ERTS_GLB_INLINE erts_aint_t erts_node_refc(ErlNode *np);
288290
ERTS_GLB_INLINE void erts_de_rlock(DistEntry *dep);
289291
ERTS_GLB_INLINE void erts_de_runlock(DistEntry *dep);
290292
ERTS_GLB_INLINE void erts_de_rwlock(DistEntry *dep);
@@ -335,6 +337,12 @@ erts_deref_node_entry(ErlNode *np, Eterm term)
335337
erts_schedule_delete_node(np);
336338
}
337339

340+
ERTS_GLB_INLINE erts_aint_t
341+
erts_node_refc(ErlNode *np)
342+
{
343+
return erts_refc_read(&np->refc, 0);
344+
}
345+
338346
#endif
339347

340348
ERTS_GLB_INLINE void

erts/emulator/test/distribution_SUITE.erl

Lines changed: 121 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -75,7 +75,9 @@
7575
system_limit/1,
7676
hopefull_data_encoding/1,
7777
hopefull_export_fun_bug/1,
78-
huge_iovec/1]).
78+
huge_iovec/1,
79+
creation_selection/1,
80+
creation_selection_test/1]).
7981

8082
%% Internal exports.
8183
-export([sender/3, receiver2/2, dummy_waiter/0, dead_process/0,
@@ -106,7 +108,7 @@ all() ->
106108
{group, bad_dist}, {group, bad_dist_ext},
107109
start_epmd_false, epmd_module, system_limit,
108110
hopefull_data_encoding, hopefull_export_fun_bug,
109-
huge_iovec].
111+
huge_iovec, creation_selection].
110112

111113
groups() ->
112114
[{bulk_send, [], [bulk_send_small, bulk_send_big, bulk_send_bigbig]},
@@ -2810,9 +2812,126 @@ mk_rand_bin(0, Data) ->
28102812
mk_rand_bin(N, Data) ->
28112813
mk_rand_bin(N-1, [rand:uniform(256) - 1 | Data]).
28122814

2815+
creation_selection(Config) when is_list(Config) ->
2816+
register(creation_selection_test_supervisor, self()),
2817+
Name = atom_to_list(?FUNCTION_NAME) ++ "-"
2818+
++ integer_to_list(erlang:system_time()),
2819+
Host = hostname(),
2820+
Cmd = lists:append(
2821+
[ct:get_progname(),
2822+
" -noshell",
2823+
" -setcookie ", atom_to_list(erlang:get_cookie()),
2824+
" -pa ", filename:dirname(code:which(?MODULE)),
2825+
" -s ", atom_to_list(?MODULE), " ",
2826+
" creation_selection_test ", atom_to_list(node()), " ",
2827+
atom_to_list(net_kernel:longnames()), " ", Name, " ", Host]),
2828+
ct:pal("Node command: ~p~n", [Cmd]),
2829+
Port = open_port({spawn, Cmd}, [exit_status]),
2830+
Node = list_to_atom(lists:append([Name, "@", Host])),
2831+
ok = receive_creation_selection_info(Port, Node).
2832+
2833+
receive_creation_selection_info(Port, Node) ->
2834+
receive
2835+
{creation_selection_test, Node, Creations, InvalidCreation,
2836+
ClashResolvedCreation} = Msg ->
2837+
ct:log("Test result: ~p~n", [Msg]),
2838+
%% Verify that creation values are created as expected. The
2839+
%% list of creations is in reverse start order...
2840+
MaxC = (1 bsl 32) - 1,
2841+
MinC = 4,
2842+
StartOrderCreations = lists:reverse(Creations),
2843+
InvalidCreation = lists:foldl(fun (C, C) when is_integer(C),
2844+
MinC =< C,
2845+
C =< MaxC ->
2846+
%% Return next expected
2847+
%% creation...
2848+
if C == MaxC -> MinC;
2849+
true -> C+1
2850+
end
2851+
end,
2852+
hd(StartOrderCreations),
2853+
StartOrderCreations),
2854+
false = lists:member(ClashResolvedCreation, [InvalidCreation
2855+
| Creations]),
2856+
receive
2857+
{Port, {exit_status, 0}} ->
2858+
Port ! {self(), close},
2859+
ok;
2860+
{Port, {exit_status, EStat}} ->
2861+
ct:fail({"node exited abnormally: ", EStat})
2862+
end;
2863+
{Port, {exit_status, EStat}} ->
2864+
ct:fail({"node prematurely exited: ", EStat});
2865+
{Port, {data, Data}} ->
2866+
ct:log("~ts", [Data]),
2867+
receive_creation_selection_info(Port, Node)
2868+
end,
2869+
ok.
2870+
2871+
creation_selection_test([TestSupNode, LongNames, Name, Host]) ->
2872+
try
2873+
StartArgs = [Name,
2874+
case LongNames of
2875+
true -> longnames;
2876+
false -> shortnames
2877+
end],
2878+
Node = list_to_atom(lists:append([atom_to_list(Name),
2879+
"@", atom_to_list(Host)])),
2880+
GoDistributed = fun (F) ->
2881+
{ok, _} = net_kernel:start(StartArgs),
2882+
Node = node(),
2883+
Creation = erlang:system_info(creation),
2884+
_ = F(Creation),
2885+
net_kernel:stop(),
2886+
Creation
2887+
end,
2888+
%% We start multiple times to verify that the creation values
2889+
%% we get from epmd are delivered in sequence. This is a
2890+
%% must for the test case such as it is written now, but can be
2891+
%% changed. If changed, this test case must be updated...
2892+
{Creations,
2893+
LastCreation} = lists:foldl(fun (_, {Cs, _LC}) ->
2894+
CFun = fun (X) -> X end,
2895+
C = GoDistributed(CFun),
2896+
{[C|Cs], C}
2897+
end, {[], 0}, lists:seq(1, 5)),
2898+
%% We create a pid with the creation that epmd will offer us the next
2899+
%% time we start the distribution and then start the distribution
2900+
%% once more. The node should avoid this creation, since this would
2901+
%% cause external identifiers in the system with same
2902+
%% nodename/creation pair as used by the local node, which in turn
2903+
%% would cause these identifers not to work as expected. That is, the
2904+
%% node should silently reject this creation and chose another one when
2905+
%% starting the distribution.
2906+
InvalidCreation = LastCreation+1,
2907+
Pid = erts_test_utils:mk_ext_pid({Node, InvalidCreation}, 4711, 0),
2908+
true = erts_debug:size(Pid) > 0, %% External pid
2909+
ResultFun = fun (ClashResolvedCreation) ->
2910+
pong = net_adm:ping(TestSupNode),
2911+
Msg = {creation_selection_test, node(), Creations,
2912+
InvalidCreation, ClashResolvedCreation},
2913+
{creation_selection_test_supervisor, TestSupNode}
2914+
! Msg,
2915+
%% Wait a bit so the message have time to get
2916+
%% through before we take down the distribution...
2917+
receive after 500 -> ok end
2918+
end,
2919+
_ = GoDistributed(ResultFun),
2920+
%% Ensure Pid is not garbage collected before starting the
2921+
%% distribution...
2922+
_ = id(Pid),
2923+
erlang:halt(0)
2924+
catch
2925+
Class:Reason:StackTrace ->
2926+
erlang:display({Class, Reason, StackTrace}),
2927+
erlang:halt(17)
2928+
end.
28132929

28142930
%%% Utilities
28152931

2932+
id(X) ->
2933+
X.
2934+
28162935
timestamp() ->
28172936
erlang:monotonic_time(millisecond).
28182937

0 commit comments

Comments
 (0)