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

« back to all changes in this revision

Viewing changes to lib/dialyzer/test/r9c_tests_SUITE_data/src/mnesia/mnesia_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: mnesia_sup.erl,v 1.1 2008/12/17 09:53:39 mikpe Exp $
 
17
%%
 
18
%% Supervisor for the entire Mnesia application
 
19
 
 
20
-module(mnesia_sup).
 
21
 
 
22
-behaviour(application).
 
23
-behaviour(supervisor).
 
24
 
 
25
-export([start/0, start/2, init/1, stop/1, start_event/0, kill/0]).
 
26
 
 
27
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
28
%% application and suprvisor callback functions
 
29
 
 
30
start(normal, Args) ->
 
31
    SupName = {local,?MODULE},
 
32
    case supervisor:start_link(SupName, ?MODULE, [Args]) of
 
33
        {ok, Pid} ->
 
34
            {ok, Pid, {normal, Args}};
 
35
        Error -> 
 
36
            Error
 
37
    end;
 
38
start(_, _) ->
 
39
    {error, badarg}.
 
40
 
 
41
start() ->
 
42
    SupName = {local,?MODULE},
 
43
    supervisor:start_link(SupName, ?MODULE, []).
 
44
 
 
45
stop(_StartArgs) ->
 
46
    ok.
 
47
 
 
48
init([]) -> % Supervisor
 
49
    init();
 
50
init([[]]) -> % Application
 
51
    init();
 
52
init(BadArg) ->
 
53
    {error, {badarg, BadArg}}.
 
54
    
 
55
init() ->
 
56
    Flags = {one_for_all, 0, 3600}, % Should be rest_for_one policy
 
57
 
 
58
    Event = event_procs(),
 
59
    Kernel = kernel_procs(),
 
60
    Mnemosyne = mnemosyne_procs(),
 
61
 
 
62
    {ok, {Flags, Event ++ Kernel ++ Mnemosyne}}.
 
63
 
 
64
event_procs() ->
 
65
    KillAfter = timer:seconds(30),
 
66
    KA = mnesia_kernel_sup:supervisor_timeout(KillAfter),
 
67
    E = mnesia_event,
 
68
    [{E, {?MODULE, start_event, []}, permanent, KA, worker, [E, gen_event]}].
 
69
 
 
70
kernel_procs() ->
 
71
    K = mnesia_kernel_sup,
 
72
    KA = infinity,
 
73
    [{K, {K, start, []}, permanent, KA, supervisor, [K, supervisor]}].
 
74
 
 
75
mnemosyne_procs() ->
 
76
    case mnesia_monitor:get_env(embedded_mnemosyne) of
 
77
        true ->
 
78
            Q = mnemosyne_sup,
 
79
            KA = infinity,
 
80
            [{Q, {Q, start, []}, permanent, KA, supervisor, [Q, supervisor]}];
 
81
        false ->
 
82
            []
 
83
    end.
 
84
    
 
85
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
86
%% event handler
 
87
 
 
88
start_event() ->
 
89
    case gen_event:start_link({local, mnesia_event}) of
 
90
        {ok, Pid} ->
 
91
            case add_event_handler() of
 
92
                ok -> 
 
93
                    {ok, Pid};
 
94
                Error ->
 
95
                    Error
 
96
            end;
 
97
        Error  ->
 
98
            Error
 
99
    end.
 
100
 
 
101
add_event_handler() ->
 
102
    Handler = mnesia_monitor:get_env(event_module),
 
103
    gen_event:add_handler(mnesia_event, Handler, []).
 
104
    
 
105
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
106
%% debug functions
 
107
 
 
108
kill() ->
 
109
    Mnesia = [mnesia_fallback | mnesia:ms()],
 
110
    Mnemosyne = mnemosyne_ms(),
 
111
    Kill = fun(Name) -> catch exit(whereis(Name), kill) end,
 
112
    lists:foreach(Kill, Mnemosyne),
 
113
    lists:foreach(Kill, Mnesia),
 
114
    lists:foreach(fun ensure_dead/1, Mnemosyne),
 
115
    lists:foreach(fun ensure_dead/1, Mnesia),
 
116
    timer:sleep(10),
 
117
    case lists:keymember(mnesia, 1, application:which_applications()) of
 
118
        true -> kill();
 
119
        false -> ok
 
120
    end.
 
121
 
 
122
ensure_dead(Name) ->
 
123
    case whereis(Name) of
 
124
        undefined ->
 
125
            ok;
 
126
        Pid when pid(Pid) ->
 
127
            exit(Pid, kill),
 
128
            timer:sleep(10),
 
129
            ensure_dead(Name)
 
130
    end.
 
131
 
 
132
mnemosyne_ms() ->
 
133
    case mnesia_monitor:get_env(embedded_mnemosyne) of
 
134
        true -> mnemosyne:ms();
 
135
        false -> []
 
136
    end.
 
137