File 4501-ssh-improve-renegotiation-alive-timeout-calculation.patch of Package erlang

From 176f2457f3ad0d604103ec2535b28948f91b08e3 Mon Sep 17 00:00:00 2001
From: Alexandre Rodrigues <alexandrejbr@live.com>
Date: Mon, 15 Dec 2025 20:00:35 +0100
Subject: [PATCH] ssh: improve renegotiation alive timeout calculation

---
 lib/ssh/src/ssh_connection_handler.erl | 17 +++++++++++++----
 lib/ssh/test/ssh_protocol_SUITE.erl    | 10 +++++-----
 lib/ssh/test/ssh_trpt_test_lib.erl     |  6 +++++-
 3 files changed, 23 insertions(+), 10 deletions(-)

diff --git a/lib/ssh/src/ssh_connection_handler.erl b/lib/ssh/src/ssh_connection_handler.erl
index 129cae9d2e..0fa4e5289c 100644
--- a/lib/ssh/src/ssh_connection_handler.erl
+++ b/lib/ssh/src/ssh_connection_handler.erl
@@ -2228,11 +2228,20 @@ triggered_alive(StateName, D0 = #data{},
 %% feature acts as a keep-alive and a timeout, an equivalent timeout is
 %% established for the renegotiation procedure if alive is enabled.
 %% For simplicity the timeout value is derived from alive_interval and
-%% alive_count.
-renegotiation_alive_timeout(#ssh{opts = Opts}) ->
+%% alive_count and takes in consideration the probes that may have already
+%% been sent.
+renegotiation_alive_timeout(#ssh{opts = Opts} = Ssh) ->
     case ?GET_ALIVE_OPT(Opts) of
-        {_AliveCount, infinity} -> infinity;
-        {AliveCount, AliveInterval} -> AliveCount * AliveInterval
+        {_AliveCount, infinity} ->
+            infinity;
+        {AliveCount, AliveInterval} ->
+            #ssh{alive_last_sent_at = AliveLastSentAt,
+                 alive_probes_sent = AliveProbesSent} = Ssh,
+            Now = erlang:monotonic_time(milli_seconds),
+            TimeSinceLastAlive = Now - AliveLastSentAt,
+            TotalElapsedTimeWithoutAlive =
+                AliveProbesSent * AliveInterval + TimeSinceLastAlive,
+            AliveCount * AliveInterval - TotalElapsedTimeWithoutAlive
     end.
 
 %%%################################################################
diff --git a/lib/ssh/test/ssh_protocol_SUITE.erl b/lib/ssh/test/ssh_protocol_SUITE.erl
index b6eac84bd2..36d2facfa6 100644
--- a/lib/ssh/test/ssh_protocol_SUITE.erl
+++ b/lib/ssh/test/ssh_protocol_SUITE.erl
@@ -1636,8 +1636,7 @@ alive_reneg_eserver_tclient(Config) ->
                   [{match, #ssh_msg_userauth_success{_='_'}, receive_msg},
                    {match, #ssh_msg_global_request{name = <<"keepalive@erlang.org">>,
                                                    want_reply = true,
-                                                   data = <<>>}, receive_msg},
-                   {send, #ssh_msg_request_failure{}}],
+                                                   data = <<>>}, receive_msg}],
                   State)
         end,
     {ok, TrptState1} = CheckAlive(TrptState0),
@@ -1647,8 +1646,7 @@ alive_reneg_eserver_tclient(Config) ->
         ssh_trpt_test_lib:exec(
           [{send, start_incomplete_renegotiation},
            {match, #ssh_msg_kexinit{_='_'}, receive_msg},
-           {match, disconnect(), receive_msg}],
-          TrptState1),
+           {match, disconnect(), receive_msg}], TrptState1),
     ?CT_LOG("[OK] triggering incomplete, client triggered remotely key renegotiation"),
     ?CT_LOG("[starting] Alive feature - normal conditions 2"),
     {ok, TrptState2} = connect_and_userauth_request(Host, Port, User, Pwd, UserDir),
@@ -1669,11 +1667,13 @@ alive_reneg_eserver_tclient(Config) ->
     [CHandlerPid] = CHandler(ssh_info:get_subs_tree(sshd_sup), []),
     ?CT_LOG("Server side connection handler PID: ~p", [CHandlerPid]),
     ssh_connection_handler:renegotiate(CHandlerPid),
+    %% The disconnect is received under 2 seconds since the tclient already
+    %% failed to reply to one of the probles from eserver.
     {ok, _} =
         ssh_trpt_test_lib:exec(
           [{match, #ssh_msg_kexinit{_='_'}, receive_msg},
            {match, disconnect(), receive_msg}],
-          TrptState3),
+          ssh_trpt_test_lib:set_timeout(TrptState3, 2000)),
     ?CT_LOG("[OK] triggering incomplete, server triggered locally key renegotiation"),
     ssh:stop_daemon(DaemonPid),
     ?CT_LOG("[OK] test case finished"),
diff --git a/lib/ssh/test/ssh_trpt_test_lib.erl b/lib/ssh/test/ssh_trpt_test_lib.erl
index 6544b8ed35..c065e8d751 100644
--- a/lib/ssh/test/ssh_trpt_test_lib.erl
+++ b/lib/ssh/test/ssh_trpt_test_lib.erl
@@ -27,7 +27,8 @@
 	 instantiate/2,
 	 format_msg/1,
 	 server_host_port/1,
-         return_value/1
+         return_value/1,
+         set_timeout/2
 	]
        ).
 
@@ -830,3 +831,6 @@ save_prints({Fmt,Args}, S) ->
 
 return_value(#s{return_value = ReturnValue}) ->
     ReturnValue.
+
+set_timeout(S, Timeout) ->
+    S#s{timeout = Timeout}.
-- 
2.51.0

openSUSE Build Service is sponsored by