Skip to content

Commit 00089cf

Browse files
committed
[erts] Fix long signal delivery time for processes in dirty run queues
OTP-18841 Commit (1) changed so that signals sent to processes scheduled for dirty execution didn't trigger rescheduling of such processes to normal schedulers in order to handle signals, but instead rely on the dirty signal handler processes to take care of handling the signals for such processes. This since a steady flow of incoming signals to processes scheduled for dirty execution caused such processes to bounce between schedulers and could prevent them from making progress. The dirty signal handler processes did however not take care of the signals until the receiving processes were selected for execution. As a result of this, if a process got stuck for a long time in a dirty run queue due to heavy usage of dirty schedulers, it took a long time until signals were delivered to such processes. As of this commit, dirty signal handler processes will also take care of signal handling for processes in dirty run queues. (1) 53b1983
1 parent 16b71c7 commit 00089cf

File tree

8 files changed

+105
-68
lines changed

8 files changed

+105
-68
lines changed

erts/emulator/beam/beam_bif_load.c

Lines changed: 2 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -645,7 +645,7 @@ BIF_RETTYPE erts_internal_check_dirty_process_code_2(BIF_ALIST_2)
645645
{
646646
erts_aint32_t state;
647647
Process *rp;
648-
int dirty, busy, reds = 0;
648+
int busy, reds = 0;
649649
Eterm res;
650650

651651
if (BIF_P != erts_dirty_process_signal_handler
@@ -667,13 +667,7 @@ BIF_RETTYPE erts_internal_check_dirty_process_code_2(BIF_ALIST_2)
667667
BIF_RET(am_false);
668668

669669
state = erts_atomic32_read_nob(&rp->state);
670-
dirty = (state & ERTS_PSFLG_DIRTY_RUNNING);
671-
/*
672-
* Ignore ERTS_PSFLG_DIRTY_RUNNING_SYS (see
673-
* comment in erts_execute_dirty_system_task()
674-
* in erl_process.c).
675-
*/
676-
if (!dirty)
670+
if (!ERTS_PROC_IN_DIRTY_STATE(state))
677671
BIF_RET(am_normal);
678672

679673
busy = erts_proc_trylock(rp, ERTS_PROC_LOCK_MAIN) == EBUSY;

erts/emulator/beam/bif.c

Lines changed: 1 addition & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1703,9 +1703,7 @@ static Eterm process_flag_aux(Process *c_p, int *redsp, Eterm flag, Eterm val)
17031703
*/
17041704

17051705
state = erts_atomic32_read_nob(&c_p->state);
1706-
if (state & (ERTS_PSFLG_RUNNING_SYS
1707-
| ERTS_PSFLG_DIRTY_RUNNING_SYS
1708-
| ERTS_PSFLG_DIRTY_RUNNING)) {
1706+
if (!(state & ERTS_PSFLG_RUNNING)) {
17091707
/*
17101708
* We are either processing signals before
17111709
* being executed or executing dirty. That
@@ -1714,7 +1712,6 @@ static Eterm process_flag_aux(Process *c_p, int *redsp, Eterm flag, Eterm val)
17141712
*redsp = 1;
17151713
}
17161714
else {
1717-
ASSERT(state & ERTS_PSFLG_RUNNING);
17181715

17191716
/*
17201717
* F_DELAY_GC is currently only set when

erts/emulator/beam/erl_proc_sig_queue.c

Lines changed: 7 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -811,7 +811,7 @@ notify_dirty_signal_handler(Eterm pid,
811811
ErtsMessage *mp;
812812
Process *sig_handler;
813813

814-
ASSERT(state & ERTS_PSFLG_DIRTY_RUNNING);
814+
ASSERT(state & (ERTS_PSFLGS_DIRTY_WORK|ERTS_PSFLG_DIRTY_RUNNING));
815815

816816
if (prio < 0)
817817
prio = (int) ERTS_PSFLGS_GET_USR_PRIO(state);
@@ -851,13 +851,10 @@ delayed_notify_dirty_signal_handler(void *vdshnp)
851851
if (proc) {
852852
erts_aint32_t state = erts_atomic32_read_acqb(&proc->state);
853853
/*
854-
* Notify the dirty signal handler if it is still running
855-
* dirty and still have signals to handle...
854+
* Notify the dirty signal handler if it is still scheduled
855+
* or running dirty and still have signals to handle...
856856
*/
857-
if (!!(state & ERTS_PSFLG_DIRTY_RUNNING)
858-
& !!(state & (ERTS_PSFLG_SIG_Q
859-
| ERTS_PSFLG_NMSG_SIG_IN_Q
860-
| ERTS_PSFLG_MSG_SIG_IN_Q))) {
857+
if (ERTS_PROC_NEED_DIRTY_SIG_HANDLING(state)) {
861858
notify_dirty_signal_handler(dshnp->pid, state, dshnp->prio);
862859
}
863860
}
@@ -1141,12 +1138,7 @@ maybe_elevate_sig_handling_prio(Process *c_p, int prio, Eterm other)
11411138
if (res) {
11421139
/* ensure handled if dirty executing... */
11431140
state = erts_atomic32_read_nob(&rp->state);
1144-
/*
1145-
* We ignore ERTS_PSFLG_DIRTY_RUNNING_SYS. For
1146-
* more info see erts_execute_dirty_system_task()
1147-
* in erl_process.c.
1148-
*/
1149-
if (state & ERTS_PSFLG_DIRTY_RUNNING)
1141+
if (ERTS_PROC_NEED_DIRTY_SIG_HANDLING(state))
11501142
erts_ensure_dirty_proc_signals_handled(rp, state,
11511143
min_prio, 0);
11521144
}
@@ -8192,12 +8184,7 @@ erts_internal_dirty_process_handle_signals_1(BIF_ALIST_1)
81928184
BIF_RET(am_noproc);
81938185

81948186
state = erts_atomic32_read_acqb(&rp->state);
8195-
dirty = (state & ERTS_PSFLG_DIRTY_RUNNING);
8196-
/*
8197-
* Ignore ERTS_PSFLG_DIRTY_RUNNING_SYS (see
8198-
* comment in erts_execute_dirty_system_task()
8199-
* in erl_process.c).
8200-
*/
8187+
dirty = ERTS_PROC_IN_DIRTY_STATE(state);
82018188
if (!dirty)
82028189
BIF_RET(am_normal);
82038190

@@ -8211,7 +8198,7 @@ erts_internal_dirty_process_handle_signals_1(BIF_ALIST_1)
82118198

82128199
state = erts_atomic32_read_mb(&rp->state);
82138200
noproc = (state & ERTS_PSFLG_FREE);
8214-
dirty = (state & ERTS_PSFLG_DIRTY_RUNNING);
8201+
dirty = ERTS_PROC_NEED_DIRTY_SIG_HANDLING(state);
82158202

82168203
if (busy) {
82178204
if (noproc)

erts/emulator/beam/erl_proc_sig_queue.h

Lines changed: 4 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -1919,29 +1919,21 @@ erts_proc_notify_new_sig(Process* rp, erts_aint32_t state,
19191919
state = erts_proc_sys_schedule(rp, state, enable_flag);
19201920
}
19211921

1922-
if (state & ERTS_PSFLG_DIRTY_RUNNING) {
1923-
/*
1924-
* We ignore ERTS_PSFLG_DIRTY_RUNNING_SYS. For
1925-
* more info see erts_execute_dirty_system_task()
1926-
* in erl_process.c.
1927-
*/
1922+
if (ERTS_PROC_IN_DIRTY_STATE(state)) {
19281923
erts_ensure_dirty_proc_signals_handled(rp, state, -1, 0);
19291924
}
19301925
}
19311926

1927+
1928+
19321929
ERTS_GLB_INLINE void
19331930
erts_proc_notify_new_message(Process *p, ErtsProcLocks locks)
19341931
{
19351932
/* No barrier needed, due to msg lock */
19361933
erts_aint32_t state = erts_atomic32_read_nob(&p->state);
19371934
if (!(state & ERTS_PSFLG_ACTIVE))
19381935
erts_schedule_process(p, state, locks);
1939-
if (state & ERTS_PSFLG_DIRTY_RUNNING) {
1940-
/*
1941-
* We ignore ERTS_PSFLG_DIRTY_RUNNING_SYS. For
1942-
* more info see erts_execute_dirty_system_task()
1943-
* in erl_process.c.
1944-
*/
1936+
if (ERTS_PROC_NEED_DIRTY_SIG_HANDLING(state)) {
19451937
erts_ensure_dirty_proc_signals_handled(p, state, -1, locks);
19461938
}
19471939
}

erts/emulator/beam/erl_process.c

Lines changed: 32 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -6588,19 +6588,19 @@ select_enqueue_run_queue(int enqueue, int enq_prio, Process *p, erts_aint32_t st
65886588
* reference count on the process when done with it...
65896589
*/
65906590
static ERTS_INLINE int
6591-
schedule_out_process(ErtsRunQueue *c_rq, erts_aint32_t state, Process *p,
6591+
schedule_out_process(ErtsRunQueue *c_rq, erts_aint32_t *statep, Process *p,
65926592
Process *proxy, int is_normal_sched)
65936593
{
65946594
erts_aint32_t a, e, n, enq_prio = -1, running_flgs;
65956595
int enqueue; /* < 0 -> use proxy */
65966596
ErtsRunQueue* runq;
65976597

6598-
ASSERT(!(state & (ERTS_PSFLG_DIRTY_IO_PROC|ERTS_PSFLG_DIRTY_CPU_PROC))
6598+
a = *statep;
6599+
6600+
ASSERT(!(a & (ERTS_PSFLG_DIRTY_IO_PROC|ERTS_PSFLG_DIRTY_CPU_PROC))
65996601
|| (BeamIsOpCode(*(const BeamInstr*)p->i, op_call_nif_WWW)
66006602
|| BeamIsOpCode(*(const BeamInstr*)p->i, op_call_bif_W)));
66016603

6602-
a = state;
6603-
66046604
/* Clear activ-sys if needed... */
66056605
while (1) {
66066606
n = e = a;
@@ -6667,6 +6667,8 @@ schedule_out_process(ErtsRunQueue *c_rq, erts_aint32_t state, Process *p,
66676667
break;
66686668
}
66696669

6670+
*statep = n;
6671+
66706672
runq = select_enqueue_run_queue(enqueue, enq_prio, p, n);
66716673

66726674
if (!runq) {
@@ -7117,10 +7119,13 @@ suspend_process(Process *c_p, Process *p)
71177119
if (c_p == p) {
71187120
state = erts_atomic32_read_bor_relb(&p->state,
71197121
ERTS_PSFLG_SUSPENDED);
7120-
ASSERT(state & (ERTS_PSFLG_RUNNING
7121-
| ERTS_PSFLG_RUNNING_SYS
7122-
| ERTS_PSFLG_DIRTY_RUNNING
7123-
| ERTS_PSFLG_DIRTY_RUNNING_SYS));
7122+
ASSERT((state & (ERTS_PSFLG_RUNNING
7123+
| ERTS_PSFLG_RUNNING_SYS
7124+
| ERTS_PSFLG_DIRTY_RUNNING
7125+
| ERTS_PSFLG_DIRTY_RUNNING_SYS))
7126+
|| ((ERTS_PROC_LOCK_MAIN
7127+
& erts_proc_lc_my_proc_locks(p))
7128+
&& (c_p->sig_qs.flags | FS_HANDLING_SIGS)));
71247129
suspended = (state & ERTS_PSFLG_SUSPENDED) ? -1: 1;
71257130
}
71267131
else {
@@ -9218,8 +9223,13 @@ void
92189223
erts_suspend(Process* c_p, ErtsProcLocks c_p_locks, Port *busy_port)
92199224
{
92209225
int suspend;
9221-
9222-
ASSERT(c_p == erts_get_current_process());
9226+
#ifdef DEBUG
9227+
Process *curr_proc = erts_get_current_process();
9228+
ASSERT(curr_proc == c_p
9229+
|| curr_proc == erts_dirty_process_signal_handler
9230+
|| curr_proc == erts_dirty_process_signal_handler_high
9231+
|| curr_proc == erts_dirty_process_signal_handler_max);
9232+
#endif
92239233
ERTS_LC_ASSERT(c_p_locks == erts_proc_lc_my_proc_locks(c_p));
92249234
if (!(c_p_locks & ERTS_PROC_LOCK_STATUS))
92259235
erts_proc_lock(c_p, ERTS_PROC_LOCK_STATUS);
@@ -9585,7 +9595,7 @@ Process *erts_schedule(ErtsSchedulerData *esdp, Process *p, int calls)
95859595
int dec_refc;
95869596

95879597
/* schedule_out_process() returns with rq locked! */
9588-
dec_refc = schedule_out_process(rq, state, p,
9598+
dec_refc = schedule_out_process(rq, &state, p,
95899599
proxy_p, is_normal_sched);
95909600
proxy_p = NULL;
95919601

@@ -9602,6 +9612,17 @@ Process *erts_schedule(ErtsSchedulerData *esdp, Process *p, int calls)
96029612
| ERTS_PROC_LOCK_STATUS
96039613
| ERTS_PROC_LOCK_TRACE));
96049614

9615+
if (ERTS_PROC_NEED_DIRTY_SIG_HANDLING(state)) {
9616+
/*
9617+
* Ensure signals are handled while scheduled
9618+
* or running dirty...
9619+
*/
9620+
int prio = ERTS_PSFLGS_GET_ACT_PRIO(state);
9621+
erts_runq_unlock(rq);
9622+
erts_ensure_dirty_proc_signals_handled(p, state, prio, 0);
9623+
erts_runq_lock(rq);
9624+
}
9625+
96059626
ERTS_MSACC_SET_STATE_CACHED(ERTS_MSACC_STATE_OTHER);
96069627

96079628
if (state & ERTS_PSFLG_FREE) {
@@ -10122,17 +10143,6 @@ Process *erts_schedule(ErtsSchedulerData *esdp, Process *p, int calls)
1012210143

1012310144
if (!is_normal_sched) {
1012410145
/* On dirty scheduler */
10125-
if (!!(state & ERTS_PSFLG_DIRTY_RUNNING)
10126-
& !!(state & (ERTS_PSFLG_SIG_Q
10127-
| ERTS_PSFLG_NMSG_SIG_IN_Q
10128-
| ERTS_PSFLG_MSG_SIG_IN_Q))) {
10129-
/* Ensure signals are handled while executing dirty... */
10130-
int prio = ERTS_PSFLGS_GET_ACT_PRIO(state);
10131-
erts_ensure_dirty_proc_signals_handled(p,
10132-
state,
10133-
prio,
10134-
ERTS_PROC_LOCK_MAIN);
10135-
}
1013610146
}
1013710147
else {
1013810148
/* On normal scheduler */

erts/emulator/beam/erl_process.h

Lines changed: 28 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1314,6 +1314,34 @@ void erts_check_for_holes(Process* p);
13141314
| ERTS_PSFLG_DIRTY_RUNNING \
13151315
| ERTS_PSFLG_DIRTY_RUNNING_SYS)
13161316

1317+
/*
1318+
* Process is in a dirty state if it got dirty work scheduled or
1319+
* is running dirty. We do not include the dirty-running-sys state
1320+
* since it executing while holding the main process lock which makes
1321+
* it hard or impossible to manipulate from the outside. The time spent
1322+
* in the dirty-running-sys is also limited compared to the other dirty
1323+
* states.
1324+
*
1325+
* For more info on why we ignore dirty running sys see
1326+
* erts_execute_dirty_system_task() in erl_process.c.
1327+
*/
1328+
#define ERTS_PROC_IN_DIRTY_STATE(S) \
1329+
((!!((S) & (ERTS_PSFLGS_DIRTY_WORK \
1330+
| ERTS_PSFLG_DIRTY_RUNNING))) \
1331+
& (!((S) & (ERTS_PSFLG_DIRTY_RUNNING_SYS \
1332+
| ERTS_PSFLG_RUNNING_SYS \
1333+
| ERTS_PSFLG_RUNNING))))
1334+
1335+
/*
1336+
* A process needs dirty signal handling if it has unhandled signals
1337+
* and is in a dirty state...
1338+
*/
1339+
#define ERTS_PROC_NEED_DIRTY_SIG_HANDLING(S) \
1340+
((!!((S) & (ERTS_PSFLG_SIG_Q \
1341+
| ERTS_PSFLG_NMSG_SIG_IN_Q \
1342+
| ERTS_PSFLG_MSG_SIG_IN_Q))) \
1343+
& ERTS_PROC_IN_DIRTY_STATE((S)))
1344+
13171345
#define ERTS_PSFLGS_GET_ACT_PRIO(PSFLGS) \
13181346
(((PSFLGS) >> ERTS_PSFLGS_ACT_PRIO_OFFSET) & ERTS_PSFLGS_PRIO_MASK)
13191347
#define ERTS_PSFLGS_GET_USR_PRIO(PSFLGS) \

erts/emulator/test/signal_SUITE.erl

Lines changed: 29 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -39,6 +39,7 @@
3939
kill2killed/1,
4040
contended_signal_handling/1,
4141
dirty_signal_handling_race/1,
42+
dirty_signal_handling/1,
4243
busy_dist_exit_signal/1,
4344
busy_dist_demonitor_signal/1,
4445
busy_dist_down_signal/1,
@@ -91,6 +92,7 @@ all() ->
9192
kill2killed,
9293
contended_signal_handling,
9394
dirty_signal_handling_race,
95+
dirty_signal_handling,
9496
busy_dist_exit_signal,
9597
busy_dist_demonitor_signal,
9698
busy_dist_down_signal,
@@ -388,6 +390,33 @@ move_dirty_signal_handlers_to_first_scheduler() ->
388390
end,
389391
ok.
390392

393+
dirty_signal_handling(Config) when is_list(Config) ->
394+
%%
395+
%% PR-7822 (third commit)
396+
%%
397+
%% Make sure signals are handled regardless of whether a process is
398+
%% executing dirty or is scheduled for dirty execution...
399+
400+
%% Make sure all dirty I/O schedulers are occupied with work...
401+
Ps = lists:map(fun (_) ->
402+
spawn(fun () ->
403+
erts_debug:dirty_io(wait, 1000)
404+
end)
405+
end, lists:seq(1, erlang:system_info(dirty_io_schedulers))),
406+
%% P ends up in the run queue waiting for a free dirty I/O scheduler...
407+
P = spawn(fun () ->
408+
erts_debug:dirty_io(wait, 1000)
409+
end),
410+
receive after 300 -> ok end,
411+
%% current_function is added to prevent read of status from being optimized
412+
%% to read status directly...
413+
[{status,runnable},{current_function, _}] = process_info(P, [status,current_function]),
414+
receive after 1000 -> ok end,
415+
[{status,running},{current_function, _}] = process_info(P, [status,current_function]),
416+
lists:foreach(fun (X) -> exit(X, kill) end, [P|Ps]),
417+
lists:foreach(fun (X) -> false = is_process_alive(X) end, [P|Ps]),
418+
ok.
419+
391420
busy_dist_exit_signal(Config) when is_list(Config) ->
392421
ct:timetrap({seconds, 10}),
393422

erts/etc/unix/etp-commands.in

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -2474,7 +2474,7 @@ define etp-proc-state-int
24742474
printf "active-sys | "
24752475
end
24762476
if ($arg0 & 0x80000)
2477-
printf "sig-in-q | "
2477+
printf "nmsig-in-q | "
24782478
end
24792479
if ($arg0 & 0x40000)
24802480
printf "sys-tasks | "
@@ -2495,7 +2495,7 @@ define etp-proc-state-int
24952495
printf "active | "
24962496
end
24972497
if ($arg0 & 0x1000)
2498-
printf "maybe-self-sigs | "
2498+
printf "msig-in-q | "
24992499
end
25002500
if ($arg0 & 0x800)
25012501
printf "exiting | "

0 commit comments

Comments
 (0)