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

« back to all changes in this revision

Viewing changes to lib/snmp/test/snmp_log_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
%% Test:    ts:run(snmp, snmp_log_test, [batch]).
 
22
%% Test:    ts:run(snmp, snmp_log_test, log_to_txt2, [batch]).
 
23
%% 
 
24
%%----------------------------------------------------------------------
 
25
-module(snmp_log_test).
 
26
 
 
27
%%----------------------------------------------------------------------
 
28
%% Include files
 
29
%%----------------------------------------------------------------------
 
30
-include("test_server.hrl").
 
31
-include("snmp_test_lib.hrl").
 
32
-define(SNMP_USE_V3, true).
 
33
-include_lib("snmp/include/snmp_types.hrl").
 
34
-include_lib("kernel/include/file.hrl").
 
35
 
 
36
 
 
37
%%----------------------------------------------------------------------
 
38
%% External exports
 
39
%%----------------------------------------------------------------------
 
40
-export([
 
41
         init_per_testcase/2, fin_per_testcase/2,
 
42
 
 
43
         all/1, 
 
44
         open_and_close/1,
 
45
         open_write_and_close/1,
 
46
         log_to_io1/1,
 
47
         log_to_io2/1,
 
48
         log_to_txt1/1,
 
49
         log_to_txt2/1
 
50
        ]).
 
51
 
 
52
%%----------------------------------------------------------------------
 
53
%% Internal exports
 
54
%%----------------------------------------------------------------------
 
55
-export([
 
56
         log_writer_main/5, 
 
57
         log_reader_main/1
 
58
        ]).
 
59
 
 
60
%%----------------------------------------------------------------------
 
61
%% Macros
 
62
%%----------------------------------------------------------------------
 
63
 
 
64
%%----------------------------------------------------------------------
 
65
%% Records
 
66
%%----------------------------------------------------------------------
 
67
 
 
68
%%======================================================================
 
69
%% External functions
 
70
%%======================================================================
 
71
 
 
72
init_per_testcase(Case, Config) when list(Config) ->
 
73
    Dir        = ?config(priv_dir, Config),
 
74
    LogTestDir = join(Dir,        ?MODULE),
 
75
    CaseDir    = join(LogTestDir, Case),
 
76
    case file:make_dir(LogTestDir) of
 
77
        ok ->
 
78
            ok;
 
79
        {error, eexist} ->
 
80
            ok;
 
81
        Error ->
 
82
            ?FAIL({failed_creating_subsuite_top_dir, Error})
 
83
    end,
 
84
    ?line ok = file:make_dir(CaseDir),
 
85
    Dog = ?WD_START(?MINS(5)),
 
86
    [{log_dir, CaseDir}, {watchdog, Dog}|Config].
 
87
 
 
88
fin_per_testcase(_Case, Config) when list(Config) ->
 
89
    %% Leave the dirs created above (enable debugging of the test case(s))
 
90
    Dog = ?config(watchdog, Config),
 
91
    ?WD_STOP(Dog),
 
92
    lists:keydelete(watchdog, 1, Config).
 
93
 
 
94
 
 
95
%%======================================================================
 
96
%% Test case definitions
 
97
%%======================================================================
 
98
%% ?SKIP(not_yet_implemented).
 
99
all(suite) ->
 
100
    [
 
101
     open_and_close,
 
102
     open_write_and_close,
 
103
     log_to_io1,
 
104
     log_to_io2,
 
105
     log_to_txt1,
 
106
     log_to_txt2
 
107
    ].
 
108
 
 
109
 
 
110
%%======================================================================
 
111
%% Test functions
 
112
%%======================================================================
 
113
 
 
114
open_and_close(suite) -> [];
 
115
open_and_close(Config) when list(Config) ->
 
116
    p(open_and_close),
 
117
    put(sname,open_and_close),
 
118
    put(verbosity,trace),
 
119
    Dir    = ?config(log_dir, Config),
 
120
    Name   = "snmp_test",
 
121
    File   = join(Dir, "snmp_test.log"),
 
122
    Size   = {1024, 10},
 
123
    Repair = true,
 
124
    ?line {ok, Log} = snmp_log:create(Name, File, Size, Repair),
 
125
    ?line ok = snmp_log:sync(Log),
 
126
    ?line {ok, Info} = snmp_log:info(Log),
 
127
    display_info(Info),
 
128
    ?line ok = snmp_log:close(Log).
 
129
    
 
130
 
 
131
%%======================================================================
 
132
 
 
133
open_write_and_close(suite) -> [];
 
134
open_write_and_close(Config) when list(Config) ->
 
135
    p(open_write_and_close),
 
136
    put(sname,open_write_and_close),
 
137
    put(verbosity,trace),
 
138
    ?DBG("open_write_and_close -> start", []),
 
139
    Dir    = ?config(log_dir, Config),
 
140
    Name   = "snmp_test",
 
141
    File   = join(Dir, "snmp_test.log"),
 
142
    Size   = {1024, 10},
 
143
    Repair = true,
 
144
    ?DBG("open_write_and_close -> create log", []),
 
145
    ?line {ok, Log} = snmp_log:create(Name, File, Size, Repair),
 
146
 
 
147
    Vsn       = 'version-2',
 
148
    Community = "all-rights",
 
149
 
 
150
    ?DBG("open_write_and_close -> create messages to log", []),
 
151
    %% A request
 
152
    ?line Req = get_next_request(Vsn, Community, [1,1], 1, 235779012),
 
153
 
 
154
    %% A reply
 
155
    ?line Rep = get_response(Vsn, Community, 
 
156
                             [1,3,6,1,2,1,1,1,0], 'OCTET STRING',
 
157
                             "Erlang SNMP agent", 1, 235779012),
 
158
    
 
159
    %% Create a list of messages to log:
 
160
    Msgs = lists:flatten(lists:duplicate(1002,[Req,Rep])),
 
161
 
 
162
    %% And now log them:
 
163
    ?DBG("open_write_and_close -> log ~p messages, ~p bytes", 
 
164
        [length(Msgs), size(list_to_binary(Msgs))]),
 
165
    Addr = ?LOCALHOST(),
 
166
    Port = 162,
 
167
    Logger = fun(Packet) ->
 
168
                     ?line ok = snmp_log:log(Log, Packet, Addr, Port)
 
169
             end,
 
170
    lists:foreach(Logger, Msgs),
 
171
    check_notify(),
 
172
    
 
173
    ?DBG("open_write_and_close -> display info", []),
 
174
    ?line {ok, Info} = snmp_log:info(Log),
 
175
    display_info(Info),
 
176
 
 
177
    ?DBG("open_write_and_close -> close log", []),
 
178
    ?line ok = snmp_log:close(Log),
 
179
 
 
180
    ?DBG("open_write_and_close -> done", []),
 
181
    ok.
 
182
    
 
183
 
 
184
 
 
185
%%======================================================================
 
186
 
 
187
log_to_io1(suite) -> [];
 
188
log_to_io1(doc) -> "Log to io from the same process that opened "
 
189
                       "and wrote the log";
 
190
log_to_io1(Config) when list(Config) ->
 
191
    p(log_to_io1),
 
192
    put(sname,l2i1),
 
193
    put(verbosity,trace),
 
194
    ?DBG("log_to_io1 -> start", []),
 
195
    Dir    = ?config(log_dir, Config),
 
196
    Name   = "snmp_test_l2i1",
 
197
    File   = join(Dir, "snmp_test_l2i1.log"),
 
198
    Size   = {1024, 10},
 
199
    Repair = true,
 
200
    ?DBG("log_to_io1 -> create log", []),
 
201
    ?line {ok, Log} = snmp_log:create(Name, File, Size, Repair),
 
202
 
 
203
    ?DBG("log_to_io1 -> create messages to log", []),
 
204
    Msgs = messages(),
 
205
 
 
206
    ?DBG("log_to_io1 -> create logger funs", []),
 
207
    Addr = ?LOCALHOST(),
 
208
    Port = 162,
 
209
    Logger = fun(Packet) ->
 
210
                     ?line ok = snmp_log:log(Log, Packet, Addr, Port)
 
211
             end,
 
212
    BatchLogger = fun(Time) ->
 
213
                          lists:foreach(Logger, Msgs),
 
214
                          ?SLEEP(Time),
 
215
                          ok
 
216
                  end,
 
217
    To = lists:duplicate(100, 100),
 
218
 
 
219
    ?DBG("log_to_io1 -> log the messages", []),
 
220
    lists:foreach(BatchLogger, To),
 
221
 
 
222
    ?DBG("log_to_io1 -> display info", []),
 
223
    ?line {ok, Info} = snmp_log:info(Log),
 
224
    display_info(Info),
 
225
 
 
226
    ?DBG("log_to_io1 -> do the convert to io (stdout)", []),
 
227
    ? line ok = snmp_log:log_to_io(Log, File, Dir, []),
 
228
 
 
229
    ?DBG("log_to_io1 -> close log", []),
 
230
    ?line ok = snmp_log:close(Log),
 
231
 
 
232
    ?DBG("log_to_io1 -> done", []),
 
233
    ok.
 
234
 
 
235
 
 
236
%%======================================================================
 
237
%% Starta en logger-process som med ett visst intervall loggar
 
238
%% meddelanden. Starta en reader-process som vid ett viss tillf�lle
 
239
%% l�ser fr�n loggen.
 
240
 
 
241
log_to_io2(suite) -> [];
 
242
log_to_io2(doc) -> "Log to io from a different process than which "
 
243
                       "opened and wrote the log";
 
244
log_to_io2(Config) when list(Config) ->
 
245
    process_flag(trap_exit, true),
 
246
    p(log_to_io2),
 
247
    put(sname, l2i2),
 
248
    put(verbosity,trace),
 
249
    ?DBG("log_to_io2 -> start", []),
 
250
    Dir    = ?config(log_dir, Config),
 
251
    Name   = "snmp_test_l2i2",
 
252
    File   = join(Dir, "snmp_test_l2i2.log"),
 
253
    Size   = {1024, 10},
 
254
    Repair = true,
 
255
    
 
256
    ?DBG("log_to_io2 -> create log writer process", []),
 
257
    ?line {ok, Log, Logger} = log_writer_start(Name, File, Size, Repair),
 
258
 
 
259
    ?DBG("log_to_io2 -> create log reader process", []),
 
260
    ?line {ok, Reader} = log_reader_start(),
 
261
 
 
262
    ?DBG("log_to_io2 -> wait some time", []),
 
263
    ?SLEEP(5000),
 
264
 
 
265
    ?DBG("log_to_io2 -> display log info", []),
 
266
    ?line log_writer_info(Logger),
 
267
 
 
268
    ?DBG("log_to_io2 -> instruct the log writer to sleep some", []),
 
269
    ?line ok = log_writer_sleep(Logger, 5000),
 
270
 
 
271
    ?DBG("log_to_io2 -> instruct the log reader to log to io", []),
 
272
    Res = 
 
273
        log_reader_log_to(Reader, 
 
274
                          fun() -> 
 
275
                                  I = disk_log:info(Log),
 
276
                                  R = snmp_log:log_to_io(Log, File, Dir, []),
 
277
                                  {R, I}
 
278
                          end),
 
279
 
 
280
    case Res of
 
281
        {ok, Info} ->
 
282
            ?DBG("log_to_io2 -> ~n   Info: ~p", [Info]),
 
283
            ok;
 
284
        {Error, Info} ->
 
285
            ?DBG("log_to_io2 -> log to io failed: "
 
286
                 "~n   Error: ~p"
 
287
                 "~n   Info:  ~p", [Error, Info]),
 
288
            ?line ?FAIL({log_lo_io_failed, Error, Info})
 
289
    end,
 
290
 
 
291
    ?DBG("log_to_io2 -> instruct the log writer to stop", []),
 
292
    ?line log_writer_stop(Logger),
 
293
 
 
294
    ?DBG("log_to_io2 -> instruct the log reader to stop", []),
 
295
    ?line log_reader_stop(Reader),
 
296
 
 
297
    ?DBG("log_to_io2 -> done", []),
 
298
    ok.
 
299
 
 
300
 
 
301
%%======================================================================
 
302
 
 
303
log_to_txt1(suite) -> [];
 
304
log_to_txt1(Config) when list(Config) ->
 
305
    p(log_to_txt1),
 
306
    put(sname,l2t1),
 
307
    put(verbosity,trace),
 
308
    ?DBG("log_to_txt1 -> start", []),
 
309
    Dir    = ?config(log_dir, Config),
 
310
    Name   = "snmp_test_l2t1",
 
311
    File   = join(Dir, "snmp_test_l2t1.log"),
 
312
    Size   = {10240, 10},
 
313
    Repair = true,
 
314
    ?DBG("log_to_txt1 -> create log", []),
 
315
    ?line {ok, Log} = snmp_log:create(Name, File, Size, Repair),
 
316
 
 
317
    ?DBG("log_to_txt1 -> create messages to log", []),
 
318
    Msgs = messages(),
 
319
 
 
320
    ?DBG("log_to_txt1 -> create logger funs", []),
 
321
    Addr = ?LOCALHOST(),
 
322
    Port = 162,
 
323
    Logger = fun(Packet) ->
 
324
                     ?line ok = snmp_log:log(Log, Packet, Addr, Port)
 
325
             end,
 
326
    BatchLogger = fun(Time) ->
 
327
                          lists:foreach(Logger, Msgs),
 
328
                          ?SLEEP(Time),
 
329
                          ok
 
330
                  end,
 
331
    To = lists:duplicate(20, 5000),
 
332
 
 
333
    ?DBG("log_to_txt1 -> log the messages", []),
 
334
    Start = calendar:local_time(),
 
335
    lists:foreach(BatchLogger, To),
 
336
    Stop  = calendar:local_time(),
 
337
 
 
338
    ?DBG("log_to_txt1 -> display info", []),
 
339
    ?line {ok, Info} = snmp_log:info(Log),
 
340
    display_info(Info),
 
341
 
 
342
    Out1 = join(Dir, "snmp_text-1.txt"),
 
343
    ?DBG("log_to_txt1 -> do the convert to a text file when"
 
344
        "~n   Out1: ~p", [Out1]),
 
345
    ?line ok = snmp:log_to_txt(Dir, [], Out1, Log, File),
 
346
 
 
347
    ?line {ok, #file_info{size = Size1}} = file:read_file_info(Out1),
 
348
    ?DBG("log_to_txt1 -> text file size: ~p", [Size1]),
 
349
    validate_size(Size1),
 
350
 
 
351
    Out2 = join(Dir, "snmp_text-2.txt"),
 
352
    ?DBG("log_to_txt1 -> do the convert to a text file when"
 
353
        "~n   Start: ~p"
 
354
        "~n   Stop:  ~p"
 
355
        "~n   Out2:  ~p", [Start, Stop, Out2]),
 
356
    ?line ok = snmp:log_to_txt(Dir, [], Out2, Log, File, Start, Stop),
 
357
 
 
358
    ?line {ok, #file_info{size = Size2}} = file:read_file_info(Out2),
 
359
    ?DBG("log_to_txt1 -> text file size: ~p", [Size2]),
 
360
    validate_size(Size2, {le, Size1}),
 
361
 
 
362
    %% Calculate new start / stop times...
 
363
    GStart = calendar:datetime_to_gregorian_seconds(Start),
 
364
    ?DBG("log_to_txt1 -> GStart: ~p", [GStart]),
 
365
    GStop  = calendar:datetime_to_gregorian_seconds(Stop),
 
366
    ?DBG("log_to_txt1 -> GStop: ~p", [GStop]),
 
367
    Diff4 = (GStop - GStart) div 4,
 
368
    ?DBG("log_to_txt1 -> Diff4: ~p", [Diff4]),
 
369
    GStart2 = GStart + Diff4,
 
370
    GStop2  = GStop - Diff4,
 
371
    if 
 
372
        GStop2 > GStart2 ->
 
373
            ok;
 
374
        true ->
 
375
            ?FAIL({date_calc_failure, GStart2, GStop2})
 
376
    end,
 
377
    
 
378
    Start2 = calendar:gregorian_seconds_to_datetime(GStart2),
 
379
    Stop2  = calendar:gregorian_seconds_to_datetime(GStop2),
 
380
    
 
381
    Out3 = join(Dir, "snmp_text-3.txt"),
 
382
    ?DBG("log_to_txt1 -> do the convert to a text file when"
 
383
        "~n   Start2: ~p"
 
384
        "~n   Stop2:  ~p"
 
385
        "~n   Out3:   ~p", [Start2, Stop2, Out3]),
 
386
    ?line ok = snmp:log_to_txt(Dir, [], Out3, Log, File, Start2, Stop2),
 
387
 
 
388
    ?line {ok, #file_info{size = Size3}} = file:read_file_info(Out3),
 
389
    ?DBG("log_to_txt1 -> text file size: ~p", [Size3]),
 
390
    validate_size(Size3, {l, Size1}),    
 
391
 
 
392
    ?DBG("log_to_txt1 -> close log", []),
 
393
    ?line ok = snmp_log:close(Log),
 
394
 
 
395
    ?DBG("log_to_txt1 -> done", []),
 
396
    ok.
 
397
 
 
398
 
 
399
%%======================================================================
 
400
%% Starta en logger-process som med ett visst intervall loggar
 
401
%% meddelanden. Starta en reader-process som vid ett viss tillf�lle
 
402
%% l�ser fr�n loggen.
 
403
%%
 
404
%% Test: ts:run(snmp, snmp_log_test, log_to_txt2, [batch]).
 
405
 
 
406
log_to_txt2(suite) -> [];
 
407
log_to_txt2(doc) -> "Log to txt file from a different process than which "
 
408
                       "opened and wrote the log";
 
409
log_to_txt2(Config) when list(Config) ->
 
410
    process_flag(trap_exit, true),
 
411
    p(log_to_txt2),
 
412
    put(sname,l2t2),
 
413
    put(verbosity,trace),
 
414
    ?DBG("log_to_txt2 -> start", []),
 
415
    Dir     = ?config(log_dir, Config),
 
416
    Name    = "snmp_test_l2t2",
 
417
    LogFile = join(Dir, "snmp_test_l2t2.log"),
 
418
    TxtFile = join(Dir, "snmp_test_l2t2.txt"),
 
419
    Meg     = 1024*1024,
 
420
    Size    = {10*Meg, 10},
 
421
    Repair  = true,
 
422
 
 
423
    StdMibDir = filename:join(code:priv_dir(snmp), "mibs") ++ "/",
 
424
    Mibs = [join(StdMibDir, "SNMPv2-MIB")],
 
425
 
 
426
    ?DBG("log_to_txt2 -> create log writer process", []),
 
427
    ?line {ok, Log, Logger} = log_writer_start(Name, LogFile, Size, Repair),
 
428
 
 
429
    ?DBG("log_to_txt2 -> create log reader process", []),
 
430
    ?line {ok, Reader} = log_reader_start(),
 
431
 
 
432
    ?DBG("log_to_txt2 -> wait some time", []),
 
433
    ?SLEEP(5000),
 
434
 
 
435
    ?DBG("log_to_txt2 -> display log info", []),
 
436
    ?line log_writer_info(Logger),
 
437
 
 
438
    ?DBG("log_to_txt2 -> instruct the log writer to sleep some", []),
 
439
    ?line ok = log_writer_sleep(Logger, 5000),
 
440
 
 
441
    ?DBG("log_to_txt2 -> instruct the log reader to log to txt", []),
 
442
    Res = 
 
443
        log_reader_log_to(Reader, 
 
444
                          fun() -> 
 
445
                                  I = disk_log:info(Log),
 
446
                                  T1 = t(), 
 
447
                                  R = snmp_log:log_to_txt(Log, LogFile, Dir, 
 
448
                                                          Mibs, TxtFile),
 
449
                                  T2 = t(), 
 
450
                                  io:format(user, 
 
451
                                            "Time converting file: ~w ms~n",
 
452
                                            [T2 - T1]),
 
453
                                  {R, I}
 
454
                          end),
 
455
 
 
456
    case Res of
 
457
        {ok, Info} ->
 
458
            ?DBG("log_to_txt2 -> ~n   Info: ~p", [Info]),
 
459
            ?line {ok, #file_info{size = FileSize}} = 
 
460
                file:read_file_info(TxtFile),
 
461
            ?DBG("log_to_txt2 -> text file size: ~p", [FileSize]),
 
462
            validate_size(FileSize);
 
463
        {Error, Info} ->
 
464
            ?DBG("log_to_txt2 -> log to txt failed: "
 
465
                 "~n   Error: ~p"
 
466
                 "~n   Info:  ~p", [Error, Info]),
 
467
            ?line ?FAIL({log_lo_txt_failed, Error, Info})
 
468
    end,
 
469
 
 
470
    ?DBG("log_to_txt2 -> instruct the log writer to stop", []),
 
471
    ?line log_writer_stop(Logger),
 
472
 
 
473
    ?DBG("log_to_txt2 -> instruct the log reader to stop", []),
 
474
    ?line log_reader_stop(Reader),
 
475
 
 
476
    ?DBG("log_to_txt2 -> done", []),
 
477
    ok.
 
478
 
 
479
 
 
480
validate_size(0) ->
 
481
    ?FAIL(invalid_size);
 
482
validate_size(_) ->
 
483
    ok.
 
484
 
 
485
validate_size(0, _) ->
 
486
    ?FAIL(invalid_size);
 
487
validate_size(A, {le, B}) when A =< B ->
 
488
    ok;
 
489
validate_size(A, {l, B}) when A < B ->
 
490
    ok;
 
491
validate_size(A, B) ->
 
492
    ?FAIL({invalid_size, A, B}).
 
493
 
 
494
    
 
495
%%======================================================================
 
496
%% Internal functions
 
497
%%======================================================================
 
498
 
 
499
log_writer_start(Name, File, Size, Repair) ->
 
500
    Pid = spawn_link(?MODULE, log_writer_main, 
 
501
                     [Name, File, Size, Repair, self()]),
 
502
    receive
 
503
        {log, Log, Pid} ->
 
504
            {ok, Log, Pid};
 
505
        {'EXIT', Pid, Reason} ->
 
506
            {error, Reason}
 
507
    after 60000 ->
 
508
            Msg  = receive Any -> Any after 0 -> nothing end,
 
509
            Info = (catch process_info(Pid)),
 
510
            exit({failed_starting_writer, timeout, Msg, Info})
 
511
    end.
 
512
 
 
513
log_writer_stop(Pid) ->
 
514
    Pid ! {stop, self()},
 
515
    T1 = t(),
 
516
    receive
 
517
        {'EXIT', Pid, normal} ->
 
518
            T2 = t(),
 
519
            ?DBG("it took ~w ms to stop the writer", [T2 - T1]),
 
520
            ok
 
521
    after 60000 ->
 
522
            Msg  = receive Any -> Any after 0 -> nothing end,
 
523
            Info = (catch process_info(Pid)),
 
524
            exit({failed_stopping_writer, timeout, Msg, Info})
 
525
    end.
 
526
 
 
527
log_writer_info(Pid) ->
 
528
    Pid ! {info, self()}.
 
529
 
 
530
log_writer_sleep(Pid, Time) ->
 
531
    Pid ! {sleep, Time, self()},
 
532
    T1 = t(),
 
533
    receive 
 
534
        {sleeping, Pid} ->
 
535
            T2 = t(),
 
536
            ?DBG("it took ~w ms to put the writer to sleep", [T2 - T1]),
 
537
            ok;
 
538
        {'EXIT', Pid, Reason} ->
 
539
            {error, Reason}
 
540
    after 60000 ->
 
541
            Msg  = receive Any -> Any after 0 -> nothing end,
 
542
            Info = (catch process_info(Pid)),
 
543
            exit({failed_put_writer_to_sleep, timeout, Msg, Info})
 
544
    end.
 
545
 
 
546
log_writer_main(Name, File, Size, Repair, P) ->
 
547
    process_flag(trap_exit, true),
 
548
    %% put(sname,log_writer),
 
549
    %% put(verbosity,trace),
 
550
    {ok, Log} = snmp_log:create(Name, File, Size, Repair),
 
551
    P ! {log, Log, self()},
 
552
    Msgs   = lists:flatten(lists:duplicate(10, messages())),
 
553
    Addr   = ?LOCALHOST(),
 
554
    Port   = 162,
 
555
    Logger =  fun(Packet) ->
 
556
                     ?line ok = snmp_log:log(Log, Packet, Addr, Port)
 
557
              end,
 
558
    BatchLogger = fun(Time) ->
 
559
                          lists:foreach(Logger, Msgs),
 
560
                          ?SLEEP(Time),
 
561
                          ok
 
562
                  end,
 
563
    log_writer(Log, BatchLogger, P).
 
564
 
 
565
log_writer(Log, Fun, P) ->
 
566
    lp("entry"),
 
567
    receive 
 
568
        {stop, P} ->
 
569
            lp("received stop request"),
 
570
            ok = snmp_log:close(Log),
 
571
            exit(normal);
 
572
        {info, P} ->
 
573
            lp("received info request"),
 
574
            {ok, Info} = snmp_log:info(Log),
 
575
            display_info(Info),
 
576
            log_writer(Log, Fun, P);
 
577
        {sleep, Time, P} ->
 
578
            lp("received sleep (~w) request", [Time]),
 
579
            P ! {sleeping, self()},
 
580
            ?SLEEP(Time),
 
581
            lp("done sleeping"),
 
582
            log_writer(Log, Fun, P);
 
583
        ELSE ->
 
584
            io:format("ERROR:logger - received unknown message: "
 
585
                      "~n   ~p~n", [ELSE]),
 
586
            log_writer(Log, Fun, P)
 
587
    after 1000 ->
 
588
            lp("log some messages"),
 
589
            To = lists:duplicate(100, 100),
 
590
            lists:foreach(Fun, To),
 
591
            log_writer(Log, Fun, P)
 
592
    end.
 
593
 
 
594
lp(F) ->
 
595
    lp(F, []).
 
596
 
 
597
lp(F, A) ->
 
598
    io:format(user,"writer [~w] " ++ F ++ "~n", [self()|A]).
 
599
 
 
600
%% --
 
601
 
 
602
log_reader_start() ->
 
603
    Pid = spawn_link(?MODULE, log_reader_main, [self()]),
 
604
    T1 = t(),
 
605
    receive 
 
606
        {started, Pid} ->
 
607
            T2 = t(),
 
608
            ?DBG("it took ~w ms to start the reader", [T2 - T1]),
 
609
            {ok, Pid};
 
610
        {'EXIT', Pid, Reason} ->
 
611
            {error, Reason}
 
612
    after 1000 ->
 
613
            error
 
614
    end.
 
615
 
 
616
log_reader_stop(Pid) ->
 
617
    Pid ! {stop, self()},
 
618
    T1 = t(),
 
619
    receive
 
620
        {'EXIT', Pid, normal} ->
 
621
            T2 = t(),
 
622
            ?DBG("it took ~w ms to put the reader to eleep", [T2 - T1]),
 
623
            ok
 
624
    after 1000 ->
 
625
            Msg = receive Any -> Any after 0 -> nothing end,
 
626
            exit({failed_stopping_reader, timeout, Msg})
 
627
    end.
 
628
 
 
629
log_reader_log_to(Pid, LogToFun) when function(LogToFun) ->
 
630
    Pid ! {log_to, LogToFun, self()},
 
631
    receive
 
632
        {log_to_reply, Res, Pid} ->
 
633
            Res
 
634
    end.
 
635
 
 
636
log_reader_main(P) ->
 
637
    put(sname,log_reader),
 
638
    put(verbosity,trace),
 
639
    P ! {started, self()},
 
640
    log_reader(P).
 
641
 
 
642
log_reader(P) ->
 
643
    rp("entry"),
 
644
    receive 
 
645
        {stop, P} ->
 
646
            rp("received stop request"),
 
647
            exit(normal);
 
648
        {log_to, F, P} ->
 
649
            rp("received log_to request"),
 
650
            Res = F(),
 
651
            rp("done with log_to - sending reply"),
 
652
            P ! {log_to_reply, Res, self()}, 
 
653
            log_reader(P);
 
654
        ELSE ->
 
655
            io:format("ERROR:reader - received unknown message: "
 
656
                      "~n   ~p~n", [ELSE]),
 
657
            log_reader(P)
 
658
    end.
 
659
    
 
660
rp(F) ->
 
661
    rp(F, []).
 
662
 
 
663
rp(F, A) ->
 
664
    io:format(user, "reader [~w] " ++ F ++ "~n", [self()|A]).
 
665
 
 
666
 
 
667
%%======================================================================
 
668
 
 
669
check_notify() ->
 
670
    receive
 
671
        {disk_log, Node, LogName, Info} ->
 
672
            io:format("disk_log notify: "
 
673
                      "~n   Node:    ~p"
 
674
                      "~n   LogName: ~s"
 
675
                      "~n   Info:    ~p"
 
676
                      "~n", [Node, LogName, Info]),
 
677
            check_notify()
 
678
    after 1000 ->
 
679
            done
 
680
    end.
 
681
 
 
682
 
 
683
messages() ->
 
684
    [get_next_request('version-1', "all-rights", 
 
685
                      [1,13], 1, 1101),
 
686
     get_response('version-1', "all-rights", 
 
687
                  [1,3,6,1,2,1,1,1,0], 
 
688
                  'OCTET STRING', "Erlang SNMP agent",
 
689
                  1, 1101),
 
690
     get_request('version-1', "all-rights", 
 
691
                 [1,3,6,1,2,1,1,1,0], 1, 1102),
 
692
     get_response('version-1', "all-rights", 
 
693
                  [1,3,6,1,2,1,1,1,0], 
 
694
                  'OCTET STRING', "Erlang SNMP agent",
 
695
                  1, 1102),
 
696
     set_request('version-1', "all-rights", 
 
697
                 [1,3,6,1,2,1,1,6,0], 
 
698
                 'OCTET STRING', "new_value",
 
699
                 1, 1003),
 
700
     get_response('version-1', "all-rights", 
 
701
                  [1,3,6,1,2,1,1,6,0], 
 
702
                  'OCTET STRING', "new_value",
 
703
                  1, 1103),
 
704
     get_bulk_request("all-rights", 1104),
 
705
     bulk_get_response('version-1', "all-rights", 
 
706
                       [48,29,6,8,43,6,1,2,1,1,1,0,4,17,69,114,108,97,
 
707
                        110,103,32,83,78,77,80,32,97,103,101,110,116,
 
708
                        48,7,6,3,43,7,1,130,0], 1104),
 
709
     inform_request("all-rights", 1105),
 
710
     get_response('version-1', "all-rights", 
 
711
                  [{[1,3,6,1,2,1,1,3,0],
 
712
                    'TimeTicks',
 
713
                    4046,
 
714
                    1},
 
715
                   {[1,3,6,1,6,3,1,1,4,1,0],
 
716
                    'OBJECT IDENTIFIER',
 
717
                    [1,3,6,1,2,1,1,0,1],2}],
 
718
                  1105),
 
719
     snmpv2_trap("all-rights", 1106),
 
720
     trap("all-rights")].
 
721
 
 
722
 
 
723
get_request(Vsn, Community, Oid, OrgIdx, ReqId) ->
 
724
    Varbind = #varbind{oid          = Oid, 
 
725
                       variabletype = 'NULL',
 
726
                       value        = 'NULL',
 
727
                       org_index    = OrgIdx},
 
728
    Pdu     = #pdu{type         = 'get-response',
 
729
                   request_id   = ReqId, 
 
730
                   error_status = noError, 
 
731
                   error_index  = 0,
 
732
                   varbinds     = [Varbind]},
 
733
    enc_message(Vsn, Community, Pdu).
 
734
 
 
735
get_next_request(Vsn, Community, Oid, OrgIdx, ReqId) ->
 
736
    Varbind = #varbind{oid          = Oid, 
 
737
                       variabletype = 'NULL',
 
738
                       value        = 'NULL',
 
739
                       org_index    = OrgIdx},
 
740
    Pdu     = #pdu{type         = 'get-next-request',
 
741
                   request_id   = ReqId, 
 
742
                   error_status = noError, 
 
743
                   error_index  = 0,
 
744
                   varbinds     = [Varbind]},
 
745
    enc_message(Vsn, Community, Pdu).
 
746
 
 
747
bulk_get_response(Vsn, Community, Bulk, ReqId) ->
 
748
    Pdu     = #pdu{type         = 'get-response',
 
749
                   request_id   = ReqId,
 
750
                   error_status = noError,
 
751
                   error_index  = 0,
 
752
                   varbinds     = Bulk},
 
753
    enc_message(Vsn, Community, Pdu).
 
754
    
 
755
get_response(Vsn, Community, VarbindData, ReqId) ->
 
756
    Varbinds = varbinds(VarbindData, []),
 
757
    Pdu     = #pdu{type         = 'get-response',
 
758
                   request_id   = ReqId,
 
759
                   error_status = noError,
 
760
                   error_index  = 0,
 
761
                   varbinds     = Varbinds},
 
762
    enc_message(Vsn, Community, Pdu).
 
763
    
 
764
get_response(Vsn, Community, Oid, Type, Value, OrgIdx, ReqId) ->
 
765
    Varbind = #varbind{oid          = Oid, 
 
766
                       variabletype = Type,
 
767
                       value        = Value,
 
768
                       org_index    = OrgIdx},
 
769
    Pdu     = #pdu{type         = 'get-response',
 
770
                   request_id   = ReqId,
 
771
                   error_status = noError,
 
772
                   error_index  = 0,
 
773
                   varbinds     = [Varbind]},
 
774
    enc_message(Vsn, Community, Pdu).
 
775
 
 
776
set_request(Vsn, Community, Oid, Type, Value, OrgIdx, ReqId) ->
 
777
    Varbind = #varbind{oid          = Oid, 
 
778
                       variabletype = Type,
 
779
                       value        = Value,
 
780
                       org_index    = OrgIdx},
 
781
    Pdu     = #pdu{type         = 'set-request',
 
782
                   request_id   = ReqId,
 
783
                   error_status = noError,
 
784
                   error_index  = 0,
 
785
                   varbinds     = [Varbind]},
 
786
    enc_message(Vsn, Community, Pdu).
 
787
 
 
788
 
 
789
get_bulk_request(Community, ReqId) ->
 
790
    Varbinds = [#varbind{oid          = [1,3,6,1,2,1,1,1],
 
791
                         variabletype = 'NULL',
 
792
                         value        = 'NULL',
 
793
                         org_index    = 1},
 
794
                #varbind{oid          = [1,3,7,1],
 
795
                         variabletype = 'NULL',
 
796
                         value        = 'NULL',
 
797
                         org_index    = 2}],
 
798
    Pdu = #pdu{type         = 'get-bulk-request',
 
799
               request_id   = ReqId,
 
800
               error_status = 1,
 
801
               error_index  = 1,
 
802
               varbinds     = Varbinds},
 
803
    enc_message('version-2', Community, Pdu).
 
804
 
 
805
inform_request(Community, ReqId) ->
 
806
    Varbinds = [#varbind{oid          = [1,3,6,1,2,1,1,3,0],
 
807
                         variabletype = 'TimeTicks',
 
808
                         value        = 4046,
 
809
                         org_index    = 1},
 
810
                #varbind{oid          = [1,3,6,1,6,3,1,1,4,1,0],
 
811
                         variabletype = 'OBJECT IDENTIFIER',
 
812
                         value        = [1,3,6,1,2,1,1,0,1],
 
813
                         org_index    = 2}],
 
814
    Pdu = #pdu{type         = 'inform-request',
 
815
               request_id   = ReqId,
 
816
               error_status = noError,
 
817
               error_index  = 0,
 
818
               varbinds     = Varbinds},
 
819
    enc_message('version-2', Community, Pdu).
 
820
 
 
821
snmpv2_trap(Community, ReqId) ->
 
822
    Varbinds = [#varbind{oid          = [1,3,6,1,2,1,1,3,0],
 
823
                         variabletype = 'TimeTicks',
 
824
                         value        = 3945,
 
825
                         org_index    = 1},
 
826
                #varbind{oid          = [1,3,6,1,6,3,1,1,4,1,0],
 
827
                         variabletype = 'OBJECT IDENTIFIER',
 
828
                         value        = [1,3,6,1,2,1,11,1],
 
829
                         org_index    = 2}],
 
830
    Pdu = #pdu{type         = 'snmpv2-trap',
 
831
               request_id   = ReqId,
 
832
               error_status = noError,
 
833
               error_index  = 0,
 
834
               varbinds     = Varbinds},
 
835
    enc_message('version-2', Community, Pdu).
 
836
 
 
837
% report() ->
 
838
%     Varbind = #varbind{oid          = ?snmpUnknownPDUHandlers,
 
839
%                      variabletype = 'Counter32',
 
840
%                      value        = 111},
 
841
%     Pdu = #pdu{type         = report, 
 
842
%              request_id   = 991199,
 
843
%              error_status = noError, 
 
844
%              error_index  = 0,
 
845
%              varbinds     = [Varbind]},
 
846
%     enc_message('version-3', Community, Pdu).
 
847
 
 
848
trap(Community) ->
 
849
    Enterp    = [1,3,6,1,2,1,1],
 
850
    Oid       = [1,3,6,1,2,1,1,4,0],
 
851
    Type      = 'OCTET STRING',
 
852
    Value     = "{mbj,eklas}@erlang.ericsson.se",
 
853
    SysUpTime = 4379, 
 
854
    Spec      = 1,
 
855
    Generic   = 6, 
 
856
    AgentIp   = [127,0,0,1],
 
857
    trap(Community, Enterp, Oid, Type, Value, SysUpTime, 
 
858
         Spec, Generic, AgentIp, 1).
 
859
 
 
860
%% V1 trap
 
861
trap(Community, Enterp, Oid, Type, Value, SysUpTime, 
 
862
     Spec, Generic, AgentIp, OrgIdx) ->
 
863
    Varbind = #varbind{oid          = Oid, 
 
864
                       variabletype = Type, 
 
865
                       value        = Value,
 
866
                       org_index    = OrgIdx},
 
867
    Trap = #trappdu{enterprise    = Enterp,
 
868
                    agent_addr    = AgentIp,
 
869
                    generic_trap  = Generic,
 
870
                    specific_trap = Spec,
 
871
                    time_stamp    = SysUpTime,
 
872
                    varbinds      = [Varbind]},
 
873
    enc_message('version-1', Community, Trap).
 
874
 
 
875
varbinds([], Varbinds) ->
 
876
    lists:reverse(Varbinds);
 
877
varbinds([{Oid, Type, Value, Idx}|T], Acc) ->
 
878
    Varbind = #varbind{oid          = Oid, 
 
879
                       variabletype = Type, 
 
880
                       value        = Value,
 
881
                       org_index    = Idx},
 
882
    varbinds(T, [Varbind|Acc]).
 
883
 
 
884
% enc_message('version-3' = Vsn, Community, Pdu) ->
 
885
%     ScopedPDU = #scopedPdu{contextEngineID = ContextEngineID,
 
886
%                          contextName     = ContextName,
 
887
%                          data            = Pdu},
 
888
%     NUsmSecParams = 
 
889
%         UsmSecParams#usmSecurityParameters{msgAuthenticationParameters =
 
890
%                                            AuthParams},
 
891
%     SecBytes = snmp_pdus:enc_usm_security_parameters(NUsmSecParams),
 
892
%     V3Hdr = #v3_hdr{msgID = MsgID,
 
893
%                   msgMaxSize = AgentMS,
 
894
%                   msgFlags = snmp_misc:mk_msg_flags(Type, SecLevel),
 
895
%                   msgSecurityParameters = SecBytes
 
896
%                   msgSecurityModel = MsgSecurityModel},
 
897
%     Msg = #message{version = Vsn, vsn_hdr = V3Hdr, 
 
898
%                  data = ScopedPDUBytes},
 
899
%     snmp_pdus:enc_message_only(Message2);
 
900
 
 
901
enc_message(Vsn, Community, Pdu) ->
 
902
    PduBytes = snmp_pdus:enc_pdu(Pdu),
 
903
    Msg      = #message{version = Vsn,
 
904
                        vsn_hdr = Community,
 
905
                        data    = PduBytes},
 
906
    list_to_binary(snmp_pdus:enc_message_only(Msg)).
 
907
 
 
908
display_info(Info) ->
 
909
    {SinceOpened, SinceLastInfo} = get_info(no_overflows, Info, {-1,-1}),
 
910
    CurrentFile = get_info(current_file, Info, -1),
 
911
    NoItems = get_info(no_current_items, Info, -1),
 
912
    NoBytes = get_info(no_current_bytes, Info, -1),
 
913
    io:format(user, "Disk log info: "
 
914
              "~n   Number of filled since opened:    ~p"
 
915
              "~n   Number of filled since last info: ~p"
 
916
              "~n   Current file:                     ~p"
 
917
              "~n   Number of items in file:          ~p"
 
918
              "~n   Number of bytes in file:          ~p" 
 
919
              "~n", 
 
920
              [SinceOpened, SinceLastInfo, CurrentFile, NoItems, NoBytes]).
 
921
 
 
922
get_info(Key, Info, Def) ->
 
923
    case lists:keysearch(Key, 1, Info) of
 
924
        {value, {Key, Val}} ->
 
925
            Val;
 
926
        false ->
 
927
            Def
 
928
    end.
 
929
 
 
930
join(D, F) ->
 
931
    filename:join(D, F).
 
932
 
 
933
p(Case) ->
 
934
    io:format(user, "test case: ~w~n", [Case]).
 
935
 
 
936
%% Time in milli sec
 
937
t() ->
 
938
    {A,B,C} = erlang:now(),
 
939
    A*1000000000+B*1000+(C div 1000).