Skip to content

Commit

Permalink
Fix channel close procedure when the peer dies or our handler goes down
Browse files Browse the repository at this point in the history
  • Loading branch information
yarisx committed Feb 18, 2025
1 parent aafdabf commit 73d333b
Show file tree
Hide file tree
Showing 2 changed files with 41 additions and 12 deletions.
16 changes: 13 additions & 3 deletions lib/ssh/src/ssh_connection.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1036,14 +1036,24 @@ handle_msg(#ssh_msg_channel_request{recipient_channel = ChannelId,
?DEC_BIN(Err, _ErrLen),
?DEC_BIN(Lang, _LangLen)>> = Data,
case ssh_client_channel:cache_lookup(Cache, ChannelId) of
#channel{remote_id = RemoteId} = Channel ->
#channel{remote_id = RemoteId, sent_close = SentClose} = Channel ->
{Reply, Connection} = reply_msg(Channel, Connection0,
{exit_signal, ChannelId,
binary_to_list(SigName),
binary_to_list(Err),
binary_to_list(Lang)}),
ChannelCloseMsg = channel_close_msg(RemoteId),
{[{connection_reply, ChannelCloseMsg}|Reply], Connection};
%% Send 'channel-close' only if it has not been sent yet
%% by e.g. our side also closing the channel or going down
%% and(!) update the cache
%% so that the 'channel-close' is not sent twice
if not SentClose ->
CloseMsg = channel_close_msg(RemoteId),
ssh_client_channel:cache_update(Cache,
Channel#channel{sent_close = true}),
{[{connection_reply, CloseMsg}|Reply], Connection};
true ->
{Reply, Connection}
end;
_ ->
%% Channel already closed by peer
{[], Connection0}
Expand Down
37 changes: 28 additions & 9 deletions lib/ssh/src/ssh_connection_handler.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1096,12 +1096,20 @@ handle_event({call,From}, {recv_window, ChannelId}, StateName, D)

handle_event({call,From}, {close, ChannelId}, StateName, D0)
when ?CONNECTED(StateName) ->
%% Send 'channel-close' only if it has not been sent yet
%% e.g. when 'exit-signal' was received from the peer
%% and(!) we update the cache so that we remember what we've done
case ssh_client_channel:cache_lookup(cache(D0), ChannelId) of
#channel{remote_id = Id} = Channel ->
#channel{remote_id = Id, sent_close = false} = Channel ->
D1 = send_msg(ssh_connection:channel_close_msg(Id), D0),
ssh_client_channel:cache_update(cache(D1), Channel#channel{sent_close = true}),
ssh_client_channel:cache_update(cache(D1),
Channel#channel{sent_close = true}),
{keep_state, D1, [cond_set_idle_timer(D1), {reply,From,ok}]};
undefined ->
_ ->
%% Here we match a channel which has already sent 'channel-close'
%% AND possible cases of 'broken cache' i.e. when a channel
%% disappeared from the cache, but has not been properly shut down
%% The latter would be a bug, but hard to chase
{keep_state_and_data, [{reply,From,ok}]}
end;

Expand Down Expand Up @@ -1259,15 +1267,26 @@ handle_event(info, {timeout, {_, From} = Request}, _,
%%% Handle that ssh channels user process goes down
handle_event(info, {'DOWN', _Ref, process, ChannelPid, _Reason}, _, D) ->
Cache = cache(D),
ssh_client_channel:cache_foldl(
fun(#channel{user=U,
local_id=Id}, Acc) when U == ChannelPid ->
ssh_client_channel:cache_delete(Cache, Id),
Acc;
%% Here we first collect the list of channel id's handled by the process
%% Do NOT remove them from the cache - they are not closed yet!
Channels = ssh_client_channel:cache_foldl(
fun(#channel{user=U} = Channel, Acc) when U == ChannelPid ->
[Channel | Acc];
(_,Acc) ->
Acc
end, [], Cache),
{keep_state, D, cond_set_idle_timer(D)};
%% Then for each channel where 'channel-close' has not been sent yet
%% we send 'channel-close' and(!) update the cache so that we remember
%% what we've done
D2 = lists:foldl(
fun(#channel{remote_id = Id, sent_close = false} = Channel, D0) ->
D1 = send_msg(ssh_connection:channel_close_msg(Id), D0),
ssh_client_channel:cache_update(cache(D1),
Channel#channel{sent_close = true}),
D1;
(_, D0) -> D0
end, D, Channels),
{keep_state, D2, cond_set_idle_timer(D2)};

handle_event({timeout,idle_time}, _Data, _StateName, D) ->
case ssh_client_channel:cache_info(num_entries, cache(D)) of
Expand Down

0 comments on commit 73d333b

Please sign in to comment.