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

« back to all changes in this revision

Viewing changes to lib/dialyzer/test/r9c_SUITE_data/src/inets/ftp.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
%% ``The contents of this file are subject to the Erlang Public License,
 
2
%% Version 1.1, (the "License"); you may not use this file except in
 
3
%% compliance with the License. You should have received a copy of the
 
4
%% Erlang Public License along with this software. If not, it can be
 
5
%% retrieved via the world wide web at http://www.erlang.org/.
 
6
%%
 
7
%% Software distributed under the License is distributed on an "AS IS"
 
8
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
9
%% the License for the specific language governing rights and limitations
 
10
%% under the License.
 
11
%%
 
12
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
 
13
%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
 
14
%% AB. All Rights Reserved.''
 
15
%%
 
16
%%     $Id: ftp.erl,v 1.2 2009/03/03 01:55:01 kostis Exp $
 
17
%%
 
18
-module(ftp).
 
19
 
 
20
-behaviour(gen_server).
 
21
 
 
22
%% This module implements an ftp client based on socket(3)/gen_tcp(3),
 
23
%% file(3) and filename(3).
 
24
%%
 
25
 
 
26
 
 
27
-define(OPEN_TIMEOUT, 60*1000).
 
28
-define(BYTE_TIMEOUT, 1000).   % Timeout for _ONE_ byte to arrive. (ms)
 
29
-define(OPER_TIMEOUT, 300).    % Operation timeout (seconds)
 
30
-define(FTP_PORT, 21).
 
31
 
 
32
%% Client interface
 
33
-export([cd/2, close/1, delete/2, formaterror/1, help/0,
 
34
         lcd/2, lpwd/1, ls/1, ls/2,
 
35
         mkdir/2, nlist/1, nlist/2,
 
36
         open/1, open/2, open/3,
 
37
         pwd/1,
 
38
         recv/2, recv/3, recv_bin/2,
 
39
         recv_chunk_start/2, recv_chunk/1,
 
40
         rename/3, rmdir/2,
 
41
         send/2, send/3, send_bin/3,
 
42
         send_chunk_start/2, send_chunk/2, send_chunk_end/1,
 
43
         type/2, user/3,user/4,account/2,
 
44
         append/3, append/2, append_bin/3,
 
45
         append_chunk/2, append_chunk_end/1, append_chunk_start/2]).
 
46
 
 
47
%% Internal
 
48
-export([init/1, handle_call/3, handle_cast/2,
 
49
         handle_info/2, terminate/2,code_change/3]).
 
50
 
 
51
 
 
52
%%
 
53
%% CLIENT FUNCTIONS
 
54
%%
 
55
 
 
56
%% open(Host)
 
57
%% open(Host, Flags)
 
58
%%
 
59
%% Purpose:  Start an ftp client and connect to a host.
 
60
%% Args:     Host = string(),
 
61
%%           Port = integer(),
 
62
%%           Flags = [Flag],
 
63
%%           Flag = verbose | debug
 
64
%% Returns:  {ok, Pid} | {error, ehost}
 
65
 
 
66
%%Tho only option was the host in textual form
 
67
open({option_list,Option_list})->
 
68
    %% Dbg = {debug,[trace,log,statistics]},
 
69
    %% Options = [Dbg],
 
70
    Options = [],
 
71
    {ok,Pid1}=case lists:keysearch(flags,1,Option_list) of
 
72
                  {value,{flags,Flags}}->
 
73
                      {ok, Pid} = gen_server:start_link(?MODULE, [Flags], Options);
 
74
                  false ->
 
75
                      {ok, Pid} = gen_server:start_link(?MODULE, [], Options)
 
76
              end,
 
77
    gen_server:call(Pid1, {open, ip_comm,Option_list}, infinity);
 
78
 
 
79
 
 
80
%%The only option was the tuple form of the ip-number
 
81
open(Host)when tuple(Host) ->
 
82
    open(Host, ?FTP_PORT, []);
 
83
 
 
84
%%Host is the string form of the hostname
 
85
open(Host)->
 
86
    open(Host,?FTP_PORT,[]).
 
87
 
 
88
 
 
89
 
 
90
open(Host, Port) when integer(Port) ->
 
91
    open(Host,Port,[]);
 
92
 
 
93
open(Host, Flags) when list(Flags) ->
 
94
    open(Host,?FTP_PORT, Flags).
 
95
 
 
96
open(Host,Port,Flags) when integer(Port), list(Flags) ->
 
97
    %% Dbg = {debug,[trace,log,statistics]},
 
98
    %% Options = [Dbg],
 
99
    Options = [],
 
100
    {ok, Pid} = gen_server:start_link(?MODULE, [Flags], Options),
 
101
    gen_server:call(Pid, {open, ip_comm, Host, Port}, infinity).
 
102
 
 
103
%% user(Pid, User, Pass)
 
104
%% Purpose:  Login.
 
105
%% Args:     Pid = pid(), User = Pass = string()
 
106
%% Returns:  ok | {error, euser} | {error, econn}
 
107
user(Pid, User, Pass) ->
 
108
  gen_server:call(Pid, {user, User, Pass}, infinity).
 
109
 
 
110
%% user(Pid, User, Pass,Acc)
 
111
%% Purpose:  Login whith a supplied account name
 
112
%% Args:     Pid = pid(), User = Pass = Acc = string()
 
113
%% Returns:  ok | {error, euser} | {error, econn} | {error, eacct}
 
114
user(Pid, User, Pass,Acc) ->
 
115
  gen_server:call(Pid, {user, User, Pass,Acc}, infinity).
 
116
 
 
117
%% account(Pid,Acc)
 
118
%% Purpose:  Set a user Account.
 
119
%% Args:     Pid = pid(), Acc= string()
 
120
%% Returns:  ok | {error, eacct}
 
121
account(Pid,Acc) ->
 
122
  gen_server:call(Pid, {account,Acc}, infinity).
 
123
 
 
124
%% pwd(Pid)
 
125
%%
 
126
%% Purpose:  Get the current working directory at remote server.
 
127
%% Args:     Pid = pid()
 
128
%% Returns:  {ok, Dir} | {error, elogin} | {error, econn}
 
129
pwd(Pid) ->
 
130
  gen_server:call(Pid, pwd, infinity).
 
131
 
 
132
%% lpwd(Pid)
 
133
%%
 
134
%% Purpose:  Get the current working directory at local server.
 
135
%% Args:     Pid = pid()
 
136
%% Returns:  {ok, Dir} | {error, elogin}
 
137
lpwd(Pid) ->
 
138
  gen_server:call(Pid, lpwd, infinity).
 
139
 
 
140
%% cd(Pid, Dir)
 
141
%%
 
142
%% Purpose:  Change current working directory at remote server.
 
143
%% Args:     Pid = pid(), Dir = string()
 
144
%% Returns:  ok | {error, epath} | {error, elogin} | {error, econn}
 
145
cd(Pid, Dir) ->
 
146
  gen_server:call(Pid, {cd, Dir}, infinity).
 
147
 
 
148
%% lcd(Pid, Dir)
 
149
%%
 
150
%% Purpose:  Change current working directory for the local client.
 
151
%% Args:     Pid = pid(), Dir = string()
 
152
%% Returns:  ok | {error, epath}
 
153
lcd(Pid, Dir) ->
 
154
  gen_server:call(Pid, {lcd, Dir}, infinity).
 
155
 
 
156
%% ls(Pid)
 
157
%% ls(Pid, Dir)
 
158
%%
 
159
%% Purpose:  List the contents of current directory (ls/1) or directory
 
160
%%           Dir (ls/2) at remote server.
 
161
%% Args:     Pid = pid(), Dir = string()
 
162
%% Returns:  {ok, Listing} | {error, epath} | {error, elogin} | {error, econn}
 
163
ls(Pid) ->
 
164
  ls(Pid, "").
 
165
ls(Pid, Dir) ->
 
166
  gen_server:call(Pid, {dir, long, Dir}, infinity).
 
167
 
 
168
%% nlist(Pid)
 
169
%% nlist(Pid, Dir)
 
170
%%
 
171
%% Purpose:  List the contents of current directory (ls/1) or directory
 
172
%%           Dir (ls/2) at remote server. The returned list is a stream
 
173
%%           of file names.
 
174
%% Args:     Pid = pid(), Dir = string()
 
175
%% Returns:  {ok, Listing} | {error, epath} | {error, elogin} | {error, econn}
 
176
nlist(Pid) ->
 
177
  nlist(Pid, "").
 
178
nlist(Pid, Dir) ->
 
179
  gen_server:call(Pid, {dir, short, Dir}, infinity).
 
180
 
 
181
%% rename(Pid, CurrFile, NewFile)
 
182
%%
 
183
%% Purpose:  Rename a file at remote server.
 
184
%% Args:     Pid = pid(), CurrFile = NewFile = string()
 
185
%% Returns:  ok | {error, epath} | {error, elogin} | {error, econn}
 
186
rename(Pid, CurrFile, NewFile) ->
 
187
  gen_server:call(Pid, {rename, CurrFile, NewFile}, infinity).
 
188
 
 
189
%% delete(Pid, File)
 
190
%%
 
191
%% Purpose:  Remove file at remote server.
 
192
%% Args:     Pid = pid(), File = string()
 
193
%% Returns:  ok | {error, epath} | {error, elogin} | {error, econn}
 
194
delete(Pid, File) ->
 
195
  gen_server:call(Pid, {delete, File}, infinity).
 
196
 
 
197
%% mkdir(Pid, Dir)
 
198
%%
 
199
%% Purpose:  Make directory at remote server.
 
200
%% Args:     Pid = pid(), Dir = string()
 
201
%% Returns:  ok | {error, epath} | {error, elogin} | {error, econn}
 
202
mkdir(Pid, Dir) ->
 
203
  gen_server:call(Pid, {mkdir, Dir}, infinity).
 
204
 
 
205
%% rmdir(Pid, Dir)
 
206
%%
 
207
%% Purpose:  Remove directory at remote server.
 
208
%% Args:     Pid = pid(), Dir = string()
 
209
%% Returns:  ok | {error, epath} | {error, elogin} | {error, econn}
 
210
rmdir(Pid, Dir) ->
 
211
  gen_server:call(Pid, {rmdir, Dir}, infinity).
 
212
 
 
213
%% type(Pid, Type)
 
214
%%
 
215
%% Purpose:  Set transfer type.
 
216
%% Args:     Pid = pid(), Type = ascii | binary
 
217
%% Returns:  ok | {error, etype} | {error, elogin} | {error, econn}
 
218
type(Pid, Type) ->
 
219
  gen_server:call(Pid, {type, Type}, infinity).
 
220
 
 
221
%% recv(Pid, RFile [, LFile])
 
222
%%
 
223
%% Purpose:  Transfer file from remote server.
 
224
%% Args:     Pid = pid(), RFile = LFile = string()
 
225
%% Returns:  ok | {error, epath} | {error, elogin} | {error, econn}
 
226
recv(Pid, RFile) ->
 
227
  recv(Pid, RFile, "").
 
228
 
 
229
recv(Pid, RFile, LFile) ->
 
230
  gen_server:call(Pid, {recv, RFile, LFile}, infinity).
 
231
 
 
232
%% recv_bin(Pid, RFile)
 
233
%%
 
234
%% Purpose:  Transfer file from remote server into binary.
 
235
%% Args:     Pid = pid(), RFile = string()
 
236
%% Returns:  {ok, Bin} | {error, epath} | {error, elogin} | {error, econn}
 
237
recv_bin(Pid, RFile) ->
 
238
  gen_server:call(Pid, {recv_bin, RFile}, infinity).
 
239
 
 
240
%% recv_chunk_start(Pid, RFile)
 
241
%%
 
242
%% Purpose:  Start receive of chunks of remote file.
 
243
%% Args:     Pid = pid(), RFile = string().
 
244
%% Returns:  ok | {error, elogin} | {error, epath} | {error, econn}
 
245
recv_chunk_start(Pid, RFile) ->
 
246
  gen_server:call(Pid, {recv_chunk_start, RFile}, infinity).
 
247
 
 
248
 
 
249
%% recv_chunk(Pid, RFile)
 
250
%%
 
251
%% Purpose:  Transfer file from remote server into binary in chunks
 
252
%% Args:     Pid = pid(), RFile = string()
 
253
%% Returns:  Reference
 
254
recv_chunk(Pid) ->
 
255
    gen_server:call(Pid, recv_chunk, infinity).
 
256
 
 
257
%% send(Pid, LFile [, RFile])
 
258
%%
 
259
%% Purpose:  Transfer file to remote server.
 
260
%% Args:     Pid = pid(), LFile = RFile = string()
 
261
%% Returns:  ok | {error, epath} | {error, elogin} | {error, econn}
 
262
send(Pid, LFile) ->
 
263
  send(Pid, LFile, "").
 
264
 
 
265
send(Pid, LFile, RFile) ->
 
266
  gen_server:call(Pid, {send, LFile, RFile}, infinity).
 
267
 
 
268
%% send_bin(Pid, Bin, RFile)
 
269
%%
 
270
%% Purpose:  Transfer a binary to a remote file.
 
271
%% Args:     Pid = pid(), Bin = binary(), RFile = string()
 
272
%% Returns:  ok | {error, epath} | {error, elogin} | {error, enotbinary}
 
273
%%           | {error, econn}
 
274
send_bin(Pid, Bin, RFile) when binary(Bin) ->
 
275
  gen_server:call(Pid, {send_bin, Bin, RFile}, infinity);
 
276
send_bin(Pid, Bin, RFile) ->
 
277
  {error, enotbinary}.
 
278
 
 
279
%% send_chunk_start(Pid, RFile)
 
280
%%
 
281
%% Purpose:  Start transfer of chunks to remote file.
 
282
%% Args:     Pid = pid(), RFile = string().
 
283
%% Returns:  ok | {error, elogin} | {error, epath} | {error, econn}
 
284
send_chunk_start(Pid, RFile) ->
 
285
  gen_server:call(Pid, {send_chunk_start, RFile}, infinity).
 
286
 
 
287
 
 
288
%% append_chunk_start(Pid, RFile)
 
289
%%
 
290
%% Purpose:  Start append chunks of data to remote file.
 
291
%% Args:     Pid = pid(), RFile = string().
 
292
%% Returns:  ok | {error, elogin} | {error, epath} | {error, econn}
 
293
append_chunk_start(Pid, RFile) ->
 
294
  gen_server:call(Pid, {append_chunk_start, RFile}, infinity).
 
295
 
 
296
 
 
297
%% send_chunk(Pid, Bin)
 
298
%%
 
299
%% Purpose:  Send chunk to remote file.
 
300
%% Args:     Pid = pid(), Bin = binary().
 
301
%% Returns:  ok | {error, elogin} | {error, enotbinary} | {error, echunk}
 
302
%%           | {error, econn}
 
303
send_chunk(Pid, Bin) when binary(Bin) ->
 
304
  gen_server:call(Pid, {send_chunk, Bin}, infinity);
 
305
send_chunk(Pid, Bin) ->
 
306
  {error, enotbinary}.
 
307
 
 
308
%%append_chunk(Pid, Bin)
 
309
%%
 
310
%% Purpose:  Append chunk to remote file.
 
311
%% Args:     Pid = pid(), Bin = binary().
 
312
%% Returns:  ok | {error, elogin} | {error, enotbinary} | {error, echunk}
 
313
%%           | {error, econn}
 
314
append_chunk(Pid, Bin) when binary(Bin) ->
 
315
  gen_server:call(Pid, {append_chunk, Bin}, infinity);
 
316
append_chunk(Pid, Bin) ->
 
317
  {error, enotbinary}.
 
318
 
 
319
%% send_chunk_end(Pid)
 
320
%%
 
321
%% Purpose:  End sending of chunks to remote file.
 
322
%% Args:     Pid = pid().
 
323
%% Returns:  ok | {error, elogin} | {error, echunk} | {error, econn}
 
324
send_chunk_end(Pid) ->
 
325
  gen_server:call(Pid, send_chunk_end, infinity).
 
326
 
 
327
%% append_chunk_end(Pid)
 
328
%%
 
329
%% Purpose:  End appending of chunks to remote file.
 
330
%% Args:     Pid = pid().
 
331
%% Returns:  ok | {error, elogin} | {error, echunk} | {error, econn}
 
332
append_chunk_end(Pid) ->
 
333
  gen_server:call(Pid, append_chunk_end, infinity).
 
334
 
 
335
%% append(Pid, LFile,RFile)
 
336
%%
 
337
%% Purpose:  Append the local file to the remote file
 
338
%% Args:     Pid = pid(), LFile = RFile = string()
 
339
%% Returns:  ok | {error, epath} | {error, elogin} | {error, econn}
 
340
append(Pid, LFile) ->
 
341
    append(Pid, LFile, "").
 
342
 
 
343
append(Pid, LFile, RFile) ->
 
344
  gen_server:call(Pid, {append, LFile, RFile}, infinity).
 
345
 
 
346
%% append_bin(Pid, Bin, RFile)
 
347
%%
 
348
%% Purpose:  Append a binary to a remote file.
 
349
%% Args:     Pid = pid(), Bin = binary(), RFile = string()
 
350
%% Returns:  ok | {error, epath} | {error, elogin} | {error, enotbinary}
 
351
%%           | {error, econn}
 
352
append_bin(Pid, Bin, RFile) when binary(Bin) ->
 
353
  gen_server:call(Pid, {append_bin, Bin, RFile}, infinity);
 
354
append_bin(Pid, Bin, RFile) ->
 
355
  {error, enotbinary}.
 
356
 
 
357
 
 
358
%% close(Pid)
 
359
%%
 
360
%% Purpose:  End the ftp session.
 
361
%% Args:     Pid = pid()
 
362
%% Returns:  ok
 
363
close(Pid) ->
 
364
  case (catch gen_server:call(Pid, close, 30000)) of
 
365
      ok ->
 
366
          ok;
 
367
      {'EXIT',{noproc,_}} ->
 
368
          %% Already gone...
 
369
          ok;
 
370
      Res ->
 
371
          Res
 
372
  end.
 
373
 
 
374
%% formaterror(Tag)
 
375
%%
 
376
%% Purpose:  Return diagnostics.
 
377
%% Args:     Tag = atom() | {error, atom()}
 
378
%% Returns:  string().
 
379
formaterror(Tag) ->
 
380
  errstr(Tag).
 
381
 
 
382
%% help()
 
383
%%
 
384
%% Purpose:  Print list of valid commands.
 
385
%%
 
386
%% Undocumented.
 
387
%%
 
388
help() ->
 
389
  io:format("\n  Commands:\n"
 
390
            "  ---------\n"
 
391
            "  cd(Pid, Dir)\n"
 
392
            "  close(Pid)\n"
 
393
            "  delete(Pid, File)\n"
 
394
            "  formaterror(Tag)\n"
 
395
            "  help()\n"
 
396
            "  lcd(Pid, Dir)\n"
 
397
            "  lpwd(Pid)\n"
 
398
            "  ls(Pid [, Dir])\n"
 
399
            "  mkdir(Pid, Dir)\n"
 
400
            "  nlist(Pid [, Dir])\n"
 
401
            "  open(Host [Port, Flags])\n"
 
402
            "  pwd(Pid)\n"
 
403
            "  recv(Pid, RFile [, LFile])\n"
 
404
            "  recv_bin(Pid, RFile)\n"
 
405
            "  recv_chunk_start(Pid, RFile)\n"
 
406
            "  recv_chunk(Pid)\n"
 
407
            "  rename(Pid, CurrFile, NewFile)\n"
 
408
            "  rmdir(Pid, Dir)\n"
 
409
            "  send(Pid, LFile [, RFile])\n"
 
410
            "  send_chunk(Pid, Bin)\n"
 
411
            "  send_chunk_start(Pid, RFile)\n"
 
412
            "  send_chunk_end(Pid)\n"
 
413
            "  send_bin(Pid, Bin, RFile)\n"
 
414
            "  append(Pid, LFile [, RFile])\n"
 
415
            "  append_chunk(Pid, Bin)\n"
 
416
            "  append_chunk_start(Pid, RFile)\n"
 
417
            "  append_chunk_end(Pid)\n"
 
418
            "  append_bin(Pid, Bin, RFile)\n"
 
419
            "  type(Pid, Type)\n"
 
420
            "  account(Pid,Account)\n"
 
421
            "  user(Pid, User, Pass)\n"
 
422
            "  user(Pid, User, Pass,Account)\n").
 
423
 
 
424
%%
 
425
%% INIT
 
426
%%
 
427
 
 
428
-record(state, {csock = undefined, dsock = undefined, flags = undefined,
 
429
                ldir = undefined, type = undefined, chunk = false,
 
430
                pending = undefined}).
 
431
 
 
432
init([Flags]) ->
 
433
    sock_start(),
 
434
    put(debug,get_debug(Flags)),
 
435
    put(verbose,get_verbose(Flags)),
 
436
    process_flag(priority, low),
 
437
    {ok, LDir} = file:get_cwd(),
 
438
    {ok, #state{flags = Flags, ldir = LDir}}.
 
439
 
 
440
%%
 
441
%% HANDLERS
 
442
%%
 
443
 
 
444
%% First group of reply code digits
 
445
-define(POS_PREL, 1).
 
446
-define(POS_COMPL, 2).
 
447
-define(POS_INTERM, 3).
 
448
-define(TRANS_NEG_COMPL, 4).
 
449
-define(PERM_NEG_COMPL, 5).
 
450
 
 
451
%% Second group of reply code digits
 
452
-define(SYNTAX,0).
 
453
-define(INFORMATION,1).
 
454
-define(CONNECTION,2).
 
455
-define(AUTH_ACC,3).
 
456
-define(UNSPEC,4).
 
457
-define(FILE_SYSTEM,5).
 
458
 
 
459
 
 
460
-define(STOP_RET(E),{stop, normal, {error, E},
 
461
                     State#state{csock = undefined}}).
 
462
 
 
463
 
 
464
rescode(?POS_PREL,_,_)                   -> pos_prel; %%Positive Preleminary Reply
 
465
rescode(?POS_COMPL,_,_)                  -> pos_compl; %%Positive Completion Reply
 
466
rescode(?POS_INTERM,?AUTH_ACC,2)         -> pos_interm_acct; %%Positive Intermediate Reply nedd account
 
467
rescode(?POS_INTERM,_,_)                 -> pos_interm; %%Positive Intermediate Reply
 
468
rescode(?TRANS_NEG_COMPL,?FILE_SYSTEM,2) -> trans_no_space; %%No storage area no action taken
 
469
rescode(?TRANS_NEG_COMPL,_,_)            -> trans_neg_compl;%%Temporary Error, no action taken
 
470
rescode(?PERM_NEG_COMPL,?FILE_SYSTEM,2)  -> perm_no_space; %%Permanent disk space error, the user shall not try again
 
471
rescode(?PERM_NEG_COMPL,?FILE_SYSTEM,3)  -> perm_fname_not_allowed;
 
472
rescode(?PERM_NEG_COMPL,_,_)             -> perm_neg_compl.
 
473
 
 
474
retcode(trans_no_space,_)         -> etnospc;
 
475
retcode(perm_no_space,_)          -> epnospc;
 
476
retcode(perm_fname_not_allowed,_) -> efnamena;
 
477
retcode(_,Otherwise)              -> Otherwise.
 
478
 
 
479
handle_call({open,ip_comm,Conn_data},From,State) ->
 
480
    case lists:keysearch(host,1,Conn_data) of
 
481
        {value,{host,Host}}->
 
482
            Port=get_key1(port,Conn_data,?FTP_PORT),
 
483
            Timeout=get_key1(timeout,Conn_data,?OPEN_TIMEOUT),
 
484
            open(Host,Port,Timeout,State);
 
485
        false ->
 
486
            ehost
 
487
    end;
 
488
 
 
489
handle_call({open,ip_comm,Host,Port},From,State) ->
 
490
    open(Host,Port,?OPEN_TIMEOUT,State);
 
491
 
 
492
handle_call({user, User, Pass}, _From, State) ->
 
493
    #state{csock = CSock} = State,
 
494
    case ctrl_cmd(CSock, "USER ~s", [User]) of
 
495
        pos_interm ->
 
496
            case ctrl_cmd(CSock, "PASS ~s", [Pass]) of
 
497
                pos_compl ->
 
498
                    set_type(binary, CSock),
 
499
                    {reply, ok, State#state{type = binary}};
 
500
                {error,enotconn} ->
 
501
                    ?STOP_RET(econn);
 
502
                _ ->
 
503
                    {reply, {error, euser}, State}
 
504
            end;
 
505
        pos_compl ->
 
506
            set_type(binary, CSock),
 
507
            {reply, ok, State#state{type = binary}};
 
508
        {error, enotconn} ->
 
509
            ?STOP_RET(econn);
 
510
        _ ->
 
511
            {reply, {error, euser}, State}
 
512
    end;
 
513
 
 
514
handle_call({user, User, Pass,Acc}, _From, State) ->
 
515
    #state{csock = CSock} = State,
 
516
    case ctrl_cmd(CSock, "USER ~s", [User]) of
 
517
        pos_interm ->
 
518
            case ctrl_cmd(CSock, "PASS ~s", [Pass]) of
 
519
                pos_compl ->
 
520
                    set_type(binary, CSock),
 
521
                    {reply, ok, State#state{type = binary}};
 
522
                pos_interm_acct->
 
523
                    case ctrl_cmd(CSock,"ACCT ~s",[Acc]) of
 
524
                        pos_compl->
 
525
                            set_type(binary, CSock),
 
526
                            {reply, ok, State#state{type = binary}};
 
527
                        {error,enotconn}->
 
528
                            ?STOP_RET(econn);
 
529
                        _ ->
 
530
                            {reply, {error, eacct}, State}
 
531
                    end;
 
532
                {error,enotconn} ->
 
533
                    ?STOP_RET(econn);
 
534
                _ ->
 
535
                    {reply, {error, euser}, State}
 
536
            end;
 
537
        pos_compl ->
 
538
            set_type(binary, CSock),
 
539
            {reply, ok, State#state{type = binary}};
 
540
        {error, enotconn} ->
 
541
            ?STOP_RET(econn);
 
542
        _ ->
 
543
            {reply, {error, euser}, State}
 
544
    end;
 
545
 
 
546
%%set_account(Acc,State)->Reply
 
547
%%Reply={reply, {error, euser}, State} | {error,enotconn}->
 
548
handle_call({account,Acc},_From,State)->
 
549
    #state{csock = CSock} = State,
 
550
    case ctrl_cmd(CSock,"ACCT ~s",[Acc]) of
 
551
        pos_compl->
 
552
            {reply, ok,State};
 
553
        {error,enotconn}->
 
554
            ?STOP_RET(econn);
 
555
        Error ->
 
556
            debug(" error: ~p",[Error]),
 
557
            {reply, {error, eacct}, State}
 
558
    end;
 
559
 
 
560
handle_call(pwd, _From, State) when State#state.chunk == false ->
 
561
  #state{csock = CSock} = State,
 
562
  %%
 
563
  %% NOTE: The directory string comes over the control connection.
 
564
  case sock_write(CSock, mk_cmd("PWD", [])) of
 
565
    ok ->
 
566
      {_, Line} = result_line(CSock),
 
567
      {_, Cs} = split($", Line),                        % XXX Ugly
 
568
      {Dir0, _} = split($", Cs),
 
569
      Dir = lists:delete($", Dir0),
 
570
      {reply, {ok, Dir}, State};
 
571
    {error, enotconn} ->
 
572
      ?STOP_RET(econn)
 
573
  end;
 
574
 
 
575
handle_call(lpwd, _From, State) ->
 
576
  #state{csock = CSock, ldir = LDir} = State,
 
577
  {reply, {ok, LDir}, State};
 
578
 
 
579
handle_call({cd, Dir}, _From, State) when State#state.chunk == false ->
 
580
  #state{csock = CSock} = State,
 
581
  case ctrl_cmd(CSock, "CWD ~s", [Dir]) of
 
582
    pos_compl ->
 
583
      {reply, ok, State};
 
584
    {error, enotconn} ->
 
585
      ?STOP_RET(econn);
 
586
    _ ->
 
587
      {reply, {error, epath}, State}
 
588
  end;
 
589
 
 
590
handle_call({lcd, Dir}, _From, State) ->
 
591
  #state{csock = CSock, ldir = LDir0} = State,
 
592
  LDir = absname(LDir0, Dir),
 
593
  case file:read_file_info(LDir) of
 
594
    {ok, _ } ->
 
595
      {reply, ok, State#state{ldir = LDir}};
 
596
    _  ->
 
597
      {reply, {error, epath}, State}
 
598
  end;
 
599
 
 
600
handle_call({dir, Len, Dir}, _From, State) when State#state.chunk == false ->
 
601
    debug("  dir : ~p: ~s~n",[Len,Dir]),
 
602
    #state{csock = CSock, type = Type} = State,
 
603
    set_type(ascii, Type, CSock),
 
604
    LSock = listen_data(CSock, raw),
 
605
    Cmd = case Len of
 
606
              short -> "NLST";
 
607
              long -> "LIST"
 
608
          end,
 
609
    Result = case Dir of
 
610
                 "" ->
 
611
                     ctrl_cmd(CSock, Cmd, "");
 
612
                 _ ->
 
613
                     ctrl_cmd(CSock, Cmd ++ " ~s", [Dir])
 
614
             end,
 
615
    debug(" ctrl : command result: ~p~n",[Result]),
 
616
    case Result of
 
617
        pos_prel ->
 
618
            debug("  dbg : await the data connection", []),
 
619
            DSock = accept_data(LSock),
 
620
            debug("  dbg : await the data", []),
 
621
            Reply0 =
 
622
                case recv_data(DSock) of
 
623
                    {ok, DirData} ->
 
624
                        debug(" data : DirData: ~p~n",[DirData]),
 
625
                        case result(CSock) of
 
626
                            pos_compl ->
 
627
                                {ok, DirData};
 
628
                            _ ->
 
629
                                {error, epath}
 
630
                        end;
 
631
                    {error, Reason} ->
 
632
                        sock_close(DSock),
 
633
                        verbose(" data : error: ~p, ~p~n",[Reason, result(CSock)]),
 
634
                        {error, epath}
 
635
                end,
 
636
 
 
637
            debug(" ctrl : reply: ~p~n",[Reply0]),
 
638
            reset_type(ascii, Type, CSock),
 
639
            {reply, Reply0, State};
 
640
        {closed, _Why} ->
 
641
            ?STOP_RET(econn);
 
642
        _ ->
 
643
            sock_close(LSock),
 
644
            {reply, {error, epath}, State}
 
645
    end;
 
646
 
 
647
 
 
648
handle_call({rename, CurrFile, NewFile}, _From, State) when State#state.chunk == false ->
 
649
  #state{csock = CSock} = State,
 
650
  case ctrl_cmd(CSock, "RNFR ~s", [CurrFile]) of
 
651
    pos_interm ->
 
652
      case ctrl_cmd(CSock, "RNTO ~s", [NewFile]) of
 
653
        pos_compl ->
 
654
          {reply, ok, State};
 
655
        _ ->
 
656
          {reply, {error, epath}, State}
 
657
      end;
 
658
    {error, enotconn} ->
 
659
      ?STOP_RET(econn);
 
660
    _ ->
 
661
      {reply, {error, epath}, State}
 
662
  end;
 
663
 
 
664
handle_call({delete, File}, _From, State) when State#state.chunk == false ->
 
665
  #state{csock = CSock} = State,
 
666
  case ctrl_cmd(CSock, "DELE ~s", [File]) of
 
667
    pos_compl ->
 
668
      {reply, ok, State};
 
669
    {error, enotconn} ->
 
670
      ?STOP_RET(econn);
 
671
    _ ->
 
672
      {reply, {error, epath}, State}
 
673
  end;
 
674
 
 
675
handle_call({mkdir, Dir}, _From, State) when State#state.chunk == false ->
 
676
  #state{csock = CSock} = State,
 
677
  case ctrl_cmd(CSock, "MKD ~s", [Dir]) of
 
678
    pos_compl ->
 
679
      {reply, ok, State};
 
680
    {error, enotconn} ->
 
681
      ?STOP_RET(econn);
 
682
    _ ->
 
683
      {reply, {error, epath}, State}
 
684
  end;
 
685
 
 
686
handle_call({rmdir, Dir}, _From, State) when State#state.chunk == false ->
 
687
  #state{csock = CSock} = State,
 
688
  case ctrl_cmd(CSock, "RMD ~s", [Dir]) of
 
689
    pos_compl ->
 
690
      {reply, ok, State};
 
691
    {error, enotconn} ->
 
692
      ?STOP_RET(econn);
 
693
    _ ->
 
694
      {reply, {error, epath}, State}
 
695
  end;
 
696
 
 
697
handle_call({type, Type}, _From, State) when State#state.chunk == false ->
 
698
  #state{csock = CSock} = State,
 
699
  case Type of
 
700
    ascii ->
 
701
      set_type(ascii, CSock),
 
702
      {reply, ok, State#state{type = ascii}};
 
703
    binary ->
 
704
      set_type(binary, CSock),
 
705
      {reply, ok, State#state{type = binary}};
 
706
    _ ->
 
707
      {reply, {error, etype}, State}
 
708
  end;
 
709
 
 
710
handle_call({recv, RFile, LFile}, _From, State) when State#state.chunk == false ->
 
711
  #state{csock = CSock, ldir = LDir} = State,
 
712
  ALFile = case LFile of
 
713
             "" ->
 
714
               absname(LDir, RFile);
 
715
             _ ->
 
716
               absname(LDir, LFile)
 
717
           end,
 
718
  case file_open(ALFile, write) of
 
719
    {ok, Fd} ->
 
720
      LSock = listen_data(CSock, binary),
 
721
      Ret = case ctrl_cmd(CSock, "RETR ~s", [RFile]) of
 
722
              pos_prel ->
 
723
                DSock = accept_data(LSock),
 
724
                recv_file(DSock, Fd),
 
725
                Reply0 = case result(CSock) of
 
726
                           pos_compl ->
 
727
                             ok;
 
728
                           _ ->
 
729
                             {error, epath}
 
730
                         end,
 
731
                sock_close(DSock),
 
732
                {reply, Reply0, State};
 
733
              {error, enotconn} ->
 
734
                ?STOP_RET(econn);
 
735
              _ ->
 
736
                {reply, {error, epath}, State}
 
737
            end,
 
738
      file_close(Fd),
 
739
      Ret;
 
740
    {error, _What} ->
 
741
      {reply, {error, epath}, State}
 
742
  end;
 
743
 
 
744
handle_call({recv_bin, RFile}, _From, State) when State#state.chunk == false ->
 
745
    #state{csock = CSock, ldir = LDir} = State,
 
746
    LSock = listen_data(CSock, binary),
 
747
    case ctrl_cmd(CSock, "RETR ~s", [RFile]) of
 
748
        pos_prel ->
 
749
            DSock = accept_data(LSock),
 
750
            Reply = recv_binary(DSock,CSock),
 
751
            sock_close(DSock),
 
752
            {reply, Reply, State};
 
753
        {error, enotconn} ->
 
754
            ?STOP_RET(econn);
 
755
        _ ->
 
756
            {reply, {error, epath}, State}
 
757
    end;
 
758
 
 
759
 
 
760
handle_call({recv_chunk_start, RFile}, _From, State)
 
761
  when State#state.chunk == false ->
 
762
    start_chunk_transfer("RETR",RFile,State);
 
763
 
 
764
handle_call(recv_chunk, _From, State)
 
765
  when State#state.chunk == true ->
 
766
    do_recv_chunk(State);
 
767
 
 
768
 
 
769
handle_call({send, LFile, RFile}, _From, State)
 
770
  when State#state.chunk == false ->
 
771
    transfer_file("STOR",LFile,RFile,State);
 
772
 
 
773
handle_call({append, LFile, RFile}, _From, State)
 
774
  when State#state.chunk == false ->
 
775
    transfer_file("APPE",LFile,RFile,State);
 
776
 
 
777
 
 
778
handle_call({send_bin, Bin, RFile}, _From, State)
 
779
  when State#state.chunk == false ->
 
780
    transfer_data("STOR",Bin,RFile,State);
 
781
 
 
782
handle_call({append_bin, Bin, RFile}, _From, State)
 
783
  when State#state.chunk == false ->
 
784
  transfer_data("APPE",Bin,RFile,State);
 
785
 
 
786
 
 
787
 
 
788
handle_call({send_chunk_start, RFile}, _From, State)
 
789
  when State#state.chunk == false ->
 
790
    start_chunk_transfer("STOR",RFile,State);
 
791
 
 
792
handle_call({append_chunk_start,RFile},_From,State)
 
793
  when State#state.chunk==false->
 
794
    start_chunk_transfer("APPE",RFile,State);
 
795
 
 
796
handle_call({send_chunk, Bin}, _From, State)
 
797
  when State#state.chunk == true ->
 
798
    chunk_transfer(Bin,State);
 
799
 
 
800
handle_call({append_chunk, Bin}, _From, State)
 
801
  when State#state.chunk == true ->
 
802
    chunk_transfer(Bin,State);
 
803
 
 
804
handle_call(append_chunk_end, _From, State)
 
805
  when State#state.chunk == true ->
 
806
    end_chunk_transfer(State);
 
807
 
 
808
handle_call(send_chunk_end, _From, State)
 
809
  when State#state.chunk == true ->
 
810
    end_chunk_transfer(State);
 
811
 
 
812
 
 
813
 
 
814
handle_call(close, _From, State) when State#state.chunk == false ->
 
815
  #state{csock = CSock} = State,
 
816
  ctrl_cmd(CSock, "QUIT", []),
 
817
  sock_close(CSock),
 
818
  {stop, normal, ok, State};
 
819
 
 
820
handle_call(_, _From, State) when State#state.chunk == true ->
 
821
  {reply, {error, echunk}, State}.
 
822
 
 
823
 
 
824
handle_cast(Msg, State) ->
 
825
  {noreply, State}.
 
826
 
 
827
 
 
828
handle_info({Sock, {fromsocket, Bytes}}, State) when Sock == State#state.csock ->
 
829
  put(leftovers, Bytes ++ leftovers()),
 
830
  {noreply, State};
 
831
 
 
832
%% Data connection closed (during chunk sending)
 
833
handle_info({Sock, {socket_closed, _Reason}}, State) when Sock == State#state.dsock ->
 
834
  {noreply, State#state{dsock = undefined}};
 
835
 
 
836
%% Control connection closed.
 
837
handle_info({Sock, {socket_closed, _Reason}}, State) when Sock == State#state.csock ->
 
838
  debug("   sc : ~s~n",[leftovers()]),
 
839
  {stop, ftp_server_close, State#state{csock = undefined}};
 
840
 
 
841
handle_info(Info, State) ->
 
842
  error_logger:info_msg("ftp : ~w : Unexpected message: ~w\n", [self(),Info]),
 
843
  {noreply, State}.
 
844
 
 
845
code_change(OldVsn,State,Extra)->
 
846
    {ok,State}.
 
847
 
 
848
terminate(Reason, State) ->
 
849
  ok.
 
850
%%
 
851
%% OPEN CONNECTION
 
852
%%
 
853
open(Host,Port,Timeout,State)->
 
854
    case sock_connect(Host,Port,Timeout) of
 
855
        {error, What} ->
 
856
            {stop, normal, {error, What}, State};
 
857
        CSock ->
 
858
            case result(CSock, State#state.flags) of
 
859
                {error,Reason} ->
 
860
                    sock_close(CSock),
 
861
                    {stop,normal,{error,Reason},State};
 
862
                _ -> % We should really check this...
 
863
                    {reply, {ok, self()}, State#state{csock = CSock}}
 
864
            end
 
865
    end.
 
866
 
 
867
 
 
868
 
 
869
%%
 
870
%% CONTROL CONNECTION
 
871
%%
 
872
 
 
873
ctrl_cmd(CSock, Fmt, Args) ->
 
874
    Cmd = mk_cmd(Fmt, Args),
 
875
    case sock_write(CSock, Cmd) of
 
876
        ok ->
 
877
            debug("  cmd : ~s",[Cmd]),
 
878
            result(CSock);
 
879
        {error, enotconn} ->
 
880
            {error, enotconn};
 
881
        Other ->
 
882
            Other
 
883
    end.
 
884
 
 
885
mk_cmd(Fmt, Args) ->
 
886
    [io_lib:format(Fmt, Args)| "\r\n"].         % Deep list ok.
 
887
 
 
888
%%
 
889
%% TRANSFER TYPE
 
890
%%
 
891
 
 
892
%%
 
893
%% set_type(NewType, CurrType, CSock)
 
894
%% reset_type(NewType, CurrType, CSock)
 
895
%%
 
896
set_type(Type, Type, CSock) ->
 
897
  ok;
 
898
set_type(NewType, _OldType, CSock) ->
 
899
  set_type(NewType, CSock).
 
900
 
 
901
reset_type(Type, Type, CSock) ->
 
902
  ok;
 
903
reset_type(_NewType, OldType, CSock) ->
 
904
  set_type(OldType, CSock).
 
905
 
 
906
set_type(ascii, CSock) ->
 
907
  ctrl_cmd(CSock, "TYPE A", []);
 
908
set_type(binary, CSock) ->
 
909
  ctrl_cmd(CSock, "TYPE I", []).
 
910
 
 
911
%%
 
912
%% DATA CONNECTION
 
913
%%
 
914
 
 
915
%% Create a listen socket for a data connection and send a PORT command
 
916
%% containing the IP address and port number. Mode is binary or raw.
 
917
%%
 
918
listen_data(CSock, Mode) ->
 
919
  {IP, _} = sock_name(CSock), % IP address of control conn.
 
920
  LSock = sock_listen(Mode, IP),
 
921
  Port = sock_listen_port(LSock),
 
922
  {A1, A2, A3, A4} = IP,
 
923
  {P1, P2} = {Port div 256, Port rem 256},
 
924
  ctrl_cmd(CSock, "PORT ~w,~w,~w,~w,~w,~w", [A1, A2, A3, A4, P1, P2]),
 
925
  LSock.
 
926
 
 
927
%%
 
928
%% Accept the data connection and close the listen socket.
 
929
%%
 
930
accept_data(LSock) ->
 
931
  Sock = sock_accept(LSock),
 
932
  sock_close(LSock),
 
933
  Sock.
 
934
 
 
935
%%
 
936
%% DATA COLLECTION (ls, dir)
 
937
%%
 
938
%% Socket is a byte stream in ASCII mode.
 
939
%%
 
940
 
 
941
%% Receive data (from data connection).
 
942
recv_data(Sock) ->
 
943
    recv_data(Sock, [], 0).
 
944
recv_data(Sock, Sofar, ?OPER_TIMEOUT) ->
 
945
    sock_close(Sock),
 
946
    {ok, lists:flatten(lists:reverse(Sofar))};
 
947
recv_data(Sock, Sofar, Retry) ->
 
948
    case sock_read(Sock) of
 
949
        {ok, Data} ->
 
950
            debug("  dbg : received some data: ~n~s", [Data]),
 
951
            recv_data(Sock, [Data| Sofar], 0);
 
952
        {error, timeout} ->
 
953
            %% Retry..
 
954
            recv_data(Sock, Sofar, Retry+1);
 
955
        {error, Reason} ->
 
956
            SoFar1 = lists:flatten(lists:reverse(Sofar)),
 
957
            {error, {socket_error, Reason, SoFar1, Retry}};
 
958
        {closed, _} ->
 
959
            {ok, lists:flatten(lists:reverse(Sofar))}
 
960
    end.
 
961
 
 
962
%%
 
963
%% BINARY TRANSFER
 
964
%%
 
965
 
 
966
%% --------------------------------------------------
 
967
 
 
968
%% recv_binary(DSock,CSock) = {ok,Bin} | {error,Reason}
 
969
%%
 
970
recv_binary(DSock,CSock) ->
 
971
    recv_binary1(recv_binary2(DSock,[],0),CSock).
 
972
 
 
973
recv_binary1(Reply,Sock) ->
 
974
    case result(Sock) of
 
975
        pos_compl -> Reply;
 
976
        _         -> {error, epath}
 
977
    end.
 
978
 
 
979
recv_binary2(Sock, _Bs, ?OPER_TIMEOUT) ->
 
980
    sock_close(Sock),
 
981
    {error,eclosed};
 
982
recv_binary2(Sock, Bs, Retry) ->
 
983
    case sock_read(Sock) of
 
984
        {ok, Bin} ->
 
985
            recv_binary2(Sock, [Bs, Bin], 0);
 
986
        {error, timeout} ->
 
987
            recv_binary2(Sock, Bs, Retry+1);
 
988
        {closed, _Why} ->
 
989
            {ok,list_to_binary(Bs)}
 
990
  end.
 
991
 
 
992
%% --------------------------------------------------
 
993
 
 
994
%%
 
995
%% recv_chunk
 
996
%%
 
997
 
 
998
do_recv_chunk(#state{dsock = undefined} = State) ->
 
999
    {reply, {error,econn}, State};
 
1000
do_recv_chunk(State) ->
 
1001
    recv_chunk1(recv_chunk2(State, 0), State).
 
1002
 
 
1003
recv_chunk1({ok, _Bin} = Reply, State) ->
 
1004
    {reply, Reply, State};
 
1005
%% Reply = ok | {error, Reason}
 
1006
recv_chunk1(Reply, #state{csock = CSock} = State) ->
 
1007
    State1 = State#state{dsock = undefined, chunk = false},
 
1008
    case result(CSock) of
 
1009
        pos_compl ->
 
1010
            {reply, Reply, State1};
 
1011
        _         ->
 
1012
            {reply, {error, epath}, State1}
 
1013
    end.
 
1014
 
 
1015
recv_chunk2(#state{dsock = DSock} = State, ?OPER_TIMEOUT) ->
 
1016
    sock_close(DSock),
 
1017
    {error, eclosed};
 
1018
recv_chunk2(#state{dsock = DSock} = State, Retry) ->
 
1019
    case sock_read(DSock) of
 
1020
        {ok, Bin} ->
 
1021
            {ok, Bin};
 
1022
        {error, timeout} ->
 
1023
           recv_chunk2(State, Retry+1);
 
1024
        {closed, Reason} ->
 
1025
            debug("  dbg : socket closed: ~p", [Reason]),
 
1026
            ok
 
1027
    end.
 
1028
 
 
1029
 
 
1030
%% --------------------------------------------------
 
1031
 
 
1032
%%
 
1033
%% FILE TRANSFER
 
1034
%%
 
1035
 
 
1036
recv_file(Sock, Fd) ->
 
1037
    recv_file(Sock, Fd, 0).
 
1038
 
 
1039
recv_file(Sock, Fd, ?OPER_TIMEOUT) ->
 
1040
    sock_close(Sock),
 
1041
    {closed, timeout};
 
1042
recv_file(Sock, Fd, Retry) ->
 
1043
    case sock_read(Sock) of
 
1044
        {ok, Bin} ->
 
1045
            file_write(Fd, Bin),
 
1046
            recv_file(Sock, Fd);
 
1047
        {error, timeout} ->
 
1048
            recv_file(Sock, Fd, Retry+1);
 
1049
%       {error, Reason} ->
 
1050
%           SoFar1 = lists:flatten(lists:reverse(Sofar)),
 
1051
%           exit({socket_error, Reason, Sock, SoFar1, Retry});
 
1052
        {closed, How} ->
 
1053
            {closed, How}
 
1054
  end.
 
1055
 
 
1056
%%
 
1057
%% send_file(Fd, Sock) = ok | {error, Why}
 
1058
%%
 
1059
 
 
1060
send_file(Fd, Sock) ->
 
1061
  {N, Bin} = file_read(Fd),
 
1062
  if
 
1063
    N > 0 ->
 
1064
      case sock_write(Sock, Bin) of
 
1065
        ok ->
 
1066
          send_file(Fd, Sock);
 
1067
        {error, Reason} ->
 
1068
          {error, Reason}
 
1069
      end;
 
1070
    true ->
 
1071
      ok
 
1072
  end.
 
1073
 
 
1074
 
 
1075
 
 
1076
%%
 
1077
%% PARSING OF RESULT LINES
 
1078
%%
 
1079
 
 
1080
%% Excerpt from RFC 959:
 
1081
%%
 
1082
%%      "A reply is defined to contain the 3-digit code, followed by Space
 
1083
%%      <SP>, followed by one line of text (where some maximum line length
 
1084
%%      has been specified), and terminated by the Telnet end-of-line
 
1085
%%      code.  There will be cases however, where the text is longer than
 
1086
%%      a single line.  In these cases the complete text must be bracketed
 
1087
%%      so the User-process knows when it may stop reading the reply (i.e.
 
1088
%%      stop processing input on the control connection) and go do other
 
1089
%%      things.  This requires a special format on the first line to
 
1090
%%      indicate that more than one line is coming, and another on the
 
1091
%%      last line to designate it as the last.  At least one of these must
 
1092
%%      contain the appropriate reply code to indicate the state of the
 
1093
%%      transaction.  To satisfy all factions, it was decided that both
 
1094
%%      the first and last line codes should be the same.
 
1095
%%
 
1096
%%         Thus the format for multi-line replies is that the first line
 
1097
%%         will begin with the exact required reply code, followed
 
1098
%%         immediately by a Hyphen, "-" (also known as Minus), followed by
 
1099
%%         text.  The last line will begin with the same code, followed
 
1100
%%         immediately by Space <SP>, optionally some text, and the Telnet
 
1101
%%         end-of-line code.
 
1102
%%
 
1103
%%            For example:
 
1104
%%                                123-First line
 
1105
%%                                Second line
 
1106
%%                                  234 A line beginning with numbers
 
1107
%%                                123 The last line
 
1108
%%
 
1109
%%         The user-process then simply needs to search for the second
 
1110
%%         occurrence of the same reply code, followed by <SP> (Space), at
 
1111
%%         the beginning of a line, and ignore all intermediary lines.  If
 
1112
%%         an intermediary line begins with a 3-digit number, the Server
 
1113
%%         must pad the front  to avoid confusion.
 
1114
%%
 
1115
%%            This scheme allows standard system routines to be used for
 
1116
%%            reply information (such as for the STAT reply), with
 
1117
%%            "artificial" first and last lines tacked on.  In rare cases
 
1118
%%            where these routines are able to generate three digits and a
 
1119
%%            Space at the beginning of any line, the beginning of each
 
1120
%%            text line should be offset by some neutral text, like Space.
 
1121
%%
 
1122
%%         This scheme assumes that multi-line replies may not be nested."
 
1123
 
 
1124
%% We have to collect the stream of result characters into lines (ending
 
1125
%% in "\r\n"; we check for "\n"). When a line is assembled, left-over
 
1126
%% characters are saved in the process dictionary.
 
1127
%%
 
1128
 
 
1129
%% result(Sock) = rescode()
 
1130
%%
 
1131
result(Sock) ->
 
1132
  result(Sock, false).
 
1133
 
 
1134
result_line(Sock) ->
 
1135
  result(Sock, true).
 
1136
 
 
1137
%% result(Sock, Bool) = {error,Reason} | rescode() | {rescode(), Lines}
 
1138
%% Printout if Bool = true.
 
1139
%%
 
1140
result(Sock, RetForm) ->
 
1141
    case getline(Sock) of
 
1142
        Line when length(Line) > 3 ->
 
1143
            [D1, D2, D3| Tail] = Line,
 
1144
            case Tail of
 
1145
                [$-| _] ->
 
1146
                    parse_to_end(Sock, [D1, D2, D3, $ ]); % 3 digits + space
 
1147
                _ ->
 
1148
                    ok
 
1149
            end,
 
1150
            result(D1,D2,D3,Line,RetForm);
 
1151
        _ ->
 
1152
            retform(rescode(?PERM_NEG_COMPL,-1,-1),[],RetForm)
 
1153
    end.
 
1154
 
 
1155
result(D1,_D2,_D3,Line,_RetForm) when D1 - $0 > 10 ->
 
1156
    {error,{invalid_server_response,Line}};
 
1157
result(D1,_D2,_D3,Line,_RetForm) when D1 - $0 < 0 ->
 
1158
    {error,{invalid_server_response,Line}};
 
1159
result(D1,D2,D3,Line,RetForm) ->
 
1160
    Res1 = D1 - $0,
 
1161
    Res2 = D2 - $0,
 
1162
    Res3 = D3 - $0,
 
1163
    verbose("    ~w : ~s", [Res1, Line]),
 
1164
    retform(rescode(Res1,Res2,Res3),Line,RetForm).
 
1165
 
 
1166
retform(ResCode,Line,true) ->
 
1167
    {ResCode,Line};
 
1168
retform(ResCode,_,_) ->
 
1169
    ResCode.
 
1170
 
 
1171
leftovers() ->
 
1172
  case get(leftovers) of
 
1173
    undefined -> [];
 
1174
    X -> X
 
1175
  end.
 
1176
 
 
1177
%% getline(Sock) = Line
 
1178
%%
 
1179
getline(Sock) ->
 
1180
  getline(Sock, leftovers()).
 
1181
 
 
1182
getline(Sock, Rest) ->
 
1183
  getline1(Sock, split($\n, Rest), 0).
 
1184
 
 
1185
getline1(Sock, {[], Rest}, ?OPER_TIMEOUT) ->
 
1186
    sock_close(Sock),
 
1187
    put(leftovers, Rest),
 
1188
    [];
 
1189
getline1(Sock, {[], Rest}, Retry) ->
 
1190
    case sock_read(Sock) of
 
1191
        {ok, More} ->
 
1192
            debug(" read : ~s~n",[More]),
 
1193
            getline(Sock, Rest ++ More);
 
1194
        {error, timeout} ->
 
1195
            %% Retry..
 
1196
            getline1(Sock, {[], Rest}, Retry+1);
 
1197
        Error ->
 
1198
            put(leftovers, Rest),
 
1199
            []
 
1200
    end;
 
1201
getline1(Sock, {Line, Rest}, Retry) ->
 
1202
    put(leftovers, Rest),
 
1203
    Line.
 
1204
 
 
1205
parse_to_end(Sock, Prefix) ->
 
1206
  Line = getline(Sock),
 
1207
  case lists:prefix(Prefix, Line) of
 
1208
    false ->
 
1209
      parse_to_end(Sock, Prefix);
 
1210
    true ->
 
1211
      ok
 
1212
  end.
 
1213
 
 
1214
 
 
1215
%% Split list after first occurence of S.
 
1216
%% Returns {Prefix, Suffix} ({[], Cs} if S not found).
 
1217
split(S, Cs) ->
 
1218
  split(S, Cs, []).
 
1219
 
 
1220
split(S, [S| Cs], As) ->
 
1221
  {lists:reverse([S|As]), Cs};
 
1222
split(S, [C| Cs], As) ->
 
1223
  split(S, Cs, [C| As]);
 
1224
split(_, [], As) ->
 
1225
  {[], lists:reverse(As)}.
 
1226
 
 
1227
%%
 
1228
%%  FILE INTERFACE
 
1229
%%
 
1230
%%  All files are opened raw in binary mode.
 
1231
%%
 
1232
-define(BUFSIZE, 4096).
 
1233
 
 
1234
file_open(File, Option) ->
 
1235
  file:open(File, [raw, binary, Option]).
 
1236
 
 
1237
file_close(Fd) ->
 
1238
  file:close(Fd).
 
1239
 
 
1240
 
 
1241
file_read(Fd) ->                                % Compatible with pre R2A.
 
1242
  case file:read(Fd, ?BUFSIZE) of
 
1243
    {ok, {N, Bytes}} ->
 
1244
      {N, Bytes};
 
1245
    {ok, Bytes} ->
 
1246
      {size(Bytes), Bytes};
 
1247
    eof ->
 
1248
      {0, []}
 
1249
  end.
 
1250
 
 
1251
file_write(Fd, Bytes) ->
 
1252
  file:write(Fd, Bytes).
 
1253
 
 
1254
absname(Dir, File) ->                           % Args swapped.
 
1255
  filename:absname(File, Dir).
 
1256
 
 
1257
 
 
1258
 
 
1259
%% sock_start()
 
1260
%%
 
1261
 
 
1262
%%
 
1263
%% USE GEN_TCP
 
1264
%%
 
1265
 
 
1266
sock_start() ->
 
1267
  inet_db:start().
 
1268
 
 
1269
%%
 
1270
%% Connect to FTP server at Host (default is TCP port 21) in raw mode,
 
1271
%% in order to establish a control connection.
 
1272
%%
 
1273
 
 
1274
sock_connect(Host,Port,TimeOut) ->
 
1275
    debug(" info : connect to server on ~p:~p~n",[Host,Port]),
 
1276
    Opts = [{packet, 0}, {active, false}],
 
1277
    case (catch gen_tcp:connect(Host, Port, Opts,TimeOut)) of
 
1278
        {'EXIT', R1} -> % XXX Probably no longer needed.
 
1279
            debug(" error: socket connectionn failed with exit reason:"
 
1280
                  "~n   ~p",[R1]),
 
1281
            {error, ehost};
 
1282
        {error, R2} ->
 
1283
            debug(" error: socket connectionn failed with exit reason:"
 
1284
                  "~n   ~p",[R2]),
 
1285
            {error, ehost};
 
1286
        {ok, Sock} ->
 
1287
            Sock
 
1288
    end.
 
1289
 
 
1290
%%
 
1291
%% Create a listen socket (any port) in binary or raw non-packet mode for
 
1292
%% data connection.
 
1293
%%
 
1294
sock_listen(Mode, IP) ->
 
1295
  Opts = case Mode of
 
1296
           binary ->
 
1297
             [binary, {packet, 0}];
 
1298
           raw ->
 
1299
             [{packet, 0}]
 
1300
         end,
 
1301
  {ok, Sock} = gen_tcp:listen(0, [{ip, IP}, {active, false} | Opts]),
 
1302
  Sock.
 
1303
 
 
1304
sock_accept(LSock) ->
 
1305
  {ok, Sock} = gen_tcp:accept(LSock),
 
1306
  Sock.
 
1307
 
 
1308
sock_close(undefined) ->
 
1309
  ok;
 
1310
sock_close(Sock) ->
 
1311
  gen_tcp:close(Sock).
 
1312
 
 
1313
sock_read(Sock) ->
 
1314
  case gen_tcp:recv(Sock, 0, ?BYTE_TIMEOUT) of
 
1315
      {ok, Bytes} ->
 
1316
          {ok, Bytes};
 
1317
 
 
1318
      {error, closed} ->
 
1319
          {closed, closed};                     % Yes
 
1320
 
 
1321
      %% --- OTP-4770 begin ---
 
1322
      %%
 
1323
      %% This seems to happen on windows
 
1324
      %% "Someone" tried to close an already closed socket...
 
1325
      %%
 
1326
 
 
1327
      {error, enotsock} ->
 
1328
          {closed, enotsock};
 
1329
 
 
1330
      %%
 
1331
      %% --- OTP-4770 end ---
 
1332
 
 
1333
      {error, etimedout} ->
 
1334
          {error, timeout};
 
1335
 
 
1336
      Other ->
 
1337
          Other
 
1338
  end.
 
1339
 
 
1340
%%    receive
 
1341
%%      {tcp, Sock, Bytes} ->
 
1342
%%          {ok, Bytes};
 
1343
%%      {tcp_closed, Sock} ->
 
1344
%%          {closed, closed}
 
1345
%%    end.
 
1346
 
 
1347
sock_write(Sock, Bytes) ->
 
1348
  gen_tcp:send(Sock, Bytes).
 
1349
 
 
1350
sock_name(Sock) ->
 
1351
  {ok, {IP, Port}} = inet:sockname(Sock),
 
1352
  {IP, Port}.
 
1353
 
 
1354
sock_listen_port(LSock) ->
 
1355
  {ok, Port} = inet:port(LSock),
 
1356
  Port.
 
1357
 
 
1358
 
 
1359
%%
 
1360
%%  ERROR STRINGS
 
1361
%%
 
1362
errstr({error, Reason}) ->
 
1363
  errstr(Reason);
 
1364
 
 
1365
errstr(echunk) -> "Synchronisation error during chung sending.";
 
1366
errstr(eclosed) -> "Session has been closed.";
 
1367
errstr(econn) ->  "Connection to remote server prematurely closed.";
 
1368
errstr(eexists) ->"File or directory already exists.";
 
1369
errstr(ehost) ->  "Host not found, FTP server not found, "
 
1370
"or connection rejected.";
 
1371
errstr(elogin) -> "User not logged in.";
 
1372
errstr(enotbinary) -> "Term is not a binary.";
 
1373
errstr(epath) ->  "No such file or directory, already exists, "
 
1374
"or permission denied.";
 
1375
errstr(etype) ->  "No such type.";
 
1376
errstr(euser) ->  "User name or password not valid.";
 
1377
errstr(etnospc) -> "Insufficient storage space in system.";
 
1378
errstr(epnospc) -> "Exceeded storage allocation "
 
1379
"(for current directory or dataset).";
 
1380
errstr(efnamena) -> "File name not allowed.";
 
1381
errstr(Reason) ->
 
1382
  lists:flatten(io_lib:format("Unknown error: ~w", [Reason])).
 
1383
 
 
1384
 
 
1385
 
 
1386
%% ----------------------------------------------------------
 
1387
 
 
1388
get_verbose(Params) -> check_param(verbose,Params).
 
1389
 
 
1390
get_debug(Flags)    -> check_param(debug,Flags).
 
1391
 
 
1392
check_param(P,Ps)   -> lists:member(P,Ps).
 
1393
 
 
1394
 
 
1395
%% verbose -> ok
 
1396
%%
 
1397
%% Prints the string if the Flags list is non-epmty
 
1398
%%
 
1399
%% Params: F   Format string
 
1400
%%         A   Arguments to the format string
 
1401
%%
 
1402
verbose(F,A) -> verbose(get(verbose),F,A).
 
1403
 
 
1404
verbose(true,F,A) -> print(F,A);
 
1405
verbose(_,_F,_A)  -> ok.
 
1406
 
 
1407
 
 
1408
 
 
1409
 
 
1410
%% debug -> ok
 
1411
%%
 
1412
%% Prints the string if debug enabled
 
1413
%%
 
1414
%% Params: F   Format string
 
1415
%%         A   Arguments to the format string
 
1416
%%
 
1417
debug(F,A) -> debug(get(debug),F,A).
 
1418
 
 
1419
debug(true,F,A) -> print(F,A);
 
1420
debug(_,_F,_A)  -> ok.
 
1421
 
 
1422
 
 
1423
print(F,A) -> io:format(F,A).
 
1424
 
 
1425
 
 
1426
 
 
1427
transfer_file(Cmd,LFile,RFile,State)->
 
1428
    #state{csock = CSock, ldir = LDir} = State,
 
1429
    ARFile = case RFile of
 
1430
               "" ->
 
1431
                   LFile;
 
1432
               _ ->
 
1433
                   RFile
 
1434
           end,
 
1435
    ALFile = absname(LDir, LFile),
 
1436
    case file_open(ALFile, read) of
 
1437
      {ok, Fd} ->
 
1438
          LSock = listen_data(CSock, binary),
 
1439
          case ctrl_cmd(CSock, "~s ~s", [Cmd,ARFile]) of
 
1440
              pos_prel ->
 
1441
                  DSock = accept_data(LSock),
 
1442
                  SFreply = send_file(Fd, DSock),
 
1443
                  file_close(Fd),
 
1444
                  sock_close(DSock),
 
1445
                  case {SFreply,result(CSock)} of
 
1446
                      {ok,pos_compl} ->
 
1447
                          {reply, ok, State};
 
1448
                      {ok,Other} ->
 
1449
                          debug(" error: unknown reply: ~p~n",[Other]),
 
1450
                          {reply, {error, epath}, State};
 
1451
                      {{error,Why},Result} ->
 
1452
                          ?STOP_RET(retcode(Result,econn))
 
1453
                  end;
 
1454
              {error, enotconn} ->
 
1455
                  ?STOP_RET(econn);
 
1456
              Other ->
 
1457
                  debug(" error: ctrl failed: ~p~n",[Other]),
 
1458
                  {reply, {error, epath}, State}
 
1459
          end;
 
1460
        {error, Reason} ->
 
1461
            debug(" error: file open: ~p~n",[Reason]),
 
1462
            {reply, {error, epath}, State}
 
1463
    end.
 
1464
 
 
1465
transfer_data(Cmd,Bin,RFile,State)->
 
1466
    #state{csock = CSock, ldir = LDir} = State,
 
1467
    LSock = listen_data(CSock, binary),
 
1468
    case ctrl_cmd(CSock, "~s ~s", [Cmd,RFile]) of
 
1469
        pos_prel ->
 
1470
            DSock  = accept_data(LSock),
 
1471
            SReply = sock_write(DSock, Bin),
 
1472
            sock_close(DSock),
 
1473
            case {SReply,result(CSock)} of
 
1474
                {ok,pos_compl} ->
 
1475
                    {reply, ok, State};
 
1476
                {ok,trans_no_space} ->
 
1477
                    ?STOP_RET(etnospc);
 
1478
                {ok,perm_no_space} ->
 
1479
                    ?STOP_RET(epnospc);
 
1480
                {ok,perm_fname_not_allowed} ->
 
1481
                    ?STOP_RET(efnamena);
 
1482
                {ok,Other} ->
 
1483
                    debug(" error: unknown reply: ~p~n",[Other]),
 
1484
                    {reply, {error, epath}, State};
 
1485
                {{error,Why},Result} ->
 
1486
                    ?STOP_RET(retcode(Result,econn))
 
1487
            %% {{error,_Why},_Result} ->
 
1488
            %%    ?STOP_RET(econn)
 
1489
            end;
 
1490
 
 
1491
        {error, enotconn} ->
 
1492
            ?STOP_RET(econn);
 
1493
 
 
1494
        Other ->
 
1495
            debug(" error: ctrl failed: ~p~n",[Other]),
 
1496
            {reply, {error, epath}, State}
 
1497
    end.
 
1498
 
 
1499
 
 
1500
start_chunk_transfer(Cmd, RFile, #state{csock = CSock} = State) ->
 
1501
  LSock = listen_data(CSock, binary),
 
1502
  case ctrl_cmd(CSock, "~s ~s", [Cmd,RFile]) of
 
1503
    pos_prel ->
 
1504
      DSock = accept_data(LSock),
 
1505
      {reply, ok, State#state{dsock = DSock, chunk = true}};
 
1506
    {error, enotconn} ->
 
1507
      ?STOP_RET(econn);
 
1508
    Otherwise ->
 
1509
      debug(" error: ctrl failed: ~p~n",[Otherwise]),
 
1510
      {reply, {error, epath}, State}
 
1511
  end.
 
1512
 
 
1513
 
 
1514
chunk_transfer(Bin,State)->
 
1515
  #state{dsock = DSock, csock = CSock} = State,
 
1516
  case DSock of
 
1517
    undefined ->
 
1518
      {reply,{error,econn},State};
 
1519
    _ ->
 
1520
      case sock_write(DSock, Bin) of
 
1521
        ok ->
 
1522
          {reply, ok, State};
 
1523
        Other ->
 
1524
          debug(" error: chunk write error: ~p~n",[Other]),
 
1525
          {reply, {error, econn}, State#state{dsock = undefined}}
 
1526
      end
 
1527
  end.
 
1528
 
 
1529
 
 
1530
 
 
1531
end_chunk_transfer(State)->
 
1532
    #state{csock = CSock, dsock = DSock} = State,
 
1533
    case DSock of
 
1534
        undefined ->
 
1535
            Result = result(CSock),
 
1536
            case Result of
 
1537
                pos_compl ->
 
1538
                    {reply,ok,State#state{dsock = undefined,
 
1539
                                          chunk = false}};
 
1540
                trans_no_space ->
 
1541
                    ?STOP_RET(etnospc);
 
1542
                perm_no_space ->
 
1543
                    ?STOP_RET(epnospc);
 
1544
                perm_fname_not_allowed ->
 
1545
                    ?STOP_RET(efnamena);
 
1546
                Result ->
 
1547
                    debug(" error: send chunk end (1): ~p~n",
 
1548
                          [Result]),
 
1549
                    {reply,{error,epath},State#state{dsock = undefined,
 
1550
                                                     chunk = false}}
 
1551
            end;
 
1552
        _ ->
 
1553
            sock_close(DSock),
 
1554
            Result = result(CSock),
 
1555
            case Result of
 
1556
                pos_compl ->
 
1557
                    {reply,ok,State#state{dsock = undefined,
 
1558
                                          chunk = false}};
 
1559
                trans_no_space ->
 
1560
                    sock_close(CSock),
 
1561
                    ?STOP_RET(etnospc);
 
1562
                perm_no_space ->
 
1563
                    sock_close(CSock),
 
1564
                    ?STOP_RET(epnospc);
 
1565
                perm_fname_not_allowed ->
 
1566
                    sock_close(CSock),
 
1567
                    ?STOP_RET(efnamena);
 
1568
                Result ->
 
1569
                    debug(" error: send chunk end (2): ~p~n",
 
1570
                          [Result]),
 
1571
                    {reply,{error,epath},State#state{dsock = undefined,
 
1572
                                                     chunk = false}}
 
1573
            end
 
1574
    end.
 
1575
 
 
1576
get_key1(Key,List,Default)->
 
1577
    case lists:keysearch(Key,1,List)of
 
1578
        {value,{_,Val}}->
 
1579
            Val;
 
1580
        false->
 
1581
            Default
 
1582
    end.