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

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%<copyright>
2
 
%% <year>1996-2007</year>
 
2
%% <year>1996-2008</year>
3
3
%% <holder>Ericsson AB, All Rights Reserved</holder>
4
4
%%</copyright>
5
5
%%<legalnotice>
31
31
         load_mibs/2, unload_mibs/2, 
32
32
         register_subagent/3, unregister_subagent/2, info/1, info/2, 
33
33
         verbosity/2, dump/1, dump/2,
34
 
         backup/2]).
 
34
         backup/2,
 
35
         invalidate_cache/1]).
35
36
 
36
37
%% Internal exports
37
38
-export([init/1, handle_call/3, handle_cast/2, handle_info/2, terminate/2,
44
45
-include("snmp_debug.hrl").
45
46
 
46
47
 
47
 
-define(SERVER, ?MODULE).
 
48
-define(SERVER,   ?MODULE).
 
49
-define(NO_CACHE, no_mibs_cache).
 
50
-define(DEFAULT_CACHE_USAGE, true).
48
51
 
49
52
-ifdef(snmp_debug).
50
53
-define(GS_START_LINK(Prio, Mibs, Opts),
63
66
%%       meo  - mib entry override
64
67
%%       teo  - trap (notification) entry override
65
68
%%-----------------------------------------------------------------
66
 
-record(state, {data, meo, teo, backup}).
 
69
-record(state, {data, meo, teo, backup, cache}).
67
70
 
68
71
 
69
72
 
88
91
stop(MibServer) ->
89
92
    call(MibServer, stop).
90
93
 
 
94
invalidate_cache(MibServer) ->
 
95
    call(MibServer, invalidate_cache).
 
96
 
91
97
 
92
98
%%-----------------------------------------------------------------
93
99
%% Func: lookup/2
201
207
    put(sname,ms),
202
208
    put(verbosity,?vvalidate(get_verbosity(Opts))),
203
209
    ?vlog("starting",[]),
 
210
    Cache      = maybe_create_cache(Opts), 
204
211
    MeOverride = get_me_override(Opts),
205
212
    TeOverride = get_te_override(Opts),
206
213
    MibStorage = get_mib_storage(Opts),
212
219
            ?vdebug("started",[]),
213
220
            snmpa_mib_data:sync(Data2),
214
221
            ?vdebug("mib data synced",[]),
215
 
            {ok, #state{data = Data2, teo = TeOverride, meo = MeOverride}};
 
222
            {ok, #state{data  = Data2, 
 
223
                        teo   = TeOverride, 
 
224
                        meo   = MeOverride,
 
225
                        cache = Cache}};
216
226
        {'aborted at', Mib, _NewData, Reason} ->
217
227
            ?vinfo("failed loading mib ~p: ~p",[Mib,Reason]),
218
228
            {error, {Mib, Reason}}
243
253
  when list(Mib) ->
244
254
    ?vtrace("mib operation on mib ~p", [Mib]),
245
255
    case apply(snmpa_mib_data, Operation, [Data0,Mib,MeOverride,TeOverride]) of
246
 
        {error, 'already loaded'} when Operation == load_mib, 
247
 
                                       Force == true ->
 
256
        {error, 'already loaded'} when (Operation =:= load_mib) andalso  
 
257
                                       (Force =:= true) ->
248
258
            ?vlog("ignore mib ~p -> already loaded", [Mib]),
249
259
            Data0;
250
 
        {error, 'not loaded'} when Operation == unload_mib, 
251
 
                                   Force == true ->
 
260
        {error, 'not loaded'} when (Operation =:= unload_mib) andalso 
 
261
                                   (Force =:= true) ->
252
262
            ?vlog("ignore mib ~p -> not loaded", [Mib]),
253
263
            Data0;
254
264
        {error, Reason} ->
265
275
%%-----------------------------------------------------------------
266
276
%% Handle messages
267
277
%%-----------------------------------------------------------------
268
 
handle_call({lookup, Oid}, _From, #state{data = Data} = State) ->
269
 
    ?vlog("lookup ~p",[Oid]),    
270
 
    Reply = snmpa_mib_data:lookup(Data, Oid),
 
278
 
 
279
handle_call(invalidate_cache, _From, #state{cache = Cache} = State) ->
 
280
    ?vlog("invalidate_cache", []), 
 
281
    NewCache = maybe_invalidate_cache(Cache),
 
282
    {reply, ignore, State#state{cache = NewCache}};
 
283
 
 
284
handle_call({lookup, Oid}, _From, 
 
285
            #state{data = Data, cache = Cache} = State) ->
 
286
    ?vlog("lookup ~p", [Oid]), 
 
287
    Key = {lookup, Oid}, 
 
288
    Reply = case maybe_cache_lookup(Cache, Key) of
 
289
                ?NO_CACHE ->
 
290
                    snmpa_mib_data:lookup(Data, Oid);
 
291
                [] ->
 
292
                    Rep = snmpa_mib_data:lookup(Data, Oid),
 
293
                    ets:insert(Cache, {Key, Rep}),
 
294
                    Rep;
 
295
                [{Key, Rep}] ->
 
296
                    ?vdebug("lookup -> found in cache", []), 
 
297
                    Rep
 
298
            end,
 
299
    ?vdebug("lookup -> Reply: ~p",[Reply]),    
271
300
    {reply, Reply, State};
272
301
 
273
302
handle_call({which_mib, Oid}, _From, #state{data = Data} = State) ->
276
305
    ?vdebug("which_mib: ~p",[Reply]),    
277
306
    {reply, Reply, State};
278
307
 
279
 
handle_call({next, Oid, MibView}, _From, #state{data = Data} = State) ->
280
 
    ?vlog("next ~p [~p]",[Oid,MibView]),    
281
 
    Reply = snmpa_mib_data:next(Data, Oid, MibView),
282
 
    ?vdebug("next: ~p",[Reply]),    
 
308
handle_call({next, Oid, MibView}, _From, 
 
309
            #state{data = Data, cache = Cache} = State) ->
 
310
    ?vlog("next ~p [~p]",[Oid,MibView]), 
 
311
    Key = {next, Oid, MibView},
 
312
    Reply = case maybe_cache_lookup(Cache, Key) of
 
313
                ?NO_CACHE ->
 
314
                    snmpa_mib_data:next(Data, Oid, MibView);
 
315
                [] ->    
 
316
                    Rep = snmpa_mib_data:next(Data, Oid, MibView),
 
317
                    ets:insert(Cache, {Key, Rep}),
 
318
                    Rep;
 
319
                [{Key, Rep}] ->
 
320
                    ?vdebug("lookup -> found in cache", []), 
 
321
                    Rep
 
322
            end,
 
323
    ?vdebug("next -> Reply: ~p",[Reply]), 
283
324
    {reply, Reply, State};
284
325
 
285
326
handle_call({load_mibs, Mibs}, _From, 
286
 
            #state{data = Data, teo = TeOverride, meo = MeOverride} = State) ->
 
327
            #state{data  = Data, 
 
328
                   teo   = TeOverride, 
 
329
                   meo   = MeOverride,
 
330
                   cache = Cache} = State) ->
287
331
    ?vlog("load mibs ~p",[Mibs]),    
 
332
    %% Invalidate cache
 
333
    NewCache = maybe_invalidate_cache(Cache),
288
334
    {NData,Reply} = 
289
335
        case (catch mib_operations(load_mib, Mibs, Data,
290
336
                                   MeOverride, TeOverride)) of
295
341
                {NewData,ok}
296
342
        end,
297
343
    snmpa_mib_data:sync(NData),
298
 
    {reply, Reply, State#state{data = NData}};
 
344
    {reply, Reply, State#state{data = NData, cache = NewCache}};
299
345
 
300
346
handle_call({unload_mibs, Mibs}, _From, 
301
 
            #state{data = Data, teo = TeOverride, meo = MeOverride} = State) ->
 
347
            #state{data  = Data, 
 
348
                   teo   = TeOverride, 
 
349
                   meo   = MeOverride,
 
350
                   cache = Cache} = State) ->
302
351
    ?vlog("unload mibs ~p",[Mibs]),    
 
352
    %% Invalidate cache
 
353
    NewCache = maybe_invalidate_cache(Cache),
 
354
    %% Unload mib(s)
303
355
    {NData,Reply} = 
304
356
        case (catch mib_operations(unload_mib, Mibs, Data,
305
357
                                   MeOverride, TeOverride)) of
306
358
            {'aborted at', Mib, NewData, Reason} ->
307
359
                ?vlog("aborted at ~p for reason ~p",[Mib,Reason]),    
308
 
                {NewData,{error, {'unload aborted at', Mib, Reason}}};
 
360
                {NewData, {error, {'unload aborted at', Mib, Reason}}};
309
361
            {ok, NewData} ->
310
362
                {NewData,ok}
311
363
        end,
312
364
    snmpa_mib_data:sync(NData),
313
 
    {reply, Reply, State#state{data = NData}};
 
365
    {reply, Reply, State#state{data = NData, cache = NewCache}};
314
366
 
315
367
handle_call(which_mibs, _From, #state{data = Data} = State) ->
316
368
    ?vlog("which mibs",[]),    
322
374
    Reply = snmpa_mib_data:whereis_mib(Data, Mib),
323
375
    {reply, Reply, State};
324
376
 
325
 
handle_call({register_subagent, Oid, Pid}, _From, State) ->
 
377
handle_call({register_subagent, Oid, Pid}, _From, 
 
378
            #state{data = Data, cache = Cache} = State) ->
326
379
    ?vlog("register subagent ~p, ~p",[Oid,Pid]),
327
 
    case snmpa_mib_data:register_subagent(State#state.data, Oid, Pid) of
 
380
    %% Invalidate cache
 
381
    NewCache = maybe_invalidate_cache(Cache),
 
382
    case snmpa_mib_data:register_subagent(Data, Oid, Pid) of
328
383
        {error, Reason} ->
329
384
            ?vlog("registration failed: ~p",[Reason]),    
330
 
            {reply, {error, Reason}, State};
 
385
            {reply, {error, Reason}, State#state{cache = NewCache}};
331
386
        NewData ->
332
 
            {reply, ok, State#state{data = NewData}}
 
387
            {reply, ok, State#state{data = NewData, cache = NewCache}}
333
388
    end;
334
389
 
335
 
handle_call({unregister_subagent, OidOrPid}, _From, State) ->
 
390
handle_call({unregister_subagent, OidOrPid}, _From, 
 
391
            #state{data = Data, cache = Cache} = State) ->
336
392
    ?vlog("unregister subagent ~p",[OidOrPid]),    
337
 
    case snmpa_mib_data:unregister_subagent(State#state.data, OidOrPid) of
 
393
    %% Invalidate cache
 
394
    NewCache = maybe_invalidate_cache(Cache),
 
395
    case snmpa_mib_data:unregister_subagent(Data, OidOrPid) of
338
396
        {ok, NewData, DeletedSubagentPid} ->
339
 
            {reply, {ok, DeletedSubagentPid}, State#state{data=NewData}};
 
397
            {reply, {ok, DeletedSubagentPid}, State#state{data  = NewData, 
 
398
                                                          cache = NewCache}};
340
399
        {error, Reason} ->
341
400
            ?vlog("unregistration failed: ~p",[Reason]),    
342
 
            {reply, {error, Reason}, State};
 
401
            {reply, {error, Reason}, State#state{cache = NewCache}};
343
402
        NewData ->
344
 
            {reply, ok, State#state{data = NewData}}
 
403
            {reply, ok, State#state{data = NewData, cache = NewCache}}
345
404
    end;
346
405
 
347
 
handle_call(info, _From, #state{data = Data} = State) ->
 
406
handle_call(info, _From, #state{data = Data, cache = Cache} = State) ->
348
407
    ?vlog("info",[]),    
349
 
    {reply, catch snmpa_mib_data:info(Data), State};
 
408
    Reply = 
 
409
        case (catch snmpa_mib_data:info(Data)) of
 
410
            Info when is_list(Info) ->
 
411
                [{cache, size_cache(Cache)} | Info];
 
412
            E ->
 
413
                    [{error, E}]
 
414
            end,
 
415
    {reply, Reply, State};
350
416
 
351
417
handle_call({info, Type}, _From, #state{data = Data} = State) ->
352
418
    ?vlog("info ~p",[Type]),    
353
 
    Reply = case (catch snmpa_mib_data:info(Data, Type)) of
354
 
                Info when list(Info) ->
355
 
                    Info;
356
 
                E ->
357
 
                    [{error, E}]
358
 
            end,
 
419
    Reply = 
 
420
        case (catch snmpa_mib_data:info(Data, Type)) of
 
421
            Info when is_list(Info) ->
 
422
                Info;
 
423
            E ->
 
424
                [{error, E}]
 
425
        end,
359
426
    {reply, Reply, State};
360
427
 
361
428
handle_call(dump, _From, State) ->
401
468
    Reply = {error, {unknown, Req}}, 
402
469
    {reply, Reply, State}.
403
470
    
404
 
handle_cast({verbosity,Verbosity}, State) ->
 
471
handle_cast({verbosity, Verbosity}, State) ->
405
472
    ?vlog("verbosity: ~p -> ~p",[get(verbosity),Verbosity]),    
406
473
    put(verbosity,snmp_verbosity:validate(Verbosity)),
407
474
    {noreply, State};
442
509
 
443
510
%% downgrade
444
511
%% 
445
 
code_change({down, _Vsn}, S1, downgrade_to_pre_4_7) ->
446
 
    #state{data = Data, meo = MEO, teo = TEO, backup = B} = S1, 
447
 
    stop_backup_server(B),
448
 
    NData = snmpa_mib_data:code_change(down, Data),
449
 
    S2 = {state, NData, MEO, TEO},
 
512
code_change({down, _Vsn}, S1, downgrade_to_pre_4_12) ->
 
513
    #state{data = Data, meo = MEO, teo = TEO, backup = B, cache = Cache} = S1, 
 
514
    del_cache(Cache), 
 
515
    S2 = {state, Data, MEO, TEO, B},
450
516
    {ok, S2};
451
517
 
452
518
%% upgrade
453
519
%% 
454
 
code_change(_Vsn, S1, upgrade_from_pre_4_7) ->
455
 
    {state, Data, MEO, TEO} = S1,
456
 
    NData = snmpa_mib_data:code_change(up, Data),
457
 
    S2 = #state{data = NData, meo = MEO, teo = TEO},
 
520
code_change(_Vsn, S1, upgrade_from_pre_4_12) ->
 
521
    {state, Data, MEO, TEO, B} = S1,
 
522
    Cache = new_cache(), 
 
523
    S2 = #state{data = Data, meo = MEO, teo = TEO, backup = B, cache = Cache},
458
524
    {ok, S2};
459
525
 
460
526
code_change(_Vsn, State, _Extra) ->
461
527
    {ok, State}.
462
528
 
463
529
 
464
 
stop_backup_server(undefined) ->
 
530
%%-----------------------------------------------------------------
 
531
%% Option access functions
 
532
%%-----------------------------------------------------------------
 
533
 
 
534
get_verbosity(Options) ->
 
535
    snmp_misc:get_option(verbosity, Options, ?default_verbosity).
 
536
 
 
537
get_me_override(Options) ->
 
538
    snmp_misc:get_option(mibentry_override, Options, false).
 
539
 
 
540
get_te_override(Options) ->
 
541
    snmp_misc:get_option(trapentry_override, Options, false).
 
542
 
 
543
get_mib_storage(Options) ->
 
544
    snmp_misc:get_option(mib_storage, Options, ets).
 
545
 
 
546
 
 
547
%% ----------------------------------------------------------------
 
548
 
 
549
maybe_create_cache(Options) when is_list(Options) ->
 
550
    case snmp_misc:get_option(cache, Options, ?DEFAULT_CACHE_USAGE) of
 
551
        true ->
 
552
            new_cache();
 
553
        _ ->
 
554
            ?NO_CACHE
 
555
    end.
 
556
 
 
557
maybe_invalidate_cache(?NO_CACHE) ->
 
558
    ?NO_CACHE;
 
559
maybe_invalidate_cache(Cache) ->
 
560
    del_cache(Cache),
 
561
    new_cache().
 
562
 
 
563
new_cache() ->
 
564
    ets:new(snmpa_mib_cache, [set, protected, {keypos, 1}]).
 
565
 
 
566
del_cache(?NO_CACHE) ->
465
567
    ok;
466
 
stop_backup_server({Pid, _}) when pid(Pid) ->
467
 
    exit(Pid, kill).
468
 
 
469
 
 
470
 
 
471
 
%%-----------------------------------------------------------------
472
 
%% Option access functions
473
 
%%-----------------------------------------------------------------
474
 
 
475
 
get_verbosity(O) ->
476
 
    snmp_misc:get_option(verbosity,O,?default_verbosity).
477
 
 
478
 
get_me_override(O) ->
479
 
    snmp_misc:get_option(mibentry_override,O,false).
480
 
 
481
 
get_te_override(O) ->
482
 
    snmp_misc:get_option(trapentry_override,O,false).
483
 
 
484
 
get_mib_storage(O) ->
485
 
    snmp_misc:get_option(mib_storage,O,ets).
 
568
del_cache(Cache) ->
 
569
    ets:delete(Cache).
 
570
 
 
571
maybe_cache_lookup(?NO_CACHE, _) ->
 
572
    ?NO_CACHE;
 
573
maybe_cache_lookup(Cache, Key) ->
 
574
    ets:lookup(Cache, Key).
 
575
 
 
576
size_cache(?NO_CACHE) ->
 
577
    undefined;
 
578
size_cache(Cache) ->
 
579
    case (catch ets:info(Cache, memory)) of
 
580
        Sz when is_integer(Sz) ->
 
581
            Sz;
 
582
        _ ->
 
583
            undefined
 
584
    end.
486
585
 
487
586
 
488
587
%% ----------------------------------------------------------------