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

« back to all changes in this revision

Viewing changes to lib/snmp/src/agent/snmpa_supervisor.erl

  • Committer: Bazaar Package Importer
  • Author(s): Soren Hansen
  • Date: 2007-05-01 16:57:10 UTC
  • mfrom: (1.1.9 upstream)
  • Revision ID: james.westby@ubuntu.com-20070501165710-2sapk0hp2gf3o0ip
Tags: 1:11.b.4-2ubuntu1
* Merge with Debian Unstable. Remaining changes:
  - Add -fno-stack-protector to fix broken crypto_drv.
* DebianMaintainerField update.

Show diffs side-by-side

added added

removed removed

Lines of Context:
39
39
%% Process structure
40
40
%% =================
41
41
%%
42
 
%%             _______________ supervisor __________________
43
 
%%            /                    |              \         \ 
44
 
%%      __misc_sup____        symbolic_store  local_db   agent_sup
45
 
%%     /     |        \                                    |   | 
46
 
%%    mib  net_if  note_store                             MA - SA
 
42
%%             ___________________ supervisor __________________
 
43
%%            /              |              |          \         \ 
 
44
%%   ___misc_sup___    target_cache  symbolic_store   local_db   agent_sup
 
45
%%  /     |        \                                               |   | 
 
46
%% mib  net_if  note_store                                        MA - SA
47
47
%%
48
48
%%  The supervisor (one at each node) starts:
49
49
%%    snmpa_symbolic_store (one at each node)
50
50
%%    snmpa_local_db (one at each node)
 
51
%%    snmpa_target_cache (one at each node) 
51
52
%%    MA - which starts
52
53
%%      own mib (hangs it under misc_sup)
53
54
%%      net_if (hangs it under misc_sup) 
89
90
    end.
90
91
 
91
92
get_own_loaded_mibs() ->
92
 
    InfoList = snmpa:info(snmp_master_agent),
93
 
    {value, {_, LoadedMibs}} = key1search(loaded_mibs, InfoList),
94
 
    [ Name || {Name, _, _} <- LoadedMibs ].
95
 
 
96
 
mibs_to_load(OtherMibs, OwnMibs) ->
97
 
    [{N, S, F} || {N, S, F} <- OtherMibs, not lists:member(N, OwnMibs)].
 
93
    AgentInfo = snmpa:info(snmp_master_agent),
 
94
    [ Name || {Name, _, _} <- loaded_mibs(AgentInfo) ].
98
95
 
99
96
try_load_other_loaded_mibs(Node, OwnMibs) ->
100
97
    case rpc:call(Node, snmpa, info, [snmp_master_agent]) of
101
98
        {badrpc, R} ->
102
99
            error_msg("could not takeover loaded mibs: ~p", [R]);
103
 
        InfoList ->
104
 
            {value, {_, LoadedMibs}} = key1search(loaded_mibs, InfoList),
 
100
        AgentInfo ->
 
101
            LoadedMibs = loaded_mibs(AgentInfo),
105
102
            MibsToLoad = mibs_to_load(LoadedMibs, OwnMibs),
106
103
            lists:foreach(fun(M) -> takeover_mib(M) end, MibsToLoad)
107
104
    end.
108
105
 
 
106
loaded_mibs(AgentInfo) ->
 
107
    {value, {_, MibInfo}}    = key1search(mib_server,  AgentInfo),
 
108
    {value, {_, LoadedMibs}} = key1search(loaded_mibs, MibInfo),
 
109
    LoadedMibs.
 
110
 
 
111
mibs_to_load(OtherMibs, OwnMibs) ->
 
112
    [{N, S, F} || {N, S, F} <- OtherMibs, not lists:member(N, OwnMibs)].
 
113
 
109
114
takeover_mib({'STANDARD-MIB', _Symbolic, _FileName}) ->
110
115
    ok;
111
116
takeover_mib({'SNMPv2-MIB', _Symbolic, _FileName}) ->
254
259
    ?vdebug("[agent table] store local db options: ~w",[LdbOpts]),
255
260
    ets:insert(snmp_agent_table, {local_db, LdbOpts}),
256
261
 
 
262
    %% -- Target cache options --
 
263
    TargetCacheOpts = get_opt(target_cache, Opts, []),
 
264
    ?vdebug("[agent table] store target cache options: ~w",[TargetCacheOpts]),
 
265
    ets:insert(snmp_agent_table, {target_cache, TargetCacheOpts}),
 
266
 
257
267
    %% -- Specs --
258
268
    SupFlags = {one_for_all, 0, 3600},
259
269
 
260
270
    MiscSupSpec = 
261
271
        sup_spec(snmpa_misc_sup, [], Restart, infinity),
 
272
 
262
273
    SymStoreOpts = [{mib_storage, MibStorage} | SsOpts], 
263
274
    SymStoreArgs = [Prio, SymStoreOpts],
264
275
    SymStoreSpec = 
265
276
        worker_spec(snmpa_symbolic_store, SymStoreArgs, Restart, 2000),
 
277
 
266
278
    LdbArgs = [Prio, DbDir, LdbOpts],
267
279
    LocalDbSpec = 
268
280
        worker_spec(snmpa_local_db, LdbArgs, Restart, 5000),
270
282
    ?vdebug("init VACM",[]),
271
283
    snmpa_vacm:init(DbDir, DbInitError),
272
284
 
 
285
    TargetCacheArgs = [Prio, TargetCacheOpts],
 
286
    TargetCacheSpec = 
 
287
        worker_spec(snmpa_target_cache, TargetCacheArgs, transient, 2000, []),
 
288
 
273
289
    Rest =
274
290
        case AgentType of
275
291
            master ->
373
389
                [AgentSupSpec]
374
390
        end,
375
391
    ?vdebug("init done",[]),
376
 
    {ok, {SupFlags, [MiscSupSpec, SymStoreSpec, LocalDbSpec | Rest]}}.
 
392
    {ok, {SupFlags, [MiscSupSpec, SymStoreSpec, LocalDbSpec, TargetCacheSpec | 
 
393
                     Rest]}}.
377
394
 
378
395
 
379
396
get_mibs(Mibs, Vsns) ->
402
419
add_mib(DefaultMib, [], _BaseNames) -> [DefaultMib];
403
420
add_mib(DefaultMib, [Mib | T], BaseNames) ->
404
421
    case lists:member(filename:basename(Mib), BaseNames) of
405
 
        true -> [Mib | T]; % The user defined his own version of the mib
 
422
        true  -> [Mib | T]; % The user defined his own version of the mib
406
423
        false -> [Mib | add_mib(DefaultMib, T, BaseNames)]
407
424
    end.
408
425
 
486
503
worker_spec(Name, Args, Type, Time) ->
487
504
    worker_spec(Name, Name, Args, Type, Time, []).
488
505
 
489
 
% worker_spec(Name, Args, Type, Time, Modules) ->
490
 
%     worker_spec(Name, Name, Args, Type, Time, Modules).
 
506
worker_spec(Name, Args, Type, Time, Modules) ->
 
507
    worker_spec(Name, Name, Args, Type, Time, Modules).
491
508
 
492
509
worker_spec(Name, Mod, Args, Type, Time, Modules) ->
493
510
    worker_spec(Name, Mod, start_link, Args, Type, Time, Modules).