File 0204-ftp-session-reuse-support-for-data-channel.patch of Package erlang

From f95c16e23ea2d9db5209a3a3cedc682fa6a542d1 Mon Sep 17 00:00:00 2001
From: Alexander Clouter <alex@digriz.org.uk>
Date: Wed, 16 Sep 2020 09:49:03 +0100
Subject: [PATCH 14/14] ftp: session reuse support for data channel

---
 lib/ftp/doc/src/ftp.xml    |  8 ++++++-
 lib/ftp/src/ftp.erl        | 27 +++++++++++++++++----
 lib/ftp/test/ftp_SUITE.erl | 49 +++++++++++++++++++++++++++-----------
 3 files changed, 64 insertions(+), 20 deletions(-)

diff --git a/lib/ftp/doc/src/ftp.xml b/lib/ftp/doc/src/ftp.xml
index cbe6771f81..817a72a820 100644
--- a/lib/ftp/doc/src/ftp.xml
+++ b/lib/ftp/doc/src/ftp.xml
@@ -547,7 +547,7 @@
 	<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()} | {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>open_option() = {ipfamily, ipfamily()} | {port, port()} | {mode, mode()} | {tls, tls_options()} | {tls_sec_method, tls_sec_method()} | {tls_ctrl_session_reuse, boolean() (default is false)} | {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() = 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>
@@ -582,6 +582,12 @@
 	the suboption <c>tls</c> is also set.
 	</p>
 
+	<p>The option <c>{tls_ctrl_session_reuse, boolean()}</c> (defaults to
+	<c>false</c>) when set to <c>true</c> the client will re-use the
+	TLS session from the control channel on the data channel as enforced by
+	many FTP servers as (<url href="https://scarybeastsecurity.blogspot.com/2009/02/vsftpd-210-released.html">proposed and implemented first by vsftpd</url>).
+	</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 970a86785a..4ad6acaef0 100644
--- a/lib/ftp/src/ftp.erl
+++ b/lib/ftp/src/ftp.erl
@@ -107,6 +107,7 @@
           sockopts_data_active = [],
           progress = ignore, % ignore | pid()
           dtimeout = ?DATA_ACCEPT_TIMEOUT, % non_neg_integer() | infinity
+          tls_ctrl_session_reuse = false, % boolean()
           tls_upgrading_data_connection = false,
           ftp_extension = ?FTP_EXT_DEFAULT
          }).
@@ -1006,6 +1007,7 @@ handle_call({_, {open, ip_comm, Options}}, From, State) ->
         Host ->
             TLSSecMethod = key_search(tls_sec_method, Opts, undefined),
             TLSOpts  = key_search(tls,      Opts, undefined),
+            TLSReuse = key_search(tls_ctrl_session_reuse, Opts, false),
             Mode     = key_search(mode,     Opts, ?DEFAULT_MODE),
             Port0    = key_search(port,     Opts, 0),
             Port     = if Port0 == 0, TLSSecMethod == ftps -> ?FTPS_PORT; Port0 == 0 -> ?FTP_PORT; true -> Port0 end,
@@ -1031,9 +1033,11 @@ handle_call({_, {open, ip_comm, Options}}, From, State) ->
             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 });
+                                       State3#state{tls_options = TLSOpts,
+						    tls_ctrl_session_reuse = TLSReuse,
+						    timeout = WaitTimeout });
                 {ok, State3, WaitTimeout} when is_list(TLSOpts) ->
-                    {noreply, State3#state{tls_options = TLSOpts}, WaitTimeout};
+                    {noreply, State3#state{tls_options = TLSOpts, tls_ctrl_session_reuse = TLSReuse }, WaitTimeout};
                 {ok, State3, WaitTimeout} ->
                     {noreply, State3, WaitTimeout};
                 {error, _Reason} ->
@@ -2152,14 +2156,21 @@ connect2(Host, Port, IpFam, SockOpts, Timeout) ->
             Error
     end.
 
+accept_data_connection_tls_options(#state{ csock = {ssl,Socket}, tls_options = TO0, tls_ctrl_session_reuse = true }) ->
+	TO = lists:keydelete(reuse_sessions, 1, TO0),
+	{ok, [{session_id,SSLSessionId},{session_data,SSLSessionData}]} = ssl:connection_information(Socket, [session_id, session_data]),
+	lists:keystore(reuse_session, 1, TO, {reuse_session,{SSLSessionId,SSLSessionData}});
+accept_data_connection_tls_options(#state{ tls_options = TO }) ->
+	TO.
 
 accept_data_connection(#state{mode     = active,
                               dtimeout = DTimeout,
-                              tls_options = TLSOptions,
+                              tls_options = TLSOptions0,
                               dsock    = {lsock, LSock}} = State0) ->
     case gen_tcp:accept(LSock, DTimeout) of
-        {ok, Socket} when  is_list(TLSOptions) ->
+        {ok, Socket} when is_list(TLSOptions0) ->
             gen_tcp:close(LSock),
+            TLSOptions = accept_data_connection_tls_options(State0),
             ?DBG('<--data ssl:connect(~p, ~p)~n~p~n',[Socket,TLSOptions,State0]),
             case ssl:connect(Socket, TLSOptions, DTimeout) of
                 {ok, TLSSocket} ->
@@ -2177,7 +2188,8 @@ accept_data_connection(#state{mode     = active,
 accept_data_connection(#state{mode = passive,
                               dtimeout = DTimeout,
                               dsock = {tcp,Socket},
-                              tls_options = TLSOptions} = State) when is_list(TLSOptions) ->
+                              tls_options = TLSOptions0} = State) when is_list(TLSOptions0) ->
+    TLSOptions = accept_data_connection_tls_options(State),
     ?DBG('<--data ssl:connect(~p, ~p)~n~p~n',[Socket,TLSOptions,State]),
     case ssl:connect(Socket, TLSOptions, DTimeout) of
         {ok, TLSSocket} ->
@@ -2494,6 +2506,10 @@ open_options(Options) ->
            (ftps) -> true;
            (_) -> false
         end,
+    ValidateTLSCtrlSessionReuse =
+        fun(Reuse) when is_boolean(Reuse) -> true;
+           (_) -> false
+        end,
     ValidateTimeout =
         fun(Timeout) when is_integer(Timeout) andalso (Timeout >= 0) -> true;
            (_) -> false
@@ -2524,6 +2540,7 @@ open_options(Options) ->
          {ipfamily, ValidateIpFamily, false, inet},
          {tls,      ValidateTLS,      false, undefined},
          {tls_sec_method, ValidateTLSSecMethod, false, ftpes},
+         {tls_ctrl_session_reuse, ValidateTLSCtrlSessionReuse, false, false},
          {timeout,  ValidateTimeout,  false, ?CONNECTION_TIMEOUT},
          {dtimeout, ValidateDTimeout, false, ?DATA_ACCEPT_TIMEOUT},
          {progress, ValidateProgress, false, ?PROGRESS_DEFAULT},
diff --git a/lib/ftp/test/ftp_SUITE.erl b/lib/ftp/test/ftp_SUITE.erl
index af998169c5..d5c827f0f2 100644
--- a/lib/ftp/test/ftp_SUITE.erl
+++ b/lib/ftp/test/ftp_SUITE.erl
@@ -55,6 +55,10 @@ all() ->
      {group, ftpes_active},
      {group, ftps_passive},
      {group, ftps_active},
+     {group, ftpes_passive_reuse},
+     {group, ftpes_active_reuse},
+     {group, ftps_passive_reuse},
+     {group, ftps_active_reuse},
      {group, ftp_sup},
      app,
      appup,
@@ -71,6 +75,10 @@ groups() ->
      {ftpes_active, [], ftp_tests_smoke()},
      {ftps_passive, [], ftp_tests_smoke()},
      {ftps_active, [], ftp_tests_smoke()},
+     {ftpes_passive_reuse, [], ftp_tests_smoke()},
+     {ftpes_active_reuse, [], ftp_tests_smoke()},
+     {ftps_passive_reuse, [], ftp_tests_smoke()},
+     {ftps_active_reuse, [], ftp_tests_smoke()},
      {ftp_sup, [], ftp_sup_tests()}
     ].
 
@@ -265,13 +273,21 @@ end_per_suite(_Config) ->
 init_per_group(Group, Config) when Group == ftpes_passive;
                                    Group == ftpes_active;
                                    Group == ftps_passive;
-                                   Group == ftps_active ->
+                                   Group == ftps_active;
+                                   Group == ftpes_passive_reuse;
+                                   Group == ftpes_active_reuse;
+                                   Group == ftps_passive_reuse;
+                                   Group == ftps_active_reuse ->
     catch crypto:stop(),
     try crypto:start() of
         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])
+            start_ftpd([{ftpd_ssl,true},{ftpd_ssl_implicit,true}|Config]);
+        ok when Group == ftpes_passive_reuse; Group == ftpes_active_reuse ->
+            start_ftpd([{ftpd_ssl,true},{ftpd_ssl_reuse,true}|Config]);
+        ok when Group == ftps_passive_reuse; Group == ftps_active_reuse ->
+            start_ftpd([{ftpd_ssl,true},{ftpd_ssl_reuse,true},{ftpd_ssl_implicit,true}|Config])
     catch
         _:_ ->
             {skip, "Crypto did not start"}
@@ -321,8 +337,11 @@ init_per_testcase(Case, Config0) ->
 init_per_testcase2(Case, Config0) ->
     Group = proplists:get_value(name, proplists:get_value(tc_group_properties,Config0)),
 
-    TLS = [{tls,vsftpd_tls()}],
+    TLSB = vsftpd_tls(),
+    TLS = [{tls,TLSB}],
     SSL = [{tls_sec_method,ftps}|TLS],
+    TLSReuse = [{tls_ctrl_session_reuse,true}|TLS],
+    SSLReuse = [{tls_sec_method,ftps}|TLSReuse],
     ACTIVE = [{mode,active}],
     PASSIVE = [{mode,passive}],
     CaseOpts = case Case of
@@ -333,14 +352,18 @@ init_per_testcase2(Case, Config0) ->
     ExtraOpts = [{verbose,true} | CaseOpts],
     Config =
         case Group of
-            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
+            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);
+            ftpes_passive_reuse -> ftp__open(Config0, TLSReuse ++ PASSIVE ++ ExtraOpts);
+            ftpes_active_reuse  -> ftp__open(Config0, TLSReuse ++  ACTIVE ++ ExtraOpts);
+            ftps_passive_reuse  -> ftp__open(Config0, SSLReuse ++ PASSIVE ++ ExtraOpts);
+            ftps_active_reuse   -> ftp__open(Config0, SSLReuse ++  ACTIVE ++ ExtraOpts);
+            ftp_sup             -> ftp_start_service(Config0,      ACTIVE ++ ExtraOpts);
+            undefined           -> Config0
         end,
     case Case of
         user           -> Config;
@@ -405,9 +428,7 @@ vsftpd_tls() ->
     [
         {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)}
+        {versions,['tlsv1.2']}
     ].
 
 %%--------------------------------------------------------------------
-- 
2.26.2

openSUSE Build Service is sponsored by