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

« back to all changes in this revision

Viewing changes to lib/megaco/test/megaco_load_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:
36
36
-define(MGC_START(Pid, Mid, ET, Verb), 
37
37
        megaco_test_mgc:start(Pid, Mid, ET, Verb)).
38
38
-define(MGC_STOP(Pid), megaco_test_mgc:stop(Pid)).
 
39
-define(MGC_USER_INFO(Pid,Tag), megaco_test_mgc:user_info(Pid,Tag)).
 
40
-define(MGC_CONN_INFO(Pid,Tag), megaco_test_mgc:conn_info(Pid,Tag)).
 
41
-define(MGC_SET_VERBOSITY(Pid, V), megaco_test_mgc:verbosity(Pid, V)).
39
42
 
40
43
-define(MG_START(Pid, Mid, Enc, Transp, Conf, Verb), 
41
44
        megaco_test_mg:start(Pid, Mid, Enc, Transp, Conf, Verb)).
46
49
-define(MG_MLOAD(Pid, NL, NR), 
47
50
        timer:tc(megaco_test_mg, apply_multi_load, [Pid, NL, NR])).
48
51
-define(MG_LOAD(Pid, NL, NR), megaco_test_mg:apply_multi_load(Pid, NL, NR)).
 
52
-define(MG_SET_VERBOSITY(Pid, V), megaco_test_mg:verbosity(Pid, V)).
49
53
 
50
54
 
51
55
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
54
58
t()     -> megaco_test_lib:t(?MODULE).
55
59
t(Case) -> megaco_test_lib:t({?MODULE, Case}).
56
60
 
 
61
min(M) -> timer:minutes(M).
57
62
 
58
63
%% Test server callbacks
 
64
init_per_testcase(single_user_medium_load = Case, Config) ->
 
65
    C = lists:keydelete(tc_timeout, 1, Config),
 
66
    do_init_per_testcase(Case, [{tc_timeout, min(5)}|C]);
59
67
init_per_testcase(single_user_heavy_load = Case, Config) ->
60
 
    process_flag(trap_exit, true),
61
68
    C = lists:keydelete(tc_timeout, 1, Config),
62
 
    megaco_test_lib:init_per_testcase(Case, [{tc_timeout,timer:minutes(10)}|C]);
 
69
    do_init_per_testcase(Case, [{tc_timeout, min(10)}|C]);
63
70
init_per_testcase(single_user_extreme_load = Case, Config) ->
64
 
    process_flag(trap_exit, true),
65
 
    C = lists:keydelete(tc_timeout, 1, Config),
66
 
    megaco_test_lib:init_per_testcase(Case, [{tc_timeout,timer:minutes(20)}|C]);
 
71
    C = lists:keydelete(tc_timeout, 1, Config),
 
72
    do_init_per_testcase(Case, [{tc_timeout, min(20)}|C]);
 
73
init_per_testcase(multi_user_medium_load = Case, Config) ->
 
74
    C = lists:keydelete(tc_timeout, 1, Config),
 
75
    do_init_per_testcase(Case, [{tc_timeout, min(5)}|C]);
 
76
init_per_testcase(multi_user_heavy_load = Case, Config) ->
 
77
    C = lists:keydelete(tc_timeout, 1, Config),
 
78
    do_init_per_testcase(Case, [{tc_timeout, min(10)}|C]);
 
79
init_per_testcase(multi_user_extreme_load = Case, Config) ->
 
80
    C = lists:keydelete(tc_timeout, 1, Config),
 
81
    do_init_per_testcase(Case, [{tc_timeout, min(20)}|C]);
67
82
init_per_testcase(Case, Config) ->
 
83
    do_init_per_testcase(Case, Config).
 
84
 
 
85
do_init_per_testcase(Case, Config) ->
68
86
    process_flag(trap_exit, true),
69
87
    megaco_test_lib:init_per_testcase(Case, Config).
70
 
 
 
88
    
71
89
fin_per_testcase(Case, Config) ->
72
90
    process_flag(trap_exit, false),
73
91
    megaco_test_lib:fin_per_testcase(Case, Config).
74
92
 
 
93
 
75
94
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
76
95
 
77
96
all(suite) ->
78
97
    Cases = 
79
98
        [
80
 
         single_user_light_load,
81
 
         single_user_medium_load,
82
 
         single_user_heavy_load,
83
 
         single_user_extreme_load,
84
 
         multi_user_light_load,
85
 
         multi_user_medium_load,
86
 
         multi_user_heavy_load,
87
 
         multi_user_extreme_load
88
 
        ].
 
99
         single_user_light_load,
 
100
         single_user_medium_load,
 
101
         single_user_heavy_load,
 
102
         single_user_extreme_load,
 
103
         multi_user_light_load,
 
104
         multi_user_medium_load,
 
105
         multi_user_heavy_load,
 
106
         multi_user_extreme_load
 
107
        ],
 
108
    Cases.
89
109
 
90
110
 
91
111
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
259
279
    ServChRes = ?MG_SERV_CHANGE(Mg),
260
280
    d("service change result: ~p", [ServChRes]),
261
281
 
 
282
    megaco_test_mg:update_conn_info(Mg,reply_timer,1000),
 
283
    megaco_test_mgc:update_conn_info(Mgc,reply_timer,1000),
 
284
 
262
285
    d("MG conn info: ~p", [?MG_CONN_INFO(Mg, all)]),
263
286
 
264
287
    d("apply the load"),
277
300
                      [Error, Time])
278
301
    end,
279
302
 
 
303
    i("flush the message queue: ~p", [megaco_test_lib:flush()]),
 
304
    
 
305
    i("verbosity to trace"),
 
306
    ?MGC_SET_VERBOSITY(Mgc, debug),
 
307
    ?MG_SET_VERBOSITY(Mg, debug),
 
308
 
280
309
    %% Tell MG to stop
281
310
    i("[MG] stop"),
282
311
    ?MG_STOP(Mg),
283
312
 
 
313
    i("flush the message queue: ~p", [megaco_test_lib:flush()]),
 
314
 
284
315
    %% Tell Mgc to stop
285
316
    i("[MGC] stop"),
286
317
    ?MGC_STOP(Mgc),
 
318
 
 
319
    i("flush the message queue: ~p", [megaco_test_lib:flush()]),
 
320
    
287
321
    ok.
288
322
 
289
323
 
306
340
    ET     = [{text,tcp}],
307
341
    {ok, Mgc} = ?MGC_START(MgcNode, MgcMid, ET, ?MGC_VERBOSITY),
308
342
 
 
343
    megaco_test_mgc:update_user_info(Mgc,reply_timer,1000),
 
344
    d("MGC user info: ~p", [?MGC_USER_INFO(Mgc, all)]),
 
345
 
309
346
    MgUsers = make_mids(MgNodes),
310
347
 
311
348
    d("start MGs, apply the load and stop MGs"),
312
349
    ok = multi_load(MgUsers, NumLoaders, ?MULTI_USER_LOAD_NUM_REQUESTS),
313
350
 
 
351
    i("flush the message queue: ~p", [megaco_test_lib:flush()]),
 
352
 
 
353
    ?MGC_SET_VERBOSITY(Mgc, debug),
 
354
 
314
355
    %% Tell Mgc to stop
315
356
    i("[MGC] stop"),
316
357
    ?MGC_STOP(Mgc),
 
358
 
 
359
    i("flush the message queue: ~p", [megaco_test_lib:flush()]),
 
360
 
317
361
    ok.
318
362
 
319
363
 
334
378
            {error, Error}
335
379
    end.
336
380
 
337
 
do_multi_load(Pids, NumLoaders, NumReqs) ->
338
 
    Fun = fun(P) -> P ! {apply_multi_load, self()} end,
 
381
do_multi_load(Pids, _NumLoaders, _NumReqs) ->
 
382
    Fun = fun({P,_}) -> P ! {apply_multi_load, self()} end,
339
383
    lists:foreach(Fun, Pids),
340
384
    await_multi_load_collectors(Pids, [], []).
341
385
 
342
386
multi_load_collector_start([], _NumLoaders, _NumReqs, Pids) ->
343
387
    Pids;
344
388
multi_load_collector_start([{Mid, Node}|MGs], NumLoaders, NumReqs, Pids) ->
 
389
    Env = get(),
345
390
    Pid = spawn_link(?MODULE, multi_load_collector, 
346
 
                     [self(), Node, Mid, NumLoaders, NumReqs]),
347
 
    multi_load_collector_start(MGs, NumLoaders, NumReqs, [Pid|Pids]).
348
 
 
349
 
 
350
 
multi_load_collector(Parent, Node, Mid, NumLoaders, NumReqs) ->
 
391
                     [self(), Node, Mid, NumLoaders, NumReqs, Env]),
 
392
    multi_load_collector_start(MGs, NumLoaders, NumReqs, [{Pid,Mid}|Pids]).
 
393
 
 
394
get_env(Key, Env) ->
 
395
    case lists:keysearch(Key, 1, Env) of
 
396
        {value, {Key, Val}} ->
 
397
            Val;
 
398
        _ ->
 
399
            undefined
 
400
    end.
 
401
 
 
402
multi_load_collector(Parent, Node, Mid, NumLoaders, NumReqs, Env) ->
 
403
    put(verbosity, get_env(verbosity, Env)),
 
404
    put(tc, get_env(tc, Env)),
 
405
    put(sname, get_env(sname, Env) ++ "-loader"),
351
406
    case ?MG_START(Node, Mid, text, tcp, [], ?MG_VERBOSITY) of
352
407
        {ok, Pid} ->
353
408
            d("MG ~p user info: ~n~p", [Mid, ?MG_USER_INFO(Pid,all)]),
354
409
            ServChRes = ?MG_SERV_CHANGE(Pid),
355
410
            d("service change result: ~p", [ServChRes]),
 
411
            megaco_test_mg:update_conn_info(Pid,reply_timer,1000),
356
412
            d("MG ~p conn info: ~p", [Mid, ?MG_CONN_INFO(Pid,all)]),
357
413
            multi_load_collector_loop(Parent, Pid, Mid, NumLoaders, NumReqs);
358
414
        Else ->
359
415
            Parent ! {load_start_failed, self(), Mid, Else}
360
416
    end.
361
417
 
362
 
multi_load_collector_loop(Perent, Pid, Mid, NumLoaders, NumReqs) ->
 
418
multi_load_collector_loop(Parent, Pid, Mid, NumLoaders, NumReqs) ->
363
419
    receive
364
420
        {apply_multi_load, Parent} ->
365
421
            Res = ?MG_LOAD(Pid, NumLoaders, NumReqs),
366
422
            Parent ! {load_complete, self(), Mid, Res},
 
423
            ?MG_SET_VERBOSITY(Pid, debug),
367
424
            ?MG_STOP(Pid),
368
425
            exit(normal)
369
426
    end.    
370
427
    
371
428
 
372
429
await_multi_load_collectors([], Oks, Errs) ->
 
430
    i("await_multi_load_collectors -> done"),
373
431
    {ok, Oks, Errs};
374
432
await_multi_load_collectors(Pids, Oks, Errs) ->
375
433
    receive
376
434
        {load_complete, Pid, Mg, {ok, Ok, Err}} ->
377
 
            Pids2 = lists:delete(Pid, Pids),
 
435
            i("await_multi_load_collectors -> "
 
436
              "received ok complete from "
 
437
              "~n   ~p [~p]", [Pid, Mg]),
 
438
            Pids2 = lists:keydelete(Pid, 1, Pids),
378
439
            Oks2  = [{Mg, Ok, Err}|Oks],
379
440
            await_multi_load_collectors(Pids2, Oks2, Errs);
380
441
        {load_complete, Pid, Mg, Error} ->
381
 
            Pids2 = lists:delete(Pid, Pids),
 
442
            i("await_multi_load_collectors -> "
 
443
              "received error complete from "
 
444
              "~n   ~p [~p]: "
 
445
              "~n   ~p", [Pid, Mg, Error]),
 
446
            Pids2 = lists:keydelete(Pid, 1, Pids),
382
447
            Errs2 = [{Mg, Error}|Errs],
383
448
            await_multi_load_collectors(Pids2, Oks, Errs2);
384
449
 
 
450
        {'EXIT', Pid, normal} ->
 
451
            %% This is assumed to be one of the collectors
 
452
            i("await_multi_load_collectors -> "
 
453
              "received (normal) exit signal from ~p", [Pid]),
 
454
            await_multi_load_collectors(Pids, Oks, Errs);
 
455
 
 
456
        {'EXIT', Pid, Reason} ->
 
457
            i("await_multi_load_collectors -> "
 
458
              "received unexpected exit from ~p:"
 
459
              "~n   ~p", [Pid, Reason]),
 
460
            case lists:keydelete(Pid, 1, Pids) of
 
461
                Pids ->
 
462
                    %% Not one of my procs, or a proc I have already
 
463
                    %% received a complete from.
 
464
                    await_multi_load_collectors(Pids, Oks, Errs);
 
465
                Pids2 ->
 
466
                    [{Pid,Mg}] = Pids -- Pids2,
 
467
                    Errs2 = [{Mg, {unexpected_exit, Reason}}|Errs],
 
468
                    await_multi_load_collectors(Pids, Oks, Errs2)
 
469
            end;
 
470
 
385
471
        Else ->
386
472
            i("await_multi_load_collectors -> received unexpected message:"
387
473
              "~n~p", [Else]),
388
474
            await_multi_load_collectors(Pids, Oks, Errs)
389
475
    after 
390
 
        300000 ->
391
 
            %% Cleanup?
392
 
            {error, {timeout, Pids, Oks, Errs}}
 
476
        5000 ->
 
477
            i("await_multi_load_collectors -> still awaiting reply from:"
 
478
              "~n~p", [Pids]),
 
479
            await_multi_load_collectors(Pids, Oks, Errs)
393
480
    end.
394
481
            
395
482
                
436
523
        [Name, _] ->
437
524
            Mid = {deviceName, Name},
438
525
            make_mids(MgNodes, [{Mid, MgNode}|Mids]);
439
 
        Else ->
 
526
        _Else ->
440
527
            exit("Test node must be started with '-sname'")
441
528
    end.
442
529
 
489
576
apply_load_timer() ->
490
577
    erlang:send_after(random(), self(), apply_load_timeout).
491
578
 
492
 
format_timestamp(Now) ->
493
 
    {N1, N2, N3} = Now,
 
579
format_timestamp({_N1, _N2, N3} = Now) ->
494
580
    {Date, Time}   = calendar:now_to_datetime(Now),
495
581
    {YYYY,MM,DD}   = Date,
496
582
    {Hour,Min,Sec} = Time,