File 0203-ftp-support-for-FTPS-with-tls_sec_method-ftps.patch of Package erlang
From f99c6f95860ad6fd7f6b69f433d4290d0ffa2ff5 Mon Sep 17 00:00:00 2001
From: Alexander Clouter <alex@digriz.org.uk>
Date: Thu, 28 May 2020 18:06:33 +0100
Subject: [PATCH 13/14] ftp: support for FTPS with {tls_sec_method,ftps}
---
lib/ftp/doc/src/ftp.xml | 14 ++++--
lib/ftp/src/ftp.erl | 48 ++++++++++++++------
lib/ftp/test/ftp_SUITE.erl | 92 +++++++++++++++++++++++++-------------
3 files changed, 106 insertions(+), 48 deletions(-)
diff --git a/lib/ftp/doc/src/ftp.xml b/lib/ftp/doc/src/ftp.xml
index 0a147c721d..cbe6771f81 100644
--- a/lib/ftp/doc/src/ftp.xml
+++ b/lib/ftp/doc/src/ftp.xml
@@ -98,7 +98,8 @@
<item>
<marker id="port"></marker>
<p>Port = <c>integer() > 0</c></p>
- <p>Default is <c>21</c>.</p>
+ <p>Default is <c>0</c> which aliases to <c>21</c> or <c>990</c> when used with
+ <seeerl marker="#open"><c>{tls_sec_method,ftps}</c></seeerl>).</p>
</item>
<tag>{mode, Mode}</tag>
@@ -546,11 +547,12 @@
<v>start_option() = {verbose, verbose()} | {debug, debug()}</v>
<v>verbose() = boolean() (default is false)</v>
<v>debug() = disable | debug | trace (default is disable)</v>
- <v>open_option() = {ipfamily, ipfamily()} | {port, port()} | {mode, mode()} | {tls, tls_options()} | {timeout, timeout()} | {dtimeout, dtimeout()} | {progress, progress() | {sock_ctrl, sock_opts()} | {sock_data_act, sock_opts()} | {sock_data_pass, sock_opts()} }</v>
+ <v>open_option() = {ipfamily, ipfamily()} | {port, port()} | {mode, mode()} | {tls, tls_options()} | {tls_sec_method, tls_sec_method()} | {timeout, timeout()} | {dtimeout, dtimeout()} | {progress, progress() | {sock_ctrl, sock_opts()} | {sock_data_act, sock_opts()} | {sock_data_pass, sock_opts()} }</v>
<v>ipfamily() = inet | inet6 | inet6fb4 (default is inet)</v>
- <v>port() = integer() > 0 (default is 21)</v>
+ <v>port() = non_neg_integer() (default is 0 which aliases to 21 or 990 when used with {tls_sec_method,ftps})</v>
<v>mode() = active | passive (default is passive)</v>
<v>tls_options() = [<seetype marker="ssl:ssl#tls_option">ssl:tls_option()</seetype>]</v>
+ <v>tls_sec_method() = ftps | ftpes (default is ftpes)</v>
<v>sock_opts() = [<seetype marker="kernel:gen_tcp#option">gen_tcp:option()</seetype> except for ipv6_v6only, active, packet, mode, packet_size and header</v>
<v>timeout() = integer() > 0 (default is 60000 milliseconds)</v>
<v>dtimeout() = integer() > 0 | infinity (default is infinity)</v>
@@ -574,6 +576,12 @@
is used for securing both the control connection and the data sessions.
</p>
+ <p>The suboption <c>{tls_sec_method, tls_sec_method()}</c> (defaults to
+ <c>ftpes</c>) when set to <c>ftps</c> will connect immediately with SSL
+ instead of upgrading with STARTTLS. This suboption is ignored unless
+ the suboption <c>tls</c> is also set.
+ </p>
+
<p>The options <c>sock_ctrl</c>, <c>sock_data_act</c> and <c>sock_data_pass</c> passes options down to
the underlying transport layer (tcp). The default value for <c>sock_ctrl</c> is <c>[]</c>. Both
<c>sock_data_act</c> and <c>sock_data_pass</c> uses the value of <c>sock_ctrl</c> as default value.
diff --git a/lib/ftp/src/ftp.erl b/lib/ftp/src/ftp.erl
index d842a5f8fe..970a86785a 100644
--- a/lib/ftp/src/ftp.erl
+++ b/lib/ftp/src/ftp.erl
@@ -67,6 +67,7 @@
%% Internal Constants
-define(FTP_PORT, 21).
+-define(FTPS_PORT, 990).
-define(FILE_BUFSIZE, 4096).
@@ -998,21 +999,24 @@ handle_call({Pid, _}, _, #state{owner = Owner} = State) when Owner =/= Pid ->
handle_call({_, {open, ip_comm, Options}}, From, State) ->
{ok, Opts} = open_options(Options),
- {ok, {CtrlOpts, DataPassOpts, DataActOpts}} = socket_options(Options),
- {ok, TLSOpts} = tls_options(Options),
case key_search(host, Opts, undefined) of
undefined ->
{stop, normal, {error, ehost}, State};
Host ->
+ TLSSecMethod = key_search(tls_sec_method, Opts, undefined),
+ TLSOpts = key_search(tls, Opts, undefined),
Mode = key_search(mode, Opts, ?DEFAULT_MODE),
- Port = key_search(port, Opts, ?FTP_PORT),
+ Port0 = key_search(port, Opts, 0),
+ Port = if Port0 == 0, TLSSecMethod == ftps -> ?FTPS_PORT; Port0 == 0 -> ?FTP_PORT; true -> Port0 end,
Timeout = key_search(timeout, Opts, ?CONNECTION_TIMEOUT),
DTimeout = key_search(dtimeout, Opts, ?DATA_ACCEPT_TIMEOUT),
Progress = key_search(progress, Opts, ignore),
IpFamily = key_search(ipfamily, Opts, inet),
FtpExt = key_search(ftp_extension, Opts, ?FTP_EXT_DEFAULT),
+ {ok, {CtrlOpts, DataPassOpts, DataActOpts}} = socket_options(Options),
+
State2 = State#state{client = From,
mode = Mode,
progress = progress(Progress),
@@ -1025,6 +1029,9 @@ handle_call({_, {open, ip_comm, Options}}, From, State) ->
ftp_extension = FtpExt},
case setup_ctrl_connection(Host, Port, Timeout, State2) of
+ {ok, State3, WaitTimeout} when is_list(TLSOpts), TLSSecMethod == ftps ->
+ handle_ctrl_result({tls_upgrade, TLSSecMethod},
+ State3#state{tls_options = TLSOpts, timeout = WaitTimeout });
{ok, State3, WaitTimeout} when is_list(TLSOpts) ->
{noreply, State3#state{tls_options = TLSOpts}, WaitTimeout};
{ok, State3, WaitTimeout} ->
@@ -1564,7 +1571,7 @@ handle_ctrl_result({pos_compl, _}, #state{csock = {tcp, _Socket},
State = activate_ctrl_connection(State0),
{noreply, State, Timeout};
-handle_ctrl_result({tls_upgrade, _}, #state{csock = {tcp, Socket},
+handle_ctrl_result({tls_upgrade, S}, #state{csock = {tcp, Socket},
tls_options = TLSOptions,
timeout = Timeout,
caller = open, client = From}
@@ -1572,11 +1579,13 @@ handle_ctrl_result({tls_upgrade, _}, #state{csock = {tcp, Socket},
?DBG('<--ctrl ssl:connect(~p, ~p)~n~p~n',[Socket,TLSOptions,State0]),
catch ssl:start(),
case ssl:connect(Socket, TLSOptions, Timeout) of
- {ok, TLSSocket} ->
+ {ok, TLSSocket} when S == ftps ->
State1 = State0#state{csock = {ssl,TLSSocket}},
- _ = send_ctrl_message(State1, mk_cmd("PBSZ 0", [])),
State = activate_ctrl_connection(State1),
- {noreply, State#state{tls_upgrading_data_connection = {true, pbsz}} };
+ {noreply, State#state{tls_upgrading_data_connection = pending}, Timeout};
+ {ok, TLSSocket} ->
+ State1 = State0#state{csock = {ssl,TLSSocket}},
+ handle_ctrl_result({pos_compl, S}, State1#state{tls_upgrading_data_connection = pending});
{error, _} = Error ->
gen_server:reply(From, Error),
{stop, normal, State0#state{client = undefined,
@@ -1584,6 +1593,11 @@ handle_ctrl_result({tls_upgrade, _}, #state{csock = {tcp, Socket},
tls_upgrading_data_connection = false}}
end;
+handle_ctrl_result({pos_compl, _}, #state{tls_upgrading_data_connection = pending} = State0) ->
+ _ = send_ctrl_message(State0, mk_cmd("PBSZ 0", [])),
+ State = activate_ctrl_connection(State0),
+ {noreply, State#state{tls_upgrading_data_connection = {true, pbsz}}};
+
handle_ctrl_result({pos_compl, _}, #state{tls_upgrading_data_connection = {true, pbsz}} = State0) ->
_ = send_ctrl_message(State0, mk_cmd("PROT P", [])),
State = activate_ctrl_connection(State0),
@@ -2461,7 +2475,7 @@ open_options(Options) ->
false
end,
ValidatePort =
- fun(Port) when is_integer(Port) andalso (Port > 0) -> true;
+ fun(Port) when is_integer(Port) andalso (Port >= 0) -> true;
(_) -> false
end,
ValidateIpFamily =
@@ -2470,6 +2484,16 @@ open_options(Options) ->
(inet6fb4) -> true;
(_) -> false
end,
+ ValidateTLS =
+ fun(TLS) when is_list(TLS) -> true;
+ (undefined) -> true;
+ (_) -> false
+ end,
+ ValidateTLSSecMethod =
+ fun(ftpes) -> true;
+ (ftps) -> true;
+ (_) -> false
+ end,
ValidateTimeout =
fun(Timeout) when is_integer(Timeout) andalso (Timeout >= 0) -> true;
(_) -> false
@@ -2496,8 +2520,10 @@ open_options(Options) ->
ValidOptions =
[{mode, ValidateMode, false, ?DEFAULT_MODE},
{host, ValidateHost, true, ehost},
- {port, ValidatePort, false, ?FTP_PORT},
+ {port, ValidatePort, false, 0},
{ipfamily, ValidateIpFamily, false, inet},
+ {tls, ValidateTLS, false, undefined},
+ {tls_sec_method, ValidateTLSSecMethod, false, ftpes},
{timeout, ValidateTimeout, false, ?CONNECTION_TIMEOUT},
{dtimeout, ValidateDTimeout, false, ?DATA_ACCEPT_TIMEOUT},
{progress, ValidateProgress, false, ?PROGRESS_DEFAULT},
@@ -2530,10 +2556,6 @@ valid_socket_option({packet_size,_} ) -> false;
valid_socket_option(_) -> true.
-tls_options(Options) ->
- %% Options will be validated by ssl application
- {ok, proplists:get_value(tls, Options, undefined)}.
-
validate_options([], [], Acc) ->
{ok, lists:reverse(Acc)};
validate_options([], ValidOptions, Acc) ->
diff --git a/lib/ftp/test/ftp_SUITE.erl b/lib/ftp/test/ftp_SUITE.erl
index 2ba54211e4..af998169c5 100644
--- a/lib/ftp/test/ftp_SUITE.erl
+++ b/lib/ftp/test/ftp_SUITE.erl
@@ -51,6 +51,8 @@ all() ->
[
{group, ftp_passive},
{group, ftp_active},
+ {group, ftpes_passive},
+ {group, ftpes_active},
{group, ftps_passive},
{group, ftps_active},
{group, ftp_sup},
@@ -65,8 +67,10 @@ groups() ->
[
{ftp_passive, [], ftp_tests()},
{ftp_active, [], ftp_tests()},
- {ftps_passive, [], ftp_tests()},
- {ftps_active, [], ftp_tests()},
+ {ftpes_passive, [], ftp_tests_smoke()},
+ {ftpes_active, [], ftp_tests_smoke()},
+ {ftps_passive, [], ftp_tests_smoke()},
+ {ftps_active, [], ftp_tests_smoke()},
{ftp_sup, [], ftp_sup_tests()}
].
@@ -109,6 +113,11 @@ ftp_tests()->
unexpected_bang
].
+ftp_tests_smoke() ->
+ [
+ ls
+ ].
+
ftp_sup_tests() ->
[
start_ftp,
@@ -168,7 +177,11 @@ ftp_sup_tests() ->
true -> ["-orequire_ssl_reuse=YES"];
_ -> []
end,
- lists:append([Args1, A0, A1]);
+ A2 = case proplists:get_value(ftpd_ssl_implicit,__CONF__) of
+ true -> ["-oimplicit_ssl=YES"];
+ _ -> []
+ end,
+ lists:append([Args1, A0, A1, A2]);
_ ->
Args1
end,
@@ -249,12 +262,16 @@ end_per_suite(_Config) ->
ok.
%%--------------------------------------------------------------------
-init_per_group(Group, Config) when Group == ftps_active;
- Group == ftps_passive ->
+init_per_group(Group, Config) when Group == ftpes_passive;
+ Group == ftpes_active;
+ Group == ftps_passive;
+ Group == ftps_active ->
catch crypto:stop(),
try crypto:start() of
- ok ->
- start_ftpd([{ftpd_ssl,true}|Config])
+ ok when Group == ftpes_passive; Group == ftpes_active ->
+ start_ftpd([{ftpd_ssl,true}|Config]);
+ ok when Group == ftps_passive; Group == ftps_active ->
+ start_ftpd([{ftpd_ssl,true},{ftpd_ssl_implicit,true}|Config])
catch
_:_ ->
{skip, "Crypto did not start"}
@@ -304,24 +321,8 @@ init_per_testcase(Case, Config0) ->
init_per_testcase2(Case, Config0) ->
Group = proplists:get_value(name, proplists:get_value(tc_group_properties,Config0)),
- %% Workaround for interoperability issues with vsftpd =< 3.0.2:
- %%
- %% vsftpd =< 3.0.2 does not support ECDHE ciphers and the ssl application
- %% removed ciphers with RSA key exchange from its default cipher list.
- %% To allow interoperability with old versions of vsftpd, cipher suites
- %% with RSA key exchange are appended to the default cipher list.
- All = ssl:cipher_suites(all, 'tlsv1.2'),
- Default = ssl:cipher_suites(default, 'tlsv1.2'),
- RSASuites =
- ssl:filter_cipher_suites(All, [{key_exchange, fun(rsa) -> true;
- (_) -> false end}]),
- Suites = ssl:append_cipher_suites(RSASuites, Default),
- %% vsftpd =< 3.0.3 gets upset with anything later than tlsv1.2
- TLS = [{tls, [
- {versions,['tlsv1.2']},{ciphers,Suites},
- % not safe for ftp ctrl channels as reuse is for data channels
- {reuse_sessions,not proplists:get_value(ftpd_ssl_reuse,Config0,false)}
- ]}],
+ TLS = [{tls,vsftpd_tls()}],
+ SSL = [{tls_sec_method,ftps}|TLS],
ACTIVE = [{mode,active}],
PASSIVE = [{mode,passive}],
CaseOpts = case Case of
@@ -332,12 +333,14 @@ init_per_testcase2(Case, Config0) ->
ExtraOpts = [{verbose,true} | CaseOpts],
Config =
case Group of
- ftp_active -> ftp__open(Config0, ACTIVE ++ ExtraOpts);
- ftps_active -> ftp__open(Config0, TLS++ ACTIVE ++ ExtraOpts);
- ftp_passive -> ftp__open(Config0, PASSIVE ++ ExtraOpts);
- ftps_passive -> ftp__open(Config0, TLS++PASSIVE ++ ExtraOpts);
- ftp_sup -> ftp_start_service(Config0, ACTIVE ++ ExtraOpts);
- undefined -> Config0
+ ftp_active -> ftp__open(Config0, ACTIVE ++ ExtraOpts);
+ ftpes_active -> ftp__open(Config0, TLS++ ACTIVE ++ ExtraOpts);
+ ftps_active -> ftp__open(Config0, SSL++ ACTIVE ++ ExtraOpts);
+ ftp_passive -> ftp__open(Config0, PASSIVE ++ ExtraOpts);
+ ftpes_passive -> ftp__open(Config0, TLS++PASSIVE ++ ExtraOpts);
+ ftps_passive -> ftp__open(Config0, SSL++PASSIVE ++ ExtraOpts);
+ ftp_sup -> ftp_start_service(Config0, ACTIVE ++ ExtraOpts);
+ undefined -> Config0
end,
case Case of
user -> Config;
@@ -386,6 +389,27 @@ end_per_testcase(_Case, Config) ->
ftp__close(Config)
end.
+vsftpd_tls() ->
+ %% Workaround for interoperability issues with vsftpd =< 3.0.2:
+ %%
+ %% vsftpd =< 3.0.2 does not support ECDHE ciphers and the ssl application
+ %% removed ciphers with RSA key exchange from its default cipher list.
+ %% To allow interoperability with old versions of vsftpd, cipher suites
+ %% with RSA key exchange are appended to the default cipher list.
+ All = ssl:cipher_suites(all, 'tlsv1.2'),
+ Default = ssl:cipher_suites(default, 'tlsv1.2'),
+ RSASuites =
+ ssl:filter_cipher_suites(All, [{key_exchange, fun(rsa) -> true;
+ (_) -> false end}]),
+ Suites = ssl:append_cipher_suites(RSASuites, Default),
+ [
+ {ciphers,Suites},
+ %% vsftpd =< 3.0.3 gets upset with anything later than tlsv1.2
+ {versions,['tlsv1.2']},
+ % not safe for ftp ctrl channels as reuse is for data channels
+ {reuse_sessions,not proplists:get_value(ftpd_ssl_reuse,Config,false)}
+ ].
+
%%--------------------------------------------------------------------
%% Test Cases --------------------------------------------------------
%%--------------------------------------------------------------------
@@ -1189,8 +1213,12 @@ start_ftpd(Config0) ->
Config = [{ftpd_host,Host},
{ftpd_port,Port},
{ftpd_start_result,StartResult} | ConfigRewrite(Config0)],
+ Options = case proplists:get_value(ftpd_ssl_implicit, Config) of
+ true -> [{tls,vsftpd_tls()},{tls_sec_method,ftps}];
+ _ -> [] % we do not need to test AUTH TLS
+ end,
try
- ftp__close(ftp__open(Config,[{verbose,true}]))
+ ftp__close(ftp__open(Config,[{verbose,true}|Options]))
of
Config1 when is_list(Config1) ->
ct:log("Usable ftp server ~p started on ~p:~p",[AbsName,Host,Port]),
--
2.26.2