1%%
2%% %CopyrightBegin%
3%%
4%% Copyright Ericsson AB 2002-2018. All Rights Reserved.
5%%
6%% Licensed under the Apache License, Version 2.0 (the "License");
7%% you may not use this file except in compliance with the License.
8%% You may obtain a copy of the License at
9%%
10%%     http://www.apache.org/licenses/LICENSE-2.0
11%%
12%% Unless required by applicable law or agreed to in writing, software
13%% distributed under the License is distributed on an "AS IS" BASIS,
14%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
15%% See the License for the specific language governing permissions and
16%% limitations under the License.
17%%
18%% %CopyrightEnd%
19%%
20%%
21
22-module(ftp).
23
24-behaviour(gen_server).
25
26-deprecated([{start_service, 1, "use ftp:open/2 instead"},
27             {stop_service, 1,  "use ftp:close/1 instead"}]).
28
29-export([start/0,
30         start_service/1,
31         stop/0,
32         stop_service/1
33        ]).
34
35-export([start_link/1, start_link/2]).
36
37%%  API - Client interface
38-export([cd/2, close/1, delete/2, formaterror/1,
39         lcd/2, lpwd/1, ls/1, ls/2,
40         mkdir/2, nlist/1, nlist/2,
41         open/1, open/2,
42         pwd/1, quote/2,
43         recv/2, recv/3, recv_bin/2,
44         recv_chunk_start/2, recv_chunk/1,
45         rename/3, rmdir/2,
46         send/2, send/3, send_bin/3,
47         send_chunk_start/2, send_chunk/2, send_chunk_end/1,
48         type/2, user/3, user/4, account/2,
49         append/3, append/2, append_bin/3,
50         append_chunk/2, append_chunk_end/1, append_chunk_start/2,
51         info/1, latest_ctrl_response/1]).
52
53%% gen_server callbacks
54-export([init/1, handle_call/3, handle_cast/2,
55         handle_info/2, terminate/2, code_change/3]).
56
57-include("ftp_internal.hrl").
58
59%% Constants used in internal state definition
60-define(CONNECTION_TIMEOUT,  60*1000).
61-define(DATA_ACCEPT_TIMEOUT, infinity).
62-define(DEFAULT_MODE,        passive).
63-define(PROGRESS_DEFAULT,    ignore).
64-define(FTP_EXT_DEFAULT,     false).
65
66%% Internal Constants
67-define(FTP_PORT, 21).
68-define(FTPS_PORT, 990).
69-define(FILE_BUFSIZE, 4096).
70
71
72%%%=========================================================================
73%%%  Data Types
74%%%=========================================================================
75
76%% Internal state
77-record(state, {
78          csock   = undefined, % socket() - Control connection socket
79          dsock   = undefined, % socket() - Data connection socket
80          tls_options = undefined, % list()
81          verbose = false, % boolean()
82          ldir    = undefined, % string() - Current local directory
83          type    = ftp_server_default, % atom() - binary | ascii
84          chunk   = false, % boolean() - Receiving data chunks
85          mode    = ?DEFAULT_MODE, % passive | active
86          timeout = ?CONNECTION_TIMEOUT, % integer()
87          %% Data received so far on the data connection
88          data    = <<>>, % binary()
89          %% Data received so far on the control connection
90          %% {BinStream, AccLines}. If a binary sequence
91          %% ends with ?CR then keep it in the binary to
92          %% be able to detect if the next received byte is ?LF
93          %% and hence the end of the response is reached!
94          ctrl_data = {<<>>, [], start}, % {binary(), [bytes()], LineStatus}
95          %% pid() - Client pid (note not the same as "From")
96          latest_ctrl_response = "",
97          owner = undefined,
98          client = undefined, % "From" to be used in gen_server:reply/2
99          %% Function that activated a connection and maybe some
100          %% data needed further on.
101          caller = undefined, % term()
102          ipfamily, % inet | inet6 | inet6fb4
103          sockopts_ctrl = [],
104          sockopts_data_passive = [],
105          sockopts_data_active = [],
106          progress = ignore, % ignore | pid()
107          dtimeout = ?DATA_ACCEPT_TIMEOUT, % non_neg_integer() | infinity
108          tls_ctrl_session_reuse = false, % boolean()
109          tls_upgrading_data_connection = false,
110          ftp_extension = ?FTP_EXT_DEFAULT
111         }).
112
113-record(recv_chunk_closing, {
114          dconn_closed = false,
115          pos_compl_received = false,
116          client_called_us = false
117         }).
118
119
120-type shortage_reason()  :: 'etnospc' | 'epnospc'.
121-type restriction_reason() :: 'epath' | 'efnamena' | 'elogin' | 'enotbinary'.
122-type common_reason() ::  'econn' | 'eclosed' | term().
123-type file_write_error_reason() :: term(). % See file:write for more info
124
125-define(DBG(F,A), 'n/a').
126%%-define(DBG(F,A), io:format(F,A)).
127%%-define(DBG(F,A), ct:pal("~p:~p " ++ if is_list(F) -> F; is_atom(F) -> atom_to_list(F) end, [?MODULE,?LINE|A])).
128
129
130%%%=========================================================================
131%%%  API
132%%%=========================================================================
133
134start() ->
135    application:start(ftp).
136
137%% This should be made an internal function when we remove the deprecation
138%% ftp client processes should always be part of ftp supervisor tree.
139%% We consider it a bug that the "standalone" concept of inets was
140%% not removed when ftp was broken out, and it is now fixed.
141start_service(Options) ->
142    try
143        {ok, StartOptions} = start_options(Options),
144        case ftp_sup:start_child([[[{client, self()} | StartOptions], []]]) of
145            {ok, Pid} ->
146                call(Pid, {open, ip_comm, Options}, plain);
147            Error1 ->
148                Error1
149        end
150    catch
151        throw:Error2 ->
152            Error2
153    end.
154
155stop() ->
156    application:stop(ftp).
157
158stop_service(Pid) ->
159    close(Pid).
160
161%%%=========================================================================
162%%%  API - CLIENT FUNCTIONS
163%%%=========================================================================
164
165%%--------------------------------------------------------------------------
166%% open(HostOrOtpList, <Port>, <Flags>) -> {ok, Pid} | {error, ehost}
167%%        HostOrOtpList = string() | [{option_list, Options}]
168%%      Port = integer(),
169%%      Flags = [Flag],
170%%      Flag = verbose | debug | trace
171%%
172%% Description:  Start an ftp client and connect to a host.
173%%--------------------------------------------------------------------------
174
175-spec open(Host :: string() | inet:ip_address()) ->
176    {'ok', Pid :: pid()} | {'error', Reason :: 'ehost' | term()}.
177
178%% <BACKWARD-COMPATIBILLITY>
179open({option_list, Options}) when is_list(Options) ->
180    start_service(Options);
181%% </BACKWARD-COMPATIBILLITY>
182
183open(Host) ->
184    open(Host, []).
185
186-spec open(Host :: string() | inet:ip_address(), Opts :: list()) ->
187    {'ok', Pid :: pid()} | {'error', Reason :: 'ehost' | term()}.
188
189%% <BACKWARD-COMPATIBILLITY>
190open(Host, Port) when is_integer(Port) ->
191    open(Host, [{port, Port}]);
192%% </BACKWARD-COMPATIBILLITY>
193
194open(Host, Options) when is_list(Options) ->
195    start_service([{host,Host}|Options]).
196
197%%--------------------------------------------------------------------------
198%% user(Pid, User, Pass, <Acc>) -> ok | {error, euser} | {error, econn}
199%%                                    | {error, eacct}
200%%        Pid = pid(),
201%%      User = Pass =  Acc = string()
202%%
203%% Description:  Login with or without a supplied account name.
204%%--------------------------------------------------------------------------
205-spec user(Pid  :: pid(),
206           User :: string(),
207           Pass :: string()) ->
208    'ok' | {'error', Reason :: 'euser' | common_reason()}.
209
210user(Pid, User, Pass) ->
211    case {is_name_sane(User), is_name_sane(Pass)} of
212        {true, true} ->
213            call(Pid, {user, User, Pass}, atom);
214        _ ->
215            {error, euser}
216    end.
217
218-spec user(Pid  :: pid(),
219           User :: string(),
220           Pass :: string(),
221           Acc  :: string()) ->
222    'ok' | {'error', Reason :: 'euser' | common_reason()}.
223
224user(Pid, User, Pass, Acc) ->
225    case {is_name_sane(User), is_name_sane(Pass), is_name_sane(Acc)} of
226        {true, true, true} ->
227            call(Pid, {user, User, Pass, Acc}, atom);
228        _ ->
229            {error, euser}
230    end.
231
232
233%%--------------------------------------------------------------------------
234%% account(Pid, Acc)  -> ok | {error, eacct}
235%%        Pid = pid()
236%%        Acc= string()
237%%
238%% Description:  Set a user Account.
239%%--------------------------------------------------------------------------
240
241-spec account(Pid :: pid(), Acc :: string()) ->
242    'ok' | {'error', Reason :: 'eacct' | common_reason()}.
243
244account(Pid, Acc) ->
245    case is_name_sane(Acc) of
246        true ->
247            call(Pid, {account, Acc}, atom);
248        _ ->
249            {error, eacct}
250    end.
251
252
253%%--------------------------------------------------------------------------
254%% pwd(Pid) -> {ok, Dir} | {error, elogin} | {error, econn}
255%%        Pid = pid()
256%%      Dir = string()
257%%
258%% Description:  Get the current working directory at remote server.
259%%--------------------------------------------------------------------------
260
261-spec pwd(Pid :: pid()) ->
262    {'ok', Dir :: string()} |
263        {'error', Reason :: restriction_reason() | common_reason()}.
264
265pwd(Pid) ->
266    call(Pid, pwd, ctrl).
267
268
269%%--------------------------------------------------------------------------
270%% lpwd(Pid) ->  {ok, Dir}
271%%        Pid = pid()
272%%      Dir = string()
273%%
274%% Description:  Get the current working directory at local server.
275%%--------------------------------------------------------------------------
276
277-spec lpwd(Pid :: pid()) ->
278    {'ok', Dir :: string()}.
279
280lpwd(Pid) ->
281    call(Pid, lpwd, string).
282
283
284%%--------------------------------------------------------------------------
285%% cd(Pid, Dir) ->  ok | {error, epath} | {error, elogin} | {error, econn}
286%%        Pid = pid()
287%%        Dir = string()
288%%
289%% Description:  Change current working directory at remote server.
290%%--------------------------------------------------------------------------
291
292-spec cd(Pid :: pid(), Dir :: string()) ->
293    'ok' | {'error', Reason :: restriction_reason() | common_reason()}.
294
295cd(Pid, Dir) ->
296    case is_name_sane(Dir) of
297        true ->
298            call(Pid, {cd, Dir}, atom);
299        _ ->
300            {error, efnamena}
301    end.
302
303
304%%--------------------------------------------------------------------------
305%% lcd(Pid, Dir) ->  ok | {error, epath}
306%%        Pid = pid()
307%%        Dir = string()
308%%
309%% Description:  Change current working directory for the local client.
310%%--------------------------------------------------------------------------
311
312-spec lcd(Pid :: pid(), Dir :: string()) ->
313    'ok' | {'error', Reason :: restriction_reason()}.
314
315lcd(Pid, Dir) ->
316    call(Pid, {lcd, Dir}, string).
317
318
319%%--------------------------------------------------------------------------
320%% ls(Pid) -> Result
321%% ls(Pid, <Dir>) -> Result
322%%
323%%        Pid = pid()
324%%        Dir = string()
325%%      Result = {ok, Listing} | {error, Reason}
326%%      Listing = string()
327%%      Reason = epath | elogin | econn
328%%
329%% Description: Returns a list of files in long format.
330%%--------------------------------------------------------------------------
331
332-spec ls(Pid :: pid()) ->
333    {'ok', Listing :: string()} |
334        {'error', Reason :: restriction_reason() | common_reason()}.
335
336ls(Pid) ->
337  ls(Pid, "").
338
339-spec ls(Pid :: pid(), Dir :: string()) ->
340    {'ok', Listing :: string()} |
341        {'error', Reason ::  restriction_reason() | common_reason()}.
342
343ls(Pid, Dir) ->
344    case is_name_sane(Dir) of
345        true ->
346            call(Pid, {dir, long, Dir}, string);
347        _ ->
348            {error, efnamena}
349    end.
350
351
352%%--------------------------------------------------------------------------
353%% nlist(Pid) -> Result
354%% nlist(Pid, Pathname) -> Result
355%%
356%%        Pid = pid()
357%%        Pathname = string()
358%%      Result = {ok, Listing} | {error, Reason}
359%%      Listing = string()
360%%      Reason = epath | elogin | econn
361%%
362%% Description:  Returns a list of files in short format
363%%--------------------------------------------------------------------------
364
365-spec nlist(Pid :: pid()) ->
366    {'ok', Listing :: string()} |
367        {'error', Reason :: restriction_reason() | common_reason()}.
368
369nlist(Pid) ->
370  nlist(Pid, "").
371
372-spec nlist(Pid :: pid(), Pathname :: string()) ->
373    {'ok', Listing :: string()} |
374        {'error', Reason :: restriction_reason() | common_reason()}.
375
376nlist(Pid, Dir) ->
377    case is_name_sane(Dir) of
378        true ->
379            call(Pid, {dir, short, Dir}, string);
380        _ ->
381            {error, efnamena}
382    end.
383
384
385%%--------------------------------------------------------------------------
386%% rename(Pid, Old, New) ->  ok | {error, epath} | {error, elogin}
387%%                              | {error, econn}
388%%        Pid = pid()
389%%        CurrFile = NewFile = string()
390%%
391%% Description:  Rename a file at remote server.
392%%--------------------------------------------------------------------------
393
394-spec rename(Pid :: pid(), Old :: string(), New :: string()) ->
395    'ok' | {'error', Reason :: restriction_reason() | common_reason()}.
396
397rename(Pid, Old, New) ->
398    case {is_name_sane(Old), is_name_sane(New)} of
399        {true, true} ->
400            call(Pid, {rename, Old, New}, string);
401        _ ->
402            {error, efnamena}
403    end.
404
405
406%%--------------------------------------------------------------------------
407%% delete(Pid, File) ->  ok | {error, epath} | {error, elogin} |
408%%                       {error, econn}
409%%        Pid = pid()
410%%        File = string()
411%%
412%% Description:  Remove file at remote server.
413%%--------------------------------------------------------------------------
414
415-spec delete(Pid :: pid(), File :: string()) ->
416    'ok' | {'error', Reason :: restriction_reason() | common_reason()}.
417
418delete(Pid, File) ->
419    case is_name_sane(File) of
420        true ->
421            call(Pid, {delete, File}, string);
422        _ ->
423            {error, efnamena}
424    end.
425
426
427%%--------------------------------------------------------------------------
428%% mkdir(Pid, Dir) -> ok | {error, epath} | {error, elogin} | {error, econn}
429%%        Pid = pid(),
430%%        Dir = string()
431%%
432%% Description:  Make directory at remote server.
433%%--------------------------------------------------------------------------
434
435-spec mkdir(Pid :: pid(), Dir :: string()) ->
436    'ok' | {'error', Reason :: restriction_reason() | common_reason()}.
437
438mkdir(Pid, Dir) ->
439    case is_name_sane(Dir) of
440        true ->
441            call(Pid, {mkdir, Dir}, atom);
442        _ ->
443            {error, efnamena}
444    end.
445
446
447%%--------------------------------------------------------------------------
448%% rmdir(Pid, Dir) -> ok | {error, epath} | {error, elogin} | {error, econn}
449%%        Pid = pid(),
450%%        Dir = string()
451%%
452%% Description:  Remove directory at remote server.
453%%--------------------------------------------------------------------------
454
455-spec rmdir(Pid :: pid(), Dir :: string()) ->
456    'ok' | {'error', Reason :: restriction_reason() | common_reason()}.
457
458rmdir(Pid, Dir) ->
459    case is_name_sane(Dir) of
460        true ->
461            call(Pid, {rmdir, Dir}, atom);
462        _ ->
463            {error, efnamena}
464    end.
465
466
467%%--------------------------------------------------------------------------
468%% type(Pid, Type) -> ok | {error, etype} | {error, elogin} | {error, econn}
469%%        Pid = pid()
470%%        Type = ascii | binary
471%%
472%% Description:  Set transfer type.
473%%--------------------------------------------------------------------------
474
475-spec type(Pid :: pid(), Type :: ascii | binary) ->
476    'ok' |
477        {'error', Reason :: 'etype' | restriction_reason() | common_reason()}.
478
479type(Pid, Type) ->
480    call(Pid, {type, Type}, atom).
481
482
483%%--------------------------------------------------------------------------
484%% recv(Pid, RemoteFileName [, LocalFileName]) -> ok | {error, epath} |
485%%                                          {error, elogin} | {error, econn}
486%%        Pid = pid()
487%%        RemoteFileName = LocalFileName = string()
488%%
489%% Description:  Transfer file from remote server.
490%%--------------------------------------------------------------------------
491
492-spec recv(Pid :: pid(), RemoteFileName :: string()) ->
493    'ok' | {'error', Reason :: restriction_reason() |
494                               common_reason() |
495                               file_write_error_reason()}.
496
497recv(Pid, RemotFileName) ->
498  recv(Pid, RemotFileName, RemotFileName).
499
500-spec recv(Pid            :: pid(),
501           RemoteFileName :: string(),
502           LocalFileName  :: string()) ->
503    'ok' | {'error', Reason :: term()}.
504
505recv(Pid, RemotFileName, LocalFileName) ->
506    case is_name_sane(RemotFileName) of
507        true ->
508            call(Pid, {recv, RemotFileName, LocalFileName}, atom);
509        _ ->
510            {error, efnamena}
511    end.
512
513
514%%--------------------------------------------------------------------------
515%% recv_bin(Pid, RemoteFile) -> {ok, Bin} | {error, epath} | {error, elogin}
516%%                           | {error, econn}
517%%        Pid = pid()
518%%        RemoteFile = string()
519%%      Bin = binary()
520%%
521%% Description:  Transfer file from remote server into binary.
522%%--------------------------------------------------------------------------
523
524-spec recv_bin(Pid        :: pid(),
525               RemoteFile :: string()) ->
526    {'ok', Bin :: binary()} |
527        {'error', Reason :: restriction_reason() | common_reason()}.
528
529recv_bin(Pid, RemoteFile) ->
530    case is_name_sane(RemoteFile) of
531        true ->
532            call(Pid, {recv_bin, RemoteFile}, bin);
533        _ ->
534            {error, efnamena}
535    end.
536
537
538%%--------------------------------------------------------------------------
539%% recv_chunk_start(Pid, RemoteFile) -> ok | {error, elogin} | {error, epath}
540%%                                 | {error, econn}
541%%        Pid = pid()
542%%        RemoteFile = string()
543%%
544%% Description:  Start receive of chunks of remote file.
545%%--------------------------------------------------------------------------
546
547-spec recv_chunk_start(Pid        :: pid(),
548                       RemoteFile :: string()) ->
549    'ok' | {'error', Reason :: restriction_reason() | common_reason()}.
550
551recv_chunk_start(Pid, RemoteFile) ->
552    case is_name_sane(RemoteFile) of
553        true ->
554            call(Pid, {recv_chunk_start, RemoteFile}, atom);
555        _ ->
556            {error, efnamena}
557    end.
558
559
560%%--------------------------------------------------------------------------
561%% recv_chunk(Pid, RemoteFile) ->  ok | {ok, Bin} | {error, Reason}
562%%        Pid = pid()
563%%        RemoteFile = string()
564%%
565%% Description:  Transfer file from remote server into binary in chunks
566%%--------------------------------------------------------------------------
567
568-spec recv_chunk(Pid :: pid()) ->
569    'ok' |
570        {'ok', Bin :: binary()} |
571        {'error', Reason :: restriction_reason() | common_reason()}.
572
573recv_chunk(Pid) ->
574    call(Pid, recv_chunk, atom).
575
576
577%%--------------------------------------------------------------------------
578%% send(Pid, LocalFileName [, RemotFileName]) -> ok | {error, epath}
579%%                                                  | {error, elogin}
580%%                                                  | {error, econn}
581%%        Pid = pid()
582%%        LocalFileName = RemotFileName = string()
583%%
584%% Description:  Transfer file to remote server.
585%%--------------------------------------------------------------------------
586
587-spec send(Pid :: pid(), LocalFileName :: string()) ->
588    'ok' |
589        {'error', Reason :: restriction_reason() |
590                            common_reason() |
591                            shortage_reason()}.
592
593send(Pid, LocalFileName) ->
594  send(Pid, LocalFileName, LocalFileName).
595
596-spec send(Pid            :: pid(),
597           LocalFileName  :: string(),
598           RemoteFileName :: string()) ->
599    'ok' |
600        {'error', Reason :: restriction_reason() |
601                            common_reason() |
602                            shortage_reason()}.
603
604send(Pid, LocalFileName, RemotFileName) ->
605    case is_name_sane(RemotFileName) of
606        true ->
607            call(Pid, {send, LocalFileName, RemotFileName}, atom);
608        _ ->
609            {error, efnamena}
610    end.
611
612
613%%--------------------------------------------------------------------------
614%% send_bin(Pid, Bin, RemoteFile) -> ok | {error, epath} | {error, elogin}
615%%                             | {error, enotbinary} | {error, econn}
616%%        Pid = pid()
617%%        Bin = binary()
618%%        RemoteFile = string()
619%%
620%% Description:  Transfer a binary to a remote file.
621%%--------------------------------------------------------------------------
622
623-spec send_bin(Pid :: pid(), Bin :: binary(), RemoteFile :: string()) ->
624    'ok' |
625        {'error', Reason :: restriction_reason() |
626                            common_reason() |
627                            shortage_reason()}.
628
629send_bin(Pid, Bin, RemoteFile) when is_binary(Bin) ->
630    case is_name_sane(RemoteFile) of
631        true ->
632            call(Pid, {send_bin, Bin, RemoteFile}, atom);
633        _ ->
634            {error, efnamena}
635    end;
636send_bin(_Pid, _Bin, _RemoteFile) ->
637  {error, enotbinary}.
638
639
640%%--------------------------------------------------------------------------
641%% send_chunk_start(Pid, RemoteFile) -> ok | {error, elogin} | {error, epath}
642%%                                 | {error, econn}
643%%        Pid = pid()
644%%        RemoteFile = string()
645%%
646%% Description:  Start transfer of chunks to remote file.
647%%--------------------------------------------------------------------------
648
649-spec send_chunk_start(Pid :: pid(), RemoteFile :: string()) ->
650    'ok' | {'error', Reason :: restriction_reason() | common_reason()}.
651
652send_chunk_start(Pid, RemoteFile) ->
653    case is_name_sane(RemoteFile) of
654        true ->
655            call(Pid, {send_chunk_start, RemoteFile}, atom);
656        _ ->
657            {error, efnamena}
658    end.
659
660
661%%--------------------------------------------------------------------------
662%% append_chunk_start(Pid, RemoteFile) -> ok | {error, elogin} |
663%%                                        {error, epath} | {error, econn}
664%%        Pid = pid()
665%%        RemoteFile = string()
666%%
667%% Description:  Start append chunks of data to remote file.
668%%--------------------------------------------------------------------------
669
670-spec append_chunk_start(Pid :: pid(), RemoteFile :: string()) ->
671    'ok' | {'error', Reason :: term()}.
672
673append_chunk_start(Pid, RemoteFile) ->
674    case is_name_sane(RemoteFile) of
675        true ->
676            call(Pid, {append_chunk_start, RemoteFile}, atom);
677        _ ->
678            {error, efnamena}
679    end.
680
681
682%%--------------------------------------------------------------------------
683%% send_chunk(Pid, Bin) -> ok | {error, elogin} | {error, enotbinary}
684%%                       | {error, echunk} | {error, econn}
685%%      Pid = pid()
686%%        Bin = binary().
687%%
688%% Purpose:  Send chunk to remote file.
689%%--------------------------------------------------------------------------
690
691-spec send_chunk(Pid :: pid(), Bin :: binary()) ->
692    'ok' |
693        {'error', Reason :: 'echunk' |
694                            restriction_reason() |
695                            common_reason()}.
696
697send_chunk(Pid, Bin) when is_binary(Bin) ->
698    call(Pid, {transfer_chunk, Bin}, atom);
699send_chunk(_Pid, _Bin) ->
700  {error, enotbinary}.
701
702
703%%--------------------------------------------------------------------------
704%% append_chunk(Pid, Bin) -> ok | {error, elogin} | {error, enotbinary}
705%%                             | {error, echunk} | {error, econn}
706%%        Pid = pid()
707%%        Bin = binary()
708%%
709%% Description:  Append chunk to remote file.
710%%--------------------------------------------------------------------------
711
712-spec append_chunk(Pid :: pid(), Bin :: binary()) ->
713    'ok' |
714        {'error', Reason :: 'echunk' |
715                            restriction_reason() |
716                            common_reason()}.
717
718append_chunk(Pid, Bin) when is_binary(Bin) ->
719    call(Pid, {transfer_chunk, Bin}, atom);
720append_chunk(_Pid, _Bin) ->
721  {error, enotbinary}.
722
723
724%%--------------------------------------------------------------------------
725%% send_chunk_end(Pid) -> ok | {error, elogin} | {error, echunk}
726%%                          | {error, econn}
727%%        Pid = pid()
728%%
729%% Description:  End sending of chunks to remote file.
730%%--------------------------------------------------------------------------
731
732-spec send_chunk_end(Pid :: pid()) ->
733    'ok' |
734        {'error', Reason :: restriction_reason() |
735                            common_reason() |
736                            shortage_reason()}.
737
738send_chunk_end(Pid) ->
739    call(Pid, chunk_end, atom).
740
741
742%%--------------------------------------------------------------------------
743%% append_chunk_end(Pid) ->  ok | {error, elogin} | {error, echunk}
744%%                             | {error, econn}
745%%        Pid = pid()
746%%
747%% Description:  End appending of chunks to remote file.
748%%--------------------------------------------------------------------------
749
750-spec append_chunk_end(Pid :: pid()) ->
751    'ok' |
752        {'error', Reason :: restriction_reason() |
753                            common_reason() |
754                            shortage_reason()}.
755
756append_chunk_end(Pid) ->
757    call(Pid, chunk_end, atom).
758
759
760%%--------------------------------------------------------------------------
761%% append(Pid, LocalFileName [, RemotFileName]) -> ok | {error, epath}
762%%                                                    | {error, elogin}
763%%                                                    | {error, econn}
764%%        Pid = pid()
765%%        LocalFileName = RemotFileName = string()
766%%
767%% Description:  Append the local file to the remote file
768%%--------------------------------------------------------------------------
769
770-spec append(Pid :: pid(), LocalFileName :: string()) ->
771    'ok' |
772        {'error', Reason :: 'epath'    |
773                            'elogin'   |
774                            'etnospc'  |
775                            'epnospc'  |
776                            'efnamena' | common_reason()}.
777
778append(Pid, LocalFileName) ->
779    append(Pid, LocalFileName, LocalFileName).
780
781-spec append(Pid            :: pid(),
782             LocalFileName  :: string(),
783             RemoteFileName :: string()) ->
784    'ok' | {'error', Reason :: term()}.
785
786append(Pid, LocalFileName, RemotFileName) ->
787    case is_name_sane(RemotFileName) of
788        true ->
789            call(Pid, {append, LocalFileName, RemotFileName}, atom);
790        _ ->
791            {error, efnamena}
792    end.
793
794
795%%--------------------------------------------------------------------------
796%% append_bin(Pid, Bin, RemoteFile) -> ok | {error, epath} | {error, elogin}
797%%                                  | {error, enotbinary} | {error, econn}
798%%        Pid = pid()
799%%        Bin = binary()
800%%        RemoteFile = string()
801%%
802%% Purpose:  Append a binary to a remote file.
803%%--------------------------------------------------------------------------
804
805-spec append_bin(Pid        :: pid(),
806                 Bin        :: binary(),
807                 RemoteFile :: string()) ->
808    'ok' |
809        {'error', Reason :: restriction_reason() |
810                            common_reason() |
811                            shortage_reason()}.
812
813append_bin(Pid, Bin, RemoteFile) when is_binary(Bin) ->
814    case is_name_sane(RemoteFile) of
815        true ->
816            call(Pid, {append_bin, Bin, RemoteFile}, atom);
817        _ ->
818            {error, efnamena}
819    end;
820append_bin(_Pid, _Bin, _RemoteFile) ->
821    {error, enotbinary}.
822
823
824%%--------------------------------------------------------------------------
825%% quote(Pid, Cmd) -> list()
826%%        Pid = pid()
827%%        Cmd = string()
828%%
829%% Description: Send arbitrary ftp command.
830%%--------------------------------------------------------------------------
831
832-spec quote(Pid :: pid(), Cmd :: string()) -> list().
833
834quote(Pid, Cmd) when is_list(Cmd) ->
835    call(Pid, {quote, Cmd}, atom).
836
837
838%%--------------------------------------------------------------------------
839%% close(Pid) -> ok
840%%        Pid = pid()
841%%
842%% Description:  End the ftp session.
843%%--------------------------------------------------------------------------
844
845-spec close(Pid :: pid()) -> 'ok'.
846
847close(Pid) ->
848    cast(Pid, close),
849    ok.
850
851
852%%--------------------------------------------------------------------------
853%% formaterror(Tag) -> string()
854%%        Tag = atom() | {error, atom()}
855%%
856%% Description:  Return diagnostics.
857%%--------------------------------------------------------------------------
858
859-spec formaterror(Tag :: term()) -> string().
860
861formaterror(Tag) ->
862  ftp_response:error_string(Tag).
863
864
865info(Pid) ->
866    call(Pid, info, list).
867
868
869%%--------------------------------------------------------------------------
870%% latest_ctrl_response(Pid) -> string()
871%%        Pid = pid()
872%%
873%% Description:  The latest received response from the server
874%%--------------------------------------------------------------------------
875
876-spec latest_ctrl_response(Pid :: pid()) -> string().
877
878latest_ctrl_response(Pid) ->
879    call(Pid, latest_ctrl_response, string).
880
881
882%%%========================================================================
883%%% gen_server callback functions
884%%%========================================================================
885
886%%-------------------------------------------------------------------------
887%% init(Args) -> {ok, State} | {ok, State, Timeout} | {stop, Reason}
888%% Description: Initiates the erlang process that manages a ftp connection.
889%%-------------------------------------------------------------------------
890init(Options) ->
891    process_flag(trap_exit, true),
892
893    %% Keep track of the client
894    {value, {client, Client}} = lists:keysearch(client, 1, Options),
895    erlang:monitor(process, Client),
896
897    %% Make sure inet is started
898    _ = inet_db:start(),
899
900    %% Where are we
901    {ok, Dir} = file:get_cwd(),
902
903    %% Maybe activate dbg
904    case key_search(debug, Options, disable) of
905        trace ->
906            dbg:tracer(),
907            dbg:p(all, [call]),
908            {ok, _} = dbg:tpl(ftp, [{'_', [], [{return_trace}]}]),
909            {ok, _} = dbg:tpl(ftp_response, [{'_', [], [{return_trace}]}]),
910            {ok, _} = dbg:tpl(ftp_progress, [{'_', [], [{return_trace}]}]),
911            ok;
912        debug ->
913            dbg:tracer(),
914            dbg:p(all, [call]),
915            {ok, _} = dbg:tp(ftp, [{'_', [], [{return_trace}]}]),
916            {ok, _} = dbg:tp(ftp_response, [{'_', [], [{return_trace}]}]),
917            {ok, _} = dbg:tp(ftp_progress, [{'_', [], [{return_trace}]}]),
918            ok;
919        _ ->
920            %% Keep silent
921            ok
922    end,
923
924    %% Verbose?
925    Verbose  = key_search(verbose, Options, false),
926
927    %% IpFamily?
928    IpFamily = key_search(ipfamily, Options, inet),
929
930    State    = #state{owner    = Client,
931                      verbose  = Verbose,
932                      ipfamily = IpFamily,
933                      ldir     = Dir},
934
935    %% Set process prio
936    Priority = key_search(priority, Options, low),
937    process_flag(priority, Priority),
938
939    %% And we are done
940    {ok, State}.
941
942
943%%--------------------------------------------------------------------------
944%% handle_call(Request, From, State) -> {reply, Reply, State} |
945%%                                      {reply, Reply, State, Timeout} |
946%%                                      {noreply, State}               |
947%%                                      {noreply, State, Timeout}      |
948%%                                      {stop, Reason, Reply, State}   |
949%% Description: Handle incoming requests.
950%%-------------------------------------------------------------------------
951
952%% Anyone can ask this question
953handle_call({_, info}, _, #state{verbose  = Verbose,
954                                 mode     = Mode,
955                                 timeout  = Timeout,
956                                 ipfamily = IpFamily,
957                                 csock    = Socket,
958                                 progress = Progress} = State) ->
959    {ok, {_, LocalPort}}  = sockname(Socket),
960    {ok, {Address, Port}} = peername(Socket),
961    Options = [{verbose,    Verbose},
962               {ipfamily,   IpFamily},
963               {mode,       Mode},
964               {peer,       Address},
965               {peer_port,  Port},
966               {local_port, LocalPort},
967               {timeout,    Timeout},
968               {progress,   Progress}],
969    {reply, {ok, Options}, State};
970
971handle_call({_,latest_ctrl_response}, _, #state{latest_ctrl_response=Resp} = State) ->
972    {reply, {ok,Resp}, State};
973
974%% But everything else must come from the owner
975handle_call({Pid, _}, _, #state{owner = Owner} = State) when Owner =/= Pid ->
976    {reply, {error, not_connection_owner}, State};
977
978handle_call({_, {open, ip_comm, Options}}, From, State) ->
979    {ok, Opts} = open_options(Options),
980
981    case key_search(host, Opts, undefined) of
982        undefined ->
983            {stop, normal, {error, ehost}, State};
984        Host ->
985            TLSSecMethod = key_search(tls_sec_method, Opts, undefined),
986            TLSOpts  = key_search(tls,      Opts, undefined),
987            TLSReuse = key_search(tls_ctrl_session_reuse, Opts, false),
988            Mode     = key_search(mode,     Opts, ?DEFAULT_MODE),
989            Port0    = key_search(port,     Opts, 0),
990            Port     = if Port0 == 0, TLSSecMethod == ftps -> ?FTPS_PORT; Port0 == 0 -> ?FTP_PORT; true -> Port0 end,
991            Timeout  = key_search(timeout,  Opts, ?CONNECTION_TIMEOUT),
992            DTimeout = key_search(dtimeout, Opts, ?DATA_ACCEPT_TIMEOUT),
993            Progress = key_search(progress, Opts, ignore),
994            IpFamily = key_search(ipfamily, Opts, inet),
995            FtpExt   = key_search(ftp_extension, Opts, ?FTP_EXT_DEFAULT),
996
997            {ok, {CtrlOpts, DataPassOpts, DataActOpts}} = socket_options(Options),
998
999            State2 = State#state{client   = From,
1000                                 mode     = Mode,
1001                                 progress = progress(Progress),
1002                                 ipfamily = IpFamily,
1003                                 sockopts_ctrl = CtrlOpts,
1004                                 sockopts_data_passive =  DataPassOpts,
1005                                 sockopts_data_active = DataActOpts,
1006                                 timeout = Timeout,
1007                                 dtimeout = DTimeout,
1008                                 ftp_extension = FtpExt},
1009
1010            case setup_ctrl_connection(Host, Port, Timeout, State2) of
1011                {ok, State3, WaitTimeout} when is_list(TLSOpts), TLSSecMethod == ftps ->
1012                    handle_ctrl_result({tls_upgrade, TLSSecMethod},
1013                                       State3#state{tls_options = TLSOpts,
1014						    tls_ctrl_session_reuse = TLSReuse,
1015						    timeout = WaitTimeout });
1016                {ok, State3, WaitTimeout} when is_list(TLSOpts) ->
1017                    {noreply, State3#state{tls_options = TLSOpts, tls_ctrl_session_reuse = TLSReuse }, WaitTimeout};
1018                {ok, State3, WaitTimeout} ->
1019                    {noreply, State3, WaitTimeout};
1020                {error, _Reason} ->
1021                    gen_server:reply(From, {error, ehost}),
1022                    {stop, normal, State2#state{client = undefined}}
1023            end
1024    end;
1025
1026handle_call({_, {user, User, Password}}, From,
1027            #state{csock = CSock} = State) when (CSock =/= undefined) ->
1028    handle_user(User, Password, "", State#state{client = From});
1029
1030handle_call({_, {user, User, Password, Acc}}, From,
1031            #state{csock = CSock} = State) when (CSock =/= undefined) ->
1032    handle_user(User, Password, Acc, State#state{client = From});
1033
1034handle_call({_, {account, Acc}}, From, State)->
1035    handle_user_account(Acc, State#state{client = From});
1036
1037handle_call({_, pwd}, From, #state{chunk = false} = State0) ->
1038    _ = send_ctrl_message(State0, mk_cmd("PWD", [])),
1039    State = activate_ctrl_connection(State0),
1040    {noreply, State#state{client = From, caller = pwd}};
1041
1042handle_call({_, lpwd}, From, #state{ldir = LDir} = State) ->
1043    {reply, {ok, LDir}, State#state{client = From}};
1044
1045handle_call({_, {cd, Dir}}, From, #state{chunk = false} = State0) ->
1046    _ = send_ctrl_message(State0, mk_cmd("CWD ~s", [Dir])),
1047    State = activate_ctrl_connection(State0),
1048    {noreply, State#state{client = From, caller = cd}};
1049
1050handle_call({_,{lcd, Dir}}, _From, #state{ldir = LDir0} = State) ->
1051    LDir = filename:absname(Dir, LDir0),
1052    case file:read_file_info(LDir) of %% FIX better check that LDir is a dir.
1053        {ok, _ } ->
1054            {reply, ok, State#state{ldir = LDir}};
1055        _  ->
1056            {reply, {error, epath}, State}
1057    end;
1058
1059handle_call({_, {dir, Len, Dir}}, {_Pid, _} = From,
1060            #state{chunk = false} = State) ->
1061    setup_data_connection(State#state{caller = {dir, Dir, Len},
1062                                      client = From});
1063handle_call({_, {rename, CurrFile, NewFile}}, From,
1064            #state{chunk = false} = State0) ->
1065    _ = send_ctrl_message(State0, mk_cmd("RNFR ~s", [CurrFile])),
1066    State = activate_ctrl_connection(State0),
1067    {noreply, State#state{caller = {rename, NewFile}, client = From}};
1068
1069handle_call({_, {delete, File}}, {_Pid, _} = From,
1070            #state{chunk = false} = State0) ->
1071    _ = send_ctrl_message(State0, mk_cmd("DELE ~s", [File])),
1072    State = activate_ctrl_connection(State0),
1073    {noreply, State#state{client = From}};
1074
1075handle_call({_, {mkdir, Dir}}, From, #state{chunk = false} = State0) ->
1076    _ = send_ctrl_message(State0, mk_cmd("MKD ~s", [Dir])),
1077    State = activate_ctrl_connection(State0),
1078    {noreply, State#state{client = From}};
1079
1080handle_call({_,{rmdir, Dir}}, From, #state{chunk = false} = State0) ->
1081    _ = send_ctrl_message(State0, mk_cmd("RMD ~s", [Dir])),
1082    State = activate_ctrl_connection(State0),
1083    {noreply, State#state{client = From}};
1084
1085handle_call({_,{type, Type}}, From, #state{chunk = false} = State0) ->
1086    case Type of
1087        ascii ->
1088            _ = send_ctrl_message(State0, mk_cmd("TYPE A", [])),
1089            State = activate_ctrl_connection(State0),
1090            {noreply, State#state{caller = type, type = ascii,
1091                                  client = From}};
1092        binary ->
1093            _ = send_ctrl_message(State0, mk_cmd("TYPE I", [])),
1094            State = activate_ctrl_connection(State0),
1095            {noreply, State#state{caller = type, type = binary,
1096                                  client = From}};
1097        _ ->
1098            {reply, {error, etype}, State0}
1099    end;
1100handle_call({_,{recv, RemoteFile, LocalFile}}, From,
1101            #state{chunk = false, ldir = LocalDir} = State) ->
1102    progress_report({remote_file, RemoteFile}, State),
1103    NewLocalFile = filename:absname(LocalFile, LocalDir),
1104
1105    case file_open(NewLocalFile, write) of
1106        {ok, Fd} ->
1107            setup_data_connection(State#state{client = From,
1108                                              caller =
1109                                              {recv_file,
1110                                               RemoteFile, Fd}});
1111        {error, _What} ->
1112            {reply, {error, epath}, State}
1113    end;
1114handle_call({_, {recv_bin, RemoteFile}}, From, #state{chunk = false} =
1115            State) ->
1116    setup_data_connection(State#state{caller = {recv_bin, RemoteFile},
1117                                      client = From});
1118handle_call({_,{recv_chunk_start, RemoteFile}}, From, #state{chunk = false}
1119            = State) ->
1120    setup_data_connection(State#state{caller = {start_chunk_transfer,
1121                                                "RETR", RemoteFile},
1122                                      client = From});
1123
1124handle_call({_, recv_chunk}, _, #state{chunk = false} = State) ->
1125    {reply, {error, "ftp:recv_chunk_start/2 not called"}, State};
1126handle_call({_, recv_chunk}, _From, #state{chunk = true,
1127                                           data = Bin,
1128                                           caller = #recv_chunk_closing{dconn_closed       = true,
1129                                                                        pos_compl_received = true,
1130                                                                        client_called_us = true
1131                                                                       }
1132                                          } = State0) ->
1133    case Bin of
1134        <<>> ->
1135            {reply, ok, State0#state{caller = undefined,
1136                                     chunk = false,
1137                                     client = undefined}};
1138        Data ->
1139            {reply, Data, State0#state{caller = undefined,
1140                                       chunk = false,
1141                                       client = undefined}}
1142    end;
1143handle_call({_, recv_chunk}, _From, #state{chunk = true,
1144                                           caller = #recv_chunk_closing{dconn_closed       = true,
1145                                                                        pos_compl_received = true
1146                                                                       }
1147                                          } = State0) ->
1148    %% The ftp:recv_chunk call was the last event we waited for, finnish and clean up
1149    ?DBG("Data connection closed recv_chunk_closing ftp:recv_chunk, last event",[]),
1150    State = activate_ctrl_connection(State0),
1151    {reply, ok, State#state{caller = undefined,
1152                             chunk = false,
1153                             client = undefined}};
1154handle_call({_, recv_chunk}, From, #state{chunk = true,
1155                                          caller = #recv_chunk_closing{pos_compl_received = true
1156                                                                      } = R
1157                                         } = State0) ->
1158    State = activate_data_connection(State0),
1159    {noreply, State#state{client = From, caller = R#recv_chunk_closing{client_called_us=true}}};
1160
1161handle_call({_, recv_chunk}, From, #state{chunk = true,
1162                                          caller = #recv_chunk_closing{} = R
1163                                         } = State) ->
1164    %% Waiting for more, don't care what
1165    ?DBG("recv_chunk_closing ftp:recv_chunk, get more",[]),
1166    {noreply, State#state{client = From, caller = R#recv_chunk_closing{client_called_us=true}}};
1167
1168handle_call({_, recv_chunk}, From, #state{chunk = true} = State0) ->
1169    State = activate_data_connection(State0),
1170    {noreply, State#state{client = From, caller = recv_chunk}};
1171
1172handle_call({_, {send, LocalFile, RemoteFile}}, From,
1173            #state{chunk = false, ldir = LocalDir} = State) ->
1174    progress_report({local_file, filename:absname(LocalFile, LocalDir)},
1175                    State),
1176    setup_data_connection(State#state{caller = {transfer_file,
1177                                                   {"STOR",
1178                                                    LocalFile, RemoteFile}},
1179                                         client = From});
1180handle_call({_, {append, LocalFile, RemoteFile}}, From,
1181            #state{chunk = false} = State) ->
1182    setup_data_connection(State#state{caller = {transfer_file,
1183                                                {"APPE",
1184                                                 LocalFile, RemoteFile}},
1185                                      client = From});
1186handle_call({_, {send_bin, Bin, RemoteFile}}, From,
1187            #state{chunk = false} = State) ->
1188    setup_data_connection(State#state{caller = {transfer_data,
1189                                               {"STOR", Bin, RemoteFile}},
1190                                      client = From});
1191handle_call({_,{append_bin, Bin, RemoteFile}}, From,
1192            #state{chunk = false} = State) ->
1193    setup_data_connection(State#state{caller = {transfer_data,
1194                                                {"APPE", Bin, RemoteFile}},
1195                                      client = From});
1196handle_call({_, {send_chunk_start, RemoteFile}}, From, #state{chunk = false}
1197            = State) ->
1198    setup_data_connection(State#state{caller = {start_chunk_transfer,
1199                                                "STOR", RemoteFile},
1200                                      client = From});
1201handle_call({_, {append_chunk_start, RemoteFile}}, From, #state{chunk = false}
1202            = State) ->
1203    setup_data_connection(State#state{caller = {start_chunk_transfer,
1204                                                "APPE", RemoteFile},
1205                                      client = From});
1206handle_call({_, {transfer_chunk, Bin}}, _, #state{chunk = true} = State) ->
1207    send_data_message(State, Bin),
1208    {reply, ok, State};
1209
1210handle_call({_, {transfer_chunk, _}}, _, #state{chunk = false} = State) ->
1211    {reply, {error, echunk}, State};
1212
1213handle_call({_, chunk_end}, From, #state{chunk = true} = State0) ->
1214    close_data_connection(State0),
1215    State = activate_ctrl_connection(State0),
1216    {noreply, State#state{client = From, dsock = undefined,
1217                          caller = end_chunk_transfer, chunk = false}};
1218
1219handle_call({_, chunk_end}, _, #state{chunk = false} = State) ->
1220    {reply, {error, echunk}, State};
1221
1222handle_call({_, {quote, Cmd}}, From, #state{chunk = false} = State0) ->
1223    _ = send_ctrl_message(State0, mk_cmd(Cmd, [])),
1224    State = activate_ctrl_connection(State0),
1225    {noreply, State#state{client = From, caller = quote}};
1226
1227handle_call({_, _Req}, _From, #state{csock = CSock} = State)
1228  when (CSock =:= undefined) ->
1229    {reply, {error, not_connected}, State};
1230
1231handle_call(_, _, #state{chunk = true} = State) ->
1232    {reply, {error, echunk}, State};
1233
1234%% Catch all -  This can only happen if the application programmer writes
1235%% really bad code that violates the API.
1236handle_call(Request, _Timeout, State) ->
1237    {stop, {'API_violation_connection_closed', Request},
1238     {error, {connection_terminated, 'API_violation'}}, State}.
1239
1240%%--------------------------------------------------------------------------
1241%% handle_cast(Request, State) -> {noreply, State} |
1242%%                                {noreply, State, Timeout} |
1243%%                                {stop, Reason, State}
1244%% Description: Handles cast messages.
1245%%-------------------------------------------------------------------------
1246handle_cast({Pid, close}, #state{owner = Pid} = State) ->
1247    _ = send_ctrl_message(State, mk_cmd("QUIT", [])),
1248    close_ctrl_connection(State),
1249    close_data_connection(State),
1250    {stop, normal, State#state{csock = undefined, dsock = undefined}};
1251
1252handle_cast({Pid, close}, State) ->
1253    Report = io_lib:format("A none owner process ~p tried to close an "
1254                             "ftp connection: ~n", [Pid]),
1255    error_logger:info_report(Report),
1256    {noreply, State};
1257
1258%% Catch all -  This can oly happen if the application programmer writes
1259%% really bad code that violates the API.
1260handle_cast(Msg, State) ->
1261  {stop, {'API_violation_connection_closed', Msg}, State}.
1262
1263%%--------------------------------------------------------------------------
1264%% handle_info(Msg, State) -> {noreply, State} | {noreply, State, Timeout} |
1265%%                              {stop, Reason, State}
1266%% Description: Handles tcp messages from the ftp-server.
1267%% Note: The order of the function clauses is significant.
1268%%--------------------------------------------------------------------------
1269
1270handle_info(timeout, #state{caller = open} = State) ->
1271    {stop, timeout, State};
1272
1273handle_info(timeout, State) ->
1274    {noreply, State};
1275
1276%%% Data socket messages %%%
1277handle_info({Trpt, Socket, Data},
1278            #state{dsock = {Trpt,Socket},
1279                   caller = {recv_file, Fd}} = State0) when Trpt==tcp;Trpt==ssl ->
1280    ?DBG('L~p --data ~p ----> ~s~p~n',[?LINE,Socket,Data,State0]),
1281    ok = file_write(binary_to_list(Data), Fd),
1282    progress_report({binary, Data}, State0),
1283    State = activate_data_connection(State0),
1284    {noreply, State};
1285
1286handle_info({Trpt, Socket, Data}, #state{dsock = {Trpt,Socket}, client = From,
1287                                        caller = recv_chunk}
1288            = State) when Trpt==tcp;Trpt==ssl ->
1289    ?DBG('L~p --data ~p ----> ~s~p~n',[?LINE,Socket,Data,State]),
1290    gen_server:reply(From, {ok, Data}),
1291    {noreply, State#state{client = undefined, caller = undefined, data = <<>>}};
1292
1293handle_info({Trpt, Socket, Data}, #state{dsock = {Trpt,Socket}} = State0) when Trpt==tcp;Trpt==ssl ->
1294    ?DBG('L~p --data ~p ----> ~s~p~n',[?LINE,Socket,Data,State0]),
1295    State = activate_data_connection(State0),
1296    {noreply, State#state{data = <<(State#state.data)/binary,
1297                                  Data/binary>>}};
1298
1299handle_info({Cls, Socket}, #state{dsock = {Trpt,Socket},
1300                                  caller = {recv_file, Fd}} = State0)
1301  when {Cls,Trpt}=={tcp_closed,tcp} ; {Cls,Trpt}=={ssl_closed,ssl} ->
1302    file_close(Fd),
1303    progress_report({transfer_size, 0}, State0),
1304    State = activate_ctrl_connection(State0),
1305    ?DBG("Data channel close",[]),
1306    {noreply, State#state{dsock = undefined, data = <<>>}};
1307
1308handle_info({Cls, Socket}, #state{dsock = {Trpt,Socket},
1309                                  client = Client,
1310                                  caller = recv_chunk} = State0)
1311  when {Cls,Trpt}=={tcp_closed,tcp} ; {Cls,Trpt}=={ssl_closed,ssl} ->
1312    ?DBG("Data channel close recv_chunk",[]),
1313    State = activate_ctrl_connection(State0),
1314    {noreply, State#state{dsock = undefined,
1315                          caller = #recv_chunk_closing{dconn_closed     =  true,
1316                                                       client_called_us =  Client =/= undefined}
1317                         }};
1318handle_info({Cls, Socket}, #state{dsock = {Trpt,Socket},
1319                                  caller = #recv_chunk_closing{client_called_us = true,
1320                                                               pos_compl_received = true} = R} = State)
1321  when {Cls,Trpt}=={tcp_closed,tcp} ; {Cls,Trpt}=={ssl_closed,ssl} ->
1322    %% Maybe handle unprocessed chunk message before acking final chunk
1323    self() ! {Cls, Socket},
1324    {noreply, State#state{caller = R#recv_chunk_closing{dconn_closed = true}}};
1325
1326handle_info({Cls, Socket}, #state{dsock = {Trpt,Socket}, caller = recv_bin,
1327                                         data = Data} = State0)
1328  when {Cls,Trpt}=={tcp_closed,tcp} ; {Cls,Trpt}=={ssl_closed,ssl} ->
1329    ?DBG("Data channel close",[]),
1330    State = activate_ctrl_connection(State0),
1331    {noreply, State#state{dsock = undefined, data = <<>>,
1332                          caller = {recv_bin, Data}}};
1333
1334handle_info({Cls, Socket}, #state{dsock = {Trpt,Socket}, data = Data,
1335                                  caller = {handle_dir_result, Dir}}
1336            = State0) when {Cls,Trpt}=={tcp_closed,tcp} ; {Cls,Trpt}=={ssl_closed,ssl} ->
1337    ?DBG("Data channel close",[]),
1338    State = activate_ctrl_connection(State0),
1339    {noreply, State#state{dsock = undefined,
1340                          caller = {handle_dir_result, Dir, Data},
1341%                          data = <<?CR,?LF>>}};
1342                          data = <<>>}};
1343
1344handle_info({Err, Socket, Reason}, #state{dsock = {Trpt,Socket},
1345                                          client = From} = State)
1346  when {Err,Trpt}=={tcp_error,tcp} ; {Err,Trpt}=={ssl_error,ssl} ->
1347    gen_server:reply(From, {error, Reason}),
1348    close_data_connection(State),
1349    {noreply, State#state{dsock = undefined, client = undefined,
1350                          data = <<>>, caller = undefined, chunk = false}};
1351
1352%%% Ctrl socket messages %%%
1353handle_info({Transport, Socket, Data}, #state{csock = {Transport, Socket},
1354                                              verbose = Verbose,
1355                                              caller = Caller,
1356                                              client = From,
1357                                              ctrl_data = {BinCtrlData, AccLines,
1358                                                           LineStatus}}
1359            = State0) ->
1360    ?DBG('--ctrl ~p ----> ~s~p~n',[Socket,<<BinCtrlData/binary, Data/binary>>,State0]),
1361    case ftp_response:parse_lines(<<BinCtrlData/binary, Data/binary>>,
1362                                  AccLines, LineStatus) of
1363        {ok, Lines, NextMsgData} ->
1364            verbose(Lines, Verbose, 'receive'),
1365            CtrlResult = ftp_response:interpret(Lines),
1366            case Caller of
1367                quote ->
1368                    gen_server:reply(From, string:tokens(Lines, [?CR, ?LF])),
1369                    {noreply, State0#state{client = undefined,
1370                                           caller = undefined,
1371                                           latest_ctrl_response = Lines,
1372                                           ctrl_data = {NextMsgData, [],
1373                                                        start}}};
1374                _ ->
1375                    ?DBG('   ...handle_ctrl_result(~p,...) ctrl_data=~p~n',[CtrlResult,{NextMsgData, [], start}]),
1376                    handle_ctrl_result(CtrlResult,
1377                                       State0#state{latest_ctrl_response = Lines,
1378                                                    ctrl_data =
1379                                                        {NextMsgData, [], start}})
1380            end;
1381        {continue, CtrlData} when CtrlData =/= State0#state.ctrl_data ->
1382            ?DBG('   ...Continue... ctrl_data=~p~n',[CtrlData]),
1383            State1 = State0#state{ctrl_data = CtrlData},
1384            State = activate_ctrl_connection(State1),
1385            {noreply, State};
1386        {continue, _CtrlData} ->
1387            ?DBG('   ...Continue... ctrl_data=~p~n',[_CtrlData]),
1388            {noreply, State0}
1389    end;
1390
1391%% If the server closes the control channel it is
1392%% the expected behavior that connection process terminates.
1393handle_info({Cls, Socket}, #state{csock = {Trpt, Socket}})
1394  when {Cls,Trpt}=={tcp_closed,tcp} ; {Cls,Trpt}=={ssl_closed,ssl} ->
1395    exit(normal); %% User will get error message from terminate/2
1396
1397handle_info({Err, Socket, Reason}, _) when Err==tcp_error ; Err==ssl_error ->
1398    Report =
1399        io_lib:format("~p on socket: ~p  for reason: ~p~n",
1400                      [Err, Socket, Reason]),
1401    error_logger:error_report(Report),
1402    %% If tcp does not work the only option is to terminate,
1403    %% this is the expected behavior under these circumstances.
1404    exit(normal); %% User will get error message from terminate/2
1405
1406%% Monitor messages - if the process owning the ftp connection goes
1407%% down there is no point in continuing.
1408handle_info({'DOWN', _Ref, _Type, _Process, normal}, State) ->
1409    {stop, normal, State#state{client = undefined}};
1410
1411handle_info({'DOWN', _Ref, _Type, _Process, shutdown}, State) ->
1412    {stop, normal, State#state{client = undefined}};
1413
1414handle_info({'DOWN', _Ref, _Type, _Process, timeout}, State) ->
1415    {stop, normal, State#state{client = undefined}};
1416
1417handle_info({'DOWN', _Ref, _Type, Process, Reason}, State) ->
1418    {stop, {stopped, {'EXIT', Process, Reason}},
1419     State#state{client = undefined}};
1420
1421handle_info({'EXIT', Pid, Reason}, #state{progress = Pid} = State) ->
1422    Report = io_lib:format("Progress reporting stopped for reason ~p~n",
1423                           [Reason]),
1424    error_logger:info_report(Report),
1425    {noreply, State#state{progress = ignore}};
1426
1427%% Catch all - throws away unknown messages (This could happen by "accident"
1428%% so we do not want to crash, but we make a log entry as it is an
1429%% unwanted behaviour.)
1430handle_info(Info, State) ->
1431    Report = io_lib:format("ftp : ~p : Unexpected message: ~p~nState: ~p~n",
1432                           [self(), Info, State]),
1433    error_logger:info_report(Report),
1434    {noreply, State}.
1435
1436%%--------------------------------------------------------------------------
1437%% terminate/2 and code_change/3
1438%%--------------------------------------------------------------------------
1439terminate(normal, State) ->
1440    %% If terminate reason =/= normal the progress reporting process will
1441    %% be killed by the exit signal.
1442    progress_report(stop, State),
1443    do_terminate({error, econn}, State);
1444terminate(Reason, State) ->
1445    Report = io_lib:format("Ftp connection closed due to: ~p~n", [Reason]),
1446    error_logger:error_report(Report),
1447    do_terminate({error, eclosed}, State).
1448
1449do_terminate(ErrorMsg, State) ->
1450    close_data_connection(State),
1451    close_ctrl_connection(State),
1452    case State#state.client of
1453        undefined ->
1454            ok;
1455        From ->
1456            gen_server:reply(From, ErrorMsg)
1457    end,
1458    ok.
1459
1460code_change(_Vsn, State1, upgrade_from_pre_5_12) ->
1461    {state, CSock, DSock, Verbose, LDir, Type, Chunk, Mode, Timeout,
1462     Data, CtrlData, Owner, Client, Caller, IPv6Disable, Progress} = State1,
1463    IpFamily =
1464        if
1465            (IPv6Disable =:= true) ->
1466                inet;
1467            true ->
1468                inet6fb4
1469        end,
1470    State2 = #state{csock     = CSock,
1471                    dsock     = DSock,
1472                    verbose   = Verbose,
1473                    ldir      = LDir,
1474                    type      = Type,
1475                    chunk     = Chunk,
1476                    mode      = Mode,
1477                    timeout   = Timeout,
1478                    data      = Data,
1479                    ctrl_data = CtrlData,
1480                    owner     = Owner,
1481                    client    = Client,
1482                    caller    = Caller,
1483                    ipfamily  = IpFamily,
1484                    progress  = Progress},
1485    {ok, State2};
1486
1487code_change(_Vsn, State1, downgrade_to_pre_5_12) ->
1488    #state{csock     = CSock,
1489           dsock     = DSock,
1490           verbose   = Verbose,
1491           ldir      = LDir,
1492           type      = Type,
1493           chunk     = Chunk,
1494           mode      = Mode,
1495           timeout   = Timeout,
1496           data      = Data,
1497           ctrl_data = CtrlData,
1498           owner     = Owner,
1499           client    = Client,
1500           caller    = Caller,
1501           ipfamily  = IpFamily,
1502           progress  = Progress} = State1,
1503    IPv6Disable =
1504        if
1505            (IpFamily =:= inet) ->
1506                true;
1507            true ->
1508                false
1509        end,
1510    State2 =
1511        {state, CSock, DSock, Verbose, LDir, Type, Chunk, Mode, Timeout,
1512         Data, CtrlData, Owner, Client, Caller, IPv6Disable, Progress},
1513    {ok, State2};
1514
1515code_change(_Vsn, State, _Extra) ->
1516    {ok, State}.
1517
1518
1519%%%=========================================================================
1520%% Start/stop
1521%%%=========================================================================
1522%%--------------------------------------------------------------------------
1523%% start_link([Opts, GenServerOptions]) -> {ok, Pid} | {error, Reason}
1524%%
1525%% Description: Callback function for the ftp supervisor. It is called
1526%%            : when open or legacy is called.
1527%%--------------------------------------------------------------------------
1528start_link([Opts, GenServerOptions]) ->
1529    start_link(Opts, GenServerOptions).
1530
1531start_link(Opts, GenServerOptions) ->
1532    case lists:keysearch(client, 1, Opts) of
1533        {value, _} ->
1534            %% Via the supervisor
1535            gen_server:start_link(?MODULE, Opts, GenServerOptions);
1536        false ->
1537            Opts2 = [{client, self()} | Opts],
1538            gen_server:start_link(?MODULE, Opts2, GenServerOptions)
1539    end.
1540
1541
1542%%% Stop functionality is handled by close/1
1543
1544%%%========================================================================
1545%%% Internal functions
1546%%%========================================================================
1547
1548%%--------------------------------------------------------------------------
1549%%% Help functions to handle_call and/or handle_ctrl_result
1550%%--------------------------------------------------------------------------
1551%% User handling
1552handle_user(User, Password, Acc, State0) ->
1553    _ = send_ctrl_message(State0, mk_cmd("USER ~s", [User])),
1554    State = activate_ctrl_connection(State0),
1555    {noreply, State#state{caller = {handle_user, Password, Acc}}}.
1556
1557handle_user_passwd(Password, Acc, State0) ->
1558    _ = send_ctrl_message(State0, mk_cmd("PASS ~s", [Password])),
1559    State = activate_ctrl_connection(State0),
1560    {noreply, State#state{caller = {handle_user_passwd, Acc}}}.
1561
1562handle_user_account(Acc, State0) ->
1563    _ = send_ctrl_message(State0, mk_cmd("ACCT ~s", [Acc])),
1564    State = activate_ctrl_connection(State0),
1565    {noreply, State#state{caller = handle_user_account}}.
1566
1567
1568%%--------------------------------------------------------------------------
1569%% handle_ctrl_result
1570%%--------------------------------------------------------------------------
1571handle_ctrl_result({pos_compl, _}, #state{csock = {tcp, _Socket},
1572                                          tls_options = TLSOptions,
1573                                          timeout = Timeout,
1574                                          caller = open}
1575                   = State0) when is_list(TLSOptions) ->
1576    _ = send_ctrl_message(State0, mk_cmd("AUTH TLS", [])),
1577    State = activate_ctrl_connection(State0),
1578    {noreply, State, Timeout};
1579
1580handle_ctrl_result({tls_upgrade, S}, #state{csock = {tcp, Socket},
1581                                            tls_options = TLSOptions,
1582                                            timeout = Timeout,
1583                                            caller = open, client = From}
1584                   = State0) when is_list(TLSOptions) ->
1585    ?DBG('<--ctrl ssl:connect(~p, ~p)~n~p~n',[Socket,TLSOptions,State0]),
1586    catch ssl:start(),
1587    case ssl:connect(Socket, TLSOptions, Timeout) of
1588        {ok, TLSSocket} when S == ftps ->
1589            State1 = State0#state{csock = {ssl,TLSSocket}},
1590            State = activate_ctrl_connection(State1),
1591            {noreply, State#state{tls_upgrading_data_connection = pending}, Timeout};
1592        {ok, TLSSocket} ->
1593            State1 = State0#state{csock = {ssl,TLSSocket}},
1594            handle_ctrl_result({pos_compl, S}, State1#state{tls_upgrading_data_connection = pending});
1595        {error, _} = Error ->
1596            gen_server:reply(From, Error),
1597            {stop, normal, State0#state{client = undefined,
1598                                        caller = undefined,
1599                                        tls_upgrading_data_connection = false}}
1600    end;
1601
1602handle_ctrl_result({pos_compl, _}, #state{tls_upgrading_data_connection = pending} = State0) ->
1603    _ = send_ctrl_message(State0, mk_cmd("PBSZ 0", [])),
1604    State = activate_ctrl_connection(State0),
1605    {noreply, State#state{tls_upgrading_data_connection = {true, pbsz}}};
1606
1607handle_ctrl_result({pos_compl, _}, #state{tls_upgrading_data_connection = {true, pbsz}} = State0) ->
1608    _ = send_ctrl_message(State0, mk_cmd("PROT P", [])),
1609    State = activate_ctrl_connection(State0),
1610    {noreply, State#state{tls_upgrading_data_connection = {true, prot}}};
1611
1612handle_ctrl_result({pos_compl, _}, #state{tls_upgrading_data_connection = {true, prot},
1613                                          client = From} = State) ->
1614    gen_server:reply(From, {ok, self()}),
1615    {noreply, State#state{client = undefined,
1616                          caller = undefined,
1617                          tls_upgrading_data_connection = false}};
1618
1619handle_ctrl_result({pos_compl, _}, #state{caller = open, client = From}
1620                   = State) ->
1621    gen_server:reply(From, {ok, self()}),
1622    {noreply, State#state{client = undefined,
1623                          caller = undefined }};
1624handle_ctrl_result({_, Lines}, #state{caller = open} = State) ->
1625    ctrl_result_response(econn, State, {error, Lines});
1626
1627%%--------------------------------------------------------------------------
1628%% Data connection setup active mode
1629handle_ctrl_result({pos_compl, _Lines},
1630                   #state{mode   = active,
1631                          caller = {setup_data_connection,
1632                                    {LSock, Caller}}} = State) ->
1633    handle_caller(State#state{caller = Caller, dsock = {lsock, LSock}});
1634
1635handle_ctrl_result({Status, _Lines},
1636                   #state{mode   = active,
1637                          caller = {setup_data_connection, {LSock, _}}}
1638                   = State) ->
1639    close_connection({tcp,LSock}),
1640    ctrl_result_response(Status, State, {error, Status});
1641
1642%% Data connection setup passive mode
1643handle_ctrl_result({pos_compl, Lines},
1644                   #state{mode     = passive,
1645                          ipfamily = inet6,
1646                          client   = From,
1647                          caller   = {setup_data_connection, Caller},
1648                          csock    = CSock,
1649                          sockopts_data_passive = SockOpts,
1650                          timeout  = Timeout}
1651                   = State) ->
1652    [_, PortStr | _] =  lists:reverse(string:tokens(Lines, "|")),
1653    {ok, {IP, _}} = peername(CSock),
1654    case connect(IP, list_to_integer(PortStr), SockOpts, Timeout, State) of
1655        {ok, _, Socket} ->
1656            handle_caller(State#state{caller = Caller, dsock = {tcp, Socket}});
1657        {error, _Reason} = Error ->
1658            gen_server:reply(From, Error),
1659            {noreply, State#state{client = undefined, caller = undefined}}
1660    end;
1661
1662handle_ctrl_result({pos_compl, Lines},
1663                   #state{mode     = passive,
1664                          ipfamily = inet,
1665                          client   = From,
1666                          caller   = {setup_data_connection, Caller},
1667                          timeout  = Timeout,
1668                          sockopts_data_passive = SockOpts,
1669                          ftp_extension = false} = State) ->
1670
1671    {_, [?LEFT_PAREN | Rest]} =
1672        lists:splitwith(fun(?LEFT_PAREN) -> false; (_) -> true end, Lines),
1673    {NewPortAddr, _} =
1674        lists:splitwith(fun(?RIGHT_PAREN) -> false; (_) -> true end, Rest),
1675    [A1, A2, A3, A4, P1, P2] =
1676        lists:map(fun(X) -> list_to_integer(X) end,
1677                  string:tokens(NewPortAddr, [$,])),
1678    IP   = {A1, A2, A3, A4},
1679    Port = (P1 * 256) + P2,
1680
1681    ?DBG('<--data tcp connect to ~p:~p, Caller=~p~n',[IP,Port,Caller]),
1682    case connect(IP, Port, SockOpts, Timeout, State) of
1683        {ok, _, Socket}  ->
1684            handle_caller(State#state{caller = Caller, dsock = {tcp,Socket}});
1685        {error, _Reason} = Error ->
1686            gen_server:reply(From, Error),
1687            {noreply,State#state{client = undefined, caller = undefined}}
1688    end;
1689
1690handle_ctrl_result({pos_compl, Lines},
1691                   #state{mode     = passive,
1692                          ipfamily = inet,
1693                          client   = From,
1694                          caller   = {setup_data_connection, Caller},
1695                          csock    = CSock,
1696                          timeout  = Timeout,
1697                          sockopts_data_passive = SockOpts,
1698                          ftp_extension = true} = State) ->
1699
1700    [_, PortStr | _] =  lists:reverse(string:tokens(Lines, "|")),
1701    {ok, {IP, _}} = peername(CSock),
1702
1703    ?DBG('<--data tcp connect to ~p:~p, Caller=~p~n',[IP,PortStr,Caller]),
1704        case connect(IP, list_to_integer(PortStr), SockOpts, Timeout, State) of
1705                {ok, _, Socket} ->
1706                    handle_caller(State#state{caller = Caller, dsock = {tcp, Socket}});
1707                {error, _Reason} = Error ->
1708                    gen_server:reply(From, Error),
1709                    {noreply, State#state{client = undefined, caller = undefined}}
1710    end;
1711
1712
1713%% FTP server does not support passive mode: try to fallback on active mode
1714handle_ctrl_result(_,
1715                   #state{mode = passive,
1716                          caller = {setup_data_connection, Caller}} = State) ->
1717    setup_data_connection(State#state{mode = active, caller = Caller});
1718
1719
1720%%--------------------------------------------------------------------------
1721%% User handling
1722handle_ctrl_result({pos_interm, _},
1723                   #state{caller = {handle_user, PassWord, Acc}} = State) ->
1724    handle_user_passwd(PassWord, Acc, State);
1725handle_ctrl_result({Status, _},
1726                   #state{caller = {handle_user, _, _}} = State) ->
1727    ctrl_result_response(Status, State, {error, euser});
1728
1729%% Accounts
1730handle_ctrl_result({pos_interm_acct, _},
1731                   #state{caller = {handle_user_passwd, Acc}} = State)
1732  when Acc =/= "" ->
1733    handle_user_account(Acc, State);
1734handle_ctrl_result({Status, _},
1735                   #state{caller = {handle_user_passwd, _}} = State) ->
1736    ctrl_result_response(Status, State, {error, euser});
1737
1738%%--------------------------------------------------------------------------
1739%% Print current working directory
1740handle_ctrl_result({pos_compl, Lines},
1741                   #state{caller = pwd, client = From} = State) ->
1742    Dir = pwd_result(Lines),
1743    gen_server:reply(From, {ok, Dir}),
1744    {noreply, State#state{client = undefined, caller = undefined}};
1745
1746%%--------------------------------------------------------------------------
1747%% Directory listing
1748handle_ctrl_result({pos_prel, _}, #state{caller = {dir, Dir}} = State0) ->
1749    case accept_data_connection(State0) of
1750        {ok, State1} ->
1751            State = activate_data_connection(State1),
1752            {noreply, State#state{caller = {handle_dir_result, Dir}}};
1753        {error, _Reason} = Error ->
1754            ctrl_result_response(error, State0, Error)
1755    end;
1756
1757handle_ctrl_result({pos_compl, _}, #state{caller = {handle_dir_result, Dir,
1758                                                    Data}, client = From}
1759                   = State) ->
1760    case Dir of
1761        "" -> % Current directory
1762            gen_server:reply(From, {ok, Data}),
1763            {noreply, State#state{client = undefined,
1764                                  caller = undefined}};
1765        _ ->
1766            %% <WTF>
1767            %% Dir cannot be assumed to be a dir. It is a string that
1768            %% could be a dir, but could also be a file or even a string
1769            %% containing wildcards (*).
1770            %%
1771            %% %% If there is only one line it might be a directory with one
1772            %% %% file but it might be an error message that the directory
1773            %% %% was not found. So in this case we have to endure a little
1774            %% %% overhead to be able to give a good return value. Alas not
1775            %% %% all ftp implementations behave the same and returning
1776            %% %% an error string is allowed by the FTP RFC.
1777            %% case lists:dropwhile(fun(?CR) -> false;(_) -> true end,
1778            %%                          binary_to_list(Data)) of
1779            %%         L when (L =:= [?CR, ?LF]) orelse (L =:= []) ->
1780            %%             send_ctrl_message(State, mk_cmd("PWD", [])),
1781            %%             activate_ctrl_connection(State),
1782            %%             {noreply,
1783            %%              State#state{caller = {handle_dir_data, Dir, Data}}};
1784            %%         _ ->
1785            %%             gen_server:reply(From, {ok, Data}),
1786            %%             {noreply, State#state{client = undefined,
1787            %%                                   caller = undefined}}
1788            %% end
1789            %% </WTF>
1790            gen_server:reply(From, {ok, Data}),
1791            {noreply, State#state{client = undefined,
1792                                  caller = undefined}}
1793    end;
1794
1795handle_ctrl_result({pos_compl, Lines},
1796                   #state{caller = {handle_dir_data, Dir, DirData}} =
1797                   State0) ->
1798    OldDir = pwd_result(Lines),
1799    _ = send_ctrl_message(State0, mk_cmd("CWD ~s", [Dir])),
1800    State = activate_ctrl_connection(State0),
1801    {noreply, State#state{caller = {handle_dir_data_second_phase, OldDir,
1802                                    DirData}}};
1803handle_ctrl_result({Status, _},
1804                   #state{caller = {handle_dir_data, _, _}} = State) ->
1805    ctrl_result_response(Status, State, {error, epath});
1806
1807handle_ctrl_result(S={_Status, _},
1808                   #state{caller = {handle_dir_result, _, _}} = State) ->
1809    %% OTP-5731, macosx
1810    ctrl_result_response(S, State, {error, epath});
1811
1812handle_ctrl_result({pos_compl, _},
1813                   #state{caller = {handle_dir_data_second_phase, OldDir,
1814                                    DirData}} = State0) ->
1815    _ = send_ctrl_message(State0, mk_cmd("CWD ~s", [OldDir])),
1816    State = activate_ctrl_connection(State0),
1817    {noreply, State#state{caller = {handle_dir_data_third_phase, DirData}}};
1818handle_ctrl_result({Status, _},
1819                   #state{caller = {handle_dir_data_second_phase, _, _}}
1820                   = State) ->
1821    ctrl_result_response(Status, State, {error, epath});
1822handle_ctrl_result(_, #state{caller = {handle_dir_data_third_phase, DirData},
1823                             client = From} = State) ->
1824    gen_server:reply(From, {ok, DirData}),
1825    {noreply, State#state{client = undefined, caller = undefined}};
1826
1827handle_ctrl_result({Status, _}, #state{caller = cd} = State) ->
1828    ctrl_result_response(Status, State, {error, Status});
1829
1830handle_ctrl_result(Status={epath, _}, #state{caller = {dir,_}} = State) ->
1831     ctrl_result_response(Status, State, {error, epath});
1832
1833%%--------------------------------------------------------------------------
1834%% File renaming
1835handle_ctrl_result({pos_interm, _}, #state{caller = {rename, NewFile}}
1836                   = State0) ->
1837    _ = send_ctrl_message(State0, mk_cmd("RNTO ~s", [NewFile])),
1838    State = activate_ctrl_connection(State0),
1839    {noreply, State#state{caller = rename_second_phase}};
1840
1841handle_ctrl_result({Status, _},
1842                   #state{caller = {rename, _}} = State) ->
1843    ctrl_result_response(Status, State, {error, Status});
1844
1845handle_ctrl_result({Status, _},
1846                   #state{caller = rename_second_phase} = State) ->
1847    ctrl_result_response(Status, State, {error, Status});
1848
1849%%--------------------------------------------------------------------------
1850%% File handling - recv_bin
1851handle_ctrl_result({pos_prel, _}, #state{caller = recv_bin} = State0) ->
1852    case accept_data_connection(State0) of
1853        {ok, State1} ->
1854            State = activate_data_connection(State1),
1855            {noreply, State};
1856        {error, _Reason} = Error ->
1857            ctrl_result_response(error, State0, Error)
1858    end;
1859
1860handle_ctrl_result({pos_compl, _}, #state{caller = {recv_bin, Data},
1861                                          client = From} = State) ->
1862    gen_server:reply(From, {ok, Data}),
1863    close_data_connection(State),
1864    {noreply, State#state{client = undefined, caller = undefined}};
1865
1866handle_ctrl_result({Status, _}, #state{caller = recv_bin} = State) ->
1867    close_data_connection(State),
1868    ctrl_result_response(Status, State#state{dsock = undefined},
1869                         {error, epath});
1870
1871handle_ctrl_result({Status, _}, #state{caller = {recv_bin, _}} = State) ->
1872    close_data_connection(State),
1873    ctrl_result_response(Status, State#state{dsock = undefined},
1874                         {error, epath});
1875%%--------------------------------------------------------------------------
1876%% File handling - start_chunk_transfer
1877handle_ctrl_result({pos_prel, _}, #state{caller = start_chunk_transfer}
1878                   = State0) ->
1879    case accept_data_connection(State0) of
1880        {ok, State1} ->
1881            State = start_chunk(State1),
1882            {noreply, State};
1883        {error, _Reason} = Error ->
1884            ctrl_result_response(error, State0, Error)
1885    end;
1886
1887%%--------------------------------------------------------------------------
1888%% File handling - chunk_transfer complete
1889
1890handle_ctrl_result({pos_compl, _}, #state{client = From,
1891                                          caller = #recv_chunk_closing{dconn_closed       = true,
1892                                                                       client_called_us   = true,
1893                                                                       pos_compl_received = false
1894                                                                      }}
1895                   = State0) when From =/= undefined ->
1896    %% The pos_compl was the last event we waited for, finnish and clean up
1897    ?DBG("recv_chunk_closing pos_compl, last event",[]),
1898    gen_server:reply(From, ok),
1899    State = activate_ctrl_connection(State0),
1900    {noreply, State#state{caller = undefined,
1901                          chunk = false,
1902                          client = undefined}};
1903
1904handle_ctrl_result({pos_compl, _}, #state{caller = #recv_chunk_closing{}=R}
1905                   = State0) ->
1906    %% Waiting for more, don't care what
1907    ?DBG("recv_chunk_closing pos_compl, wait more",[]),
1908    {noreply, State0#state{caller = R#recv_chunk_closing{pos_compl_received=true}}};
1909
1910handle_ctrl_result({pos_compl, _}, #state{caller = undefined, chunk = true}
1911                   = State0) ->
1912    %% Waiting for user to call recv_chunk
1913    {noreply, State0#state{caller = #recv_chunk_closing{pos_compl_received=true}}};
1914
1915%%--------------------------------------------------------------------------
1916%% File handling - recv_file
1917handle_ctrl_result({pos_prel, _}, #state{caller = {recv_file, _}} = State0) ->
1918    case accept_data_connection(State0) of
1919        {ok, State1} ->
1920            State = activate_data_connection(State1),
1921            {noreply, State};
1922        {error, _Reason} = Error ->
1923            ctrl_result_response(error, State0, Error)
1924    end;
1925
1926handle_ctrl_result({Status, _}, #state{caller = {recv_file, Fd}} = State) ->
1927    file_close(Fd),
1928    close_data_connection(State),
1929    ctrl_result_response(Status, State#state{dsock = undefined},
1930                         {error, epath});
1931%%--------------------------------------------------------------------------
1932%% File handling - transfer_*
1933handle_ctrl_result({pos_prel, _}, #state{caller = {transfer_file, Fd}}
1934                   = State0) ->
1935    case accept_data_connection(State0) of
1936        {ok, State1} ->
1937            send_file(State1, Fd);
1938        {error, _Reason} = Error ->
1939            ctrl_result_response(error, State0, Error)
1940    end;
1941
1942handle_ctrl_result({pos_prel, _}, #state{caller = {transfer_data, Bin}}
1943                   = State0) ->
1944    case accept_data_connection(State0) of
1945        {ok, State} ->
1946            send_bin(State, Bin);
1947        {error, _Reason} = Error ->
1948            ctrl_result_response(error, State0, Error)
1949    end;
1950
1951%%--------------------------------------------------------------------------
1952%% Default
1953handle_ctrl_result({Status, _Lines}, #state{client = From} = State)
1954  when From =/= undefined ->
1955    ctrl_result_response(Status, State, {error, Status}).
1956
1957%%--------------------------------------------------------------------------
1958%% Help functions to handle_ctrl_result
1959%%--------------------------------------------------------------------------
1960ctrl_result_response(pos_compl, #state{client = From} = State, _)  ->
1961    gen_server:reply(From, ok),
1962    {noreply, State#state{client = undefined, caller = undefined}};
1963
1964ctrl_result_response(enofile, #state{client = From} = State, _) ->
1965    gen_server:reply(From, {error, enofile}),
1966    {noreply, State#state{client = undefined, caller = undefined}};
1967
1968ctrl_result_response(error, State0, {error, _Reason} = Error) ->
1969    case State0#state.client of
1970        undefined ->
1971            {stop, Error, State0};
1972        From ->
1973            gen_server:reply(From, Error),
1974            State = activate_ctrl_connection(State0),
1975            {noreply, State}
1976    end;
1977
1978ctrl_result_response(Status, #state{client = From} = State, _)
1979  when (Status =:= etnospc)  orelse
1980       (Status =:= epnospc)  orelse
1981       (Status =:= efnamena) orelse
1982       (Status =:= econn) ->
1983    gen_server:reply(From, {error, Status}),
1984    {stop, normal, State#state{client = undefined}};
1985
1986ctrl_result_response(_, #state{client = From} = State, ErrorMsg) ->
1987    gen_server:reply(From, ErrorMsg),
1988    {noreply, State#state{client = undefined, caller = undefined}}.
1989
1990%%--------------------------------------------------------------------------
1991handle_caller(#state{caller = {dir, Dir, Len}} = State0) ->
1992    Cmd = case Len of
1993              short -> "NLST";
1994              long -> "LIST"
1995          end,
1996    _ = case Dir of
1997            "" ->
1998                send_ctrl_message(State0, mk_cmd(Cmd, ""));
1999            _ ->
2000                send_ctrl_message(State0, mk_cmd(Cmd ++ " ~s", [Dir]))
2001        end,
2002    State = activate_ctrl_connection(State0),
2003    {noreply, State#state{caller = {dir, Dir}}};
2004
2005handle_caller(#state{caller = {recv_bin, RemoteFile}} = State0) ->
2006    _ = send_ctrl_message(State0, mk_cmd("RETR ~s", [RemoteFile])),
2007    State = activate_ctrl_connection(State0),
2008    {noreply, State#state{caller = recv_bin}};
2009
2010handle_caller(#state{caller = {start_chunk_transfer, Cmd, RemoteFile}} =
2011              State0) ->
2012    _ = send_ctrl_message(State0, mk_cmd("~s ~s", [Cmd, RemoteFile])),
2013    State = activate_ctrl_connection(State0),
2014    {noreply, State#state{caller = start_chunk_transfer}};
2015
2016handle_caller(#state{caller = {recv_file, RemoteFile, Fd}} = State0) ->
2017    _ = send_ctrl_message(State0, mk_cmd("RETR ~s", [RemoteFile])),
2018    State = activate_ctrl_connection(State0),
2019    {noreply, State#state{caller = {recv_file, Fd}}};
2020
2021handle_caller(#state{caller = {transfer_file, {Cmd, LocalFile, RemoteFile}},
2022                     ldir = LocalDir, client = From} = State0) ->
2023    case file_open(filename:absname(LocalFile, LocalDir), read) of
2024        {ok, Fd} ->
2025            _ = send_ctrl_message(State0, mk_cmd("~s ~s", [Cmd, RemoteFile])),
2026            State = activate_ctrl_connection(State0),
2027            {noreply, State#state{caller = {transfer_file, Fd}}};
2028        {error, _} ->
2029            gen_server:reply(From, {error, epath}),
2030            {noreply, State0#state{client = undefined, caller = undefined,
2031                                   dsock = undefined}}
2032    end;
2033
2034handle_caller(#state{caller = {transfer_data, {Cmd, Bin, RemoteFile}}} =
2035              State0) ->
2036    _ = send_ctrl_message(State0, mk_cmd("~s ~s", [Cmd, RemoteFile])),
2037    State = activate_ctrl_connection(State0),
2038    {noreply, State#state{caller = {transfer_data, Bin}}}.
2039
2040%%  ----------- FTP SERVER COMMUNICATION  -------------------------
2041
2042%% Connect to FTP server at Host (default is TCP port 21)
2043%% in order to establish a control connection.
2044setup_ctrl_connection(Host, Port, Timeout, #state{sockopts_ctrl = SockOpts} = State0) ->
2045    MsTime = erlang:monotonic_time(),
2046    case connect(Host, Port, SockOpts, Timeout, State0) of
2047        {ok, IpFam, CSock} ->
2048            State1 = State0#state{csock = {tcp, CSock}, ipfamily = IpFam},
2049            State = activate_ctrl_connection(State1),
2050            case Timeout - millisec_passed(MsTime) of
2051                Timeout2 when (Timeout2 >= 0) ->
2052                    {ok, State#state{caller = open}, Timeout2};
2053                _ ->
2054                    %% Oups: Simulate timeout
2055                    {ok, State#state{caller = open}, 0}
2056            end;
2057        Error ->
2058            Error
2059    end.
2060
2061setup_data_connection(#state{mode   = active,
2062                             caller = Caller,
2063                             csock  = CSock,
2064                             sockopts_data_active = SockOpts,
2065                             ftp_extension = FtpExt} = State0) ->
2066    case (catch sockname(CSock)) of
2067        {ok, {{_, _, _, _, _, _, _, _} = IP0, _}} ->
2068            IP = proplists:get_value(ip, SockOpts, IP0),
2069            {ok, LSock} =
2070                gen_tcp:listen(0, [{ip, IP}, {active, false},
2071                                   inet6, binary, {packet, 0} |
2072                                   lists:keydelete(ip,1,SockOpts)]),
2073            {ok, {_, Port}} = sockname({tcp,LSock}),
2074            IpAddress = inet_parse:ntoa(IP),
2075            Cmd = mk_cmd("EPRT |2|~s|~p|", [IpAddress, Port]),
2076            _ = send_ctrl_message(State0, Cmd),
2077            State = activate_ctrl_connection(State0),
2078            {noreply, State#state{caller = {setup_data_connection,
2079                                            {LSock, Caller}}}};
2080        {ok, {{_,_,_,_} = IP0, _}} ->
2081            IP = proplists:get_value(ip, SockOpts, IP0),
2082            {ok, LSock} = gen_tcp:listen(0, [{ip, IP}, {active, false},
2083                                             binary, {packet, 0} |
2084                                             lists:keydelete(ip,1,SockOpts)]),
2085            {ok, Port} = inet:port(LSock),
2086            _ = case FtpExt of
2087                    false ->
2088                        {IP1, IP2, IP3, IP4} = IP,
2089                        {Port1, Port2} = {Port div 256, Port rem 256},
2090                        send_ctrl_message(State0,
2091                                          mk_cmd("PORT ~w,~w,~w,~w,~w,~w",
2092                                                 [IP1, IP2, IP3, IP4, Port1, Port2]));
2093                    true ->
2094                        IpAddress = inet_parse:ntoa(IP),
2095                        Cmd = mk_cmd("EPRT |1|~s|~p|", [IpAddress, Port]),
2096                        send_ctrl_message(State0, Cmd)
2097                end,
2098            State = activate_ctrl_connection(State0),
2099            {noreply, State#state{caller = {setup_data_connection,
2100                                            {LSock, Caller}}}}
2101    end;
2102
2103setup_data_connection(#state{mode = passive, ipfamily = inet6,
2104                             caller = Caller} = State0) ->
2105    _ = send_ctrl_message(State0, mk_cmd("EPSV", [])),
2106    State = activate_ctrl_connection(State0),
2107    {noreply, State#state{caller = {setup_data_connection, Caller}}};
2108
2109setup_data_connection(#state{mode = passive, ipfamily = inet,
2110                             caller = Caller,
2111                             ftp_extension = false} = State0) ->
2112    _ = send_ctrl_message(State0, mk_cmd("PASV", [])),
2113    State = activate_ctrl_connection(State0),
2114    {noreply, State#state{caller = {setup_data_connection, Caller}}};
2115
2116setup_data_connection(#state{mode = passive, ipfamily = inet,
2117                             caller = Caller,
2118                             ftp_extension = true} = State0) ->
2119    _ = send_ctrl_message(State0, mk_cmd("EPSV", [])),
2120    State = activate_ctrl_connection(State0),
2121    {noreply, State#state{caller = {setup_data_connection, Caller}}}.
2122
2123connect(Host, Port, SockOpts, Timeout, #state{ipfamily = inet = IpFam}) ->
2124    connect2(Host, Port, IpFam, SockOpts, Timeout);
2125
2126connect(Host, Port, SockOpts, Timeout, #state{ipfamily = inet6 = IpFam}) ->
2127    connect2(Host, Port, IpFam, SockOpts, Timeout);
2128
2129connect(Host, Port, SockOpts, Timeout, #state{ipfamily = inet6fb4}) ->
2130    case inet:getaddr(Host, inet6) of
2131        {ok, {0, 0, 0, 0, 0, 16#ffff, _, _} = IPv6} ->
2132            case inet:getaddr(Host, inet) of
2133                {ok, IPv4} ->
2134                    IpFam = inet,
2135                    connect2(IPv4, Port, IpFam, SockOpts, Timeout);
2136
2137                _ ->
2138                    IpFam = inet6,
2139                    connect2(IPv6, Port, IpFam, SockOpts, Timeout)
2140            end;
2141
2142        {ok, IPv6} ->
2143            IpFam = inet6,
2144            connect2(IPv6, Port, IpFam, SockOpts, Timeout);
2145
2146        _ ->
2147            case inet:getaddr(Host, inet) of
2148                {ok, IPv4} ->
2149                    IpFam = inet,
2150                    connect2(IPv4, Port, IpFam, SockOpts, Timeout);
2151                Error ->
2152                    Error
2153            end
2154    end.
2155
2156connect2(Host, Port, IpFam, SockOpts, Timeout) ->
2157    Opts = [IpFam, binary, {packet, 0}, {active, false} | SockOpts],
2158    case gen_tcp:connect(Host, Port, Opts, Timeout) of
2159        {ok, Sock} ->
2160            {ok, IpFam, Sock};
2161        Error ->
2162            Error
2163    end.
2164
2165accept_data_connection_tls_options(#state{ csock = {ssl,Socket}, tls_options = TO0, tls_ctrl_session_reuse = true }) ->
2166	TO = lists:keydelete(reuse_sessions, 1, TO0),
2167	{ok, [{session_id,SSLSessionId},{session_data,SSLSessionData}]} = ssl:connection_information(Socket, [session_id, session_data]),
2168	lists:keystore(reuse_session, 1, TO, {reuse_session,{SSLSessionId,SSLSessionData}});
2169accept_data_connection_tls_options(#state{ tls_options = TO }) ->
2170	TO.
2171
2172accept_data_connection(#state{mode     = active,
2173                              dtimeout = DTimeout,
2174                              tls_options = TLSOptions0,
2175                              dsock    = {lsock, LSock}} = State0) ->
2176    case gen_tcp:accept(LSock, DTimeout) of
2177        {ok, Socket} when is_list(TLSOptions0) ->
2178            gen_tcp:close(LSock),
2179            TLSOptions = accept_data_connection_tls_options(State0),
2180            ?DBG('<--data ssl:connect(~p, ~p)~n~p~n',[Socket,TLSOptions,State0]),
2181            case ssl:connect(Socket, TLSOptions, DTimeout) of
2182                {ok, TLSSocket} ->
2183                    {ok, State0#state{dsock={ssl,TLSSocket}}};
2184                {error, Reason} ->
2185                    {error, {ssl_connect_failed, Reason}}
2186            end;
2187        {ok, Socket} ->
2188            gen_tcp:close(LSock),
2189            {ok, State0#state{dsock={tcp,Socket}}};
2190        {error, Reason} ->
2191            {error, {data_connect_failed, Reason}}
2192    end;
2193
2194accept_data_connection(#state{mode = passive,
2195                              dtimeout = DTimeout,
2196                              dsock = {tcp,Socket},
2197                              tls_options = TLSOptions0} = State) when is_list(TLSOptions0) ->
2198    TLSOptions = accept_data_connection_tls_options(State),
2199    ?DBG('<--data ssl:connect(~p, ~p)~n~p~n',[Socket,TLSOptions,State]),
2200    case ssl:connect(Socket, TLSOptions, DTimeout) of
2201        {ok, TLSSocket} ->
2202            {ok, State#state{dsock={ssl,TLSSocket}}};
2203        {error, Reason} ->
2204            {error, {ssl_connect_failed, Reason}}
2205    end;
2206accept_data_connection(#state{mode = passive} = State) ->
2207    {ok,State}.
2208
2209
2210send_ctrl_message(_S=#state{csock = Socket, verbose = Verbose}, Message) ->
2211    verbose(lists:flatten(Message),Verbose,send),
2212    ?DBG('<--ctrl ~p ---- ~s~p~n',[Socket,Message,_S]),
2213    _ = send_message(Socket, Message).
2214
2215send_data_message(_S=#state{dsock = Socket}, Message) ->
2216    ?DBG('<==data ~p ==== ~s~n~p~n',[Socket,Message,_S]),
2217    case send_message(Socket, Message) of
2218        ok ->
2219            ok;
2220        {error, Reason} ->
2221            Report = io_lib:format("send/2 for socket ~p failed with "
2222                                   "reason ~p~n", [Socket, Reason]),
2223            error_logger:error_report(Report),
2224            %% If tcp/ssl does not work the only option is to terminate,
2225            %% this is the expected behavior under these circumstances.
2226            exit(normal) %% User will get error message from terminate/2
2227    end.
2228
2229send_message({tcp, Socket}, Message) ->
2230    gen_tcp:send(Socket, Message);
2231send_message({ssl, Socket}, Message) ->
2232    ssl:send(Socket, Message).
2233
2234activate_ctrl_connection(#state{csock = CSock, ctrl_data = {<<>>, _, _}} = State) ->
2235    _ = activate_connection(CSock),
2236    State;
2237activate_ctrl_connection(#state{csock = CSock} = State0) ->
2238    _ = activate_connection(CSock),
2239    %% We have already received at least part of the next control message,
2240    %% that has been saved in ctrl_data, process this first.
2241    {noreply, State} = handle_info({socket_type(CSock), unwrap_socket(CSock), <<>>}, State0),
2242    State.
2243
2244activate_data_connection(#state{dsock = DSock} = State) ->
2245    _ = activate_connection(DSock),
2246    State.
2247
2248activate_connection(Socket) ->
2249    case socket_type(Socket) of
2250        tcp ->
2251            _ = activate_connection(inet, tcp_closed, Socket);
2252        ssl ->
2253            _ = activate_connection(ssl, ssl_closed, Socket)
2254    end.
2255
2256activate_connection(API, CloseTag, Socket0) ->
2257    Socket = unwrap_socket(Socket0),
2258    case API:setopts(Socket, [{active, once}]) of
2259        ok ->
2260            ok;
2261        {error, _} -> %% inet can retrun einval instead of closed
2262            self() ! {CloseTag, Socket}
2263    end.
2264
2265ignore_return_value(_) -> ok.
2266
2267unwrap_socket({tcp,Socket}) -> Socket;
2268unwrap_socket({ssl,Socket}) -> Socket.
2269
2270socket_type({tcp,_Socket}) -> tcp;
2271socket_type({ssl,_Socket}) -> ssl.
2272
2273close_ctrl_connection(#state{csock = undefined}) -> ok;
2274close_ctrl_connection(#state{csock = Socket}) -> close_connection(Socket).
2275
2276close_data_connection(#state{dsock = undefined}) -> ok;
2277close_data_connection(#state{dsock = Socket}) -> close_connection(Socket).
2278
2279close_connection({lsock,Socket}) -> ignore_return_value( gen_tcp:close(Socket) );
2280close_connection({tcp, Socket})  -> ignore_return_value( gen_tcp:close(Socket) );
2281close_connection({ssl, Socket})  -> ignore_return_value( ssl:close(Socket) ).
2282
2283%%  ------------ FILE HANDLING  ----------------------------------------
2284send_file(#state{tls_upgrading_data_connection = {true, CTRL, _}} = State, Fd) ->
2285    {noreply, State#state{tls_upgrading_data_connection = {true, CTRL, ?MODULE, send_file, Fd}}};
2286send_file(State0, Fd) ->
2287    case file_read(Fd) of
2288        {ok, N, Bin} when N > 0 ->
2289            send_data_message(State0, Bin),
2290            progress_report({binary, Bin}, State0),
2291            send_file(State0, Fd);
2292        {ok, _, _} ->
2293            file_close(Fd),
2294            close_data_connection(State0),
2295            progress_report({transfer_size, 0}, State0),
2296            State = activate_ctrl_connection(State0),
2297            {noreply, State#state{caller = transfer_file_second_phase,
2298                                  dsock = undefined}};
2299        {error, Reason} ->
2300            gen_server:reply(State0#state.client, {error, Reason}),
2301            {stop, normal, State0#state{client = undefined}}
2302    end.
2303
2304file_open(File, Option) ->
2305  file:open(File, [raw, binary, Option]).
2306
2307file_close(Fd) ->
2308    ignore_return_value( file:close(Fd) ).
2309
2310file_read(Fd) ->
2311    case file:read(Fd, ?FILE_BUFSIZE) of
2312        {ok, Bytes} ->
2313            {ok, size(Bytes), Bytes};
2314        eof ->
2315            {ok, 0, []};
2316        Other ->
2317            Other
2318    end.
2319
2320file_write(Bytes, Fd) ->
2321    file:write(Fd, Bytes).
2322
2323%% --------------  MISC ----------------------------------------------
2324
2325call(GenServer, Msg, Format) ->
2326    call(GenServer, Msg, Format, infinity).
2327call(GenServer, Msg, Format, Timeout) ->
2328    Req = {self(), Msg},
2329    case (catch gen_server:call(GenServer, Req, Timeout)) of
2330        {ok, Bin} when is_binary(Bin) andalso (Format =:= string) ->
2331            {ok, binary_to_list(Bin)};
2332        {'EXIT', _, _} ->
2333            {error, eclosed};
2334        {'EXIT', _} ->
2335            {error, eclosed};
2336        Result ->
2337            Result
2338    end.
2339
2340cast(GenServer, Msg) ->
2341    gen_server:cast(GenServer, {self(), Msg}).
2342
2343send_bin(#state{tls_upgrading_data_connection = {true, CTRL, _}} = State, Bin) ->
2344    State#state{tls_upgrading_data_connection = {true, CTRL, ?MODULE, send_bin, Bin}};
2345send_bin(State0, Bin) ->
2346    send_data_message(State0, Bin),
2347    close_data_connection(State0),
2348    State = activate_ctrl_connection(State0),
2349    {noreply, State#state{caller = transfer_data_second_phase,
2350                          dsock = undefined}}.
2351
2352mk_cmd(Fmt, Args) ->
2353    [io_lib:format(Fmt, Args)| [?CR, ?LF]]. % Deep list ok.
2354
2355is_name_sane([]) ->
2356    true;
2357is_name_sane([?CR| _]) ->
2358    false;
2359is_name_sane([?LF| _]) ->
2360    false;
2361is_name_sane([_| Rest]) ->
2362    is_name_sane(Rest).
2363
2364pwd_result(Lines) ->
2365    {_, [?DOUBLE_QUOTE | Rest]} =
2366        lists:splitwith(fun(?DOUBLE_QUOTE) -> false; (_) -> true end, Lines),
2367    {Dir, _} =
2368        lists:splitwith(fun(?DOUBLE_QUOTE) -> false; (_) -> true end, Rest),
2369    Dir.
2370
2371
2372key_search(Key, List, Default) ->
2373    case lists:keysearch(Key, 1, List) of
2374        {value, {_,Val}} ->
2375            Val;
2376        false ->
2377            Default
2378    end.
2379
2380verbose(Lines, true, Direction) ->
2381    DirStr =
2382        case Direction of
2383            send ->
2384                "Sending: ";
2385            _ ->
2386                "Receiving: "
2387        end,
2388    Str = string:strip(string:strip(Lines, right, ?LF), right, ?CR),
2389    erlang:display(DirStr++Str);
2390verbose(_, false,_) ->
2391    ok.
2392
2393progress(Options) ->
2394    ftp_progress:start_link(Options).
2395
2396progress_report(_, #state{progress = ignore}) ->
2397    ok;
2398progress_report(stop, #state{progress = ProgressPid}) ->
2399    ftp_progress:stop(ProgressPid);
2400progress_report({binary, Data}, #state{progress = ProgressPid}) ->
2401    ftp_progress:report(ProgressPid, {transfer_size, size(Data)});
2402progress_report(Report, #state{progress = ProgressPid}) ->
2403    ftp_progress:report(ProgressPid, Report).
2404
2405
2406peername({tcp, Socket}) -> inet:peername(Socket);
2407peername({ssl, Socket}) -> ssl:peername(Socket).
2408
2409sockname({tcp, Socket}) -> inet:sockname(Socket);
2410sockname({ssl, Socket}) -> ssl:sockname(Socket).
2411
2412start_chunk(#state{tls_upgrading_data_connection = {true, CTRL, _}} = State) ->
2413    State#state{tls_upgrading_data_connection = {true, CTRL, ?MODULE, start_chunk, undefined}};
2414start_chunk(#state{client = From} = State) ->
2415    gen_server:reply(From, ok),
2416    State#state{chunk = true,
2417                client = undefined,
2418                caller = undefined}.
2419
2420
2421%% This function extracts the start options from the
2422%% Valid options:
2423%%     debug,
2424%%     verbose
2425%%     ipfamily
2426%%     priority
2427%%     flags    (for backward compatibillity)
2428start_options(Options) ->
2429    case lists:keysearch(flags, 1, Options) of
2430        {value, {flags, Flags}} ->
2431            Verbose = lists:member(verbose, Flags),
2432            IsTrace = lists:member(trace, Flags),
2433            IsDebug = lists:member(debug, Flags),
2434            DebugLevel =
2435                if
2436                    (IsTrace =:= true) ->
2437                        trace;
2438                    IsDebug =:= true ->
2439                        debug;
2440                    true ->
2441                        disable
2442                end,
2443            {ok, [{verbose,  Verbose},
2444                  {debug,    DebugLevel},
2445                  {priority, low}]};
2446        false ->
2447            ValidateVerbose =
2448                fun(true) -> true;
2449                   (false) -> true;
2450                   (_) -> false
2451                end,
2452            ValidateDebug =
2453                fun(trace) -> true;
2454                   (debug) -> true;
2455                   (disable) -> true;
2456                   (_) -> false
2457                end,
2458            ValidatePriority =
2459                fun(low) -> true;
2460                   (normal) -> true;
2461                   (high) -> true;
2462                   (_) -> false
2463                end,
2464            ValidOptions =
2465                [{verbose,  ValidateVerbose,  false, false},
2466                 {debug,    ValidateDebug,    false, disable},
2467                 {priority, ValidatePriority, false, low}],
2468            validate_options(Options, ValidOptions, [])
2469    end.
2470
2471
2472%% This function extracts and validates the open options from the
2473%% Valid options:
2474%%    mode
2475%%    host
2476%%    port
2477%%    timeout
2478%%    dtimeout
2479%%    progress
2480%%          ftp_extension
2481
2482open_options(Options) ->
2483    ValidateMode =
2484        fun(active) -> true;
2485           (passive) -> true;
2486           (_) -> false
2487        end,
2488    ValidateHost =
2489        fun(Host) when is_list(Host) ->
2490                true;
2491           (Host) when is_tuple(Host) andalso
2492                       ((size(Host) =:= 4) orelse (size(Host) =:= 8)) ->
2493                true;
2494           (_) ->
2495                false
2496        end,
2497    ValidatePort =
2498        fun(Port) when is_integer(Port) andalso (Port >= 0) -> true;
2499           (_) -> false
2500        end,
2501    ValidateIpFamily =
2502        fun(inet) -> true;
2503           (inet6) -> true;
2504           (inet6fb4) -> true;
2505           (_) -> false
2506        end,
2507    ValidateTLS =
2508        fun(TLS) when is_list(TLS) -> true;
2509           (undefined) -> true;
2510           (_) -> false
2511        end,
2512    ValidateTLSSecMethod =
2513        fun(ftpes) -> true;
2514           (ftps) -> true;
2515           (_) -> false
2516        end,
2517    ValidateTLSCtrlSessionReuse =
2518        fun(Reuse) when is_boolean(Reuse) -> true;
2519           (_) -> false
2520        end,
2521    ValidateTimeout =
2522        fun(Timeout) when is_integer(Timeout) andalso (Timeout >= 0) -> true;
2523           (_) -> false
2524        end,
2525    ValidateDTimeout =
2526        fun(DTimeout) when is_integer(DTimeout) andalso (DTimeout >= 0) -> true;
2527           (infinity) -> true;
2528           (_) -> false
2529        end,
2530    ValidateProgress =
2531        fun(ignore) ->
2532                true;
2533           ({Mod, Func, _InitProgress}) when is_atom(Mod) andalso
2534                                             is_atom(Func) ->
2535                true;
2536           (_) ->
2537                false
2538        end,
2539        ValidateFtpExtension =
2540        fun(true) -> true;
2541                (false) -> true;
2542                (_) -> false
2543        end,
2544    ValidOptions =
2545        [{mode,     ValidateMode,     false, ?DEFAULT_MODE},
2546         {host,     ValidateHost,     true,  ehost},
2547         {port,     ValidatePort,     false, 0},
2548         {ipfamily, ValidateIpFamily, false, inet},
2549         {tls,      ValidateTLS,      false, undefined},
2550         {tls_sec_method, ValidateTLSSecMethod, false, ftpes},
2551         {tls_ctrl_session_reuse, ValidateTLSCtrlSessionReuse, false, false},
2552         {timeout,  ValidateTimeout,  false, ?CONNECTION_TIMEOUT},
2553         {dtimeout, ValidateDTimeout, false, ?DATA_ACCEPT_TIMEOUT},
2554         {progress, ValidateProgress, false, ?PROGRESS_DEFAULT},
2555         {ftp_extension, ValidateFtpExtension, false, ?FTP_EXT_DEFAULT}],
2556    validate_options(Options, ValidOptions, []).
2557
2558socket_options(Options) ->
2559    CtrlOpts = proplists:get_value(sock_ctrl, Options, []),
2560    DataActOpts = proplists:get_value(sock_data_act, Options, CtrlOpts),
2561    DataPassOpts = proplists:get_value(sock_data_pass, Options, CtrlOpts),
2562    case [O || O <- lists:usort(CtrlOpts++DataPassOpts++DataActOpts),
2563               not valid_socket_option(O)] of
2564        [] ->
2565            {ok, {CtrlOpts, DataPassOpts, DataActOpts}};
2566        Invalid ->
2567            throw({error,{sock_opts,Invalid}})
2568    end.
2569
2570
2571valid_socket_option(inet            ) -> false;
2572valid_socket_option(inet6           ) -> false;
2573valid_socket_option({ipv6_v6only, _}) -> false;
2574valid_socket_option({active,_}      ) -> false;
2575valid_socket_option({packet,_}      ) -> false;
2576valid_socket_option({mode,_}        ) -> false;
2577valid_socket_option(binary          ) -> false;
2578valid_socket_option(list            ) -> false;
2579valid_socket_option({header,_}      ) -> false;
2580valid_socket_option({packet_size,_} ) -> false;
2581valid_socket_option(_) -> true.
2582
2583
2584validate_options([], [], Acc) ->
2585    {ok, lists:reverse(Acc)};
2586validate_options([], ValidOptions, Acc) ->
2587    %% Check if any mandatory options are missing!
2588    case [{Key, Reason} || {Key, _, true, Reason} <- ValidOptions] of
2589        [] ->
2590            Defaults =
2591                [{Key, Default} || {Key, _, _, Default} <- ValidOptions],
2592            {ok, lists:reverse(Defaults ++ Acc)};
2593        [{_, Reason}|_Missing] ->
2594            throw({error, Reason})
2595    end;
2596validate_options([{Key, Value}|Options], ValidOptions, Acc) ->
2597    case lists:keysearch(Key, 1, ValidOptions) of
2598        {value, {Key, Validate, _, Default}} ->
2599            case (catch Validate(Value)) of
2600                true ->
2601                    NewValidOptions = lists:keydelete(Key, 1, ValidOptions),
2602                    validate_options(Options, NewValidOptions,
2603                                     [{Key, Value} | Acc]);
2604                _ ->
2605                    NewValidOptions = lists:keydelete(Key, 1, ValidOptions),
2606                    validate_options(Options, NewValidOptions,
2607                                     [{Key, Default} | Acc])
2608            end;
2609        false ->
2610            validate_options(Options, ValidOptions, Acc)
2611    end;
2612validate_options([_|Options], ValidOptions, Acc) ->
2613    validate_options(Options, ValidOptions, Acc).
2614
2615%% Help function, elapsed milliseconds since T0
2616millisec_passed(T0) ->
2617    %% OTP 18
2618    erlang:convert_time_unit(erlang:monotonic_time() - T0,
2619                             native,
2620                             micro_seconds) div 1000.
2621