File 4474-ssh-add-tests-and-improve-implementation-of-ssh-keep.patch of Package erlang

From b420175fcce57306a62debd688ed65742f910c51 Mon Sep 17 00:00:00 2001
From: Alexandre Rodrigues <alexandrejbr@live.com>
Date: Wed, 13 Aug 2025 16:03:51 +0200
Subject: [PATCH 04/20] ssh: add tests and improve implementation of ssh keep
 alive

---
 lib/ssh/src/ssh_connection_handler.erl |  36 ++++-----
 lib/ssh/src/ssh_options.erl            |   2 +-
 lib/ssh/test/ssh_protocol_SUITE.erl    | 103 ++++++++++++++++++++++++-
 3 files changed, 118 insertions(+), 23 deletions(-)

diff --git a/lib/ssh/src/ssh_connection_handler.erl b/lib/ssh/src/ssh_connection_handler.erl
index 614adfad68..c13b827b7f 100644
--- a/lib/ssh/src/ssh_connection_handler.erl
+++ b/lib/ssh/src/ssh_connection_handler.erl
@@ -96,11 +96,6 @@
 -define(call_disconnectfun_and_log_cond(LogMsg, DetailedText, StateName, D),
         call_disconnectfun_and_log_cond(LogMsg, DetailedText, ?MODULE, ?LINE, StateName, D)).
 
--define(KEEP_ALIVE_REQUEST,
-    {ssh_msg_global_request,"keepalive@example.com", true,<<>>}).
--define(KEEP_ALIVE_RESPONSE_F, {ssh_msg_request_failure}).
--define(KEEP_ALIVE_RESPONSE_S, {ssh_msg_request_success}).
-
 %%====================================================================
 %% Start / stop
 %%====================================================================
@@ -762,9 +757,12 @@ handle_event(internal, #ssh_msg_debug{} = Msg, _StateName, D) ->
     debug_fun(Msg, D),
     keep_state_and_data;
 
-handle_event(_, {conn_msg, Msg}, _, D = #data{ssh_params = Ssh})
-  when Ssh#ssh.awaiting_keepalive_response,
-       (Msg =:= ?KEEP_ALIVE_RESPONSE_F orelse Msg =:= ?KEEP_ALIVE_RESPONSE_S) ->
+handle_event(internal, {conn_msg, #ssh_msg_request_failure{}}, _, D = #data{ssh_params = Ssh})
+  when Ssh#ssh.awaiting_keepalive_response ->
+    {keep_state, D#data{ssh_params = Ssh#ssh{awaiting_keepalive_response = false}}};
+
+handle_event(internal, {conn_msg, #ssh_msg_request_success{}}, _, D = #data{ssh_params = Ssh})
+  when Ssh#ssh.awaiting_keepalive_response ->
     {keep_state, D#data{ssh_params = Ssh#ssh{awaiting_keepalive_response = false}}};
 
 handle_event(internal, {conn_msg,Msg}, StateName, #data{connection_state = Connection0,
@@ -2188,17 +2186,14 @@ update_inet_buffers(Socket) ->
 %%% Keep-alive
 
 %% Reset the last_alive timer on #data{ssh_params=#ssh{}} record
-reset_alive(D = #data{ssh_params = Ssh}) ->
-    D#data{ssh_params = reset_alive_ssh_params(Ssh)}.
-
-%% Update #data.ssh_params last_alive on an incoming SSH message
-reset_alive_ssh_params(SSH = #ssh{alive_interval = AliveInterval})
-  when is_integer(AliveInterval) ->
-    Now = erlang:monotonic_time(milli_seconds),
-    SSH#ssh{alive_sent_probes = 0,
-            last_alive_at     = Now};
-reset_alive_ssh_params(SSH) ->
-    SSH.
+reset_alive(D = #data{ssh_params = Ssh0}) ->
+    case Ssh0 of
+        #ssh{alive_interval = AliveInterval} when is_integer(AliveInterval) ->
+            Now = erlang:monotonic_time(milli_seconds),
+            Ssh = Ssh0#ssh{alive_sent_probes = 0, last_alive_at = Now},
+            D#data{ssh_params = Ssh};
+        _ -> D
+    end.
 
 %% Returns a pair of {TriggerFlag, Actions} where trigger flag indicates that
 %% the timeout has been triggered already and it is time to disconnect, and
@@ -2226,7 +2221,8 @@ triggered_alive(StateName, D0 = #data{},
     {Shutdown, D} = ?send_disconnect(?SSH_DISCONNECT_CONNECTION_LOST, Details, StateName, D0),
     {stop, Shutdown, D};
 triggered_alive(_StateName, Data, _Ssh = #ssh{alive_sent_probes = SentProbes}, Actions) ->
-    Data1 = send_msg(?KEEP_ALIVE_REQUEST, Data),
+    Data1 = send_msg({ssh_msg_global_request,"keepalive@erlang.org", true,<<>>},
+                     Data),
     Ssh = Data1#data.ssh_params,
     Now = erlang:monotonic_time(milli_seconds),
     Ssh1 = Ssh#ssh{alive_sent_probes = SentProbes + 1,
diff --git a/lib/ssh/src/ssh_options.erl b/lib/ssh/src/ssh_options.erl
index 31ebafcc56..8665732bf6 100644
--- a/lib/ssh/src/ssh_options.erl
+++ b/lib/ssh/src/ssh_options.erl
@@ -861,7 +861,7 @@ default(common) ->
             },
 
       alive_params =>
-          #{default => {0, infinity},
+          #{default => {3, infinity},
             chk => fun({AliveCount, AliveIntervalSeconds}) ->
                         check_pos_integer(AliveCount) andalso
                                check_timeout(AliveIntervalSeconds)
diff --git a/lib/ssh/test/ssh_protocol_SUITE.erl b/lib/ssh/test/ssh_protocol_SUITE.erl
index 914d9c1595..38e6ba50ad 100644
--- a/lib/ssh/test/ssh_protocol_SUITE.erl
+++ b/lib/ssh/test/ssh_protocol_SUITE.erl
@@ -60,6 +60,9 @@
          empty_service_name/1,
          ext_info_c/1,
          ext_info_s/1,
+         keep_alive_sent/1,
+         keep_alive_maxcount_exceeded/1,
+         keep_alive_renegotiate_timeout/1,
          kex_strict_negotiated/1,
          kex_strict_violation_key_exchange/1,
          kex_strict_violation_new_keys/1,
@@ -138,7 +141,8 @@ all() ->
      {group,ext_info},
      {group,preferred_algorithms},
      {group,client_close_early},
-     {group,channel_close}
+     {group,channel_close},
+     {group,keep_alive}
     ].
 
 groups() ->
@@ -190,7 +194,10 @@ groups() ->
                                  modify_combo
                                 ]},
      {client_close_early, [], [client_close_after_hello]},
-     {channel_close, [], [channel_close_timeout]}
+     {channel_close, [], [channel_close_timeout]},
+     {keep_alive, [], [keep_alive_sent,
+                       keep_alive_maxcount_exceeded,
+                       keep_alive_renegotiate_timeout]}
     ].
 
 
@@ -1495,6 +1502,98 @@ extra_ssh_msg_service_request(Config) ->
 	  ], EndState),
     ok.
 
+keep_alive_sent(Config) ->
+    User = "foo",
+    Pwd = "morot",
+    UserDir = user_dir(Config),
+    {Pid, Host, Port} = ssh_test_lib:daemon([{system_dir, system_dir(Config)},
+					     {user_dir, UserDir},
+					     {password, Pwd},
+					     {failfun, fun ssh_test_lib:failfun/2},
+					     {alive_params, {1,2}}]),
+
+    {ok,AfterUserAuthReqState} = connect_and_userauth_request(Host, Port, User, Pwd, UserDir),
+    {ok,EndState} =
+	ssh_trpt_test_lib:exec(
+	  [{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{}},
+           {match, #ssh_msg_global_request{name = <<"keepalive@erlang.org">>,
+                                           want_reply = true,
+                                           data = <<>>}, receive_msg},
+           %% Send success just to check that it works as well
+           {send, #ssh_msg_request_success{data = <<>>}},
+           {match, #ssh_msg_global_request{name = <<"keepalive@erlang.org">>,
+                                           want_reply = true,
+                                           data = <<>>}, receive_msg}
+	  ], AfterUserAuthReqState),
+
+    {ok,_} = trpt_test_lib_send_disconnect(EndState),
+
+    ssh:stop_daemon(Pid),
+    Config.
+
+keep_alive_maxcount_exceeded(Config) ->
+    User = "foo",
+    Pwd = "morot",
+    UserDir = user_dir(Config),
+    {Pid, Host, Port} = ssh_test_lib:daemon([{system_dir, system_dir(Config)},
+					     {user_dir, UserDir},
+					     {password, Pwd},
+					     {failfun, fun ssh_test_lib:failfun/2},
+					     {alive_params, {2,2}}]),
+
+    {ok,AfterUserAuthReqState} = connect_and_userauth_request(Host, Port, User, Pwd, UserDir),
+    {ok,EndState} =
+	ssh_trpt_test_lib:exec(
+	  [{match, #ssh_msg_userauth_success{_='_'}, receive_msg},
+           {match, #ssh_msg_global_request{name = <<"keepalive@erlang.org">>,
+                                           want_reply = true,
+                                           data = <<>>}, receive_msg},
+           {match, #ssh_msg_global_request{name = <<"keepalive@erlang.org">>,
+                                           want_reply = true,
+                                           data = <<>>}, receive_msg},
+           {match, #ssh_msg_disconnect{_='_'}, receive_msg}
+	  ], AfterUserAuthReqState),
+
+    {ok,_} = trpt_test_lib_send_disconnect(EndState),
+
+    ssh:stop_daemon(Pid),
+    Config.
+
+keep_alive_renegotiate_timeout(Config) ->
+    %% User = "foo",
+    %% Pwd = "morot",
+    %% UserDir = user_dir(Config),
+    %% {Pid, Host, Port} = ssh_test_lib:daemon([{system_dir, system_dir(Config)},
+    %%     				     {user_dir, UserDir},
+    %%     				     {password, Pwd},
+    %%     				     {failfun, fun ssh_test_lib:failfun/2},
+    %%     				     {alive_params, {2,2}}]),
+
+    %% {ok,AfterUserAuthReqState} = connect_and_userauth_request(Host, Port, User, Pwd, UserDir),
+    %% {ok,EndState} =
+    %%     ssh_trpt_test_lib:exec(
+    %%       [{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{}},
+    %%        {send, ssh_msg_kexinit},
+    %%        {match, #ssh_msg_global_request{name = <<"keepalive@erlang.org">>,
+    %%                                        want_reply = true,
+    %%                                        data = <<>>}, receive_msg}
+    %%       ], AfterUserAuthReqState),
+
+    %% {ok,_} = trpt_test_lib_send_disconnect(EndState),
+
+    %% ssh:stop_daemon(Pid),
+
+    %%% TODO: figure out why ssh_msg_kexinit can't be decoded by the server
+    Config.
+
 %%%================================================================
 %%%==== Internal functions ========================================
 %%%================================================================
-- 
2.51.0

openSUSE Build Service is sponsored by