File 1412-Fix-process_info-_-status-from-other-process-with-ot.patch of Package erlang
From 23149c55ed29cd00c260b21c1c74adc33e1b6918 Mon Sep 17 00:00:00 2001
From: Rickard Green <rickard@erlang.org>
Date: Thu, 9 Sep 2021 23:39:37 +0200
Subject: [PATCH] Fix process_info(_, status) from other process with other
prio
---
erts/emulator/beam/erl_bif_info.c | 23 +++++++-----
erts/emulator/beam/erl_process.c | 52 ++++++++++++++++++++++++++++
erts/emulator/beam/erl_process.h | 1 +
erts/emulator/test/process_SUITE.erl | 22 ++++++++++--
4 files changed, 87 insertions(+), 11 deletions(-)
diff --git a/erts/emulator/beam/erl_bif_info.c b/erts/emulator/beam/erl_bif_info.c
index 96f399fbbe..04d625305b 100644
--- a/erts/emulator/beam/erl_bif_info.c
+++ b/erts/emulator/beam/erl_bif_info.c
@@ -1394,17 +1394,22 @@ process_info_aux(Process *c_p,
if (res == am_running && (state & ERTS_PSFLG_RUNNING_SYS)) {
ASSERT(c_p == rp);
ASSERT(flags & ERTS_PI_FLAG_REQUEST_FOR_OTHER);
- if (!(state & (ERTS_PSFLG_SYS_TASKS
- | ERTS_PSFLG_ACTIVE
+ if (!(state & (ERTS_PSFLG_ACTIVE
| ERTS_PSFLG_SIG_Q
| ERTS_PSFLG_SIG_IN_Q))) {
- /*
- * We are servicing a process-info request from
- * another process. If that other process could
- * have inspected our state itself, we would have
- * been in the 'waiting' state.
- */
- res = am_waiting;
+ int sys_tasks = 0;
+ if (state & ERTS_PSFLG_SYS_TASKS)
+ sys_tasks = erts_have_non_prio_elev_sys_tasks(rp,
+ rp_locks);
+ if (!sys_tasks) {
+ /*
+ * We are servicing a process-info request from
+ * another process. If that other process could
+ * have inspected our state itself, we would have
+ * been in the 'waiting' state.
+ */
+ res = am_waiting;
+ }
}
}
break;
diff --git a/erts/emulator/beam/erl_process.c b/erts/emulator/beam/erl_process.c
index 1f464e2e5a..01a2587e78 100644
--- a/erts/emulator/beam/erl_process.c
+++ b/erts/emulator/beam/erl_process.c
@@ -6915,6 +6915,58 @@ erts_proc_sys_schedule(Process *p, erts_aint32_t state, erts_aint32_t enable_fla
return active_sys_enqueue(p, NULL, 0, enable_flag, state, &fail_state);
}
+int
+erts_have_non_prio_elev_sys_tasks(Process *c_p, ErtsProcLocks locks)
+{
+ ErtsProcSysTaskQs *qs;
+ int res = 0;
+
+ if (!(locks & ERTS_PROC_LOCK_STATUS))
+ erts_proc_lock(c_p, ERTS_PROC_LOCK_STATUS);
+
+ qs = c_p->sys_task_qs;
+ if (qs) {
+ int qmask = qs->qmask;
+ ASSERT(qmask);
+ while (qmask) {
+ ErtsProcSysTask *st, *first_st;
+ switch (qmask & -qmask) {
+ case MAX_BIT:
+ qmask &= ~MAX_BIT;
+ st = first_st = qs->q[PRIORITY_MAX];
+ break;
+ case HIGH_BIT:
+ qmask &= ~HIGH_BIT;
+ st = first_st = qs->q[PRIORITY_HIGH];
+ break;
+ case NORMAL_BIT:
+ case LOW_BIT:
+ st = first_st = qs->q[PRIORITY_NORMAL];
+ qmask &= ~(NORMAL_BIT|LOW_BIT);
+ break;
+ default:
+ st = first_st = NULL;
+ break;
+ }
+ ASSERT(st);
+ do {
+ if (st->type != ERTS_PSTT_PRIO_SIG) {
+ res = !0;
+ goto done;
+ }
+ st = st->next;
+ } while (st != first_st);
+ }
+ }
+
+done:
+
+ if (!(locks & ERTS_PROC_LOCK_STATUS))
+ erts_proc_unlock(c_p, ERTS_PROC_LOCK_STATUS);
+
+ return res;
+}
+
static int
schedule_process_sys_task(Process *p, erts_aint32_t prio, ErtsProcSysTask *st,
erts_aint32_t *fail_state_p)
diff --git a/erts/emulator/beam/erl_process.h b/erts/emulator/beam/erl_process.h
index 43937f216c..9b50467340 100644
--- a/erts/emulator/beam/erl_process.h
+++ b/erts/emulator/beam/erl_process.h
@@ -1874,6 +1874,7 @@ ErtsSchedulerData *erts_get_scheduler_data(void);
void erts_schedule_process(Process *, erts_aint32_t, ErtsProcLocks);
erts_aint32_t erts_proc_sys_schedule(Process *p, erts_aint32_t state,
erts_aint32_t enable_flag);
+int erts_have_non_prio_elev_sys_tasks(Process *c_p, ErtsProcLocks locks);
ERTS_GLB_INLINE void erts_proc_notify_new_message(Process *p, ErtsProcLocks locks);
ERTS_GLB_INLINE void erts_schedule_dirty_sys_execution(Process *c_p);
diff --git a/erts/emulator/test/process_SUITE.erl b/erts/emulator/test/process_SUITE.erl
index 0cb0d6c1e2..c2bd151eb6 100644
--- a/erts/emulator/test/process_SUITE.erl
+++ b/erts/emulator/test/process_SUITE.erl
@@ -38,6 +38,7 @@
exit_and_timeout/1, exit_twice/1,
t_process_info/1, process_info_other/1, process_info_other_msg/1,
process_info_other_dist_msg/1,
+ process_info_other_status/1,
process_info_2_list/1, process_info_lock_reschedule/1,
process_info_lock_reschedule2/1,
process_info_lock_reschedule3/1,
@@ -78,7 +79,8 @@ all() ->
[spawn_with_binaries, t_exit_1, {group, t_exit_2},
trap_exit_badarg, trap_exit_badarg_in_bif,
t_process_info, process_info_other, process_info_other_msg,
- process_info_other_dist_msg, process_info_2_list,
+ process_info_other_dist_msg, process_info_other_status,
+ process_info_2_list,
process_info_lock_reschedule,
process_info_lock_reschedule2,
process_info_lock_reschedule3,
@@ -650,7 +652,23 @@ process_info_other_dist_msg(Config) when is_list(Config) ->
Pid ! stop,
stop_node(Node),
ok.
-
+
+process_info_other_status(Config) when is_list(Config) ->
+ %% OTP-17628: status was erroneously reported as 'running',
+ %% when it should be 'waiting', when the priority of the
+ %% caller exceeded the priority of the processes being
+ %% checked (due to prio elevation).
+ Self = self(),
+ Other = spawn_link(fun () -> other_process(Self) end),
+ receive {go_ahead, Other} -> ok end,
+ receive after 100 -> ok end,
+ {status, waiting} = process_info(Other, status),
+ process_flag(priority, high),
+ {status, waiting} = process_info(Other, status),
+ process_flag(priority, max),
+ {status, waiting} = process_info(Other, status),
+ Other ! stop,
+ ok.
other_process(Parent) ->
self() ! {my,own,message},
--
2.31.1