File 1161-Fix-multi-zero-timeout-callback-handling-in-timer-wh.patch of Package erlang

From 8d3393e8bfec37842003ef808e760af850637a3c Mon Sep 17 00:00:00 2001
From: Rickard Green <rickard@erlang.org>
Date: Thu, 4 Mar 2021 16:26:59 +0100
Subject: [PATCH] Fix multi-zero timeout callback handling in timer wheel

Execution of a zero timeout callback which was started from another
zero timeout callback could be delayed. Most timers in the system
do not behave like this. The service timer placed in the timer wheel
for management of the red-black tree of very long timers may however
behave like this.
---
 erts/emulator/beam/erl_bif_info.c      | 34 ++++++++++++++++++++++++++
 erts/emulator/beam/time.c              |  4 +++
 erts/emulator/test/timer_bif_SUITE.erl | 26 ++++++++++++++++++--
 3 files changed, 62 insertions(+), 2 deletions(-)

diff --git a/erts/emulator/beam/erl_bif_info.c b/erts/emulator/beam/erl_bif_info.c
index 96f399fbbe..8b3cf21d0a 100644
--- a/erts/emulator/beam/erl_bif_info.c
+++ b/erts/emulator/beam/erl_bif_info.c
@@ -3980,6 +3980,27 @@ static void broken_halt_test(Eterm bif_arg_2)
     erts_exit(ERTS_DUMP_EXIT, "%T", bif_arg_2);
 }
 
+static void
+test_multizero_timeout_in_timeout3(void *vproc)
+{
+    Process *proc = (Process *) vproc;
+    ErtsMessage *mp = erts_alloc_message(0, NULL);
+    ERTS_DECL_AM(multizero_timeout_in_timeout_done);
+    erts_queue_message(proc, 0, mp, AM_multizero_timeout_in_timeout_done, am_system);
+    erts_proc_dec_refc(proc);
+}
+
+static void
+test_multizero_timeout_in_timeout2(void *vproc)
+{
+    erts_start_timer_callback(0, test_multizero_timeout_in_timeout3, vproc);
+}
+
+static void
+test_multizero_timeout_in_timeout(void *vproc)
+{
+    erts_start_timer_callback(0, test_multizero_timeout_in_timeout2, vproc);
+}
 
 BIF_RETTYPE erts_debug_set_internal_state_2(BIF_ALIST_2)
 {
@@ -4306,6 +4327,18 @@ BIF_RETTYPE erts_debug_set_internal_state_2(BIF_ALIST_2)
             }
             BIF_RET(am_ok);
         }
+        else if (ERTS_IS_ATOM_STR("multizero_timeout_in_timeout", BIF_ARG_1)) {
+            Sint64 timeout;
+            if (term_to_Sint64(BIF_ARG_2, &timeout)) {
+                if (timeout < 0)
+                    timeout = 0;
+                erts_proc_inc_refc(BIF_P);
+                erts_start_timer_callback((ErtsMonotonicTime) timeout,
+                                          test_multizero_timeout_in_timeout,
+                                          (void *) BIF_P);
+                BIF_RET(am_ok);
+            }
+        }
     }
 
     BIF_ERROR(BIF_P, BADARG);
diff --git a/erts/emulator/beam/time.c b/erts/emulator/beam/time.c
index a3069e419a..6c528a362b 100644
--- a/erts/emulator/beam/time.c
+++ b/erts/emulator/beam/time.c
@@ -871,6 +871,8 @@ erts_bump_timers(ErtsTimerWheel *tiw, ErtsMonotonicTime curr_time)
 	    }
 
 	    if (tiw->pos >= bump_to) {
+                if (tiw->at_once.nto)
+                    continue;
                 ERTS_MSACC_POP_STATE_M_X();
 		break;
             }
diff --git a/erts/emulator/test/timer_bif_SUITE.erl b/erts/emulator/test/timer_bif_SUITE.erl
index fc11a04a31..3531444b66 100644
--- a/erts/emulator/test/timer_bif_SUITE.erl
+++ b/erts/emulator/test/timer_bif_SUITE.erl
@@ -31,7 +31,8 @@
 	 cleanup/1, evil_timers/1, registered_process/1, same_time_yielding/1,
 	 same_time_yielding_with_cancel/1, same_time_yielding_with_cancel_other/1,
 %	 same_time_yielding_with_cancel_other_accessor/1,
-	 auto_cancel_yielding/1]).
+	 auto_cancel_yielding/1,
+         multizero_timeout_in_timeout/1]).
 
 -include_lib("common_test/include/ct.hrl").
 
@@ -70,7 +71,8 @@ all() ->
      same_time_yielding, same_time_yielding_with_cancel,
      same_time_yielding_with_cancel_other,
 %     same_time_yielding_with_cancel_other_accessor,
-     auto_cancel_yielding].
+     auto_cancel_yielding,
+     multizero_timeout_in_timeout].
 
 
 %% Basic start_timer/3 functionality
@@ -657,6 +659,26 @@ auto_cancel_yielding(Config) when is_list(Config) ->
     Mem = mem(),
     ok.
 
+multizero_timeout_in_timeout(Config) when is_list(Config) ->
+    Timeout = 500,
+    MaxTimeoutDiff = 1000,
+
+    %% We want to operate on the same timer wheel all the time...
+    process_flag(scheduler, erlang:system_info(schedulers_online)),
+
+    erlang:send_after(5*(Timeout+MaxTimeoutDiff), self(), pling),
+    erlang:yield(),
+    Start = erlang:monotonic_time(),
+    erts_debug:set_internal_state(multizero_timeout_in_timeout, Timeout),
+    receive multizero_timeout_in_timeout_done -> ok end,
+    End = erlang:monotonic_time(),
+    Time = erlang:convert_time_unit(End-Start, native, millisecond),
+    io:format("Time=~p~n", [Time]),
+    true = Time < Timeout + MaxTimeoutDiff,
+    ok.
+            
+        
+
 process_is_cleaned_up(P) when is_pid(P) ->
     undefined == erts_debug:get_internal_state({process_status, P}).
 
-- 
2.26.2

openSUSE Build Service is sponsored by