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

« back to all changes in this revision

Viewing changes to lib/inets/test/ftp_suite_lib.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
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 2005-2011. All Rights Reserved.
 
5
%% 
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%% 
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%% 
 
17
%% %CopyrightEnd%
 
18
%%
 
19
%%
 
20
 
 
21
-module(ftp_suite_lib).
 
22
 
 
23
 
 
24
-include_lib("test_server/include/test_server.hrl").
 
25
-include_lib("test_server/include/test_server_line.hrl").
 
26
-include("inets_test_lib.hrl").
 
27
 
 
28
%% Test server specific exports
 
29
% -export([init_per_testcase/2, end_per_testcase/2]).
 
30
 
 
31
-compile(export_all).
 
32
 
 
33
 
 
34
-record(progress, {
 
35
          current = 0,
 
36
          total
 
37
         }).
 
38
 
 
39
 
 
40
 
 
41
-define(FTP_USER, "anonymous").
 
42
-define(FTP_PASS, passwd()).
 
43
-define(FTP_PORT, 21).
 
44
 
 
45
-define(BAD_HOST, "badhostname").
 
46
-define(BAD_USER, "baduser").
 
47
-define(BAD_DIR,  "baddirectory").
 
48
 
 
49
-ifdef(ftp_debug_client).
 
50
-define(ftp_open(Host, Flags), 
 
51
        do_ftp_open(Host, [{debug, debug}, 
 
52
                           {timeout, timer:seconds(15)} | Flags])).
 
53
-else.
 
54
-ifdef(ftp_trace_client).
 
55
-define(ftp_open(Host, Flags), 
 
56
        do_ftp_open(Host, [{debug, trace}, 
 
57
                           {timeout, timer:seconds(15)} | Flags])).
 
58
-else.
 
59
-define(ftp_open(Host, Flags), 
 
60
        do_ftp_open(Host, [{verbose, true}, 
 
61
                           {timeout, timer:seconds(15)} | Flags])).
 
62
-endif.
 
63
-endif.
 
64
 
 
65
%% -- Tickets --
 
66
 
 
67
tickets(doc) ->
 
68
     "Test cases for reported bugs";
 
69
tickets(suite) ->
 
70
     [ticket_6035].
 
71
 
 
72
%% --
 
73
 
 
74
ftpd_init(FtpdTag, Config) ->
 
75
    %% Get the host name(s) of FTP server
 
76
    Hosts = 
 
77
        case ct:get_config(ftpd_hosts) of
 
78
            undefined ->
 
79
                ftpd_hosts(data_dir(Config));
 
80
            H ->
 
81
                H
 
82
        end,
 
83
    p("ftpd_init -> "
 
84
      "~n   Hosts:   ~p"
 
85
      "~n   Config:  ~p"
 
86
      "~n   FtpdTag: ~p", [Hosts, Config, FtpdTag]),
 
87
    %% Get the first host that actually have a running FTP server
 
88
    case lists:keysearch(FtpdTag, 1, Hosts) of
 
89
        {value, {_, TagHosts}} when is_list(TagHosts) ->
 
90
            inets:start(),
 
91
            case (catch get_ftpd_host(TagHosts)) of
 
92
                {ok, Host} ->
 
93
                    inets:stop(),
 
94
                    [{ftp_remote_host, Host}|Config];
 
95
                _ ->
 
96
                    inets:stop(),
 
97
                    Reason = lists:flatten(
 
98
                               io_lib:format("Could not find a valid "
 
99
                                             "FTP server for ~p (~p)", 
 
100
                                             [FtpdTag, TagHosts])),
 
101
                    {skip, Reason}
 
102
            end;
 
103
        _ ->
 
104
            Reason = lists:flatten(
 
105
                       io_lib:format("No host(s) running FTPD server "
 
106
                                     "for ~p", [FtpdTag])),
 
107
            {skip, Reason}
 
108
    end.
 
109
 
 
110
ftpd_fin(Config) ->
 
111
    lists:keydelete(ftp_remote_host, 1, Config).
 
112
 
 
113
get_ftpd_host([]) ->    
 
114
    {error, no_host};
 
115
get_ftpd_host([Host|Hosts]) -> 
 
116
    p("get_ftpd_host -> entry with"
 
117
      "~n   Host: ~p"
 
118
      "~n", [Host]),
 
119
    case (catch ftp:open(Host, [{port, ?FTP_PORT}, {timeout, 20000}])) of
 
120
        {ok, Pid} ->
 
121
            (catch ftp:close(Pid)),
 
122
            {ok, Host};
 
123
        _ ->
 
124
            get_ftpd_host(Hosts)
 
125
    end.
 
126
 
 
127
 
 
128
%%--------------------------------------------------------------------
 
129
 
 
130
dirty_select_ftpd_host(Config) ->
 
131
    Hosts = 
 
132
        case ct:get_config(ftpd_hosts) of
 
133
            undefined ->
 
134
                ftpd_hosts(data_dir(Config));
 
135
            H ->
 
136
                H
 
137
        end,
 
138
    dirty_select_ftpd_host2(Hosts).
 
139
 
 
140
dirty_select_ftpd_host2([]) ->
 
141
    throw({error, not_found});
 
142
dirty_select_ftpd_host2([{PlatformTag, Hosts} | PlatformHosts]) ->
 
143
    case dirty_select_ftpd_host3(Hosts) of
 
144
        none ->
 
145
            dirty_select_ftpd_host2(PlatformHosts);
 
146
        {ok, Host} ->
 
147
            {PlatformTag, Host}
 
148
    end.
 
149
 
 
150
dirty_select_ftpd_host3([]) ->
 
151
    none;
 
152
dirty_select_ftpd_host3([Host|Hosts]) when is_list(Host) ->
 
153
    case dirty_select_ftpd_host4(Host) of
 
154
        true ->
 
155
            {ok, Host};
 
156
        false ->
 
157
            dirty_select_ftpd_host3(Hosts)
 
158
    end;
 
159
dirty_select_ftpd_host3([_|Hosts]) ->
 
160
    dirty_select_ftpd_host3(Hosts).
 
161
 
 
162
%% This is a very simple and dirty test that there is a 
 
163
%% (FTP) deamon on the other end.
 
164
dirty_select_ftpd_host4(Host) ->
 
165
    Port    = 21, 
 
166
    IpFam   = inet, 
 
167
    Opts    = [IpFam, binary, {packet, 0}, {active, false}],
 
168
    Timeout = ?SECS(5),
 
169
    case gen_tcp:connect(Host, Port, Opts, Timeout) of
 
170
        {ok, Sock} ->
 
171
            gen_tcp:close(Sock),
 
172
            true;
 
173
        _Error ->
 
174
            false
 
175
    end.
 
176
 
 
177
 
 
178
%%--------------------------------------------------------------------
 
179
 
 
180
test_filenames() ->
 
181
    {ok, Host} = inet:gethostname(),
 
182
    File = Host ++ "_ftp_test.txt",
 
183
    NewFile = "new_" ++ File,
 
184
    {File, NewFile}.
 
185
 
 
186
%%--------------------------------------------------------------------
 
187
%% Function: init_per_testcase(Case, Config) -> Config
 
188
%% Case - atom()
 
189
%%   Name of the test case that is about to be run.
 
190
%% Config - [tuple()]
 
191
%%   A list of key/value pairs, holding the test case configuration.
 
192
%%
 
193
%% Description: Initiation before each test case
 
194
%%
 
195
%% Note: This function is free to add any key/value pairs to the Config
 
196
%% variable, but should NOT alter/remove any existing entries.
 
197
%%--------------------------------------------------------------------
 
198
init_per_testcase(Case, Config) 
 
199
  when (Case =:= open) orelse (Case =:= open_port) ->
 
200
    io:format(user, "~n~n*** INIT ~w:~w ***~n~n", [?MODULE, Case]),
 
201
    inets:start(),
 
202
    NewConfig = data_dir(Config),
 
203
    watch_dog(NewConfig);
 
204
 
 
205
init_per_testcase(Case, Config)  ->
 
206
    put(ftp_testcase, Case), 
 
207
    inets:enable_trace(max, io, ftpc),
 
208
    do_init_per_testcase(Case, Config).
 
209
 
 
210
do_init_per_testcase(Case, Config)  
 
211
   when (Case =:= passive_user) ->
 
212
    io:format(user, "~n~n*** INIT ~w:~w ***~n~n", [?MODULE,Case]),
 
213
    inets:start(),
 
214
    NewConfig = close_connection(watch_dog(Config)),
 
215
    Host = ftp_host(Config), 
 
216
    case (catch ?ftp_open(Host, [{mode, passive}])) of
 
217
        {ok, Pid} ->
 
218
            [{ftp, Pid} | data_dir(NewConfig)];
 
219
        {skip, _} = SKIP ->
 
220
            SKIP
 
221
    end;
 
222
 
 
223
do_init_per_testcase(Case, Config)  
 
224
  when (Case =:= active_user) ->
 
225
    io:format(user, "~n~n*** INIT ~w:~w ***~n~n", [?MODULE, Case]),
 
226
    inets:start(),
 
227
    NewConfig = close_connection(watch_dog(Config)),
 
228
    Host = ftp_host(Config), 
 
229
    case (catch ?ftp_open(Host, [{mode, active}])) of
 
230
        {ok, Pid} ->
 
231
            [{ftp, Pid} | data_dir(NewConfig)];
 
232
        {skip, _} = SKIP ->
 
233
            SKIP
 
234
    end;
 
235
 
 
236
do_init_per_testcase(Case, Config) 
 
237
  when (Case =:= progress_report_send) orelse 
 
238
       (Case =:= progress_report_recv) ->
 
239
    inets:start(),
 
240
    io:format(user, "~n~n*** INIT ~w:~w ***~n~n", [?MODULE, Case]),
 
241
    NewConfig = close_connection(watch_dog(Config)),
 
242
    Host = ftp_host(Config), 
 
243
    Opts = [{port,     ?FTP_PORT},
 
244
            {verbose,  true},
 
245
            {progress, {?MODULE, progress, #progress{}}}], 
 
246
    case ftp:open(Host, Opts) of
 
247
        {ok, Pid} ->
 
248
            ok = ftp:user(Pid, ?FTP_USER, ?FTP_PASS),
 
249
            [{ftp, Pid} | data_dir(NewConfig)];
 
250
        {skip, _} = SKIP ->
 
251
            SKIP
 
252
    end;
 
253
 
 
254
do_init_per_testcase(Case, Config) ->
 
255
    io:format(user,"~n~n*** INIT ~w:~w ***~n~n", [?MODULE, Case]),
 
256
    inets:start(),
 
257
    NewConfig = close_connection(watch_dog(Config)),
 
258
    Host = ftp_host(Config), 
 
259
    Opts1 = 
 
260
        if 
 
261
            ((Case =:= passive_ip_v6_disabled) orelse
 
262
             (Case =:= active_ip_v6_disabled)) ->
 
263
                [{ipfamily, inet}];
 
264
            true ->
 
265
                []
 
266
        end,
 
267
    Opts2 = 
 
268
        case string:tokens(atom_to_list(Case), [$_]) of
 
269
            [_, "active" | _] ->
 
270
                [{mode, active}  | Opts1];
 
271
            _ ->
 
272
                [{mode, passive} | Opts1]
 
273
        end,
 
274
    case (catch ?ftp_open(Host, Opts2)) of
 
275
        {ok, Pid} ->
 
276
            ok = ftp:user(Pid, ?FTP_USER, ?FTP_PASS),
 
277
            [{ftp, Pid} | data_dir(NewConfig)];
 
278
        {skip, _} = SKIP ->
 
279
            SKIP
 
280
    end.
 
281
 
 
282
 
 
283
%%--------------------------------------------------------------------
 
284
%% Function: end_per_testcase(Case, Config) -> _
 
285
%% Case - atom()
 
286
%%   Name of the test case that is about to be run.
 
287
%% Config - [tuple()]
 
288
%%   A list of key/value pairs, holding the test case configuration.
 
289
%% Description: Cleanup after each test case
 
290
%%--------------------------------------------------------------------
 
291
end_per_testcase(_, Config) ->  
 
292
    NewConfig = close_connection(Config),
 
293
    Dog = ?config(watchdog, NewConfig),
 
294
    inets:stop(),
 
295
    test_server:timetrap_cancel(Dog),
 
296
    ok.
 
297
 
 
298
 
 
299
%%-------------------------------------------------------------------------
 
300
%% Suites similar for all hosts.
 
301
%%-------------------------------------------------------------------------
 
302
 
 
303
passive(suite) ->
 
304
    [
 
305
     passive_user, 
 
306
     passive_pwd, 
 
307
     passive_cd, 
 
308
     passive_lcd,
 
309
     passive_ls, 
 
310
     passive_nlist, 
 
311
     passive_rename, 
 
312
     passive_delete, 
 
313
     passive_mkdir, 
 
314
     passive_send, 
 
315
     passive_send_bin, 
 
316
     passive_send_chunk, 
 
317
     passive_append, 
 
318
     passive_append_bin,
 
319
     passive_append_chunk, 
 
320
     passive_recv, 
 
321
     passive_recv_bin, 
 
322
     passive_recv_chunk, 
 
323
     passive_type, 
 
324
     passive_quote, 
 
325
     passive_ip_v6_disabled
 
326
    ].
 
327
 
 
328
active(suite) ->
 
329
    [
 
330
     active_user, 
 
331
     active_pwd, 
 
332
     active_cd,
 
333
     active_lcd, 
 
334
     active_ls, 
 
335
     active_nlist, 
 
336
     active_rename, 
 
337
     active_delete, 
 
338
     active_mkdir, 
 
339
     active_send, 
 
340
     active_send_bin, 
 
341
     active_send_chunk, 
 
342
     active_append, 
 
343
     active_append_bin, 
 
344
     active_append_chunk, 
 
345
     active_recv, 
 
346
     active_recv_bin, 
 
347
     active_recv_chunk, 
 
348
     active_type, 
 
349
     active_quote, 
 
350
     active_ip_v6_disabled
 
351
    ].
 
352
 
 
353
 
 
354
 
 
355
%%-------------------------------------------------------------------------
 
356
%% Test cases starts here.
 
357
%%-------------------------------------------------------------------------
 
358
 
 
359
open(doc) ->
 
360
    ["Open an ftp connection to a host and close the connection."
 
361
     "Also check that !-messages does not disturbe the connection"];
 
362
open(suite) ->
 
363
    [];
 
364
open(Config) when is_list(Config) ->
 
365
    Host = ftp_host(Config), 
 
366
    (catch tc_open(Host)).
 
367
 
 
368
 
 
369
tc_open(Host) ->
 
370
    {ok, Pid} = ?ftp_open(Host, []),
 
371
    ok = ftp:close(Pid),
 
372
    {ok, Pid1} = 
 
373
        ftp:open({option_list, [{host,Host}, 
 
374
                                {port, ?FTP_PORT}, 
 
375
                                {flags, [verbose]}, 
 
376
                                {timeout, 30000}]}),
 
377
    ok = ftp:close(Pid1),
 
378
    
 
379
    {error, ehost} = 
 
380
        ftp:open({option_list, [{port, ?FTP_PORT}, {flags, [verbose]}]}),
 
381
    {ok, Pid2} = ftp:open(Host),
 
382
    ok = ftp:close(Pid2),
 
383
    
 
384
    {ok, NewHost} = inet:getaddr(Host, inet),
 
385
    {ok, Pid3} = ftp:open(NewHost),
 
386
    ftp:user(Pid3, ?FTP_USER, ?FTP_PASS),
 
387
    Pid3 ! foobar,
 
388
    test_server:sleep(5000),
 
389
    {message_queue_len, 0} = process_info(self(), message_queue_len),
 
390
    ["200" ++ _] = ftp:quote(Pid3, "NOOP"),
 
391
    ok = ftp:close(Pid3),
 
392
 
 
393
    %% Bad input that has default values are ignored and the defult 
 
394
    %% is used.
 
395
    {ok, Pid4} = 
 
396
        ftp:open({option_list, [{host, Host}, {port, badarg}, 
 
397
                                {flags, [verbose]}, 
 
398
                                {timeout, 30000}]}),
 
399
    test_server:sleep(100),
 
400
    ok = ftp:close(Pid4),
 
401
    {ok, Pid5} = 
 
402
        ftp:open({option_list, [{host, Host}, {port, ?FTP_PORT}, 
 
403
                                {flags, [verbose]}, 
 
404
                                {timeout, -42}]}),
 
405
    test_server:sleep(100),
 
406
    ok = ftp:close(Pid5),
 
407
    {ok, Pid6} = 
 
408
        ftp:open({option_list, [{host, Host}, {port, ?FTP_PORT}, 
 
409
                                {flags, [verbose]}, 
 
410
                                {mode, cool}]}),
 
411
    test_server:sleep(100),
 
412
    ok = ftp:close(Pid6),
 
413
 
 
414
    {ok, Pid7} = 
 
415
        ftp:open(Host, [{port, ?FTP_PORT}, {verbose, true}, {timeout, 30000}]),
 
416
    ok = ftp:close(Pid7),
 
417
 
 
418
    {ok, Pid8} = 
 
419
        ftp:open(Host, ?FTP_PORT),
 
420
    ok = ftp:close(Pid8),
 
421
 
 
422
    ok.
 
423
 
 
424
    
 
425
%%-------------------------------------------------------------------------
 
426
 
 
427
open_port(doc) ->
 
428
    ["Open an ftp connection to a host with given port number "
 
429
     "and close the connection."]; % See also OTP-3892 
 
430
open_port(suite) ->
 
431
    [];
 
432
open_port(Config) when is_list(Config) ->
 
433
    Host = ftp_host(Config), 
 
434
    {ok, Pid} = ftp:open(Host, [{port, ?FTP_PORT}]),
 
435
    ok = ftp:close(Pid),
 
436
    {error, ehost} = ftp:open(?BAD_HOST, []),
 
437
    ok.
 
438
 
 
439
 
 
440
%%-------------------------------------------------------------------------
 
441
 
 
442
passive_user(doc) ->
 
443
    ["Open an ftp connection to a host, and logon as anonymous ftp."];
 
444
passive_user(suite) ->
 
445
    [];
 
446
passive_user(Config) when is_list(Config) ->
 
447
    Pid = ?config(ftp, Config),
 
448
    io:format("Pid: ~p~n",[Pid]),
 
449
    do_user(Pid).
 
450
 
 
451
 
 
452
%%-------------------------------------------------------------------------
 
453
    
 
454
passive_pwd(doc) ->
 
455
    ["Test ftp:pwd/1 & ftp:lpwd/1"];
 
456
passive_pwd(suite) ->
 
457
    [];
 
458
passive_pwd(Config) when is_list(Config) ->
 
459
    Pid = ?config(ftp, Config),
 
460
    do_pwd(Pid).
 
461
 
 
462
 
 
463
%%-------------------------------------------------------------------------
 
464
 
 
465
passive_cd(doc) ->
 
466
    ["Open an ftp connection, log on as anonymous ftp, and cd to the"
 
467
     "directory \"/pub\" and the to the  non-existent directory."];
 
468
passive_cd(suite) ->
 
469
    [];
 
470
passive_cd(Config) when is_list(Config) ->
 
471
    Pid = ?config(ftp, Config),
 
472
    do_cd(Pid).
 
473
 
 
474
 
 
475
%%-------------------------------------------------------------------------
 
476
 
 
477
passive_lcd(doc) ->
 
478
    ["Test api function ftp:lcd/2"];
 
479
passive_lcd(suite) ->
 
480
    [];
 
481
passive_lcd(Config) when is_list(Config) ->
 
482
    Pid = ?config(ftp, Config),
 
483
    PrivDir = ?config(priv_dir, Config),
 
484
    do_lcd(Pid, PrivDir).
 
485
 
 
486
 
 
487
%%-------------------------------------------------------------------------
 
488
 
 
489
passive_ls(doc) ->
 
490
    ["Open an ftp connection; ls the current directory, and the "
 
491
     "\"incoming\" directory. We assume that ls never fails, since "
 
492
     "it's output is meant to be read by humans. "];
 
493
passive_ls(suite) ->
 
494
    [];
 
495
passive_ls(Config) when is_list(Config) ->
 
496
    Pid = ?config(ftp, Config),
 
497
    do_ls(Pid).
 
498
 
 
499
 
 
500
%%-------------------------------------------------------------------------
 
501
 
 
502
passive_nlist(doc) ->
 
503
    ["Open an ftp connection; nlist the current directory, and the "
 
504
     "\"incoming\" directory. Nlist does not behave consistenly over "
 
505
     "operating systems. On some it is an error to have an empty "
 
506
     "directory."];
 
507
passive_nlist(suite) ->
 
508
    [];
 
509
passive_nlist(Config) when is_list(Config) ->
 
510
    Pid = ?config(ftp, Config),
 
511
    WildcardSupport = ?config(wildcard_support, Config),
 
512
    do_nlist(Pid, WildcardSupport).
 
513
 
 
514
 
 
515
%%-------------------------------------------------------------------------
 
516
 
 
517
passive_rename(doc) ->
 
518
    ["Transfer a file to the server, and rename it; then remove it."];
 
519
passive_rename(suite) ->
 
520
    [];
 
521
passive_rename(Config) when is_list(Config) ->
 
522
    Pid = ?config(ftp, Config),
 
523
    do_rename(Pid, Config).
 
524
    
 
525
 
 
526
%%-------------------------------------------------------------------------
 
527
 
 
528
passive_delete(doc) ->
 
529
    ["Transfer a file to the server, and then delete it"];
 
530
passive_delete(suite) ->
 
531
    [];
 
532
passive_delete(Config) when is_list(Config) ->
 
533
    Pid = ?config(ftp, Config),
 
534
    do_delete(Pid, Config).
 
535
   
 
536
 
 
537
%%-------------------------------------------------------------------------
 
538
 
 
539
passive_mkdir(doc) ->
 
540
    ["Make a remote directory, cd to it, go to parent directory, and "
 
541
     "remove the directory."];
 
542
passive_mkdir(suite) ->
 
543
    [];
 
544
passive_mkdir(Config) when is_list(Config) ->
 
545
    Pid = ?config(ftp, Config),
 
546
    do_mkdir(Pid).
 
547
   
 
548
 
 
549
%%-------------------------------------------------------------------------
 
550
 
 
551
passive_send(doc) ->
 
552
    ["Create a local file in priv_dir; open an ftp connection to a host; "
 
553
     "logon as anonymous ftp; cd to the directory \"incoming\"; lcd to "
 
554
     "priv_dir; send the file; get a directory listing and check that "
 
555
     "the file is on the list;, delete the remote file; get another listing "
 
556
     "and check that the file is not on the list; close the session; "
 
557
     "delete the local file."];
 
558
passive_send(suite) ->
 
559
    [];
 
560
passive_send(Config) when is_list(Config) ->
 
561
    Pid = ?config(ftp, Config),
 
562
    do_send(Pid, Config).
 
563
 
 
564
 
 
565
%%-------------------------------------------------------------------------
 
566
 
 
567
passive_append(doc) ->
 
568
    ["Create a local file in priv_dir; open an ftp connection to a host; "
 
569
     "logon as anonymous ftp; cd to the directory \"incoming\"; lcd to "
 
570
     "priv_dir; append the file to a file at the remote side that not exits"
 
571
     "this will create the file at the remote side. Then it append the file "
 
572
     "again. When this is done it recive the remote file and control that"
 
573
     "the content is doubled in it.After that it will remove the files"];
 
574
passive_append(suite) ->
 
575
    [];
 
576
passive_append(Config) when is_list(Config) ->
 
577
    Pid = ?config(ftp, Config),
 
578
    do_append(Pid, Config).
 
579
   
 
580
 
 
581
%%------------------------------------------------------------------------- 
 
582
 
 
583
passive_send_bin(doc) ->
 
584
    ["Open a connection to a host; cd to the directory \"incoming\"; "
 
585
     "send a binary; remove file; close the connection."];
 
586
passive_send_bin(suite) ->
 
587
    [];
 
588
passive_send_bin(Config) when is_list(Config) ->
 
589
    Pid = ?config(ftp, Config),
 
590
    do_send_bin(Pid, Config).
 
591
 
 
592
%%-------------------------------------------------------------------------
 
593
 
 
594
passive_append_bin(doc) ->
 
595
    ["Open a connection to a host; cd to the directory \"incoming\"; "
 
596
     "append  a binary twice; get the file and compare the content"
 
597
     "remove file; close the connection."];
 
598
passive_append_bin(suite) ->
 
599
    [];
 
600
passive_append_bin(Config) when is_list(Config) ->
 
601
    Pid = ?config(ftp, Config),
 
602
    do_append_bin(Pid, Config).
 
603
 
 
604
 
 
605
%%-------------------------------------------------------------------------    
 
606
 
 
607
passive_send_chunk(doc) ->
 
608
    ["Open a connection to a host; cd to the directory \"incoming\"; "
 
609
     "send chunks; remove file; close the connection."];
 
610
passive_send_chunk(suite) ->
 
611
    [];
 
612
passive_send_chunk(Config) when is_list(Config) ->
 
613
    Pid = ?config(ftp, Config),
 
614
    do_send_chunk(Pid, Config).
 
615
 
 
616
 
 
617
%%-------------------------------------------------------------------------
 
618
 
 
619
passive_append_chunk(doc) ->
 
620
    ["Open a connection to a host; cd to the directory \"incoming\"; "
 
621
     "append chunks;control content remove file; close the connection."];
 
622
passive_append_chunk(suite) ->
 
623
    [];
 
624
passive_append_chunk(Config) when is_list(Config) ->
 
625
    Pid = ?config(ftp, Config),
 
626
    do_append_chunk(Pid, Config).
 
627
 
 
628
 
 
629
%%-------------------------------------------------------------------------
 
630
 
 
631
passive_recv(doc) ->
 
632
    ["Create a local file and transfer it to the remote host into the "
 
633
     "the \"incoming\" directory, remove "
 
634
     "the local file. Then open a new connection; cd to \"incoming\", "
 
635
     "lcd to the private directory; receive the file; delete the "
 
636
     "remote file; close connection; check that received file is in "
 
637
     "the correct directory; cleanup." ];
 
638
passive_recv(suite) ->
 
639
    [];
 
640
passive_recv(Config) when is_list(Config) ->
 
641
    Pid = ?config(ftp, Config),
 
642
    do_recv(Pid, Config).
 
643
 
 
644
 
 
645
%%-------------------------------------------------------------------------
 
646
 
 
647
passive_recv_bin(doc) ->
 
648
    ["Send a binary to the remote host; and retreive "
 
649
     "the file; then remove the file."];
 
650
passive_recv_bin(suite) ->
 
651
    [];
 
652
passive_recv_bin(Config) when is_list(Config) ->
 
653
    Pid = ?config(ftp, Config),
 
654
    do_recv_bin(Pid, Config).
 
655
 
 
656
 
 
657
%%-------------------------------------------------------------------------
 
658
 
 
659
passive_recv_chunk(doc) ->
 
660
    ["Send a binary to the remote host; Connect again, and retreive "
 
661
     "the file; then remove the file."];
 
662
passive_recv_chunk(suite) ->
 
663
    [];
 
664
passive_recv_chunk(Config) when is_list(Config) ->
 
665
    Pid = ?config(ftp, Config),
 
666
    do_recv_chunk(Pid, Config).
 
667
 
 
668
 
 
669
%%-------------------------------------------------------------------------
 
670
 
 
671
passive_type(doc) ->
 
672
    ["Test that we can change btween ASCCI and binary transfer mode"];
 
673
passive_type(suite) ->
 
674
    [];
 
675
passive_type(Config) when is_list(Config) ->
 
676
    Pid = ?config(ftp, Config),
 
677
    do_type(Pid).
 
678
 
 
679
 
 
680
%%-------------------------------------------------------------------------
 
681
 
 
682
passive_quote(doc) ->
 
683
    [""];
 
684
passive_quote(suite) ->
 
685
    [];
 
686
passive_quote(Config) when is_list(Config) ->
 
687
    Pid = ?config(ftp, Config),
 
688
    do_quote(Pid).
 
689
 
 
690
 
 
691
%%-------------------------------------------------------------------------
 
692
 
 
693
passive_ip_v6_disabled(doc) ->
 
694
    ["Test ipv4 command PASV"];
 
695
passive_ip_v6_disabled(suite) ->
 
696
    [];
 
697
passive_ip_v6_disabled(Config) when is_list(Config) ->
 
698
    Pid = ?config(ftp, Config),
 
699
    do_send(Pid, Config).
 
700
 
 
701
 
 
702
%%-------------------------------------------------------------------------
 
703
 
 
704
active_user(doc) ->
 
705
    ["Open an ftp connection to a host, and logon as anonymous ftp."];
 
706
active_user(suite) ->
 
707
    [];
 
708
active_user(Config) when is_list(Config) ->
 
709
    Pid = ?config(ftp, Config),
 
710
    do_user(Pid).
 
711
 
 
712
 
 
713
%%-------------------------------------------------------------------------
 
714
 
 
715
active_pwd(doc) ->
 
716
    ["Test ftp:pwd/1 & ftp:lpwd/1"];
 
717
active_pwd(suite) ->
 
718
    [];
 
719
active_pwd(Config) when is_list(Config) ->
 
720
    Pid = ?config(ftp, Config),
 
721
    do_pwd(Pid).
 
722
 
 
723
 
 
724
%%-------------------------------------------------------------------------
 
725
 
 
726
active_cd(doc) ->
 
727
    ["Open an ftp connection, log on as anonymous ftp, and cd to the"
 
728
     "directory \"/pub\" and to a non-existent directory."];
 
729
active_cd(suite) ->
 
730
    [];
 
731
active_cd(Config) when is_list(Config) ->
 
732
    Pid = ?config(ftp, Config),
 
733
    do_cd(Pid).
 
734
 
 
735
 
 
736
%%-------------------------------------------------------------------------
 
737
 
 
738
active_lcd(doc) ->
 
739
    ["Test api function ftp:lcd/2"];
 
740
active_lcd(suite) ->
 
741
    [];
 
742
active_lcd(Config) when is_list(Config) ->
 
743
    Pid = ?config(ftp, Config),
 
744
    PrivDir = ?config(priv_dir, Config),
 
745
    do_lcd(Pid, PrivDir).
 
746
 
 
747
 
 
748
%%-------------------------------------------------------------------------
 
749
 
 
750
active_ls(doc) ->
 
751
    ["Open an ftp connection; ls the current directory, and the "
 
752
     "\"incoming\" directory. We assume that ls never fails, since "
 
753
     "it's output is meant to be read by humans. "];
 
754
active_ls(suite) ->
 
755
    [];
 
756
active_ls(Config) when is_list(Config) ->
 
757
    Pid = ?config(ftp, Config),
 
758
    do_ls(Pid).
 
759
 
 
760
 
 
761
%%-------------------------------------------------------------------------
 
762
 
 
763
active_nlist(doc) ->
 
764
    ["Open an ftp connection; nlist the current directory, and the "
 
765
     "\"incoming\" directory. Nlist does not behave consistenly over "
 
766
     "operating systems. On some it is an error to have an empty "
 
767
     "directory."];
 
768
active_nlist(suite) ->
 
769
    [];
 
770
active_nlist(Config) when is_list(Config) ->
 
771
    Pid = ?config(ftp, Config),
 
772
    WildcardSupport = ?config(wildcard_support, Config),
 
773
    do_nlist(Pid, WildcardSupport).
 
774
 
 
775
 
 
776
%%-------------------------------------------------------------------------
 
777
 
 
778
active_rename(doc) ->
 
779
    ["Transfer a file to the server, and rename it; then remove it."];
 
780
active_rename(suite) ->
 
781
    [];
 
782
active_rename(Config) when is_list(Config) ->
 
783
    Pid = ?config(ftp, Config),
 
784
    do_rename(Pid, Config).
 
785
    
 
786
 
 
787
%%-------------------------------------------------------------------------
 
788
 
 
789
active_delete(doc) ->
 
790
    ["Transfer a file to the server, and then delete it"];
 
791
active_delete(suite) ->
 
792
    [];
 
793
active_delete(Config) when is_list(Config) ->
 
794
    Pid = ?config(ftp, Config),
 
795
    do_delete(Pid, Config).
 
796
   
 
797
 
 
798
%%-------------------------------------------------------------------------
 
799
 
 
800
active_mkdir(doc) ->
 
801
    ["Make a remote directory, cd to it, go to parent directory, and "
 
802
     "remove the directory."];
 
803
active_mkdir(suite) ->
 
804
    [];
 
805
active_mkdir(Config) when is_list(Config) ->
 
806
    Pid = ?config(ftp, Config),
 
807
    do_mkdir(Pid).
 
808
   
 
809
 
 
810
%%-------------------------------------------------------------------------
 
811
 
 
812
active_send(doc) ->
 
813
    ["Create a local file in priv_dir; open an ftp connection to a host; "
 
814
     "logon as anonymous ftp; cd to the directory \"incoming\"; lcd to "
 
815
     "priv_dir; send the file; get a directory listing and check that "
 
816
     "the file is on the list;, delete the remote file; get another listing "
 
817
     "and check that the file is not on the list; close the session; "
 
818
     "delete the local file."];
 
819
active_send(suite) ->
 
820
    [];
 
821
active_send(Config) when is_list(Config) ->
 
822
    Pid = ?config(ftp, Config),
 
823
    do_send(Pid, Config).
 
824
 
 
825
 
 
826
%%-------------------------------------------------------------------------
 
827
 
 
828
active_append(doc) ->
 
829
    ["Create a local file in priv_dir; open an ftp connection to a host; "
 
830
     "logon as anonymous ftp; cd to the directory \"incoming\"; lcd to "
 
831
     "priv_dir; append the file to a file at the remote side that not exits"
 
832
     "this will create the file at the remote side. Then it append the file "
 
833
     "again. When this is done it recive the remote file and control that"
 
834
     "the content is doubled in it.After that it will remove the files"];
 
835
active_append(suite) ->
 
836
    [];
 
837
active_append(Config) when is_list(Config) ->
 
838
    Pid = ?config(ftp, Config),
 
839
    do_append(Pid, Config).
 
840
   
 
841
 
 
842
%%------------------------------------------------------------------------- 
 
843
 
 
844
active_send_bin(doc) ->
 
845
    ["Open a connection to a host; cd to the directory \"incoming\"; "
 
846
     "send a binary; remove file; close the connection."];
 
847
active_send_bin(suite) ->
 
848
    [];
 
849
active_send_bin(Config) when is_list(Config) ->
 
850
    Pid = ?config(ftp, Config),
 
851
    do_send_bin(Pid, Config).
 
852
 
 
853
 
 
854
%%-------------------------------------------------------------------------
 
855
 
 
856
active_append_bin(doc) ->
 
857
    ["Open a connection to a host; cd to the directory \"incoming\"; "
 
858
     "append  a binary twice; get the file and compare the content"
 
859
     "remove file; close the connection."];
 
860
active_append_bin(suite) ->
 
861
    [];
 
862
active_append_bin(Config) when is_list(Config) ->
 
863
    Pid = ?config(ftp, Config),
 
864
    do_append_bin(Pid, Config).
 
865
 
 
866
 
 
867
%%-------------------------------------------------------------------------    
 
868
 
 
869
active_send_chunk(doc) ->
 
870
    ["Open a connection to a host; cd to the directory \"incoming\"; "
 
871
     "send chunks; remove file; close the connection."];
 
872
active_send_chunk(suite) ->
 
873
    [];
 
874
active_send_chunk(Config) when is_list(Config) ->
 
875
    Pid = ?config(ftp, Config),
 
876
    do_send_chunk(Pid, Config).
 
877
 
 
878
 
 
879
%%-------------------------------------------------------------------------
 
880
 
 
881
active_append_chunk(doc) ->
 
882
    ["Open a connection to a host; cd to the directory \"incoming\"; "
 
883
     "append chunks;control content remove file; close the connection."];
 
884
active_append_chunk(suite) ->
 
885
    [];
 
886
active_append_chunk(Config) when is_list(Config) ->
 
887
    Pid = ?config(ftp, Config),
 
888
    do_append_chunk(Pid, Config).
 
889
 
 
890
 
 
891
%%-------------------------------------------------------------------------
 
892
 
 
893
active_recv(doc) ->
 
894
    ["Create a local file and transfer it to the remote host into the "
 
895
     "the \"incoming\" directory, remove "
 
896
     "the local file. Then open a new connection; cd to \"incoming\", "
 
897
     "lcd to the private directory; receive the file; delete the "
 
898
     "remote file; close connection; check that received file is in "
 
899
     "the correct directory; cleanup." ];
 
900
active_recv(suite) ->
 
901
    [];
 
902
active_recv(Config) when is_list(Config) ->
 
903
    Pid = ?config(ftp, Config),
 
904
    do_recv(Pid, Config).
 
905
 
 
906
 
 
907
%%-------------------------------------------------------------------------
 
908
 
 
909
active_recv_bin(doc) ->
 
910
    ["Send a binary to the remote host; and retreive "
 
911
     "the file; then remove the file."];
 
912
active_recv_bin(suite) ->
 
913
    [];
 
914
active_recv_bin(Config) when is_list(Config) ->
 
915
    Pid = ?config(ftp, Config),
 
916
    do_recv_bin(Pid, Config).
 
917
 
 
918
 
 
919
%%-------------------------------------------------------------------------
 
920
 
 
921
active_recv_chunk(doc) ->
 
922
    ["Send a binary to the remote host; Connect again, and retreive "
 
923
     "the file; then remove the file."];
 
924
active_recv_chunk(suite) ->
 
925
    [];
 
926
active_recv_chunk(Config) when is_list(Config) ->
 
927
    Pid = ?config(ftp, Config),
 
928
    do_recv_chunk(Pid, Config).
 
929
 
 
930
 
 
931
%%-------------------------------------------------------------------------
 
932
 
 
933
active_type(doc) ->
 
934
    ["Test that we can change btween ASCCI and binary transfer mode"];
 
935
active_type(suite) ->
 
936
    [];
 
937
active_type(Config) when is_list(Config) ->
 
938
    Pid = ?config(ftp, Config),
 
939
    do_type(Pid).
 
940
 
 
941
 
 
942
%%-------------------------------------------------------------------------
 
943
 
 
944
active_quote(doc) ->
 
945
    [""];
 
946
active_quote(suite) ->
 
947
    [];
 
948
active_quote(Config) when is_list(Config) ->
 
949
    Pid = ?config(ftp, Config),
 
950
    do_quote(Pid).
 
951
 
 
952
 
 
953
%%-------------------------------------------------------------------------
 
954
 
 
955
active_ip_v6_disabled(doc) ->
 
956
    ["Test ipv4 command PORT"];
 
957
active_ip_v6_disabled(suite) ->
 
958
    [];
 
959
active_ip_v6_disabled(Config) when is_list(Config) ->
 
960
    Pid = ?config(ftp, Config),
 
961
    do_send(Pid, Config).
 
962
 
 
963
 
 
964
%%-------------------------------------------------------------------------
 
965
 
 
966
api_missuse(doc)->
 
967
    ["Test that behaviour of the ftp process if the api is abused"];
 
968
api_missuse(suite) -> [];
 
969
api_missuse(Config) when is_list(Config) ->
 
970
    io:format("api_missuse -> entry~n", []),
 
971
    Flag =  process_flag(trap_exit, true),
 
972
    Pid = ?config(ftp, Config),
 
973
    Host = ftp_host(Config), 
 
974
    
 
975
    %% Serious programming fault, connetion will be shut down 
 
976
    io:format("api_missuse -> verify bad call termination (~p)~n", [Pid]),
 
977
    case (catch gen_server:call(Pid, {self(), foobar, 10}, infinity)) of
 
978
        {error, {connection_terminated, 'API_violation'}} ->
 
979
            ok;
 
980
        Unexpected1 ->
 
981
            exit({unexpected_result, Unexpected1})
 
982
    end,
 
983
    test_server:sleep(500),
 
984
    undefined = process_info(Pid, status),
 
985
 
 
986
    io:format("api_missuse -> start new client~n", []),
 
987
    {ok, Pid2} =  ?ftp_open(Host, []),
 
988
    %% Serious programming fault, connetion will be shut down 
 
989
    io:format("api_missuse -> verify bad cast termination~n", []),
 
990
    gen_server:cast(Pid2, {self(), foobar, 10}),
 
991
    test_server:sleep(500),
 
992
    undefined = process_info(Pid2, status),
 
993
 
 
994
    io:format("api_missuse -> start new client~n", []),
 
995
    {ok, Pid3} =  ?ftp_open(Host, []),
 
996
    %% Could be an innocent misstake the connection lives. 
 
997
    io:format("api_missuse -> verify bad bang~n", []),
 
998
    Pid3 ! foobar, 
 
999
    test_server:sleep(500),
 
1000
    {status, _} = process_info(Pid3, status),
 
1001
    process_flag(trap_exit, Flag),
 
1002
    io:format("api_missuse -> done~n", []),
 
1003
    ok.
 
1004
 
 
1005
 
 
1006
%%-------------------------------------------------------------------------
 
1007
 
 
1008
not_owner(doc) ->
 
1009
    ["Test what happens if a process that not owns the connection tries "
 
1010
    "to use it"];
 
1011
not_owner(suite) ->
 
1012
    [];
 
1013
not_owner(Config) when is_list(Config) ->
 
1014
    Pid = ?config(ftp, Config),
 
1015
    OtherPid = spawn_link(?MODULE, not_owner, [Pid, self()]),
 
1016
    
 
1017
    receive
 
1018
        {OtherPid, ok} ->
 
1019
            {ok, _} = ftp:pwd(Pid)
 
1020
    end,
 
1021
    ok.
 
1022
 
 
1023
not_owner(FtpPid, Pid) ->
 
1024
    {error, not_connection_owner} = ftp:pwd(FtpPid),
 
1025
    ftp:close(FtpPid),
 
1026
    test_server:sleep(100),
 
1027
    Pid ! {self(), ok}.
 
1028
 
 
1029
 
 
1030
%%-------------------------------------------------------------------------
 
1031
 
 
1032
 
 
1033
progress_report(doc) ->
 
1034
    ["Solaris 8 sparc test the option progress."];
 
1035
progress_report(suite) ->
 
1036
    [progress_report_send, progress_report_recv].
 
1037
 
 
1038
 
 
1039
%% -- 
 
1040
 
 
1041
progress_report_send(doc) ->
 
1042
    ["Test the option progress for ftp:send/[2,3]"];
 
1043
progress_report_send(suite) ->
 
1044
    [];
 
1045
progress_report_send(Config) when is_list(Config) ->
 
1046
    Pid = ?config(ftp, Config),
 
1047
    ReportPid = 
 
1048
        spawn_link(?MODULE, progress_report_receiver_init, [self(), 1]),
 
1049
    do_send(Pid, Config),
 
1050
    receive
 
1051
        {ReportPid, ok} ->
 
1052
            ok
 
1053
    end.
 
1054
 
 
1055
 
 
1056
%% -- 
 
1057
 
 
1058
progress_report_recv(doc) ->
 
1059
    ["Test the option progress for ftp:recv/[2,3]"];
 
1060
progress_report_recv(suite) ->
 
1061
    [];
 
1062
progress_report_recv(Config) when is_list(Config) ->
 
1063
    Pid = ?config(ftp, Config),
 
1064
    ReportPid = 
 
1065
        spawn_link(?MODULE, progress_report_receiver_init, [self(), 3]),
 
1066
    do_recv(Pid, Config),
 
1067
    receive
 
1068
        {ReportPid, ok} ->
 
1069
            ok
 
1070
    end,
 
1071
    ok.
 
1072
 
 
1073
progress(#progress{} = Progress , _File, {file_size, Total}) ->
 
1074
    progress_report_receiver ! start,
 
1075
    Progress#progress{total = Total};
 
1076
progress(#progress{total = Total, current = Current} 
 
1077
         = Progress, _File, {transfer_size, 0}) ->
 
1078
    progress_report_receiver ! finish,
 
1079
    case Total of
 
1080
        unknown ->
 
1081
            ok;
 
1082
        Current ->
 
1083
            ok;
 
1084
        _  ->
 
1085
            test_server:fail({error, {progress, {total, Total},
 
1086
                                      {current, Current}}})
 
1087
    end,
 
1088
    Progress;
 
1089
progress(#progress{current = Current} = Progress, _File, 
 
1090
         {transfer_size, Size}) ->
 
1091
    progress_report_receiver ! update,
 
1092
    Progress#progress{current = Current + Size}.
 
1093
 
 
1094
progress_report_receiver_init(Pid, N) ->
 
1095
    register(progress_report_receiver, self()),
 
1096
    receive
 
1097
        start ->
 
1098
            ok
 
1099
    end,
 
1100
    progress_report_receiver_loop(Pid, N-1).
 
1101
 
 
1102
progress_report_receiver_loop(Pid, N) ->
 
1103
      receive
 
1104
          update ->
 
1105
            progress_report_receiver_loop(Pid, N);
 
1106
          finish when N =:= 0 ->
 
1107
              Pid ! {self(), ok};
 
1108
          finish  ->
 
1109
              Pid ! {self(), ok},
 
1110
              receive
 
1111
                  start ->
 
1112
                      ok
 
1113
              end,
 
1114
              progress_report_receiver_loop(Pid, N-1)
 
1115
      end.
 
1116
 
 
1117
 
 
1118
%%-------------------------------------------------------------------------
 
1119
%% Ticket test cases
 
1120
%%-------------------------------------------------------------------------
 
1121
 
 
1122
ticket_6035(doc) -> ["Test that owning process that exits with reason "
 
1123
                     "'shutdown' does not cause an error message."];
 
1124
ticket_6035(suite) -> [];
 
1125
ticket_6035(Config) ->
 
1126
    p("ticket_6035 -> entry with"
 
1127
      "~n   Config: ~p", [Config]),
 
1128
    PrivDir = ?config(priv_dir, Config),
 
1129
    LogFile = filename:join([PrivDir,"ticket_6035.log"]),
 
1130
    try
 
1131
        begin
 
1132
            Host = dirty_select_ftpd_host(Config), 
 
1133
            Pid  = spawn(?MODULE, open_wait_6035, [Host, self()]),
 
1134
            error_logger:logfile({open, LogFile}),
 
1135
            ok = kill_ftp_proc_6035(Pid,LogFile),
 
1136
            error_logger:logfile(close),
 
1137
            p("ticket_6035 -> done", []),
 
1138
            ok
 
1139
        end
 
1140
    catch 
 
1141
        throw:{error, not_found} ->
 
1142
            {skip, "No available FTP servers"}
 
1143
    end.
 
1144
 
 
1145
kill_ftp_proc_6035(Pid, LogFile) ->
 
1146
    p("kill_ftp_proc_6035 -> entry"),
 
1147
    receive
 
1148
        open ->
 
1149
            p("kill_ftp_proc_6035 -> received open: send shutdown"),
 
1150
            exit(Pid, shutdown),
 
1151
            kill_ftp_proc_6035(Pid, LogFile);
 
1152
        {open_failed, Reason} ->
 
1153
            p("kill_ftp_proc_6035 -> received open_failed"
 
1154
              "~n   Reason: ~p", [Reason]),
 
1155
            exit({skip, {failed_openening_server_connection, Reason}})
 
1156
    after
 
1157
        5000 ->
 
1158
            p("kill_ftp_proc_6035 -> timeout"),
 
1159
            is_error_report_6035(LogFile)
 
1160
    end.
 
1161
 
 
1162
open_wait_6035(FtpServer, From) ->
 
1163
    p("open_wait_6035 -> try connect to ~s", [FtpServer]),
 
1164
    case ftp:open(FtpServer, [{timeout, timer:seconds(15)}]) of
 
1165
        {ok, Pid} ->
 
1166
            p("open_wait_6035 -> connected, now login"),
 
1167
            LoginResult = ftp:user(Pid,"anonymous","kldjf"),
 
1168
            p("open_wait_6035 -> login result: ~p", [LoginResult]),
 
1169
            From ! open,
 
1170
            receive
 
1171
                dummy -> 
 
1172
                    p("open_wait_6035 -> received dummy"),
 
1173
                    ok
 
1174
            after
 
1175
                10000 ->
 
1176
                    p("open_wait_6035 -> timeout"),
 
1177
                    ok
 
1178
            end,
 
1179
            p("open_wait_6035 -> done(ok)"),
 
1180
            ok;
 
1181
        {error, Reason} ->
 
1182
            p("open_wait_6035 -> open failed"
 
1183
              "~n   Reason: ~p", [Reason]),
 
1184
            From ! {open_failed, {Reason, FtpServer}},
 
1185
            p("open_wait_6035 -> done(error)"),
 
1186
            ok
 
1187
    end.
 
1188
 
 
1189
is_error_report_6035(LogFile) ->
 
1190
    p("is_error_report_6035 -> entry"),
 
1191
    Res =
 
1192
        case file:read_file(LogFile) of
 
1193
            {ok, Bin} ->
 
1194
                p("is_error_report_6035 -> logfile read"),
 
1195
                read_log_6035(binary_to_list(Bin));
 
1196
            _ ->
 
1197
                ok
 
1198
        end,
 
1199
    p("is_error_report_6035 -> logfile read result: "
 
1200
      "~n   ~p", [Res]),
 
1201
    file:delete(LogFile),
 
1202
    Res.
 
1203
 
 
1204
read_log_6035("=ERROR REPORT===="++_Rest) ->
 
1205
    error_report;
 
1206
read_log_6035([_H|T]) ->
 
1207
    read_log_6035(T);
 
1208
read_log_6035([]) ->
 
1209
    ok.
 
1210
 
 
1211
 
 
1212
%%--------------------------------------------------------------------
 
1213
%% Internal functions
 
1214
%%--------------------------------------------------------------------
 
1215
do_user(Pid) ->
 
1216
    {error, euser} = ftp:user(Pid, ?BAD_USER, ?FTP_PASS),
 
1217
    ok = ftp:user(Pid, ?FTP_USER, ?FTP_PASS),
 
1218
    ok.
 
1219
 
 
1220
do_pwd(Pid) ->
 
1221
    {ok, "/"} = ftp:pwd(Pid),
 
1222
    {ok, Path} = ftp:lpwd(Pid),
 
1223
    {ok, Path} = file:get_cwd(),
 
1224
    ok.
 
1225
 
 
1226
do_cd(Pid) ->
 
1227
    ok = ftp:cd(Pid, "/pub"),
 
1228
    {error, epath} = ftp:cd(Pid, ?BAD_DIR),
 
1229
    ok.
 
1230
 
 
1231
do_lcd(Pid, Dir) ->
 
1232
    ok = ftp:lcd(Pid, Dir),
 
1233
    {error, epath} = ftp:lcd(Pid, ?BAD_DIR),
 
1234
    ok.
 
1235
 
 
1236
 
 
1237
do_ls(Pid) ->
 
1238
    {ok, _} = ftp:ls(Pid),
 
1239
    {ok, _} = ftp:ls(Pid, "incoming"),
 
1240
    %% neither nlist nor ls operates on a directory
 
1241
    %% they operate on a pathname, which *can* be a 
 
1242
    %% directory, but can also be a filename or a group 
 
1243
    %% of files (including wildcards).
 
1244
    {ok, _} = ftp:ls(Pid, "incom*"),
 
1245
    ok.
 
1246
 
 
1247
do_nlist(Pid, WildcardSupport) ->
 
1248
    {ok, _} = ftp:nlist(Pid),
 
1249
    {ok, _} = ftp:nlist(Pid, "incoming"),
 
1250
    %% neither nlist nor ls operates on a directory
 
1251
    %% they operate on a pathname, which *can* be a 
 
1252
    %% directory, but can also be a filename or a group 
 
1253
    %% of files (including wildcards).
 
1254
    case WildcardSupport of
 
1255
        true ->
 
1256
            {ok, _} = ftp:nlist(Pid, "incom*"),
 
1257
            ok;
 
1258
        _ ->
 
1259
            ok
 
1260
    end.
 
1261
 
 
1262
do_rename(Pid, Config) ->
 
1263
    PrivDir = ?config(priv_dir, Config),
 
1264
    LFile  = ?config(file, Config),
 
1265
    NewLFile  = ?config(new_file, Config),
 
1266
    AbsLFile = filename:absname(LFile, PrivDir),
 
1267
    Contents = "ftp_SUITE test ...",
 
1268
    ok = file:write_file(AbsLFile, list_to_binary(Contents)),
 
1269
    ok = ftp:cd(Pid, "incoming"),
 
1270
    ok = ftp:lcd(Pid, PrivDir),
 
1271
    ftp:delete(Pid, LFile),             % reset
 
1272
    ftp:delete(Pid, NewLFile),          % reset
 
1273
    ok = ftp:send(Pid, LFile), 
 
1274
    {error, epath} = ftp:rename(Pid, NewLFile, LFile),
 
1275
    ok = ftp:rename(Pid, LFile, NewLFile),
 
1276
    ftp:delete(Pid, LFile),             % cleanup
 
1277
    ftp:delete(Pid, NewLFile),          % cleanup
 
1278
    ok.
 
1279
 
 
1280
do_delete(Pid, Config) ->
 
1281
    PrivDir = ?config(priv_dir, Config),
 
1282
    LFile  = ?config(file, Config),
 
1283
    AbsLFile = filename:absname(LFile, PrivDir),
 
1284
    Contents = "ftp_SUITE test ...",
 
1285
    ok = file:write_file(AbsLFile, list_to_binary(Contents)),    
 
1286
    ok = ftp:cd(Pid, "incoming"),
 
1287
    ok = ftp:lcd(Pid, PrivDir),
 
1288
    ftp:delete(Pid,LFile),              % reset
 
1289
    ok = ftp:send(Pid, LFile),
 
1290
    ok = ftp:delete(Pid,LFile),
 
1291
    ok.
 
1292
 
 
1293
do_mkdir(Pid) ->
 
1294
    {A, B, C} = erlang:now(),
 
1295
    NewDir = "nisse_" ++ integer_to_list(A) ++ "_" ++
 
1296
        integer_to_list(B) ++ "_" ++ integer_to_list(C),
 
1297
    ok = ftp:cd(Pid, "incoming"),
 
1298
    {ok, CurrDir} = ftp:pwd(Pid),
 
1299
    ok = ftp:mkdir(Pid, NewDir),
 
1300
    ok = ftp:cd(Pid, NewDir),
 
1301
    ok = ftp:cd(Pid, CurrDir),
 
1302
    ok = ftp:rmdir(Pid, NewDir),
 
1303
    ok.
 
1304
 
 
1305
do_send(Pid, Config) ->
 
1306
    PrivDir = ?config(priv_dir, Config),
 
1307
    LFile  = ?config(file, Config),
 
1308
    RFile = LFile ++ ".remote",
 
1309
    AbsLFile = filename:absname(LFile, PrivDir),
 
1310
    Contents = "ftp_SUITE test ...",
 
1311
    ok = file:write_file(AbsLFile, list_to_binary(Contents)),
 
1312
    ok = ftp:cd(Pid, "incoming"),
 
1313
    ok = ftp:lcd(Pid, PrivDir),
 
1314
    ok = ftp:send(Pid, LFile, RFile),
 
1315
    {ok, RFilesString} = ftp:nlist(Pid),
 
1316
    RFiles = split(RFilesString),
 
1317
    true = lists:member(RFile, RFiles),
 
1318
    ok = ftp:delete(Pid, RFile),
 
1319
    case ftp:nlist(Pid) of
 
1320
        {error, epath} ->
 
1321
            ok;                         % No files
 
1322
        {ok, RFilesString1} ->
 
1323
            RFiles1 = split(RFilesString1),
 
1324
            false = lists:member(RFile, RFiles1)
 
1325
    end,
 
1326
    ok = file:delete(AbsLFile).
 
1327
 
 
1328
do_append(Pid, Config) ->
 
1329
    PrivDir = ?config(priv_dir, Config),
 
1330
    LFile  =  ?config(file, Config),
 
1331
    RFile =  ?config(new_file, Config),
 
1332
    AbsLFile = filename:absname(LFile, PrivDir),
 
1333
    Contents = "ftp_SUITE test:appending\r\n",
 
1334
 
 
1335
    ok = file:write_file(AbsLFile, list_to_binary(Contents)),
 
1336
    ok = ftp:cd(Pid, "incoming"),
 
1337
    ok = ftp:lcd(Pid, PrivDir),
 
1338
 
 
1339
    %% remove files from earlier failed test case
 
1340
    ftp:delete(Pid, RFile),
 
1341
    ftp:delete(Pid, LFile),
 
1342
 
 
1343
    ok = ftp:append(Pid, LFile, RFile),
 
1344
    ok = ftp:append(Pid, LFile, RFile),
 
1345
    ok = ftp:append(Pid, LFile),
 
1346
 
 
1347
    %% Control the contents of the file
 
1348
    {ok, Bin1} = ftp:recv_bin(Pid, RFile),
 
1349
    ok = ftp:delete(Pid, RFile),
 
1350
    ok = file:delete(AbsLFile),
 
1351
    ok = check_content(binary_to_list(Bin1), Contents, double),
 
1352
    
 
1353
    {ok, Bin2}  = ftp:recv_bin(Pid, LFile),
 
1354
    ok = ftp:delete(Pid, LFile),
 
1355
    ok = check_content(binary_to_list(Bin2), Contents, singel),
 
1356
    ok.
 
1357
 
 
1358
do_send_bin(Pid, Config) ->
 
1359
    File = ?config(file, Config),
 
1360
    Contents = "ftp_SUITE test ...",
 
1361
    Bin = list_to_binary(Contents),
 
1362
    ok = ftp:cd(Pid, "incoming"),
 
1363
    {error, enotbinary} = ftp:send_bin(Pid, Contents, File),
 
1364
    ok = ftp:send_bin(Pid, Bin, File),
 
1365
    {ok, RFilesString} = ftp:nlist(Pid),
 
1366
    RFiles = split(RFilesString),
 
1367
    true = lists:member(File, RFiles),
 
1368
    ok = ftp:delete(Pid, File),
 
1369
    ok.
 
1370
 
 
1371
do_append_bin(Pid, Config) ->
 
1372
    File = ?config(file, Config),
 
1373
    Contents = "ftp_SUITE test ...",
 
1374
    Bin = list_to_binary(Contents),
 
1375
    ok = ftp:cd(Pid, "incoming"),
 
1376
    {error, enotbinary} = ftp:append_bin(Pid, Contents, File),
 
1377
    ok = ftp:append_bin(Pid, Bin, File),
 
1378
    ok = ftp:append_bin(Pid, Bin, File),
 
1379
    %% Control the contents of the file
 
1380
    {ok, Bin2} = ftp:recv_bin(Pid, File),
 
1381
    ok = ftp:delete(Pid,File),
 
1382
    ok = check_content(binary_to_list(Bin2),binary_to_list(Bin), double).
 
1383
 
 
1384
do_send_chunk(Pid, Config) ->
 
1385
    File = ?config(file, Config),
 
1386
    Contents = "ftp_SUITE test ...",
 
1387
    Bin = list_to_binary(Contents),
 
1388
    ok = ftp:cd(Pid, "incoming"),
 
1389
    ok = ftp:send_chunk_start(Pid, File),
 
1390
    {error, echunk} = ftp:cd(Pid, "incoming"),
 
1391
    {error, enotbinary} = ftp:send_chunk(Pid, Contents),
 
1392
    ok = ftp:send_chunk(Pid, Bin),
 
1393
    ok = ftp:send_chunk(Pid, Bin),
 
1394
    ok = ftp:send_chunk_end(Pid),
 
1395
    {ok, RFilesString} = ftp:nlist(Pid),
 
1396
    RFiles = split(RFilesString),
 
1397
    true = lists:member(File, RFiles),
 
1398
    ok = ftp:delete(Pid, File),
 
1399
    ok.
 
1400
 
 
1401
do_append_chunk(Pid, Config) ->
 
1402
    File = ?config(file, Config),
 
1403
    Contents = ["ER","LE","RL"],
 
1404
    ok = ftp:cd(Pid, "incoming"),
 
1405
    ok = ftp:append_chunk_start(Pid, File),
 
1406
    {error, enotbinary} = ftp:append_chunk(Pid, lists:nth(1,Contents)),
 
1407
    ok = ftp:append_chunk(Pid,list_to_binary(lists:nth(1,Contents))),
 
1408
    ok = ftp:append_chunk(Pid,list_to_binary(lists:nth(2,Contents))),
 
1409
    ok = ftp:append_chunk(Pid,list_to_binary(lists:nth(3,Contents))),
 
1410
    ok = ftp:append_chunk_end(Pid),
 
1411
    %%Control the contents of the file
 
1412
    {ok, Bin2}  = ftp:recv_bin(Pid, File),
 
1413
    ok = check_content(binary_to_list(Bin2),"ERL", double),
 
1414
    ok = ftp:delete(Pid, File),
 
1415
    ok.
 
1416
 
 
1417
do_recv(Pid, Config) ->
 
1418
    PrivDir = ?config(priv_dir, Config),
 
1419
    File  = ?config(file, Config),
 
1420
    Newfile = ?config(new_file, Config),
 
1421
    AbsFile = filename:absname(File, PrivDir),
 
1422
    Contents = "ftp_SUITE:recv test ...",
 
1423
    ok = file:write_file(AbsFile, list_to_binary(Contents)),
 
1424
    ok = ftp:cd(Pid, "incoming"),
 
1425
    ftp:delete(Pid, File),              % reset
 
1426
    ftp:lcd(Pid, PrivDir),
 
1427
    ok = ftp:send(Pid, File),
 
1428
    ok = file:delete(AbsFile),          % cleanup
 
1429
    test_server:sleep(100),
 
1430
    ok = ftp:lcd(Pid, PrivDir),
 
1431
    ok = ftp:recv(Pid, File),
 
1432
    {ok, Files} = file:list_dir(PrivDir),
 
1433
    true = lists:member(File, Files),
 
1434
    ok = file:delete(AbsFile), % cleanup
 
1435
    ok = ftp:recv(Pid, File, Newfile), 
 
1436
    ok = ftp:delete(Pid, File),         % cleanup
 
1437
    ok.
 
1438
 
 
1439
do_recv_bin(Pid, Config) ->
 
1440
    File = ?config(file, Config),
 
1441
    Contents1 = "ftp_SUITE test ...",
 
1442
    Bin1 = list_to_binary(Contents1),
 
1443
    ok = ftp:cd(Pid, "incoming"),
 
1444
    ok = ftp:send_bin(Pid, Bin1, File),
 
1445
    test_server:sleep(100),
 
1446
    {ok, Bin2}  = ftp:recv_bin(Pid, File),
 
1447
    ok = ftp:delete(Pid, File),         % cleanup
 
1448
    Contents2 = binary_to_list(Bin2),
 
1449
    Contents1 = Contents2,
 
1450
    ok.
 
1451
 
 
1452
do_recv_chunk(Pid, Config) ->
 
1453
    File = ?config(file, Config),
 
1454
    Data = "AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA"
 
1455
        "BBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBB"
 
1456
        "CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC"
 
1457
        "DDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDD"
 
1458
        "EEEEEEEEEEEEEEEEEEEEEEEEEEEEEEEEEEEEEEEEEEEEEEEEEEEEEEEEEEEEEEE"
 
1459
        "FFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFF"
 
1460
        "GGGGGGGGGGGGGGGGGGGGGGGGGGGGGGGGGGGGGGGGGGGGGGGGGGGGGGGGGGGGGGG"
 
1461
        "HHHHHHHHHHHHHHHHHHHHHHHHHHHHHHHHHHHHHHHHHHHHHHHHHHHHHHHHHHHHHHH"
 
1462
        "IIIIIIIIIIIIIIIIIIIIIIIIIIIIIIIIIIIIIIIIIIIIIIIIIIIIIIIIIIIIIII",
 
1463
 
 
1464
    Contents1 = lists:flatten(lists:duplicate(10, Data)),
 
1465
    Bin1 = list_to_binary(Contents1),
 
1466
    ok = ftp:cd(Pid, "incoming"),
 
1467
    ok = ftp:type(Pid, binary),
 
1468
    ok = ftp:send_bin(Pid, Bin1, File),
 
1469
    test_server:sleep(100),
 
1470
    {error, "ftp:recv_chunk_start/2 not called"} = recv_chunk(Pid, <<>>),
 
1471
    ok = ftp:recv_chunk_start(Pid, File),
 
1472
    {ok, Contents2} = recv_chunk(Pid, <<>>),
 
1473
    ok = ftp:delete(Pid, File),         % cleanup
 
1474
    ok = find_diff(Contents2, Contents1, 1),
 
1475
    ok.
 
1476
 
 
1477
do_type(Pid) ->
 
1478
    ok = ftp:type(Pid, ascii),
 
1479
    ok = ftp:type(Pid, binary),
 
1480
    ok = ftp:type(Pid, ascii),
 
1481
    {error, etype} = ftp:type(Pid, foobar),
 
1482
    ok.
 
1483
 
 
1484
do_quote(Pid) ->
 
1485
    ["257 \"/\""++_Rest] = ftp:quote(Pid, "pwd"), %% 257
 
1486
    [_| _] = ftp:quote(Pid, "help"),
 
1487
    %% This negativ test causes some ftp servers to hang. This test
 
1488
    %% is not important for the client, so we skip it for now.
 
1489
    %%["425 Can't build data connection: Connection refused."] 
 
1490
    %% = ftp:quote(Pid, "list"), 
 
1491
    ok.
 
1492
 
 
1493
 watch_dog(Config) ->
 
1494
     Dog = test_server:timetrap(inets_test_lib:minutes(1)),
 
1495
     NewConfig = lists:keydelete(watchdog, 1, Config),
 
1496
     [{watchdog, Dog} | NewConfig].
 
1497
 
 
1498
 close_connection(Config) ->
 
1499
     case ?config(ftp, Config) of
 
1500
        Pid when is_pid(Pid) ->
 
1501
            ok = ftp:close(Pid),
 
1502
            lists:delete({ftp, Pid}, Config);
 
1503
        _ ->
 
1504
            Config
 
1505
     end.
 
1506
  
 
1507
ftp_host(Config) ->
 
1508
    case ?config(ftp_remote_host, Config) of
 
1509
        undefined ->
 
1510
            exit({skip, "No host specified"});
 
1511
        Host ->
 
1512
            Host   
 
1513
    end.
 
1514
 
 
1515
check_content(RContent, LContent, Amount) ->
 
1516
    LContent2 = case Amount of 
 
1517
                    double ->
 
1518
                        LContent ++ LContent;
 
1519
                    singel ->
 
1520
                        LContent
 
1521
                end,
 
1522
    case string:equal(RContent, LContent2) of
 
1523
        true ->
 
1524
            ok;
 
1525
        false ->
 
1526
            %% Find where the diff is
 
1527
            Where = find_diff(RContent, LContent2, 1),
 
1528
            Where
 
1529
    end.
 
1530
 
 
1531
find_diff(A, A, _) ->
 
1532
    ok;
 
1533
find_diff([H|T1], [H|T2], Pos) ->
 
1534
    find_diff(T1, T2, Pos+1);
 
1535
find_diff(RC, LC, Pos) ->
 
1536
    {error, {diff, Pos, RC, LC}}.
 
1537
 
 
1538
recv_chunk(Pid, Acc) ->
 
1539
    case ftp:recv_chunk(Pid) of
 
1540
        ok ->
 
1541
            {ok, binary_to_list(Acc)};
 
1542
        {ok, Bin} ->
 
1543
            recv_chunk(Pid, <<Acc/binary, Bin/binary>>);
 
1544
        Error ->
 
1545
            Error
 
1546
    end.
 
1547
 
 
1548
split(Cs) ->
 
1549
    split(Cs, [], []).
 
1550
 
 
1551
split([$\r, $\n| Cs], I, Is) ->
 
1552
    split(Cs, [], [lists:reverse(I)| Is]); 
 
1553
split([C| Cs], I, Is) ->
 
1554
    split(Cs, [C| I], Is);
 
1555
split([], I, Is) ->
 
1556
    lists:reverse([lists:reverse(I)| Is]).
 
1557
 
 
1558
do_ftp_open(Host, Opts) ->
 
1559
    io:format("do_ftp_open -> entry with"
 
1560
              "~n   Host: ~p"
 
1561
              "~n   Opts: ~p", [Host, Opts]), 
 
1562
    case ftp:open(Host, Opts) of
 
1563
        {ok, _} = OK ->
 
1564
            OK;
 
1565
        {error, Reason} ->
 
1566
            Str = 
 
1567
                lists:flatten(
 
1568
                  io_lib:format("Unable to reach test FTP server ~p (~p)", 
 
1569
                                [Host, Reason])),
 
1570
            throw({skip, Str})
 
1571
    end.
 
1572
         
 
1573
 
 
1574
passwd() ->
 
1575
    Host = 
 
1576
        case inet:gethostname() of
 
1577
            {ok, H} ->
 
1578
                H;
 
1579
            _ ->
 
1580
                "localhost"
 
1581
        end,
 
1582
    "ftp_SUITE@" ++ Host.
 
1583
 
 
1584
ftpd_hosts(Config) ->
 
1585
    DataDir = ?config(data_dir, Config),
 
1586
    FileName = filename:join([DataDir, "../ftp_SUITE_data/", ftpd_hosts]),
 
1587
    io:format("FileName: ~p~n", [FileName]),
 
1588
    case file:consult(FileName) of
 
1589
        {ok, [Hosts]} when is_list(Hosts) ->
 
1590
            Hosts;
 
1591
        _ -> 
 
1592
            []
 
1593
    end.
 
1594
 
 
1595
wrapper(Prefix,doc,Func) ->
 
1596
    Prefix++Func(doc);
 
1597
wrapper(_,X,Func) ->
 
1598
    Func(X).
 
1599
 
 
1600
data_dir(Config) ->
 
1601
    case ?config(data_dir, Config) of
 
1602
        List when (length(List) > 0) ->
 
1603
            PathList        = filename:split(List),
 
1604
            {NewPathList,_} = lists:split((length(PathList)-1), PathList),
 
1605
            DataDir   = filename:join(NewPathList ++ [ftp_SUITE_data]),
 
1606
            NewConfig = 
 
1607
                lists:keyreplace(data_dir,1,Config, {data_dir,DataDir}),
 
1608
            NewConfig;
 
1609
        _ -> Config
 
1610
    end.
 
1611
    
 
1612
       
 
1613
    
 
1614
p(F) ->
 
1615
    p(F, []).
 
1616
 
 
1617
p(F, A) ->
 
1618
    case get(ftp_testcase) of
 
1619
        undefined ->
 
1620
            io:format("~w [~w] " ++ F ++ "~n", [?MODULE, self() | A]);
 
1621
        TC when is_atom(TC) ->
 
1622
            io:format("~w [~w] ~w:" ++ F ++ "~n", [?MODULE, self(), TC | A])
 
1623
    end.