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

« back to all changes in this revision

Viewing changes to lib/kernel/test/inet_SUITE.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2010-03-09 17:34:57 UTC
  • mfrom: (10.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20100309173457-4yd6hlcb2osfhx31
Tags: 1:13.b.4-dfsg-3
Manpages in section 1 are needed even if only arch-dependent packages are
built. So, re-enabled them.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 1997-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 1997-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
-module(inet_SUITE).
28
28
         gethostnative_parallell/1, cname_loop/1, 
29
29
         gethostnative_soft_restart/1,gethostnative_debug_level/1,getif/1]).
30
30
 
31
 
-export([get_hosts/1, get_ipv6_hosts/1, parse_hosts/1, 
 
31
-export([get_hosts/1, get_ipv6_hosts/1, parse_hosts/1, parse_address/1,
32
32
         kill_gethost/0, parallell_gethost/0]).
33
33
-export([init_per_testcase/2, end_per_testcase/2]).
34
34
 
249
249
            ?line {ok,IP46} = inet:getaddr(IP46, inet6),
250
250
            ?line {ok,IP46} = inet:getaddr(Name, inet6),
251
251
            ?line {ok,IP46} = inet:getaddr(FullName, inet6),
252
 
            ?line IP4toIP6 = inet:getaddr(IPStr, inet6),
253
 
            ?line case IP4toIP6 of
254
 
                      {ok,IP46} ->              % only native can do this
255
 
                          ?line true = lists:member(native,
256
 
                                                    inet_db:res_option(lookup));
257
 
                      {error,nxdomain} ->
258
 
                          ok
259
 
                  end,
 
252
            ?line {ok,IP46} = inet:getaddr(IPStr, inet6),
 
253
%%          ?line IP4toIP6 = inet:getaddr(IPStr, inet6),
 
254
%%          ?line case IP4toIP6 of
 
255
%%                    {ok,IP46} ->
 
256
%%                        ?line ok;
 
257
%%                    {error,nxdomain} ->
 
258
%%                        ?line false =
 
259
%%                            lists:member(native,
 
260
%%                                         inet_db:res_option(lookup))
 
261
%%                end,
260
262
            ?line {Name6, FullName6, IPStr6, IP6, _} =
261
263
                                        ?config(test_host_ipv6_only, Config),
262
264
            ?line {ok,_} = inet:getaddr(list_to_atom(Name6), inet6),
301
303
        end,
302
304
    ?line case {IP4to6Res,inet:gethostbyname(IPStr, inet6)} of
303
305
              {true,{ok,HEnt}} ->
304
 
                  ?line true = lists:member(native, inet_db:res_option(lookup)),
305
306
                  ?line HEnt_ = HEnt#hostent{h_addrtype = inet6,
306
307
                                             h_length = 16,
307
308
                                             h_addr_list = [IP_46]},
374
375
get_hosts([], _, _, Result) ->
375
376
    Result.
376
377
    
377
 
parse(suite) -> [parse_hosts];
 
378
parse(suite) -> [parse_hosts, parse_address];
378
379
parse(doc) -> ["Test that parsing of the hosts file or equivalent works,",
379
380
               "and that erroneous lines are skipped"].
 
381
 
380
382
parse_hosts(Config) when is_list(Config) ->
381
383
    ?line DataDir = ?config(data_dir,Config),
382
384
    ?line HostFile = filename:join(DataDir, "hosts"),
388
390
    ?line ResolvErr1 = filename:join(DataDir,"resolv.conf.err1"),
389
391
    ?line inet_parse:resolv(ResolvErr1).
390
392
 
 
393
parse_address(Config) when is_list(Config) ->
 
394
    V4Strict =
 
395
        [{{0,0,0,0},"0.0.0.0"},
 
396
         {{1,2,3,4},"1.2.3.4"},
 
397
         {{253,252,251,250},"253.252.251.250"},
 
398
         {{1,2,255,254},"1.2.255.254"}],
 
399
    V6Strict =
 
400
        [{{0,0,0,0,0,0,0,0},"::"},
 
401
         {{15,0,0,0,0,0,0,2},"f::2"},
 
402
         {{15,16#f11,0,0,0,0,256,2},"f:f11::0100:2"},
 
403
         {{0,0,0,0,0,0,0,16#17},"::17"},
 
404
         {{16#700,0,0,0,0,0,0,0},"0700::"},
 
405
         {{0,0,0,0,0,0,2,1},"::2:1"},
 
406
         {{0,0,0,0,0,3,2,1},"::3:2:1"},
 
407
         {{0,0,0,0,4,3,2,1},"::4:3:2:1"},
 
408
         {{0,0,0,5,4,3,2,1},"::5:4:3:2:1"},
 
409
         {{0,0,6,5,4,3,2,1},"::6:5:4:3:2:1"},
 
410
         {{0,7,6,5,4,3,2,1},"::7:6:5:4:3:2:1"},
 
411
         {{7,0,0,0,0,0,0,0},"7::"},
 
412
         {{7,6,0,0,0,0,0,0},"7:6::"},
 
413
         {{7,6,5,0,0,0,0,0},"7:6:5::"},
 
414
         {{7,6,5,4,0,0,0,0},"7:6:5:4::"},
 
415
         {{7,6,5,4,3,0,0,0},"7:6:5:4:3::"},
 
416
         {{7,6,5,4,3,2,0,0},"7:6:5:4:3:2::"},
 
417
         {{7,6,5,4,3,2,1,0},"7:6:5:4:3:2:1::"},
 
418
         {{16#c11,16#c22,16#5c33,16#c440,16#55c0,16#c66c,16#77,16#88},
 
419
          "c11:0c22:5c33:c440:55c0:c66c:77:0088"},
 
420
         {{16#c11,0,16#5c33,16#c440,16#55c0,16#c66c,16#77,16#88},
 
421
          "c11::5c33:c440:55c0:c66c:77:0088"},
 
422
         {{16#c11,16#c22,0,16#c440,16#55c0,16#c66c,16#77,16#88},
 
423
          "c11:0c22::c440:55c0:c66c:77:0088"},
 
424
         {{16#c11,16#c22,16#5c33,0,16#55c0,16#c66c,16#77,16#88},
 
425
          "c11:0c22:5c33::55c0:c66c:77:0088"},
 
426
         {{16#c11,16#c22,16#5c33,16#c440,0,16#c66c,16#77,16#88},
 
427
          "c11:0c22:5c33:c440::c66c:77:0088"},
 
428
         {{16#c11,16#c22,16#5c33,16#c440,16#55c0,0,16#77,16#88},
 
429
          "c11:0c22:5c33:c440:55c0::77:0088"},
 
430
         {{16#c11,16#c22,16#5c33,16#c440,16#55c0,16#c66c,0,16#88},
 
431
          "c11:0c22:5c33:c440:55c0:c66c::0088"},
 
432
         {{16#c11,0,0,16#c440,16#55c0,16#c66c,16#77,16#88},
 
433
          "c11::c440:55c0:c66c:77:0088"},
 
434
         {{16#c11,16#c22,0,0,16#55c0,16#c66c,16#77,16#88},
 
435
          "c11:0c22::55c0:c66c:77:0088"},
 
436
         {{16#c11,16#c22,16#5c33,0,0,16#c66c,16#77,16#88},
 
437
          "c11:0c22:5c33::c66c:77:0088"},
 
438
         {{16#c11,16#c22,16#5c33,16#c440,0,0,16#77,16#88},
 
439
          "c11:0c22:5c33:c440::77:0088"},
 
440
         {{16#c11,16#c22,16#5c33,16#c440,16#55c0,0,0,16#88},
 
441
          "c11:0c22:5c33:c440:55c0::0088"},
 
442
         {{16#c11,0,0,0,16#55c0,16#c66c,16#77,16#88},
 
443
          "c11::55c0:c66c:77:0088"},
 
444
         {{16#c11,16#c22,0,0,0,16#c66c,16#77,16#88},
 
445
          "c11:0c22::c66c:77:0088"},
 
446
         {{16#c11,16#c22,16#5c33,0,0,0,16#77,16#88},
 
447
          "c11:0c22:5c33::77:0088"},
 
448
         {{16#c11,16#c22,16#5c33,16#c440,0,0,0,16#88},
 
449
          "c11:0c22:5c33:c440::0088"},
 
450
         {{16#c11,0,0,0,0,16#c66c,16#77,16#88},
 
451
          "c11::c66c:77:0088"},
 
452
         {{16#c11,16#c22,0,0,0,0,16#77,16#88},
 
453
          "c11:0c22::77:0088"},
 
454
         {{16#c11,16#c22,16#5c33,0,0,0,0,16#88},
 
455
          "c11:0c22:5c33::0088"},
 
456
         {{16#c11,0,0,0,0,0,16#77,16#88},
 
457
          "c11::77:0088"},
 
458
         {{16#c11,16#c22,0,0,0,0,0,16#88},
 
459
          "c11:0c22::0088"},
 
460
         {{0,0,0,0,0,65535,258,65534},"::FFFF:1.2.255.254"},
 
461
         {{16#ffff,16#ffff,16#ffff,16#ffff,16#ffff,16#ffff,16#ffff,16#ffff},
 
462
          "ffff:ffff:ffff:ffff:ffff:ffff:ffff:ffff"}
 
463
        |[{{D2,0,0,0,0,P,(D1 bsl 8) bor D2,(D3 bsl 8) bor D4},
 
464
           erlang:integer_to_list(D2, 16)++"::"++Q++S}
 
465
          || {{D1,D2,D3,D4},S} <- V4Strict,
 
466
             {P,Q} <- [{0,""},{16#17,"17:"},{16#ff0,"0ff0:"}]]],
 
467
    V4Sloppy =
 
468
        [{{10,1,16#98,16#76},"10.0x019876"},
 
469
         {{8#12,1,8#130,8#321},"012.01.054321"},
 
470
         {{255,255,255,255},"255.255.255.0377"},
 
471
         {{255,255,255,255},"0Xff.000000000377.0x0000ff.255"},
 
472
         {{255,255,255,255},"255.255.65535"},
 
473
         {{255,255,255,255},"255.0xFF.0177777"},
 
474
         {{255,255,255,255},"255.16777215"},
 
475
         {{255,255,255,255},"00377.0XFFFFFF"},
 
476
         {{255,255,255,255},"4294967295"},
 
477
         {{255,255,255,255},"0xffffffff"},
 
478
         {{255,255,255,255},"00000000000037777777777"},
 
479
         {{16#12,16#34,16#56,16#78},"0x12345678"},
 
480
         {{16#12,16#34,16#56,16#78},"0x12.0x345678"},
 
481
         {{16#12,16#34,16#56,16#78},"0x12.0X34.0x5678"},
 
482
         {{16#12,16#34,16#56,16#78},"0x12.0X34.0x56.0X78"},
 
483
         {{0,0,0,0},"0"},
 
484
         {{0,0,0,0},"00"},
 
485
         {{0,0,0,0},"0.0"},
 
486
         {{0,0,0,0},"00.00.00"},
 
487
         {{0,0,0,0},"0.00.0.0"},
 
488
         {{0,0,0,0},"0.0.000000000000.0"}],
 
489
    V6Sloppy =
 
490
        [{{0,0,0,0,0,65535,(D1 bsl 8) bor D2,(D3 bsl 8) bor D4},S}
 
491
         || {{D1,D2,D3,D4},S} <- V4Strict++V4Sloppy],
 
492
    V4Err =
 
493
        ["0.256.0.1",
 
494
         "1.2.3.4.5",
 
495
         "256.255.65535",
 
496
         "4294967296",
 
497
         "0x100000000",
 
498
         "040000000000",
 
499
         "1.2.3.-4",
 
500
         "1.2.-3.4",
 
501
         "1.-2.3.4",
 
502
         "-1.2.3.4",
 
503
         "10.",
 
504
         "172.16.",
 
505
         "198.168.0.",
 
506
         "127.0.0.1."],
 
507
    V6Err =
 
508
        [":::",
 
509
         "f:::2",
 
510
         "::-1",
 
511
         "::g",
 
512
         "f:f11::10100:2",
 
513
         "::17000",
 
514
         "10000::",
 
515
         "::8:7:6:5:4:3:2:1",
 
516
         "8:7:6:5:4:3:2:1::",
 
517
         "8:7:6:5:4::3:2:1",
 
518
         "::1.2.3.4.5",
 
519
         "::1.2.3.04",
 
520
         "::1.256.3.4",
 
521
         "::-5.4.3.2",
 
522
         "::5.-4.3.2",
 
523
         "::5.4.-3.2",
 
524
         "::5.4.3.-2",
 
525
         "::FFFF:1.2.3.4.5",
 
526
         "::10.",
 
527
         "::FFFF:172.16.",
 
528
         "fe80::198.168.0.",
 
529
         "fec0::fFfF:127.0.0.1."],
 
530
    t_parse_address
 
531
      (ipv6_address,
 
532
       V6Strict++V6Sloppy++V6Err++V4Err),
 
533
    t_parse_address
 
534
      (ipv6strict_address,
 
535
       V6Strict++V6Err++V4Err++[S || {_,S} <- V6Sloppy]),
 
536
    t_parse_address
 
537
      (ipv4_address,
 
538
       V4Strict++V4Sloppy++V4Err++V6Err++[S || {_,S} <- V6Strict]),
 
539
    t_parse_address
 
540
      (ipv4strict_address,
 
541
       V4Strict++V4Err++V6Err++[S || {_,S} <- V4Sloppy++V6Strict]).
 
542
 
 
543
t_parse_address(Func, []) ->
 
544
    io:format("~p done.~n", [Func]),
 
545
    ok;
 
546
t_parse_address(Func, [{Addr,String}|L]) ->
 
547
    io:format("~p = ~p.~n", [Addr,String]),
 
548
    {ok,Addr} = inet_parse:Func(String),
 
549
    t_parse_address(Func, L);
 
550
t_parse_address(Func, [String|L]) ->
 
551
    io:format("~p.~n", [String]),
 
552
    {error,einval} = inet_parse:Func(String),
 
553
    t_parse_address(Func, L).
 
554
 
 
555
 
 
556
 
391
557
t_gethostnative(suite) ->[];
392
558
t_gethostnative(doc) ->[];
393
559
t_gethostnative(Config) when is_list(Config) ->