File 4921-ssh-Implement-max_initial_idle_time.patch of Package erlang
From e8406a80f09f52e6c27d3340487f09430eb23de1 Mon Sep 17 00:00:00 2001
From: Hans Nilsson <hans@erlang.org>
Date: Thu, 18 Aug 2022 16:07:23 +0200
Subject: [PATCH 1/2] ssh: Implement max_initial_idle_time
---
lib/ssh/src/ssh.hrl | 2 ++
lib/ssh/src/ssh_connection_handler.erl | 8 +++++++-
lib/ssh/src/ssh_fsm_userauth_server.erl | 26 +++++++++++++++++++++----
lib/ssh/src/ssh_options.erl | 6 ++++++
lib/ssh/test/ssh_basic_SUITE.erl | 24 ++++++++++++++++++++++-
5 files changed, 60 insertions(+), 6 deletions(-)
diff --git a/lib/ssh/src/ssh.hrl b/lib/ssh/src/ssh.hrl
index 796a35bbb8..c6d1d9d086 100644
--- a/lib/ssh/src/ssh.hrl
+++ b/lib/ssh/src/ssh.hrl
@@ -322,6 +322,7 @@
| tcpip_tunnel_in_daemon_option()
| authentication_daemon_options()
| diffie_hellman_group_exchange_daemon_option()
+ | max_initial_idle_time_daemon_option()
| negotiation_timeout_daemon_option()
| hello_timeout_daemon_option()
| hardening_daemon_options()
@@ -392,6 +393,7 @@
-type explicit_group_file() :: {file,string()} .
-type ssh_moduli_file() :: {ssh_moduli_file,string()}.
+-type max_initial_idle_time_daemon_option() :: {max_initial_idle_time, timeout()} .
-type negotiation_timeout_daemon_option() :: {negotiation_timeout, timeout()} .
-type hello_timeout_daemon_option() :: {hello_timeout, timeout()} .
diff --git a/lib/ssh/src/ssh_connection_handler.erl b/lib/ssh/src/ssh_connection_handler.erl
index bd98aaddc0..849f4b46d2 100644
--- a/lib/ssh/src/ssh_connection_handler.erl
+++ b/lib/ssh/src/ssh_connection_handler.erl
@@ -1118,7 +1118,10 @@ handle_event(info, {Proto, Sock, NewData}, StateName, D0 = #data{socket = Sock,
#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, ?CONNECTION_MSG(Msg)};
+ #ssh_msg_channel_open{} = Msg -> {keep_state, D1,
+ [{{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)};
@@ -1232,6 +1235,9 @@ handle_event({timeout,idle_time}, _Data, _StateName, D) ->
keep_state_and_data
end;
+handle_event({timeout,max_initial_idle_time}, _Data, _StateName, _D) ->
+ {stop, {shutdown, "Timeout"}};
+
%%% So that terminate will be run when supervisor is shutdown
handle_event(info, {'EXIT', _Sup, Reason}, StateName, _D) ->
Role = ?role(StateName),
diff --git a/lib/ssh/src/ssh_fsm_userauth_server.erl b/lib/ssh/src/ssh_fsm_userauth_server.erl
index 0d12cb43ec..9a64df4545 100644
--- a/lib/ssh/src/ssh_fsm_userauth_server.erl
+++ b/lib/ssh/src/ssh_fsm_userauth_server.erl
@@ -71,7 +71,12 @@ handle_event(internal,
{keep_state, D};
{authorized, User, {Reply, Ssh1}} ->
D = connected_state(Reply, Ssh1, User, Method, D0),
- {next_state, {connected,server}, D, {change_callback_module,ssh_connection_handler}}
+ {next_state, {connected,server}, D,
+ [set_max_initial_idle_timeout(D),
+ {change_callback_module,ssh_connection_handler}
+ ]
+ }
+
end;
{"ssh-connection", "ssh-connection", Method} ->
@@ -82,7 +87,10 @@ handle_event(internal,
case ssh_auth:handle_userauth_request(Msg, Ssh0#ssh.session_id, Ssh0) of
{authorized, User, {Reply, Ssh1}} ->
D = connected_state(Reply, Ssh1, User, Method, D0),
- {next_state, {connected,server}, D, {change_callback_module,ssh_connection_handler}};
+ {next_state, {connected,server}, 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, D0),
D = ssh_connection_handler:send_msg(Reply, D0#data{ssh_params = Ssh}),
@@ -115,7 +123,10 @@ handle_event(internal, #ssh_msg_userauth_info_response{} = Msg, {userauth_keyboa
case ssh_auth:handle_userauth_info_response(Msg, D0#data.ssh_params) of
{authorized, User, {Reply, Ssh1}} ->
D = connected_state(Reply, Ssh1, User, "keyboard-interactive", D0),
- {next_state, {connected,server}, D, {change_callback_module,ssh_connection_handler}};
+ {next_state, {connected,server}, 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}),
@@ -130,7 +141,11 @@ handle_event(internal, #ssh_msg_userauth_info_response{} = Msg, {userauth_keyboa
{authorized, User, {Reply, Ssh1}} =
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, {change_callback_module,ssh_connection_handler}};
+ {next_state, {connected,server}, D,
+ [set_max_initial_idle_timeout(D),
+ {change_callback_module,ssh_connection_handler}
+ ]
+ };
%%% ######## UNHANDLED EVENT!
@@ -164,6 +179,9 @@ connected_state(Reply, Ssh1, User, Method, D0) ->
ssh_params = Ssh#ssh{authenticated = true}}.
+set_max_initial_idle_timeout(#data{ssh_params = #ssh{opts=Opts}}) ->
+ {{timeout,max_initial_idle_time}, ?GET_OPT(max_initial_idle_time,Opts), none}.
+
connected_fun(User, Method, #data{ssh_params = #ssh{peer = {_,Peer}}} = D) ->
?CALL_FUN(connectfun,D)(User, Peer, Method).
diff --git a/lib/ssh/src/ssh_options.erl b/lib/ssh/src/ssh_options.erl
index 9e06ddb7de..2acc46807b 100644
--- a/lib/ssh/src/ssh_options.erl
+++ b/lib/ssh/src/ssh_options.erl
@@ -533,6 +533,12 @@ default(server) ->
class => user_option
},
+ max_initial_idle_time =>
+ #{default => infinity, %% To not break compatibility
+ chk => fun(V) -> check_timeout(V) end,
+ class => user_option
+ },
+
negotiation_timeout =>
#{default => 2*60*1000,
chk => fun(V) -> check_timeout(V) end,
diff --git a/lib/ssh/test/ssh_basic_SUITE.erl b/lib/ssh/test/ssh_basic_SUITE.erl
index cc74d5e725..a508d08613 100644
--- a/lib/ssh/test/ssh_basic_SUITE.erl
+++ b/lib/ssh/test/ssh_basic_SUITE.erl
@@ -74,6 +74,7 @@
login_bad_pwd_no_retry3/1,
login_bad_pwd_no_retry4/1,
login_bad_pwd_no_retry5/1,
+ max_initial_idle_time/1,
misc_ssh_options/1,
multi_daemon_opt_fd/1,
openssh_zlib_basic_test/1,
@@ -155,7 +156,9 @@ groups() ->
exec, exec_compressed,
exec_with_io_out, exec_with_io_in,
cli, cli_exit_normal, cli_exit_status,
- idle_time_client, idle_time_server, openssh_zlib_basic_test,
+ idle_time_client, idle_time_server,
+ max_initial_idle_time,
+ openssh_zlib_basic_test,
misc_ssh_options, inet_option, inet6_option,
shell, shell_socket, shell_ssh_conn, shell_no_unicode, shell_unicode_string,
close
@@ -471,6 +474,25 @@ idle_time_common(DaemonExtraOpts, ClientExtraOpts, Config) ->
end,
ssh:stop_daemon(Pid).
+%%--------------------------------------------------------------------
+max_initial_idle_time(Config) ->
+ SystemDir = filename:join(proplists:get_value(priv_dir, Config), system),
+ UserDir = proplists:get_value(priv_dir, Config),
+
+ {Pid, Host, Port} = ssh_test_lib:daemon([{system_dir, SystemDir},
+ {user_dir, UserDir},
+ {failfun, fun ssh_test_lib:failfun/2},
+ {max_initial_idle_time, 2000}
+ ]),
+ ConnectionRef =
+ ssh_test_lib:connect(Host, Port, [{silently_accept_hosts, true},
+ {user_dir, UserDir},
+ {user_interaction, false}
+ ]),
+ timer:sleep(8000),
+ {error, closed} = ssh_connection:session_channel(ConnectionRef, 1000),
+ ssh:stop_daemon(Pid).
+
%%--------------------------------------------------------------------
%%% Test that ssh:shell/2 works
shell(Config) when is_list(Config) ->
--
2.35.3