File 4001-inets-drop-all-support-for-ftp-and-tftp-in-inets.patch of Package erlang

From 69529d35636c23e9bf13607097da8136f0f1aa80 Mon Sep 17 00:00:00 2001
From: Ao Song <andy@erlang.org>
Date: Mon, 13 Jul 2020 13:08:47 +0200
Subject: [PATCH] inets: drop all support for ftp and tftp in inets

Change-Id: Iad27ce3d779de6b88de9012278437310b25bb0b0
---
 lib/inets/Makefile                            |   2 +-
 lib/inets/doc/src/inets.xml                   |   2 +-
 lib/inets/info                                |   2 +-
 lib/inets/src/inets_app/Makefile              |   4 +-
 lib/inets/src/inets_app/inets.app.src         |   8 +-
 lib/inets/src/inets_app/inets.erl             |  47 +--
 lib/inets/src/inets_app/inets_ftp_wrapper.erl |  48 ---
 .../src/inets_app/inets_tftp_wrapper.erl      |  48 ---
 lib/inets/src/inets_app/inets_trace.erl       |   6 +-
 .../ftp_simple_client_server.erl              | 307 ------------------
 .../ftp_simple_client_server_data/vsftpd.conf |  26 --
 11 files changed, 18 insertions(+), 482 deletions(-)
 delete mode 100644 lib/inets/src/inets_app/inets_ftp_wrapper.erl
 delete mode 100644 lib/inets/src/inets_app/inets_tftp_wrapper.erl
 delete mode 100644 lib/inets/test/property_test/ftp_simple_client_server.erl
 delete mode 100644 lib/inets/test/property_test/ftp_simple_client_server_data/vsftpd.conf

diff --git a/lib/inets/Makefile b/lib/inets/Makefile
index a7723dc0d8..5a8d7b4661 100644
--- a/lib/inets/Makefile
+++ b/lib/inets/Makefile
@@ -37,6 +37,6 @@ SPECIAL_TARGETS =
 # ----------------------------------------------------
 include $(ERL_TOP)/make/otp_subdir.mk
 
-DIA_PLT_APPS=runtime_tools ftp mnesia ssl tftp
+DIA_PLT_APPS=runtime_tools mnesia ssl
 
 include $(ERL_TOP)/make/app_targets.mk
diff --git a/lib/inets/doc/src/inets.xml b/lib/inets/doc/src/inets.xml
index cdf4eb940a..400ee325f1 100644
--- a/lib/inets/doc/src/inets.xml
+++ b/lib/inets/doc/src/inets.xml
@@ -43,7 +43,7 @@
     <title>DATA TYPES</title>
     <p>Type definitions that are used more than once in
       this module:</p>
-    <p><c>service() = ftpc | tftp | httpc | httpd</c></p>
+    <p><c>service() = httpc | httpd</c></p>
     <p><c>property() = atom()</c></p>
     <marker id="functions"></marker>
     <marker id="services"></marker>
diff --git a/lib/inets/info b/lib/inets/info
index 079a271fe2..088298ec60 100644
--- a/lib/inets/info
+++ b/lib/inets/info
@@ -1,2 +1,2 @@
 group: comm
-short: A set of services such as a Web server and a ftp client etc. 
+short: A set of services such as a Web server etc. 
diff --git a/lib/inets/src/inets_app/Makefile b/lib/inets/src/inets_app/Makefile
index ec1ae70305..edaec7655b 100644
--- a/lib/inets/src/inets_app/Makefile
+++ b/lib/inets/src/inets_app/Makefile
@@ -48,9 +48,7 @@ MODULES = \
 	inets_app \
 	inets_sup \
 	inets_trace \
-	inets_lib \
-	inets_ftp_wrapper \
-	inets_tftp_wrapper
+	inets_lib
 
 INTERNAL_HRL_FILES = inets_internal.hrl
 EXTERNAL_HRL_FILES = ../../include/httpd.hrl \
diff --git a/lib/inets/src/inets_app/inets.app.src b/lib/inets/src/inets_app/inets.app.src
index 54b60ee1f7..04158ca1b6 100644
--- a/lib/inets/src/inets_app/inets.app.src
+++ b/lib/inets/src/inets_app/inets.app.src
@@ -28,9 +28,6 @@
 	    inets_service,	                  
 	    inets_trace,
             inets_lib,
-
-            %% FTP
-            inets_ftp_wrapper,
             
             %% HTTP client:
             httpc, 
@@ -94,10 +91,7 @@
             mod_responsecontrol,
             mod_security,
             mod_security_server,
-            mod_trace,
-            
-            %% TFTP
-            inets_tftp_wrapper
+            mod_trace
         ]},
   {registered,[inets_sup, httpc_manager]},
   %% If the "new" ssl is used then 'crypto' must be started before inets.
diff --git a/lib/inets/src/inets_app/inets.erl b/lib/inets/src/inets_app/inets.erl
index ab2bc5b784..77b1d6d9cd 100644
--- a/lib/inets/src/inets_app/inets.erl
+++ b/lib/inets/src/inets_app/inets.erl
@@ -58,7 +58,7 @@ start(Type) ->
 %% Function: start(Service, ServiceConfig [, How]) -> {ok, Pid} | 
 %%                                                {error, Reason}
 %%
-%% Service = - ftpc | tftpd | tftpc | tftp | httpc | httpd
+%% Service = - httpc | httpd
 %% ServiceConfig = ConfPropList | ConfFile
 %% ConfPropList = [{Property, Value}] according to service 
 %% ConfFile = Path - when service is httpd
@@ -81,12 +81,10 @@ start(Type) ->
 %% top supervisor.
 %% --------------------------------------------------------------------
 start(Service, ServiceConfig) ->
-    Module = service_module(Service),
-    start_service(Module, ServiceConfig, inets).
+    start_service(Service, ServiceConfig, inets).
 
 start(Service, ServiceConfig, How) ->
-    Module = service_module(Service),
-    start_service(Module, ServiceConfig, How).
+    start_service(Service, ServiceConfig, How).
 
 
 %%--------------------------------------------------------------------
@@ -101,7 +99,7 @@ stop() ->
 %%--------------------------------------------------------------------
 %% Function: stop(Service, Pid) -> ok
 %%
-%% Service - ftpc | ftp | tftpd | tftpc | tftp | httpc | httpd | stand_alone
+%% Service - httpc | httpd | stand_alone
 %%
 %% Description: Stops a started service of the inets application or takes
 %% down a stand alone "service" gracefully.
@@ -111,8 +109,7 @@ stop(stand_alone, Pid) ->
     ok;
 
 stop(Service, Pid) ->
-    Module = service_module(Service),
-    call_service(Module, stop_service, Pid).
+    call_service(Service, stop_service, Pid).
 
 
 %%--------------------------------------------------------------------
@@ -122,11 +119,9 @@ stop(Service, Pid) ->
 %% Note: Services started with the stand alone option will not be listed
 %%--------------------------------------------------------------------
 services() ->
-    Modules = [service_module(Service) || Service <- 
-					      service_names()],
     try lists:flatten(lists:map(fun(Module) ->
 					Module:services()
-				end, Modules)) of
+				end, service_names())) of
 	Result ->
 	    Result
     catch 
@@ -147,9 +142,8 @@ services_info() ->
 	    {error, inets_not_started};
 	Services ->
 	    Fun =  fun({Service, Pid}) -> 
-			   Module = service_module(Service),
 			   Info =  
-			       case Module:service_info(Pid) of
+			       case Service:service_info(Pid) of
 				   {ok, PropList} ->
 				       PropList;
 				   {error, Reason} ->
@@ -378,7 +372,7 @@ key1search(Key, Vals, Def) ->
 %% Description: Returns a list of supported services
 %%-------------------------------------------------------------------
 service_names() ->
-    [ftpc, tftp, httpc, httpd].
+    [httpc, httpd].
 
 
 %%-----------------------------------------------------------------
@@ -388,7 +382,7 @@ service_names() ->
 %% Parameters:
 %% Level -> max | min | integer()
 %% Destination -> File | Port | io | HandlerSpec
-%% Service -> httpc | httpd | ftpc | tftp | all
+%% Service -> httpc | httpd | all
 %% File -> string()
 %% Port -> integer()
 %% Verbosity -> true | false
@@ -437,7 +431,7 @@ set_trace(Level) -> inets_trace:set_level(Level).
 %% Parameters:
 %% Severity -> 0 =< integer() =< 100
 %% Label -> string()
-%% Service -> httpd | httpc | ftp | tftp
+%% Service -> httpd | httpc
 %% Content -> [{tag, term()}]
 %%
 %% Description:
@@ -465,24 +459,3 @@ call_service(Service, Call, Args) ->
         exit:{noproc, _} ->
             {error, inets_not_started}
     end.
-
-%% Obsolete! Kept for backward compatiblity!
-%% TFTP application has been moved out from inets
-service_module(tftpd) ->
-    inets_tftp_wrapper;
-service_module(tftpc) ->
-    inets_tftp_wrapper;
-service_module(tftp) ->
-    inets_tftp_wrapper;
-%% Obsolete! Kept for backward compatiblity!
-%% FTP application has been moved out from inets
-service_module(ftpc) ->
-    inets_ftp_wrapper;
-service_module(Service) ->
-    Service.
-
-
-
-
-
-
diff --git a/lib/inets/src/inets_app/inets_ftp_wrapper.erl b/lib/inets/src/inets_app/inets_ftp_wrapper.erl
deleted file mode 100644
index e350a490f7..0000000000
--- a/lib/inets/src/inets_app/inets_ftp_wrapper.erl
+++ /dev/null
@@ -1,48 +0,0 @@
-%%
-%% %CopyrightBegin%
-%%
-%% Copyright Ericsson AB 2006-2018. All Rights Reserved.
-%%
-%% Licensed under the Apache License, Version 2.0 (the "License");
-%% you may not use this file except in compliance with the License.
-%% You may obtain a copy of the License at
-%%
-%%     http://www.apache.org/licenses/LICENSE-2.0
-%%
-%% Unless required by applicable law or agreed to in writing, software
-%% distributed under the License is distributed on an "AS IS" BASIS,
-%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-%% See the License for the specific language governing permissions and
-%% limitations under the License.
-%%
-%% %CopyrightEnd%
-%%
--module(inets_ftp_wrapper).
-
-
--export([start_standalone/1,
-         start_service/1,
-	 stop_service/1,
-	 services/0,
-         service_info/1]).
-
-
-start_standalone(Options) ->
-    ftp:start_standalone(Options).
-
-
-start_service(Options) ->
-    application:ensure_started(ftp),
-    ftp:start_service(Options).
-
-
-stop_service(Pid) ->
-    ftp:stop_service(Pid).
-
-
-services() ->
-    [].
-
-
-service_info(_) ->
-    [].
diff --git a/lib/inets/src/inets_app/inets_tftp_wrapper.erl b/lib/inets/src/inets_app/inets_tftp_wrapper.erl
deleted file mode 100644
index 1e5deb234b..0000000000
--- a/lib/inets/src/inets_app/inets_tftp_wrapper.erl
+++ /dev/null
@@ -1,48 +0,0 @@
-%%
-%% %CopyrightBegin%
-%%
-%% Copyright Ericsson AB 2006-2018. All Rights Reserved.
-%%
-%% Licensed under the Apache License, Version 2.0 (the "License");
-%% you may not use this file except in compliance with the License.
-%% You may obtain a copy of the License at
-%%
-%%     http://www.apache.org/licenses/LICENSE-2.0
-%%
-%% Unless required by applicable law or agreed to in writing, software
-%% distributed under the License is distributed on an "AS IS" BASIS,
-%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-%% See the License for the specific language governing permissions and
-%% limitations under the License.
-%%
-%% %CopyrightEnd%
-%%
--module(inets_tftp_wrapper).
-
-
--export([start_standalone/1,
-         start_service/1,
-	 stop_service/1,
-	 services/0,
-         service_info/1]).
-
-
-start_standalone(Options) ->
-    tftp:start_standalone(Options).
-
-
-start_service(Options) ->
-    application:ensure_started(tftp),
-    tftp:start_service(Options).
-
-
-stop_service(Pid) ->
-    tftp:stop_service(Pid).
-
-
-services() ->
-    [].
-
-
-service_info(_) ->
-    [].
diff --git a/lib/inets/src/inets_app/inets_trace.erl b/lib/inets/src/inets_app/inets_trace.erl
index 64ab9bec35..050a3bdc04 100644
--- a/lib/inets/src/inets_app/inets_trace.erl
+++ b/lib/inets/src/inets_app/inets_trace.erl
@@ -42,7 +42,7 @@
 %% Parameters:
 %% Level -> max | min | integer()
 %% Destination -> File | Port | io | HandlerSpec
-%% Service -> httpc | httpd | ftpc | tftp | all
+%% Service -> httpc | httpd | all
 %% File -> string()
 %% Port -> integer()
 %% Verbosity -> true | false
@@ -99,7 +99,7 @@ do_enable(Level, Type, HandleSpec) ->
 valid_trace_service(all) ->
     true;
 valid_trace_service(Service) ->
-    lists:member(Service, [httpc, httpd, ftpc, tftp]).
+    lists:member(Service, [httpc, httpd]).
 
 
 %%-----------------------------------------------------------------
@@ -188,7 +188,7 @@ error_to_exit(Where, {error, Reason}) ->
 %% Parameters:
 %% Severity -> 0 =< integer() =< 100
 %% Label -> string()
-%% Service -> httpd | httpc | ftp | tftp
+%% Service -> httpd | httpc
 %% Content -> [{tag, term()}]
 %%
 %% Description:
diff --git a/lib/inets/test/property_test/ftp_simple_client_server.erl b/lib/inets/test/property_test/ftp_simple_client_server.erl
deleted file mode 100644
index c98d87b514..0000000000
--- a/lib/inets/test/property_test/ftp_simple_client_server.erl
+++ /dev/null
@@ -1,307 +0,0 @@
-%%
-%% %CopyrightBegin%
-%% 
-%% Copyright Ericsson AB 2004-2016. All Rights Reserved.
-%% 
-%% Licensed under the Apache License, Version 2.0 (the "License");
-%% you may not use this file except in compliance with the License.
-%% You may obtain a copy of the License at
-%%
-%%     http://www.apache.org/licenses/LICENSE-2.0
-%%
-%% Unless required by applicable law or agreed to in writing, software
-%% distributed under the License is distributed on an "AS IS" BASIS,
-%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-%% See the License for the specific language governing permissions and
-%% limitations under the License.
-%% 
-%% %CopyrightEnd%
-%%
-%%
-
--module(ftp_simple_client_server).
-
--compile(export_all).
-
--ifndef(EQC).
--ifndef(PROPER).
--define(EQC,true).
-%%-define(PROPER,true).
--endif.
--endif.
-
-
--ifdef(EQC).
-
--include_lib("eqc/include/eqc.hrl").
--include_lib("eqc/include/eqc_statem.hrl").
--define(MOD_eqc, eqc).
--define(MOD_eqc_gen, eqc_gen).
--define(MOD_eqc_statem, eqc_statem).
-
--else.
--ifdef(PROPER).
-
--include_lib("proper/include/proper.hrl").
--define(MOD_eqc, proper).
--define(MOD_eqc_gen, proper_gen).
--define(MOD_eqc_statem, proper_statem).
-
--endif.
--endif.
-
--record(state, {
-	  initialized = false,
-	  priv_dir,
-	  data_dir,
-	  servers = [], % [ {IP,Port,Userid,Pwd} ]
-	  clients = [], % [ client_ref() ]
-	  store = []    % [ {Name,Contents} ]
-	 }).
-
--define(fmt(F,A), io:format(F,A)).
-%%-define(fmt(F,A), ok).
-
--define(v(K,L), proplists:get_value(K,L)).
-
-%%%================================================================
-%%%
-%%% Properties
-%%% 
-
-%% This function is for normal eqc calls:
-prop_ftp() ->
-    {ok,PWD} = file:get_cwd(),
-    prop_ftp(filename:join([PWD,?MODULE_STRING++"_data"]),
-	     filename:join([PWD,?MODULE_STRING,"_files"])).
-
-%% This function is for calls from common_test test cases:
-prop_ftp(Config) ->
-    prop_ftp(filename:join([?v(property_dir,Config), ?MODULE_STRING++"_data"]),
-	     ?v(priv_dir,Config) ).
-
-
-prop_ftp(DataDir, PrivDir) ->
-    S0 = #state{data_dir = DataDir,
-		priv_dir = PrivDir},
-    ?FORALL(Cmds,  more_commands(10,commands(?MODULE,S0)),
-	 aggregate(command_names(Cmds),
-	   begin {_H,S,Result} = run_commands(?MODULE,Cmds),
-		 % io:format('**** Result=~p~n',[Result]),
-		 % io:format('**** S=~p~n',[S]),
-		 % io:format('**** _H=~p~n',[_H]),
-		 % io:format('**** Cmds=~p~n',[Cmds]),
-		 [cmnd_stop_server(X) || X <- S#state.servers],
-		 [inets:stop(ftpc,X) || {ok,X} <- S#state.clients],
-		 Result==ok
-	   end)
-	   ).
-
-%%%================================================================
-%%%
-%%% State model
-%%% 
-
-%% @doc Returns the state in which each test case starts. (Unless a different 
-%%      initial state is supplied explicitly to, e.g. commands/2.)
--spec initial_state() ->?MOD_eqc_statem:symbolic_state().
-initial_state() -> 
-    ?fmt("Initial_state()~n",[]),
-    #state{}.
-
-%% @doc Command generator, S is the current state
--spec command(S :: ?MOD_eqc_statem:symbolic_state()) -> ?MOD_eqc_gen:gen(eqc_statem:call()).
-
-command(#state{initialized=false,
-	       priv_dir=PrivDir}) -> 
-    {call,?MODULE,cmnd_init,[PrivDir]};
-
-command(#state{servers=[],
-	       priv_dir=PrivDir,
-	       data_dir=DataDir}) -> 
-    {call,?MODULE,cmnd_start_server,[PrivDir,DataDir]};
-
-command(#state{servers=Ss=[_|_],
-	       clients=[]}) -> 
-    {call,?MODULE,cmnd_start_client,[oneof(Ss)]};
-
-command(#state{servers=Ss=[_|_],
-	       clients=Cs=[_|_],
-	       store=Store=[_|_]
-	      }) ->
-    frequency([
-	       { 5, {call,?MODULE,cmnd_start_client,[oneof(Ss)]}},
-	       { 5, {call,?MODULE,cmnd_stop_client,[oneof(Cs)]}},
-	       {10, {call,?MODULE,cmnd_put,[oneof(Cs),file_path(),file_contents()]}},
-	       {20, {call,?MODULE,cmnd_get,[oneof(Cs),oneof(Store)]}},
-	       {10, {call,?MODULE,cmnd_delete,[oneof(Cs),oneof(Store)]}}
-	      ]);
-		 
-command(#state{servers=Ss=[_|_],
-	       clients=Cs=[_|_],
-	       store=[]
-	      }) ->
-    frequency([
-	       {5, {call,?MODULE,cmnd_start_client,[oneof(Ss)]}},
-	       {5, {call,?MODULE,cmnd_stop_client,[oneof(Cs)]}},
-	       {10, {call,?MODULE,cmnd_put,[oneof(Cs),file_path(),file_contents()]}}
-	      ]).
-		 
-%% @doc Precondition, checked before command is added to the command sequence. 
--spec precondition(S :: ?MOD_eqc_statem:symbolic_state(), C :: ?MOD_eqc_statem:call()) -> boolean().
-
-precondition(#state{clients=Cs}, {call, _, cmnd_put, [C,_,_]}) -> lists:member(C,Cs);
-
-precondition(#state{clients=Cs, store=Store}, 
-	     {call, _, cmnd_get, [C,X]}) -> lists:member(C,Cs) andalso lists:member(X,Store);
-
-precondition(#state{clients=Cs, store=Store},
-	     {call, _, cmnd_delete, [C,X]}) -> lists:member(C,Cs) andalso lists:member(X,Store);
-
-precondition(#state{servers=Ss}, {call, _, cmnd_start_client, _}) ->  Ss =/= [];
-
-precondition(#state{clients=Cs}, {call, _, cmnd_stop_client, [C]}) -> lists:member(C,Cs);
-
-precondition(#state{initialized=IsInit}, {call, _, cmnd_init, _}) -> IsInit==false;
-
-precondition(_S, {call, _, _, _}) -> true.
-
-
-%% @doc Postcondition, checked after command has been evaluated
-%%      Note: S is the state before next_state(S,_,C) 
--spec postcondition(S :: ?MOD_eqc_statem:dynamic_state(), C :: ?MOD_eqc_statem:call(), 
-                    Res :: term()) -> boolean().
-
-postcondition(_S, {call, _, cmnd_get, [_,{_Name,Expected}]}, {ok,Value}) ->
-    Value == Expected;
-
-postcondition(S, {call, _, cmnd_delete, [_,{Name,_Expected}]}, ok) ->
-    ?fmt("file:read_file(..) = ~p~n",[file:read_file(filename:join(S#state.priv_dir,Name))]),
-    {error,enoent} == file:read_file(filename:join(S#state.priv_dir,Name));
-
-postcondition(S, {call, _, cmnd_put,  [_,Name,Value]}, ok) -> 
-    {ok,Bin} = file:read_file(filename:join(S#state.priv_dir,Name)),
-    Bin == unicode:characters_to_binary(Value);
-
-postcondition(_S, {call, _, cmnd_stop_client, _}, ok) -> true;
-
-postcondition(_S, {call, _, cmnd_start_client, _}, {ok,_}) -> true;
-
-postcondition(_S, {call, _, cmnd_init, _}, ok) -> true;
-
-postcondition(_S, {call, _, cmnd_start_server, _}, {ok,_}) -> true.
-
-
-%% @doc Next state transformation, S is the current state. Returns next state.
--spec next_state(S :: ?MOD_eqc_statem:symbolic_state(), 
-		 V :: ?MOD_eqc_statem:var(), 
-                 C :: ?MOD_eqc_statem:call()) -> ?MOD_eqc_statem:symbolic_state().
-
-next_state(S, _V, {call, _, cmnd_put, [_,Name,Val]}) ->
-    S#state{store = [{Name,Val} | lists:keydelete(Name,1,S#state.store)]};
-
-next_state(S, _V, {call, _, cmnd_delete, [_,{Name,_Val}]}) ->
-    S#state{store = lists:keydelete(Name,1,S#state.store)};
-
-next_state(S, V, {call, _, cmnd_start_client, _}) ->
-    S#state{clients = [V | S#state.clients]};
-
-next_state(S, V, {call, _, cmnd_start_server, _}) ->
-    S#state{servers = [V | S#state.servers]};
-
-next_state(S, _V, {call, _, cmnd_stop_client, [C]}) ->
-    S#state{clients = S#state.clients -- [C]};
-
-next_state(S, _V, {call, _, cmnd_init, _}) ->
-    S#state{initialized=true};
-
-next_state(S, _V, {call, _, _, _}) ->
-    S.
-
-%%%================================================================
-%%%
-%%% Data model
-%%% 
-
-file_path() -> non_empty(list(alphanum_char())).
-%%file_path() -> non_empty( list(oneof([alphanum_char(), utf8_char()])) ).
-
-%%file_contents() -> list(alphanum_char()).
-file_contents() -> list(oneof([alphanum_char(), utf8_char()])).
-    
-alphanum_char() -> oneof(lists:seq($a,$z) ++ lists:seq($A,$Z) ++ lists:seq($0,$9)).
-
-utf8_char() -> oneof("åäöÅÄÖ話话カタカナひらがな").
-
-%%%================================================================
-%%%
-%%% Commands doing something with the System Under Test
-%%% 
-
-cmnd_init(PrivDir) ->
-    ?fmt('Call cmnd_init(~p)~n',[PrivDir]),
-    os:cmd("killall vsftpd"),
-    clear_files(PrivDir),
-    ok.
-
-cmnd_start_server(PrivDir, DataDir) ->
-    ?fmt('Call cmnd_start_server(~p, ~p)~n',[PrivDir,DataDir]),
-    Cmnd = ["vsftpd ", filename:join(DataDir,"vsftpd.conf"),
-	    " -oftpd_banner=erlang_otp_testing"
-	    " -oanon_root=",PrivDir
-	   ],
-    ?fmt("Cmnd=~s~n",[Cmnd]),
-    case os:cmd(Cmnd) of
-	[] ->
-	    {ok,{"localhost",9999,"ftp","usr@example.com"}};
-	Other ->
-	    {error,Other}
-    end.
-
-cmnd_stop_server({ok,{_Host,Port,_Usr,_Pwd}}) ->
-    os:cmd("kill `netstat -tpln | grep "++integer_to_list(Port)++" | awk '{print $7}' | awk -F/ '{print $1}'`").
-
-cmnd_start_client({ok,{Host,Port,Usr,Pwd}}) ->
-    ?fmt('Call cmnd_start_client(~p)...',[{Host,Port,Usr,Pwd}]),
-    case inets:start(ftpc, [{host,Host},{port,Port}]) of
-	{ok,Client} ->
-	    ?fmt("~p...",[{ok,Client}]),
-	    case ftp:user(Client, Usr, Pwd) of
-		ok -> 
-		    ?fmt("OK!~n",[]),
-		    {ok,Client};
-		Other -> 
-		    ?fmt("Other1=~p~n",[Other]),
-		    inets:stop(ftpc,Client), Other
-	    end;
-	Other -> 
-	    ?fmt("Other2=~p~n",[Other]),
-	    Other
-    end.
-		     
-cmnd_stop_client({ok,Client}) ->
-    ?fmt('Call cmnd_stop_client(~p)~n',[Client]),
-    inets:stop(ftpc, Client). %% -> ok | Other
-
-cmnd_delete({ok,Client}, {Name,_ExpectedValue}) ->
-    ?fmt('Call cmnd_delete(~p, ~p)~n',[Client,Name]),
-    R=ftp:delete(Client, Name),
-    ?fmt("R=~p~n",[R]),
-    R.
-
-cmnd_put({ok,Client}, Name, Value) ->
-    ?fmt('Call cmnd_put(~p, ~p, ~p)...',[Client, Name, Value]),
-    R = ftp:send_bin(Client, unicode:characters_to_binary(Value), Name), % ok | {error,Error}
-    ?fmt('~p~n',[R]),
-    R.
-
-cmnd_get({ok,Client}, {Name,_ExpectedValue}) ->
-    ?fmt('Call cmnd_get(~p, ~p)~n',[Client,Name]),
-    case ftp:recv_bin(Client, Name) of
-	{ok,Bin} -> {ok, unicode:characters_to_list(Bin)};
-	Other -> Other
-    end.
-
-
-clear_files(Dir) ->
-    os:cmd(["rm -fr ",filename:join(Dir,"*")]).
diff --git a/lib/inets/test/property_test/ftp_simple_client_server_data/vsftpd.conf b/lib/inets/test/property_test/ftp_simple_client_server_data/vsftpd.conf
deleted file mode 100644
index fd48e2abf0..0000000000
--- a/lib/inets/test/property_test/ftp_simple_client_server_data/vsftpd.conf
+++ /dev/null
@@ -1,26 +0,0 @@
-
-###
-### Some parameters are given in the vsftpd start command.
-### 
-### Typical command-line paramters are such that has a file path
-### component like cert files.
-###
-
-
-listen=YES
-listen_port=9999
-run_as_launching_user=YES
-ssl_enable=NO
-#allow_anon_ssl=YES
-
-background=YES
-
-write_enable=YES
-anonymous_enable=YES
-anon_upload_enable=YES
-anon_mkdir_write_enable=YES
-anon_other_write_enable=YES
-anon_world_readable_only=NO
-
-### Shouldn't be necessary....
-require_ssl_reuse=NO
-- 
2.26.2

openSUSE Build Service is sponsored by