Skip to content

Commit

Permalink
Add channel close timer to closing procedure from our side
Browse files Browse the repository at this point in the history
If the peer fails to respond to ssh_msg_channel_close the corresponding channel
entry will be removed from cache after the timeout (assuming the connection is
still alive with probably other channels open).
  • Loading branch information
yarisx committed Feb 18, 2025
1 parent addb6b4 commit 704973a
Show file tree
Hide file tree
Showing 4 changed files with 145 additions and 13 deletions.
9 changes: 7 additions & 2 deletions lib/ssh/src/ssh_connection.erl
Original file line number Diff line number Diff line change
Expand Up @@ -776,9 +776,10 @@ handle_msg(#ssh_msg_channel_open_confirmation{recipient_channel = ChannelId,
reply_msg(Channel, Connection0, {open, ChannelId});
true ->
%% There is no user process so nobody cares about the channel
%% close it
%% close it and remove from the cache, reply from the peer will be
%% ignored
CloseMsg = channel_close_msg(RemoteId),
ssh_client_channel:cache_update(Cache, Channel#channel{sent_close = true}),
ssh_client_channel:cache_delete(Cache, ChannelId),
{[{connection_reply, CloseMsg}], Connection0}
end;

Expand Down Expand Up @@ -829,6 +830,10 @@ handle_msg(#ssh_msg_channel_close{recipient_channel = ChannelId},
{Replies, Connection};

undefined ->
%% This may happen among other reasons
%% - we sent 'channel-close' %% and the peer failed to respond in time
%% - we tried to open a channel but the handler died prematurely
%% and the channel entry was removed from the cache
{[], Connection0}
end;

Expand Down
35 changes: 27 additions & 8 deletions lib/ssh/src/ssh_connection_handler.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1104,7 +1104,9 @@ handle_event({call,From}, {close, ChannelId}, StateName, D0)
D1 = send_msg(ssh_connection:channel_close_msg(Id), D0),
ssh_client_channel:cache_update(cache(D1),
Channel#channel{sent_close = true}),
{keep_state, D1, [cond_set_idle_timer(D1), {reply,From,ok}]};
{keep_state, D1, [cond_set_idle_timer(D1),
channel_close_timer(D1, Id),
{reply,From,ok}]};
_ ->
%% Here we match a channel which has already sent 'channel-close'
%% AND possible cases of 'broken cache' i.e. when a channel
Expand Down Expand Up @@ -1279,19 +1281,21 @@ handle_event(info, {'DOWN', _Ref, process, ChannelPid, _Reason}, _, D) ->
%% we send 'channel-close' and(!) update the cache so that we remember
%% what we've done.
%% Also set user as 'undefined' as there is no such process anyway
D2 = lists:foldl(
fun(#channel{remote_id = Id, sent_close = false} = Channel, D0) when Id /= undefined ->
{D2, NewTimers} = lists:foldl(
fun(#channel{remote_id = Id, sent_close = false} = Channel,
{D0, Timers}) when Id /= undefined ->
D1 = send_msg(ssh_connection:channel_close_msg(Id), D0),
ssh_client_channel:cache_update(cache(D1),
Channel#channel{sent_close = true,
user = undefined}),
D1;
(Channel, D0) ->
ChannelTimer = channel_close_timer(D1, Id),
{D1, [ChannelTimer | Timers]};
(Channel, {D0, _} = Acc) ->
ssh_client_channel:cache_update(cache(D0),
Channel#channel{user = undefined}),
D0
end, D, Channels),
{keep_state, D2, cond_set_idle_timer(D2)};
Acc
end, {D, []}, Channels),
{keep_state, D2, [cond_set_idle_timer(D2) | NewTimers]};

handle_event({timeout,idle_time}, _Data, _StateName, D) ->
case ssh_client_channel:cache_info(num_entries, cache(D)) of
Expand All @@ -1304,6 +1308,16 @@ handle_event({timeout,idle_time}, _Data, _StateName, D) ->
handle_event({timeout,max_initial_idle_time}, _Data, _StateName, _D) ->
{stop, {shutdown, "Timeout"}};

handle_event({timeout, {channel_close, ChannelId}}, _Data, _StateName, D) ->
Cache = cache(D),
case ssh_client_channel:cache_lookup(Cache, ChannelId) of
#channel{sent_close = true} ->
ssh_client_channel:cache_delete(Cache, ChannelId),
{keep_state, D, cond_set_idle_timer(D)};
_ ->
keep_state_and_data
end;

%%% So that terminate will be run when supervisor is shutdown
handle_event(info, {'EXIT', _Sup, Reason}, StateName, _D) ->
Role = ?role(StateName),
Expand Down Expand Up @@ -2076,6 +2090,11 @@ cond_set_idle_timer(D) ->
_ -> {{timeout,idle_time}, infinity, none}
end.

channel_close_timer(D, ChannelId) ->
%{{timeout, {channel_close, ChannelId}}, 3000, none}. %?GET_OPT(idle_time, (D#data.ssh_params)#ssh.opts), none}.
{{timeout, {channel_close, ChannelId}},
?GET_OPT(channel_close_timeout, (D#data.ssh_params)#ssh.opts), none}.

%%%----------------------------------------------------------------
start_channel_request_timer(_,_, infinity) ->
ok;
Expand Down
6 changes: 6 additions & 0 deletions lib/ssh/src/ssh_options.erl
Original file line number Diff line number Diff line change
Expand Up @@ -886,6 +886,12 @@ default(common) ->
#{default => ?MAX_RND_PADDING_LEN,
chk => fun(V) -> check_non_neg_integer(V) end,
class => undoc_user_option
},

channel_close_timeout =>
#{default => 5 * 1000,
chk => fun(V) -> check_non_neg_integer(V) end,
class => undoc_user_option
}
}.

Expand Down
108 changes: 105 additions & 3 deletions lib/ssh/test/ssh_protocol_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -26,6 +26,7 @@
-include_lib("kernel/include/inet.hrl").
-include("ssh.hrl"). % ?UINT32, ?BYTE, #ssh{} ...
-include("ssh_transport.hrl").
-include("ssh_connect.hrl").
-include("ssh_auth.hrl").
-include("ssh_test_lib.hrl").

Expand Down Expand Up @@ -81,7 +82,8 @@
preferred_algorithms/1,
service_name_length_too_large/1,
service_name_length_too_short/1,
client_close_after_hello/1
client_close_after_hello/1,
channel_close_timeout/1
]).

-define(NEWLINE, <<"\r\n">>).
Expand Down Expand Up @@ -119,7 +121,8 @@ all() ->
{group,field_size_error},
{group,ext_info},
{group,preferred_algorithms},
{group,client_close_early}
{group,client_close_early},
{group,channel_close}
].

groups() ->
Expand Down Expand Up @@ -166,7 +169,8 @@ groups() ->
modify_combo
]},
{client_close_early, [], [client_close_after_hello
]}
]},
{channel_close, [], [channel_close_timeout]}
].


Expand Down Expand Up @@ -1298,6 +1302,104 @@ connect_and_kex(Config, InitialState) ->
],
InitialState).

channel_close_timeout(Config) ->
{User,_Pwd} = server_user_password(Config),

%% Create a listening socket as server socket:
{ok,InitialState} = ssh_trpt_test_lib:exec(listen),
HostPort = ssh_trpt_test_lib:server_host_port(InitialState),

%% Start a process handling one connection on the server side:
spawn_link(
fun() ->
{ok,_} =
ssh_trpt_test_lib:exec(
[{set_options, [print_ops, print_messages]},
{accept, [{system_dir, system_dir(Config)},
{user_dir, user_dir(Config)},
{idle_time, 50000}]},
receive_hello,
{send, hello},

{send, ssh_msg_kexinit},
{match, #ssh_msg_kexinit{_='_'}, receive_msg},

{match, #ssh_msg_kexdh_init{_='_'}, receive_msg},
{send, ssh_msg_kexdh_reply},

{send, #ssh_msg_newkeys{}},
{match, #ssh_msg_newkeys{_='_'}, receive_msg},

{match, #ssh_msg_service_request{name="ssh-userauth"}, receive_msg},
{send, #ssh_msg_service_accept{name="ssh-userauth"}},

{match, #ssh_msg_userauth_request{service="ssh-connection",
method="none",
user=User,
_='_'}, receive_msg},

{send, #ssh_msg_userauth_failure{authentications = "password",
partial_success = false}},

{match, #ssh_msg_userauth_request{service="ssh-connection",
method="password",
user=User,
_='_'}, receive_msg},
{send, #ssh_msg_userauth_success{}},
{match, #ssh_msg_channel_open{channel_type="session",
sender_channel=0,
initial_window_size=640*1024,
maximum_packet_size=64*1024,
data = <<>>},
receive_msg},
{send, #ssh_msg_channel_open_confirmation{recipient_channel= 0,
sender_channel = 0,
initial_window_size = 64*1024,
maximum_packet_size = 32*1024
}},
{match, #ssh_msg_channel_open{channel_type="session",
sender_channel=1,
initial_window_size=640*1024,
maximum_packet_size=64*1024,
data = <<>>},
receive_msg},
{send, #ssh_msg_channel_open_confirmation{recipient_channel= 1,
sender_channel = 1,
initial_window_size = 64*1024,
maximum_packet_size = 32*1024
}},
{match, #ssh_msg_channel_close{recipient_channel = 0}, receive_msg},
{match, disconnect(), receive_msg},
print_state
],
InitialState)
end),

%% connect to it with a regular Erlang SSH client:
ChannelCloseTimeout = 3000,
{ok, ConnRef} = std_connect(HostPort, Config,
[{preferred_algorithms,[{kex,[?DEFAULT_KEX]},
{cipher,?DEFAULT_CIPHERS}
]},
{channel_close_timeout, ChannelCloseTimeout},
{idle_time, 50000}
]
),
{ok, Channel0} = ssh_connection:session_channel(ConnRef, 50000),
{ok, Channel1} = ssh_connection:session_channel(ConnRef, 50000),
%% Close the channel from client side, the server does not reply with 'channel-close'
%% After the timeout, the client should drop the cache entry
_ = ssh_connection:close(ConnRef, Channel0),
receive
after ChannelCloseTimeout + 1000 ->
{channels, Channels} = ssh:connection_info(ConnRef, channels),
ct:log("Channel entries ~p", [Channels]),
%% Only one channel entry should be present, the other one should be dropped
1 = length(Channels),
ssh:close(ConnRef)
end.


%%%----------------------------------------------------------------

%%% For matching peer disconnection
Expand Down

0 comments on commit 704973a

Please sign in to comment.