File 4471-ssh-ssh-keep-alive.patch of Package erlang

From a7107fef0870d79f694a8c6fd19ec9112c0e7a5f Mon Sep 17 00:00:00 2001
From: Alexandre Rodrigues <alexandrejbr@live.com>
Date: Sun, 24 Nov 2024 21:45:23 +0100
Subject: [PATCH 01/20] ssh: ssh keep alive

---
 lib/ssh/src/ssh.hrl                     |   9 +-
 lib/ssh/src/ssh_connection_handler.erl  | 155 +++++++++++++++++++-----
 lib/ssh/src/ssh_fsm_kexinit.erl         |   4 +-
 lib/ssh/src/ssh_fsm_userauth_client.erl |   5 +-
 lib/ssh/src/ssh_fsm_userauth_server.erl |  16 ++-
 lib/ssh/src/ssh_options.erl             |   9 ++
 6 files changed, 159 insertions(+), 39 deletions(-)

diff --git a/lib/ssh/src/ssh.hrl b/lib/ssh/src/ssh.hrl
index ad8b831985..7b9c292d63 100644
--- a/lib/ssh/src/ssh.hrl
+++ b/lib/ssh/src/ssh.hrl
@@ -1278,7 +1278,14 @@ Experimental options that should not to be used in products.
 	  available_host_keys,
 	  pwdfun_user_state,
 	  authenticated = false,
-	  userauth_banner_sent = false
+	  userauth_banner_sent = false,
+          %% Keep-alive
+          alive_interval = infinity           :: non_neg_integer() | infinity,
+          alive_count = 0                     :: non_neg_integer(),
+          alive_started = false               :: boolean(),
+          last_alive_at = 0                   :: non_neg_integer(),
+          awaiting_keepalive_response = false :: boolean(),
+          alive_sent_probes = 0               :: non_neg_integer()
 	 }).
 
 -record(alg,
diff --git a/lib/ssh/src/ssh_connection_handler.erl b/lib/ssh/src/ssh_connection_handler.erl
index eac77f6d8b..855783b7c7 100644
--- a/lib/ssh/src/ssh_connection_handler.erl
+++ b/lib/ssh/src/ssh_connection_handler.erl
@@ -96,6 +96,11 @@
 -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
 %%====================================================================
@@ -440,11 +445,18 @@ init_ssh_record(Role, Socket, Opts) ->
 
 init_ssh_record(Role, Socket, PeerAddr, Opts) ->
     AuthMethods = ?GET_OPT(auth_methods, Opts),
+    {AliveCount, AliveIntervalSeconds} = ?GET_OPT(alive_params, Opts),
+    AliveInterval = case AliveIntervalSeconds of
+                        V when is_integer(V) -> V * 1000;
+                        infinity -> infinity
+                    end,
     S0 = #ssh{role = Role,
 	      opts = Opts,
 	      userauth_supported_methods = AuthMethods,
 	      available_host_keys = available_hkey_algorithms(Role, Opts),
-	      random_length_padding = ?GET_OPT(max_random_length_padding, Opts)
+	      random_length_padding = ?GET_OPT(max_random_length_padding, Opts),
+	      alive_interval = AliveInterval,
+	      alive_count = AliveCount
 	   },
 
     {Vsn, Version} = ssh_transport:versions(Role, Opts),
@@ -750,6 +762,11 @@ 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) ->
+    {keep_state, D#data{ssh_params = Ssh#ssh{awaiting_keepalive_response = false}}};
+
 handle_event(internal, {conn_msg,Msg}, StateName, #data{connection_state = Connection0,
                                                         event_queue = Qev0} = D0) ->
     Role = ?role(StateName),
@@ -831,6 +848,21 @@ handle_event({timeout,check_data_size}, _, StateName, D0) ->
             keep_state_and_data
     end;
 
+handle_event({timeout, alive}, _, StateName, D = #data{ssh_params=Ssh}) ->
+    {TriggerFlag, Actions} = get_next_alive_timeout(Ssh),
+    case TriggerFlag of
+        true -> % timeout occured
+            triggered_alive(StateName, D, Ssh, Actions);
+        false -> % no timeout, check later
+            {keep_state, D, Actions}
+    end;
+
+handle_event({timeout, renegotiation_alive}, _, StateName, D) ->
+    Details = "Renegotiation alive timeout reached.",
+    {Shutdown, D1} = ?send_disconnect(?SSH_DISCONNECT_CONNECTION_LOST, Details, StateName, D),
+    {stop, Shutdown, D1};
+
+
 handle_event({call,From}, get_alg, _, D) ->
     #ssh{algorithms=Algs} = D#data.ssh_params,
     {keep_state_and_data, [{reply,From,Algs}]};
@@ -1140,15 +1172,16 @@ handle_event(info, {Proto, Sock, NewData}, StateName,
              D0 = #data{socket = Sock,
                         transport_protocol = Proto,
                         ssh_params = SshParams}) ->
+    D1 = reset_alive(D0),
     try ssh_transport:handle_packet_part(
-	  D0#data.decrypted_data_buffer,
-	  <<(D0#data.encrypted_data_buffer)/binary, NewData/binary>>,
-          D0#data.aead_data,
-          D0#data.undecrypted_packet_length,
-	  D0#data.ssh_params)
+	  D1#data.decrypted_data_buffer,
+	  <<(D1#data.encrypted_data_buffer)/binary, NewData/binary>>,
+          D1#data.aead_data,
+          D1#data.undecrypted_packet_length,
+	  D1#data.ssh_params)
     of
 	{packet_decrypted, DecryptedBytes, EncryptedDataRest, Ssh1} ->
-	    D1 = D0#data{ssh_params =
+	    D2 = D1#data{ssh_params =
                              Ssh1#ssh{recv_sequence =
                                           ssh_transport:next_seqnum(StateName,
                                                                     Ssh1#ssh.recv_sequence,
@@ -1158,33 +1191,33 @@ handle_event(info, {Proto, Sock, NewData}, StateName,
                          aead_data = <<>>,
                          encrypted_data_buffer = EncryptedDataRest},
 	    try
-		ssh_message:decode(set_kex_overload_prefix(DecryptedBytes,D1))
+		ssh_message:decode(set_kex_overload_prefix(DecryptedBytes,D2))
 	    of
 		#ssh_msg_kexinit{} = Msg ->
-		    {keep_state, D1, [{next_event, internal, prepare_next_packet},
+		    {keep_state, D2, [{next_event, internal, prepare_next_packet},
 				     {next_event, internal, {Msg,DecryptedBytes}}
 				    ]};
 
-                #ssh_msg_global_request{}            = Msg -> {keep_state, D1, ?CONNECTION_MSG(Msg)};
-                #ssh_msg_request_success{}           = Msg -> {keep_state, D1, ?CONNECTION_MSG(Msg)};
-                #ssh_msg_request_failure{}           = Msg -> {keep_state, D1, ?CONNECTION_MSG(Msg)};
-                #ssh_msg_channel_open{}              = Msg -> {keep_state, D1,
+                #ssh_msg_global_request{}            = Msg -> {keep_state, D2, ?CONNECTION_MSG(Msg)};
+                #ssh_msg_request_success{}           = Msg -> {keep_state, D2, ?CONNECTION_MSG(Msg)};
+                #ssh_msg_request_failure{}           = Msg -> {keep_state, D2, ?CONNECTION_MSG(Msg)};
+                #ssh_msg_channel_open{}              = Msg -> {keep_state, D2,
                                                                [{{timeout, max_initial_idle_time}, cancel} |
                                                                 ?CONNECTION_MSG(Msg)
                                                                ]};
-                #ssh_msg_channel_open_confirmation{} = Msg -> {keep_state, D1, ?CONNECTION_MSG(Msg)};
-                #ssh_msg_channel_open_failure{}      = Msg -> {keep_state, D1, ?CONNECTION_MSG(Msg)};
-                #ssh_msg_channel_window_adjust{}     = Msg -> {keep_state, D1, ?CONNECTION_MSG(Msg)};
-                #ssh_msg_channel_data{}              = Msg -> {keep_state, D1, ?CONNECTION_MSG(Msg)};
-                #ssh_msg_channel_extended_data{}     = Msg -> {keep_state, D1, ?CONNECTION_MSG(Msg)};
-                #ssh_msg_channel_eof{}               = Msg -> {keep_state, D1, ?CONNECTION_MSG(Msg)};
-                #ssh_msg_channel_close{}             = Msg -> {keep_state, D1, ?CONNECTION_MSG(Msg)};
-                #ssh_msg_channel_request{}           = Msg -> {keep_state, D1, ?CONNECTION_MSG(Msg)};
-                #ssh_msg_channel_failure{}           = Msg -> {keep_state, D1, ?CONNECTION_MSG(Msg)};
-                #ssh_msg_channel_success{}           = Msg -> {keep_state, D1, ?CONNECTION_MSG(Msg)};
+                #ssh_msg_channel_open_confirmation{} = Msg -> {keep_state, D2, ?CONNECTION_MSG(Msg)};
+                #ssh_msg_channel_open_failure{}      = Msg -> {keep_state, D2, ?CONNECTION_MSG(Msg)};
+                #ssh_msg_channel_window_adjust{}     = Msg -> {keep_state, D2, ?CONNECTION_MSG(Msg)};
+                #ssh_msg_channel_data{}              = Msg -> {keep_state, D2, ?CONNECTION_MSG(Msg)};
+                #ssh_msg_channel_extended_data{}     = Msg -> {keep_state, D2, ?CONNECTION_MSG(Msg)};
+                #ssh_msg_channel_eof{}               = Msg -> {keep_state, D2, ?CONNECTION_MSG(Msg)};
+                #ssh_msg_channel_close{}             = Msg -> {keep_state, D2, ?CONNECTION_MSG(Msg)};
+                #ssh_msg_channel_request{}           = Msg -> {keep_state, D2, ?CONNECTION_MSG(Msg)};
+                #ssh_msg_channel_failure{}           = Msg -> {keep_state, D2, ?CONNECTION_MSG(Msg)};
+                #ssh_msg_channel_success{}           = Msg -> {keep_state, D2, ?CONNECTION_MSG(Msg)};
 
 		Msg ->
-		    {keep_state, D1, [{next_event, internal, prepare_next_packet},
+		    {keep_state, D2, [{next_event, internal, prepare_next_packet},
                                       {next_event, internal, Msg}
 				    ]}
 	    catch
@@ -1203,7 +1236,7 @@ handle_event(info, {Proto, Sock, NewData}, StateName,
                     {Shutdown, D} =
                         ?send_disconnect(?SSH_DISCONNECT_PROTOCOL_ERROR,
                                          ?SELECT_MSG(MsgFun),
-                                         StateName, D1),
+                                         StateName, D2),
                     {stop, Shutdown, D}
 	    end;
 
@@ -1211,7 +1244,7 @@ handle_event(info, {Proto, Sock, NewData}, StateName,
 	    %% Here we know that there are not enough bytes in
 	    %% EncryptedDataRest to use. We must wait for more.
 	    inet:setopts(Sock, [{active, once}]),
-	    {keep_state, D0#data{encrypted_data_buffer = EncryptedDataRest,
+	    {keep_state, D1#data{encrypted_data_buffer = EncryptedDataRest,
 				 decrypted_data_buffer = DecryptedBytes,
                                  undecrypted_packet_length = RemainingSshPacketLen,
                                  aead_data = AeadData,
@@ -1221,7 +1254,7 @@ handle_event(info, {Proto, Sock, NewData}, StateName,
             {Shutdown, D} =
                 ?send_disconnect(?SSH_DISCONNECT_PROTOCOL_ERROR,
                                  "Bad packet: bad mac",
-                                 StateName, D0#data{ssh_params=Ssh1}),
+                                 StateName, D1#data{ssh_params=Ssh1}),
             {stop, Shutdown, D};
 
 	{error, {exceeds_max_size,PacketLen}} ->
@@ -1229,7 +1262,7 @@ handle_event(info, {Proto, Sock, NewData}, StateName,
                 ?send_disconnect(?SSH_DISCONNECT_PROTOCOL_ERROR,
                                  io_lib:format("Bad packet: Size (~p bytes) exceeds max size",
                                                [PacketLen]),
-                                 StateName, D0),
+                                 StateName, D1),
             {stop, Shutdown, D}
     catch
 	Class:Reason0:Stacktrace ->
@@ -1246,7 +1279,7 @@ handle_event(info, {Proto, Sock, NewData}, StateName,
                 end,
             {Shutdown, D} =
                 ?send_disconnect(?SSH_DISCONNECT_PROTOCOL_ERROR, ?SELECT_MSG(MsgFun),
-                                 StateName, D0),
+                                 StateName, D1),
             {stop, Shutdown, D}
     end;
 
@@ -1802,7 +1835,10 @@ start_rekeying(Role, D0) ->
     send_bytes(SshPacket, D0),
     D = D0#data{ssh_params = Ssh,
                 key_exchange_init_msg = KeyInitMsg},
-    {next_state, {kexinit,Role,renegotiate}, D, {change_callback_module,ssh_fsm_kexinit}}.
+    {next_state, {kexinit,Role,renegotiate}, D,
+     [{change_callback_module,ssh_fsm_kexinit},
+      {{timeout, alive}, cancel},
+      {{timeout, renegotiation_alive}, renegotiation_alive_timeout(Ssh), none}]}.
 
 
 init_renegotiate_timers(_OldState, NewState, D) ->
@@ -2148,6 +2184,65 @@ update_inet_buffers(Socket) ->
         _:_ -> ok
     end.
 
+%%%----------------------------------------------------------------
+%%% Keep-alive
+
+%% @doc Reset the last_alive timer on #data{ssh_params=#ssh{}} record
+%% @private
+reset_alive(D = #data{ssh_params = Ssh}) ->
+    D#data{ssh_params = reset_alive_ssh_params(Ssh)}.
+
+%% @doc Update #data.ssh_params last_alive on an incoming SSH message
+%% @private
+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.
+
+%% @doc Returns a pair of {TriggerFlag, Actions} where trigger flag indicates that
+%% the timeout has been triggered already and it is time to disconnect, and
+%% Actions may contain a new timeout action to check for the timeout again.
+get_next_alive_timeout(#ssh{alive_interval = AliveInterval,
+                            last_alive_at  = LastAlive})
+    when erlang:is_integer(AliveInterval) ->
+    TimeToNextAlive = AliveInterval - (erlang:monotonic_time(milli_seconds) - LastAlive),
+    case TimeToNextAlive of
+        Trigger when Trigger =< 0 ->
+            %% Already it is time to disconnect, or to ping
+            {true, [{{timeout, alive}, AliveInterval, none}]};
+        TimeToNextAlive ->
+            {false, [{{timeout, alive}, TimeToNextAlive, none}]}
+    end;
+get_next_alive_timeout(_) ->
+    {false, []}.
+
+triggered_alive(StateName, D0 = #data{},
+                #ssh{alive_count       = Count,
+                     alive_sent_probes = SentProbesCount}, _Actions)
+    when SentProbesCount >= Count ->
+    %% Max probes count reached (equal to `alive_count`), we disconnect
+    Details = "Alive timeout triggered",
+    {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),
+    Ssh = Data1#data.ssh_params,
+    Now = erlang:monotonic_time(milli_seconds),
+    Ssh1 = Ssh#ssh{alive_sent_probes = SentProbes + 1,
+                   awaiting_keepalive_response = true,
+                   last_alive_at = Now},
+    {keep_state, Data1#data{ssh_params = Ssh1}, Actions}.
+
+renegotiation_alive_timeout(#ssh{alive_interval = infinity}) ->
+    infinity;
+renegotiation_alive_timeout(#ssh{alive_interval = Interval, alive_count = Count}) ->
+    Interval * Count.
+
+
 %%%################################################################
 %%%#
 %%%# Tracing
diff --git a/lib/ssh/src/ssh_fsm_kexinit.erl b/lib/ssh/src/ssh_fsm_kexinit.erl
index 319d9fd712..9b28326dff 100644
--- a/lib/ssh/src/ssh_fsm_kexinit.erl
+++ b/lib/ssh/src/ssh_fsm_kexinit.erl
@@ -215,7 +215,9 @@ handle_event(internal, #ssh_msg_newkeys{} = Msg, {new_keys,Role,renegotiate}, D)
     {ok, Ssh} = ssh_transport:handle_new_keys(Msg, D#data.ssh_params),
     %% {ok, ExtInfo, Ssh} = ssh_transport:ext_info_message(Ssh1),
     %% ssh_connection_handler:send_bytes(ExtInfo, D),
-    {next_state, {ext_info,Role,renegotiate}, D#data{ssh_params=Ssh}};
+    {next_state, {ext_info,Role,renegotiate}, D#data{ssh_params=Ssh},
+     [{{timeout, alive}, Ssh#ssh.alive_interval, none},
+      {{timeout, renegotiation_alive}, cancel}]};
 
 
 %%% ######## {ext_info, client|server, init|renegotiate} ####
diff --git a/lib/ssh/src/ssh_fsm_userauth_client.erl b/lib/ssh/src/ssh_fsm_userauth_client.erl
index 47b93f56c0..43e2a86447 100644
--- a/lib/ssh/src/ssh_fsm_userauth_client.erl
+++ b/lib/ssh/src/ssh_fsm_userauth_client.erl
@@ -69,7 +69,10 @@ handle_event(internal, #ssh_msg_userauth_success{}, {userauth,client}, D0=#data{
     ssh_auth:ssh_msg_userauth_result(success),
     ssh_connection_handler:handshake(ssh_connected, D0),
     D = D0#data{ssh_params=Ssh#ssh{authenticated = true}},
-    {next_state, {connected,client}, D, {change_callback_module,ssh_connection_handler}};
+    {next_state, {connected,client}, D,
+     [{{timeout, alive}, Ssh#ssh.alive_interval, none},
+      {change_callback_module,ssh_connection_handler}]};
+
 
 
 %%---- userauth failure response to clientfrom the server
diff --git a/lib/ssh/src/ssh_fsm_userauth_server.erl b/lib/ssh/src/ssh_fsm_userauth_server.erl
index 435f45835e..a5a1b123a3 100644
--- a/lib/ssh/src/ssh_fsm_userauth_server.erl
+++ b/lib/ssh/src/ssh_fsm_userauth_server.erl
@@ -93,9 +93,9 @@ handle_event(internal,
 			{authorized, User, {Reply, Ssh1}} ->
                             D = connected_state(Reply, Ssh1, User, Method, D1),
                             {next_state, {connected,server}, D,
-                             [set_max_initial_idle_timeout(D),
+                             start_alive(D, [set_max_initial_idle_timeout(D),
                               {change_callback_module,ssh_connection_handler}
-                             ]};
+                             ])};
 			{not_authorized, {User, Reason}, {Reply, Ssh}} when Method == "keyboard-interactive" ->
 			    retry_fun(User, Reason, D1),
                             D = ssh_connection_handler:send_msg(Reply, D1#data{ssh_params = Ssh}),
@@ -129,9 +129,9 @@ handle_event(internal, #ssh_msg_userauth_info_response{} = Msg, {userauth_keyboa
 	{authorized, User, {Reply, Ssh1}} ->
             D = connected_state(Reply, Ssh1, User, "keyboard-interactive", D0),
             {next_state, {connected,server}, D,
-             [set_max_initial_idle_timeout(D),
+             start_alive(D, [set_max_initial_idle_timeout(D),
               {change_callback_module,ssh_connection_handler}
-             ]};
+             ])};
 	{not_authorized, {User, Reason}, {Reply, Ssh}} ->
 	    retry_fun(User, Reason, D0),
             D = ssh_connection_handler:send_msg(Reply, D0#data{ssh_params = Ssh}),
@@ -147,9 +147,9 @@ handle_event(internal, #ssh_msg_userauth_info_response{} = Msg, {userauth_keyboa
         ssh_auth:handle_userauth_info_response({extra,Msg}, D0#data.ssh_params),
     D = connected_state(Reply, Ssh1, User, "keyboard-interactive", D0),
     {next_state, {connected,server}, D,
-     [set_max_initial_idle_timeout(D),
+     start_alive(D, [set_max_initial_idle_timeout(D),
       {change_callback_module,ssh_connection_handler}
-     ]
+     ])
     };
 
 
@@ -230,3 +230,7 @@ maybe_send_banner(D0 = #data{ssh_params = #ssh{userauth_banner_sent = false} = S
     end;
 maybe_send_banner(D, _) ->
     D.
+
+start_alive(#data{ssh_params = #ssh{alive_interval = AliveInterval}},
+            Actions) ->
+    [{{timeout, alive}, AliveInterval, none} | Actions].
diff --git a/lib/ssh/src/ssh_options.erl b/lib/ssh/src/ssh_options.erl
index f2a71b9a97..31ebafcc56 100644
--- a/lib/ssh/src/ssh_options.erl
+++ b/lib/ssh/src/ssh_options.erl
@@ -860,6 +860,15 @@ default(common) ->
              class => user_option
             },
 
+      alive_params =>
+          #{default => {0, infinity},
+            chk => fun({AliveCount, AliveIntervalSeconds}) ->
+                        check_pos_integer(AliveCount) andalso
+                               check_timeout(AliveIntervalSeconds)
+                   end,
+            class => user_option
+           },
+
 %%%%% Undocumented
        transport =>
            #{default => ?DEFAULT_TRANSPORT,
-- 
2.51.0

openSUSE Build Service is sponsored by