~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

Viewing changes to lib/ssh/src/ssh_system_sup.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%<copyright>
 
2
%% <year>2008-2008</year>
 
3
%% <holder>Ericsson AB, All Rights Reserved</holder>
 
4
%%</copyright>
 
5
%%<legalnotice>
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%%
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%%
 
17
%% The Initial Developer of the Original Code is Ericsson AB.
 
18
%%</legalnotice>
 
19
%%
 
20
%%----------------------------------------------------------------------
 
21
%% Purpose: The ssh server instance supervisor, an instans of this supervisor
 
22
%%          exists for every ip-address and port combination, hangs under  
 
23
%%          sshd_sup.
 
24
%%----------------------------------------------------------------------
 
25
 
 
26
-module(ssh_system_sup).
 
27
 
 
28
-behaviour(supervisor).
 
29
 
 
30
-export([start_link/1, stop_listener/1,
 
31
         stop_listener/2, stop_system/1,
 
32
         stop_system/2, system_supervisor/2,
 
33
         subsystem_supervisor/1, channel_supervisor/1, 
 
34
         connection_supervisor/1, 
 
35
         acceptor_supervisor/1, connection_manager/1,
 
36
         restart_subsystem/2, restart_acceptor/2]).
 
37
 
 
38
%% Supervisor callback
 
39
-export([init/1]).
 
40
 
 
41
%%%=========================================================================
 
42
%%%  API
 
43
%%%=========================================================================
 
44
start_link(ServerOpts) ->
 
45
    Address = proplists:get_value(address, ServerOpts),
 
46
    Port = proplists:get_value(port, ServerOpts),
 
47
    Name = make_name(Address, Port),
 
48
    supervisor:start_link({local, Name}, ?MODULE, [ServerOpts]).
 
49
 
 
50
stop_listener(SysSup) ->
 
51
    stop_acceptor(SysSup). 
 
52
 
 
53
stop_listener(Address, Port) ->
 
54
    Name = make_name(Address, Port),
 
55
    stop_acceptor(whereis(Name)). 
 
56
 
 
57
stop_system(SysSup) ->
 
58
    Name = sshd_sup:system_name(SysSup),
 
59
    sshd_sup:stop_child(Name).
 
60
    
 
61
stop_system(Address, Port) -> 
 
62
    sshd_sup:stop_child(Address, Port).
 
63
 
 
64
system_supervisor(Address, Port) ->
 
65
    Name = make_name(Address, Port),
 
66
    whereis(Name).
 
67
 
 
68
subsystem_supervisor(SystemSup) ->
 
69
    ssh_subsystem_sup(supervisor:which_children(SystemSup)).
 
70
 
 
71
connection_manager(SystemSup) ->
 
72
    SubSysSup = ssh_subsystem_sup(supervisor:which_children(SystemSup)),
 
73
    ssh_subsystem_sup:connection_manager(SubSysSup).
 
74
 
 
75
channel_supervisor(SystemSup) ->
 
76
    SubSysSup = ssh_subsystem_sup(supervisor:which_children(SystemSup)),
 
77
    ssh_subsystem_sup:channel_supervisor(SubSysSup).
 
78
 
 
79
connection_supervisor(SystemSup) ->
 
80
    SubSysSup = ssh_subsystem_sup(supervisor:which_children(SystemSup)),
 
81
    ssh_subsystem_sup:connection_supervisor(SubSysSup).
 
82
 
 
83
acceptor_supervisor(SystemSup) ->
 
84
    ssh_acceptor_sup(supervisor:which_children(SystemSup)).
 
85
 
 
86
restart_subsystem(Address, Port) ->
 
87
    SysSupName = make_name(Address, Port),
 
88
    SubSysName = id(ssh_subsystem_sup, Address, Port),
 
89
    case supervisor:terminate_child(SysSupName, SubSysName) of
 
90
        ok ->
 
91
            supervisor:restart_child(SysSupName, SubSysName);
 
92
        Error  ->
 
93
            Error
 
94
    end.
 
95
 
 
96
restart_acceptor(Address, Port) ->
 
97
    SysSupName = make_name(Address, Port),
 
98
    AcceptorName = id(ssh_acceptor_sup, Address, Port),
 
99
    supervisor:restart_child(SysSupName, AcceptorName).
 
100
 
 
101
%%%=========================================================================
 
102
%%%  Supervisor callback
 
103
%%%=========================================================================
 
104
init([ServerOpts]) ->
 
105
    RestartStrategy = one_for_one,
 
106
    MaxR = 10,
 
107
    MaxT = 3600,
 
108
    Children = child_specs(ServerOpts),
 
109
    {ok, {{RestartStrategy, MaxR, MaxT}, Children}}.
 
110
 
 
111
%%%=========================================================================
 
112
%%%  Internal functions
 
113
%%%=========================================================================
 
114
child_specs(ServerOpts) ->
 
115
    [ssh_acceptor_child_spec(ServerOpts), ssh_subsystem_child_spec(ServerOpts)].
 
116
  
 
117
ssh_acceptor_child_spec(ServerOpts) ->
 
118
    Address = proplists:get_value(address, ServerOpts),
 
119
    Port = proplists:get_value(port, ServerOpts),
 
120
    Name = id(ssh_acceptor_sup, Address, Port),
 
121
    StartFunc = {ssh_acceptor_sup, start_link, [ServerOpts]},
 
122
    Restart = permanent, 
 
123
    Shutdown = infinity,
 
124
    Modules = [ssh_acceptor_sup],
 
125
    Type = supervisor,
 
126
    {Name, StartFunc, Restart, Shutdown, Type, Modules}.
 
127
 
 
128
ssh_subsystem_child_spec(ServerOpts) ->
 
129
    Address = proplists:get_value(address, ServerOpts),
 
130
    Port =  proplists:get_value(port, ServerOpts),
 
131
    Name = id(ssh_subsystem_sup, Address, Port),
 
132
    StartFunc = {ssh_subsystem_sup, start_link, [ServerOpts]},
 
133
    Restart = permanent, 
 
134
    Shutdown = infinity,
 
135
    Modules = [ssh_subsystem_sup],
 
136
    Type = supervisor,
 
137
    {Name, StartFunc, Restart, Shutdown, Type, Modules}.
 
138
 
 
139
 
 
140
id(Sup, Address, Port) ->
 
141
    {Sup, Address, Port}.
 
142
 
 
143
make_name(Address, Port) ->
 
144
    list_to_atom(lists:flatten(io_lib:format("ssh_system_~p_~p_sup", 
 
145
                                             [Address, Port]))).
 
146
 
 
147
ssh_subsystem_sup([{_, Child, _, [ssh_subsystem_sup]} | _]) ->
 
148
    Child;
 
149
ssh_subsystem_sup([_ | Rest]) ->
 
150
    ssh_subsystem_sup(Rest).
 
151
 
 
152
ssh_acceptor_sup([{_, Child, _, [ssh_acceptor_sup]} | _]) ->
 
153
    Child;
 
154
ssh_acceptor_sup([_ | Rest]) ->
 
155
    ssh_acceptor_sup(Rest).
 
156
 
 
157
stop_acceptor(Sup) ->
 
158
    [Name] =
 
159
        [SupName || {SupName, _, _, [ssh_acceptor_sup]} <- 
 
160
                          supervisor:which_children(Sup)],
 
161
    supervisor:terminate_child(Sup, Name).
 
162