File 1637-erts-Fix-process_info-Pid-message_queue_len-on-other.patch of Package erlang
From 90de933f617ae6da4b6d3e7799345b333eae631a Mon Sep 17 00:00:00 2001
From: Rickard Green <rickard@erlang.org>
Date: Tue, 5 Jul 2022 16:23:43 +0200
Subject: [PATCH] [erts] Fix process_info(Pid, message_queue_len) on other
process
---
erts/emulator/beam/erl_bif_info.c | 3 +-
erts/emulator/test/process_SUITE.erl | 65 ++++++++++++++++++++++++++++
2 files changed, 67 insertions(+), 1 deletion(-)
diff --git a/erts/emulator/beam/erl_bif_info.c b/erts/emulator/beam/erl_bif_info.c
index 5789fa8e71..25193f4959 100644
--- a/erts/emulator/beam/erl_bif_info.c
+++ b/erts/emulator/beam/erl_bif_info.c
@@ -1179,7 +1179,7 @@ process_info_bif(Process *c_p, Eterm pid, Eterm opt, int always_wrap, int pi2)
ASSERT(locks & ERTS_PROC_LOCK_MAIN);
erts_proc_lock(rp, ERTS_PROC_LOCK_MSGQ);
erts_proc_sig_fetch(rp);
- if (c_p->sig_qs.cont) {
+ if (rp->sig_qs.cont) {
erts_proc_unlock(rp, locks|ERTS_PROC_LOCK_MSGQ);
locks = 0;
goto send_signal;
@@ -1463,6 +1463,7 @@ process_info_aux(Process *c_p,
case ERTS_PI_IX_MESSAGE_QUEUE_LEN: {
Sint len = rp->sig_qs.len;
ASSERT(flags & ERTS_PI_FLAG_NEED_MSGQ_LEN);
+ ASSERT(!rp->sig_qs.cont);
ASSERT(len >= 0);
if (len <= MAX_SMALL)
res = make_small(len);
diff --git a/erts/emulator/test/process_SUITE.erl b/erts/emulator/test/process_SUITE.erl
index 585c5a1871..7920931b4d 100644
--- a/erts/emulator/test/process_SUITE.erl
+++ b/erts/emulator/test/process_SUITE.erl
@@ -37,6 +37,7 @@
t_exit_2_catch/1, trap_exit_badarg/1, trap_exit_badarg_in_bif/1,
exit_and_timeout/1, exit_twice/1,
t_process_info/1, process_info_other/1, process_info_other_msg/1,
+ process_info_other_message_queue_len_signal_race/1,
process_info_other_dist_msg/1,
process_info_other_status/1,
process_info_2_list/1, process_info_lock_reschedule/1,
@@ -80,6 +81,7 @@ all() ->
process_info_lock_reschedule,
process_info_lock_reschedule2,
process_info_lock_reschedule3,
+ process_info_other_message_queue_len_signal_race,
process_info_garbage_collection,
process_info_smoke_all,
process_info_status_handled_signal,
@@ -597,6 +599,69 @@ process_info_other_msg(Config) when is_list(Config) ->
Pid ! stop,
ok.
+process_info_other_message_queue_len_signal_race(Config) when is_list(Config) ->
+ %% OTP-18169
+ %%
+ %% The race window triggering this bug is quite small. This test
+ %% wont fail even with the bug present, but it may trigger an
+ %% assertion in the debug compiled emulator if the bug is
+ %% present...
+ process_flag(priority, high),
+ SSchdlr = case erlang:system_info(schedulers_online) of
+ 1 -> 1;
+ _ -> 2
+ end,
+ Flush = fun Flush () ->
+ receive _ -> Flush()
+ after 0 -> ok
+ end
+ end,
+ RFun = fun RFun () ->
+ receive
+ {flush, From} ->
+ Flush(),
+ From ! flushed
+ end,
+ RFun()
+ end,
+ R = spawn_opt(RFun, [link,
+ {scheduler, 1},
+ {message_queue_data, on_heap}]),
+ SFun = fun SFun () ->
+ receive go -> ok end,
+ M = erlang:monitor(process, R),
+ R ! hi,
+ receive
+ {demonitor, From} ->
+ _ = erlang:demonitor(M),
+ From ! demonitored
+ end,
+ SFun()
+ end,
+ S = spawn_opt(SFun, [link,
+ {scheduler, SSchdlr},
+ {priority, high}]),
+ process_info_other_message_queue_len_signal_race_test(10000, S, R),
+ unlink(R),
+ exit(R, kill),
+ unlink(S),
+ exit(S, kill),
+ false = is_process_alive(R),
+ false = is_process_alive(S),
+ ok.
+
+process_info_other_message_queue_len_signal_race_test(0, _S, _R) ->
+ ok;
+process_info_other_message_queue_len_signal_race_test(N, S, R) ->
+ S ! go,
+ erlang:yield(),
+ _ = process_info(R, message_queue_len),
+ S ! {demonitor, self()},
+ receive demonitored -> ok end,
+ R ! {flush, self()},
+ receive flushed -> ok end,
+ process_info_other_message_queue_len_signal_race_test(N-1, S, R).
+
process_info_other_dist_msg(Config) when is_list(Config) ->
%%
%% Check that process_info can handle messages that have not been
--
2.35.3