~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/inets/src/http_server/httpd_misc_sup.erl

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%% ``The contents of this file are subject to the Erlang Public License,
 
2
%% Version 1.1, (the "License"); you may not use this file except in
 
3
%% compliance with the License. You should have received a copy of the
 
4
%% Erlang Public License along with this software. If not, it can be
 
5
%% retrieved via the world wide web at http://www.erlang.org/.
 
6
%% 
 
7
%% Software distributed under the License is distributed on an "AS IS"
 
8
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
9
%% the License for the specific language governing rights and limitations
 
10
%% under the License.
 
11
%% 
 
12
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
 
13
%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
 
14
%% AB. All Rights Reserved.''
 
15
%% 
 
16
%%     $Id$
 
17
%%
 
18
%%----------------------------------------------------------------------
 
19
%% Purpose: The supervisor for auth and sec processes in the http server, 
 
20
%%          hangs under the httpd_instance_sup_<Addr>_<Port> supervisor.
 
21
%%----------------------------------------------------------------------
 
22
 
 
23
-module(httpd_misc_sup).
 
24
 
 
25
-behaviour(supervisor).
 
26
 
 
27
%% API 
 
28
-export([start_link/2, start_auth_server/2, stop_auth_server/2, 
 
29
         start_sec_server/2,  stop_sec_server/2]).
 
30
 
 
31
%% Supervisor callback
 
32
-export([init/1]).
 
33
 
 
34
%%%=========================================================================
 
35
%%%  API
 
36
%%%=========================================================================
 
37
 
 
38
start_link(Addr, Port) ->
 
39
    SupName = make_name(Addr, Port),
 
40
    supervisor:start_link({local, SupName}, ?MODULE, []).
 
41
 
 
42
%%----------------------------------------------------------------------
 
43
%% Function: [start|stop]_[auth|sec]_server/3
 
44
%% Description: Starts a [auth | security] worker (child) process
 
45
%%----------------------------------------------------------------------
 
46
start_auth_server(Addr, Port) ->
 
47
    start_permanent_worker(mod_auth_server, Addr, Port, [gen_server]).
 
48
 
 
49
stop_auth_server(Addr, Port) ->
 
50
    stop_permanent_worker(mod_auth_server, Addr, Port).
 
51
 
 
52
 
 
53
start_sec_server(Addr, Port) ->
 
54
    start_permanent_worker(mod_security_server, Addr, Port, [gen_server]).
 
55
 
 
56
stop_sec_server(Addr, Port) ->
 
57
    stop_permanent_worker(mod_security_server, Addr, Port).
 
58
 
 
59
 
 
60
%%%=========================================================================
 
61
%%%  Supervisor callback
 
62
%%%=========================================================================
 
63
init(_) -> 
 
64
    Flags     = {one_for_one, 0, 1},
 
65
    Workers   = [],
 
66
    {ok, {Flags, Workers}}.
 
67
 
 
68
%%%=========================================================================
 
69
%%%  Internal functions
 
70
%%%=========================================================================
 
71
start_permanent_worker(Mod, Addr, Port, Modules) ->
 
72
    SupName = make_name(Addr, Port),
 
73
    Spec    = {{Mod, Addr, Port},
 
74
               {Mod, start_link, [Addr, Port]}, 
 
75
               permanent, timer:seconds(1), worker, [Mod] ++ Modules},
 
76
    supervisor:start_child(SupName, Spec).
 
77
 
 
78
stop_permanent_worker(Mod, Addr, Port) ->
 
79
    SupName = make_name(Addr, Port),
 
80
    Name    = {Mod, Addr, Port},
 
81
    case supervisor:terminate_child(SupName, Name) of
 
82
        ok ->
 
83
            supervisor:delete_child(SupName, Name);
 
84
        Error ->
 
85
            Error
 
86
    end.
 
87
    
 
88
make_name(Addr,Port) ->
 
89
    httpd_util:make_name("httpd_misc_sup",Addr,Port).