9696-define (call_disconnectfun_and_log_cond (LogMsg , DetailedText , StateName , D ),
9797        call_disconnectfun_and_log_cond (LogMsg , DetailedText , ? MODULE , ? LINE , StateName , D )).
9898
99+ -define (KEEP_ALIVE_REQUEST ,
100+     {
ssh_msg_global_request ,
" [email protected] " , 
true ,<<>>}).
101+ -define (KEEP_ALIVE_RESPONSE_F , {ssh_msg_request_failure }).
102+ -define (KEEP_ALIVE_RESPONSE_S , {ssh_msg_request_success }).
103+ 
99104% %====================================================================
100105% % Start / stop
101106% %====================================================================
@@ -440,11 +445,18 @@ init_ssh_record(Role, Socket, Opts) ->
440445
441446init_ssh_record (Role , Socket , PeerAddr , Opts ) -> 
442447    AuthMethods  =  ? GET_OPT (auth_methods , Opts ),
448+     {AliveCount , AliveIntervalSeconds } =  ? GET_OPT (alive_params , Opts ),
449+     AliveInterval  =  case  AliveIntervalSeconds  of 
450+                         V  when  is_integer (V ) -> V  *  1000 ;
451+                         infinity  -> infinity 
452+                     end ,
443453    S0  =  # ssh {role  =  Role ,
444454	      opts  =  Opts ,
445455	      userauth_supported_methods  =  AuthMethods ,
446456	      available_host_keys  =  available_hkey_algorithms (Role , Opts ),
447- 	      random_length_padding  =  ? GET_OPT (max_random_length_padding , Opts )
457+ 	      random_length_padding  =  ? GET_OPT (max_random_length_padding , Opts ),
458+ 	      alive_interval  =  AliveInterval ,
459+ 	      alive_count  =  AliveCount 
448460	   },
449461
450462    {Vsn , Version } =  ssh_transport :versions (Role , Opts ),
@@ -750,6 +762,11 @@ handle_event(internal, #ssh_msg_debug{} = Msg, _StateName, D) ->
750762    debug_fun (Msg , D ),
751763    keep_state_and_data ;
752764
765+ handle_event (_ , {conn_msg , Msg }, _ , D  =  # data {ssh_params  =  Ssh })
766+   when  Ssh # ssh .awaiting_keepalive_response ,
767+        (Msg  =:=  ? KEEP_ALIVE_RESPONSE_F  orelse  Msg  =:=  ? KEEP_ALIVE_RESPONSE_S ) -> 
768+     {keep_state , D # data {ssh_params  =  Ssh # ssh {awaiting_keepalive_response  =  false }}};
769+ 
753770handle_event (internal , {conn_msg ,Msg }, StateName , # data {connection_state  =  Connection0 ,
754771                                                        event_queue  =  Qev0 } =  D0 ) -> 
755772    Role  =  ? role (StateName ),
@@ -831,6 +848,21 @@ handle_event({timeout,check_data_size}, _, StateName, D0) ->
831848            keep_state_and_data 
832849    end ;
833850
851+ handle_event ({timeout , alive }, _ , StateName , D  =  # data {ssh_params = Ssh }) -> 
852+     {TriggerFlag , Actions } =  get_next_alive_timeout (Ssh ),
853+     case  TriggerFlag  of 
854+         true  -> %  timeout occured
855+             triggered_alive (StateName , D , Ssh , Actions );
856+         false  -> %  no timeout, check later
857+             {keep_state , D , Actions }
858+     end ;
859+ 
860+ handle_event ({timeout , renegotiation_alive }, _ , StateName , D ) -> 
861+     Details  =  " Renegotiation alive timeout reached." 
862+     {Shutdown , D1 } =  ? send_disconnect (? SSH_DISCONNECT_CONNECTION_LOST , Details , StateName , D ),
863+     {stop , Shutdown , D1 };
864+ 
865+ 
834866handle_event ({call ,From }, get_alg , _ , D ) -> 
835867    # ssh {algorithms = Algs } =  D # data .ssh_params ,
836868    {keep_state_and_data , [{reply ,From ,Algs }]};
@@ -1140,15 +1172,16 @@ handle_event(info, {Proto, Sock, NewData}, StateName,
11401172             D0  =  # data {socket  =  Sock ,
11411173                        transport_protocol  =  Proto ,
11421174                        ssh_params  =  SshParams }) -> 
1175+     D1  =  reset_alive (D0 ),
11431176    try  ssh_transport :handle_packet_part (
1144- 	  D0 # data .decrypted_data_buffer ,
1145- 	  <<(D0 # data .encrypted_data_buffer )/binary , NewData /binary >>,
1146-           D0 # data .aead_data ,
1147-           D0 # data .undecrypted_packet_length ,
1148- 	  D0 # data .ssh_params )
1177+ 	  D1 # data .decrypted_data_buffer ,
1178+ 	  <<(D1 # data .encrypted_data_buffer )/binary , NewData /binary >>,
1179+           D1 # data .aead_data ,
1180+           D1 # data .undecrypted_packet_length ,
1181+ 	  D1 # data .ssh_params )
11491182    of 
11501183	{packet_decrypted , DecryptedBytes , EncryptedDataRest , Ssh1 } ->
1151- 	    D1  =  D0 # data {ssh_params  = 
1184+ 	    D2  =  D1 # data {ssh_params  = 
11521185                             Ssh1 # ssh {recv_sequence  = 
11531186                                          ssh_transport :next_seqnum (StateName ,
11541187                                                                    Ssh1 # ssh .recv_sequence ,
@@ -1158,33 +1191,33 @@ handle_event(info, {Proto, Sock, NewData}, StateName,
11581191                         aead_data  =  <<>>,
11591192                         encrypted_data_buffer  =  EncryptedDataRest },
11601193	    try 
1161- 		ssh_message :decode (set_kex_overload_prefix (DecryptedBytes ,D1 ))
1194+ 		ssh_message :decode (set_kex_overload_prefix (DecryptedBytes ,D2 ))
11621195	    of 
11631196		# ssh_msg_kexinit {} =  Msg  ->
1164- 		    {keep_state , D1 , [{next_event , internal , prepare_next_packet },
1197+ 		    {keep_state , D2 , [{next_event , internal , prepare_next_packet },
11651198				     {next_event , internal , {Msg ,DecryptedBytes }}
11661199				    ]};
11671200
1168-                 # ssh_msg_global_request {}            =  Msg  -> {keep_state , D1 , ? CONNECTION_MSG (Msg )};
1169-                 # ssh_msg_request_success {}           =  Msg  -> {keep_state , D1 , ? CONNECTION_MSG (Msg )};
1170-                 # ssh_msg_request_failure {}           =  Msg  -> {keep_state , D1 , ? CONNECTION_MSG (Msg )};
1171-                 # ssh_msg_channel_open {}              =  Msg  -> {keep_state , D1 ,
1201+                 # ssh_msg_global_request {}            =  Msg  -> {keep_state , D2 , ? CONNECTION_MSG (Msg )};
1202+                 # ssh_msg_request_success {}           =  Msg  -> {keep_state , D2 , ? CONNECTION_MSG (Msg )};
1203+                 # ssh_msg_request_failure {}           =  Msg  -> {keep_state , D2 , ? CONNECTION_MSG (Msg )};
1204+                 # ssh_msg_channel_open {}              =  Msg  -> {keep_state , D2 ,
11721205                                                               [{{timeout , max_initial_idle_time }, cancel } |
11731206                                                                ? CONNECTION_MSG (Msg )
11741207                                                               ]};
1175-                 # ssh_msg_channel_open_confirmation {} =  Msg  -> {keep_state , D1 , ? CONNECTION_MSG (Msg )};
1176-                 # ssh_msg_channel_open_failure {}      =  Msg  -> {keep_state , D1 , ? CONNECTION_MSG (Msg )};
1177-                 # ssh_msg_channel_window_adjust {}     =  Msg  -> {keep_state , D1 , ? CONNECTION_MSG (Msg )};
1178-                 # ssh_msg_channel_data {}              =  Msg  -> {keep_state , D1 , ? CONNECTION_MSG (Msg )};
1179-                 # ssh_msg_channel_extended_data {}     =  Msg  -> {keep_state , D1 , ? CONNECTION_MSG (Msg )};
1180-                 # ssh_msg_channel_eof {}               =  Msg  -> {keep_state , D1 , ? CONNECTION_MSG (Msg )};
1181-                 # ssh_msg_channel_close {}             =  Msg  -> {keep_state , D1 , ? CONNECTION_MSG (Msg )};
1182-                 # ssh_msg_channel_request {}           =  Msg  -> {keep_state , D1 , ? CONNECTION_MSG (Msg )};
1183-                 # ssh_msg_channel_failure {}           =  Msg  -> {keep_state , D1 , ? CONNECTION_MSG (Msg )};
1184-                 # ssh_msg_channel_success {}           =  Msg  -> {keep_state , D1 , ? CONNECTION_MSG (Msg )};
1208+                 # ssh_msg_channel_open_confirmation {} =  Msg  -> {keep_state , D2 , ? CONNECTION_MSG (Msg )};
1209+                 # ssh_msg_channel_open_failure {}      =  Msg  -> {keep_state , D2 , ? CONNECTION_MSG (Msg )};
1210+                 # ssh_msg_channel_window_adjust {}     =  Msg  -> {keep_state , D2 , ? CONNECTION_MSG (Msg )};
1211+                 # ssh_msg_channel_data {}              =  Msg  -> {keep_state , D2 , ? CONNECTION_MSG (Msg )};
1212+                 # ssh_msg_channel_extended_data {}     =  Msg  -> {keep_state , D2 , ? CONNECTION_MSG (Msg )};
1213+                 # ssh_msg_channel_eof {}               =  Msg  -> {keep_state , D2 , ? CONNECTION_MSG (Msg )};
1214+                 # ssh_msg_channel_close {}             =  Msg  -> {keep_state , D2 , ? CONNECTION_MSG (Msg )};
1215+                 # ssh_msg_channel_request {}           =  Msg  -> {keep_state , D2 , ? CONNECTION_MSG (Msg )};
1216+                 # ssh_msg_channel_failure {}           =  Msg  -> {keep_state , D2 , ? CONNECTION_MSG (Msg )};
1217+                 # ssh_msg_channel_success {}           =  Msg  -> {keep_state , D2 , ? CONNECTION_MSG (Msg )};
11851218
11861219		Msg  ->
1187- 		    {keep_state , D1 , [{next_event , internal , prepare_next_packet },
1220+ 		    {keep_state , D2 , [{next_event , internal , prepare_next_packet },
11881221                                      {next_event , internal , Msg }
11891222				    ]}
11901223	    catch 
@@ -1194,15 +1227,15 @@ handle_event(info, {Proto, Sock, NewData}, StateName,
11941227                        ? send_disconnect (? SSH_DISCONNECT_PROTOCOL_ERROR ,
11951228                                         io_lib :format (" Bad packet: Decrypted, but can't decode~n~p :~p~n~p " 
11961229                                                       [C ,E ,ST ], [{chars_limit , MaxLogItemLen }]),
1197-                                          StateName , D1 ),
1230+                                          StateName , D2 ),
11981231                    {stop , Shutdown , D }
11991232	    end ;
12001233
12011234	{get_more , DecryptedBytes , EncryptedDataRest , AeadData , RemainingSshPacketLen , Ssh1 } ->
12021235	    % % Here we know that there are not enough bytes in
12031236	    % % EncryptedDataRest to use. We must wait for more.
12041237	    inet :setopts (Sock , [{active , once }]),
1205- 	    {keep_state , D0 # data {encrypted_data_buffer  =  EncryptedDataRest ,
1238+ 	    {keep_state , D1 # data {encrypted_data_buffer  =  EncryptedDataRest ,
12061239				 decrypted_data_buffer  =  DecryptedBytes ,
12071240                                 undecrypted_packet_length  =  RemainingSshPacketLen ,
12081241                                 aead_data  =  AeadData ,
@@ -1212,15 +1245,15 @@ handle_event(info, {Proto, Sock, NewData}, StateName,
12121245            {Shutdown , D } = 
12131246                ? send_disconnect (? SSH_DISCONNECT_PROTOCOL_ERROR ,
12141247                                 " Bad packet: bad mac" 
1215-                                  StateName , D0 # data {ssh_params = Ssh1 }),
1248+                                  StateName , D1 # data {ssh_params = Ssh1 }),
12161249            {stop , Shutdown , D };
12171250
12181251	{error , {exceeds_max_size ,PacketLen }} ->
12191252            {Shutdown , D } = 
12201253                ? send_disconnect (? SSH_DISCONNECT_PROTOCOL_ERROR ,
12211254                                 io_lib :format (" Bad packet: Size (~p  bytes) exceeds max size" 
12221255                                               [PacketLen ]),
1223-                                  StateName , D0 ),
1256+                                  StateName , D1 ),
12241257            {stop , Shutdown , D }
12251258    catch 
12261259	C :E :ST  ->
@@ -1229,7 +1262,7 @@ handle_event(info, {Proto, Sock, NewData}, StateName,
12291262                ? send_disconnect (? SSH_DISCONNECT_PROTOCOL_ERROR ,
12301263                                 io_lib :format (" Bad packet: Couldn't decrypt~n~p :~p~n~p " 
12311264                                               [C ,E ,ST ], [{chars_limit , MaxLogItemLen }]),
1232-                                  StateName , D0 ),
1265+                                  StateName , D1 ),
12331266            {stop , Shutdown , D }
12341267    end ;
12351268
@@ -1785,7 +1818,10 @@ start_rekeying(Role, D0) ->
17851818    send_bytes (SshPacket , D0 ),
17861819    D  =  D0 # data {ssh_params  =  Ssh ,
17871820                key_exchange_init_msg  =  KeyInitMsg },
1788-     {next_state , {kexinit ,Role ,renegotiate }, D , {change_callback_module ,ssh_fsm_kexinit }}.
1821+     {next_state , {kexinit ,Role ,renegotiate }, D ,
1822+      [{change_callback_module ,ssh_fsm_kexinit },
1823+       {{timeout , alive }, cancel },
1824+       {{timeout , renegotiation_alive }, renegotiation_alive_timeout (Ssh ), none }]}.
17891825
17901826
17911827init_renegotiate_timers (_OldState , NewState , D ) -> 
@@ -2131,6 +2167,65 @@ update_inet_buffers(Socket) ->
21312167        _ :_  -> ok 
21322168    end .
21332169
2170+ % %%----------------------------------------------------------------
2171+ % %% Keep-alive
2172+ 
2173+ % % @doc Reset the last_alive timer on #data{ssh_params=#ssh{}} record
2174+ % % @private
2175+ reset_alive (D  =  # data {ssh_params  =  Ssh }) -> 
2176+     D # data {ssh_params  =  reset_alive_ssh_params (Ssh )}.
2177+ 
2178+ % % @doc Update #data.ssh_params last_alive on an incoming SSH message
2179+ % % @private
2180+ reset_alive_ssh_params (SSH  =  # ssh {alive_interval  =  AliveInterval })
2181+   when  is_integer (AliveInterval ) -> 
2182+     Now  =  erlang :monotonic_time (milli_seconds ),
2183+     SSH # ssh {alive_sent_probes  =  0 ,
2184+             last_alive_at      =  Now };
2185+ reset_alive_ssh_params (SSH ) -> 
2186+     SSH .
2187+ 
2188+ % % @doc Returns a pair of {TriggerFlag, Actions} where trigger flag indicates that
2189+ % % the timeout has been triggered already and it is time to disconnect, and
2190+ % % Actions may contain a new timeout action to check for the timeout again.
2191+ get_next_alive_timeout (# ssh {alive_interval  =  AliveInterval ,
2192+                             last_alive_at   =  LastAlive })
2193+     when  erlang :is_integer (AliveInterval ) -> 
2194+     TimeToNextAlive  =  AliveInterval  -  (erlang :monotonic_time (milli_seconds ) -  LastAlive ),
2195+     case  TimeToNextAlive  of 
2196+         Trigger  when  Trigger  =<  0  ->
2197+             % % Already it is time to disconnect, or to ping
2198+             {true , [{{timeout , alive }, AliveInterval , none }]};
2199+         TimeToNextAlive  ->
2200+             {false , [{{timeout , alive }, TimeToNextAlive , none }]}
2201+     end ;
2202+ get_next_alive_timeout (_ ) -> 
2203+     {false , []}.
2204+ 
2205+ triggered_alive (StateName , D0  =  # data {},
2206+                 # ssh {alive_count        =  Count ,
2207+                      alive_sent_probes  =  SentProbesCount }, _Actions )
2208+     when  SentProbesCount  >=  Count  -> 
2209+     % % Max probes count reached (equal to `alive_count`), we disconnect
2210+     Details  =  " Alive timeout triggered" 
2211+     {Shutdown , D } =  ? send_disconnect (? SSH_DISCONNECT_CONNECTION_LOST , Details , StateName , D0 ),
2212+     {stop , Shutdown , D };
2213+ 
2214+ triggered_alive (_StateName , Data , _Ssh  =  # ssh {alive_sent_probes  =  SentProbes }, Actions ) -> 
2215+     Data1  =  send_msg (? KEEP_ALIVE_REQUEST , Data ),
2216+     Ssh  =  Data1 # data .ssh_params ,
2217+     Now  =  erlang :monotonic_time (milli_seconds ),
2218+     Ssh1  =  Ssh # ssh {alive_sent_probes  =  SentProbes  +  1 ,
2219+                    awaiting_keepalive_response  =  true ,
2220+                    last_alive_at  =  Now },
2221+     {keep_state , Data1 # data {ssh_params  =  Ssh1 }, Actions }.
2222+ 
2223+ renegotiation_alive_timeout (# ssh {alive_interval  =  infinity }) -> 
2224+     infinity ;
2225+ renegotiation_alive_timeout (# ssh {alive_interval  =  Interval , alive_count  =  Count }) -> 
2226+     Interval  *  Count .
2227+ 
2228+ 
21342229% %%################################################################
21352230% %%#
21362231% %%# Tracing
0 commit comments