~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/snmp/test/snmp_log_test.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%% 
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 2003-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 2003-2010. All Rights Reserved.
 
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%% 
19
19
 
29
29
%%----------------------------------------------------------------------
30
30
%% Include files
31
31
%%----------------------------------------------------------------------
32
 
-include("test_server.hrl").
 
32
-include_lib("test_server/include/test_server.hrl").
33
33
-include("snmp_test_lib.hrl").
34
34
-define(SNMP_USE_V3, true).
35
35
-include_lib("snmp/include/snmp_types.hrl").
40
40
%% External exports
41
41
%%----------------------------------------------------------------------
42
42
-export([
43
 
         init_per_testcase/2, fin_per_testcase/2,
 
43
         init_per_testcase/2, end_per_testcase/2,
44
44
 
45
 
         all/1, 
 
45
        all/0,groups/0,init_per_group/2,end_per_group/2, 
46
46
         open_and_close/1,
47
 
         open_write_and_close/1,
 
47
        
 
48
         open_write_and_close1/1,
 
49
         open_write_and_close2/1,
 
50
         open_write_and_close3/1,
 
51
         open_write_and_close4/1,
 
52
        
48
53
         log_to_io1/1,
49
54
         log_to_io2/1,
 
55
        
50
56
         log_to_txt1/1,
51
 
         log_to_txt2/1
 
57
         log_to_txt2/1,
 
58
         log_to_txt3/1
52
59
        ]).
53
60
 
 
61
 
54
62
%%----------------------------------------------------------------------
55
63
%% Internal exports
56
64
%%----------------------------------------------------------------------
57
65
-export([
58
66
         log_writer_main/5, 
59
 
         log_reader_main/1
 
67
         log_reader_main/1,
 
68
         next_seqno/2
60
69
        ]).
61
70
 
 
71
 
62
72
%%----------------------------------------------------------------------
63
73
%% Macros
64
74
%%----------------------------------------------------------------------
87
97
    Dog = ?WD_START(?MINS(5)),
88
98
    [{log_dir, CaseDir}, {watchdog, Dog}|Config].
89
99
 
90
 
fin_per_testcase(_Case, Config) when is_list(Config) ->
 
100
end_per_testcase(_Case, Config) when is_list(Config) ->
91
101
    %% Leave the dirs created above (enable debugging of the test case(s))
92
102
    Dog = ?config(watchdog, Config),
93
103
    ?WD_STOP(Dog),
98
108
%% Test case definitions
99
109
%%======================================================================
100
110
%% ?SKIP(not_yet_implemented).
101
 
all(suite) ->
102
 
    [
103
 
     open_and_close,
104
 
     open_write_and_close,
105
 
     log_to_io1,
106
 
     log_to_io2,
107
 
     log_to_txt1,
108
 
     log_to_txt2
109
 
    ].
 
111
all() -> 
 
112
[open_and_close, {group, open_write_and_close},
 
113
 {group, log_to_io}, {group, log_to_txt}].
 
114
 
 
115
groups() -> 
 
116
    [{open_write_and_close, [],
 
117
  [open_write_and_close1, open_write_and_close2,
 
118
   open_write_and_close3, open_write_and_close4]},
 
119
 {log_to_io, [], [log_to_io1, log_to_io2]},
 
120
 {log_to_txt, [],
 
121
  [log_to_txt1, log_to_txt2, log_to_txt3]}].
 
122
 
 
123
init_per_group(_GroupName, Config) ->
 
124
        Config.
 
125
 
 
126
end_per_group(_GroupName, Config) ->
 
127
        Config.
 
128
 
 
129
 
 
130
 
 
131
 
 
132
 
 
133
 
 
134
 
110
135
 
111
136
 
112
137
%%======================================================================
132
157
 
133
158
%%======================================================================
134
159
 
135
 
open_write_and_close(suite) -> [];
136
 
open_write_and_close(Config) when is_list(Config) ->
137
 
    p(open_write_and_close),
138
 
    put(sname,open_write_and_close),
139
 
    put(verbosity,trace),
140
 
    ?DBG("open_write_and_close -> start", []),
 
160
open_write_and_close1(suite) -> 
 
161
    [];
 
162
open_write_and_close1(doc) -> 
 
163
    "Open a plain (no sequence-numbering) log file";
 
164
open_write_and_close1(Config) when is_list(Config) ->
 
165
    p(open_write_and_close1),
 
166
    put(sname,open_write_and_close1),
 
167
    put(verbosity,trace),
 
168
    ?DBG("open_write_and_close1 -> start", []),
 
169
 
 
170
    SeqNoGen = none, 
 
171
    ?line ok = open_write_and_close(SeqNoGen, Config),
 
172
 
 
173
    ?DBG("open_write_and_close1 -> done", []),
 
174
    ok.
 
175
    
 
176
 
 
177
%%======================================================================
 
178
 
 
179
open_write_and_close2(suite) -> 
 
180
    [];
 
181
open_write_and_close2(doc) -> 
 
182
    "Open a log file with sequence-numbering explicitly disabled";
 
183
open_write_and_close2(Config) when is_list(Config) ->
 
184
    p(open_write_and_close2),
 
185
    put(sname,open_write_and_close2),
 
186
    put(verbosity,trace),
 
187
    ?DBG("open_write_and_close2 -> start", []),
 
188
 
 
189
    SeqNoGen = disabled, 
 
190
    ?line ok = open_write_and_close(SeqNoGen, Config),
 
191
 
 
192
    ?DBG("open_write_and_close2 -> done", []),
 
193
    ok.
 
194
 
 
195
 
 
196
%%======================================================================
 
197
 
 
198
open_write_and_close3(suite) -> 
 
199
    [];
 
200
open_write_and_close3(doc) -> 
 
201
    "Open a log file with sequence-numbering using MFA";
 
202
open_write_and_close3(Config) when is_list(Config) ->
 
203
    p(open_write_and_close3),
 
204
    put(sname,open_write_and_close3),
 
205
    put(verbosity,trace),
 
206
    ?DBG("open_write_and_close2 -> start", []),
 
207
 
 
208
    seqno_init(), 
 
209
    SeqNoGen = {?MODULE, next_seqno, [10, 100]}, 
 
210
    ?line ok = open_write_and_close(SeqNoGen, Config),
 
211
    seqno_finish(),
 
212
 
 
213
    ?DBG("open_write_and_close2 -> done", []),
 
214
    ok.
 
215
 
 
216
 
 
217
%%======================================================================
 
218
 
 
219
open_write_and_close4(suite) -> 
 
220
    [];
 
221
open_write_and_close4(doc) -> 
 
222
    "Open a log file with sequence-numbering using fun";
 
223
open_write_and_close4(Config) when is_list(Config) ->
 
224
    p(open_write_and_close4),
 
225
    put(sname,open_write_and_close4),
 
226
    put(verbosity,trace),
 
227
    ?DBG("open_write_and_close2 -> start", []),
 
228
 
 
229
    seqno_init(), 
 
230
    SeqNoGen = fun() -> next_seqno(10, 100) end, 
 
231
    ?line ok = open_write_and_close(SeqNoGen, Config),
 
232
    seqno_finish(),
 
233
 
 
234
    ?DBG("open_write_and_close2 -> done", []),
 
235
    ok.
 
236
 
 
237
 
 
238
%%======================================================================
 
239
 
 
240
seqno_init() ->
 
241
    ets:new(snmp_log_test_seqno_tab, [named_table, set, protected]).
 
242
 
 
243
seqno_finish() ->
 
244
    ets:delete(snmp_log_test_seqno_tab).
 
245
 
 
246
next_seqno(Initial, Max) ->
 
247
    Key       = seqno, 
 
248
    Position  = 2, 
 
249
    Increment = 1, 
 
250
    Threshold = Max,
 
251
    SetValue  = Initial, 
 
252
    UpdateOp  = {Position, Increment, Threshold, SetValue},
 
253
    Tab       = snmp_log_test_seqno_tab, 
 
254
    case (catch ets:update_counter(Tab, Key, UpdateOp)) of
 
255
        {'EXIT', {badarg, _}} ->
 
256
            ets:insert(Tab, {seqno, Initial}),
 
257
            Initial;
 
258
        Next when is_integer(Next) ->
 
259
            Next
 
260
    end.
 
261
    
 
262
open_write_and_close(SeqNoGen, Config) ->
 
263
    ?DBG("open_write_and_close1 -> start", []),
141
264
    Dir    = ?config(log_dir, Config),
142
265
    Name   = "snmp_test",
143
266
    File   = join(Dir, "snmp_test.log"),
144
267
    Size   = {1024, 10},
145
268
    Repair = true,
146
269
    ?DBG("open_write_and_close -> create log", []),
147
 
    ?line {ok, Log} = snmp_log:create(Name, File, Size, Repair),
 
270
    
 
271
    ?line {ok, Log} = 
 
272
        case SeqNoGen of
 
273
            none -> 
 
274
                snmp_log:create(Name, File, Size, Repair);
 
275
            _ ->
 
276
                snmp_log:create(Name, File, SeqNoGen, Size, Repair)
 
277
        end,
148
278
 
149
279
    Vsn       = 'version-2',
150
280
    Community = "all-rights",
151
281
 
152
 
    ?DBG("open_write_and_close -> create messages to log", []),
 
282
    ?DBG("open_write_and_close1 -> create messages to log", []),
153
283
    %% A request
154
284
    ?line Req = get_next_request(Vsn, Community, [1,1], 1, 235779012),
155
285
 
162
292
    Msgs = lists:flatten(lists:duplicate(1002,[Req,Rep])),
163
293
 
164
294
    %% And now log them:
165
 
    ?DBG("open_write_and_close -> log ~p messages, ~p bytes", 
 
295
    ?DBG("open_write_and_close1 -> log ~p messages, ~p bytes", 
166
296
        [length(Msgs), size(list_to_binary(Msgs))]),
167
297
    Addr = ?LOCALHOST(),
168
298
    Port = 162,
172
302
    lists:foreach(Logger, Msgs),
173
303
    check_notify(),
174
304
    
175
 
    ?DBG("open_write_and_close -> display info", []),
 
305
    ?DBG("open_write_and_close1 -> display info", []),
176
306
    ?line {ok, Info} = snmp_log:info(Log),
177
307
    display_info(Info),
178
308
 
179
 
    ?DBG("open_write_and_close -> close log", []),
 
309
    ?DBG("open_write_and_close1 -> close log", []),
180
310
    ?line ok = snmp_log:close(Log),
181
311
 
182
312
    ?DBG("open_write_and_close -> done", []),
308
438
    put(sname,l2t1),
309
439
    put(verbosity,trace),
310
440
    ?DBG("log_to_txt1 -> start", []),
 
441
 
 
442
    Name     = "snmp_test_l2t1",
 
443
    SeqNoGen = disabled, 
 
444
    ?line ok = log_to_txt(Name, SeqNoGen, Config), 
 
445
 
 
446
    ?DBG("log_to_txt1 -> done", []),
 
447
    ok.
 
448
 
 
449
 
 
450
 
 
451
%%======================================================================
 
452
 
 
453
log_to_txt2(suite) -> [];
 
454
log_to_txt2(Config) when is_list(Config) ->
 
455
    p(log_to_txt2),
 
456
    put(sname,l2t2),
 
457
    put(verbosity,trace),
 
458
    ?DBG("log_to_txt2 -> start", []),
 
459
 
 
460
    Name     = "snmp_test_l2t2",
 
461
    seqno_init(), 
 
462
    SeqNoGen = {?MODULE, next_seqno, [1, 100]}, 
 
463
    ?line ok = log_to_txt(Name, SeqNoGen, Config), 
 
464
    seqno_finish(),
 
465
 
 
466
    ?DBG("log_to_txt2 -> done", []),
 
467
    ok.
 
468
 
 
469
 
 
470
 
 
471
%%======================================================================
 
472
 
 
473
log_to_txt(Name, SeqNoGen, Config) when is_list(Config) ->
 
474
    ?DBG("log_to_txt -> entry", []),
311
475
    Dir    = ?config(log_dir, Config),
312
 
    Name   = "snmp_test_l2t1",
313
 
    File   = join(Dir, "snmp_test_l2t1.log"),
 
476
    File   = join(Dir, Name ++ ".log"),
314
477
    Size   = {10240, 10},
315
478
    Repair = true,
316
 
    ?DBG("log_to_txt1 -> create log", []),
317
 
    ?line {ok, Log} = snmp_log:create(Name, File, Size, Repair),
318
 
 
319
 
    ?DBG("log_to_txt1 -> create messages to log", []),
 
479
 
 
480
    ?DBG("log_to_txt -> create log", []),
 
481
    ?line {ok, Log} = 
 
482
        case SeqNoGen of
 
483
            none -> 
 
484
                snmp_log:create(Name, File, Size, Repair);
 
485
            _ ->
 
486
                snmp_log:create(Name, File, SeqNoGen, Size, Repair)
 
487
        end,
 
488
 
 
489
    ?DBG("log_to_txt -> create messages to log", []),
320
490
    Msgs = messages(),
321
491
 
322
 
    ?DBG("log_to_txt1 -> create logger funs", []),
 
492
    ?DBG("log_to_txt -> create logger funs", []),
323
493
    Addr = ?LOCALHOST(),
324
494
    Port = 162,
325
495
    Logger = fun(Packet) ->
332
502
                  end,
333
503
    To = lists:duplicate(20, 5000),
334
504
 
335
 
    ?DBG("log_to_txt1 -> log the messages", []),
 
505
    ?DBG("log_to_txt -> log the messages", []),
336
506
    Start = calendar:local_time(),
337
507
    lists:foreach(BatchLogger, To),
338
508
    Stop  = calendar:local_time(),
339
509
 
340
 
    ?DBG("log_to_txt1 -> display info", []),
 
510
    ?DBG("log_to_txt -> display info", []),
341
511
    ?line {ok, Info} = snmp_log:info(Log),
342
512
    display_info(Info),
343
513
 
344
514
    Out1 = join(Dir, "snmp_text-1.txt"),
345
 
    ?DBG("log_to_txt1 -> do the convert to a text file when"
 
515
    ?DBG("log_to_txt -> do the convert to a text file when"
346
516
        "~n   Out1: ~p", [Out1]),
347
517
    ?line ok = snmp:log_to_txt(Dir, [], Out1, Log, File),
348
518
 
349
519
    ?line {ok, #file_info{size = Size1}} = file:read_file_info(Out1),
350
 
    ?DBG("log_to_txt1 -> text file size: ~p", [Size1]),
 
520
    ?DBG("log_to_txt -> text file size: ~p", [Size1]),
351
521
    validate_size(Size1),
352
522
 
353
523
    Out2 = join(Dir, "snmp_text-2.txt"),
354
 
    ?DBG("log_to_txt1 -> do the convert to a text file when"
 
524
    ?DBG("log_to_txt -> do the convert to a text file when"
355
525
        "~n   Start: ~p"
356
526
        "~n   Stop:  ~p"
357
527
        "~n   Out2:  ~p", [Start, Stop, Out2]),
358
528
    ?line ok = snmp:log_to_txt(Dir, [], Out2, Log, File, Start, Stop),
359
529
 
360
530
    ?line {ok, #file_info{size = Size2}} = file:read_file_info(Out2),
361
 
    ?DBG("log_to_txt1 -> text file size: ~p", [Size2]),
 
531
    ?DBG("log_to_txt -> text file size: ~p", [Size2]),
362
532
    validate_size(Size2, {le, Size1}),
363
533
 
364
534
    %% Calculate new start / stop times...
365
535
    GStart = calendar:datetime_to_gregorian_seconds(Start),
366
 
    ?DBG("log_to_txt1 -> GStart: ~p", [GStart]),
 
536
    ?DBG("log_to_txt -> GStart: ~p", [GStart]),
367
537
    GStop  = calendar:datetime_to_gregorian_seconds(Stop),
368
 
    ?DBG("log_to_txt1 -> GStop: ~p", [GStop]),
 
538
    ?DBG("log_to_txt -> GStop: ~p", [GStop]),
369
539
    Diff4 = (GStop - GStart) div 4,
370
 
    ?DBG("log_to_txt1 -> Diff4: ~p", [Diff4]),
 
540
    ?DBG("log_to_txt -> Diff4: ~p", [Diff4]),
371
541
    GStart2 = GStart + Diff4,
372
542
    GStop2  = GStop - Diff4,
373
543
    if 
381
551
    Stop2  = calendar:gregorian_seconds_to_datetime(GStop2),
382
552
    
383
553
    Out3 = join(Dir, "snmp_text-3.txt"),
384
 
    ?DBG("log_to_txt1 -> do the convert to a text file when"
 
554
    ?DBG("log_to_txt -> do the convert to a text file when"
385
555
        "~n   Start2: ~p"
386
556
        "~n   Stop2:  ~p"
387
557
        "~n   Out3:   ~p", [Start2, Stop2, Out3]),
388
558
    ?line ok = snmp:log_to_txt(Dir, [], Out3, Log, File, Start2, Stop2),
389
559
 
390
560
    ?line {ok, #file_info{size = Size3}} = file:read_file_info(Out3),
391
 
    ?DBG("log_to_txt1 -> text file size: ~p", [Size3]),
 
561
    ?DBG("log_to_txt -> text file size: ~p", [Size3]),
392
562
    validate_size(Size3, {l, Size1}),    
393
563
 
394
 
    ?DBG("log_to_txt1 -> close log", []),
 
564
    ?DBG("log_to_txt -> close log", []),
395
565
    ?line ok = snmp_log:close(Log),
396
566
 
397
 
    ?DBG("log_to_txt1 -> done", []),
 
567
    ?DBG("log_to_txt -> done", []),
398
568
    ok.
399
569
 
400
570
 
405
575
%%
406
576
%% Test: ts:run(snmp, snmp_log_test, log_to_txt2, [batch]).
407
577
 
408
 
log_to_txt2(suite) -> [];
409
 
log_to_txt2(doc) -> "Log to txt file from a different process than which "
410
 
                       "opened and wrote the log";
411
 
log_to_txt2(Config) when is_list(Config) ->
 
578
log_to_txt3(suite) -> 
 
579
    [];
 
580
log_to_txt3(doc) -> 
 
581
    "Log to txt file from a different process than which "
 
582
        "opened and wrote the log";
 
583
log_to_txt3(Config) when is_list(Config) ->
412
584
    process_flag(trap_exit, true),
413
 
    p(log_to_txt2),
414
 
    put(sname,l2t2),
 
585
    p(log_to_txt3),
 
586
    put(sname,l2t3),
415
587
    put(verbosity,trace),
416
 
    ?DBG("log_to_txt2 -> start", []),
 
588
    ?DBG("log_to_txt3 -> start", []),
417
589
    Dir     = ?config(log_dir, Config),
418
 
    Name    = "snmp_test_l2t2",
419
 
    LogFile = join(Dir, "snmp_test_l2t2.log"),
420
 
    TxtFile = join(Dir, "snmp_test_l2t2.txt"),
 
590
    Name    = "snmp_test_l2t3",
 
591
    LogFile = join(Dir, "snmp_test_l2t3.log"),
 
592
    TxtFile = join(Dir, "snmp_test_l2t3.txt"),
421
593
    Meg     = 1024*1024,
422
594
    Size    = {10*Meg, 10},
423
595
    Repair  = true,
425
597
    StdMibDir = filename:join(code:priv_dir(snmp), "mibs") ++ "/",
426
598
    Mibs = [join(StdMibDir, "SNMPv2-MIB")],
427
599
 
428
 
    ?DBG("log_to_txt2 -> create log writer process", []),
 
600
    ?DBG("log_to_txt3 -> create log writer process", []),
429
601
    ?line {ok, Log, Logger} = log_writer_start(Name, LogFile, Size, Repair),
430
602
 
431
 
    ?DBG("log_to_txt2 -> create log reader process", []),
 
603
    ?DBG("log_to_txt3 -> create log reader process", []),
432
604
    ?line {ok, Reader} = log_reader_start(),
433
605
 
434
 
    ?DBG("log_to_txt2 -> wait some time", []),
 
606
    ?DBG("log_to_txt3 -> wait some time", []),
435
607
    ?SLEEP(5000),
436
608
 
437
 
    ?DBG("log_to_txt2 -> display log info", []),
 
609
    ?DBG("log_to_txt3 -> display log info", []),
438
610
    ?line log_writer_info(Logger),
439
611
 
440
 
    ?DBG("log_to_txt2 -> instruct the log writer to sleep some", []),
 
612
    ?DBG("log_to_txt3 -> instruct the log writer to sleep some", []),
441
613
    ?line ok = log_writer_sleep(Logger, 5000),
442
614
 
443
 
    ?DBG("log_to_txt2 -> instruct the log reader to log to txt", []),
 
615
    ?DBG("log_to_txt3 -> instruct the log reader to log to txt", []),
444
616
    Res = 
445
617
        log_reader_log_to(Reader, 
446
618
                          fun() -> 
457
629
 
458
630
    case Res of
459
631
        {ok, Info} ->
460
 
            ?DBG("log_to_txt2 -> ~n   Info: ~p", [Info]),
 
632
            ?DBG("log_to_txt3 -> ~n   Info: ~p", [Info]),
461
633
            ?line {ok, #file_info{size = FileSize}} = 
462
634
                file:read_file_info(TxtFile),
463
 
            ?DBG("log_to_txt2 -> text file size: ~p", [FileSize]),
 
635
            ?DBG("log_to_txt3 -> text file size: ~p", [FileSize]),
464
636
            validate_size(FileSize);
465
637
        {Error, Info} ->
466
 
            ?DBG("log_to_txt2 -> log to txt failed: "
 
638
            ?DBG("log_to_txt3 -> log to txt failed: "
467
639
                 "~n   Error: ~p"
468
640
                 "~n   Info:  ~p", [Error, Info]),
469
641
            ?line ?FAIL({log_lo_txt_failed, Error, Info})
470
642
    end,
471
643
 
472
 
    ?DBG("log_to_txt2 -> instruct the log writer to stop", []),
 
644
    ?DBG("log_to_txt3 -> instruct the log writer to stop", []),
473
645
    ?line log_writer_stop(Logger),
474
646
 
475
 
    ?DBG("log_to_txt2 -> instruct the log reader to stop", []),
 
647
    ?DBG("log_to_txt3 -> instruct the log reader to stop", []),
476
648
    ?line log_reader_stop(Reader),
477
649
 
478
 
    ?DBG("log_to_txt2 -> done", []),
 
650
    ?DBG("log_to_txt3 -> done", []),
479
651
    ok.
480
652
 
481
653