File 2311-Use-timer-time-for-non-negative-timeout-values.patch of Package erlang
From 5d9f5b46badce737234b8e13a3a77ca7670855cd Mon Sep 17 00:00:00 2001
From: Johannes Christ <jc@jchri.st>
Date: Tue, 11 Mar 2025 20:09:23 +0100
Subject: [PATCH] Use timer:time for non-negative timeout values
As suggested in #9515. In some parts of the code, `pos_integer()` is
currently used for timeouts, which can't be replaced with `timer:time()`
as it is specified as `integer() >= 0`.
Locally tested by running dialyzer with updated preloaded code.
---
lib/common_test/src/ct.erl | 9 ++++-----
lib/common_test/src/ct_gen_conn.erl | 2 +-
lib/common_test/src/ct_suite.erl | 2 +-
lib/common_test/src/ct_telnet.erl | 2 +-
lib/common_test/src/test_server.erl | 8 ++------
lib/eldap/src/eldap.erl | 2 +-
lib/eunit/src/eunit_proc.erl | 2 +-
lib/inets/src/inets_app/inets_lib.erl | 6 ------
lib/kernel/src/gen_tcp.erl | 2 +-
lib/observer/src/ttb.erl | 2 +-
lib/odbc/src/odbc.erl | 2 +-
lib/os_mon/src/disksup.erl | 2 +-
lib/os_mon/src/memsup.erl | 2 +-
lib/ssh/src/ssh_agent.erl | 2 +-
lib/ssh/test/ssh_test_lib.erl | 1 +
lib/stdlib/src/dets.hrl | 2 +-
16 files changed, 19 insertions(+), 29 deletions(-)
diff --git a/lib/common_test/src/ct.erl b/lib/common_test/src/ct.erl
index 1d9c2d648b..7446e67dc0 100644
--- a/lib/common_test/src/ct.erl
+++ b/lib/common_test/src/ct.erl
@@ -1449,11 +1449,10 @@ the new timetrap.
""".
-doc(#{since => <<"OTP R14B">>}).
-spec timetrap(Time) -> infinity | pid()
- when Time :: {hours, Hours} | {minutes, Mins} | {seconds, Secs} | Millisecs | infinity | Func,
+ when Time :: {hours, Hours} | {minutes, Mins} | {seconds, Secs} | timeout() | Func,
Hours :: integer(),
Mins :: integer(),
Secs :: integer(),
- Millisecs :: integer(),
Func :: {M, F, A} | function(),
M :: atom(),
F :: atom(),
@@ -1471,7 +1470,7 @@ Note the `Time` is not the scaled result.
""".
-doc(#{since => <<"OTP R15B">>}).
-spec get_timetrap_info() -> {Time, {Scaling,ScaleVal}}
- when Time :: integer() | infinity,
+ when Time :: timeout(),
Scaling :: boolean(),
ScaleVal :: integer().
get_timetrap_info() ->
@@ -1486,11 +1485,11 @@ up the time automatically if `scale_timetraps` is set to `true` (default is
""".
-doc(#{since => <<"OTP R14B">>}).
-spec sleep(Time) -> ok
- when Time :: {hours, Hours} | {minutes, Mins} | {seconds, Secs} | Millisecs | infinity,
+ when Time :: {hours, Hours} | {minutes, Mins} | {seconds, Secs} | Millisecs,
Hours :: integer(),
Mins :: integer(),
Secs :: integer(),
- Millisecs :: integer() | float().
+ Millisecs :: timeout() | float().
sleep({hours,Hs}) ->
sleep(trunc(Hs * 1000 * 60 * 60));
sleep({minutes,Ms}) ->
diff --git a/lib/common_test/src/ct_gen_conn.erl b/lib/common_test/src/ct_gen_conn.erl
index 4c0b5368f5..3fd4e1f898 100644
--- a/lib/common_test/src/ct_gen_conn.erl
+++ b/lib/common_test/src/ct_gen_conn.erl
@@ -220,7 +220,7 @@ end_log() ->
-spec do_within_time(Fun, Tmo)
-> Result
when Fun :: fun(),
- Tmo :: non_neg_integer(),
+ Tmo :: timeout(),
Result :: term().
%% Return the result of evaluating Fun, or interrupt after Tmo
diff --git a/lib/common_test/src/ct_suite.erl b/lib/common_test/src/ct_suite.erl
index 007b11a808..4521cce8b3 100644
--- a/lib/common_test/src/ct_suite.erl
+++ b/lib/common_test/src/ct_suite.erl
@@ -92,7 +92,7 @@ The test suite information, as returned by [`Module:suite/0`](`c:suite/0`),
{silent_connections, Conns :: [atom()]} |
{stylesheet, CSSFile :: string()} |
{ct_hooks, CTHs :: ct_hooks()}.
--type ct_info_timetrap() :: MilliSec :: integer() |
+-type ct_info_timetrap() :: timeout() |
{seconds, integer()} |
{minutes, integer()} |
{hours, integer()} |
diff --git a/lib/common_test/src/ct_telnet.erl b/lib/common_test/src/ct_telnet.erl
index b678cf5a46..6c81c9a632 100644
--- a/lib/common_test/src/ct_telnet.erl
+++ b/lib/common_test/src/ct_telnet.erl
@@ -60,7 +60,7 @@ term:
{tcp_nodelay,Bool}]}.
```
-`Millisec = integer(), N = integer()`
+`Millisec = timeout(), N = integer()`
Enter the `telnet_settings` term in a configuration file included in the test
and `ct_telnet` retrieves the information automatically.
diff --git a/lib/common_test/src/test_server.erl b/lib/common_test/src/test_server.erl
index ab5eac0f07..9eaaae1d71 100644
--- a/lib/common_test/src/test_server.erl
+++ b/lib/common_test/src/test_server.erl
@@ -1915,11 +1915,9 @@ permit_io(GroupLeader, FromPid) ->
ok.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-%% sleep(Time) -> ok
-%% Time = integer() | float() | infinity
-%%
%% Sleeps the specified number of milliseconds. This sleep also accepts
%% floating point numbers (which are truncated) and the atom 'infinity'.
+-spec sleep(timeout() | float()) -> ok.
sleep(infinity) ->
receive
after infinity ->
@@ -1933,14 +1931,12 @@ sleep(MSecs) ->
ok.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-%% adjusted_sleep(Time) -> ok
-%% Time = integer() | float() | infinity
-%%
%% Sleeps the specified number of milliseconds, multiplied by the
%% 'multiply_timetraps' value (if set) and possibly also automatically scaled
%% up if 'scale_timetraps' is set to true (which is default).
%% This function also accepts floating point numbers (which are truncated) and
%% the atom 'infinity'.
+-spec adjusted_sleep(timeout() | float()) -> ok.
adjusted_sleep(infinity) ->
receive
after infinity ->
diff --git a/lib/eldap/src/eldap.erl b/lib/eldap/src/eldap.erl
index f70e193640..c3987c99ef 100644
--- a/lib/eldap/src/eldap.erl
+++ b/lib/eldap/src/eldap.erl
@@ -225,7 +225,7 @@ All TCP socket options are accepted except `active`, `binary`, `deliver`,
Options ::
[{port, integer()} |
{log, function()} |
- {timeout, integer()} |
+ {timeout, timeout()} |
{ssl, boolean()} |
{sslopts, [ssl:tls_client_option()]} |
{tcpopts, [inet:inet_backend() | gen_tcp:connect_option()]}],
diff --git a/lib/eunit/src/eunit_proc.erl b/lib/eunit/src/eunit_proc.erl
index 2da1cd3fdb..11a5e37298 100644
--- a/lib/eunit/src/eunit_proc.erl
+++ b/lib/eunit/src/eunit_proc.erl
@@ -92,7 +92,7 @@ get_output() ->
%%
%% {progress, 'end', {Status, Data}}
%% Status = 'ok' | {error, Exception} | {skipped, Cause} | integer()
-%% Data = [{time,integer()}, {output,binary()}]
+%% Data = [{time,timer:time()}, {output,binary()}]
%%
%% where Time is measured in milliseconds and Output is the data
%% written to the standard output stream during the test; if
diff --git a/lib/inets/src/inets_app/inets_lib.erl b/lib/inets/src/inets_app/inets_lib.erl
index 0a8468e535..07524276d6 100644
--- a/lib/inets/src/inets_app/inets_lib.erl
+++ b/lib/inets/src/inets_app/inets_lib.erl
@@ -27,13 +27,7 @@
-%% Help function, elapsed milliseconds since T0
-millisec_passed({_,_,_} = T0 ) ->
- %% OTP 17 and earlier
- timer:now_diff(erlang:timestamp(), T0) div 1000;
-
millisec_passed(T0) ->
- %% OTP 18
erlang:convert_time_unit(erlang:monotonic_time() - T0,
native,
micro_seconds) div 1000.
diff --git a/lib/kernel/src/gen_tcp.erl b/lib/kernel/src/gen_tcp.erl
index 2d1c67c88c..d08bd79ace 100644
--- a/lib/kernel/src/gen_tcp.erl
+++ b/lib/kernel/src/gen_tcp.erl
@@ -292,7 +292,7 @@ way, option `send_timeout` comes in handy.
{reuseaddr, boolean()} |
{reuseport, boolean()} |
{reuseport_lb, boolean()} |
- {send_timeout, non_neg_integer() | infinity} |
+ {send_timeout, timeout()} |
{send_timeout_close, boolean()} |
{show_econnreset, boolean()} |
{sndbuf, non_neg_integer()} |
diff --git a/lib/observer/src/ttb.erl b/lib/observer/src/ttb.erl
index 482b99f404..f65c5628e6 100644
--- a/lib/observer/src/ttb.erl
+++ b/lib/observer/src/ttb.erl
@@ -261,7 +261,7 @@ _Options:_
{overload_check, {MSec, Module, Function}} | {flush, MSec} |
resume | {resume, MSec} | {queue_size, non_neg_integer()},
TimerSpec :: MSec | {MSec, stop_opts()},
- MSec :: integer(),
+ MSec :: timer:time(),
Module :: atom(),
Function :: atom(),
Client :: File | {local, File},
diff --git a/lib/odbc/src/odbc.erl b/lib/odbc/src/odbc.erl
index 528a60efdc..1f4e157071 100644
--- a/lib/odbc/src/odbc.erl
+++ b/lib/odbc/src/odbc.erl
@@ -279,7 +279,7 @@ dealing with a known underlying database.
{error, Reason} when
ConnectionStr :: string(),
Options :: [{auto_commit, on | off} |
- {timeout, erlang:timeout()} |
+ {timeout, timeout()} |
{binary_strings, on | off} |
{tuple_row, on | off} |
{scrollable_cursors, on | off} |
diff --git a/lib/os_mon/src/disksup.erl b/lib/os_mon/src/disksup.erl
index 72533af291..2860900f96 100644
--- a/lib/os_mon/src/disksup.erl
+++ b/lib/os_mon/src/disksup.erl
@@ -172,7 +172,7 @@ get_disk_info(Path) ->
-doc """
Returns the time interval, in milliseconds, for the periodic disk space check.
""".
--spec get_check_interval() -> Milliseconds :: integer().
+-spec get_check_interval() -> Milliseconds :: timer:time().
get_check_interval() ->
os_mon:call(disksup, get_check_interval, infinity).
diff --git a/lib/os_mon/src/memsup.erl b/lib/os_mon/src/memsup.erl
index edbb1160c1..fbf50ca308 100644
--- a/lib/os_mon/src/memsup.erl
+++ b/lib/os_mon/src/memsup.erl
@@ -248,7 +248,7 @@ get_system_memory_data() ->
-doc """
Returns the time interval, in milliseconds, for the periodic memory check.
""".
--spec get_check_interval() -> Milliseconds :: integer().
+-spec get_check_interval() -> Milliseconds :: timer:time().
get_check_interval() ->
os_mon:call(memsup, get_check_interval, infinity).
-doc """
diff --git a/lib/ssh/src/ssh_agent.erl b/lib/ssh/src/ssh_agent.erl
index 0b4959c9a8..754f103b84 100644
--- a/lib/ssh/src/ssh_agent.erl
+++ b/lib/ssh/src/ssh_agent.erl
@@ -79,7 +79,7 @@ Sets the time-out in milliseconds when communicating with the agent via the
socket. The default value is `1000`.
""".
-doc(#{title => <<"Options">>}).
--type timeout_option() :: {timeout, integer()}.
+-type timeout_option() :: {timeout, timeout()}.
-doc """
The module which the `add_host_key` and `is_host_key` callbacks are delegated
to. Defaults to the `m:ssh_file` module.
diff --git a/lib/ssh/test/ssh_test_lib.erl b/lib/ssh/test/ssh_test_lib.erl
index 7fdea43aeb..30bb4b4510 100644
--- a/lib/ssh/test/ssh_test_lib.erl
+++ b/lib/ssh/test/ssh_test_lib.erl
@@ -894,6 +894,7 @@ open_port(Arg1, ExtraOpts) ->
%%% Sleeping
%%% Milli sec
+-spec sleep_millisec(timeout()) -> ok.
sleep_millisec(Nms) -> receive after Nms -> ok end.
%%% Micro sec
diff --git a/lib/stdlib/src/dets.hrl b/lib/stdlib/src/dets.hrl
index 525cc20445..41b5ea7283 100644
--- a/lib/stdlib/src/dets.hrl
+++ b/lib/stdlib/src/dets.hrl
@@ -49,7 +49,7 @@
-define(DETS_CALL(Pid, Req), {'$dets_call', Pid, Req}).
-type access() :: 'read' | 'read_write'.
--type auto_save() :: 'infinity' | non_neg_integer().
+-type auto_save() :: timeout().
-type hash_bif() :: 'phash' | 'phash2'.
-type keypos() :: pos_integer().
-type no_colls() :: [{LogSize :: non_neg_integer(),
--
2.43.0