Skip to content

Commit 532436e

Browse files
committed
ssh: rename ssh_subsystem_sup to ssh_connection_sup
- rename in order to improve supervision readability
1 parent 4727d51 commit 532436e

15 files changed

+101
-106
lines changed

lib/compiler/test/compile_SUITE_data/ssh_connect.hrl

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -269,5 +269,5 @@
269269
suggest_window_size,
270270
suggest_packet_size,
271271
exec,
272-
sub_system_supervisor
272+
connection_supervisor
273273
}).

lib/ssh/src/Makefile

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -80,7 +80,7 @@ MODULES= \
8080
ssh_sftpd \
8181
ssh_sftpd_file\
8282
ssh_shell \
83-
ssh_subsystem_sup \
83+
ssh_connection_sup \
8484
ssh_system_sup \
8585
ssh_tcpip_forward_srv \
8686
ssh_tcpip_forward_client \

lib/ssh/src/ssh.app.src

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -36,7 +36,7 @@
3636
ssh_sftpd,
3737
ssh_sftpd_file,
3838
ssh_sftpd_file_api,
39-
ssh_subsystem_sup,
39+
ssh_connection_sup,
4040
ssh_tcpip_forward_client,
4141
ssh_tcpip_forward_srv,
4242
ssh_tcpip_forward_acceptor_sup,
@@ -51,7 +51,7 @@
5151
ssh_acceptor,
5252
ssh_channel_sup,
5353
ssh_connection_handler,
54-
ssh_subsystem_sup,
54+
ssh_connection_sup,
5555
ssh_system_sup
5656
]},
5757
{default_filter, rm} %% rm | filter

lib/ssh/src/ssh.erl

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -414,7 +414,7 @@ continue_connect(Socket, Options0, NegTimeout) ->
414414
port = SockPort,
415415
profile = ?GET_OPT(profile,Options)
416416
},
417-
ssh_system_sup:start_subsystem(client, Address, Socket, Options).
417+
ssh_system_sup:start_connection(client, Address, Socket, Options).
418418

419419
%%--------------------------------------------------------------------
420420
-doc "Closes an SSH connection.".
@@ -532,7 +532,7 @@ daemon(Socket, UserOptions) ->
532532
profile = ?GET_OPT(profile,Options0)
533533
},
534534
Options = ?PUT_INTERNAL_OPT({connected_socket, Socket}, Options0),
535-
case ssh_system_sup:start_subsystem(server, Address, Socket, Options) of
535+
case ssh_system_sup:start_connection(server, Address, Socket, Options) of
536536
{ok,Pid} ->
537537
{ok,Pid};
538538
{error, {already_started, _}} ->

lib/ssh/src/ssh_acceptor.erl

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -191,7 +191,7 @@ handle_connection(Address, Port, _Peer, Options, Socket, _MaxSessions, _NumSessi
191191
handle_connection(Address, Port, Options0, Socket) ->
192192
Options = ?PUT_INTERNAL_OPT([{user_pid, self()}
193193
], Options0),
194-
ssh_system_sup:start_subsystem(server,
194+
ssh_system_sup:start_connection(server,
195195
#address{address = Address,
196196
port = Port,
197197
profile = ?GET_OPT(profile,Options)
@@ -247,7 +247,7 @@ handle_error(Reason, ToAddress, ToPort, FromAddress, FromPort) ->
247247

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

lib/ssh/src/ssh_connect.hrl

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -269,5 +269,5 @@
269269
suggest_window_size,
270270
suggest_packet_size,
271271
exec,
272-
sub_system_supervisor
272+
connection_supervisor
273273
}).

lib/ssh/src/ssh_connection.erl

Lines changed: 10 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -886,15 +886,15 @@ handle_msg(#ssh_msg_channel_open{channel_type = "forwarded-tcpip",
886886
suggest_window_size = WinSz,
887887
suggest_packet_size = PktSz,
888888
options = Options,
889-
sub_system_supervisor = SubSysSup
889+
connection_supervisor = ConnectionSup
890890
} = C,
891891
client, _SSH) ->
892892
{ReplyMsg, NextChId} =
893893
case ssh_connection_handler:retrieve(C, {tcpip_forward,ConnectedHost,ConnectedPort}) of
894894
{ok, {ConnectToHost,ConnectToPort}} ->
895895
case gen_tcp:connect(ConnectToHost, ConnectToPort, [{active,false}, binary]) of
896896
{ok,Sock} ->
897-
{ok,Pid} = ssh_subsystem_sup:start_channel(client, SubSysSup, self(),
897+
{ok,Pid} = ssh_connection_sup:start_channel(client, ConnectionSup, self(),
898898
ssh_tcpip_forward_client, ChId,
899899
[Sock], undefined, Options),
900900
ssh_client_channel:cache_update(Cache,
@@ -944,7 +944,7 @@ handle_msg(#ssh_msg_channel_open{channel_type = "direct-tcpip",
944944
suggest_window_size = WinSz,
945945
suggest_packet_size = PktSz,
946946
options = Options,
947-
sub_system_supervisor = SubSysSup
947+
connection_supervisor = ConnectionSup
948948
} = C,
949949
server, _SSH) ->
950950
{ReplyMsg, NextChId} =
@@ -960,7 +960,7 @@ handle_msg(#ssh_msg_channel_open{channel_type = "direct-tcpip",
960960
case gen_tcp:connect(binary_to_list(HostToConnect), PortToConnect,
961961
[{active,false}, binary]) of
962962
{ok,Sock} ->
963-
{ok,Pid} = ssh_subsystem_sup:start_channel(server, SubSysSup, self(),
963+
{ok,Pid} = ssh_connection_sup:start_channel(server, ConnectionSup, self(),
964964
ssh_tcpip_forward_srv, ChId,
965965
[Sock], undefined, Options),
966966
ssh_client_channel:cache_update(Cache,
@@ -1192,8 +1192,8 @@ handle_msg(#ssh_msg_global_request{name = <<"tcpip-forward">>,
11921192
{[{connection_reply, request_failure_msg()}], Connection};
11931193

11941194
true ->
1195-
SubSysSup = ?GET_INTERNAL_OPT(subsystem_sup, Opts),
1196-
FwdSup = ssh_subsystem_sup:tcpip_fwd_supervisor(SubSysSup),
1195+
ConnectionSup = ?GET_INTERNAL_OPT(connection_sup, Opts),
1196+
FwdSup = ssh_connection_sup:tcpip_fwd_supervisor(ConnectionSup),
11971197
ConnPid = self(),
11981198
case ssh_tcpip_forward_acceptor:supervised_start(FwdSup,
11991199
{ListenAddrStr, ListenPort},
@@ -1423,22 +1423,22 @@ setup_session(#connection{channel_cache = Cache,
14231423
start_cli(#connection{options = Options,
14241424
cli_spec = CliSpec,
14251425
exec = Exec,
1426-
sub_system_supervisor = SubSysSup}, ChannelId) ->
1426+
connection_supervisor = ConnectionSup}, ChannelId) ->
14271427
case CliSpec of
14281428
no_cli ->
14291429
{error, cli_disabled};
14301430
{CbModule, Args} ->
1431-
ssh_subsystem_sup:start_channel(server, SubSysSup, self(), CbModule, ChannelId, Args, Exec, Options)
1431+
ssh_connection_sup:start_channel(server, ConnectionSup, self(), CbModule, ChannelId, Args, Exec, Options)
14321432
end.
14331433

14341434

14351435
start_subsystem(BinName, #connection{options = Options,
1436-
sub_system_supervisor = SubSysSup},
1436+
connection_supervisor = ConnectionSup},
14371437
#channel{local_id = ChannelId}, _ReplyMsg) ->
14381438
Name = binary_to_list(BinName),
14391439
case check_subsystem(Name, Options) of
14401440
{Callback, Opts} when is_atom(Callback), Callback =/= none ->
1441-
ssh_subsystem_sup:start_channel(server, SubSysSup, self(), Callback, ChannelId, Opts, undefined, Options);
1441+
ssh_connection_sup:start_channel(server, ConnectionSup, self(), Callback, ChannelId, Opts, undefined, Options);
14421442
{none, _} ->
14431443
{error, bad_subsystem};
14441444
{_, _} ->

lib/ssh/src/ssh_connection_handler.erl

Lines changed: 10 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -111,7 +111,7 @@ start_link(Role, Id, Socket, Options) ->
111111
%% Announce the ConnectionRef to the system supervisor so it could
112112
%% 1) initiate the socket handover, and
113113
%% 2) be returned to whoever called for example ssh:connect; the Pid
114-
%% returned from this function is "consumed" by the subsystem
114+
%% returned from this function is "consumed" by the connection
115115
%% supervisor.
116116
?GET_INTERNAL_OPT(user_pid,Options) ! {new_connection_ref, Id, Pid},
117117
{ok, Pid};
@@ -197,8 +197,8 @@ open_channel(ConnectionHandler,
197197

198198
%% . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . .
199199
start_channel(ConnectionHandler, CallbackModule, ChannelId, Args, Exec) ->
200-
{ok, {SubSysSup,Role,Opts}} = call(ConnectionHandler, get_misc),
201-
ssh_subsystem_sup:start_channel(Role, SubSysSup,
200+
{ok, {ConnectionSup,Role,Opts}} = call(ConnectionHandler, get_misc),
201+
ssh_connection_sup:start_channel(Role, ConnectionSup,
202202
ConnectionHandler, CallbackModule, ChannelId,
203203
Args, Exec, Opts).
204204

@@ -418,7 +418,7 @@ init_connection_record(Role, Socket, Opts) ->
418418
suggest_packet_size = PktSz,
419419
requests = [],
420420
options = Opts,
421-
sub_system_supervisor = ?GET_INTERNAL_OPT(subsystem_sup, Opts)
421+
connection_supervisor = ?GET_INTERNAL_OPT(connection_sup, Opts)
422422
},
423423
case Role of
424424
server ->
@@ -1022,8 +1022,8 @@ handle_event({call,From}, {eof, ChannelId}, StateName, D0)
10221022

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

10291029
handle_event({call,From},
@@ -1286,9 +1286,9 @@ handle_event(info, check_cache, _, D) ->
12861286
handle_event(info, {fwd_connect_received, Sock, ChId, ChanCB}, StateName, #data{connection_state = Connection}) ->
12871287
#connection{options = Options,
12881288
channel_cache = Cache,
1289-
sub_system_supervisor = SubSysSup} = Connection,
1289+
connection_supervisor = ConnectionSup} = Connection,
12901290
Channel = ssh_client_channel:cache_lookup(Cache, ChId),
1291-
{ok,Pid} = ssh_subsystem_sup:start_channel(?role(StateName), SubSysSup, self(), ChanCB, ChId, [Sock], undefined, Options),
1291+
{ok,Pid} = ssh_connection_sup:start_channel(?role(StateName), ConnectionSup, self(), ChanCB, ChId, [Sock], undefined, Options),
12921292
ssh_client_channel:cache_update(Cache, Channel#channel{user=Pid}),
12931293
gen_tcp:controlling_process(Sock, Pid),
12941294
inet:setopts(Sock, [{active,once}]),
@@ -1297,8 +1297,8 @@ handle_event(info, {fwd_connect_received, Sock, ChId, ChanCB}, StateName, #data{
12971297
handle_event({call,From},
12981298
{handle_direct_tcpip, ListenHost, ListenPort, ConnectToHost, ConnectToPort, _Timeout},
12991299
_StateName,
1300-
#data{connection_state = #connection{sub_system_supervisor=SubSysSup}}) ->
1301-
case ssh_tcpip_forward_acceptor:supervised_start(ssh_subsystem_sup:tcpip_fwd_supervisor(SubSysSup),
1300+
#data{connection_state = #connection{connection_supervisor=ConnectionSup}}) ->
1301+
case ssh_tcpip_forward_acceptor:supervised_start(ssh_connection_sup:tcpip_fwd_supervisor(ConnectionSup),
13021302
{ListenHost, ListenPort},
13031303
{ConnectToHost, ConnectToPort},
13041304
"direct-tcpip", ssh_tcpip_forward_client,

lib/ssh/src/ssh_subsystem_sup.erl renamed to lib/ssh/src/ssh_connection_sup.erl

Lines changed: 28 additions & 33 deletions
Original file line numberDiff line numberDiff line change
@@ -19,10 +19,10 @@
1919
%%
2020
%%
2121
%%----------------------------------------------------------------------
22-
%% Purpose: The ssh subsystem supervisor
22+
%% Purpose: The ssh connection supervisor
2323
%%----------------------------------------------------------------------
2424

25-
-module(ssh_subsystem_sup).
25+
-module(ssh_connection_sup).
2626
-moduledoc false.
2727

2828
-behaviour(supervisor).
@@ -52,52 +52,47 @@ start_channel(Role, SupPid, ConnRef, Callback, Id, Args, Exec, Opts) ->
5252
ChannelSup = channel_supervisor(SupPid),
5353
ssh_channel_sup:start_child(Role, ChannelSup, ConnRef, Callback, Id, Args, Exec, Opts).
5454

55-
tcpip_fwd_supervisor(SubSysSup) ->
56-
find_child(tcpip_forward_acceptor_sup, SubSysSup).
55+
tcpip_fwd_supervisor(ConnectionSup) ->
56+
find_child(tcpip_forward_acceptor_sup, ConnectionSup).
5757

5858

5959
%%%=========================================================================
6060
%%% Supervisor callback
6161
%%%=========================================================================
6262
init([Role, Id, Socket, Options]) ->
63-
ssh_lib:set_label(Role, {subsystem_sup, Socket}),
64-
SubSysSup = self(),
63+
ssh_lib:set_label(Role, {connection_sup, Socket}),
64+
ConnectionSup = self(),
6565
SupFlags = #{strategy => one_for_all,
6666
auto_shutdown => any_significant,
6767
intensity => 0,
68-
period => 3600
69-
},
70-
ChildSpecs = [#{id => connection,
71-
restart => temporary,
72-
type => worker,
73-
significant => true,
74-
start => {ssh_connection_handler,
75-
start_link,
76-
[Role, Id, Socket,
77-
?PUT_INTERNAL_OPT([
78-
{subsystem_sup, SubSysSup}
79-
], Options)
80-
]
81-
}
82-
},
83-
#{id => channel_sup,
84-
restart => temporary,
85-
type => supervisor,
86-
start => {ssh_channel_sup, start_link, [Options]}
87-
},
68+
period => 3600},
69+
ChildSpecs =
70+
[#{id => connection,
71+
restart => temporary,
72+
type => worker,
73+
significant => true,
74+
start => {ssh_connection_handler,
75+
start_link,
76+
[Role, Id, Socket,
77+
?PUT_INTERNAL_OPT([{connection_sup, ConnectionSup}], Options)]}
78+
},
79+
#{id => channel_sup,
80+
restart => temporary,
81+
type => supervisor,
82+
start => {ssh_channel_sup, start_link, [Options]}
83+
},
8884

89-
#{id => tcpip_forward_acceptor_sup,
90-
restart => temporary,
91-
type => supervisor,
92-
start => {ssh_tcpip_forward_acceptor_sup, start_link, []}
93-
}
94-
],
85+
#{id => tcpip_forward_acceptor_sup,
86+
restart => temporary,
87+
type => supervisor,
88+
start => {ssh_tcpip_forward_acceptor_sup, start_link, []}
89+
}],
9590
{ok, {SupFlags,ChildSpecs}}.
9691

9792
%%%=========================================================================
9893
%%% Internal functions
9994
%%%=========================================================================
100-
channel_supervisor(SubSysSup) -> find_child(channel_sup, SubSysSup).
95+
channel_supervisor(ConnectionSup) -> find_child(channel_sup, ConnectionSup).
10196

10297
find_child(Id, Sup) when is_pid(Sup) ->
10398
try

lib/ssh/src/ssh_info.erl

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -133,7 +133,7 @@ format_sup(server, {{{ssh_system_sup,LocalAddress},Pid,supervisor,[ssh_system_su
133133
io_lib:nl() % Separate system supervisors by an empty line
134134
];
135135
format_sup(client,
136-
{{Ref,SubSysSup,supervisor,[ssh_subsystem_sup]}, _SubSysSpec,
136+
{{Ref,ConnSup,supervisor,[ssh_connection_sup]}, _ConnSupSpec,
137137
[{{connection,ConnPid,worker,[ssh_connection_handler]}, _ConnSpec}
138138
| Children]
139139
},
@@ -143,23 +143,23 @@ format_sup(client,
143143
"~sConnectionRef=~s, subsys_sup=~s~n",
144144
[indent(Indent), local_addr(ConnPid),
145145
indent(Indent), peer_addr(ConnPid), peer_version(client,ConnPid),
146-
indent(Indent), print_pid(ConnPid), print_pid(SubSysSup)
146+
indent(Indent), print_pid(ConnPid), print_pid(ConnSup)
147147
]),
148148
walk_tree(client,
149149
[{H,{connref,ConnPid},Cs} || {H,_,Cs} <- Children],
150150
?inc(Indent)),
151151
io_lib:nl() % Separate sub system supervisors by an empty line
152152
];
153153
format_sup(server,
154-
{{Ref,SubSysSup,supervisor,[ssh_subsystem_sup]}, _SubSysSpec,
155-
[{{connection,ConnPid,worker,[ssh_connection_handler]}, _ConnSpec}
154+
{{Ref,ConnSup,supervisor,[ssh_connection_sup]}, _ConnSupSpec,
155+
[{{connection,ConnPid,worker,[ssh_connection_handler]}, _ConnSpec}
156156
| Children]
157157
},
158158
Indent) when is_reference(Ref) ->
159159
[io_lib:format("~sRemote: ~s (Version: ~s)~n"
160160
"~sConnectionRef=~s, subsys_sup=~s~n",
161161
[indent(Indent), peer_addr(ConnPid), peer_version(server,ConnPid),
162-
indent(Indent), print_pid(ConnPid), print_pid(SubSysSup)
162+
indent(Indent), print_pid(ConnPid), print_pid(ConnSup)
163163
]),
164164
walk_tree(server,
165165
[{H,{connref,ConnPid},Cs} || {H,_,Cs} <- Children],

0 commit comments

Comments
 (0)