File 0775-erts-Test-ensuring-that-dist-spawn-init-message-orde.patch of Package erlang
From 51926794c62c348def0c06f2b2981b59ac220902 Mon Sep 17 00:00:00 2001
From: Rickard Green <rickard@erlang.org>
Date: Mon, 9 Oct 2023 18:23:38 +0200
Subject: [PATCH] [erts] Test ensuring that dist spawn init message order is
preserved
---
erts/emulator/beam/erl_process.c | 15 ++++++
erts/emulator/test/process_SUITE.erl | 73 +++++++++++++++++++++++++++-
2 files changed, 87 insertions(+), 1 deletion(-)
diff --git a/erts/emulator/beam/erl_process.c b/erts/emulator/beam/erl_process.c
index 3e6173429a..736091b163 100644
--- a/erts/emulator/beam/erl_process.c
+++ b/erts/emulator/beam/erl_process.c
@@ -12742,6 +12742,21 @@ erl_create_process(Process* parent, /* Parent of process (default group leader).
erts_queue_message(p, locks, erts_alloc_message(0, NULL),
am_dist_spawn_init, am_system);
+ /*
+ * The process was created with msgq-lock locked and no siq-inq
+ * buffers installed. The msgq-lock has not been released, so
+ * sig-inq buffers cannot have been installed yet. Since the
+ * above messages already exist in the *single* outer signal
+ * queue, no other messages can be reordered past them...
+ */
+ ASSERT(erts_atomic_read_nob(&p->sig_inq_buffers) == (erts_aint_t)NULL);
+
+ /*
+ * ... but we anyway move the messages into the message queue
+ * since we already got the msgq-lock at this point.
+ */
+ erts_proc_sig_fetch(p);
+
erts_proc_unlock(p, locks & ERTS_PROC_LOCKS_ALL_MINOR);
if (so->flags & SPO_LINK) {
diff --git a/erts/emulator/test/process_SUITE.erl b/erts/emulator/test/process_SUITE.erl
index 080b63c5f6..143e6247c1 100644
--- a/erts/emulator/test/process_SUITE.erl
+++ b/erts/emulator/test/process_SUITE.erl
@@ -92,6 +92,7 @@
spawn_old_node/1,
spawn_new_node/1,
spawn_request_reply_option/1,
+ dist_spawn_arg_list_mixup/1,
alias_bif/1,
dist_frag_alias/1,
dist_frag_unaliased/1,
@@ -151,6 +152,8 @@ groups() ->
spawn_old_node,
spawn_new_node,
spawn_request_reply_option,
+ spawn_request_reply_option,
+ dist_spawn_arg_list_mixup,
otp_6237,
{group, processes_bif},
{group, otp_7738}, garb_other_running,
@@ -3918,6 +3920,75 @@ spawn_request_reply_option_test(Peer, Node) ->
ok
end.
+dist_spawn_arg_list_mixup(Config) when is_list(Config) ->
+ %% A process newly spawned via the distribution is passed the
+ %% argument list to use as the first message followed by an intialization
+ %% message. Those two messages *must* be the first messages in its queue
+ %% when it begins execution. The parallel receive/send signal optimization
+ %% could potentially cause reordering of messages if certain future
+ %% changes are made. This test case tries to cause a situation where a
+ %% message reordering potentially could happen, and hopefully will detect
+ %% such problematic changes.
+ Tester = self(),
+ NoScheds = 8,
+ NoSchedsStr = integer_to_list(NoScheds),
+ NoSchedsList = lists:seq(1, NoScheds),
+ {ok, Peer, Node} = ?CT_PEER(["+S"++NoSchedsStr++":"++NoSchedsStr]),
+ AttackMsg = make_ref(),
+ AttackArgList = [Tester, AttackMsg],
+ OkMsg = make_ref(),
+ As = lists:map(
+ fun (_) ->
+ spawn_opt(
+ Node,
+ fun () ->
+ dist_spawn_arg_list_mixup_sender(AttackArgList,
+ 1000)
+ end, [{priority, high}, link])
+ end, NoSchedsList),
+ Relay = spawn_opt(
+ Node,
+ fun () ->
+ receive
+ {attack, Victim} ->
+ lists:foreach(fun (A) ->
+ A ! {attack, Victim}
+ end, As)
+ end
+ end, [{priority, max}, link]),
+ receive after 100 -> ok end,
+ Victim = spawn_opt(Node, erlang, send, [Tester, OkMsg],
+ [{message_queue_data, off_heap},
+ {priority, normal},
+ link]),
+ Relay ! {attack, Victim},
+ receive
+ OkMsg ->
+ ok;
+ AttackMsg ->
+ ct:fail(child_process_used_message_as_argument_list)
+ end,
+ lists:foreach(fun (P) ->
+ unlink(P)
+ end, [Victim] ++ [Relay] ++ As),
+ peer:stop(Peer),
+ ok.
+
+dist_spawn_arg_list_mixup_sender(Msg, N) ->
+ receive
+ {attack, Victim} ->
+ dist_spawn_arg_list_mixup_sender(Victim, Msg, N)
+ after
+ 0 ->
+ dist_spawn_arg_list_mixup_sender(Msg, N)
+ end.
+
+dist_spawn_arg_list_mixup_sender(_Pid, _Msg, 0) ->
+ ok;
+dist_spawn_arg_list_mixup_sender(Pid, Msg, N) ->
+ Pid ! Msg,
+ dist_spawn_arg_list_mixup_sender(Pid, Msg, N-1).
+
processes_term_proc_list(Config) when is_list(Config) ->
Tester = self(),
--
2.35.3