~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to lib/inets/test/ftp_suite_lib.erl

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
3
%% 
4
 
%% Copyright Ericsson AB 2005-2010. All Rights Reserved.
 
4
%% Copyright Ericsson AB 2005-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
-module(ftp_suite_lib).
22
22
 
23
23
 
24
 
-include("test_server.hrl").
25
 
-include("test_server_line.hrl").
 
24
-include_lib("test_server/include/test_server.hrl").
 
25
-include_lib("test_server/include/test_server_line.hrl").
26
26
-include("inets_test_lib.hrl").
27
27
 
28
28
%% Test server specific exports
74
74
ftpd_init(FtpdTag, Config) ->
75
75
    %% Get the host name(s) of FTP server
76
76
    Hosts = 
77
 
        case ?config(ftpd_hosts, Config) of
 
77
        case ct:get_config(ftpd_hosts) of
78
78
            undefined ->
79
79
                ftpd_hosts(data_dir(Config));
80
80
            H ->
129
129
 
130
130
dirty_select_ftpd_host(Config) ->
131
131
    Hosts = 
132
 
        case ?config(ftpd_hosts, Config) of
 
132
        case ct:get_config(ftpd_hosts) of
133
133
            undefined ->
134
134
                ftpd_hosts(data_dir(Config));
135
135
            H ->
196
196
%% variable, but should NOT alter/remove any existing entries.
197
197
%%--------------------------------------------------------------------
198
198
init_per_testcase(Case, Config) 
199
 
  when (Case =:= open) orelse (Case =:= open_port) ->
 
199
  when (Case =:= open) orelse 
 
200
       (Case =:= open_port) ->
 
201
    put(ftp_testcase, Case), 
200
202
    io:format(user, "~n~n*** INIT ~w:~w ***~n~n", [?MODULE, Case]),
201
203
    inets:start(),
202
204
    NewConfig = data_dir(Config),
266
268
        end,
267
269
    Opts2 = 
268
270
        case string:tokens(atom_to_list(Case), [$_]) of
269
 
            [_, "active" | _] ->
 
271
            ["active" | _] ->
270
272
                [{mode, active}  | Opts1];
271
273
            _ ->
272
274
                [{mode, passive} | Opts1]
367
369
 
368
370
 
369
371
tc_open(Host) ->
 
372
    p("tc_open -> entry with"
 
373
      "~n   Host: ~p", [Host]),
370
374
    {ok, Pid} = ?ftp_open(Host, []),
371
375
    ok = ftp:close(Pid),
 
376
    p("tc_open -> try (ok) open 1"),
372
377
    {ok, Pid1} = 
373
378
        ftp:open({option_list, [{host,Host}, 
374
379
                                {port, ?FTP_PORT}, 
376
381
                                {timeout, 30000}]}),
377
382
    ok = ftp:close(Pid1),
378
383
    
 
384
    p("tc_open -> try (fail) open 2"),
379
385
    {error, ehost} = 
380
386
        ftp:open({option_list, [{port, ?FTP_PORT}, {flags, [verbose]}]}),
381
387
    {ok, Pid2} = ftp:open(Host),
382
388
    ok = ftp:close(Pid2),
383
389
    
 
390
    p("tc_open -> try (ok) open 3"),
384
391
    {ok, NewHost} = inet:getaddr(Host, inet),
385
392
    {ok, Pid3} = ftp:open(NewHost),
386
393
    ftp:user(Pid3, ?FTP_USER, ?FTP_PASS),
392
399
 
393
400
    %% Bad input that has default values are ignored and the defult 
394
401
    %% is used.
 
402
    p("tc_open -> try (ok) open 4"),
395
403
    {ok, Pid4} = 
396
 
        ftp:open({option_list, [{host, Host}, {port, badarg}, 
397
 
                                {flags, [verbose]}, 
 
404
        ftp:open({option_list, [{host,    Host}, 
 
405
                                {port,    badarg}, 
 
406
                                {flags,   [verbose]}, 
398
407
                                {timeout, 30000}]}),
399
408
    test_server:sleep(100),
400
409
    ok = ftp:close(Pid4),
 
410
 
 
411
    p("tc_open -> try (ok) open 5"),
401
412
    {ok, Pid5} = 
402
 
        ftp:open({option_list, [{host, Host}, {port, ?FTP_PORT}, 
403
 
                                {flags, [verbose]}, 
 
413
        ftp:open({option_list, [{host,    Host}, 
 
414
                                {port,    ?FTP_PORT}, 
 
415
                                {flags,   [verbose]}, 
404
416
                                {timeout, -42}]}),
405
417
    test_server:sleep(100),
406
418
    ok = ftp:close(Pid5),
 
419
 
 
420
    p("tc_open -> try (ok) open 6"),
407
421
    {ok, Pid6} = 
408
 
        ftp:open({option_list, [{host, Host}, {port, ?FTP_PORT}, 
 
422
        ftp:open({option_list, [{host,  Host}, 
 
423
                                {port,  ?FTP_PORT}, 
409
424
                                {flags, [verbose]}, 
410
 
                                {mode, cool}]}),
 
425
                                {mode,  cool}]}),
411
426
    test_server:sleep(100),
412
427
    ok = ftp:close(Pid6),
413
428
 
 
429
    p("tc_open -> try (ok) open 7"),
414
430
    {ok, Pid7} = 
415
431
        ftp:open(Host, [{port, ?FTP_PORT}, {verbose, true}, {timeout, 30000}]),
416
432
    ok = ftp:close(Pid7),
417
433
 
 
434
    p("tc_open -> try (ok) open 8"),
418
435
    {ok, Pid8} = 
419
436
        ftp:open(Host, ?FTP_PORT),
420
437
    ok = ftp:close(Pid8),
421
438
 
 
439
    p("tc_open -> try (ok) open 9"),
 
440
    {ok, Pid9} = 
 
441
        ftp:open(Host, [{port,     ?FTP_PORT}, 
 
442
                        {verbose,  true}, 
 
443
                        {timeout,  30000}, 
 
444
                        {dtimeout, -99}]),
 
445
    ok = ftp:close(Pid9),
 
446
 
 
447
    p("tc_open -> try (ok) open 10"),
 
448
    {ok, Pid10} = 
 
449
        ftp:open(Host, [{port,     ?FTP_PORT}, 
 
450
                        {verbose,  true}, 
 
451
                        {timeout,  30000}, 
 
452
                        {dtimeout, "foobar"}]),
 
453
    ok = ftp:close(Pid10),
 
454
 
 
455
    p("tc_open -> try (ok) open 11"),
 
456
    {ok, Pid11} = 
 
457
        ftp:open(Host, [{port,     ?FTP_PORT}, 
 
458
                        {verbose,  true}, 
 
459
                        {timeout,  30000}, 
 
460
                        {dtimeout, 1}]),
 
461
    ok = ftp:close(Pid11),
 
462
 
 
463
    p("tc_open -> done"),
422
464
    ok.
423
465
 
424
466
    
445
487
    [];
446
488
passive_user(Config) when is_list(Config) ->
447
489
    Pid = ?config(ftp, Config),
448
 
    io:format("Pid: ~p~n",[Pid]),
 
490
    p("Pid: ~p",[Pid]),
449
491
    do_user(Pid).
450
492
 
451
493
 
967
1009
    ["Test that behaviour of the ftp process if the api is abused"];
968
1010
api_missuse(suite) -> [];
969
1011
api_missuse(Config) when is_list(Config) ->
970
 
    io:format("api_missuse -> entry~n", []),
 
1012
    p("api_missuse -> entry"),
971
1013
    Flag =  process_flag(trap_exit, true),
972
1014
    Pid = ?config(ftp, Config),
973
1015
    Host = ftp_host(Config), 
974
1016
    
975
1017
    %% Serious programming fault, connetion will be shut down 
976
 
    io:format("api_missuse -> verify bad call termination (~p)~n", [Pid]),
 
1018
    p("api_missuse -> verify bad call termination (~p)", [Pid]),
977
1019
    case (catch gen_server:call(Pid, {self(), foobar, 10}, infinity)) of
978
1020
        {error, {connection_terminated, 'API_violation'}} ->
979
1021
            ok;
983
1025
    test_server:sleep(500),
984
1026
    undefined = process_info(Pid, status),
985
1027
 
986
 
    io:format("api_missuse -> start new client~n", []),
 
1028
    p("api_missuse -> start new client"),
987
1029
    {ok, Pid2} =  ?ftp_open(Host, []),
988
1030
    %% Serious programming fault, connetion will be shut down 
989
 
    io:format("api_missuse -> verify bad cast termination~n", []),
 
1031
    p("api_missuse -> verify bad cast termination"),
990
1032
    gen_server:cast(Pid2, {self(), foobar, 10}),
991
1033
    test_server:sleep(500),
992
1034
    undefined = process_info(Pid2, status),
993
1035
 
994
 
    io:format("api_missuse -> start new client~n", []),
 
1036
    p("api_missuse -> start new client"),
995
1037
    {ok, Pid3} =  ?ftp_open(Host, []),
996
1038
    %% Could be an innocent misstake the connection lives. 
997
 
    io:format("api_missuse -> verify bad bang~n", []),
 
1039
    p("api_missuse -> verify bad bang"),
998
1040
    Pid3 ! foobar, 
999
1041
    test_server:sleep(500),
1000
1042
    {status, _} = process_info(Pid3, status),
1001
1043
    process_flag(trap_exit, Flag),
1002
 
    io:format("api_missuse -> done~n", []),
 
1044
    p("api_missuse -> done"),
1003
1045
    ok.
1004
1046
 
1005
1047
 
1129
1171
    LogFile = filename:join([PrivDir,"ticket_6035.log"]),
1130
1172
    try
1131
1173
        begin
 
1174
            p("ticket_6035 -> select ftpd host"),
1132
1175
            Host = dirty_select_ftpd_host(Config), 
 
1176
            p("ticket_6035 -> ftpd host selected (~p) => now spawn ftp owner", [Host]),
1133
1177
            Pid  = spawn(?MODULE, open_wait_6035, [Host, self()]),
 
1178
            p("ticket_6035 -> waiter spawned: ~p => now open error logfile (~p)", 
 
1179
              [Pid, LogFile]),
1134
1180
            error_logger:logfile({open, LogFile}),
1135
 
            ok = kill_ftp_proc_6035(Pid,LogFile),
 
1181
            p("ticket_6035 -> error logfile open => now kill waiter process"),
 
1182
            true = kill_ftp_proc_6035(Pid, LogFile),
 
1183
            p("ticket_6035 -> waiter process killed => now close error logfile"),
1136
1184
            error_logger:logfile(close),
1137
1185
            p("ticket_6035 -> done", []),
1138
1186
            ok
1146
1194
    p("kill_ftp_proc_6035 -> entry"),
1147
1195
    receive
1148
1196
        open ->
1149
 
            p("kill_ftp_proc_6035 -> received open: send shutdown"),
 
1197
            p("kill_ftp_proc_6035 -> received open => now issue shutdown"),
1150
1198
            exit(Pid, shutdown),
1151
1199
            kill_ftp_proc_6035(Pid, LogFile);
1152
1200
        {open_failed, Reason} ->
1159
1207
            is_error_report_6035(LogFile)
1160
1208
    end.
1161
1209
 
1162
 
open_wait_6035(FtpServer, From) ->
1163
 
    p("open_wait_6035 -> try connect to ~s", [FtpServer]),
 
1210
open_wait_6035({Tag, FtpServer}, From) ->
 
1211
    p("open_wait_6035 -> try connect to [~p] ~s for ~p", [Tag, FtpServer, From]),
1164
1212
    case ftp:open(FtpServer, [{timeout, timer:seconds(15)}]) of
1165
1213
        {ok, Pid} ->
1166
 
            p("open_wait_6035 -> connected, now login"),
 
1214
            p("open_wait_6035 -> connected (~p), now login", [Pid]),
1167
1215
            LoginResult = ftp:user(Pid,"anonymous","kldjf"),
1168
1216
            p("open_wait_6035 -> login result: ~p", [LoginResult]),
1169
1217
            From ! open,
1191
1239
    Res =
1192
1240
        case file:read_file(LogFile) of
1193
1241
            {ok, Bin} ->
1194
 
                p("is_error_report_6035 -> logfile read"),
1195
 
                read_log_6035(binary_to_list(Bin));
 
1242
                Txt = binary_to_list(Bin), 
 
1243
                p("is_error_report_6035 -> logfile read: ~n~p", [Txt]),
 
1244
                read_log_6035(Txt);
1196
1245
            _ ->
1197
 
                ok
 
1246
                false
1198
1247
        end,
1199
1248
    p("is_error_report_6035 -> logfile read result: "
1200
1249
      "~n   ~p", [Res]),
1201
 
    file:delete(LogFile),
 
1250
    %% file:delete(LogFile),
1202
1251
    Res.
1203
1252
 
1204
1253
read_log_6035("=ERROR REPORT===="++_Rest) ->
1205
 
    error_report;
1206
 
read_log_6035([_H|T]) ->
 
1254
    p("read_log_6035 -> ERROR REPORT detected"),
 
1255
    true;
 
1256
read_log_6035([H|T]) ->
 
1257
    p("read_log_6035 -> OTHER: "
 
1258
      "~p", [H]),
1207
1259
    read_log_6035(T);
1208
1260
read_log_6035([]) ->
1209
 
    ok.
 
1261
    p("read_log_6035 -> done"),
 
1262
    false.
1210
1263
 
1211
1264
 
1212
1265
%%--------------------------------------------------------------------
1556
1609
    lists:reverse([lists:reverse(I)| Is]).
1557
1610
 
1558
1611
do_ftp_open(Host, Opts) ->
1559
 
    io:format("do_ftp_open -> entry with"
1560
 
              "~n   Host: ~p"
1561
 
              "~n   Opts: ~p", [Host, Opts]), 
 
1612
    p("do_ftp_open -> entry with"
 
1613
      "~n   Host: ~p"
 
1614
      "~n   Opts: ~p", [Host, Opts]), 
1562
1615
    case ftp:open(Host, Opts) of
1563
1616
        {ok, _} = OK ->
1564
1617
            OK;
1584
1637
ftpd_hosts(Config) ->
1585
1638
    DataDir = ?config(data_dir, Config),
1586
1639
    FileName = filename:join([DataDir, "../ftp_SUITE_data/", ftpd_hosts]),
1587
 
    io:format("FileName: ~p~n", [FileName]),
 
1640
    p("FileName: ~p", [FileName]),
1588
1641
    case file:consult(FileName) of
1589
1642
        {ok, [Hosts]} when is_list(Hosts) ->
1590
1643
            Hosts;