File 3201-ftp-Use-OTP-supervisor-as-intended.patch of Package erlang

From ab496b62705d3b7908b4bb56bd407bf7155ea649 Mon Sep 17 00:00:00 2001
From: Ingela Anderton Andin <ingela@erlang.org>
Date: Fri, 29 Jan 2021 18:43:28 +0100
Subject: [PATCH 1/6] ftp: Use OTP supervisor as intended

Due to legacy reasons FTP clients are not part of the FTP
applications supervisor tree unless they where started
with start_service/1. This function is a legcy from a mechanism
in inets that was never intended to be part of the ftp application.
---
 lib/ftp/doc/src/ftp.xml              | 23 +++++++--------
 lib/ftp/doc/src/ftp_client.xml       |  4 +--
 lib/ftp/src/ftp.erl                  | 44 +++++++---------------------
 lib/ftp/test/ftp_SUITE.erl           | 41 ++++----------------------
 lib/stdlib/src/otp_internal.erl      |  4 +++
 system/doc/general_info/DEPRECATIONS |  3 ++
 6 files changed, 34 insertions(+), 85 deletions(-)

diff --git a/lib/ftp/doc/src/ftp.xml b/lib/ftp/doc/src/ftp.xml
index c643ba4fa0..3dc0c097ad 100644
--- a/lib/ftp/doc/src/ftp.xml
+++ b/lib/ftp/doc/src/ftp.xml
@@ -42,12 +42,10 @@
       to active FTP mode if this fails. This default behavior can be 
       changed by start option <seeerl marker="#mode">mode</seeerl>.</p>
 
-    <marker id="two_start"></marker>
-
-    <p>An FTP client can be started in two ways. One is using the 
-      <seeerl marker="#service_start">service_start</seeerl> function,
-      the other is to start it directly as a standalone process
-      using function <seeerl marker="#open">open</seeerl>.</p>
+      <p>An FTP client is always started as part of the ftp application
+      and legacy 
+      <seeerl marker="#service_start">start_service</seeerl> function,
+      is deprecated in OTP-24 </p>
 
     <p>For a simple example of an FTP session, see 
       <seeguide marker="ftp_client">FTP User's Guide</seeguide>.</p>
@@ -74,16 +72,16 @@
       error if the request is a listing of the contents of a directory
       that exists but is empty.</p>
 
-    <marker id="service_start"></marker>
+      <marker id="service_start"></marker>
   </description>
 
   <section>
-    <title>FTP CLIENT SERVICE START/STOP</title>
+    <title>FTP CLIENT START/STOP</title>
     
     <p>The FTP client can be started and stopped dynamically in runtime by
       calling the <c>ftp</c> application API
-      <c>ftp:start_service(ServiceConfig)</c> and
-      <c>ftp:stop_service(Pid)</c>.</p>
+      <c>ftp:open(Host, Options)</c> and
+      <c>ftp:close(Client)</c>.</p>
 
     <p>The available configuration options are as follows:</p>
     
@@ -538,7 +536,7 @@
     <func>
       <name since="">open(Host) -> {ok, Pid} | {error, Reason}</name>
       <name since="">open(Host, Opts) -> {ok, Pid} | {error, Reason}</name>
-      <fsummary>Starts a standalone FTP client.</fsummary>
+      <fsummary>Starts a FTP client.</fsummary>
       <type>
 	<v>Host = string() | ip_address()</v>
 	<v>Opts = options()</v>
@@ -564,8 +562,7 @@
       </type>
 
       <desc>
-	<p>Starts a standalone FTP client process 
-          (without the <c>ftp</c> service framework) and
+	<p>Starts a FTP client process and
           opens a session with the FTP server at <c>Host</c>. </p>
 
 	<p>If option <c>{tls, tls_options()}</c> is present, the FTP session 
diff --git a/lib/ftp/doc/src/ftp_client.xml b/lib/ftp/doc/src/ftp_client.xml
index 047b055be7..7686548388 100644
--- a/lib/ftp/doc/src/ftp_client.xml
+++ b/lib/ftp/doc/src/ftp_client.xml
@@ -55,7 +55,7 @@
     <code type="erl"><![CDATA[
       1> ftp:start().
       ok
-      2> {ok, Pid} = ftp:start_service([{host, "erlang.org"}]).
+      2> {ok, Pid} = ftp:open([{host, "erlang.org"}]).
       {ok,<0.22.0>}
       3> ftp:user(Pid, "guest", "password").
       ok
@@ -69,7 +69,7 @@
       ok
       8> ftp:recv(Pid, "appl.erl").
       ok
-      9> ftp:stop_service(Pid).
+      9> ftp:close(Pid).
       ok
       10> ftp:stop().
       ok
diff --git a/lib/ftp/src/ftp.erl b/lib/ftp/src/ftp.erl
index 4ad6acaef0..c4d909a1d0 100644
--- a/lib/ftp/src/ftp.erl
+++ b/lib/ftp/src/ftp.erl
@@ -23,17 +23,15 @@
 
 -behaviour(gen_server).
 
+-deprecated([{start_service, 1, "use ftp:open/2 instead"},
+             {stop_service, 1,  "use ftp:close/1 instead"}]).
+
 -export([start/0,
          start_service/1,
          stop/0,
-         stop_service/1,
-         services/0,
-         service_info/1
+         stop_service/1
         ]).
 
-%% Added for backward compatibility
--export([start_standalone/1]).
-
 -export([start_link/1, start_link/2]).
 
 %%  API - Client interface
@@ -136,20 +134,10 @@
 start() ->
     application:start(ftp).
 
-start_standalone(Options) ->
-    try
-        {ok, StartOptions} = start_options(Options),
-        case start_link(StartOptions, []) of
-            {ok, Pid} ->
-                call(Pid, {open, ip_comm, Options}, plain);
-            Error1 ->
-                Error1
-        end
-    catch
-        throw:Error2 ->
-            Error2
-    end.
-
+%% This should be made an internal function when we remove the deprecation
+%% ftp client processes should always be part of ftp supervisor tree.
+%% We consider it a bug that the "standalone" concept of inets was 
+%% not removed when ftp was broken out, and it is now fixed.
 start_service(Options) ->
     try
         {ok, StartOptions} = start_options(Options),
@@ -170,17 +158,6 @@ stop() ->
 stop_service(Pid) ->
     close(Pid).
 
-services() ->
-    [{ftpc, Pid} || {_, Pid, _, _} <-
-                        supervisor:which_children(ftp_sup)].
-service_info(Pid) ->
-    {ok, Info} = call(Pid, info, list),
-    {ok, [proplists:lookup(mode, Info),
-          proplists:lookup(local_port, Info),
-          proplists:lookup(peer, Info),
-          proplists:lookup(peer_port, Info)]}.
-
-
 %%%=========================================================================
 %%%  API - CLIENT FUNCTIONS
 %%%=========================================================================
@@ -215,7 +192,7 @@ open(Host, Port) when is_integer(Port) ->
 %% </BACKWARD-COMPATIBILLITY>
 
 open(Host, Options) when is_list(Options) ->
-    start_standalone([{host,Host}|Options]).
+    start_service([{host,Host}|Options]).
 
 %%--------------------------------------------------------------------------
 %% user(Pid, User, Pass, <Acc>) -> ok | {error, euser} | {error, econn}
@@ -1520,8 +1497,7 @@ code_change(_Vsn, State, _Extra) ->
 %% start_link([Opts, GenServerOptions]) -> {ok, Pid} | {error, Reason}
 %%
 %% Description: Callback function for the ftp supervisor. It is called
-%%            : when start_service/1 calls ftp_sup:start_child/1 to start an
-%%            : instance of the ftp process. Also called by start_standalone/1
+%%            : when open or legacy is called. 
 %%--------------------------------------------------------------------------
 start_link([Opts, GenServerOptions]) ->
     start_link(Opts, GenServerOptions).
diff --git a/lib/ftp/test/ftp_SUITE.erl b/lib/ftp/test/ftp_SUITE.erl
index d5c827f0f2..b2cdd882c6 100644
--- a/lib/ftp/test/ftp_SUITE.erl
+++ b/lib/ftp/test/ftp_SUITE.erl
@@ -128,7 +128,6 @@ ftp_tests_smoke() ->
 
 ftp_sup_tests() ->
     [
-     start_ftp,
      ftp_worker
     ].
 
@@ -292,22 +291,10 @@ init_per_group(Group, Config) when Group == ftpes_passive;
         _:_ ->
             {skip, "Crypto did not start"}
     end;
-init_per_group(ftp_sup, Config) ->
-    try ftp:start() of
-        ok ->
-            start_ftpd(Config)
-    catch
-        _:_ ->
-            {skip, "Ftp did not start"}
-    end;
+
 init_per_group(_Group, Config) ->
     start_ftpd(Config).
 
-
-end_per_group(ftp_sup, Config) ->
-    ftp:stop(),
-    stop_ftpd(Config),
-    Config;
 end_per_group(_Group, Config) ->
     stop_ftpd(Config),
     Config.
@@ -316,6 +303,7 @@ end_per_group(_Group, Config) ->
 init_per_testcase(T, Config0) when T =:= app; T =:= appup ->
     Config0;
 init_per_testcase(Case, Config0) ->
+    application:ensure_started(ftp),
     case Case of
         error_datafail ->
             catch crypto:stop(),
@@ -362,7 +350,7 @@ init_per_testcase2(Case, Config0) ->
             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);
+            ftp_sup             -> ftp__open(Config0, ACTIVE ++ ExtraOpts);
             undefined           -> Config0
         end,
     case Case of
@@ -1025,26 +1013,6 @@ clean_shutdown(Config) ->
             end
     end.
 
-%%-------------------------------------------------------------------------
-start_ftp() ->
-    [{doc, "Start/stop of ftp service"}].
-start_ftp(Config) ->
-    Pid0 = proplists:get_value(ftp,Config),
-    Pids0 = [ServicePid || {_, ServicePid} <- ftp:services()],
-    true = lists:member(Pid0, Pids0),
-    {ok, [_|_]} = ftp:service_info(Pid0),
-    ftp:stop_service(Pid0),
-    ct:sleep(100),
-    Pids1 =  [ServicePid || {_, ServicePid} <- ftp:services()],
-    false = lists:member(Pid0, Pids1),
-
-    Host = proplists:get_value(ftpd_host,Config),
-    Port = proplists:get_value(ftpd_port,Config),
-
-    {ok, Pid1} = ftp:start_standalone([{host, Host},{port, Port}]),
-    Pids2 =  [ServicePid || {_, ServicePid} <- ftp:services()],
-    false = lists:member(Pid1, Pids2).
-
 %%-------------------------------------------------------------------------
 ftp_worker() ->
     [{doc, "Makes sure the ftp worker processes are added and removed "
@@ -1053,7 +1021,7 @@ ftp_worker(Config) ->
     Pid = proplists:get_value(ftp,Config),
     case supervisor:which_children(ftp_sup) of
         [{_,_, worker, [ftp]}] ->
-            ftp:stop_service(Pid),
+            ftp:close(Pid),
             ct:sleep(5000),
             [] = supervisor:which_children(ftp_sup),
             ok;
@@ -1264,6 +1232,7 @@ ftpd_running(Config) ->
     undefined =/= ChkUp(proplists:get_value(ftpd_start_result,Config)).
 
 ftp__open(Config, Options) ->
+    application:ensure_started(ftp),
     Host = proplists:get_value(ftpd_host,Config),
     Port = proplists:get_value(ftpd_port,Config),
     ct:log("Host=~p, Port=~p",[Host,Port]),
diff --git a/lib/stdlib/src/otp_internal.erl b/lib/stdlib/src/otp_internal.erl
index 6f691f2c3c..55fbbc4a6e 100644
--- a/lib/stdlib/src/otp_internal.erl
+++ b/lib/stdlib/src/otp_internal.erl
@@ -23,6 +23,10 @@
 -include("otp_internal.hrl").
 %%
 -dialyzer({no_match, obsolete/3}).
+obsolete(ftp, start_service, 1) ->
+    {deprecated, "use ftp:open/2 instead"};
+obsolete(ftp, stop_service, 1) ->
+    {deprecated, "use ftp:close/1 instead"};
 obsolete(auth, cookie, 0) ->
     {deprecated, "use erlang:get_cookie/0 instead"};
 obsolete(auth, cookie, 1) ->
diff --git a/system/doc/general_info/DEPRECATIONS b/system/doc/general_info/DEPRECATIONS
index 0b18d6216f..54994ce80f 100644
--- a/system/doc/general_info/DEPRECATIONS
+++ b/system/doc/general_info/DEPRECATIONS
@@ -17,6 +17,12 @@
 # is scheduled to be removed in OTP 25.
 #
 
+#
+# Added in OTP 24.
+#
+
+ftp:start_service/1 since=24 remove=26
+ftp:start_service/1 since=24 remove=26
 disk_log:accessible_logs/0 since=24 remove=26
 disk_log:lclose/1 since=24 remove=26
 disk_log:lclose/2 since=24 remove=26
-- 
2.26.2

openSUSE Build Service is sponsored by