File 2891-Avoid-busy-wait-in-dirty-process-signal-handlers.patch of Package erlang

From 9e569594249025b72eb444d925a182fedb2c2168 Mon Sep 17 00:00:00 2001
From: Rickard Green <rickard@erlang.org>
Date: Mon, 16 Dec 2019 13:27:14 +0100
Subject: [PATCH] Avoid busy wait in dirty process signal handlers

Currently all dirty system tasks are handled while holding
the main lock (done in erts_execute_dirty_system_task() in
erl_process.c). The process is during this in the state
ERTS_PSFLG_DIRTY_RUNNING_SYS. The dirty signal handlers
(erts/preloaded/src/erts_dirty_process_signal_handler.erl)
cannot execute any signal handling on behalf of a process
executing dirty unless they will be able to acquire the
main lock. If they try to, they will just end up in a
busy wait until the lock has been released.

We now therefore do not schedule any handling on dirty
signal handlers while a process is in the state
ERTS_PSFLG_DIRTY_RUNNING_SYS. We instead leave the work
scheduled on the process an let it detect it itself
when it leaves the ERTS_PSFLG_DIRTY_RUNNING_SYS state.
See erts_proc_notify_new_sig() in erl_proc_sig_queue.h,
request_system_task() (check_process_code) in
erl_process.c, and maybe_elevate_sig_handling_prio()
in erl_proc_sig_queue.c for scheduling points.
---
 erts/emulator/beam/beam_bif_load.c      |  8 ++++--
 erts/emulator/beam/erl_proc_sig_queue.c | 23 +++++++++++-------
 erts/emulator/beam/erl_proc_sig_queue.h |  8 ++++--
 erts/emulator/beam/erl_process.c        | 43 +++++++++++++++++++++++++++------
 4 files changed, 62 insertions(+), 20 deletions(-)

diff --git a/erts/emulator/beam/beam_bif_load.c b/erts/emulator/beam/beam_bif_load.c
index 857c929880..4d03d2cf6b 100644
--- a/erts/emulator/beam/beam_bif_load.c
+++ b/erts/emulator/beam/beam_bif_load.c
@@ -605,8 +605,12 @@ BIF_RETTYPE erts_internal_check_dirty_process_code_2(BIF_ALIST_2)
         BIF_RET(am_false);
 
     state = erts_atomic32_read_nob(&rp->state);
-    dirty = (state & (ERTS_PSFLG_DIRTY_RUNNING
-                      | ERTS_PSFLG_DIRTY_RUNNING_SYS));
+    dirty = (state & ERTS_PSFLG_DIRTY_RUNNING);
+    /*
+     * Ignore ERTS_PSFLG_DIRTY_RUNNING_SYS (see
+     * comment in erts_execute_dirty_system_task()
+     * in erl_process.c).
+     */
     if (!dirty)
         BIF_RET(am_normal);
 
diff --git a/erts/emulator/beam/erl_proc_sig_queue.c b/erts/emulator/beam/erl_proc_sig_queue.c
index 2347527e28..f8d82a8f98 100644
--- a/erts/emulator/beam/erl_proc_sig_queue.c
+++ b/erts/emulator/beam/erl_proc_sig_queue.c
@@ -560,8 +560,7 @@ erts_make_dirty_proc_handled(Eterm pid,
     ErtsMessage *mp;
     Process *sig_handler;
 
-    ASSERT(state & (ERTS_PSFLG_DIRTY_RUNNING |
-                    ERTS_PSFLG_DIRTY_RUNNING_SYS));
+    ASSERT(state & ERTS_PSFLG_DIRTY_RUNNING);
 
     if (prio < 0)
         prio = (int) ERTS_PSFLGS_GET_USR_PRIO(state);
@@ -765,10 +764,13 @@ maybe_elevate_sig_handling_prio(Process *c_p, Eterm other)
             if (res) {
                 /* ensure handled if dirty executing... */
                 state = erts_atomic32_read_nob(&rp->state);
-                if (state & (ERTS_PSFLG_DIRTY_RUNNING
-                             | ERTS_PSFLG_DIRTY_RUNNING_SYS)) {
+                /*
+                 * We ignore ERTS_PSFLG_DIRTY_RUNNING_SYS. For
+                 * more info see erts_execute_dirty_system_task()
+                 * in erl_process.c.
+                 */
+                if (state & ERTS_PSFLG_DIRTY_RUNNING)
                     erts_make_dirty_proc_handled(other, state, my_prio);
-                }
             }
         }
     }
@@ -4565,8 +4567,12 @@ erts_internal_dirty_process_handle_signals_1(BIF_ALIST_1)
         BIF_RET(am_noproc);
 
     state = erts_atomic32_read_nob(&rp->state);
-    dirty = (state & (ERTS_PSFLG_DIRTY_RUNNING
-                      | ERTS_PSFLG_DIRTY_RUNNING_SYS));
+    dirty = (state & ERTS_PSFLG_DIRTY_RUNNING);
+    /*
+     * Ignore ERTS_PSFLG_DIRTY_RUNNING_SYS (see
+     * comment in erts_execute_dirty_system_task()
+     * in erl_process.c).
+     */
     if (!dirty)
         BIF_RET(am_normal);
 
@@ -4574,8 +4580,7 @@ erts_internal_dirty_process_handle_signals_1(BIF_ALIST_1)
 
     state = erts_atomic32_read_mb(&rp->state);
     noproc = (state & ERTS_PSFLG_FREE);
-    dirty = (state & (ERTS_PSFLG_DIRTY_RUNNING
-                      | ERTS_PSFLG_DIRTY_RUNNING_SYS));
+    dirty = (state & ERTS_PSFLG_DIRTY_RUNNING);
 
     if (busy) {
         if (noproc)
diff --git a/erts/emulator/beam/erl_proc_sig_queue.h b/erts/emulator/beam/erl_proc_sig_queue.h
index 2b055e73bc..2789179b34 100644
--- a/erts/emulator/beam/erl_proc_sig_queue.h
+++ b/erts/emulator/beam/erl_proc_sig_queue.h
@@ -1115,8 +1115,12 @@ erts_proc_notify_new_sig(Process* rp, erts_aint32_t state,
         state = erts_proc_sys_schedule(rp, state, enable_flag);
     }
 
-    if (state & (ERTS_PSFLG_DIRTY_RUNNING
-                 | ERTS_PSFLG_DIRTY_RUNNING_SYS)) {
+    if (state & ERTS_PSFLG_DIRTY_RUNNING) {
+        /*
+         * We ignore ERTS_PSFLG_DIRTY_RUNNING_SYS. For
+         * more info see erts_execute_dirty_system_task()
+         * in erl_process.c.
+         */
         erts_make_dirty_proc_handled(rp->common.id, state, -1);
     }
 }
diff --git a/erts/emulator/beam/erl_process.c b/erts/emulator/beam/erl_process.c
index 4c91c60220..d7d242ca86 100644
--- a/erts/emulator/beam/erl_process.c
+++ b/erts/emulator/beam/erl_process.c
@@ -10484,6 +10484,34 @@ erts_execute_dirty_system_task(Process *c_p)
     Eterm cla_res = THE_NON_VALUE;
     ErtsProcSysTask *stasks;
 
+    ASSERT(erts_atomic32_read_nob(&c_p->state)
+           & ERTS_PSFLG_DIRTY_RUNNING_SYS);
+    /*
+     * Currently all dirty system tasks are handled while holding
+     * the main lock. The process is during this in the state
+     * ERTS_PSFLG_DIRTY_RUNNING_SYS. The dirty signal handlers
+     * (erts/preloaded/src/erts_dirty_process_signal_handler.erl)
+     * cannot execute any signal handling on behalf of a process
+     * executing dirty unless they will be able to acquire the
+     * main lock. If they try to, they will just end up in a
+     * busy wait until the lock has been released.
+     *
+     * We now therefore do not schedule any handling on dirty
+     * signal handlers while a process is in the state
+     * ERTS_PSFLG_DIRTY_RUNNING_SYS. We instead leave the work
+     * scheduled on the process an let it detect it itself
+     * when it leaves the ERTS_PSFLG_DIRTY_RUNNING_SYS state.
+     * See erts_proc_notify_new_sig() in erl_proc_sig_queue.h,
+     * request_system_task() (check_process_code) in
+     * erl_process.c, and maybe_elevate_sig_handling_prio()
+     * in erl_proc_sig_queue.c for scheduling points.
+     *
+     * If there are dirty system tasks introduced that execute
+     * without the main lock held, we most likely want to trigger
+     * handling of signals via dirty signal handlers for these
+     * states.
+     */
+
     /*
      * If multiple operations, perform them in the following
      * order (in order to avoid unnecessary GC):
@@ -10579,8 +10607,7 @@ dispatch_system_task(Process *c_p, erts_aint_t fail_state,
 
     switch (st->type) {
     case ERTS_PSTT_CPC:
-	ASSERT(fail_state & (ERTS_PSFLG_DIRTY_RUNNING
-			     | ERTS_PSFLG_DIRTY_RUNNING_SYS));
+	ASSERT(fail_state & ERTS_PSFLG_DIRTY_RUNNING);
 	switch (st->prio) {
 	case am_max:
 	    rp = erts_dirty_process_signal_handler_max;
@@ -10726,9 +10753,12 @@ request_system_task(Process *c_p, Eterm requester, Eterm target,
 	 * If the process should start executing dirty
 	 * code it is important that this task is
 	 * aborted. Therefore this strict fail state...
-	 */
-	fail_state |= (ERTS_PSFLG_DIRTY_RUNNING
-		       | ERTS_PSFLG_DIRTY_RUNNING_SYS);
+         *
+         * We ignore ERTS_PSFLG_DIRTY_RUNNING_SYS. For
+         * more info see erts_execute_dirty_system_task()
+         * in erl_process.c.
+         */
+	fail_state |= ERTS_PSFLG_DIRTY_RUNNING;
 	break;
 
     case am_copy_literals:
@@ -10751,8 +10781,7 @@ request_system_task(Process *c_p, Eterm requester, Eterm target,
 	noproc:
 	    notify_sys_task_executed(c_p, st, noproc_res, 1);
 	}
-	else if (fail_state & (ERTS_PSFLG_DIRTY_RUNNING
-			       | ERTS_PSFLG_DIRTY_RUNNING_SYS)) {
+	else if (fail_state & ERTS_PSFLG_DIRTY_RUNNING) {
 	    ret = dispatch_system_task(c_p, fail_state, st,
 				       target, operation);
 	    goto cleanup_return;
-- 
2.16.4

openSUSE Build Service is sponsored by