Skip to content

Commit 7956220

Browse files
committed
Merge branch 'maint'
2 parents 58a6fa3 + 6fe4430 commit 7956220

File tree

6 files changed

+326
-33
lines changed

6 files changed

+326
-33
lines changed

lib/ssh/src/ssh_connection.erl

Lines changed: 35 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -780,17 +780,26 @@ handle_msg(#ssh_msg_channel_open_confirmation{recipient_channel = ChannelId,
780780
maximum_packet_size = PacketSz},
781781
#connection{channel_cache = Cache} = Connection0, _, _SSH) ->
782782

783-
#channel{remote_id = undefined} = Channel =
783+
#channel{remote_id = undefined, user = U} = Channel =
784784
ssh_client_channel:cache_lookup(Cache, ChannelId),
785785

786-
ssh_client_channel:cache_update(Cache, Channel#channel{
787-
remote_id = RemoteId,
788-
recv_packet_size = max(32768, % rfc4254/5.2
789-
min(PacketSz, Channel#channel.recv_packet_size)
790-
),
791-
send_window_size = WindowSz,
792-
send_packet_size = PacketSz}),
793-
reply_msg(Channel, Connection0, {open, ChannelId});
786+
if U /= undefined ->
787+
ssh_client_channel:cache_update(Cache, Channel#channel{
788+
remote_id = RemoteId,
789+
recv_packet_size = max(32768, % rfc4254/5.2
790+
min(PacketSz, Channel#channel.recv_packet_size)
791+
),
792+
send_window_size = WindowSz,
793+
send_packet_size = PacketSz}),
794+
reply_msg(Channel, Connection0, {open, ChannelId});
795+
true ->
796+
%% There is no user process so nobody cares about the channel
797+
%% close it and remove from the cache, reply from the peer will be
798+
%% ignored
799+
CloseMsg = channel_close_msg(RemoteId),
800+
ssh_client_channel:cache_delete(Cache, ChannelId),
801+
{[{connection_reply, CloseMsg}], Connection0}
802+
end;
794803

795804
handle_msg(#ssh_msg_channel_open_failure{recipient_channel = ChannelId,
796805
reason = Reason,
@@ -839,6 +848,10 @@ handle_msg(#ssh_msg_channel_close{recipient_channel = ChannelId},
839848
{Replies, Connection};
840849

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

@@ -1064,14 +1077,24 @@ handle_msg(#ssh_msg_channel_request{recipient_channel = ChannelId,
10641077
?DEC_BIN(Err, _ErrLen),
10651078
?DEC_BIN(Lang, _LangLen)>> = Data,
10661079
case ssh_client_channel:cache_lookup(Cache, ChannelId) of
1067-
#channel{remote_id = RemoteId} = Channel ->
1080+
#channel{remote_id = RemoteId, sent_close = SentClose} = Channel ->
10681081
{Reply, Connection} = reply_msg(Channel, Connection0,
10691082
{exit_signal, ChannelId,
10701083
binary_to_list(SigName),
10711084
binary_to_list(Err),
10721085
binary_to_list(Lang)}),
1073-
ChannelCloseMsg = channel_close_msg(RemoteId),
1074-
{[{connection_reply, ChannelCloseMsg}|Reply], Connection};
1086+
%% Send 'channel-close' only if it has not been sent yet
1087+
%% by e.g. our side also closing the channel or going down
1088+
%% and(!) update the cache
1089+
%% so that the 'channel-close' is not sent twice
1090+
if not SentClose ->
1091+
CloseMsg = channel_close_msg(RemoteId),
1092+
ssh_client_channel:cache_update(Cache,
1093+
Channel#channel{sent_close = true}),
1094+
{[{connection_reply, CloseMsg}|Reply], Connection};
1095+
true ->
1096+
{Reply, Connection}
1097+
end;
10751098
_ ->
10761099
%% Channel already closed by peer
10771100
{[], Connection0}

lib/ssh/src/ssh_connection_handler.erl

Lines changed: 55 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -1091,12 +1091,22 @@ handle_event({call,From}, {recv_window, ChannelId}, StateName, D)
10911091

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

@@ -1257,15 +1267,33 @@ handle_event(info, {timeout, {_, From} = Request}, _,
12571267
%%% Handle that ssh channels user process goes down
12581268
handle_event(info, {'DOWN', _Ref, process, ChannelPid, _Reason}, _, D) ->
12591269
Cache = cache(D),
1260-
ssh_client_channel:cache_foldl(
1261-
fun(#channel{user=U,
1262-
local_id=Id}, Acc) when U == ChannelPid ->
1263-
ssh_client_channel:cache_delete(Cache, Id),
1264-
Acc;
1265-
(_,Acc) ->
1266-
Acc
1267-
end, [], Cache),
1268-
{keep_state, D, cond_set_idle_timer(D)};
1270+
%% Here we first collect the list of channel id's handled by the process
1271+
%% Do NOT remove them from the cache - they are not closed yet!
1272+
Channels = ssh_client_channel:cache_foldl(
1273+
fun(#channel{user=U} = Channel, Acc) when U == ChannelPid ->
1274+
[Channel | Acc];
1275+
(_,Acc) ->
1276+
Acc
1277+
end, [], Cache),
1278+
%% Then for each channel where 'channel-close' has not been sent yet
1279+
%% we send 'channel-close' and(!) update the cache so that we remember
1280+
%% what we've done.
1281+
%% Also set user as 'undefined' as there is no such process anyway
1282+
{D2, NewTimers} = lists:foldl(
1283+
fun(#channel{remote_id = Id, sent_close = false} = Channel,
1284+
{D0, Timers}) when Id /= undefined ->
1285+
D1 = send_msg(ssh_connection:channel_close_msg(Id), D0),
1286+
ssh_client_channel:cache_update(cache(D1),
1287+
Channel#channel{sent_close = true,
1288+
user = undefined}),
1289+
ChannelTimer = channel_close_timer(D1, Id),
1290+
{D1, [ChannelTimer | Timers]};
1291+
(Channel, {D0, _} = Acc) ->
1292+
ssh_client_channel:cache_update(cache(D0),
1293+
Channel#channel{user = undefined}),
1294+
Acc
1295+
end, {D, []}, Channels),
1296+
{keep_state, D2, [cond_set_idle_timer(D2) | NewTimers]};
12691297

12701298
handle_event({timeout,idle_time}, _Data, _StateName, D) ->
12711299
case ssh_client_channel:cache_info(num_entries, cache(D)) of
@@ -1278,6 +1306,16 @@ handle_event({timeout,idle_time}, _Data, _StateName, D) ->
12781306
handle_event({timeout,max_initial_idle_time}, _Data, _StateName, _D) ->
12791307
{stop, {shutdown, "Timeout"}};
12801308

1309+
handle_event({timeout, {channel_close, ChannelId}}, _Data, _StateName, D) ->
1310+
Cache = cache(D),
1311+
case ssh_client_channel:cache_lookup(Cache, ChannelId) of
1312+
#channel{sent_close = true} ->
1313+
ssh_client_channel:cache_delete(Cache, ChannelId),
1314+
{keep_state, D, cond_set_idle_timer(D)};
1315+
_ ->
1316+
keep_state_and_data
1317+
end;
1318+
12811319
%%% So that terminate will be run when supervisor is shutdown
12821320
handle_event(info, {'EXIT', _Sup, Reason}, StateName, _D) ->
12831321
Role = ?role(StateName),
@@ -2050,6 +2088,10 @@ cond_set_idle_timer(D) ->
20502088
_ -> {{timeout,idle_time}, infinity, none}
20512089
end.
20522090

2091+
channel_close_timer(D, ChannelId) ->
2092+
{{timeout, {channel_close, ChannelId}},
2093+
?GET_OPT(channel_close_timeout, (D#data.ssh_params)#ssh.opts), none}.
2094+
20532095
%%%----------------------------------------------------------------
20542096
start_channel_request_timer(_,_, infinity) ->
20552097
ok;

lib/ssh/src/ssh_options.erl

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -893,6 +893,12 @@ default(common) ->
893893
#{default => ?MAX_RND_PADDING_LEN,
894894
chk => fun(V) -> check_non_neg_integer(V) end,
895895
class => undoc_user_option
896+
},
897+
898+
channel_close_timeout =>
899+
#{default => 5 * 1000,
900+
chk => fun(V) -> check_non_neg_integer(V) end,
901+
class => undoc_user_option
896902
}
897903
}.
898904

lib/ssh/test/ssh_connection_SUITE.erl

Lines changed: 136 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -111,6 +111,7 @@
111111
stop_listener/1,
112112
trap_exit_connect/1,
113113
trap_exit_daemon/1,
114+
handler_down_before_open/1,
114115
ssh_exec_echo/2 % called as an MFA
115116
]).
116117

@@ -182,7 +183,8 @@ all() ->
182183
stop_listener,
183184
no_sensitive_leak,
184185
start_subsystem_on_closed_channel,
185-
max_channels_option
186+
max_channels_option,
187+
handler_down_before_open
186188
].
187189
groups() ->
188190
[{openssh, [], payload() ++ ptty() ++ sock()}].
@@ -1295,7 +1297,7 @@ simple_eval(Inp) -> {simple_eval,Inp}.
12951297

12961298
do_start_shell_exec_fun(Fun, Command, Expect, ExpectType, Config) ->
12971299
DefaultReceiveFun =
1298-
fun(ConnectionRef, ChannelId, Expect, ExpectType) ->
1300+
fun(ConnectionRef, ChannelId, _Expect, _ExpectType) ->
12991301
receive
13001302
{ssh_cm, ConnectionRef, {data, ChannelId, ExpectType, Expect}} ->
13011303
ok
@@ -1944,6 +1946,138 @@ max_channels_option(Config) when is_list(Config) ->
19441946
ssh:close(ConnectionRef),
19451947
ssh:stop_daemon(Pid).
19461948

1949+
handler_down_before_open(Config) ->
1950+
%% Start echo subsystem with a delay in init() - until a signal is received
1951+
%% One client opens a channel on the connection
1952+
%% the other client requests the echo subsystem on the second channel and then immediately goes down
1953+
%% the test monitors the client and when receiving 'DOWN' signals 'echo' to proceed
1954+
%% a) there should be no crash after 'channel-open-confirmation'
1955+
%% b) there should be proper 'channel-close' exchange
1956+
%% c) the 'exec' channel should not be affected after the 'echo' channel goes down
1957+
PrivDir = proplists:get_value(priv_dir, Config),
1958+
UserDir = filename:join(PrivDir, nopubkey), % to make sure we don't use public-key-auth
1959+
file:make_dir(UserDir),
1960+
SysDir = proplists:get_value(data_dir, Config),
1961+
Parent = self(),
1962+
EchoSS_spec = {ssh_echo_server, [8, [{dbg, true}, {parent, Parent}]]},
1963+
{Pid, Host, Port} = ssh_test_lib:daemon([{system_dir, SysDir},
1964+
{user_dir, UserDir},
1965+
{password, "morot"},
1966+
{exec, fun ssh_exec_echo/1},
1967+
{subsystems, [{"echo_n",EchoSS_spec}]}]),
1968+
ct:log("~p:~p connect", [?MODULE,?LINE]),
1969+
ConnectionRef = ssh_test_lib:connect(Host, Port, [{silently_accept_hosts, true},
1970+
{user, "foo"},
1971+
{password, "morot"},
1972+
{user_interaction, false},
1973+
{user_dir, UserDir}]),
1974+
ct:log("~p:~p connected", [?MODULE,?LINE]),
1975+
1976+
ExecChannelPid =
1977+
spawn(
1978+
fun() ->
1979+
{ok, ChannelId0} = ssh_connection:session_channel(ConnectionRef, infinity),
1980+
1981+
%% This is to get peer's connection handler PID ({conn_peer ...} below) and suspend it
1982+
{ok, ChannelId1} = ssh_connection:session_channel(ConnectionRef, infinity),
1983+
ssh_connection:subsystem(ConnectionRef, ChannelId1, "echo_n", infinity),
1984+
ssh_connection:close(ConnectionRef, ChannelId1),
1985+
receive
1986+
{ssh_cm, ConnectionRef, {closed, 1}} -> ok
1987+
end,
1988+
1989+
Parent ! {self(), channelId, ChannelId0},
1990+
Result = receive
1991+
cmd ->
1992+
ct:log("~p:~p Channel ~p executing", [?MODULE, ?LINE, ChannelId0]),
1993+
success = ssh_connection:exec(ConnectionRef, ChannelId0, "testing", infinity),
1994+
Expect = <<"echo testing\n">>,
1995+
ExpSz = size(Expect),
1996+
receive
1997+
{ssh_cm, ConnectionRef, {data, ChannelId0, 0,
1998+
<<Expect:ExpSz/binary, _/binary>>}} = R ->
1999+
ct:log("~p:~p Got expected ~p",[?MODULE,?LINE, R]),
2000+
ok;
2001+
Other ->
2002+
ct:log("~p:~p Got unexpected ~p~nExpect: ~p~n",
2003+
[?MODULE,?LINE, Other, {ssh_cm, ConnectionRef,
2004+
{data, ChannelId0, 0, Expect}}]),
2005+
{fail, "Unexpected data"}
2006+
after 5000 ->
2007+
{fail, "Exec Timeout"}
2008+
end;
2009+
stop -> {fail, "Stopped"}
2010+
end,
2011+
Parent ! {self(), Result}
2012+
end),
2013+
try
2014+
receive
2015+
{ExecChannelPid, channelId, ExId} ->
2016+
ct:log("~p:~p Channel that should stay: ~p pid ~p",
2017+
[?MODULE, ?LINE, ExId, ExecChannelPid]),
2018+
%% This is sent by the echo subsystem as a reaction to channel1 above
2019+
ConnPeer = receive {conn_peer, CM} -> CM end,
2020+
%% The sole purpose of this channel is to go down
2021+
%% before the opening procedure is complete
2022+
DownChannelPid = spawn(
2023+
fun() ->
2024+
ct:log("~p:~p open channel (incomplete)",[?MODULE,?LINE]),
2025+
Parent ! {self(), channelId, ok},
2026+
%% This is to prevent the peer from answering our 'channel-open' in time
2027+
sys:suspend(ConnPeer),
2028+
{ok, _} = ssh_connection:session_channel(ConnectionRef, infinity)
2029+
end),
2030+
MonRef = erlang:monitor(process, DownChannelPid),
2031+
receive
2032+
{DownChannelPid, channelId, ok} ->
2033+
ct:log("~p:~p Channel handler that won't continue: pid ~p",
2034+
[?MODULE, ?LINE, DownChannelPid]),
2035+
ensure_channels(ConnectionRef, 2),
2036+
channel_down_sequence(DownChannelPid, ExecChannelPid,
2037+
ExId, MonRef, ConnectionRef, ConnPeer)
2038+
end
2039+
end,
2040+
ensure_channels(ConnectionRef, 0)
2041+
after
2042+
ssh:close(ConnectionRef),
2043+
ssh:stop_daemon(Pid)
2044+
end.
2045+
2046+
ensure_channels(ConnRef, Expected) ->
2047+
{ok, ChannelList} = ssh_connection_handler:info(ConnRef),
2048+
do_ensure_channels(ConnRef, Expected, length(ChannelList)).
2049+
2050+
do_ensure_channels(_ConnRef, NumExpected, NumExpected) ->
2051+
ok;
2052+
do_ensure_channels(ConnRef, NumExpected, _ChannelListLen) ->
2053+
ct:sleep(100),
2054+
{ok, ChannelList} = ssh_connection_handler:info(ConnRef),
2055+
do_ensure_channels(ConnRef, NumExpected, length(ChannelList)).
2056+
2057+
channel_down_sequence(DownChannelPid, ExecChannelPid, ExecChannelId, MonRef, ConnRef, Peer) ->
2058+
ct:log("~p:~p sending order to ~p to go down", [?MODULE, ?LINE, DownChannelPid]),
2059+
exit(DownChannelPid, die),
2060+
receive {'DOWN', MonRef, _, _, _} -> ok end,
2061+
ct:log("~p:~p order executed, sending order to ~p to proceed", [?MODULE, ?LINE, Peer]),
2062+
%% Resume the peer connection to let it clean up among its channels
2063+
sys:resume(Peer),
2064+
ensure_channels(ConnRef, 1),
2065+
ExecChannelPid ! cmd,
2066+
try
2067+
receive
2068+
{ExecChannelPid, ok} ->
2069+
ct:log("~p:~p expected exec result: ~p", [?MODULE, ?LINE, ok]),
2070+
ok;
2071+
{ExecChannelPid, Result} ->
2072+
ct:log("~p:~p Unexpected exec result: ~p", [?MODULE, ?LINE, Result]),
2073+
{fail, "Unexpected exec result"}
2074+
after 5000 ->
2075+
{fail, "Exec result timeout"}
2076+
end
2077+
after
2078+
ssh_connection:close(ConnRef, ExecChannelId)
2079+
end.
2080+
19472081
%%--------------------------------------------------------------------
19482082
%% Internal functions ------------------------------------------------
19492083
%%--------------------------------------------------------------------

lib/ssh/test/ssh_echo_server.erl

Lines changed: 9 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -29,7 +29,8 @@
2929
n,
3030
id,
3131
cm,
32-
dbg = false
32+
dbg = false,
33+
parent
3334
}).
3435
-export([init/1, handle_msg/2, handle_ssh_msg/2, terminate/2]).
3536

@@ -44,13 +45,19 @@ init([N]) ->
4445
{ok, #state{n = N}};
4546
init([N,Opts]) ->
4647
State = #state{n = N,
47-
dbg = proplists:get_value(dbg,Opts,false)
48+
dbg = proplists:get_value(dbg,Opts,false),
49+
parent = proplists:get_value(parent, Opts)
4850
},
4951
?DBG(State, "init([~p])",[N]),
5052
{ok, State}.
5153

5254
handle_msg({ssh_channel_up, ChannelId, ConnectionManager}, State) ->
5355
?DBG(State, "ssh_channel_up Cid=~p ConnMngr=~p",[ChannelId,ConnectionManager]),
56+
Pid = State#state.parent,
57+
if Pid /= undefined ->
58+
Pid ! {conn_peer, ConnectionManager};
59+
true -> ok
60+
end,
5461
{ok, State#state{id = ChannelId,
5562
cm = ConnectionManager}}.
5663

0 commit comments

Comments
 (0)