Skip to content

Commit

Permalink
Merge branch 'kuba/ssh/no_system_sup_for_client/GH-7550' into maint
Browse files Browse the repository at this point in the history
OTP-19124

* kuba/ssh/no_system_sup_for_client/GH-7550:
  ssh: rename ssh_subsystem_sup to ssh_connection_sup
  ssh: do_start_subsystem added, skip system_sup for client
  ssh: remove unused Address from function arguments
  ssh: ssh_connection_SUITE prints interesting events
  ssh: ssh_connection_SUITE interrupted_send explained in code comment
  • Loading branch information
u3s committed Sep 23, 2024
2 parents 03887c7 + 5862f24 commit 0bf06d2
Show file tree
Hide file tree
Showing 18 changed files with 331 additions and 202 deletions.
2 changes: 1 addition & 1 deletion lib/compiler/test/compile_SUITE_data/ssh_connect.hrl
Original file line number Diff line number Diff line change
Expand Up @@ -269,5 +269,5 @@
suggest_window_size,
suggest_packet_size,
exec,
sub_system_supervisor
connection_supervisor
}).
2 changes: 1 addition & 1 deletion lib/ssh/src/Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -80,7 +80,7 @@ MODULES= \
ssh_sftpd \
ssh_sftpd_file\
ssh_shell \
ssh_subsystem_sup \
ssh_connection_sup \
ssh_system_sup \
ssh_tcpip_forward_srv \
ssh_tcpip_forward_client \
Expand Down
4 changes: 2 additions & 2 deletions lib/ssh/src/ssh.app.src
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,7 @@
ssh_sftpd,
ssh_sftpd_file,
ssh_sftpd_file_api,
ssh_subsystem_sup,
ssh_connection_sup,
ssh_tcpip_forward_client,
ssh_tcpip_forward_srv,
ssh_tcpip_forward_acceptor_sup,
Expand All @@ -51,7 +51,7 @@
ssh_acceptor,
ssh_channel_sup,
ssh_connection_handler,
ssh_subsystem_sup,
ssh_connection_sup,
ssh_system_sup
]},
{default_filter, rm} %% rm | filter
Expand Down
15 changes: 6 additions & 9 deletions lib/ssh/src/ssh.erl
Original file line number Diff line number Diff line change
Expand Up @@ -414,7 +414,7 @@ continue_connect(Socket, Options0, NegTimeout) ->
port = SockPort,
profile = ?GET_OPT(profile,Options)
},
ssh_system_sup:start_subsystem(client, Address, Socket, Options).
ssh_system_sup:start_connection(client, Address, Socket, Options).

%%--------------------------------------------------------------------
-doc "Closes an SSH connection.".
Expand Down Expand Up @@ -532,7 +532,7 @@ daemon(Socket, UserOptions) ->
profile = ?GET_OPT(profile,Options0)
},
Options = ?PUT_INTERNAL_OPT({connected_socket, Socket}, Options0),
case ssh_system_sup:start_subsystem(server, Address, Socket, Options) of
case ssh_system_sup:start_connection(server, Address, Socket, Options) of
{ok,Pid} ->
{ok,Pid};
{error, {already_started, _}} ->
Expand Down Expand Up @@ -610,8 +610,7 @@ daemon(Host0, Port0, UserOptions0) when 0 =< Port0, Port0 =< 65535,

%% throws error:Error if no usable hostkey is found
ssh_connection_handler:available_hkey_algorithms(server, Options1),
ssh_system_sup:start_system(server,
#address{address = Host,
ssh_system_sup:start_system(#address{address = Host,
port = Port,
profile = ?GET_OPT(profile,Options1)},
Options1)
Expand Down Expand Up @@ -799,16 +798,15 @@ stop_listener(Address, Port, Profile) ->
lists:foreach(fun({Sup,_Addr}) ->
stop_listener(Sup)
end,
ssh_system_sup:addresses(server,
#address{address=Address,
ssh_system_sup:addresses(#address{address=Address,
port=Port,
profile=Profile})).

-doc(#{equiv => stop_daemon/3}).
-spec stop_daemon(DaemonRef::daemon_ref()) -> ok.

stop_daemon(SysSup) ->
ssh_system_sup:stop_system(server, SysSup).
ssh_system_sup:stop_system(SysSup).


-doc(#{equiv => stop_daemon/3}).
Expand All @@ -826,8 +824,7 @@ stop_daemon(Address, Port, Profile) ->
lists:foreach(fun({Sup,_Addr}) ->
stop_daemon(Sup)
end,
ssh_system_sup:addresses(server,
#address{address=Address,
ssh_system_sup:addresses(#address{address=Address,
port=Port,
profile=Profile})).

Expand Down
4 changes: 2 additions & 2 deletions lib/ssh/src/ssh_acceptor.erl
Original file line number Diff line number Diff line change
Expand Up @@ -191,7 +191,7 @@ handle_connection(Address, Port, _Peer, Options, Socket, _MaxSessions, _NumSessi
handle_connection(Address, Port, Options0, Socket) ->
Options = ?PUT_INTERNAL_OPT([{user_pid, self()}
], Options0),
ssh_system_sup:start_subsystem(server,
ssh_system_sup:start_connection(server,
#address{address = Address,
port = Port,
profile = ?GET_OPT(profile,Options)
Expand Down Expand Up @@ -247,7 +247,7 @@ handle_error(Reason, ToAddress, ToPort, FromAddress, FromPort) ->

%%%----------------------------------------------------------------
number_of_connections(SysSupPid) ->
lists:foldl(fun({_Ref,_Pid,supervisor,[ssh_subsystem_sup]}, N) -> N+1;
lists:foldl(fun({_Ref,_Pid,supervisor,[ssh_connection_sup]}, N) -> N+1;
(_, N) -> N
end, 0, supervisor:which_children(SysSupPid)).

Expand Down
2 changes: 1 addition & 1 deletion lib/ssh/src/ssh_connect.hrl
Original file line number Diff line number Diff line change
Expand Up @@ -269,5 +269,5 @@
suggest_window_size,
suggest_packet_size,
exec,
sub_system_supervisor
connection_supervisor
}).
20 changes: 10 additions & 10 deletions lib/ssh/src/ssh_connection.erl
Original file line number Diff line number Diff line change
Expand Up @@ -886,15 +886,15 @@ handle_msg(#ssh_msg_channel_open{channel_type = "forwarded-tcpip",
suggest_window_size = WinSz,
suggest_packet_size = PktSz,
options = Options,
sub_system_supervisor = SubSysSup
connection_supervisor = ConnectionSup
} = C,
client, _SSH) ->
{ReplyMsg, NextChId} =
case ssh_connection_handler:retrieve(C, {tcpip_forward,ConnectedHost,ConnectedPort}) of
{ok, {ConnectToHost,ConnectToPort}} ->
case gen_tcp:connect(ConnectToHost, ConnectToPort, [{active,false}, binary]) of
{ok,Sock} ->
{ok,Pid} = ssh_subsystem_sup:start_channel(client, SubSysSup, self(),
{ok,Pid} = ssh_connection_sup:start_channel(client, ConnectionSup, self(),
ssh_tcpip_forward_client, ChId,
[Sock], undefined, Options),
ssh_client_channel:cache_update(Cache,
Expand Down Expand Up @@ -944,7 +944,7 @@ handle_msg(#ssh_msg_channel_open{channel_type = "direct-tcpip",
suggest_window_size = WinSz,
suggest_packet_size = PktSz,
options = Options,
sub_system_supervisor = SubSysSup
connection_supervisor = ConnectionSup
} = C,
server, _SSH) ->
{ReplyMsg, NextChId} =
Expand All @@ -960,7 +960,7 @@ handle_msg(#ssh_msg_channel_open{channel_type = "direct-tcpip",
case gen_tcp:connect(binary_to_list(HostToConnect), PortToConnect,
[{active,false}, binary]) of
{ok,Sock} ->
{ok,Pid} = ssh_subsystem_sup:start_channel(server, SubSysSup, self(),
{ok,Pid} = ssh_connection_sup:start_channel(server, ConnectionSup, self(),
ssh_tcpip_forward_srv, ChId,
[Sock], undefined, Options),
ssh_client_channel:cache_update(Cache,
Expand Down Expand Up @@ -1192,8 +1192,8 @@ handle_msg(#ssh_msg_global_request{name = <<"tcpip-forward">>,
{[{connection_reply, request_failure_msg()}], Connection};

true ->
SubSysSup = ?GET_INTERNAL_OPT(subsystem_sup, Opts),
FwdSup = ssh_subsystem_sup:tcpip_fwd_supervisor(SubSysSup),
ConnectionSup = ?GET_INTERNAL_OPT(connection_sup, Opts),
FwdSup = ssh_connection_sup:tcpip_fwd_supervisor(ConnectionSup),
ConnPid = self(),
case ssh_tcpip_forward_acceptor:supervised_start(FwdSup,
{ListenAddrStr, ListenPort},
Expand Down Expand Up @@ -1423,22 +1423,22 @@ setup_session(#connection{channel_cache = Cache,
start_cli(#connection{options = Options,
cli_spec = CliSpec,
exec = Exec,
sub_system_supervisor = SubSysSup}, ChannelId) ->
connection_supervisor = ConnectionSup}, ChannelId) ->
case CliSpec of
no_cli ->
{error, cli_disabled};
{CbModule, Args} ->
ssh_subsystem_sup:start_channel(server, SubSysSup, self(), CbModule, ChannelId, Args, Exec, Options)
ssh_connection_sup:start_channel(server, ConnectionSup, self(), CbModule, ChannelId, Args, Exec, Options)
end.


start_subsystem(BinName, #connection{options = Options,
sub_system_supervisor = SubSysSup},
connection_supervisor = ConnectionSup},
#channel{local_id = ChannelId}, _ReplyMsg) ->
Name = binary_to_list(BinName),
case check_subsystem(Name, Options) of
{Callback, Opts} when is_atom(Callback), Callback =/= none ->
ssh_subsystem_sup:start_channel(server, SubSysSup, self(), Callback, ChannelId, Opts, undefined, Options);
ssh_connection_sup:start_channel(server, ConnectionSup, self(), Callback, ChannelId, Opts, undefined, Options);
{none, _} ->
{error, bad_subsystem};
{_, _} ->
Expand Down
28 changes: 14 additions & 14 deletions lib/ssh/src/ssh_connection_handler.erl
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@
%%====================================================================

%%% Start and stop
-export([start_link/4, start_link/5,
-export([start_link/3, start_link/4,
takeover/4,
stop/1
]).
Expand Down Expand Up @@ -99,10 +99,10 @@
%% Start / stop
%%====================================================================

start_link(Role, Address, Socket, Options) ->
start_link(Role, Address, undefined, Socket, Options).
start_link(Role, Socket, Options) ->
start_link(Role, undefined, Socket, Options).

start_link(Role, _Address=#address{}, Id, Socket, Options) ->
start_link(Role, Id, Socket, Options) ->
case gen_statem:start_link(?MODULE,
[Role, Socket, Options],
[{spawn_opt, [{message_queue_data,off_heap}]}]) of
Expand All @@ -111,7 +111,7 @@ start_link(Role, _Address=#address{}, Id, Socket, Options) ->
%% Announce the ConnectionRef to the system supervisor so it could
%% 1) initiate the socket handover, and
%% 2) be returned to whoever called for example ssh:connect; the Pid
%% returned from this function is "consumed" by the subsystem
%% returned from this function is "consumed" by the connection
%% supervisor.
?GET_INTERNAL_OPT(user_pid,Options) ! {new_connection_ref, Id, Pid},
{ok, Pid};
Expand Down Expand Up @@ -197,8 +197,8 @@ open_channel(ConnectionHandler,

%% . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . .
start_channel(ConnectionHandler, CallbackModule, ChannelId, Args, Exec) ->
{ok, {SubSysSup,Role,Opts}} = call(ConnectionHandler, get_misc),
ssh_subsystem_sup:start_channel(Role, SubSysSup,
{ok, {ConnectionSup,Role,Opts}} = call(ConnectionHandler, get_misc),
ssh_connection_sup:start_channel(Role, ConnectionSup,
ConnectionHandler, CallbackModule, ChannelId,
Args, Exec, Opts).

Expand Down Expand Up @@ -418,7 +418,7 @@ init_connection_record(Role, Socket, Opts) ->
suggest_packet_size = PktSz,
requests = [],
options = Opts,
sub_system_supervisor = ?GET_INTERNAL_OPT(subsystem_sup, Opts)
connection_supervisor = ?GET_INTERNAL_OPT(connection_sup, Opts)
},
case Role of
server ->
Expand Down Expand Up @@ -1022,8 +1022,8 @@ handle_event({call,From}, {eof, ChannelId}, StateName, D0)

handle_event({call,From}, get_misc, StateName,
#data{connection_state = #connection{options = Opts}} = D) when ?CONNECTED(StateName) ->
SubSysSup = ?GET_INTERNAL_OPT(subsystem_sup, Opts),
Reply = {ok, {SubSysSup, ?role(StateName), Opts}},
ConnectionSup = ?GET_INTERNAL_OPT(connection_sup, Opts),
Reply = {ok, {ConnectionSup, ?role(StateName), Opts}},
{keep_state, D, [{reply,From,Reply}]};

handle_event({call,From},
Expand Down Expand Up @@ -1286,9 +1286,9 @@ handle_event(info, check_cache, _, D) ->
handle_event(info, {fwd_connect_received, Sock, ChId, ChanCB}, StateName, #data{connection_state = Connection}) ->
#connection{options = Options,
channel_cache = Cache,
sub_system_supervisor = SubSysSup} = Connection,
connection_supervisor = ConnectionSup} = Connection,
Channel = ssh_client_channel:cache_lookup(Cache, ChId),
{ok,Pid} = ssh_subsystem_sup:start_channel(?role(StateName), SubSysSup, self(), ChanCB, ChId, [Sock], undefined, Options),
{ok,Pid} = ssh_connection_sup:start_channel(?role(StateName), ConnectionSup, self(), ChanCB, ChId, [Sock], undefined, Options),
ssh_client_channel:cache_update(Cache, Channel#channel{user=Pid}),
gen_tcp:controlling_process(Sock, Pid),
inet:setopts(Sock, [{active,once}]),
Expand All @@ -1297,8 +1297,8 @@ handle_event(info, {fwd_connect_received, Sock, ChId, ChanCB}, StateName, #data{
handle_event({call,From},
{handle_direct_tcpip, ListenHost, ListenPort, ConnectToHost, ConnectToPort, _Timeout},
_StateName,
#data{connection_state = #connection{sub_system_supervisor=SubSysSup}}) ->
case ssh_tcpip_forward_acceptor:supervised_start(ssh_subsystem_sup:tcpip_fwd_supervisor(SubSysSup),
#data{connection_state = #connection{connection_supervisor=ConnectionSup}}) ->
case ssh_tcpip_forward_acceptor:supervised_start(ssh_connection_sup:tcpip_fwd_supervisor(ConnectionSup),
{ListenHost, ListenPort},
{ConnectToHost, ConnectToPort},
"direct-tcpip", ssh_tcpip_forward_client,
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -19,17 +19,17 @@
%%
%%
%%----------------------------------------------------------------------
%% Purpose: The ssh subsystem supervisor
%% Purpose: The ssh connection supervisor
%%----------------------------------------------------------------------

-module(ssh_subsystem_sup).
-module(ssh_connection_sup).
-moduledoc false.

-behaviour(supervisor).

-include("ssh.hrl").

-export([start_link/5,
-export([start_link/4,
start_channel/8,
tcpip_fwd_supervisor/1
]).
Expand All @@ -40,8 +40,8 @@
%%%=========================================================================
%%% API
%%%=========================================================================
start_link(Role, Address=#address{}, Id, Socket, Options) ->
case supervisor:start_link(?MODULE, [Role, Address, Id, Socket, Options]) of
start_link(Role, Id, Socket, Options) ->
case supervisor:start_link(?MODULE, [Role, Id, Socket, Options]) of
{error, {shutdown, {failed_to_start_child, _, Error}}} ->
{error,Error};
Other ->
Expand All @@ -52,52 +52,47 @@ start_channel(Role, SupPid, ConnRef, Callback, Id, Args, Exec, Opts) ->
ChannelSup = channel_supervisor(SupPid),
ssh_channel_sup:start_child(Role, ChannelSup, ConnRef, Callback, Id, Args, Exec, Opts).

tcpip_fwd_supervisor(SubSysSup) ->
find_child(tcpip_forward_acceptor_sup, SubSysSup).
tcpip_fwd_supervisor(ConnectionSup) ->
find_child(tcpip_forward_acceptor_sup, ConnectionSup).


%%%=========================================================================
%%% Supervisor callback
%%%=========================================================================
init([Role, Address, Id, Socket, Options]) ->
ssh_lib:set_label(Role, {subsystem_sup, Socket}),
SubSysSup = self(),
init([Role, Id, Socket, Options]) ->
ssh_lib:set_label(Role, {connection_sup, Socket}),
ConnectionSup = self(),
SupFlags = #{strategy => one_for_all,
auto_shutdown => any_significant,
intensity => 0,
period => 3600
},
ChildSpecs = [#{id => connection,
restart => temporary,
type => worker,
significant => true,
start => {ssh_connection_handler,
start_link,
[Role, Address, Id, Socket,
?PUT_INTERNAL_OPT([
{subsystem_sup, SubSysSup}
], Options)
]
}
},
#{id => channel_sup,
restart => temporary,
type => supervisor,
start => {ssh_channel_sup, start_link, [Options]}
},
period => 3600},
ChildSpecs =
[#{id => connection,
restart => temporary,
type => worker,
significant => true,
start => {ssh_connection_handler,
start_link,
[Role, Id, Socket,
?PUT_INTERNAL_OPT([{connection_sup, ConnectionSup}], Options)]}
},
#{id => channel_sup,
restart => temporary,
type => supervisor,
start => {ssh_channel_sup, start_link, [Options]}
},

#{id => tcpip_forward_acceptor_sup,
restart => temporary,
type => supervisor,
start => {ssh_tcpip_forward_acceptor_sup, start_link, []}
}
],
#{id => tcpip_forward_acceptor_sup,
restart => temporary,
type => supervisor,
start => {ssh_tcpip_forward_acceptor_sup, start_link, []}
}],
{ok, {SupFlags,ChildSpecs}}.

%%%=========================================================================
%%% Internal functions
%%%=========================================================================
channel_supervisor(SubSysSup) -> find_child(channel_sup, SubSysSup).
channel_supervisor(ConnectionSup) -> find_child(channel_sup, ConnectionSup).

find_child(Id, Sup) when is_pid(Sup) ->
try
Expand Down
Loading

0 comments on commit 0bf06d2

Please sign in to comment.