Skip to content

Commit 5612d3d

Browse files
author
Erlang/OTP
committed
Merge branch 'rickard/creation-fix/25.3.1/OTP-18570' into maint-25
* rickard/creation-fix/25.3.1/OTP-18570: [erts] ensure no mix of external and internal identifiers
2 parents c487c0e + f8c3c6f commit 5612d3d

File tree

4 files changed

+155
-5
lines changed

4 files changed

+155
-5
lines changed

erts/emulator/beam/dist.c

Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -4906,6 +4906,19 @@ BIF_RETTYPE setnode_2(BIF_ALIST_2)
49064906
success = (!ERTS_PROC_IS_EXITING(net_kernel)
49074907
& !ERTS_PROC_GET_DIST_ENTRY(net_kernel));
49084908
if (success) {
4909+
/*
4910+
* Ensure we don't use a nodename-creation pair with
4911+
* external identifiers existing in the system.
4912+
*/
4913+
while (!0) {
4914+
ErlNode *nep;
4915+
if (creation < 4)
4916+
creation = 4;
4917+
nep = erts_find_node(BIF_ARG_1, creation);
4918+
if (!nep || erts_node_refc(nep) == 0)
4919+
break;
4920+
creation++;
4921+
}
49094922
inc_no_nodes();
49104923
erts_set_this_node(BIF_ARG_1, (Uint32) creation);
49114924
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
@@ -885,6 +885,18 @@ erts_node_table_info(fmtfn_t to, void *to_arg)
885885
erts_rwmtx_runlock(&erts_node_table_rwmtx);
886886
}
887887

888+
ErlNode *erts_find_node(Eterm sysname, Uint32 creation)
889+
{
890+
ErlNode *res;
891+
ErlNode ne;
892+
ne.sysname = sysname;
893+
ne.creation = creation;
894+
895+
erts_rwmtx_rlock(&erts_node_table_rwmtx);
896+
res = hash_get(&erts_node_table, (void *) &ne);
897+
erts_rwmtx_runlock(&erts_node_table_rwmtx);
898+
return res;
899+
}
888900

889901
ErlNode *erts_find_or_insert_node(Eterm sysname, Uint32 creation, Eterm book)
890902
{

erts/emulator/beam/erl_node_tables.h

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -255,6 +255,7 @@ void erts_set_dist_entry_not_connected(DistEntry *);
255255
void erts_set_dist_entry_pending(DistEntry *);
256256
void erts_set_dist_entry_connected(DistEntry *, Eterm, Uint64);
257257
ErlNode *erts_find_or_insert_node(Eterm, Uint32, Eterm);
258+
ErlNode *erts_find_node(Eterm, Uint32);
258259
void erts_schedule_delete_node(ErlNode *);
259260
void erts_set_this_node(Eterm, Uint32);
260261
Uint erts_node_table_size(void);
@@ -282,6 +283,7 @@ ERTS_GLB_INLINE void erts_deref_node_entry__(ErlNode *np, Eterm term, char *file
282283
ERTS_GLB_INLINE erts_aint_t erts_ref_node_entry(ErlNode *np, int min_val, Eterm term);
283284
ERTS_GLB_INLINE void erts_deref_node_entry(ErlNode *np, Eterm term);
284285
#endif
286+
ERTS_GLB_INLINE erts_aint_t erts_node_refc(ErlNode *np);
285287
ERTS_GLB_INLINE void erts_de_rlock(DistEntry *dep);
286288
ERTS_GLB_INLINE void erts_de_runlock(DistEntry *dep);
287289
ERTS_GLB_INLINE void erts_de_rwlock(DistEntry *dep);
@@ -332,6 +334,12 @@ erts_deref_node_entry(ErlNode *np, Eterm term)
332334
erts_schedule_delete_node(np);
333335
}
334336

337+
ERTS_GLB_INLINE erts_aint_t
338+
erts_node_refc(ErlNode *np)
339+
{
340+
return erts_refc_read(&np->refc, 0);
341+
}
342+
335343
#endif
336344

337345
ERTS_GLB_INLINE void

erts/emulator/test/distribution_SUITE.erl

Lines changed: 122 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -84,7 +84,9 @@
8484
dyn_node_name_monitor/1,
8585
async_dist_flag/1,
8686
async_dist_port_dctrlr/1,
87-
async_dist_proc_dctrlr/1]).
87+
async_dist_proc_dctrlr/1,
88+
creation_selection/1,
89+
creation_selection_test/1]).
8890

8991
%% Internal exports.
9092
-export([sender/3, receiver2/2, dummy_waiter/0, dead_process/0,
@@ -118,7 +120,7 @@ all() ->
118120
start_epmd_false, no_epmd, epmd_module, system_limit,
119121
hopefull_data_encoding, hopefull_export_fun_bug,
120122
huge_iovec, is_alive, dyn_node_name_monitor_node, dyn_node_name_monitor,
121-
{group, async_dist}].
123+
{group, async_dist}, creation_selection].
122124

123125
groups() ->
124126
[{bulk_send, [], [bulk_send_small, bulk_send_big, bulk_send_bigbig]},
@@ -520,9 +522,6 @@ nodes2(Config) when is_list(Config) ->
520522
end,
521523
ok.
522524

523-
id(X) ->
524-
X.
525-
526525
%% Test optimistic distribution flags toward pending connections (DFLAG_DIST_HOPEFULLY)
527526
optimistic_dflags(Config) when is_list(Config) ->
528527
{ok, PeerSender, _Sender} = ?CT_PEER(#{connection => 0, args => ["-setcookie", "NONE"]}),
@@ -3594,8 +3593,126 @@ async_dist_test(Node) ->
35943593

35953594
ok.
35963595

3596+
creation_selection(Config) when is_list(Config) ->
3597+
register(creation_selection_test_supervisor, self()),
3598+
Name = atom_to_list(?FUNCTION_NAME) ++ "-"
3599+
++ integer_to_list(erlang:system_time()),
3600+
Host = hostname(),
3601+
Cmd = lists:append(
3602+
[ct:get_progname(),
3603+
" -noshell",
3604+
" -setcookie ", atom_to_list(erlang:get_cookie()),
3605+
" -pa ", filename:dirname(code:which(?MODULE)),
3606+
" -s ", atom_to_list(?MODULE), " ",
3607+
" creation_selection_test ", atom_to_list(node()), " ",
3608+
atom_to_list(net_kernel:longnames()), " ", Name, " ", Host]),
3609+
ct:pal("Node command: ~p~n", [Cmd]),
3610+
Port = open_port({spawn, Cmd}, [exit_status]),
3611+
Node = list_to_atom(lists:append([Name, "@", Host])),
3612+
ok = receive_creation_selection_info(Port, Node).
3613+
3614+
receive_creation_selection_info(Port, Node) ->
3615+
receive
3616+
{creation_selection_test, Node, Creations, InvalidCreation,
3617+
ClashResolvedCreation} = Msg ->
3618+
ct:log("Test result: ~p~n", [Msg]),
3619+
%% Verify that creation values are created as expected. The
3620+
%% list of creations is in reverse start order...
3621+
MaxC = (1 bsl 32) - 1,
3622+
MinC = 4,
3623+
StartOrderCreations = lists:reverse(Creations),
3624+
InvalidCreation = lists:foldl(fun (C, C) when is_integer(C),
3625+
MinC =< C,
3626+
C =< MaxC ->
3627+
%% Return next expected
3628+
%% creation...
3629+
if C == MaxC -> MinC;
3630+
true -> C+1
3631+
end
3632+
end,
3633+
hd(StartOrderCreations),
3634+
StartOrderCreations),
3635+
false = lists:member(ClashResolvedCreation, [InvalidCreation
3636+
| Creations]),
3637+
receive
3638+
{Port, {exit_status, 0}} ->
3639+
Port ! {self(), close},
3640+
ok;
3641+
{Port, {exit_status, EStat}} ->
3642+
ct:fail({"node exited abnormally: ", EStat})
3643+
end;
3644+
{Port, {exit_status, EStat}} ->
3645+
ct:fail({"node prematurely exited: ", EStat});
3646+
{Port, {data, Data}} ->
3647+
ct:log("~ts", [Data]),
3648+
receive_creation_selection_info(Port, Node)
3649+
end,
3650+
ok.
3651+
3652+
creation_selection_test([TestSupNode, LongNames, Name, Host]) ->
3653+
try
3654+
StartArgs = [Name,
3655+
case LongNames of
3656+
true -> longnames;
3657+
false -> shortnames
3658+
end],
3659+
Node = list_to_atom(lists:append([atom_to_list(Name),
3660+
"@", atom_to_list(Host)])),
3661+
GoDistributed = fun (F) ->
3662+
{ok, _} = net_kernel:start(StartArgs),
3663+
Node = node(),
3664+
Creation = erlang:system_info(creation),
3665+
_ = F(Creation),
3666+
net_kernel:stop(),
3667+
Creation
3668+
end,
3669+
%% We start multiple times to verify that the creation values
3670+
%% we get from epmd are delivered in sequence. This is a
3671+
%% must for the test case such as it is written now, but can be
3672+
%% changed. If changed, this test case must be updated...
3673+
{Creations,
3674+
LastCreation} = lists:foldl(fun (_, {Cs, _LC}) ->
3675+
CFun = fun (X) -> X end,
3676+
C = GoDistributed(CFun),
3677+
{[C|Cs], C}
3678+
end, {[], 0}, lists:seq(1, 5)),
3679+
%% We create a pid with the creation that epmd will offer us the next
3680+
%% time we start the distribution and then start the distribution
3681+
%% once more. The node should avoid this creation, since this would
3682+
%% cause external identifiers in the system with same
3683+
%% nodename/creation pair as used by the local node, which in turn
3684+
%% would cause these identifers not to work as expected. That is, the
3685+
%% node should silently reject this creation and chose another one when
3686+
%% starting the distribution.
3687+
InvalidCreation = LastCreation+1,
3688+
Pid = erts_test_utils:mk_ext_pid({Node, InvalidCreation}, 4711, 0),
3689+
true = erts_debug:size(Pid) > 0, %% External pid
3690+
ResultFun = fun (ClashResolvedCreation) ->
3691+
pong = net_adm:ping(TestSupNode),
3692+
Msg = {creation_selection_test, node(), Creations,
3693+
InvalidCreation, ClashResolvedCreation},
3694+
{creation_selection_test_supervisor, TestSupNode}
3695+
! Msg,
3696+
%% Wait a bit so the message have time to get
3697+
%% through before we take down the distribution...
3698+
receive after 500 -> ok end
3699+
end,
3700+
_ = GoDistributed(ResultFun),
3701+
%% Ensure Pid is not garbage collected before starting the
3702+
%% distribution...
3703+
_ = id(Pid),
3704+
erlang:halt(0)
3705+
catch
3706+
Class:Reason:StackTrace ->
3707+
erlang:display({Class, Reason, StackTrace}),
3708+
erlang:halt(17)
3709+
end.
3710+
35973711
%%% Utilities
35983712

3713+
id(X) ->
3714+
X.
3715+
35993716
wait_until(Fun) ->
36003717
wait_until(Fun, 24*60*60*1000).
36013718

0 commit comments

Comments
 (0)