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

« back to all changes in this revision

Viewing changes to lib/snmp/examples/ex2/snmp_ex2_manager.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
%% This module examplifies how to write test suites for your SNMP agent.
 
20
%%----------------------------------------------------------------------
 
21
 
 
22
-module(snmp_ex2_manager).
 
23
 
 
24
-behaviour(gen_server).
 
25
-behaviour(snmpm_user).
 
26
 
 
27
-export([start_link/0, start_link/1, stop/0,
 
28
         agent/2, agent/3,
 
29
         sync_get/2,      sync_get/3,
 
30
         sync_get_next/2, sync_get_next/3,
 
31
         sync_get_bulk/4, sync_get_bulk/5,
 
32
         sync_set/2,      sync_set/3,
 
33
 
 
34
         oid_to_name/1
 
35
        ]).
 
36
 
 
37
%% Manager callback API:
 
38
-export([handle_error/3,
 
39
         handle_agent/4,
 
40
         handle_pdu/5,
 
41
         handle_trap/4,
 
42
         handle_inform/4,
 
43
         handle_report/4]).
 
44
 
 
45
%% gen_server callbacks
 
46
-export([init/1, handle_call/3, handle_cast/2, handle_info/2,
 
47
         code_change/3, terminate/2]).
 
48
 
 
49
-include_lib("snmp/include/snmp_types.hrl").
 
50
 
 
51
 
 
52
-define(SERVER,   ?MODULE).
 
53
-define(USER,     ?MODULE).
 
54
-define(USER_MOD, ?MODULE).
 
55
 
 
56
-record(state, {parent}).
 
57
 
 
58
 
 
59
%%%-------------------------------------------------------------------
 
60
%%% API
 
61
%%%-------------------------------------------------------------------
 
62
 
 
63
start_link() ->
 
64
    start_link([]).
 
65
 
 
66
start_link(Opts) when is_list(Opts) ->
 
67
    gen_server:start_link({local, ?SERVER}, ?MODULE, [self(), Opts], []).
 
68
 
 
69
stop() ->
 
70
    cast(stop).
 
71
 
 
72
 
 
73
%% --- Instruct manager to handle an agent ---
 
74
 
 
75
agent(Addr, Conf) ->
 
76
    call({agent, Addr, Conf}).
 
77
 
 
78
agent(Addr, Port, Conf) ->
 
79
    call({agent, Addr, Port, Conf}).
 
80
 
 
81
 
 
82
%% --- Misc utility functions ---
 
83
 
 
84
oid_to_name(Oid) ->
 
85
    call({oid_to_name, Oid}).
 
86
 
 
87
 
 
88
%% --- Various SNMP operations ----
 
89
 
 
90
sync_get(Addr, Oids) ->
 
91
    call({sync_get, Addr, Oids}).
 
92
 
 
93
sync_get(Addr, Port, Oids) ->
 
94
    call({sync_get, Addr, Port, Oids}).
 
95
 
 
96
 
 
97
sync_get_next(Addr, Oids) ->
 
98
    call({sync_get_next, Addr, Oids}).
 
99
 
 
100
sync_get_next(Addr, Port, Oids) ->
 
101
    call({sync_get_next, Addr, Port, Oids}).
 
102
 
 
103
 
 
104
sync_get_bulk(Addr, NR, MR, Oids) ->
 
105
    call({sync_get_bulk, Addr, NR, MR, Oids}).
 
106
 
 
107
sync_get_bulk(Addr, Port, NR, MR, Oids) ->
 
108
    call({sync_get_bulk, Addr, Port, NR, MR, Oids}).
 
109
 
 
110
 
 
111
sync_set(Addr, VarsAndVals) ->
 
112
    call({sync_set, Addr, VarsAndVals}).
 
113
 
 
114
sync_set(Addr, Port, VarsAndVals) ->
 
115
    call({sync_set, Addr, Port, VarsAndVals}).
 
116
 
 
117
 
 
118
%%%-------------------------------------------------------------------
 
119
%%% Callback functions from gen_server
 
120
%%%-------------------------------------------------------------------
 
121
 
 
122
init([Parent, Opts]) ->
 
123
    process_flag(trap_exit, true),
 
124
    case (catch do_init(Opts)) of
 
125
        {ok, State} ->
 
126
            {ok, State#state{parent = Parent}};
 
127
        {error, Reason} ->
 
128
            {stop, Reason};
 
129
        Crap ->
 
130
            {stop, Crap}
 
131
    end.
 
132
 
 
133
do_init(Opts) ->
 
134
    {Dir, MgrConf, MgrOpts} = parse_opts(Opts),
 
135
    write_config(Dir, MgrConf),
 
136
    start_manager(MgrOpts),
 
137
    register_user(),
 
138
    {ok, #state{}}.
 
139
 
 
140
write_config(Dir, Conf) ->
 
141
    case snmp_config:write_manager_config(Dir, "", Conf) of
 
142
        ok ->
 
143
            ok;
 
144
        Error ->
 
145
            error({failed_writing_config, Error})
 
146
    end.
 
147
 
 
148
start_manager(Opts) ->
 
149
    case snmpm:start_link(Opts) of
 
150
        ok ->
 
151
            ok; 
 
152
        Error ->
 
153
            error({failed_starting_manager, Error})
 
154
    end.
 
155
 
 
156
register_user() ->
 
157
    case snmpm:register_user(?USER, ?USER_MOD, self()) of
 
158
        ok ->
 
159
            ok;
 
160
        Error ->
 
161
            error({failed_register_user, Error})
 
162
    end.
 
163
 
 
164
parse_opts(Opts) ->
 
165
    Port     = get_opt(port,             Opts, 5000),
 
166
    EngineId = get_opt(engine_id,        Opts, "mgrEngine"),
 
167
    MMS      = get_opt(max_message_size, Opts, 484),
 
168
 
 
169
    MgrConf = [{port,             Port},
 
170
               {engine_id,        EngineId},
 
171
               {max_message_size, MMS}],
 
172
 
 
173
    %% Manager options
 
174
    Mibs      = get_opt(mibs,     Opts, []),
 
175
    Vsns      = get_opt(versions, Opts, [v1, v2, v3]),
 
176
    {ok, Cwd} = file:get_cwd(),
 
177
    Dir       = get_opt(dir, Opts, Cwd),
 
178
    MgrOpts   = [{mibs,     Mibs},
 
179
                 {versions, Vsns}, 
 
180
                 %% {server,   [{verbosity, trace}]}, 
 
181
                 {config,   [% {verbosity, trace}, 
 
182
                             {dir, Dir}, {db_dir, Dir}]}],
 
183
    
 
184
    {Dir, MgrConf, MgrOpts}.
 
185
 
 
186
 
 
187
%%--------------------------------------------------------------------
 
188
%% Func: handle_call/3
 
189
%% Returns: {reply, Reply, State}          |
 
190
%%          {reply, Reply, State, Timeout} |
 
191
%%          {noreply, State}               |
 
192
%%          {noreply, State, Timeout}      |
 
193
%%          {stop, Reason, Reply, State}   | (terminate/2 is called)
 
194
%%          {stop, Reason, State}            (terminate/2 is called)
 
195
%%--------------------------------------------------------------------
 
196
 
 
197
handle_call({agent, Addr, Conf}, _From, S) ->
 
198
    Reply = (catch snmpm:register_agent(?USER, Addr, Conf)),
 
199
    {reply, Reply, S};
 
200
 
 
201
handle_call({agent, Addr, Port, Conf}, _From, S) ->
 
202
    Reply = (catch snmpm:register_agent(?USER, Addr, Port, Conf)),
 
203
    {reply, Reply, S};
 
204
 
 
205
handle_call({oid_to_name, Oid}, _From, S) ->
 
206
    Reply = (catch snmpm:oid_to_name(Oid)),
 
207
    {reply, Reply, S};
 
208
 
 
209
handle_call({sync_get, Addr, Oids}, _From, S) ->
 
210
    Reply = (catch snmpm:g(?USER, Addr, Oids)),
 
211
    {reply, Reply, S};
 
212
 
 
213
handle_call({sync_get, Addr, Port, Oids}, _From, S) ->
 
214
    Reply = (catch snmpm:g(?USER, Addr, Port, Oids)),
 
215
    {reply, Reply, S};
 
216
 
 
217
handle_call({sync_get_next, Addr, Oids}, _From, S) ->
 
218
    Reply = (catch snmpm:gn(?USER, Addr, Oids)),
 
219
    {reply, Reply, S};
 
220
 
 
221
handle_call({sync_get_next, Addr, Port, Oids}, _From, S) ->
 
222
    Reply = (catch snmpm:gn(?USER, Addr, Port, Oids)),
 
223
    {reply, Reply, S};
 
224
 
 
225
handle_call({sync_get_bulk, Addr, NR, MR, Oids}, _From, S) ->
 
226
    Reply = (catch snmpm:gb(?USER, Addr, NR, MR, Oids)),
 
227
    {reply, Reply, S};
 
228
 
 
229
handle_call({sync_get_bulk, Addr, Port, NR, MR, Oids}, _From, S) ->
 
230
    Reply = (catch snmpm:gb(?USER, Addr, Port, NR, MR, Oids)),
 
231
    {reply, Reply, S};
 
232
 
 
233
handle_call({sync_set, Addr, VarsAndVals}, _From, S) ->
 
234
    Reply = (catch snmpm:s(?USER, Addr, VarsAndVals)),
 
235
    {reply, Reply, S};
 
236
 
 
237
handle_call({sync_set, Addr, Port, VarsAndVals}, _From, S) ->
 
238
    Reply = (catch snmpm:s(?USER, Addr, Port, VarsAndVals)),
 
239
    {reply, Reply, S};
 
240
 
 
241
handle_call(Req, From, State) ->
 
242
    error_msg("received unknown request ~n~p~nFrom ~p", [Req, From]),
 
243
    {reply, {error, {unknown_request, Req}}, State}.
 
244
 
 
245
 
 
246
%%--------------------------------------------------------------------
 
247
%% Func: handle_cast/2
 
248
%% Returns: {noreply, State}          |
 
249
%%          {noreply, State, Timeout} |
 
250
%%          {stop, Reason, State}            (terminate/2 is called)
 
251
%%--------------------------------------------------------------------
 
252
handle_cast(stop, S) ->
 
253
    (catch snmpm:stop()),
 
254
    {stop, normal, S};
 
255
 
 
256
handle_cast(Msg, State) ->
 
257
    error_msg("received unknown message ~n~p", [Msg]),
 
258
    {noreply, State}.
 
259
 
 
260
 
 
261
%%--------------------------------------------------------------------
 
262
%% Func: handle_info/2
 
263
%% Returns: {noreply, State}          |
 
264
%%          {noreply, State, Timeout} |
 
265
%%          {stop, Reason, State}            (terminate/2 is called)
 
266
%%--------------------------------------------------------------------
 
267
handle_info({snmp_callback, Tag, Info}, State) ->
 
268
    handle_snmp_callback(Tag, Info),
 
269
    {noreply, State};
 
270
 
 
271
handle_info(Info, State) ->
 
272
    error_msg("received unknown info: "
 
273
              "~n   Info: ~p", [Info]),
 
274
    {noreply, State}.
 
275
 
 
276
 
 
277
%%--------------------------------------------------------------------
 
278
%% Func: terminate/2
 
279
%% Purpose: Shutdown the server
 
280
%% Returns: any (ignored by gen_server)
 
281
%%--------------------------------------------------------------------
 
282
terminate(_Reason, _State) ->
 
283
    ok.
 
284
 
 
285
 
 
286
code_change({down, _Vsn}, State, _Extra) ->
 
287
    {ok, State};
 
288
 
 
289
% upgrade
 
290
code_change(_Vsn, State, _Extra) ->
 
291
    {ok, State}.
 
292
 
 
293
 
 
294
%% ========================================================================
 
295
%% ========================================================================
 
296
 
 
297
handle_snmp_callback(handle_error, {ReqId, Reason}) ->
 
298
    io:format("*** FAILURE ***"
 
299
              "~n   Request Id: ~p"
 
300
              "~n   Reason:     ~p"
 
301
              "~n", [ReqId, Reason]),
 
302
    ok;
 
303
handle_snmp_callback(handle_agent, {Addr, Port, SnmpInfo}) ->
 
304
    {ES, EI, VBs} = SnmpInfo, 
 
305
    io:format("*** UNKNOWN AGENT ***"
 
306
              "~n   Address:   ~p"
 
307
              "~n   Port:      ~p"
 
308
              "~n   SNMP Info: "
 
309
              "~n     Error Status: ~w"
 
310
              "~n     Error Index:  ~w"
 
311
              "~n     Varbinds:     ~p"
 
312
              "~n", [Addr, Port, ES, EI, VBs]),
 
313
    ok;
 
314
handle_snmp_callback(handle_pdu, {Addr, Port, ReqId, SnmpResponse}) ->
 
315
    {ES, EI, VBs} = SnmpResponse, 
 
316
    io:format("*** Received PDU ***"
 
317
              "~n   Address:       ~p"
 
318
              "~n   Port:          ~p"
 
319
              "~n   Request Id:    ~p"
 
320
              "~n   SNMP response:"
 
321
              "~n     Error Status: ~w"
 
322
              "~n     Error Index:  ~w"
 
323
              "~n     Varbinds:     ~p"
 
324
              "~n", [Addr, Port, ReqId, ES, EI, VBs]),
 
325
    ok;
 
326
handle_snmp_callback(handle_trap, {Addr, Port, SnmpTrap}) ->
 
327
    TrapStr = 
 
328
        case SnmpTrap of
 
329
            {Enteprise, Generic, Spec, Timestamp, Varbinds} ->
 
330
                io_lib:format("~n     Generic:    ~w"
 
331
                              "~n     Exterprise: ~w"
 
332
                              "~n     Specific:   ~w"
 
333
                              "~n     Timestamp:  ~w"
 
334
                              "~n     Varbinds:   ~p", 
 
335
                              [Generic, Enteprise, Spec, Timestamp, Varbinds]);
 
336
            {ErrorStatus, ErrorIndex, Varbinds} ->
 
337
                io_lib:format("~n     Error Status: ~w"
 
338
                              "~n     Error Index:  ~w"
 
339
                              "~n     Varbinds:     ~p"
 
340
                              "~n", [ErrorStatus, ErrorIndex, Varbinds])
 
341
        end,
 
342
    io:format("*** Received TRAP ***"
 
343
              "~n   Address:   ~p"
 
344
              "~n   Port:      ~p"
 
345
              "~n   SNMP trap: ~s"
 
346
              "~n", [Addr, Port, lists:flatten(TrapStr)]),
 
347
    ok;
 
348
handle_snmp_callback(handle_inform, {Addr, Port, SnmpInform}) ->
 
349
    {ES, EI, VBs} = SnmpInform, 
 
350
    io:format("*** Received INFORM ***"
 
351
              "~n   Address:     ~p"
 
352
              "~n   Port:        ~p"
 
353
              "~n   SNMP inform: "
 
354
              "~n     Error Status: ~w"
 
355
              "~n     Error Index:  ~w"
 
356
              "~n     Varbinds:     ~p"
 
357
              "~n", [Addr, Port, ES, EI, VBs]),
 
358
    ok;
 
359
handle_snmp_callback(handle_report, {Addr, Port, SnmpReport}) ->
 
360
    {ES, EI, VBs} = SnmpReport, 
 
361
    io:format("*** Received REPORT ***"
 
362
              "~n   Address:   ~p"
 
363
              "~n   Port:      ~p"
 
364
              "~n   SNMP report: "
 
365
              "~n     Error Status: ~w"
 
366
              "~n     Error Index:  ~w"
 
367
              "~n     Varbinds:     ~p"
 
368
              "~n", [Addr, Port, ES, EI, VBs]),
 
369
    ok;
 
370
handle_snmp_callback(BadTag, Crap) ->
 
371
    io:format("*** Received crap ***"
 
372
              "~n   ~p"
 
373
              "~n   ~p"
 
374
              "~n", [BadTag, Crap]),
 
375
    ok.
 
376
    
 
377
 
 
378
 
 
379
error(Reason) ->
 
380
    throw({error, Reason}).
 
381
 
 
382
 
 
383
error_msg(F, A) ->
 
384
    catch error_logger:error_msg("*** TEST-MANAGER: " ++ F ++ "~n", A).
 
385
 
 
386
 
 
387
call(Req) ->
 
388
    gen_server:call(?SERVER, Req, infinity).
 
389
 
 
390
cast(Msg) ->
 
391
    gen_server:cast(?SERVER, Msg).
 
392
 
 
393
 
 
394
%% ========================================================================
 
395
%% Misc internal utility functions
 
396
%% ========================================================================
 
397
 
 
398
%% get_opt(Key, Opts) ->
 
399
%%     case lists:keysearch(Key, 1, Opts) of
 
400
%%         {value, {Key, Val}} ->
 
401
%%             Val;
 
402
%%         false ->
 
403
%%             throw({error, {missing_mandatory, Key}})
 
404
%%     end.
 
405
 
 
406
get_opt(Key, Opts, Def) ->
 
407
    case lists:keysearch(Key, 1, Opts) of
 
408
        {value, {Key, Val}} ->
 
409
            Val;
 
410
        false ->
 
411
            Def
 
412
    end.
 
413
 
 
414
 
 
415
%% ========================================================================
 
416
%% SNMPM user callback functions
 
417
%% ========================================================================
 
418
 
 
419
handle_error(ReqId, Reason, Server) when is_pid(Server) ->
 
420
    report_callback(Server, handle_error, {ReqId, Reason}),
 
421
    ignore.
 
422
 
 
423
 
 
424
handle_agent(Addr, Port, SnmpInfo, Server) when is_pid(Server) ->
 
425
    report_callback(Server, handle_agent, {Addr, Port, SnmpInfo}),
 
426
    ignore.
 
427
 
 
428
 
 
429
handle_pdu(Addr, Port, ReqId, SnmpResponse, Server) when is_pid(Server) ->
 
430
    report_callback(Server, handle_pdu, {Addr, Port, ReqId, SnmpResponse}),
 
431
    ignore.
 
432
 
 
433
 
 
434
handle_trap(Addr, Port, SnmpTrap, Server) when is_pid(Server) ->
 
435
    report_callback(Server, handle_trap, {Addr, Port, SnmpTrap}),
 
436
    ok.
 
437
 
 
438
handle_inform(Addr, Port, SnmpInform, Server) when is_pid(Server) ->
 
439
    report_callback(Server, handle_inform, {Addr, Port, SnmpInform}),
 
440
    ok.
 
441
 
 
442
 
 
443
handle_report(Addr, Port, SnmpReport, Server) when is_pid(Server) ->
 
444
    report_callback(Server, handle_inform, {Addr, Port, SnmpReport}),
 
445
    ok.
 
446
 
 
447
report_callback(Pid, Tag, Info) ->
 
448
    Pid ! {snmp_callback, Tag, Info}.