Skip to content

Commit

Permalink
Merge branch 'maint'
Browse files Browse the repository at this point in the history
  • Loading branch information
u3s committed Oct 4, 2024
2 parents 358c4aa + 19ede2c commit 5439fba
Show file tree
Hide file tree
Showing 8 changed files with 119 additions and 45 deletions.
2 changes: 1 addition & 1 deletion lib/ssh/src/ssh.erl
Original file line number Diff line number Diff line change
Expand Up @@ -355,7 +355,7 @@ connect(Host0, Port, UserOptions, NegotiationTimeout)
{error, Reason};

Options ->
SocketOpts = [{active,false} | ?GET_OPT(socket_options,Options)],
SocketOpts = ?GET_OPT(socket_options,Options) ++ [{active,false}],
Host = mangle_connect_address(Host0, Options),
try
transport_connect(Host, Port, SocketOpts, Options)
Expand Down
26 changes: 11 additions & 15 deletions lib/ssh/src/ssh_acceptor.erl
Original file line number Diff line number Diff line change
Expand Up @@ -48,7 +48,7 @@ start_link(SystemSup, Address, Options) ->
%%%----------------------------------------------------------------
listen(Port, Options) ->
{_, Callback, _} = ?GET_OPT(transport, Options),
SockOpts = [{active, false}, {reuseaddr,true} | ?GET_OPT(socket_options, Options)],
SockOpts = ?GET_OPT(socket_options, Options) ++ [{active, false}, {reuseaddr,true}],
case Callback:listen(Port, SockOpts) of
{error, nxdomain} ->
Callback:listen(Port, lists:delete(inet6, SockOpts));
Expand Down Expand Up @@ -87,7 +87,6 @@ acceptor_init(Parent, SystemSup,
proc_lib:init_ack(Parent, {ok, self()}),
request_ownership(LSock, SockOwner),
acceptor_loop(Port, Address, Opts, LSock, AcceptTimeout, SystemSup);

{error,_Error} ->
%% Not open, a restart
%% Allow gen_tcp:listen to fail 4 times if eaddrinuse (It is a bug fix):
Expand All @@ -100,7 +99,6 @@ acceptor_init(Parent, SystemSup,
proc_lib:init_fail(Parent, {error,Error}, {exit, normal})
end
end;

undefined ->
%% No listening socket (nor fd option) was provided; open a listening socket:
case try_listen(Port, Opts, 4) of
Expand All @@ -112,7 +110,6 @@ acceptor_init(Parent, SystemSup,
end
end.


try_listen(Port, Opts, NtriesLeft) ->
try_listen(Port, Opts, 1, NtriesLeft).

Expand All @@ -125,7 +122,6 @@ try_listen(Port, Opts, N, Nmax) ->
Other
end.


request_ownership(LSock, SockOwner) ->
SockOwner ! {request_control,LSock,self()},
receive
Expand All @@ -141,7 +137,8 @@ acceptor_loop(Port, Address, Opts, ListenSocket, AcceptTimeout, SystemSup) ->
MaxSessions = ?GET_OPT(max_sessions, Opts),
NumSessions = number_of_connections(SystemSup),
ParallelLogin = ?GET_OPT(parallel_login, Opts),
case handle_connection(Address, Port, PeerName, Opts, Socket, MaxSessions, NumSessions, ParallelLogin) of
case handle_connection(Address, Port, PeerName, Opts, Socket,
MaxSessions, NumSessions, ParallelLogin) of
{error,Error} ->
catch close(Socket, Opts),
handle_error(Error, Address, Port, PeerName);
Expand All @@ -158,18 +155,19 @@ acceptor_loop(Port, Address, Opts, ListenSocket, AcceptTimeout, SystemSup) ->
?MODULE:acceptor_loop(Port, Address, Opts, ListenSocket, AcceptTimeout, SystemSup).

%%%----------------------------------------------------------------
handle_connection(_Address, _Port, _Peer, _Options, _Socket, MaxSessions, NumSessions, _ParallelLogin)
handle_connection(_Address, _Port, _Peer, _Options, _Socket,
MaxSessions, NumSessions, _ParallelLogin)
when NumSessions >= MaxSessions->
{error,{max_sessions,MaxSessions}};

handle_connection(_Address, _Port, {error,Error}, _Options, _Socket, _MaxSessions, _NumSessions, _ParallelLogin) ->
handle_connection(_Address, _Port, {error,Error}, _Options, _Socket,
_MaxSessions, _NumSessions, _ParallelLogin) ->
{error,Error};

handle_connection(Address, Port, _Peer, Options, Socket, _MaxSessions, _NumSessions, ParallelLogin)
handle_connection(Address, Port, _Peer, Options, Socket,
_MaxSessions, _NumSessions, ParallelLogin)
when ParallelLogin == false ->
handle_connection(Address, Port, Options, Socket);

handle_connection(Address, Port, _Peer, Options, Socket, _MaxSessions, _NumSessions, ParallelLogin)
handle_connection(Address, Port, _Peer, Options, Socket,
_MaxSessions, _NumSessions, ParallelLogin)
when ParallelLogin == true ->
Ref = make_ref(),
Pid = spawn_link(
Expand All @@ -186,8 +184,6 @@ handle_connection(Address, Port, _Peer, Options, Socket, _MaxSessions, _NumSessi
Pid ! {start,Ref},
ok.



handle_connection(Address, Port, Options0, Socket) ->
Options = ?PUT_INTERNAL_OPT([{user_pid, self()}
], Options0),
Expand Down
6 changes: 3 additions & 3 deletions lib/ssh/src/ssh_app.erl
Original file line number Diff line number Diff line change
Expand Up @@ -23,11 +23,11 @@
%%%=========================================================================
%%% Purpose : Application master and top supervisors for SSH.
%%%
%%% -----> ssh_sup -----+-----> sshc_sup --+--> "system sup" (etc)
%%% -----> ssh_sup -----+-----> sshc_sup --+--> "connection sup" (etc)
%%% | |
%%% | +--> "system sup" (etc)
%%% | +--> "connection sup" (etc)
%%% | :
%%% | +--> "system sup" (etc)
%%% | +--> "connection sup" (etc)
%%% |
%%% +-----> sshc_sup --+--> "system sup" (etc)
%%% |
Expand Down
49 changes: 33 additions & 16 deletions lib/ssh/src/ssh_connection_handler.erl
Original file line number Diff line number Diff line change
Expand Up @@ -120,12 +120,13 @@ start_link(Role, Id, Socket, Options) ->
Others
end.


takeover(ConnPid, client, Socket, Options) ->
group_leader(group_leader(), ConnPid),
takeover(ConnPid, common, Socket, Options);

takeover(ConnPid, _, Socket, Options) ->
takeover(ConnPid, Role, Socket, Options) ->
case Role of
client ->
group_leader(group_leader(), ConnPid);
_ ->
ok
end,
{_, Callback, _} = ?GET_OPT(transport, Options),
case Callback:controlling_process(Socket, ConnPid) of
ok ->
Expand All @@ -135,7 +136,7 @@ takeover(ConnPid, _, Socket, Options) ->
Options,
?GET_OPT(negotiation_timeout, Options)
),
handshake(ConnPid, Ref, NegTimeout);
handshake(ConnPid, Role, Ref, NegTimeout);
{error, Reason} ->
{error, Reason}
end.
Expand Down Expand Up @@ -490,25 +491,41 @@ init_ssh_record(Role, Socket, PeerAddr, Opts) ->
}
end.


handshake(Pid, Ref, Timeout) ->
handshake(ConnPid, server, Ref, Timeout) ->
receive
{Pid, ssh_connected} ->
{ConnPid, ssh_connected} ->
erlang:demonitor(Ref, [flush]),
{ok, Pid};
{Pid, {not_connected, Reason}} ->
{ok, ConnPid};
{ConnPid, {not_connected, Reason}} ->
erlang:demonitor(Ref, [flush]),
{error, Reason};
{'DOWN', Ref, process, Pid, {shutdown, Reason}} ->
{'DOWN', Ref, process, ConnPid, {shutdown, Reason}} ->
{error, Reason};
{'DOWN', Ref, process, Pid, Reason} ->
{'DOWN', Ref, process, ConnPid, Reason} ->
{error, Reason};
{'EXIT',_,Reason} ->
stop(Pid),
stop(ConnPid),
{error, {exit,Reason}}
after Timeout ->
erlang:demonitor(Ref, [flush]),
ssh_connection_handler:stop(Pid),
ssh_connection_handler:stop(ConnPid),
{error, timeout}
end;
handshake(ConnPid, client, Ref, Timeout) ->
receive
{ConnPid, ssh_connected} ->
erlang:demonitor(Ref, [flush]),
{ok, ConnPid};
{ConnPid, {not_connected, Reason}} ->
erlang:demonitor(Ref, [flush]),
{error, Reason};
{'DOWN', Ref, process, ConnPid, {shutdown, Reason}} ->
{error, Reason};
{'DOWN', Ref, process, ConnPid, Reason} ->
{error, Reason}
after Timeout ->
erlang:demonitor(Ref, [flush]),
ssh_connection_handler:stop(ConnPid),
{error, timeout}
end.

Expand Down
4 changes: 2 additions & 2 deletions lib/ssh/src/ssh_info.erl
Original file line number Diff line number Diff line change
Expand Up @@ -140,7 +140,7 @@ format_sup(client,
Indent) when is_reference(Ref) ->
[io_lib:format("~sLocal: ~s~n"
"~sRemote: ~s (Version: ~s)~n"
"~sConnectionRef=~s, subsys_sup=~s~n",
"~sConnectionRef=~s, connection_sup=~s~n",
[indent(Indent), local_addr(ConnPid),
indent(Indent), peer_addr(ConnPid), peer_version(client,ConnPid),
indent(Indent), print_pid(ConnPid), print_pid(ConnSup)
Expand All @@ -157,7 +157,7 @@ format_sup(server,
},
Indent) when is_reference(Ref) ->
[io_lib:format("~sRemote: ~s (Version: ~s)~n"
"~sConnectionRef=~s, subsys_sup=~s~n",
"~sConnectionRef=~s, connection_sup=~s~n",
[indent(Indent), peer_addr(ConnPid), peer_version(server,ConnPid),
indent(Indent), print_pid(ConnPid), print_pid(ConnSup)
]),
Expand Down
5 changes: 2 additions & 3 deletions lib/ssh/src/ssh_tcpip_forward_acceptor.erl
Original file line number Diff line number Diff line change
Expand Up @@ -36,9 +36,8 @@ supervised_start(FwdSup, {ListenAddrStr, ListenPort}, ConnectToAddr, ChanType, C
case get_fwd_listen_opts(ListenAddrStr) of
{ok,Opts} ->
%% start listening on Addr:BoundPort
case gen_tcp:listen(ListenPort, [binary,
{reuseaddr,true},
{active,false} | Opts]) of
case gen_tcp:listen(ListenPort,
Opts ++ [binary, {reuseaddr,true}, {active,false}]) of
{ok,LSock} ->
{ok,{_, TrueListenPort}} = inet:sockname(LSock),
ssh_tcpip_forward_acceptor_sup:start_child(FwdSup,
Expand Down
57 changes: 57 additions & 0 deletions lib/ssh/test/ssh_connection_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -107,6 +107,8 @@
start_shell_sock_exec_fun/1,
start_subsystem_on_closed_channel/1,
stop_listener/1,
trap_exit_connect/1,
trap_exit_daemon/1,
ssh_exec_echo/2 % called as an MFA
]).

Expand Down Expand Up @@ -134,6 +136,8 @@ all() ->
start_shell,
new_shell_dumb_term,
new_shell_xterm_term,
trap_exit_connect,
trap_exit_daemon,
start_shell_pty,
start_shell_exec,
start_shell_exec_fun,
Expand Down Expand Up @@ -1331,6 +1335,59 @@ do_start_shell_exec_fun(Fun, Command, Expect, ExpectType, ReceiveFun, Config) ->
ssh:close(ConnectionRef),
ssh:stop_daemon(Pid).

%%--------------------------------------------------------------------
%% Issue GH-8223
trap_exit_connect(Config) when is_list(Config) ->
PrivDir = proplists:get_value(priv_dir, Config),
UserDir = filename:join(PrivDir, nopubkey),
file:make_dir(UserDir),
SysDir = proplists:get_value(data_dir, Config),
{Pid, Host, Port} = ssh_test_lib:daemon([{system_dir, SysDir},
{user_dir, UserDir},
{password, "morot"}]),
%% Fake an EXIT message
ExitMsg = {'EXIT', self(), make_ref()},
self() ! ExitMsg,

{ok, ConnectionRef} = ssh:connect(Host, Port, [{silently_accept_hosts, true},
{save_accepted_host, false},
{user, "foo"},
{password, "morot"},
{user_interaction, true},
{user_dir, UserDir}]),
ssh:close(ConnectionRef),
ssh:stop_daemon(Pid),

%% Ensure the EXIT message is still there
receive
ExitMsg -> ok
after 0 ->
ct:fail("No EXIT message")
end.

%%--------------------------------------------------------------------
%% Issue GH-8223
trap_exit_daemon(Config) when is_list(Config) ->
PrivDir = proplists:get_value(priv_dir, Config),
UserDir = filename:join(PrivDir, nopubkey),
file:make_dir(UserDir),
SysDir = proplists:get_value(data_dir, Config),

%% Fake an EXIT message
ExitMsg = {'EXIT', self(), make_ref()},
self() ! ExitMsg,

{ok, DaemonRef} = ssh:daemon(0, [{system_dir, SysDir},
{user_dir, UserDir}]),
ssh:stop_daemon(DaemonRef),

%% Ensure the EXIT message is still there
receive
ExitMsg -> ok
after 0 ->
ct:fail("No EXIT message")
end.

%%--------------------------------------------------------------------
start_shell_sock_exec_fun(Config) when is_list(Config) ->
PrivDir = proplists:get_value(priv_dir, Config),
Expand Down
15 changes: 10 additions & 5 deletions lib/ssh/test/ssh_protocol_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1250,18 +1250,23 @@ find_handshake_parent([{{ssh_acceptor_sup,{address,_,Port,_}},
Port, {AccP,AccC,AccH}) ->
ParentHandshakers =
[{PidW,PidH} ||
{{ssh_acceptor_sup,{address,_,Port1,_}}, PidW, worker, [ssh_acceptor]} <-
supervisor:which_children(PidS),
{{ssh_acceptor_sup,{address,_,Port1,_}}, PidW, worker,
[ssh_acceptor]} <- supervisor:which_children(PidS),
Port1 == Port,
PidH <- element(2, process_info(PidW,links)),
is_pid(PidH),
process_info(PidH,current_function) == {current_function,{ssh_connection_handler,handshake,3}}],
process_info(PidH,current_function) ==
{current_function,
{ssh_connection_handler,handshake,4}}],
{Parents,Handshakers} = lists:unzip(ParentHandshakers),
find_handshake_parent(T, Port, {AccP++Parents, AccC, AccH++Handshakers});

find_handshake_parent([{_Ref,PidS,supervisor,[ssh_connection_sup]}|T], Port, {AccP,AccC,AccH}) ->
find_handshake_parent([{_Ref,PidS,supervisor,[ssh_connection_sup]}|T],
Port, {AccP,AccC,AccH}) ->
Connections =
[Pid || {connection,Pid,worker,[ssh_connection_handler]} <- supervisor:which_children(PidS)],
[Pid ||
{connection,Pid,worker,[ssh_connection_handler]} <-
supervisor:which_children(PidS)],
find_handshake_parent(T, Port, {AccP, AccC++Connections, AccH});

find_handshake_parent([_|T], Port, Acc) ->
Expand Down

0 comments on commit 5439fba

Please sign in to comment.