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

« back to all changes in this revision

Viewing changes to lib/kernel/test/gen_udp_SUITE.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
3
%% 
4
 
%% Copyright Ericsson AB 1998-2009. All Rights Reserved.
 
4
%% Copyright Ericsson AB 1998-2011. All Rights Reserved.
5
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
21
21
% because udp is not deterministic.
22
22
%
23
23
-module(gen_udp_SUITE).
24
 
-include("test_server.hrl").
 
24
-include_lib("test_server/include/test_server.hrl").
25
25
 
26
26
 
27
27
-define(default_timeout, ?t:minutes(1)).
29
29
% XXX - we should pick a port that we _know_ is closed. That's pretty hard.
30
30
-define(CLOSED_PORT, 6666).
31
31
 
32
 
-export([all/1]).
33
 
-export([init_per_testcase/2, fin_per_testcase/2]).
 
32
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
 
33
         init_per_group/2,end_per_group/2]).
 
34
-export([init_per_testcase/2, end_per_testcase/2]).
34
35
 
35
36
-export([send_to_closed/1, 
36
37
         buffer_size/1, binary_passive_recv/1, bad_address/1,
37
 
         read_packets/1, open_fd/1]).
38
 
 
39
 
all(suite) ->
40
 
    [send_to_closed, 
41
 
     buffer_size, binary_passive_recv, bad_address, read_packets,
42
 
     open_fd].
 
38
         read_packets/1, open_fd/1, connect/1, implicit_inet6/1]).
 
39
 
 
40
suite() -> [{ct_hooks,[ts_install_cth]}].
 
41
 
 
42
all() -> 
 
43
    [send_to_closed, buffer_size, binary_passive_recv,
 
44
     bad_address, read_packets, open_fd, connect,
 
45
     implicit_inet6].
 
46
 
 
47
groups() -> 
 
48
    [].
 
49
 
 
50
init_per_suite(Config) ->
 
51
    Config.
 
52
 
 
53
end_per_suite(_Config) ->
 
54
    ok.
 
55
 
 
56
init_per_group(_GroupName, Config) ->
 
57
    Config.
 
58
 
 
59
end_per_group(_GroupName, Config) ->
 
60
    Config.
 
61
 
43
62
 
44
63
init_per_testcase(_Case, Config) ->
45
64
    ?line Dog=test_server:timetrap(?default_timeout),
46
65
    [{watchdog, Dog}|Config].
47
66
 
48
 
fin_per_testcase(_Case, Config) ->
 
67
end_per_testcase(_Case, Config) ->
49
68
    Dog=?config(watchdog, Config),
50
69
    test_server:timetrap_cancel(Dog),
51
70
    ok.
408
427
 
409
428
stop_node(Node) ->
410
429
    ?t:stop_node(Node).
 
430
 
 
431
 
 
432
connect(suite) ->
 
433
    [];
 
434
connect(doc) ->
 
435
    ["Test that connect/3 has effect"];
 
436
connect(Config) when is_list(Config) ->
 
437
    ?line Addr = {127,0,0,1},
 
438
    ?line {ok,S1} = gen_udp:open(0),
 
439
    ?line {ok,P1} = inet:port(S1),
 
440
    ?line {ok,S2} = gen_udp:open(0),
 
441
    ?line ok = inet:setopts(S2, [{active,false}]),
 
442
    ?line ok = gen_udp:close(S1),
 
443
    ?line ok = gen_udp:connect(S2, Addr, P1),
 
444
    ?line ok = gen_udp:send(S2, <<16#deadbeef:32>>),
 
445
    ?line ok = case gen_udp:recv(S2, 0, 5) of
 
446
        {error,econnrefused} -> ok;
 
447
        {error,econnreset} -> ok;
 
448
        Other -> Other
 
449
    end,
 
450
    ok.
 
451
 
 
452
implicit_inet6(Config) when is_list(Config) ->
 
453
    ?line Host = ok(inet:gethostname()),
 
454
    ?line
 
455
        case inet:getaddr(Host, inet6) of
 
456
            {ok,Addr} ->
 
457
                ?line implicit_inet6(Host, Addr);
 
458
            {error,Reason} ->
 
459
                {skip,
 
460
                 "Can not look up IPv6 address: "
 
461
                 ++atom_to_list(Reason)}
 
462
        end.
 
463
 
 
464
implicit_inet6(Host, Addr) ->
 
465
    ?line Active = {active,false},
 
466
    ?line
 
467
        case gen_udp:open(0, [inet6,Active]) of
 
468
            {ok,S1} ->
 
469
                ?line Loopback = {0,0,0,0,0,0,0,1},
 
470
                ?line io:format("~s ~p~n", ["::1",Loopback]),
 
471
                ?line implicit_inet6(S1, Active, Loopback),
 
472
                ?line ok = gen_udp:close(S1),
 
473
                %%
 
474
                ?line Localhost = "localhost",
 
475
                ?line Localaddr = ok(inet:getaddr(Localhost, inet6)),
 
476
                ?line io:format("~s ~p~n", [Localhost,Localaddr]),
 
477
                ?line S2 = ok(gen_udp:open(0, [{ip,Localaddr},Active])),
 
478
                ?line implicit_inet6(S2, Active, Localaddr),
 
479
                ?line ok = gen_udp:close(S2),
 
480
                %%
 
481
                ?line io:format("~s ~p~n", [Host,Addr]),
 
482
                ?line S3 = ok(gen_udp:open(0, [{ifaddr,Addr},Active])),
 
483
                ?line implicit_inet6(S3, Active, Addr),
 
484
                ?line ok = gen_udp:close(S3);
 
485
            _ ->
 
486
                {skip,"IPv6 not supported"}
 
487
        end.
 
488
 
 
489
implicit_inet6(S1, Active, Addr) ->
 
490
    ?line P1 = ok(inet:port(S1)),
 
491
    ?line S2 = ok(gen_udp:open(0, [inet6,Active])),
 
492
    ?line P2 = ok(inet:port(S2)),
 
493
    ?line ok = gen_udp:connect(S2, Addr, P1),
 
494
    ?line ok = gen_udp:connect(S1, Addr, P2),
 
495
    ?line {Addr,P2} = ok(inet:peername(S1)),
 
496
    ?line {Addr,P1} = ok(inet:peername(S2)),
 
497
    ?line {Addr,P1} = ok(inet:sockname(S1)),
 
498
    ?line {Addr,P2} = ok(inet:sockname(S2)),
 
499
    ?line ok = gen_udp:send(S1, Addr, P2, "ping"),
 
500
    ?line {Addr,P1,"ping"} = ok(gen_udp:recv(S2, 1024, 1000)),
 
501
    ?line ok = gen_udp:send(S2, Addr, P1, "pong"),
 
502
    ?line {Addr,P2,"pong"} = ok(gen_udp:recv(S1, 1024)),
 
503
    ?line ok = gen_udp:close(S2).
 
504
 
 
505
ok({ok,V}) -> V.