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

« back to all changes in this revision

Viewing changes to lib/snmp/src/snmp_agent_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
 
-module(snmp_agent_sup).
19
 
 
20
 
-behaviour(supervisor).
21
 
 
22
 
%% External exports
23
 
-export([start_link/1, start_link/2, start_subagent/3, stop_subagent/1]).
24
 
 
25
 
%% Internal exports
26
 
-export([init/1]).
27
 
 
28
 
%%%-----------------------------------------------------------------
29
 
%%% This is a supervisor for the mib processes.  Each agent has one
30
 
%%% mib process.
31
 
%%%-----------------------------------------------------------------
32
 
start_link(Prio) ->
33
 
    supervisor:start_link({local, snmp_agent_sup}, snmp_agent_sup,
34
 
                          [Prio, []]).
35
 
start_link(Prio, AgentSpec) ->
36
 
    supervisor:start_link({local, snmp_agent_sup}, snmp_agent_sup,
37
 
                          [Prio, [AgentSpec]]).
38
 
 
39
 
start_subagent(ParentAgent, Subtree, Mibs) ->
40
 
    Max = find_max(supervisor:which_children(snmp_agent_sup), 1),
41
 
    [{_, Prio}] = ets:lookup(snmp_agent_table, priority),
42
 
    Ref = make_ref(),
43
 
    Options = [{priority, Prio}, {mibs,Mibs}, {misc_sup, snmp_misc_sup}],
44
 
    Agent = {{sub_agent, Max},
45
 
             {snmp_agent, start_link,
46
 
              [ParentAgent, Ref, Options]},
47
 
             permanent, 2000, worker, [snmp_agent]},
48
 
    case supervisor:start_child(snmp_agent_sup, Agent) of
49
 
        {ok, SA} -> 
50
 
            snmp_agent:register_subagent(ParentAgent, Subtree, SA),
51
 
            {ok, SA};
52
 
        Error ->
53
 
            Error
54
 
    end.
55
 
 
56
 
stop_subagent(SubAgentPid) ->
57
 
    case find_name(supervisor:which_children(snmp_agent_sup), SubAgentPid) of
58
 
        undefined -> no_such_child;
59
 
        Name ->
60
 
            supervisor:terminate_child(snmp_agent_sup, Name),
61
 
            supervisor:delete_child(snmp_agent_sup, Name),
62
 
            ok
63
 
    end.
64
 
 
65
 
init([Prio, Children]) ->
66
 
    process_flag(priority, Prio),
67
 
    %% 20 restarts in ten minutes.  If the agent crashes and restarts,
68
 
    %% it may very well crash again, because the management application
69
 
    %% tries to resend the very same request.  This depends on the resend
70
 
    %% strategy used by the management application.
71
 
    SupFlags = {one_for_one, 20, 600},
72
 
    {ok, {SupFlags, Children}}.
73
 
 
74
 
 
75
 
find_max([{{sub_agent, N}, _, _, _} | T], M) when N >= M -> find_max(T, N+1);
76
 
find_max([_|T], M) -> find_max(T, M);
77
 
find_max([], M) -> M.
78
 
 
79
 
find_name([{Name, Pid, _, _} | _T], Pid)-> Name;
80
 
find_name([_|T], Pid) -> find_name(T, Pid);
81
 
find_name([], _Pid) -> undefined.