~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

Viewing changes to lib/megaco/test/megaco_tcp_test.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%<copyright>
2
 
%% <year>2000-2007</year>
 
2
%% <year>2000-2008</year>
3
3
%% <holder>Ericsson AB, All Rights Reserved</holder>
4
4
%%</copyright>
5
5
%%<legalnotice>
40
40
         start/1,
41
41
         start_normal/1,
42
42
         start_invalid_opt/1,
 
43
         start_and_stop/1,
43
44
 
44
45
         sending/1,
45
46
         sendreceive/1, 
 
47
         block_unblock/1, 
46
48
 
47
49
         errors/1,
48
 
         socket/1,
 
50
         socket_failure/1,
49
51
         accept_process/1,
50
52
         accept_supervisor/1,
51
53
         connection_supervisor/1,
59
61
%%----------------------------------------------------------------------
60
62
%% Internal exports
61
63
%%----------------------------------------------------------------------
 
64
 
62
65
-export([
 
66
         receive_message/4,
 
67
         process_received_message/4
63
68
        ]).
64
69
 
 
70
 
65
71
%%----------------------------------------------------------------------
66
72
%% Macros
67
73
%%----------------------------------------------------------------------
70
76
%% Records
71
77
%%----------------------------------------------------------------------
72
78
 
 
79
-record(command, {id, desc, cmd}).
 
80
-record(server,  {parent, transport_ref, control_pid, handle}).
 
81
-record(client,  {parent, transport_ref, control_pid, handle}).
 
82
 
 
83
 
73
84
%%======================================================================
74
85
%% External functions
75
86
%%======================================================================
77
88
%% Function: t/0
78
89
%% Description: Run all test cases
79
90
%%----------------------------------------------------------------------
80
 
t()     -> megaco_test_lib:t(?MODULE).
 
91
t() -> megaco_test_lib:t(?MODULE).
 
92
 
81
93
 
82
94
%%----------------------------------------------------------------------
83
95
%% Function: t/1
96
108
init_per_testcase(Case, Config) ->
97
109
    megaco_test_lib:init_per_testcase(Case, Config).
98
110
 
 
111
 
99
112
%%----------------------------------------------------------------------
100
113
%% Function: fin_per_testcase/2
101
114
%% Description: 
103
116
fin_per_testcase(Case, Config) ->
104
117
    megaco_test_lib:fin_per_testcase(Case, Config).
105
118
 
 
119
 
106
120
%%======================================================================
107
121
%% Test case definitions
108
122
%%======================================================================
116
130
start(suite) ->
117
131
    [
118
132
     start_normal,
119
 
     start_invalid_opt
 
133
     start_invalid_opt,
 
134
     start_and_stop
120
135
    ].
121
136
 
122
137
sending(suite) ->
123
138
    [
124
 
     sendreceive
 
139
     sendreceive,
 
140
     block_unblock
125
141
    ].
126
142
 
127
143
errors(suite) ->
128
144
    [
129
 
     socket,
 
145
     socket_failure,
130
146
     accept_process,
131
147
     accept_supervisor,
132
148
     connection_supervisor,
136
152
 
137
153
%% ------------------ start ------------------------
138
154
 
 
155
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
156
 
139
157
start_normal(suite) ->
140
158
    [];
141
 
start_normal(Config) when list(Config) ->
142
 
    ?ACQUIRE_NODES(1, Config),
 
159
start_normal(Config) when is_list(Config) ->
 
160
    put(sname, "start_normal"),
 
161
    p("BEGIN TEST-CASE"), 
143
162
    Options = [{port, 20000}, {receive_handle, apa}],
144
163
    {ok, Pid} = start_case(Options, ok),
145
 
    exit(Pid, kill),
 
164
    megaco_tcp:stop_transport(Pid),
 
165
    p("done"),
146
166
    ok.
147
167
 
 
168
 
 
169
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
170
 
148
171
start_invalid_opt(suite) ->
149
172
    [];
150
 
start_invalid_opt(Config) when list(Config) ->
151
 
    ?ACQUIRE_NODES(1, Config),
 
173
start_invalid_opt(Config) when is_list(Config) ->
 
174
    put(sname, "start_invalid_opt"),
 
175
    p("BEGIN TEST-CASE"), 
152
176
    Options = [{port, 20000}, {receivehandle, apa}],
153
 
    ok = start_case(Options, error).
 
177
    ok = start_case(Options, error),
 
178
    p("done"),
 
179
    ok.
 
180
 
 
181
 
 
182
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
183
 
 
184
start_and_stop(suite) ->
 
185
    [];
 
186
start_and_stop(doc) ->
 
187
    ["This test case sets up a connection and then cloises it. "
 
188
     "No data is sent. "];
 
189
start_and_stop(Config) when is_list(Config) ->
 
190
    put(sname, "start_and_stop"),
 
191
    p("BEGIN TEST-CASE"), 
 
192
 
 
193
    process_flag(trap_exit, true),
 
194
 
 
195
    p("create nodes"),
 
196
    ServerNode = make_node_name(server),
 
197
    ClientNode = make_node_name(client),
 
198
    Nodes = [ServerNode, ClientNode], 
 
199
    ok = megaco_test_lib:start_nodes(Nodes, ?FILE, ?LINE),
 
200
 
 
201
    %% Create command sequences
 
202
    p("create command sequences"),
 
203
    ServerPort = 2944, 
 
204
    ServerCmds = start_and_stop_server_commands(ServerPort),
 
205
    {ok, ServerHost} = inet:gethostname(),
 
206
    ClientCmds = start_and_stop_client_commands(ServerPort, ServerHost),
 
207
 
 
208
    %% Start the test procs used in the test-case, one for each node
 
209
    p("start command handlers"),
 
210
    Server = server_start_command_handler(ServerNode, ServerCmds),
 
211
    p("server command handler started: ~p", [Server]),
 
212
    Client = client_start_command_handler(ClientNode, ClientCmds),
 
213
    p("client command handler started: ~p", [Client]),
 
214
 
 
215
    ok = 
 
216
        receive
 
217
            {listening, Server} ->
 
218
                p("received listening message from server [~p] => "
 
219
                  "send continue to client [~p]~n", [Server, Client]),
 
220
                Client ! {continue, self()},
 
221
                ok
 
222
        after 5000 ->
 
223
                {error, server_timeout}
 
224
        end,
 
225
    
 
226
    await_command_handler_completion([Server, Client], timer:seconds(20)),
 
227
    p("done"),
 
228
    ok.
 
229
 
 
230
 
 
231
start_and_stop_server_commands(Port) ->
 
232
    Opts = [{port, Port}], 
 
233
    Self = self(),
 
234
    [
 
235
     #command{id   = 1,
 
236
              desc = "Command sequence init",
 
237
              cmd  = fun(State) -> 
 
238
                             {ok, State#server{parent = Self}} 
 
239
                     end},
 
240
 
 
241
     #command{id   = 2,
 
242
              desc = "Start transport",
 
243
              cmd  = fun(State) -> 
 
244
                             server_start_transport(State) 
 
245
                     end},
 
246
 
 
247
     #command{id   = 3,
 
248
              desc = "Listen",
 
249
              cmd  = fun(State) -> 
 
250
                             server_listen(State, Opts) 
 
251
                     end},
 
252
 
 
253
     #command{id   = 4,
 
254
              desc = "Notify listening",
 
255
              cmd  = fun(State) -> 
 
256
                             server_notify_listening(State) 
 
257
                     end},
 
258
 
 
259
     #command{id   = 5,
 
260
              desc = "Await nothing",
 
261
              cmd  = fun(State) -> 
 
262
                             server_await_nothing(State, 6000) 
 
263
                     end},
 
264
 
 
265
     #command{id   = 6,
 
266
              desc = "Stop",
 
267
              cmd  = fun(State) -> 
 
268
                             server_stop_transport(State) 
 
269
                     end}
 
270
 
 
271
    ].
 
272
 
 
273
 
 
274
start_and_stop_client_commands(ServerPort, ServerHost) ->
 
275
    Opts = [{port, ServerPort}, {host, ServerHost}], 
 
276
    Self = self(),
 
277
    [
 
278
     #command{id   = 1,
 
279
              desc = "Command sequence init",
 
280
              cmd  = fun(State) -> 
 
281
                             {ok, State#client{parent = Self}} 
 
282
                     end},
 
283
 
 
284
     #command{id   = 2,
 
285
              desc = "Start transport",
 
286
              cmd  = fun(State) -> 
 
287
                             client_start_transport(State) 
 
288
                     end},
 
289
 
 
290
     #command{id   = 3,
 
291
              desc = "Await continue",
 
292
              cmd  = fun(State) -> 
 
293
                             client_await_continue_signal(State, 5000) 
 
294
                     end},
 
295
 
 
296
     #command{id   = 4,
 
297
              desc = "Connect",
 
298
              cmd  = fun(State) -> 
 
299
                             client_connect(State, Opts) 
 
300
                     end},
 
301
 
 
302
     #command{id   = 5,
 
303
              desc = "Await nothing",
 
304
              cmd  = fun(State) -> 
 
305
                             client_await_nothing(State, 5000) 
 
306
                     end},
 
307
 
 
308
     #command{id   = 6,
 
309
              desc = "Disconnect",
 
310
              cmd  = fun(State) -> 
 
311
                             client_disconnect(State) 
 
312
                     end},
 
313
 
 
314
     #command{id   = 7,
 
315
              desc = "Stop transport",
 
316
              cmd  = fun(State) -> 
 
317
                             client_stop_transport(State) 
 
318
                     end}
 
319
    ].
154
320
 
155
321
 
156
322
%% ------------------ sending ------------------------
157
323
 
 
324
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
325
 
158
326
sendreceive(suite) ->
159
327
    [];
160
 
sendreceive(Config) when list(Config) ->
161
 
    ?ACQUIRE_NODES(1, Config),
162
 
    sendreceive().
 
328
sendreceive(Config) when is_list(Config) ->
 
329
    put(sname, "sendreceive"),
 
330
    p("BEGIN TEST-CASE"), 
 
331
 
 
332
    process_flag(trap_exit, true),
 
333
 
 
334
    p("create nodes"),
 
335
    ServerNode = make_node_name(server),
 
336
    ClientNode = make_node_name(client),
 
337
    Nodes = [ServerNode, ClientNode], 
 
338
    ok = megaco_test_lib:start_nodes(Nodes, ?FILE, ?LINE),
 
339
 
 
340
    %% Create command sequences
 
341
    p("create command sequences"),
 
342
    ServerPort = 2944, 
 
343
    ServerCmds = sendreceive_server_commands(ServerPort),
 
344
    {ok, ServerHost} = inet:gethostname(),
 
345
    ClientCmds = sendreceive_client_commands(ServerPort, ServerHost),
 
346
 
 
347
    %% Start the test procs used in the test-case, one for each node
 
348
    p("start command handlers"),
 
349
    Server = server_start_command_handler(ServerNode, ServerCmds),
 
350
    p("server command handler started: ~p", [Server]),
 
351
    Client = client_start_command_handler(ClientNode, ClientCmds),
 
352
    p("client command handler started: ~p", [Client]),
 
353
 
 
354
    ok = 
 
355
        receive
 
356
            {listening, Server} ->
 
357
                p("received listening message from server [~p] => "
 
358
                  "send continue to client [~p]~n", [Server, Client]),
 
359
                Client ! {continue, self()},
 
360
                ok
 
361
        after 5000 ->
 
362
                {error, server_timeout}
 
363
        end,
 
364
    
 
365
    await_command_handler_completion([Server, Client], timer:seconds(20)),
 
366
    p("done"),
 
367
    ok.
 
368
 
 
369
 
 
370
sendreceive_server_commands(Port) ->
 
371
    Opts = [{port, Port}], 
 
372
    Self = self(),
 
373
    [
 
374
     #command{id   = 1,
 
375
              desc = "Command sequence init",
 
376
              cmd  = fun(State) -> 
 
377
                             {ok, State#server{parent = Self}} 
 
378
                     end},
 
379
 
 
380
     #command{id   = 2,
 
381
              desc = "Start transport",
 
382
              cmd  = fun(State) -> 
 
383
                             server_start_transport(State) 
 
384
                     end},
 
385
 
 
386
     #command{id   = 3,
 
387
              desc = "Listen",
 
388
              cmd  = fun(State) -> 
 
389
                             server_listen(State, Opts) 
 
390
                     end},
 
391
 
 
392
     #command{id   = 4,
 
393
              desc = "Notify listening",
 
394
              cmd  = fun(State) -> 
 
395
                             server_notify_listening(State) 
 
396
                     end},
 
397
 
 
398
     #command{id   = 5,
 
399
              desc = "Await initial message (ping)",
 
400
              cmd  = fun(State) -> 
 
401
                             server_await_initial_message(State, "ping", 5000) 
 
402
                     end},
 
403
 
 
404
     #command{id   = 6,
 
405
              desc = "Send reply (pong) to initial message",
 
406
              cmd  = fun(State) -> 
 
407
                             server_send_message(State, "pong") 
 
408
                     end},
 
409
 
 
410
     #command{id   = 7,
 
411
              desc = "Await nothing before sending a message (hejsan)",
 
412
              cmd  = fun(State) -> 
 
413
                             server_await_nothing(State, 1000) 
 
414
                     end},
 
415
 
 
416
     #command{id   = 8,
 
417
              desc = "Send message (hejsan)",
 
418
              cmd  = fun(State) -> 
 
419
                             server_send_message(State, "hejsan") 
 
420
                     end},
 
421
 
 
422
     #command{id   = 9,
 
423
              desc = "Await reply (hoppsan) to message",
 
424
              cmd  = fun(State) -> 
 
425
                             server_await_message(State, "hoppsan", 1000) 
 
426
                     end},
 
427
 
 
428
     #command{id   = 10,
 
429
              desc = "Await nothing before disconnecting",
 
430
              cmd  = fun(State) -> 
 
431
                             server_await_nothing(State, 1000) 
 
432
                     end},
 
433
 
 
434
     #command{id   = 11,
 
435
              desc = "Disconnect",
 
436
              cmd  = fun(State) -> 
 
437
                             server_disconnect(State) 
 
438
                     end},
 
439
 
 
440
     #command{id   = 12,
 
441
              desc = "Await nothing before stopping transport",
 
442
              cmd  = fun(State) -> 
 
443
                             server_await_nothing(State, 1000) 
 
444
                     end},
 
445
 
 
446
     #command{id   = 13,
 
447
              desc = "Stop",
 
448
              cmd  = fun(State) -> 
 
449
                             server_stop_transport(State) 
 
450
                     end}
 
451
 
 
452
    ].
 
453
 
 
454
sendreceive_client_commands(ServerPort, ServerHost) ->
 
455
    Opts = [{port, ServerPort}, {host, ServerHost}], 
 
456
    Self = self(),
 
457
    [
 
458
     #command{id   = 1,
 
459
              desc = "Command sequence init",
 
460
              cmd  = fun(State) -> 
 
461
                             {ok, State#client{parent = Self}} 
 
462
                     end},
 
463
 
 
464
     #command{id   = 2,
 
465
              desc = "Start transport",
 
466
              cmd  = fun(State) -> 
 
467
                             client_start_transport(State) 
 
468
                     end},
 
469
 
 
470
     #command{id   = 3,
 
471
              desc = "Await continue",
 
472
              cmd  = fun(State) -> 
 
473
                             client_await_continue_signal(State, 5000) 
 
474
                     end},
 
475
 
 
476
     #command{id   = 4,
 
477
              desc = "Connect",
 
478
              cmd  = fun(State) -> 
 
479
                             client_connect(State, Opts) 
 
480
                     end},
 
481
 
 
482
     #command{id   = 5,
 
483
              desc = "Send initial message (ping)",
 
484
              cmd  = fun(State) -> 
 
485
                             client_send_message(State, "ping") 
 
486
                     end},
 
487
 
 
488
     #command{id   = 6,
 
489
              desc = "Await reply (pong) to initial message",
 
490
              cmd  = fun(State) -> 
 
491
                             client_await_message(State, "pong", 1000) 
 
492
                     end},
 
493
 
 
494
     #command{id   = 7,
 
495
              desc = "Await message (hejsan)",
 
496
              cmd  = fun(State) -> 
 
497
                             client_await_message(State, "hejsan", 5000) 
 
498
                     end},
 
499
 
 
500
     #command{id   = 8,
 
501
              desc = "Send reply (hoppsan) to message",
 
502
              cmd  = fun(State) -> 
 
503
                             client_send_message(State, "hoppsan") 
 
504
                     end},
 
505
 
 
506
     #command{id   = 9,
 
507
              desc = "Await nothing before disconnecting",
 
508
              cmd  = fun(State) -> 
 
509
                             client_await_nothing(State, 1000) 
 
510
                     end},
 
511
 
 
512
     #command{id   = 10,
 
513
              desc = "Disconnect",
 
514
              cmd  = fun(State) -> 
 
515
                             client_disconnect(State) 
 
516
                     end},
 
517
 
 
518
     #command{id   = 11,
 
519
              desc = "Await nothing before stopping transport",
 
520
              cmd  = fun(State) -> 
 
521
                             client_await_nothing(State, 1000) 
 
522
                     end},
 
523
 
 
524
     #command{id   = 12,
 
525
              desc = "Stop transport",
 
526
              cmd  = fun(State) -> 
 
527
                             client_stop_transport(State) 
 
528
                     end}
 
529
    ].
 
530
 
 
531
 
 
532
 
 
533
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
534
 
 
535
block_unblock(suite) ->
 
536
    [];
 
537
block_unblock(Config) when is_list(Config) ->
 
538
    put(sname, "block_unblock"),
 
539
    p("BEGIN TEST-CASE"), 
 
540
 
 
541
    process_flag(trap_exit, true),
 
542
 
 
543
    p("create nodes"),
 
544
    ServerNode = make_node_name(server),
 
545
    ClientNode = make_node_name(client),
 
546
    Nodes = [ServerNode, ClientNode], 
 
547
    ok = megaco_test_lib:start_nodes(Nodes, ?FILE, ?LINE),
 
548
 
 
549
    %% Create command sequences
 
550
    p("create command sequences"),
 
551
    ServerPort = 2944, 
 
552
    ServerCmds = block_unblock_server_commands(ServerPort),
 
553
    {ok, ServerHost} = inet:gethostname(),
 
554
    ClientCmds = block_unblock_client_commands(ServerPort, ServerHost),
 
555
 
 
556
    %% Start the test procs used in the test-case, one for each node
 
557
    p("start command handlers"),
 
558
    Server = server_start_command_handler(ServerNode, ServerCmds),
 
559
    p("server command handler started: ~p", [Server]),
 
560
    Client = client_start_command_handler(ClientNode, ClientCmds),
 
561
    p("client command handler started: ~p", [Client]),
 
562
 
 
563
    ok = 
 
564
        receive
 
565
            {listening, Server} ->
 
566
                p("received listening message from server [~p] => "
 
567
                  "send continue to client [~p]~n", [Server, Client]),
 
568
                Client ! {continue, self()},
 
569
                ok
 
570
        after 5000 ->
 
571
                {error, server_timeout}
 
572
        end,
 
573
 
 
574
    ok = 
 
575
        receive
 
576
            {blocked, Client} ->
 
577
                p("received blocked message from client [~p] => "
 
578
                  "send continue to server [~p]~n", [Client, Server]),
 
579
                Server ! {continue, self()},
 
580
                ok
 
581
        after 5000 ->
 
582
                {error, timeout}
 
583
        end,
 
584
 
 
585
    await_command_handler_completion([Server, Client], timer:seconds(30)),
 
586
    p("done"),
 
587
    ok.
 
588
 
 
589
 
 
590
block_unblock_server_commands(Port) ->
 
591
    Opts = [{port, Port}], 
 
592
    Self = self(),
 
593
    [
 
594
     #command{id   = 1,
 
595
              desc = "Command sequence init",
 
596
              cmd  = fun(State) -> 
 
597
                             {ok, State#server{parent = Self}} 
 
598
                     end},
 
599
 
 
600
     #command{id   = 2,
 
601
              desc = "Start transport",
 
602
              cmd  = fun(State) -> 
 
603
                             server_start_transport(State) 
 
604
                     end},
 
605
 
 
606
     #command{id   = 3,
 
607
              desc = "Listen",
 
608
              cmd  = fun(State) -> 
 
609
                             server_listen(State, Opts) 
 
610
                     end},
 
611
 
 
612
     #command{id   = 4,
 
613
              desc = "Notify listening",
 
614
              cmd  = fun(State) -> 
 
615
                             server_notify_listening(State) 
 
616
                     end},
 
617
 
 
618
     #command{id   = 5,
 
619
              desc = "Await initial message (ping)",
 
620
              cmd  = fun(State) -> 
 
621
                             server_await_initial_message(State, "ping", 5000) 
 
622
                     end},
 
623
 
 
624
     #command{id   = 6,
 
625
              desc = "Send reply (pong) to initial message",
 
626
              cmd  = fun(State) -> 
 
627
                             server_send_message(State, "pong") 
 
628
                     end},
 
629
 
 
630
     #command{id   = 7,
 
631
              desc = "Await continue",
 
632
              cmd  = fun(State) -> 
 
633
                             server_await_continue_signal(State, 5000) 
 
634
                     end},
 
635
 
 
636
     #command{id   = 9,
 
637
              desc = "Await nothing before sending a message (hejsan)",
 
638
              cmd  = fun(State) -> 
 
639
                             server_await_nothing(State, 1000) 
 
640
                     end},
 
641
 
 
642
     #command{id   = 10,
 
643
              desc = "Send message (hejsan)",
 
644
              cmd  = fun(State) -> 
 
645
                             server_send_message(State, "hejsan") 
 
646
                     end},
 
647
 
 
648
     #command{id   = 11,
 
649
              desc = "Await reply (hoppsan) to message",
 
650
              cmd  = fun(State) -> 
 
651
                             server_await_message(State, "hoppsan", 10000) 
 
652
                     end},
 
653
 
 
654
     #command{id   = 12,
 
655
              desc = "Await nothing before disconnecting",
 
656
              cmd  = fun(State) -> 
 
657
                             server_await_nothing(State, 1000) 
 
658
                     end},
 
659
 
 
660
     #command{id   = 13,
 
661
              desc = "Disconnect",
 
662
              cmd  = fun(State) -> 
 
663
                             server_disconnect(State) 
 
664
                     end},
 
665
 
 
666
     #command{id   = 14,
 
667
              desc = "Await nothing before stopping transport",
 
668
              cmd  = fun(State) -> 
 
669
                             server_await_nothing(State, 1000) 
 
670
                     end},
 
671
 
 
672
     #command{id   = 15,
 
673
              desc = "Stop",
 
674
              cmd  = fun(State) -> 
 
675
                             server_stop_transport(State) 
 
676
                     end}
 
677
 
 
678
    ].
 
679
 
 
680
block_unblock_client_commands(ServerPort, ServerHost) ->
 
681
    Opts = [{port, ServerPort}, {host, ServerHost}], 
 
682
    Self = self(),
 
683
    [
 
684
     #command{id   = 1,
 
685
              desc = "Command sequence init",
 
686
              cmd  = fun(State) -> 
 
687
                             {ok, State#client{parent = Self}} 
 
688
                     end},
 
689
 
 
690
     #command{id   = 2,
 
691
              desc = "Start transport",
 
692
              cmd  = fun(State) -> 
 
693
                             client_start_transport(State) 
 
694
                     end},
 
695
 
 
696
     #command{id   = 3,
 
697
              desc = "Await continue",
 
698
              cmd  = fun(State) -> 
 
699
                             client_await_continue_signal(State, 5000) 
 
700
                     end},
 
701
 
 
702
     #command{id   = 4,
 
703
              desc = "Connect",
 
704
              cmd  = fun(State) -> 
 
705
                             client_connect(State, Opts) 
 
706
                     end},
 
707
 
 
708
     #command{id   = 5,
 
709
              desc = "Send initial message (ping)",
 
710
              cmd  = fun(State) -> 
 
711
                             client_send_message(State, "ping") 
 
712
                     end},
 
713
 
 
714
     #command{id   = 6,
 
715
              desc = "Await reply (pong) to initial message",
 
716
              cmd  = fun(State) -> 
 
717
                             client_await_message(State, "pong", 1000) 
 
718
                     end},
 
719
 
 
720
     #command{id   = 7,
 
721
              desc = "Await nothing before blocking",
 
722
              cmd  = fun(State) -> 
 
723
                             client_await_nothing(State, 1000) 
 
724
                     end},
 
725
 
 
726
     #command{id   = 8,
 
727
              desc = "Block",
 
728
              cmd  = fun(State) -> 
 
729
                             client_block(State) 
 
730
                     end},
 
731
 
 
732
     #command{id   = 9,
 
733
              desc = "Notify blocked",
 
734
              cmd  = fun(State) -> 
 
735
                             client_notify_blocked(State) 
 
736
                     end},
 
737
 
 
738
     #command{id   = 10,
 
739
              desc = "Await nothing before unblocking",
 
740
              cmd  = fun(State) -> 
 
741
                             client_await_nothing(State, 5000) 
 
742
                     end},
 
743
 
 
744
     #command{id   = 11,
 
745
              desc = "Unblock",
 
746
              cmd  = fun(State) -> 
 
747
                             client_unblock(State) 
 
748
                     end},
 
749
 
 
750
     #command{id   = 12,
 
751
              desc = "Await message (hejsan)",
 
752
              cmd  = fun(State) -> 
 
753
                             client_await_message(State, "hejsan", 100) 
 
754
                     end},
 
755
 
 
756
     #command{id   = 13,
 
757
              desc = "Send reply (hoppsan) to message",
 
758
              cmd  = fun(State) -> 
 
759
                             client_send_message(State, "hoppsan") 
 
760
                     end},
 
761
 
 
762
     #command{id   = 14,
 
763
              desc = "Await nothing before disconnecting",
 
764
              cmd  = fun(State) -> 
 
765
                             client_await_nothing(State, 1000) 
 
766
                     end},
 
767
 
 
768
     #command{id   = 15,
 
769
              desc = "Disconnect",
 
770
              cmd  = fun(State) -> 
 
771
                             client_disconnect(State) 
 
772
                     end},
 
773
 
 
774
     #command{id   = 16,
 
775
              desc = "Await nothing before stopping transport",
 
776
              cmd  = fun(State) -> 
 
777
                             client_await_nothing(State, 1000) 
 
778
                     end},
 
779
 
 
780
     #command{id   = 17,
 
781
              desc = "Stop transport",
 
782
              cmd  = fun(State) -> 
 
783
                             client_stop_transport(State) 
 
784
                     end}
 
785
    ].
 
786
 
163
787
 
164
788
 
165
789
%% ------------------ errors ------------------------
166
790
 
167
 
socket(suite) ->
 
791
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
792
 
 
793
socket_failure(suite) ->
168
794
    [];
169
 
socket(Config) when list(Config) ->
170
 
    ?ACQUIRE_NODES(1, Config),
171
 
    failing_socket().
 
795
socket_failure(Config) when is_list(Config) ->
 
796
    put(sname, "socket_failure"),
 
797
    p("BEGIN TEST-CASE"), 
 
798
 
 
799
    %% process_flag(trap_exit, true),
 
800
 
 
801
    socket_faulure().
 
802
 
 
803
 
 
804
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
172
805
 
173
806
accept_process(suite) ->
174
807
    [];
175
 
accept_process(Config) when list(Config) ->
176
 
    ?ACQUIRE_NODES(1, Config),
 
808
accept_process(Config) when is_list(Config) ->
 
809
    put(sname, "accept_process"),
 
810
    p("BEGIN TEST-CASE"), 
 
811
 
 
812
    %% process_flag(trap_exit, true),
 
813
 
177
814
    failing_accept_process().
178
815
 
 
816
 
 
817
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
818
 
179
819
accept_supervisor(suite) ->
180
820
    [];
181
 
accept_supervisor(Config) when list(Config) ->
182
 
    ?ACQUIRE_NODES(1, Config),
 
821
accept_supervisor(Config) when is_list(Config) ->
 
822
    put(sname, "accept_supervisor"),
 
823
    p("BEGIN TEST-CASE"), 
 
824
 
 
825
    %% process_flag(trap_exit, true),
 
826
 
183
827
    failing_accept_supervisor().
184
828
 
 
829
 
 
830
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
831
 
185
832
connection_supervisor(suite) ->
186
833
    [];
187
 
connection_supervisor(Config) when list(Config) ->
188
 
    ?ACQUIRE_NODES(1, Config),
 
834
connection_supervisor(Config) when is_list(Config) ->
 
835
    put(sname, "connection_supervisor"),
 
836
    p("BEGIN TEST-CASE"), 
 
837
 
 
838
    %% process_flag(trap_exit, true),
 
839
 
189
840
    failing_connection_supervisor().
190
841
 
 
842
 
 
843
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
844
 
191
845
tcp_server(suite) ->
192
846
    [];
193
 
tcp_server(Config) when list(Config) ->
194
 
    ?ACQUIRE_NODES(1, Config),
 
847
tcp_server(Config) when is_list(Config) ->
 
848
    put(sname, "tcp_server"),
 
849
    p("BEGIN TEST-CASE"), 
 
850
 
 
851
    %% process_flag(trap_exit, true),
 
852
 
195
853
    failing_tcp_server().
196
854
 
197
855
 
200
858
%%======================================================================
201
859
 
202
860
start_case(Options, Expect) ->
 
861
    p("start transport"),
203
862
    case (catch megaco_tcp:start_transport()) of
204
863
        {ok, Pid} ->
 
864
            p("create listen socket"),
205
865
            case (catch megaco_tcp:listen(Pid, Options)) of
206
 
                ok when Expect == ok ->
 
866
                ok when Expect =:= ok ->
 
867
                    p("extected listen result [ok]"),
207
868
                    {ok, Pid};
208
869
                ok ->
209
 
                    exit(Pid, kill),
 
870
                    p("unextected listen result [ok] - stop transport"),
 
871
                    megaco_tcp:stop_transport(Pid),
210
872
                    ?ERROR(unexpected_start_sucesss);
211
 
                {error, _Reason} when Expect == error ->
212
 
                    exit(Pid, kill),
 
873
                {error, _Reason} when Expect =:= error ->
 
874
                    p("extected listen result [error] - stop transport"),
 
875
                    megaco_tcp:stop_transport(Pid),
213
876
                    ok;
214
877
                {error, Reason} ->
215
 
                    exit(Pid, kill),
 
878
                    p("unextected listen result [error] - stop transport"),
 
879
                    megaco_tcp:stop_transport(Pid),
216
880
                    ?ERROR({unexpected_start_failure, Reason});
217
881
                Error ->
 
882
                    p("unextected listen result"),
218
883
                    ?ERROR({unexpected_result, Error})
219
884
            end;
220
885
        {error, Reason} ->
 
886
            p("unextected start_transport result"),
221
887
            ?ERROR({failed_starting_transport, Reason})
222
888
    end.
223
889
 
224
 
sendreceive() ->
225
 
    ?SKIP(not_yet_implemented).
226
 
 
227
 
failing_socket() ->
 
890
socket_faulure() ->
228
891
    ?SKIP(not_yet_implemented).
229
892
 
230
893
failing_accept_process() ->
240
903
    ?SKIP(not_yet_implemented).
241
904
 
242
905
 
 
906
%%----------------------------------------------------------------------
 
907
%% Message Callback functions 
 
908
%%----------------------------------------------------------------------
 
909
 
 
910
receive_message(ReceiveHandle, ControlPid, SendHandle, BinMsg) 
 
911
  when is_pid(ReceiveHandle) andalso is_binary(BinMsg) ->
 
912
    Msg = binary_to_list(BinMsg), 
 
913
    ReceiveHandle ! {receive_message, {ControlPid, SendHandle, Msg}},
 
914
    ok.
 
915
    
 
916
process_received_message(ReceiveHandle, ControlPid, SendHandle, BinMsg) 
 
917
  when is_pid(ReceiveHandle) andalso is_binary(BinMsg) ->
 
918
    Msg = binary_to_list(BinMsg), 
 
919
    ReceiveHandle ! {process_received_message, {ControlPid, SendHandle, Msg}},
 
920
    ok.
 
921
 
 
922
 
243
923
%%======================================================================
244
924
%% Internal functions
245
925
%%======================================================================
246
 
% compute_res(All) ->
247
 
%     compute_res(All, [], 0).
248
 
 
249
 
% compute_res([H | T], Bad, Sum) when integer(H) ->
250
 
%     compute_res(T, Bad, Sum + H);
251
 
% compute_res([H | T], Bad, Sum) ->
252
 
%     compute_res(T, [H | Bad], Sum);
253
 
% compute_res([], Bad, Sum) ->
254
 
%     ok = io:format("#bytes: ~w; errors: ~p~n", [Sum, Bad]).
 
926
 
 
927
%% -------  Server command handler and utility functions ----------
 
928
 
 
929
server_start_command_handler(Node, Commands) ->
 
930
    start_command_handler(Node, Commands, #server{}, "server").
 
931
 
 
932
server_start_transport(State) when is_record(State, server) ->
 
933
    case (catch megaco_tcp:start_transport()) of
 
934
        {ok, Ref} ->
 
935
            {ok, State#server{transport_ref = Ref}};
 
936
        Error ->
 
937
            Error
 
938
    end.
 
939
 
 
940
server_listen(#server{transport_ref = Ref} = State, Options) 
 
941
  when is_record(State, server) andalso is_list(Options) ->
 
942
    Opts = [{receive_handle, self()}, {module, ?MODULE} | Options], 
 
943
    case (catch megaco_tcp:listen(Ref, Opts)) of
 
944
        ok ->
 
945
            {ok, State};
 
946
        Error ->
 
947
            Error
 
948
    end.
 
949
 
 
950
server_notify_listening(#server{parent = Parent} = State) 
 
951
  when is_record(State, server) ->
 
952
    Parent ! {listening, self()},
 
953
    {ok, State}.
 
954
 
 
955
server_await_continue_signal(#server{parent = Parent} = State, Timeout) ->
 
956
    receive
 
957
        {continue, Parent} ->
 
958
            {ok, State}
 
959
    after Timeout ->
 
960
            {error, timeout}
 
961
    end.
 
962
    
 
963
server_await_initial_message(State, InitialMessage, Timeout) 
 
964
  when is_record(State, server) ->
 
965
    receive 
 
966
        {receive_message, {ControlPid, Handle, InitialMessage}} ->
 
967
            NewState = State#server{control_pid = ControlPid,
 
968
                                    handle      = Handle},
 
969
            {ok, NewState};
 
970
 
 
971
        Any ->
 
972
            p("received unexpected event: ~p", [Any]),
 
973
            {error, {unexpected_event, Any}}
 
974
 
 
975
    after Timeout ->
 
976
            {error, timeout}
 
977
    end.
 
978
 
 
979
server_send_message(#server{handle = Handle} = State, Message) ->
 
980
    megaco_tcp:send_message(Handle, Message),
 
981
    {ok, State}.
 
982
 
 
983
server_await_nothing(State, Timeout) 
 
984
  when is_record(State, server) ->
 
985
    receive 
 
986
        Any ->
 
987
            p("received unexpected event: ~p", [Any]),
 
988
            {error, {unexpected_event, Any}}
 
989
 
 
990
    after Timeout ->
 
991
            {ok, State}
 
992
    end.
 
993
 
 
994
 
 
995
server_await_message(State, ExpectMessage, Timeout) 
 
996
  when is_record(State, server) ->
 
997
    receive
 
998
        {receive_message, {_, _, ExpectMessage}} ->
 
999
            {ok, State};
 
1000
 
 
1001
        Any ->
 
1002
            p("received unexpected event: ~p", [Any]),
 
1003
            {error, {unexpected_event, Any}}
 
1004
 
 
1005
    after Timeout ->
 
1006
            {error, timeout}
 
1007
    end.
 
1008
 
 
1009
server_disconnect(#server{handle = Handle} = State) 
 
1010
  when (Handle =/= undefined) ->
 
1011
     megaco_tcp:close(Handle),
 
1012
    {ok, State#server{handle = undefined}}.
 
1013
 
 
1014
server_block(#server{handle = Handle} = State) 
 
1015
  when (Handle =/= undefined) ->
 
1016
     megaco_tcp:block(Handle),
 
1017
    {ok, State}.
 
1018
 
 
1019
server_unblock(#server{handle = Handle} = State) 
 
1020
  when (Handle =/= undefined) ->
 
1021
     megaco_tcp:unblock(Handle),
 
1022
    {ok, State}.
 
1023
 
 
1024
server_stop_transport(#server{transport_ref = Ref} = State) 
 
1025
  when (Ref =/= undefined) ->
 
1026
    megaco_tcp:stop_transport(Ref),
 
1027
    {ok, State}.
 
1028
 
 
1029
 
 
1030
%% -------  Client command handler and utility functions ----------
 
1031
 
 
1032
client_start_command_handler(Node, Commands) ->
 
1033
    start_command_handler(Node, Commands, #client{}, "client").
 
1034
                  
 
1035
client_start_transport(State) when is_record(State, client) ->
 
1036
    case (catch megaco_tcp:start_transport()) of
 
1037
        {ok, Ref} ->
 
1038
            {ok, State#client{transport_ref = Ref}};
 
1039
        Error ->
 
1040
            Error
 
1041
    end.
 
1042
 
 
1043
client_connect(#client{transport_ref = Ref} = State, Options) 
 
1044
  when is_record(State, client) andalso is_list(Options) ->
 
1045
    Opts = [{receive_handle, self()}, {module, ?MODULE} | Options], 
 
1046
    case (catch megaco_tcp:connect(Ref, Opts)) of
 
1047
        {ok, Handle, ControlPid} ->
 
1048
            {ok, State#client{control_pid = ControlPid, 
 
1049
                              handle      = Handle}};
 
1050
        Error ->
 
1051
            Error
 
1052
    end.
 
1053
 
 
1054
client_await_continue_signal(#client{parent = Parent} = State, Timeout) ->
 
1055
    receive
 
1056
        {continue, Parent} ->
 
1057
            {ok, State}
 
1058
    after Timeout ->
 
1059
            {error, timeout}
 
1060
    end.
 
1061
    
 
1062
client_notify_blocked(#client{parent = Parent} = State) ->
 
1063
    Parent ! {blocked, self()},
 
1064
    {ok, State}.
 
1065
 
 
1066
client_await_nothing(State, Timeout) 
 
1067
  when is_record(State, client) ->
 
1068
    receive 
 
1069
        Any ->
 
1070
            p("received unexpected event: ~p", [Any]),
 
1071
            {error, {unexpected_event, Any}}
 
1072
    after Timeout ->
 
1073
            {ok, State}
 
1074
    end.
 
1075
 
 
1076
client_send_message(#client{handle = Handle} = State, Message) ->
 
1077
    megaco_tcp:send_message(Handle, Message),
 
1078
    {ok, State}.
 
1079
 
 
1080
client_await_message(State, ExpectMessage, Timeout) 
 
1081
  when is_record(State, client) ->
 
1082
    receive
 
1083
        {receive_message, {_, _, ExpectMessage}} ->
 
1084
            {ok, State};
 
1085
 
 
1086
        Any ->
 
1087
            p("received unexpected event: ~p", [Any]),
 
1088
            {error, {unexpected_event, Any}}
 
1089
 
 
1090
    after Timeout ->
 
1091
            {error, timeout}
 
1092
    end.
 
1093
 
 
1094
client_block(#client{handle = Handle} = State) 
 
1095
  when (Handle =/= undefined) ->
 
1096
    megaco_tcp:block(Handle),
 
1097
    {ok, State}.
 
1098
 
 
1099
client_unblock(#client{handle = Handle} = State) 
 
1100
  when (Handle =/= undefined) ->
 
1101
    megaco_tcp:unblock(Handle),
 
1102
    {ok, State}.
 
1103
 
 
1104
client_disconnect(#client{handle = Handle} = State) 
 
1105
  when (Handle =/= undefined) ->
 
1106
    megaco_tcp:close(Handle),
 
1107
    {ok, State#client{handle = undefined, control_pid = undefined}}.
 
1108
 
 
1109
client_stop_transport(#client{transport_ref = Ref} = State) 
 
1110
  when (Ref =/= undefined) ->
 
1111
    megaco_tcp:stop_transport(Ref),
 
1112
    {ok, State}.
 
1113
 
 
1114
    
 
1115
%% -------- Command handler ---------
 
1116
 
 
1117
start_command_handler(Node, Commands, State, ShortName) ->
 
1118
    Fun = fun() ->
 
1119
                  put(sname, ShortName), 
 
1120
                  process_flag(trap_exit, true),
 
1121
                  Result = (catch command_handler(Commands, State)),
 
1122
                  p("command handler terminated with: "
 
1123
                    "~n   Result: ~p", [Result]),
 
1124
                  exit(Result)
 
1125
          end,
 
1126
    erlang:spawn_link(Node, Fun).
 
1127
                  
 
1128
command_handler([], State) ->
 
1129
    p("command_handler -> entry when done with"
 
1130
      "~n   State: ~p", [State]),
 
1131
    {ok, State};
 
1132
command_handler([#command{id   = Id,
 
1133
                          desc = Desc,
 
1134
                          cmd  = Cmd}|Commands], State) ->
 
1135
    p("command_handler -> entry with"
 
1136
      "~n   Id:   ~p"
 
1137
      "~n   Desc: ~p", [Id, Desc]),
 
1138
    case (catch Cmd(State)) of
 
1139
        {ok, NewState} ->
 
1140
            p("command_handler -> cmd ~w ok", [Id]),
 
1141
            command_handler(Commands, NewState);
 
1142
        {error, Reason} ->
 
1143
            p("command_handler -> cmd ~w error: "
 
1144
              "~n   Reason: ~p", [Id, Reason]),
 
1145
            {error, {cmd_error, Reason}};
 
1146
        {'EXIT', Reason} ->
 
1147
            p("command_handler -> cmv ~w exit: "
 
1148
              "~n   Reason: ~p", [Id, Reason]),
 
1149
            {error, {cmd_exit, Reason}};
 
1150
        Error ->
 
1151
            p("command_handler -> cmd ~w failure: "
 
1152
              "~n   Error: ~p", [Id, Error]),
 
1153
            {error, {cmd_failure, Error}}
 
1154
    end.
 
1155
 
 
1156
 
 
1157
await_command_handler_completion(Pids, Timeout) ->
 
1158
    await_command_handler_completion(Pids, [], [], Timeout).
 
1159
 
 
1160
await_command_handler_completion([], [], _Good, _Timeout) ->
 
1161
    p("await_command_handler_completion -> entry when done"),
 
1162
    ok;
 
1163
await_command_handler_completion([], Bad, Good, _Timeout) ->
 
1164
    p("await_command_handler_completion -> entry when done with bad result: "
 
1165
      "~n   Bad:  ~p"
 
1166
      "~n   Good: ~p", [Bad, Good]),
 
1167
    ok;
 
1168
await_command_handler_completion(Pids, Bad, Good, Timeout) ->
 
1169
    p("await_command_handler_completion -> entry when waiting for"
 
1170
      "~n   Pids:    ~p"
 
1171
      "~n   Bad:     ~p"
 
1172
      "~n   Good:    ~p"
 
1173
      "~n   Timeout: ~p", [Pids, Bad, Good, Timeout]), 
 
1174
    Begin = ms(), 
 
1175
    receive 
 
1176
        {'EXIT', Pid, {ok, FinalState}} ->
 
1177
            p("await_command_handler_completion -> "
 
1178
              "received ok EXIT signal from ~p", [Pid]), 
 
1179
            case lists:delete(Pid, Pids) of
 
1180
                Pids ->
 
1181
                    await_command_handler_completion(Pids, Bad, Good, 
 
1182
                                                     Timeout - (ms() - Begin));
 
1183
                Pids2 ->
 
1184
                    p("await_command_handler_completion -> ~p done", [Pid]), 
 
1185
                    await_command_handler_completion(Pids2, 
 
1186
                                                     Bad, 
 
1187
                                                     [{Pid, FinalState}|Good],
 
1188
                                                     Timeout - (ms() - Begin))
 
1189
            end;
 
1190
 
 
1191
        {'EXIT', Pid, {error, Reason}} ->
 
1192
            p("await_command_handler_completion -> "
 
1193
              "received error EXIT signal from ~p", [Pid]), 
 
1194
            case lists:delete(Pid, Pids) of
 
1195
                Pids ->
 
1196
                    await_command_handler_completion(Pids, Bad, Good, 
 
1197
                                                     Timeout - (ms() - Begin));
 
1198
                Pids2 ->
 
1199
                    p("await_command_handler_completion -> ~p done", [Pid]), 
 
1200
                    await_command_handler_completion(Pids2, 
 
1201
                                                     [{Pid, Reason}|Bad], 
 
1202
                                                     Good, 
 
1203
                                                     Timeout - (ms() - Begin))
 
1204
            end
 
1205
 
 
1206
    after Timeout ->
 
1207
            p("await_command_handler_completion -> timeout"), 
 
1208
            exit({timeout, Pids})
 
1209
    end.
 
1210
 
 
1211
 
 
1212
 
 
1213
%% ------- Misc functions --------
 
1214
 
 
1215
make_node_name(Name) ->
 
1216
    case string:tokens(atom_to_list(node()), [$@]) of
 
1217
        [_,Host] ->
 
1218
            list_to_atom(lists:concat([atom_to_list(Name) ++ "@" ++ Host]));
 
1219
        _ ->
 
1220
            exit("Test node must be started with '-sname'")
 
1221
    end.
 
1222
 
 
1223
 
 
1224
p(F) ->
 
1225
    p(F, []).
 
1226
 
 
1227
p(F, A) ->
 
1228
    p(get(sname), F, A).
 
1229
 
 
1230
p(S, F, A) when is_list(S) ->
 
1231
    io:format("*** [~s] ~p ~s ***" 
 
1232
              "~n   " ++ F ++ "~n", 
 
1233
              [format_timestamp(now()), self(), S | A]);
 
1234
p(_S, F, A) ->
 
1235
    io:format("*** [~s] ~p ~s *** "
 
1236
              "~n   " ++ F ++ "~n", 
 
1237
              [format_timestamp(now()), self(), "undefined" | A]).
 
1238
 
 
1239
 
 
1240
ms() ->
 
1241
    {A,B,C} = erlang:now(),
 
1242
    A*1000000000+B*1000+(C div 1000).
 
1243
    
 
1244
 
 
1245
format_timestamp({_N1, _N2, N3} = Now) ->
 
1246
    {Date, Time}   = calendar:now_to_datetime(Now),
 
1247
    {YYYY,MM,DD}   = Date,
 
1248
    {Hour,Min,Sec} = Time,
 
1249
    FormatDate =
 
1250
        io_lib:format("~.4w:~.2.0w:~.2.0w ~.2.0w:~.2.0w:~.2.0w 4~w",
 
1251
                      [YYYY,MM,DD,Hour,Min,Sec,round(N3/1000)]),
 
1252
    lists:flatten(FormatDate).