File 4488-ssh-alive-messages-processed-in-ssh_connection.patch of Package erlang
From 9b5b0d2424be422e8e7ed2f75d84b86b726ab0b5 Mon Sep 17 00:00:00 2001
From: Jakub Witczak <kuba@erlang.org>
Date: Fri, 24 Oct 2025 14:44:20 +0200
Subject: [PATCH 18/20] ssh: alive messages processed in ssh_connection
- use alive in ssh_to_openssh_SUITE for Erlang implementation
- drop alive_awaiting_response flag
- don't process ssh_msg_request_success and ssh_msg_request_failure
outside of ssh_connectio module
---
lib/ssh/src/ssh.hrl | 1 -
lib/ssh/src/ssh_connection.erl | 12 ++++++++++-
lib/ssh/src/ssh_connection_handler.erl | 28 ++++++++-----------------
lib/ssh/test/ssh_test_lib.erl | 3 ++-
lib/ssh/test/ssh_to_openssh_SUITE.erl | 29 +++++++++++++++++++++++---
lib/ssh/test/ssh_trpt_test_lib.erl | 6 +++---
6 files changed, 51 insertions(+), 28 deletions(-)
diff --git a/lib/ssh/src/ssh.hrl b/lib/ssh/src/ssh.hrl
index 52a501447a..414e666cad 100644
--- a/lib/ssh/src/ssh.hrl
+++ b/lib/ssh/src/ssh.hrl
@@ -1307,7 +1307,6 @@ Experimental options that should not to be used in products.
userauth_banner_sent = false,
%% Keep-alive
alive_last_sent_at = 0 :: non_neg_integer(),
- alive_awaiting_response = false :: boolean(),
alive_probes_sent = 0 :: non_neg_integer()
}).
diff --git a/lib/ssh/src/ssh_connection.erl b/lib/ssh/src/ssh_connection.erl
index 44327a1081..a3a6c49618 100644
--- a/lib/ssh/src/ssh_connection.erl
+++ b/lib/ssh/src/ssh_connection.erl
@@ -1310,7 +1310,17 @@ handle_msg(#ssh_msg_request_success{data = Data},
#connection{requests = [{_, From, Fun} | Rest]} = Connection0, _, _SSH) ->
Connection = Fun({success,Data}, Connection0),
{[{channel_request_reply, From, {success, Data}}],
- Connection#connection{requests = Rest}}.
+ Connection#connection{requests = Rest}};
+
+%% alive responses
+handle_msg(#ssh_msg_request_success{},
+ #connection{requests = []} = Connection, _, _SSH) ->
+ {[], Connection};
+
+handle_msg(#ssh_msg_request_failure{},
+ #connection{requests = []} = Connection, _, _SSH) ->
+ {[], Connection}.
+
%%%----------------------------------------------------------------
diff --git a/lib/ssh/src/ssh_connection_handler.erl b/lib/ssh/src/ssh_connection_handler.erl
index eacd4550b0..b323287d1d 100644
--- a/lib/ssh/src/ssh_connection_handler.erl
+++ b/lib/ssh/src/ssh_connection_handler.erl
@@ -577,7 +577,7 @@ renegotiation(_) -> false.
-define(CONNECTION_MSG(Msg),
[{next_event, internal, prepare_next_packet},
- {next_event,internal,{conn_msg,Msg}}]).
+ {next_event, internal, {conn_msg,Msg}}]).
%% . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . .
callback_mode() ->
@@ -754,16 +754,8 @@ handle_event(internal, #ssh_msg_debug{} = Msg, _StateName, D) ->
debug_fun(Msg, D),
keep_state_and_data;
-handle_event(internal, {conn_msg, #ssh_msg_request_failure{}}, _, D = #data{ssh_params = Ssh})
- when Ssh#ssh.alive_awaiting_response ->
- {keep_state, D#data{ssh_params = Ssh#ssh{alive_awaiting_response = false}}};
-
-handle_event(internal, {conn_msg, #ssh_msg_request_success{}}, _, D = #data{ssh_params = Ssh})
- when Ssh#ssh.alive_awaiting_response ->
- {keep_state, D#data{ssh_params = Ssh#ssh{alive_awaiting_response = false}}};
-
-handle_event(internal, {conn_msg,Msg}, StateName, #data{connection_state = Connection0,
- event_queue = Qev0} = D0) ->
+handle_event(internal, {conn_msg, Msg}, StateName, #data{connection_state = Connection0,
+ event_queue = Qev0} = D0) ->
Role = ?role(StateName),
Rengotation = renegotiation(StateName),
try ssh_connection:handle_msg(Msg, Connection0, Role, D0#data.ssh_params) of
@@ -2226,7 +2218,6 @@ triggered_alive(StateName, D0 = #data{},
Ssh = D#data.ssh_params,
Now = erlang:monotonic_time(milli_seconds),
Ssh1 = Ssh#ssh{alive_probes_sent = SentProbes + 1,
- alive_awaiting_response = true,
alive_last_sent_at = Now},
{keep_state, D#data{ssh_params = Ssh1}, Actions}
end.
@@ -2263,6 +2254,7 @@ ssh_dbg_on(alive) ->
dbg:tp(?MODULE, handle_event, 4, x),
dbg:tpl(?MODULE, init_ssh_record, 4, x),
dbg:tpl(?MODULE, start_rekeying, 2, x),
+ dbg:tpl(?MODULE, reset_alive, 1, x),
dbg:tpl(?MODULE, triggered_alive, 4, x);
ssh_dbg_on(connections) -> dbg:tp(?MODULE, init, 1, x),
ssh_dbg_on(terminate);
@@ -2288,6 +2280,7 @@ ssh_dbg_on(disconnect) -> dbg:tpl(?MODULE, send_disconnect, 7, x).
ssh_dbg_off(alive) ->
dbg:ctpg(?MODULE, handle_event, 4),
dbg:ctpl(?MODULE, start_rekeying, 2),
+ dbg:ctpl(?MODULE, reset_alive, 1, x),
dbg:ctpl(?MODULE, init_ssh_record, 4),
dbg:ctpl(?MODULE, triggered_alive, 4);
ssh_dbg_off(disconnect) -> dbg:ctpl(?MODULE, send_disconnect, 7);
@@ -2312,12 +2305,9 @@ ssh_dbg_format(alive, {return_from, {?MODULE, F=init_ssh_record, A=4}, Ssh}) ->
{AliveCount, AliveInterval} = ?GET_ALIVE_OPT(Ssh#ssh.opts),
Str = io_lib:format("Interval=~p Count=~p", [AliveInterval, AliveCount]),
?PRINT_ALIVE_EVENT(?MODULE, F, A, Str);
-ssh_dbg_format(alive, {call, {?MODULE,F=handle_event,
- [EventType, EventContent = {conn_msg, Msg}, State, _Data]}})
- when is_record(Msg, ssh_msg_request_failure) orelse
- is_record(Msg, ssh_msg_request_success) ->
- Str = io_lib:format("~n~p ~p (state: ~p)", [EventType, EventContent, State]),
- ?PRINT_ALIVE_EVENT(?MODULE, F, 4, Str);
+ssh_dbg_format(alive, {call, {?MODULE,F=reset_alive, [_Data]}}) ->
+ Str = io_lib:format("", []),
+ ?PRINT_ALIVE_EVENT(?MODULE, F, 1, Str);
ssh_dbg_format(alive, {call, {?MODULE,F=handle_event,
[EventType, EventContent, State, _Data]}})
when EventType == {timeout, alive} orelse EventType == {timeout, renegotiation_alive} ->
@@ -2328,7 +2318,7 @@ ssh_dbg_format(alive, {call, {?MODULE,F=triggered_alive,
#ssh{opts = Opts, alive_probes_sent = SentProbesCount}, _]
}}) ->
{Count, _AliveInterval} = ?GET_ALIVE_OPT(Opts),
- Str = io_lib:format("~n~p out ~p alive probes sent (state: ~w)", [SentProbesCount, Count, State]),
+ Str = io_lib:format("~nsending alive probe ~p/~p (state: ~w)", [SentProbesCount+1, Count, State]),
?PRINT_ALIVE_EVENT(?MODULE, F, 4, Str);
ssh_dbg_format(alive, {return_from, {?MODULE, F=triggered_alive, 4}, {stop, Details, _}}) ->
Str = io_lib:format("~n0 alive probes left {stop, ~p, _}", [Details]),
diff --git a/lib/ssh/test/ssh_test_lib.erl b/lib/ssh/test/ssh_test_lib.erl
index 4dfcc3fe87..0f9339c05a 100644
--- a/lib/ssh/test/ssh_test_lib.erl
+++ b/lib/ssh/test/ssh_test_lib.erl
@@ -341,7 +341,8 @@ start_shell(Port, IOServer, ExtraOptions) ->
[?MODULE,?LINE,self(), Port, IOServer, ExtraOptions]),
Options = [{user_interaction, false},
{silently_accept_hosts,true},
- {save_accepted_host,false}
+ {save_accepted_host,false},
+ {alive, #{count_max => 3, interval => 100}}
| ExtraOptions],
try
group_leader(IOServer, self()),
diff --git a/lib/ssh/test/ssh_to_openssh_SUITE.erl b/lib/ssh/test/ssh_to_openssh_SUITE.erl
index 56b5053452..7118e2e81c 100644
--- a/lib/ssh/test/ssh_to_openssh_SUITE.erl
+++ b/lib/ssh/test/ssh_to_openssh_SUITE.erl
@@ -58,7 +58,7 @@
]).
-define(REKEY_DATA_TMO, 65000).
-
+-define(ALIVE, {alive, #{count_max => 3, interval => 100}}).
%%--------------------------------------------------------------------
%% Common Test interface functions -----------------------------------
%%--------------------------------------------------------------------
@@ -207,6 +207,7 @@ eclient_oserver_helper2({Shell, Prev, IO}, Config) ->
exec_with_io_in_sshc(Config) when is_list(Config) ->
SystemDir = proplists:get_value(data_dir, Config),
{Pid, Host, Port} = ssh_test_lib:daemon([{system_dir, SystemDir},
+ ?ALIVE,
{failfun, fun ssh_test_lib:failfun/2}]),
ct:sleep(500),
@@ -216,6 +217,8 @@ exec_with_io_in_sshc(Config) when is_list(Config) ->
[" -o UserKnownHostsFile=", "/dev/null",
" -o CheckHostIP=no"
" -o StrictHostKeyChecking=no"
+ " -o ServerAliveCountMax=3"
+ " -o ServerAliveInterval=100"
" -q"
" -x" % Disable X forwarding
],
@@ -236,6 +239,7 @@ exec_direct_with_io_in_sshc(Config) when is_list(Config) ->
SystemDir = proplists:get_value(data_dir, Config),
{Pid, Host, Port} = ssh_test_lib:daemon([{system_dir, SystemDir},
{failfun, fun ssh_test_lib:failfun/2},
+ ?ALIVE,
{exec,{direct,fun(Cmnd) ->
{ok,X} = io:read(Cmnd),
{ok,{X,lists:reverse(atom_to_list(X))}}
@@ -248,6 +252,8 @@ exec_direct_with_io_in_sshc(Config) when is_list(Config) ->
[" -o UserKnownHostsFile=", "/dev/null",
" -o CheckHostIP=no"
" -o StrictHostKeyChecking=no"
+ " -o ServerAliveCountMax=3"
+ " -o ServerAliveInterval=100"
" -q"
" -x" % Disable X forwarding
],
@@ -296,6 +302,7 @@ eserver_oclient_renegotiate_helper1(Config) ->
{Pid, Host, Port} = ssh_test_lib:daemon([{system_dir, SystemDir},
{failfun, fun ssh_test_lib:failfun/2},
+ ?ALIVE,
{bannerfun, BannerFun}]),
ct:sleep(500),
@@ -308,6 +315,8 @@ eserver_oclient_renegotiate_helper1(Config) ->
[" -o UserKnownHostsFile=", "/dev/null",
" -o CheckHostIP=no"
" -o StrictHostKeyChecking=no"
+ " -o ServerAliveCountMax=3"
+ " -o ServerAliveInterval=100"
" -q"
" -x",
" -o RekeyLimit=",integer_to_list(RenegLimitK),"K"]),
@@ -354,6 +363,7 @@ tunnel_out_non_erlclient_erlserver(Config) ->
{_Pid, Host, Port} = ssh_test_lib:daemon([{tcpip_tunnel_out, true},
{system_dir, SystemDir},
+ ?ALIVE,
{failfun, fun ssh_test_lib:failfun/2}]),
{ToSock, _ToHost, ToPort} = tunneling_listner(),
@@ -364,6 +374,8 @@ tunnel_out_non_erlclient_erlserver(Config) ->
[" -o UserKnownHostsFile=", "/dev/null",
" -o CheckHostIP=no"
" -o StrictHostKeyChecking=no"
+ " -o ServerAliveCountMax=3"
+ " -o ServerAliveInterval=100"
" -q"
" -x",
" -R ",integer_to_list(ListenPort),":127.0.0.1:",integer_to_list(ToPort)]),
@@ -382,6 +394,7 @@ tunnel_in_non_erlclient_erlserver(Config) ->
_UserDir = proplists:get_value(priv_dir, Config),
{_Pid, Host, Port} = ssh_test_lib:daemon([{tcpip_tunnel_in, true},
{system_dir, SystemDir},
+ ?ALIVE,
{failfun, fun ssh_test_lib:failfun/2}]),
{ToSock, _ToHost, ToPort} = tunneling_listner(),
@@ -393,6 +406,8 @@ tunnel_in_non_erlclient_erlserver(Config) ->
[" -o UserKnownHostsFile=", "/dev/null",
" -o CheckHostIP=no"
" -o StrictHostKeyChecking=no"
+ " -o ServerAliveCountMax=3"
+ " -o ServerAliveInterval=100"
" -q"
" -x",
" -L ",integer_to_list(ListenPort),":127.0.0.1:",integer_to_list(ToPort)]),
@@ -411,10 +426,12 @@ tunnel_in_erlclient_erlserver(Config) ->
{_Pid, Host, Port} = ssh_test_lib:daemon([{tcpip_tunnel_in, true},
{system_dir, SystemDir},
{user_dir, UserDir},
+ ?ALIVE,
{user_passwords, [{"foo", "bar"}]},
{failfun, fun ssh_test_lib:failfun/2}]),
C = ssh_test_lib:connect(Host, Port, [{silently_accept_hosts, true},
{user_dir, UserDir},
+ ?ALIVE,
{user,"foo"},{password,"bar"},
{user_interaction, false}]),
{ToSock, ToHost, ToPort} = tunneling_listner(),
@@ -437,10 +454,12 @@ tunnel_in_erlclient_erlserver_allowed(Config) ->
{_Pid, Host, Port} = ssh_test_lib:daemon([{tcpip_tunnel_in, AllowedFun},
{system_dir, SystemDir},
{user_dir, UserDir},
+ ?ALIVE,
{user_passwords, [{"foo", "bar"}]},
{failfun, fun ssh_test_lib:failfun/2}]),
C = ssh_test_lib:connect(Host, Port, [{silently_accept_hosts, true},
{user_dir, UserDir},
+ ?ALIVE,
{user,"foo"},{password,"bar"},
{user_interaction, false}]),
@@ -464,9 +483,11 @@ tunnel_in_erlclient_erlserver_denied(Config) ->
{system_dir, SystemDir},
{user_dir, UserDir},
{user_passwords, [{"foo", "bar"}]},
+ ?ALIVE,
{failfun, fun ssh_test_lib:failfun/2}]),
C = ssh_test_lib:connect(Host, Port, [{silently_accept_hosts, true},
{user_dir, UserDir},
+ ?ALIVE,
{user,"foo"},{password,"bar"},
{user_interaction, false}]),
@@ -479,7 +500,7 @@ tunnel_in_erlclient_erlserver_denied(Config) ->
%%--------------------------------------------------------------------
tunnel_in_erlclient_openssh_server(_Config) ->
- C = ssh_test_lib:connect(?SSH_DEFAULT_PORT, []),
+ C = ssh_test_lib:connect(?SSH_DEFAULT_PORT, [?ALIVE]),
{ToSock, ToHost, ToPort} = tunneling_listner(),
ListenHost = {127,0,0,1},
@@ -495,10 +516,12 @@ tunnel_out_erlclient_erlserver(Config) ->
{system_dir, SystemDir},
{user_dir, UserDir},
{user_passwords, [{"foo", "bar"}]},
+ ?ALIVE,
{failfun, fun ssh_test_lib:failfun/2}]),
C = ssh_test_lib:connect(Host, Port, [{silently_accept_hosts, true},
{user_dir, UserDir},
{user,"foo"},{password,"bar"},
+ ?ALIVE,
{user_interaction, false}]),
{ToSock, ToHost, ToPort} = tunneling_listner(),
@@ -509,7 +532,7 @@ tunnel_out_erlclient_erlserver(Config) ->
%%--------------------------------------------------------------------
tunnel_out_erlclient_openssh_server(_Config) ->
- C = ssh_test_lib:connect(?SSH_DEFAULT_PORT, []),
+ C = ssh_test_lib:connect(?SSH_DEFAULT_PORT, [?ALIVE]),
{ToSock, ToHost, ToPort} = tunneling_listner(),
ListenHost = {127,0,0,1},
diff --git a/lib/ssh/test/ssh_trpt_test_lib.erl b/lib/ssh/test/ssh_trpt_test_lib.erl
index 992e20867a..6544b8ed35 100644
--- a/lib/ssh/test/ssh_trpt_test_lib.erl
+++ b/lib/ssh/test/ssh_trpt_test_lib.erl
@@ -32,9 +32,9 @@
).
-include_lib("common_test/include/ct.hrl").
--include("ssh.hrl"). % ?UINT32, ?BYTE, #ssh{} ...
--include("ssh_transport.hrl").
--include("ssh_auth.hrl").
+-include_lib("ssh/src/ssh.hrl"). % ?UINT32, ?BYTE, #ssh{} ...
+-include_lib("ssh/src/ssh_transport.hrl").
+-include_lib("ssh/src/ssh_auth.hrl").
%%%----------------------------------------------------------------
-record(s, {
--
2.51.0