File 1427-erts-Don-t-expose-timeout-primitives-to-huge-timeout.patch of Package erlang
From 114466c12919f97ea7c63c35c939b9dac5a087af Mon Sep 17 00:00:00 2001
From: Rickard Green <rickard@erlang.org>
Date: Sat, 23 Dec 2023 22:34:22 +0100
Subject: [PATCH 1/3] [erts] Don't expose timeout primitives to huge timeouts
---
erts/emulator/beam/time.c | 17 ++++++++-
erts/emulator/test/timer_bif_SUITE.erl | 53 ++++++++++++++++++++++++--
2 files changed, 65 insertions(+), 5 deletions(-)
diff --git a/erts/emulator/beam/time.c b/erts/emulator/beam/time.c
index ce57b041d6..9584c6b600 100644
--- a/erts/emulator/beam/time.c
+++ b/erts/emulator/beam/time.c
@@ -613,7 +613,22 @@ find_next_timeout(ErtsSchedulerData *esdp, ErtsTimerWheel *tiw)
}
done: {
- ErtsMonotonicTime min_timeout;
+ ErtsMonotonicTime min_timeout, timeout_pos_limit;
+
+ timeout_pos_limit = tiw->pos + ERTS_CLKTCKS_WEEK;
+ if (min_timeout_pos > timeout_pos_limit) {
+ /*
+ * We never expose a timeout larger than a week in order to avoid
+ * issues with primitives that have a limited maximum timeout
+ * time (for example, poll() with a timeout in milliseconds passed
+ * in a variable of type 'int' which is around 3,5 weeks). The
+ * overhead, in case all timers are very far in the future, will
+ * be that the scheduler once a week will have to check if we got
+ * any timeouts closer in time than a week...
+ */
+ min_timeout_pos = timeout_pos_limit;
+ true_min_timeout = 0;
+ }
min_timeout = ERTS_CLKTCKS_TO_MONOTONIC(min_timeout_pos);
tiw->next_timeout_pos = min_timeout_pos;
diff --git a/erts/emulator/test/timer_bif_SUITE.erl b/erts/emulator/test/timer_bif_SUITE.erl
index c02d2c767f..9586d4b23f 100644
--- a/erts/emulator/test/timer_bif_SUITE.erl
+++ b/erts/emulator/test/timer_bif_SUITE.erl
@@ -32,7 +32,8 @@
% same_time_yielding_with_cancel_other_accessor/1,
auto_cancel_yielding/1,
suspended_scheduler_timeout/1,
- multizero_timeout_in_timeout/1]).
+ multizero_timeout_in_timeout/1,
+ huge_timeout/1]).
-include_lib("common_test/include/ct.hrl").
@@ -72,7 +73,8 @@ all() ->
% same_time_yielding_with_cancel_other_accessor,
auto_cancel_yielding,
suspended_scheduler_timeout,
- multizero_timeout_in_timeout].
+ multizero_timeout_in_timeout,
+ huge_timeout].
%% Basic start_timer/3 functionality
@@ -771,8 +773,51 @@ multizero_timeout_in_timeout(Config) when is_list(Config) ->
io:format("Time=~p~n", [Time]),
true = Time < Timeout + MaxTimeoutDiff,
ok.
-
-
+
+huge_timeout(Config) when is_list(Config) ->
+ %% More than 2^31 seconds...
+ huge_timeout_test((1 bsl 31)*1000 + 1000),
+ %% More than 2^32 seconds...
+ huge_timeout_test((1 bsl 32)*1000 + 1000),
+ %% More than 2^31 milliseconds...
+ huge_timeout_test((1 bsl 31) + 1000),
+ %% More than 2^32 milliseconds...
+ huge_timeout_test((1 bsl 32) + 1000),
+ ok.
+
+huge_timeout_test(HugeTmo) ->
+ SOnln = erlang:system_info(schedulers_online),
+ process_flag(trap_exit, true),
+ %% Likely to hit the bug if we set a huge timeout in an
+ %% empty timer wheel, then set a small timeout
+ %% and let the small timeout trigger. The huge timeout
+ %% will then be found as the next timeout in the wheel.
+ %% Just setting a huge timeout wont trigger the bug
+ %% since an empty wheel have a fake timeout of one week.
+ Ps = lists:map(
+ fun (N) ->
+ spawn_opt(
+ fun () ->
+ erlang:send_after(HugeTmo, self(), hej),
+ erlang:send_after(2, self(), hej),
+ receive after infinity -> ok end
+ end, [{scheduler,N}, link])
+ end, lists:seq(1, erlang:system_info(schedulers))),
+ %% If we have schedulers offline, those timer wheels are likely
+ %% empty, so set them online increasing the chanse of hitting
+ %% a bug.
+ try
+ erlang:system_flag(schedulers_online, erlang:system_info(schedulers)),
+ receive after 1000 -> ok end
+ after
+ lists:foreach(fun (P) ->
+ unlink(P),
+ exit(P, kill),
+ false = is_process_alive(P)
+ end, Ps),
+ erlang:system_flag(schedulers_online, SOnln),
+ process_flag(trap_exit, false)
+ end.
process_is_cleaned_up(P) when is_pid(P) ->
undefined == erts_debug:get_internal_state({process_status, P}).
--
2.35.3