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

« back to all changes in this revision

Viewing changes to lib/snmp/test/snmp_agent_mibs_test.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
%%----------------------------------------------------------------------
 
19
%% Purpose:
 
20
%%----------------------------------------------------------------------
 
21
-module(snmp_agent_mibs_test).
 
22
 
 
23
%%----------------------------------------------------------------------
 
24
%% Include files
 
25
%%----------------------------------------------------------------------
 
26
-include("test_server.hrl").
 
27
-include("snmp_test_lib.hrl").
 
28
-include_lib("snmp/include/snmp_types.hrl").
 
29
-include_lib("snmp/include/SNMP-COMMUNITY-MIB.hrl").
 
30
-include_lib("snmp/include/SNMP-VIEW-BASED-ACM-MIB.hrl").
 
31
-include_lib("snmp/include/SNMP-USER-BASED-SM-MIB.hrl").
 
32
 
 
33
 
 
34
%%----------------------------------------------------------------------
 
35
%% External exports
 
36
%%----------------------------------------------------------------------
 
37
-export([
 
38
         all/1, 
 
39
         init_per_testcase/2, fin_per_testcase/2,
 
40
         init_all/1, finish_all/1, 
 
41
 
 
42
         start_and_stop/1,
 
43
         size_check/1,
 
44
         size_check_ets/1,
 
45
         size_check_dets/1,
 
46
         size_check_mnesia/1,
 
47
         load_unload/1,
 
48
         me_lookup/1,
 
49
         which_mib/1
 
50
 
 
51
        ]).
 
52
 
 
53
%%----------------------------------------------------------------------
 
54
%% Internal exports
 
55
%%----------------------------------------------------------------------
 
56
-export([
 
57
        ]).
 
58
 
 
59
%%----------------------------------------------------------------------
 
60
%% Macros
 
61
%%----------------------------------------------------------------------
 
62
 
 
63
%%----------------------------------------------------------------------
 
64
%% Records
 
65
%%----------------------------------------------------------------------
 
66
 
 
67
%%======================================================================
 
68
%% External functions
 
69
%%======================================================================
 
70
 
 
71
init_per_testcase(size_check_dets, Config) when list(Config) ->
 
72
    Dir = ?config(priv_dir, Config),
 
73
    DetsDir = join(Dir, "dets_dir/"),
 
74
    ?line ok = file:make_dir(DetsDir),
 
75
    [{dets_dir, DetsDir}|Config];
 
76
init_per_testcase(size_check_mnesia, Config) when list(Config) ->
 
77
    Dir = ?config(priv_dir, Config),
 
78
    MnesiaDir = join(Dir, "mnesia_dir/"),
 
79
    ?line ok = file:make_dir(MnesiaDir),
 
80
    mnesia_start([{dir, MnesiaDir}]),
 
81
    [{mnesia_dir, MnesiaDir}|Config];
 
82
init_per_testcase(_Case, Config) when list(Config) ->
 
83
    Config.
 
84
 
 
85
fin_per_testcase(size_check_dets, Config) when list(Config) ->
 
86
    Dir = ?config(dets_dir, Config),
 
87
    ?line ok = ?DEL_DIR(Dir),
 
88
    lists:keydelete(dets_dir, 1, Config);
 
89
fin_per_testcase(size_check_mnesia, Config) when list(Config) ->
 
90
    mnesia_stop(),
 
91
    Dir = ?config(mnesia_dir, Config),
 
92
    ?line ok = ?DEL_DIR(Dir),
 
93
    lists:keydelete(mnesia_dir, 1, Config);
 
94
fin_per_testcase(_Case, Config) when list(Config) ->
 
95
    Config.
 
96
 
 
97
 
 
98
%%======================================================================
 
99
%% Test case definitions
 
100
%%======================================================================
 
101
 
 
102
all(suite) ->
 
103
    {conf, init_all, cases(), finish_all}.
 
104
 
 
105
cases() ->
 
106
    [
 
107
     start_and_stop,
 
108
     load_unload,
 
109
     size_check,
 
110
     me_lookup,
 
111
     which_mib
 
112
    ].
 
113
 
 
114
init_all(Config) when list(Config) ->
 
115
    %% Data dir points wrong
 
116
    DataDir0     = ?config(data_dir, Config),
 
117
    DataDir1     = filename:split(filename:absname(DataDir0)),
 
118
    [_|DataDir2] = lists:reverse(DataDir1),
 
119
    DataDir      = filename:join(lists:reverse(DataDir2) ++ [?snmp_test_data]),
 
120
    [{snmp_data_dir, DataDir ++ "/"}|Config].
 
121
 
 
122
finish_all(Config) when list(Config) ->
 
123
    lists:keydelete(snmp_data_dir, 1, Config).
 
124
 
 
125
 
 
126
%%======================================================================
 
127
%% Test functions
 
128
%%======================================================================
 
129
 
 
130
start_and_stop(suite) -> [];
 
131
start_and_stop(Config) when list(Config) ->
 
132
    Prio      = normal,
 
133
    Verbosity = trace,
 
134
 
 
135
    ?line sym_start(Prio, Verbosity),
 
136
    ?line MibsPid = mibs_start(Prio, Verbosity),
 
137
 
 
138
    ?line mibs_info(MibsPid),
 
139
 
 
140
    ?line mibs_stop(MibsPid),
 
141
    ?line sym_stop(),
 
142
 
 
143
    ok.
 
144
 
 
145
 
 
146
%% ---------------------------------------------------------------------
 
147
 
 
148
load_unload(suite) -> [];
 
149
load_unload(Config) when list(Config) ->
 
150
    Prio       = normal,
 
151
    Verbosity  = log,
 
152
    %% MibStorage = ets,
 
153
    MibDir     = ?config(snmp_data_dir, Config),
 
154
 
 
155
    ?DBG("load_unload -> start symbolic store", []),
 
156
    ?line sym_start(Prio, Verbosity),
 
157
 
 
158
    ?DBG("load_unload -> start mib server", []),
 
159
    ?line MibsPid = mibs_start(Prio, Verbosity),
 
160
    
 
161
    ?DBG("load_unload -> load one not already loaded mib", []),
 
162
    ?line ok = verify_loaded_mibs(MibsPid, MibDir, []),
 
163
    ?line ok = load_mibs(MibsPid, MibDir, ["Test2"]),
 
164
    ?line ok = verify_loaded_mibs(MibsPid, MibDir, ["Test2"]),
 
165
    
 
166
    ?DBG("load_unload -> load one already loaded mib", []),
 
167
    ?line {error, _} = load_mibs(MibsPid, MibDir, ["Test2"]),
 
168
 
 
169
    ?DBG("load_unload -> load 2 not already loaded mibs", []),
 
170
    ?line ok = load_mibs(MibsPid, MibDir, ["TestTrap", "TestTrapv2"]),
 
171
    ?line ok = verify_loaded_mibs(MibsPid, MibDir, 
 
172
                                  ["Test2", "TestTrap", "TestTrapv2"]),
 
173
    
 
174
    ?DBG("load_unload -> unload one loaded mib", []),
 
175
    ?line ok = unload_mibs(MibsPid, ["Test2"]),
 
176
    ?line ok = verify_loaded_mibs(MibsPid, MibDir, ["TestTrap", "TestTrapv2"]),
 
177
    
 
178
    ?DBG("load_unload -> try unload two loaded mibs and one not loaded", []),
 
179
    ?line {error, _} = unload_mibs(MibsPid, ["TestTrap","Test2","TestTrapv2"]),
 
180
    ?line ok = verify_loaded_mibs(MibsPid, MibDir, ["TestTrapv2"]),
 
181
    
 
182
    ?DBG("load_unload -> unload the remaining loaded mib", []),
 
183
    ?line ok = unload_mibs(MibsPid, ["TestTrapv2"]),
 
184
    ?line ok = verify_loaded_mibs(MibsPid, MibDir, []),
 
185
    
 
186
    ?DBG("load_unload -> stop mib server", []),
 
187
    ?line mibs_stop(MibsPid),
 
188
 
 
189
    ?DBG("load_unload -> stop symbolic store", []),
 
190
    ?line sym_stop(),
 
191
 
 
192
    ok.
 
193
 
 
194
 
 
195
%% ---------------------------------------------------------------------
 
196
 
 
197
size_check(suite) ->
 
198
    [
 
199
     size_check_ets,
 
200
     size_check_dets,
 
201
     size_check_mnesia
 
202
    ].
 
203
 
 
204
size_check_ets(suite) ->
 
205
    [];
 
206
size_check_ets(Config) when list(Config) ->
 
207
    do_size_check([{mib_storage, ets}|Config]).
 
208
 
 
209
size_check_dets(suite) ->
 
210
    [];
 
211
size_check_dets(Config) when list(Config) ->
 
212
    Dir = ?config(dets_dir, Config),
 
213
    do_size_check([{mib_storage, {dets, Dir}}|Config]).
 
214
 
 
215
size_check_mnesia(suite) ->
 
216
    [];
 
217
size_check_mnesia(Config) when list(Config) ->
 
218
    do_size_check([{mib_storage, {mnesia, [node()]}}|Config]).
 
219
 
 
220
do_size_check(Config) ->
 
221
    ?DBG("do_size_check -> start", []),
 
222
    Prio      = normal,
 
223
    Verbosity = trace,
 
224
 
 
225
    MibStorage = ?config(mib_storage, Config),
 
226
    ?DBG("do_size_check -> MibStorage: ~p", [MibStorage]),
 
227
    MibDir     = ?config(snmp_data_dir, Config),
 
228
    StdMibDir  = filename:join(code:priv_dir(snmp), "mibs") ++ "/",
 
229
    
 
230
    ?DBG("do_size_check -> start symbolic store", []),
 
231
    ?line sym_start(Prio, MibStorage, Verbosity),
 
232
    ?DBG("do_size_check -> start mib server", []),
 
233
    ?line MibsPid = mibs_start(Prio, MibStorage, Verbosity),
 
234
 
 
235
    Mibs    = ["Test2", "TestTrap", "TestTrapv2"],
 
236
    StdMibs = ["OTP-SNMPEA-MIB",
 
237
               "SNMP-COMMUNITY-MIB",
 
238
               "SNMP-FRAMEWORK-MIB",
 
239
               "SNMP-MPD-MIB",
 
240
               "SNMP-NOTIFICATION-MIB",
 
241
               "SNMP-TARGET-MIB",
 
242
               "SNMP-USER-BASED-SM-MIB",
 
243
               "SNMP-VIEW-BASED-ACM-MIB",
 
244
               "SNMPv2-MIB",
 
245
               "SNMPv2-TC",
 
246
               "SNMPv2-TM"],
 
247
 
 
248
    ?DBG("do_size_check -> load mibs", []),
 
249
    ?line load_mibs(MibsPid, MibDir, Mibs),
 
250
    ?DBG("do_size_check -> load std mibs", []),
 
251
    ?line load_mibs(MibsPid, StdMibDir, StdMibs),
 
252
 
 
253
    ?SLEEP(2000),
 
254
    ?DBG("do_size_check -> display mem usage", []),
 
255
    ?line display_memory_usage(MibsPid),
 
256
    
 
257
    ?DBG("do_size_check -> unload std mibs", []),
 
258
    ?line unload_mibs(MibsPid, StdMibs),
 
259
    ?DBG("do_size_check -> unload mibs", []),
 
260
    ?line unload_mibs(MibsPid, Mibs),
 
261
 
 
262
    ?DBG("do_size_check -> stop mib server", []),
 
263
    ?line mibs_stop(MibsPid),
 
264
    ?DBG("do_size_check -> stop symbolic store", []),
 
265
    ?line sym_stop(),
 
266
 
 
267
    ?DBG("do_size_check -> done", []),
 
268
    ok.
 
269
 
 
270
 
 
271
%% ---------------------------------------------------------------------
 
272
 
 
273
me_lookup(suite) -> [];
 
274
me_lookup(Config) when list(Config) ->
 
275
    Prio       = normal,
 
276
    Verbosity  = trace,
 
277
    %% MibStorage = ets,
 
278
    MibDir     = ?config(snmp_data_dir, Config),
 
279
    StdMibDir  = filename:join(code:priv_dir(snmp), "mibs") ++ "/",
 
280
    Mibs    = ["Test2", "TestTrap", "TestTrapv2"],
 
281
    StdMibs = ["OTP-SNMPEA-MIB",
 
282
               "SNMP-COMMUNITY-MIB",
 
283
               "SNMP-FRAMEWORK-MIB",
 
284
               "SNMP-MPD-MIB",
 
285
               "SNMP-NOTIFICATION-MIB",
 
286
               "SNMP-TARGET-MIB",
 
287
               %% "SNMP-USER-BASED-SM-MIB",
 
288
               "SNMP-VIEW-BASED-ACM-MIB",
 
289
               "SNMPv2-MIB",
 
290
               "SNMPv2-TC",
 
291
               "SNMPv2-TM"],
 
292
 
 
293
    ?DBG("me_lookup -> start symbolic store", []),
 
294
    ?line sym_start(Prio, Verbosity),
 
295
 
 
296
    ?DBG("me_lookup -> start mib server", []),
 
297
    ?line MibsPid = mibs_start(Prio, Verbosity),
 
298
    
 
299
    ?DBG("me_lookup -> load mibs", []),
 
300
    ?line load_mibs(MibsPid, MibDir, Mibs),
 
301
    ?DBG("me_lookup -> load std mibs", []),
 
302
    ?line load_mibs(MibsPid, StdMibDir, StdMibs),
 
303
 
 
304
    ?DBG("me_lookup -> find ~w from SNMP-COMMUNITY-MIB", 
 
305
         [?snmpTrapCommunity_instance]),
 
306
    ?line ok = me_lookup(MibsPid, ?snmpTrapCommunity_instance),
 
307
    
 
308
    ?DBG("me_lookup -> find ~w from SNMP-VIEW-BASED-ACM-MIB", 
 
309
         [?vacmViewSpinLock_instance]),
 
310
    ?line ok = me_lookup(MibsPid, ?vacmViewSpinLock_instance),
 
311
    
 
312
    ?DBG("me_lookup -> find ~w from SNMP-USER-BASED-SM-MIB", 
 
313
         [?usmStatsNotInTimeWindows_instance]),
 
314
    ?line {error, _} = me_lookup(MibsPid, ?usmStatsNotInTimeWindows_instance),
 
315
    
 
316
    ?DBG("me_lookup -> stop mib server", []),
 
317
    ?line mibs_stop(MibsPid),
 
318
 
 
319
    ?DBG("me_lookup -> stop symbolic store", []),
 
320
    ?line sym_stop(),
 
321
 
 
322
    ok.
 
323
 
 
324
 
 
325
%% ---------------------------------------------------------------------
 
326
 
 
327
which_mib(suite) -> [];
 
328
which_mib(Config) when list(Config) ->
 
329
    Prio       = normal,
 
330
    Verbosity  = trace,
 
331
    %% MibStorage = ets,
 
332
    MibDir     = ?config(snmp_data_dir, Config),
 
333
    StdMibDir  = filename:join(code:priv_dir(snmp), "mibs") ++ "/",
 
334
    Mibs    = ["Test2", "TestTrap", "TestTrapv2"],
 
335
    StdMibs = ["OTP-SNMPEA-MIB",
 
336
               "SNMP-COMMUNITY-MIB",
 
337
               "SNMP-FRAMEWORK-MIB",
 
338
               "SNMP-MPD-MIB",
 
339
               "SNMP-NOTIFICATION-MIB",
 
340
               "SNMP-TARGET-MIB",
 
341
               %% "SNMP-USER-BASED-SM-MIB",
 
342
               "SNMP-VIEW-BASED-ACM-MIB",
 
343
               "SNMPv2-MIB",
 
344
               "SNMPv2-TC",
 
345
               "SNMPv2-TM"],
 
346
 
 
347
    ?DBG("which_mib -> start symbolic store", []),
 
348
    ?line sym_start(Prio, Verbosity),
 
349
 
 
350
    ?DBG("which_mib -> start mib server", []),
 
351
    ?line MibsPid = mibs_start(Prio, Verbosity),
 
352
    
 
353
    ?DBG("which_mib -> load mibs", []),
 
354
    ?line load_mibs(MibsPid, MibDir, Mibs),
 
355
    ?DBG("which_mib -> load std mibs", []),
 
356
    ?line load_mibs(MibsPid, StdMibDir, StdMibs),
 
357
 
 
358
    ?DBG("which_mib -> find ~w from SNMP-COMMUNITY-MIB", 
 
359
         [?snmpTrapCommunity_instance]),
 
360
    ?line ok = which_mib(MibsPid, ?snmpTrapCommunity_instance, 
 
361
                         "SNMP-COMMUNITY-MIB"),
 
362
    
 
363
    ?DBG("which_mib -> find ~w from SNMP-VIEW-BASED-ACM-MIB", 
 
364
         [?vacmViewSpinLock_instance]),
 
365
    ?line ok = which_mib(MibsPid, ?vacmViewSpinLock_instance, 
 
366
                         "SNMP-VIEW-BASED-ACM-MIB"),
 
367
    
 
368
    ?DBG("which_mib -> find ~w from SNMP-USER-BASED-SM-MIB (not loaded)", 
 
369
         [?usmStatsNotInTimeWindows_instance]),
 
370
    ?line {error, _} = which_mib(MibsPid, ?usmStatsNotInTimeWindows_instance,
 
371
                                "SNMP-USER-BASED-SM-MIB"),
 
372
    
 
373
    ?DBG("which_mib -> stop mib server", []),
 
374
    ?line mibs_stop(MibsPid),
 
375
 
 
376
    ?DBG("which_mib -> stop symbolic store", []),
 
377
    ?line sym_stop(),
 
378
 
 
379
    ok.
 
380
 
 
381
 
 
382
%%======================================================================
 
383
%% Internal functions
 
384
%%======================================================================
 
385
 
 
386
%% -- Mnesia functions
 
387
 
 
388
mnesia_start(Opts) ->
 
389
    mnesia_start(Opts, [node()]).
 
390
 
 
391
mnesia_start(Opts, Nodes) ->
 
392
    ?DBG("mnesia_start -> load mnesia", []),
 
393
    ?line ok = application:load(mnesia),
 
394
    F = fun({Key, Val}) ->
 
395
                ?DBG("mnesia_start -> set mnesia env: ~n~p -> ~p", [Key,Val]),
 
396
                ?line application_controller:set_env(mnesia, Key, Val)
 
397
        end,
 
398
    lists:foreach(F, Opts),
 
399
    ?DBG("mnesia_start -> create mnesia schema on ~p", [Nodes]),
 
400
    ?line ok = mnesia:create_schema(Nodes),
 
401
    ?DBG("mnesia_start -> start mnesia", []),
 
402
    ?line ok = application:start(mnesia),
 
403
    ok.
 
404
 
 
405
mnesia_stop() ->
 
406
    ?DBG("mnesia_stop -> stop mnesia", []),
 
407
    application:stop(mnesia),
 
408
    ?DBG("mnesia_stop -> unload mnesia", []),
 
409
    application:unload(mnesia),
 
410
    ok.
 
411
    
 
412
%% - Symbolic Store mini interface
 
413
 
 
414
sym_start(Prio, Verbosity) ->
 
415
    sym_start(Prio, ets, Verbosity).
 
416
 
 
417
sym_start(Prio, MibStorage, Verbosity) ->
 
418
    Opts = [{mib_storage, MibStorage}, {verbosity,Verbosity}],
 
419
    {ok, _Pid} = snmpa_symbolic_store:start_link(Prio, Opts),
 
420
    ok.
 
421
 
 
422
sym_stop() ->
 
423
    ok = snmpa_symbolic_store:stop().
 
424
 
 
425
sym_info() ->
 
426
    snmpa_symbolic_store:info().
 
427
 
 
428
 
 
429
%% -- MIB server mini interface 
 
430
                   
 
431
mibs_start(Prio, Verbosity) ->
 
432
    mibs_start(Prio, ets, [], Verbosity).
 
433
 
 
434
mibs_start(Prio, MibStorage, Verbosity) ->
 
435
    mibs_start(Prio, MibStorage, [], Verbosity).
 
436
 
 
437
mibs_start(Prio, MibStorage, Mibs, Verbosity) ->
 
438
    Opts = [{mib_storage, MibStorage}, {verbosity,Verbosity}],
 
439
    {ok, Pid} = snmpa_mib:start_link(Prio, Mibs, Opts),
 
440
    Pid.
 
441
 
 
442
mibs_stop(Pid) ->
 
443
    ok = snmpa_mib:stop(Pid).
 
444
 
 
445
mibs_info(Pid) ->
 
446
    snmpa_mib:info(Pid).
 
447
 
 
448
load_mibs(Pid, Dir, Mibs0) ->
 
449
    Mibs = [join(Dir, Mib) || Mib <- Mibs0],
 
450
    snmpa_mib:load_mibs(Pid, Mibs).
 
451
 
 
452
unload_mibs(Pid, Mibs) ->
 
453
    snmpa_mib:unload_mibs(Pid, Mibs).
 
454
 
 
455
verify_loaded_mibs(Pid, Dir, ExpectedMibs0) ->
 
456
    ExpectedMibs = [join(Dir, Mib) || Mib <- ExpectedMibs0],
 
457
    case snmpa_mib:info(Pid, loaded_mibs) of
 
458
        ExpectedMibs ->
 
459
            ok;
 
460
        LoadedMibs0 ->
 
461
            ?DBG("verify_loaded_mibs -> LoadedMibs0: ~p", [LoadedMibs0]),
 
462
            LoadedMibs = [filename:rootname(FN, ".bin") || FN <- LoadedMibs0],
 
463
            ?DBG("verify_loaded_mibs -> LoadedMibs: ~p", [LoadedMibs]),
 
464
            ExpNotLoadedMibs = ExpectedMibs -- LoadedMibs,
 
465
            LoadedNotExpMibs = LoadedMibs -- ExpectedMibs,
 
466
            ?DBG("verify_loaded_mibs -> "
 
467
                 "~n   ExpNotLoadedMibs: ~p"
 
468
                 "~n   LoadedNotExpMibs: ~p", 
 
469
                 [ExpNotLoadedMibs, LoadedNotExpMibs]),
 
470
            case ExpNotLoadedMibs of
 
471
                [] ->
 
472
                    case LoadedNotExpMibs of
 
473
                        [] ->
 
474
                            ok;
 
475
                        _ ->
 
476
                            {error, {unexpected_loaded_mibs, LoadedNotExpMibs}}
 
477
                    end;
 
478
                _ ->
 
479
                    case LoadedNotExpMibs of
 
480
                        [] ->
 
481
                            {error, {not_loaded_mibs, ExpNotLoadedMibs}};
 
482
                        _ ->
 
483
                            {error, {unexpected_mibs, 
 
484
                                     ExpNotLoadedMibs, LoadedNotExpMibs}}
 
485
                    end
 
486
            end
 
487
        
 
488
    end.
 
489
 
 
490
me_lookup(Pid, Oid) ->    
 
491
    case snmpa_mib:lookup(Pid, Oid) of
 
492
        {variable, #me{oid = Oid}} ->
 
493
            ok;
 
494
        {variable, #me{oid = OtherOid}} ->
 
495
            case lists:reverse(Oid) of
 
496
                [0|Rest] ->
 
497
                    case lists:reverse(Rest) of
 
498
                        OtherOid ->
 
499
                            ok;
 
500
                        AnotherOid ->
 
501
                            {error, {invalid_oid, Oid, AnotherOid}}
 
502
                    end;
 
503
                _ ->
 
504
                    {error, {invalid_oid, Oid, OtherOid}}
 
505
            end;
 
506
        {table_column, _ME, _TableEntryOid} ->
 
507
            ok;
 
508
        {subagent, SubAgentPid, _SANextOid} ->
 
509
            {error, {subagent, SubAgentPid}};
 
510
        {false, Reason} ->
 
511
            {error, Reason};
 
512
        Else ->
 
513
            {error, Else}
 
514
    end.
 
515
 
 
516
                            
 
517
which_mib(Pid, Oid, Mib1) ->    
 
518
    case snmpa_mib:which_mib(Pid, Oid) of
 
519
        {ok, Mib2} when atom(Mib2) ->
 
520
            Mib3 = atom_to_list(Mib2),
 
521
            which_mib(Mib1, Mib3);
 
522
        {ok, Mib2} ->
 
523
            which_mib(Mib1, Mib2);
 
524
        {error, Reason} ->
 
525
            {error, Reason};
 
526
        Else ->
 
527
            {error, Else}
 
528
    end.
 
529
 
 
530
which_mib(M, M) ->
 
531
    ok;
 
532
which_mib(M1, M2) ->
 
533
    {error, {invalid_mib, M1, M2}}.
 
534
 
 
535
 
 
536
%% -- 
 
537
 
 
538
display_memory_usage(MibsPid) ->
 
539
    SymInfo     = sym_info(),
 
540
    SymProcSize = key1search(process_memory, SymInfo),
 
541
    DbSize      = key1search(db_memory,      SymInfo),
 
542
    MibsInfo    = mibs_info(MibsPid),
 
543
    TreeSize    = key1search(tree_size_bytes,  MibsInfo),
 
544
    MibsProcMem = key1search(process_memory,   MibsInfo),
 
545
    MibDbSize   = key1search([db_memory,mib],  MibsInfo),
 
546
    NodeDbSize  = key1search([db_memory,node], MibsInfo),
 
547
    TreeDbSize  = key1search([db_memory,tree], MibsInfo),
 
548
    ?INF("Symbolic store memory usage: "
 
549
        "~n   Process memory size: ~p"
 
550
        "~n   Db size:             ~p"
 
551
        "~n"
 
552
        "~nMib server memory usage: "
 
553
        "~n   Tree size:           ~p"
 
554
        "~n   Process memory size: ~p"
 
555
        "~n   Mib db size:         ~p"
 
556
        "~n   Node db size:        ~p"
 
557
        "~n   Tree db size:        ~p"
 
558
        "~n", 
 
559
        [SymProcSize, DbSize,
 
560
        TreeSize, MibsProcMem, MibDbSize, NodeDbSize, TreeDbSize]).
 
561
    
 
562
key1search([], Res) ->
 
563
    Res;
 
564
key1search([Key|Keys], List) when atom(Key), list(List) ->
 
565
    case lists:keysearch(Key, 1, List) of
 
566
        {value, {Key, Val}} ->
 
567
            key1search(Keys, Val);
 
568
        false ->
 
569
            undefined
 
570
    end;
 
571
key1search(Key, List) when atom(Key) ->
 
572
    case lists:keysearch(Key, 1, List) of
 
573
        {value, {Key, Val}} ->
 
574
            Val;
 
575
        false ->
 
576
            undefined
 
577
    end.
 
578
 
 
579
join(Dir, File) ->
 
580
    filename:join(Dir, File).