~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/dialyzer/test/r9c_tests_SUITE_data/src/inets/httpd_misc_sup.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

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: httpd_misc_sup.erl,v 1.1 2008/12/17 09:53:34 mikpe Exp $
 
17
%%
 
18
%%----------------------------------------------------------------------
 
19
%% Purpose: The top supervisor for the Megaco/H.248 application
 
20
%%----------------------------------------------------------------------
 
21
 
 
22
-module(httpd_misc_sup).
 
23
 
 
24
-behaviour(supervisor).
 
25
 
 
26
-include("httpd_verbosity.hrl").
 
27
 
 
28
%% public
 
29
-export([start/3, stop/1, init/1]).
 
30
 
 
31
-export([start_auth_server/3, stop_auth_server/2, 
 
32
         start_sec_server/3,  stop_sec_server/2]).
 
33
 
 
34
 
 
35
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
36
%% supervisor callback functions
 
37
 
 
38
 
 
39
start(Addr, Port, MiscSupVerbosity) ->
 
40
    SupName = make_name(Addr, Port),
 
41
    supervisor:start_link({local, SupName}, ?MODULE, [MiscSupVerbosity]).
 
42
 
 
43
stop(StartArgs) ->
 
44
    ok.
 
45
 
 
46
init([Verbosity]) -> % Supervisor
 
47
    do_init(Verbosity);
 
48
init(BadArg) ->
 
49
    {error, {badarg, BadArg}}.
 
50
 
 
51
do_init(Verbosity) ->
 
52
    put(verbosity,?vvalidate(Verbosity)),
 
53
    put(sname,misc_sup),
 
54
    ?vlog("starting", []),
 
55
    Flags     = {one_for_one, 0, 1},
 
56
    KillAfter = timer:seconds(1),
 
57
    Workers   = [],
 
58
    {ok, {Flags, Workers}}.
 
59
 
 
60
 
 
61
%%----------------------------------------------------------------------
 
62
%% Function: [start|stop]_[auth|sec]_server/3
 
63
%% Description: Starts a [auth | security] worker (child) process
 
64
%%----------------------------------------------------------------------
 
65
 
 
66
start_auth_server(Addr, Port, Verbosity) ->
 
67
    start_permanent_worker(mod_auth_server, Addr, Port, 
 
68
                           Verbosity, [gen_server]).
 
69
 
 
70
stop_auth_server(Addr, Port) ->
 
71
    stop_permanent_worker(mod_auth_server, Addr, Port).
 
72
 
 
73
 
 
74
start_sec_server(Addr, Port, Verbosity) ->
 
75
    start_permanent_worker(mod_security_server, Addr, Port, 
 
76
                           Verbosity, [gen_server]).
 
77
 
 
78
stop_sec_server(Addr, Port) ->
 
79
    stop_permanent_worker(mod_security_server, Addr, Port).
 
80
 
 
81
 
 
82
 
 
83
%%----------------------------------------------------------------------
 
84
%% Function:    start_permanent_worker/5
 
85
%% Description: Starts a permanent worker (child) process
 
86
%%----------------------------------------------------------------------
 
87
 
 
88
start_permanent_worker(Mod, Addr, Port, Verbosity, Modules) ->
 
89
    SupName = make_name(Addr, Port),
 
90
    Spec    = {{Mod, Addr, Port},
 
91
               {Mod, start_link, [Addr, Port, Verbosity]}, 
 
92
               permanent, timer:seconds(1), worker, [Mod] ++ Modules},
 
93
    supervisor:start_child(SupName, Spec).
 
94
 
 
95
 
 
96
%%----------------------------------------------------------------------
 
97
%% Function:    stop_permanent_worker/3
 
98
%% Description: Stops a permanent worker (child) process
 
99
%%----------------------------------------------------------------------
 
100
 
 
101
stop_permanent_worker(Mod, Addr, Port) ->
 
102
    SupName = make_name(Addr, Port),
 
103
    Name    = {Mod, Addr, Port},
 
104
    case supervisor:terminate_child(SupName, Name) of
 
105
        ok ->
 
106
            supervisor:delete_child(SupName, Name);
 
107
        Error ->
 
108
            Error
 
109
    end.
 
110
    
 
111
 
 
112
make_name(Addr,Port) ->
 
113
    httpd_util:make_name("httpd_misc_sup",Addr,Port).
 
114
 
 
115
 
 
116