File 0127-ssh-Join-basic-and-renegotiation-suites-and-parallel.patch of Package erlang

From f85ac4ea30269110763178d67e25e65fec22d1c8 Mon Sep 17 00:00:00 2001
From: Hans Nilsson <hans@erlang.org>
Date: Fri, 16 Mar 2018 18:14:19 +0100
Subject: [PATCH 4/4] ssh: Join basic and renegotiation suites and parallelize

---
 lib/ssh/test/Makefile                              |   1 -
 lib/ssh/test/ssh_basic_SUITE.erl                   | 314 ++++++++++++++-------
 lib/ssh/test/ssh_renegotiate_SUITE.erl             | 239 ----------------
 lib/ssh/test/ssh_renegotiate_SUITE_data/id_dsa     |  13 -
 lib/ssh/test/ssh_renegotiate_SUITE_data/id_rsa     |  15 -
 .../ssh_renegotiate_SUITE_data/ssh_host_dsa_key    |  13 -
 .../ssh_host_dsa_key.pub                           |  11 -
 .../ssh_renegotiate_SUITE_data/ssh_host_rsa_key    |  16 --
 .../ssh_host_rsa_key.pub                           |   5 -
 9 files changed, 215 insertions(+), 412 deletions(-)
 delete mode 100644 lib/ssh/test/ssh_renegotiate_SUITE.erl
 delete mode 100644 lib/ssh/test/ssh_renegotiate_SUITE_data/id_dsa
 delete mode 100644 lib/ssh/test/ssh_renegotiate_SUITE_data/id_rsa
 delete mode 100644 lib/ssh/test/ssh_renegotiate_SUITE_data/ssh_host_dsa_key
 delete mode 100644 lib/ssh/test/ssh_renegotiate_SUITE_data/ssh_host_dsa_key.pub
 delete mode 100644 lib/ssh/test/ssh_renegotiate_SUITE_data/ssh_host_rsa_key
 delete mode 100644 lib/ssh/test/ssh_renegotiate_SUITE_data/ssh_host_rsa_key.pub

diff --git a/lib/ssh/test/Makefile b/lib/ssh/test/Makefile
index 21359a0386..4d84b6c6b6 100644
--- a/lib/ssh/test/Makefile
+++ b/lib/ssh/test/Makefile
@@ -34,7 +34,6 @@ VSN=$(GS_VSN)
 MODULES= \
 	ssh_algorithms_SUITE \
 	ssh_options_SUITE \
-	ssh_renegotiate_SUITE \
 	ssh_basic_SUITE \
 	ssh_bench_SUITE \
 	ssh_compat_SUITE \
diff --git a/lib/ssh/test/ssh_basic_SUITE.erl b/lib/ssh/test/ssh_basic_SUITE.erl
index 6fadc45789..d3f93c7382 100644
--- a/lib/ssh/test/ssh_basic_SUITE.erl
+++ b/lib/ssh/test/ssh_basic_SUITE.erl
@@ -28,61 +28,12 @@
 -include("ssh_test_lib.hrl").
 
 %% Note: This directive should only be used in test suites.
-%%-compile(export_all).
-
-%%% Test cases
--export([
-	 app_test/1, 
-	 appup_test/1,
-	 cli/1,
-	 close/1,
-	 daemon_already_started/1, 
-         daemon_error_closes_port/1,
-	 daemon_opt_fd/1,
-	 multi_daemon_opt_fd/1,
-	 double_close/1, 
-	 exec/1,
-	 exec_compressed/1,  
-	 exec_key_differs1/1,
-	 exec_key_differs2/1,
-	 exec_key_differs3/1,
-	 exec_key_differs_fail/1,
-         fail_daemon_start/1,
-	 idle_time_client/1,
-	 idle_time_server/1,
-	 inet6_option/1,
-	 inet_option/1,
-	 internal_error/1,
-	 known_hosts/1,
-	 login_bad_pwd_no_retry1/1,
-	 login_bad_pwd_no_retry2/1,
-	 login_bad_pwd_no_retry3/1,
-	 login_bad_pwd_no_retry4/1,
-	 login_bad_pwd_no_retry5/1,
-	 misc_ssh_options/1,
-	 openssh_zlib_basic_test/1,  
-	 packet_size/1, 
-	 pass_phrase/1,
-	 peername_sockname/1, 
-	 send/1,
-	 shell/1,
-	 shell_no_unicode/1,
-	 shell_unicode_string/1,
-	 ssh_info_print/1,
-	 key_callback/1,
-	 key_callback_options/1,
-	 shell_exit_status/1
-	]).
-
-%%% Common test callbacks
--export([suite/0, all/0, groups/0, 
-	 init_per_suite/1, end_per_suite/1, 
-	 init_per_group/2, end_per_group/2, 
-	 init_per_testcase/2, end_per_testcase/2
-	]).
+-compile(export_all).
 
 -define(NEWLINE, <<"\r\n">>).
 
+-define(REKEY_DATA_TMO, 65000).
+
 %%--------------------------------------------------------------------
 %% Common Test interface functions -----------------------------------
 %%--------------------------------------------------------------------
@@ -92,44 +43,55 @@ suite() ->
      {timetrap,{seconds,40}}].
 
 all() -> 
-    [app_test,
-     appup_test,
-     {group, dsa_key},
-     {group, rsa_key},
-     {group, ecdsa_sha2_nistp256_key},
-     {group, ecdsa_sha2_nistp384_key},
-     {group, ecdsa_sha2_nistp521_key},
-     {group, dsa_pass_key},
-     {group, rsa_pass_key},
-     {group, ecdsa_sha2_nistp256_pass_key},
-     {group, ecdsa_sha2_nistp384_pass_key},
-     {group, ecdsa_sha2_nistp521_pass_key},
-     {group, host_user_key_differs},
-     {group, key_cb},
-     {group, internal_error},
-     {group, rsa_host_key_is_actualy_ecdsa},
-     daemon_already_started,
-     daemon_error_closes_port,
-     double_close,
-     daemon_opt_fd,
-     multi_daemon_opt_fd,
-     packet_size,
-     ssh_info_print,
-     {group, login_bad_pwd_no_retry},
-     shell_exit_status
-    ].
+    [{group, all_tests}].
+
 
 groups() ->
-    [{dsa_key, [], basic_tests()},
-     {rsa_key, [], basic_tests()},
-     {ecdsa_sha2_nistp256_key, [], basic_tests()},
-     {ecdsa_sha2_nistp384_key, [], basic_tests()},
-     {ecdsa_sha2_nistp521_key, [], basic_tests()},
+    [{all_tests, [parallel], [{group, ssh_renegotiate_SUITE},
+                              {group, ssh_basic_SUITE}
+                             ]},
+     {ssh_basic_SUITE, [], [app_test,
+                            appup_test,
+                            {group, dsa_key},
+                            {group, rsa_key},
+                            {group, ecdsa_sha2_nistp256_key},
+                            {group, ecdsa_sha2_nistp384_key},
+                            {group, ecdsa_sha2_nistp521_key},
+                            {group, dsa_pass_key},
+                            {group, rsa_pass_key},
+                            {group, ecdsa_sha2_nistp256_pass_key},
+                            {group, ecdsa_sha2_nistp384_pass_key},
+                            {group, ecdsa_sha2_nistp521_pass_key},
+                            {group, host_user_key_differs},
+                            {group, key_cb},
+                            {group, internal_error},
+                            {group, rsa_host_key_is_actualy_ecdsa},
+                            daemon_already_started,
+                            daemon_error_closes_port,
+                            double_close,
+                            daemon_opt_fd,
+                            multi_daemon_opt_fd,
+                            packet_size,
+                            ssh_info_print,
+                            {group, login_bad_pwd_no_retry},
+                            shell_exit_status
+                           ]},
+
+     {ssh_renegotiate_SUITE, [parallel], [rekey,
+                                          rekey_limit,
+                                          renegotiate1,
+                                          renegotiate2]},
+
+     {dsa_key, [], [{group, basic}]},
+     {rsa_key, [], [{group, basic}]},
+     {ecdsa_sha2_nistp256_key, [], [{group, basic}]},
+     {ecdsa_sha2_nistp384_key, [], [{group, basic}]},
+     {ecdsa_sha2_nistp521_key, [], [{group, basic}]},
      {rsa_host_key_is_actualy_ecdsa, [], [fail_daemon_start]},
      {host_user_key_differs, [parallel], [exec_key_differs1,
-				  exec_key_differs2,
-				  exec_key_differs3,
-				  exec_key_differs_fail]},
+                                          exec_key_differs2,
+                                          exec_key_differs3,
+                                          exec_key_differs_fail]},
      {dsa_pass_key, [], [pass_phrase]},
      {rsa_pass_key, [], [pass_phrase]},
      {ecdsa_sha2_nistp256_pass_key, [], [pass_phrase]},
@@ -138,24 +100,25 @@ groups() ->
      {key_cb, [parallel], [key_callback, key_callback_options]},
      {internal_error, [], [internal_error]},
      {login_bad_pwd_no_retry, [parallel], [login_bad_pwd_no_retry1,
-				   login_bad_pwd_no_retry2,
-				   login_bad_pwd_no_retry3,
-				   login_bad_pwd_no_retry4,
-				   login_bad_pwd_no_retry5
-				  ]}
+                                           login_bad_pwd_no_retry2,
+                                           login_bad_pwd_no_retry3,
+                                           login_bad_pwd_no_retry4,
+                                           login_bad_pwd_no_retry5
+                                          ]},
+     
+     {basic, [], [{group,p_basic},
+                  close, 
+                  known_hosts
+                 ]},
+     {p_basic, [parallel], [send, peername_sockname,
+                            exec, exec_compressed, 
+                            shell, shell_no_unicode, shell_unicode_string,
+                            cli,
+                            idle_time_client, idle_time_server, openssh_zlib_basic_test, 
+                            misc_ssh_options, inet_option, inet6_option]}
     ].
 
 
-basic_tests() ->
-    [{group, [parallel], [send, peername_sockname,
-                          exec, exec_compressed, 
-                          shell, shell_no_unicode, shell_unicode_string,
-                          cli,
-                          idle_time_client, idle_time_server, openssh_zlib_basic_test, 
-                          misc_ssh_options, inet_option, inet6_option]},
-     close, 
-     known_hosts
-    ].
         
 
 
@@ -170,6 +133,8 @@ end_per_suite(_Config) ->
     ssh:stop().
 
 %%--------------------------------------------------------------------
+init_per_group(ssh_renegotiate_SUITE, Config) ->
+    [{preferred_algorithms, ssh:default_algorithms()} | Config];
 init_per_group(dsa_key, Config) ->
     case lists:member('ssh-dss',
 		      ssh_transport:default_algorithms(public_key)) of
@@ -1379,6 +1344,156 @@ shell_exit_status(Config) when is_list(Config) ->
     ssh:stop_daemon(Pid).
 
 
+%%% Idle timeout test
+rekey() -> [{timetrap,{seconds,90}}].
+    
+rekey(Config) ->
+    {Pid, Host, Port} = 
+	ssh_test_lib:std_daemon(Config,
+				[{rekey_limit, 0}]),
+    ConnectionRef =
+	ssh_test_lib:std_connect(Config, Host, Port, 
+				 [{rekey_limit, 0}]),
+    Kex1 = ssh_test_lib:get_kex_init(ConnectionRef),
+    receive
+    after ?REKEY_DATA_TMO ->
+	    %%By this time rekeying would have been done
+	    Kex2 = ssh_test_lib:get_kex_init(ConnectionRef),
+	    false = (Kex2 == Kex1),
+	    ssh:close(ConnectionRef),
+	    ssh:stop_daemon(Pid)
+    end.
+
+%%--------------------------------------------------------------------
+
+%%% Test rekeying by data volume
+
+rekey_limit() -> [{timetrap,{seconds,400}}].
+
+rekey_limit(Config) ->
+    UserDir = proplists:get_value(priv_dir, Config),
+    DataFile = filename:join(UserDir, "rekey.data"),
+
+    Algs = proplists:get_value(preferred_algorithms, Config),
+    {Pid, Host, Port} = ssh_test_lib:std_daemon(Config,[{max_random_length_padding,0},
+							{preferred_algorithms,Algs}]),
+
+    ConnectionRef = ssh_test_lib:std_connect(Config, Host, Port, [{rekey_limit, 6000},
+								  {max_random_length_padding,0}]),
+    {ok, SftpPid} = ssh_sftp:start_channel(ConnectionRef),
+
+    Kex1 = ssh_test_lib:get_kex_init(ConnectionRef),
+
+    timer:sleep(?REKEY_DATA_TMO),
+    Kex1 = ssh_test_lib:get_kex_init(ConnectionRef),
+
+    Data = lists:duplicate(159000,1),
+    ok = ssh_sftp:write_file(SftpPid, DataFile, Data),
+
+    timer:sleep(?REKEY_DATA_TMO),
+    Kex2 = ssh_test_lib:get_kex_init(ConnectionRef),
+
+    false = (Kex2 == Kex1),
+
+    timer:sleep(?REKEY_DATA_TMO),
+    Kex2 = ssh_test_lib:get_kex_init(ConnectionRef),
+
+    ok = ssh_sftp:write_file(SftpPid, DataFile, "hi\n"),
+
+    timer:sleep(?REKEY_DATA_TMO),
+    Kex2 = ssh_test_lib:get_kex_init(ConnectionRef),
+
+    false = (Kex2 == Kex1),
+
+    timer:sleep(?REKEY_DATA_TMO),
+    Kex2 = ssh_test_lib:get_kex_init(ConnectionRef),
+
+    ssh_sftp:stop_channel(SftpPid),
+    ssh:close(ConnectionRef),
+    ssh:stop_daemon(Pid).
+
+%%--------------------------------------------------------------------
+
+%%% Test rekeying with simulataneous send request
+
+renegotiate1(Config) ->
+    UserDir = proplists:get_value(priv_dir, Config),
+    DataFile = filename:join(UserDir, "renegotiate1.data"),
+
+    Algs = proplists:get_value(preferred_algorithms, Config),
+    {Pid, Host, DPort} = ssh_test_lib:std_daemon(Config,[{max_random_length_padding,0},
+							 {preferred_algorithms,Algs}]),
+
+    RPort = ssh_test_lib:inet_port(),
+    {ok,RelayPid} = ssh_relay:start_link({0,0,0,0}, RPort, Host, DPort),
+
+
+    ConnectionRef = ssh_test_lib:std_connect(Config, Host, RPort, [{max_random_length_padding,0}]),
+    {ok, SftpPid} = ssh_sftp:start_channel(ConnectionRef),
+
+    Kex1 = ssh_test_lib:get_kex_init(ConnectionRef),
+
+    {ok, Handle} = ssh_sftp:open(SftpPid, DataFile, [write]),
+
+    ok = ssh_sftp:write(SftpPid, Handle, "hi\n"),
+
+    ssh_relay:hold(RelayPid, rx, 20, 1000),
+    ssh_connection_handler:renegotiate(ConnectionRef),
+    spawn(fun() -> ok=ssh_sftp:write(SftpPid, Handle, "another hi\n") end),
+
+    timer:sleep(2000),
+
+    Kex2 = ssh_test_lib:get_kex_init(ConnectionRef),
+
+    false = (Kex2 == Kex1),
+    
+    ssh_relay:stop(RelayPid),
+    ssh_sftp:stop_channel(SftpPid),
+    ssh:close(ConnectionRef),
+    ssh:stop_daemon(Pid).
+
+%%--------------------------------------------------------------------
+
+%%% Test rekeying with inflight messages from peer
+
+renegotiate2(Config) ->
+    UserDir = proplists:get_value(priv_dir, Config),
+    DataFile = filename:join(UserDir, "renegotiate2.data"),
+
+    Algs = proplists:get_value(preferred_algorithms, Config),
+    {Pid, Host, DPort} = ssh_test_lib:std_daemon(Config,[{max_random_length_padding,0},
+							 {preferred_algorithms,Algs}]),
+
+    RPort = ssh_test_lib:inet_port(),
+    {ok,RelayPid} = ssh_relay:start_link({0,0,0,0}, RPort, Host, DPort),
+
+    ConnectionRef = ssh_test_lib:std_connect(Config, Host, RPort, [{max_random_length_padding,0}]),
+    {ok, SftpPid} = ssh_sftp:start_channel(ConnectionRef),
+
+    Kex1 = ssh_test_lib:get_kex_init(ConnectionRef),
+
+    {ok, Handle} = ssh_sftp:open(SftpPid, DataFile, [write]),
+
+    ok = ssh_sftp:write(SftpPid, Handle, "hi\n"),
+
+    ssh_relay:hold(RelayPid, rx, 20, infinity),
+    spawn(fun() -> ok=ssh_sftp:write(SftpPid, Handle, "another hi\n") end),
+    %% need a small pause here to ensure ssh_sftp:write is executed
+    ct:sleep(10),
+    ssh_connection_handler:renegotiate(ConnectionRef),
+    ssh_relay:release(RelayPid, rx),
+
+    timer:sleep(2000),
+
+    Kex2 = ssh_test_lib:get_kex_init(ConnectionRef),
+
+    false = (Kex2 == Kex1),
+
+    ssh_relay:stop(RelayPid),
+    ssh_sftp:stop_channel(SftpPid),
+    ssh:close(ConnectionRef),
+    ssh:stop_daemon(Pid).
+
 %%--------------------------------------------------------------------
 %% Internal functions ------------------------------------------------
 %%--------------------------------------------------------------------
diff --git a/lib/ssh/test/ssh_renegotiate_SUITE.erl b/lib/ssh/test/ssh_renegotiate_SUITE.erl
deleted file mode 100644
index 0e7e1218ab..0000000000
--- a/lib/ssh/test/ssh_renegotiate_SUITE.erl
+++ /dev/null
@@ -1,239 +0,0 @@
-%%
-%% %CopyrightBegin%
-%%
-%% Copyright Ericsson AB 2008-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(ssh_renegotiate_SUITE).
-
--include_lib("common_test/include/ct.hrl").
--include("ssh_test_lib.hrl").
-
-%% Note: This directive should only be used in test suites.
--compile(export_all).
-
--define(REKEY_DATA_TMO, 65000).
-%%--------------------------------------------------------------------
-%% Common Test interface functions -----------------------------------
-%%--------------------------------------------------------------------
-
-suite() -> [{ct_hooks,[ts_install_cth]},
-	    {timetrap,{seconds,40}}].
-
-all() -> [{group,default_algs},
-	  {group,aes_gcm}
-	 ].
-
-groups() -> [{default_algs, [parallel], tests()},
-	     {aes_gcm,      [parallel], tests()}
-	    ].
-
-tests() -> [rekey, rekey_limit, renegotiate1, renegotiate2].
-
-%%--------------------------------------------------------------------
-init_per_suite(Config) ->
-    ?CHECK_CRYPTO(begin
-                      ssh:start(),
-                      Config
-                  end
-                 ).
-
-end_per_suite(_Config) ->
-    ssh:stop().
-
-%%--------------------------------------------------------------------
-init_per_group(aes_gcm, Config) ->
-    case lists:member({client2server,['aes128-gcm@openssh.com']},
-		      ssh_transport:supported_algorithms(cipher)) of
-	true ->
-	    [{preferred_algorithms, [{cipher,[{client2server,['aes128-gcm@openssh.com']},
-					      {server2client,['aes128-gcm@openssh.com']}]}]}
-	     | Config];
-	false ->
-	    {skip, "aes_gcm not supported"}
-    end;
-init_per_group(_, Config) ->
-    [{preferred_algorithms, ssh:default_algorithms()} | Config].
-
-
-end_per_group(_, Config) ->
-    Config.
-
-%%--------------------------------------------------------------------
-init_per_testcase(_TestCase, Config) ->
-    Config.
-
-end_per_testcase(_TestCase, _Config) ->
-    ok.
-
-%%--------------------------------------------------------------------
-%% Test Cases --------------------------------------------------------
-%%--------------------------------------------------------------------
-
-%%% Idle timeout test
-rekey() -> [{timetrap,{seconds,90}}].
-    
-rekey(Config) ->
-    {Pid, Host, Port} = 
-	ssh_test_lib:std_daemon(Config,
-				[{rekey_limit, 0}]),
-    ConnectionRef =
-	ssh_test_lib:std_connect(Config, Host, Port, 
-				 [{rekey_limit, 0}]),
-    Kex1 = ssh_test_lib:get_kex_init(ConnectionRef),
-    receive
-    after ?REKEY_DATA_TMO ->
-	    %%By this time rekeying would have been done
-	    Kex2 = ssh_test_lib:get_kex_init(ConnectionRef),
-	    false = (Kex2 == Kex1),
-	    ssh:close(ConnectionRef),
-	    ssh:stop_daemon(Pid)
-    end.
-
-%%--------------------------------------------------------------------
-
-%%% Test rekeying by data volume
-
-rekey_limit() -> [{timetrap,{seconds,400}}].
-
-rekey_limit(Config) ->
-    UserDir = proplists:get_value(priv_dir, Config),
-    DataFile = filename:join(UserDir, "rekey.data"),
-
-    Algs = proplists:get_value(preferred_algorithms, Config),
-    {Pid, Host, Port} = ssh_test_lib:std_daemon(Config,[{max_random_length_padding,0},
-							{preferred_algorithms,Algs}]),
-
-    ConnectionRef = ssh_test_lib:std_connect(Config, Host, Port, [{rekey_limit, 6000},
-								  {max_random_length_padding,0}]),
-    {ok, SftpPid} = ssh_sftp:start_channel(ConnectionRef),
-
-    Kex1 = ssh_test_lib:get_kex_init(ConnectionRef),
-
-    timer:sleep(?REKEY_DATA_TMO),
-    Kex1 = ssh_test_lib:get_kex_init(ConnectionRef),
-
-    Data = lists:duplicate(159000,1),
-    ok = ssh_sftp:write_file(SftpPid, DataFile, Data),
-
-    timer:sleep(?REKEY_DATA_TMO),
-    Kex2 = ssh_test_lib:get_kex_init(ConnectionRef),
-
-    false = (Kex2 == Kex1),
-
-    timer:sleep(?REKEY_DATA_TMO),
-    Kex2 = ssh_test_lib:get_kex_init(ConnectionRef),
-
-    ok = ssh_sftp:write_file(SftpPid, DataFile, "hi\n"),
-
-    timer:sleep(?REKEY_DATA_TMO),
-    Kex2 = ssh_test_lib:get_kex_init(ConnectionRef),
-
-    false = (Kex2 == Kex1),
-
-    timer:sleep(?REKEY_DATA_TMO),
-    Kex2 = ssh_test_lib:get_kex_init(ConnectionRef),
-
-    ssh_sftp:stop_channel(SftpPid),
-    ssh:close(ConnectionRef),
-    ssh:stop_daemon(Pid).
-
-%%--------------------------------------------------------------------
-
-%%% Test rekeying with simulataneous send request
-
-renegotiate1(Config) ->
-    UserDir = proplists:get_value(priv_dir, Config),
-    DataFile = filename:join(UserDir, "renegotiate1.data"),
-
-    Algs = proplists:get_value(preferred_algorithms, Config),
-    {Pid, Host, DPort} = ssh_test_lib:std_daemon(Config,[{max_random_length_padding,0},
-							 {preferred_algorithms,Algs}]),
-
-    RPort = ssh_test_lib:inet_port(),
-    {ok,RelayPid} = ssh_relay:start_link({0,0,0,0}, RPort, Host, DPort),
-
-
-    ConnectionRef = ssh_test_lib:std_connect(Config, Host, RPort, [{max_random_length_padding,0}]),
-    {ok, SftpPid} = ssh_sftp:start_channel(ConnectionRef),
-
-    Kex1 = ssh_test_lib:get_kex_init(ConnectionRef),
-
-    {ok, Handle} = ssh_sftp:open(SftpPid, DataFile, [write]),
-
-    ok = ssh_sftp:write(SftpPid, Handle, "hi\n"),
-
-    ssh_relay:hold(RelayPid, rx, 20, 1000),
-    ssh_connection_handler:renegotiate(ConnectionRef),
-    spawn(fun() -> ok=ssh_sftp:write(SftpPid, Handle, "another hi\n") end),
-
-    timer:sleep(2000),
-
-    Kex2 = ssh_test_lib:get_kex_init(ConnectionRef),
-
-    false = (Kex2 == Kex1),
-    
-    ssh_relay:stop(RelayPid),
-    ssh_sftp:stop_channel(SftpPid),
-    ssh:close(ConnectionRef),
-    ssh:stop_daemon(Pid).
-
-%%--------------------------------------------------------------------
-
-%%% Test rekeying with inflight messages from peer
-
-renegotiate2(Config) ->
-    UserDir = proplists:get_value(priv_dir, Config),
-    DataFile = filename:join(UserDir, "renegotiate2.data"),
-
-    Algs = proplists:get_value(preferred_algorithms, Config),
-    {Pid, Host, DPort} = ssh_test_lib:std_daemon(Config,[{max_random_length_padding,0},
-							 {preferred_algorithms,Algs}]),
-
-    RPort = ssh_test_lib:inet_port(),
-    {ok,RelayPid} = ssh_relay:start_link({0,0,0,0}, RPort, Host, DPort),
-
-    ConnectionRef = ssh_test_lib:std_connect(Config, Host, RPort, [{max_random_length_padding,0}]),
-    {ok, SftpPid} = ssh_sftp:start_channel(ConnectionRef),
-
-    Kex1 = ssh_test_lib:get_kex_init(ConnectionRef),
-
-    {ok, Handle} = ssh_sftp:open(SftpPid, DataFile, [write]),
-
-    ok = ssh_sftp:write(SftpPid, Handle, "hi\n"),
-
-    ssh_relay:hold(RelayPid, rx, 20, infinity),
-    spawn(fun() -> ok=ssh_sftp:write(SftpPid, Handle, "another hi\n") end),
-    %% need a small pause here to ensure ssh_sftp:write is executed
-    ct:sleep(10),
-    ssh_connection_handler:renegotiate(ConnectionRef),
-    ssh_relay:release(RelayPid, rx),
-
-    timer:sleep(2000),
-
-    Kex2 = ssh_test_lib:get_kex_init(ConnectionRef),
-
-    false = (Kex2 == Kex1),
-
-    ssh_relay:stop(RelayPid),
-    ssh_sftp:stop_channel(SftpPid),
-    ssh:close(ConnectionRef),
-    ssh:stop_daemon(Pid).
-
-%%--------------------------------------------------------------------
-%% Internal functions ------------------------------------------------
-%%--------------------------------------------------------------------
diff --git a/lib/ssh/test/ssh_renegotiate_SUITE_data/id_dsa b/lib/ssh/test/ssh_renegotiate_SUITE_data/id_dsa
deleted file mode 100644
index d306f8b26e..0000000000
--- a/lib/ssh/test/ssh_renegotiate_SUITE_data/id_dsa
+++ /dev/null
@@ -1,13 +0,0 @@
------BEGIN DSA PRIVATE KEY-----
-MIIBvAIBAAKBgQDfi2flSTZZofwT4yQT0NikX/LGNT7UPeB/XEWe/xovEYCElfaQ
-APFixXvEgXwoojmZ5kiQRKzLM39wBP0jPERLbnZXfOOD0PDnw0haMh7dD7XKVMod
-/EigVgHf/qBdM2M8yz1s/rRF7n1UpLSypziKjkzCm7JoSQ2zbWIPdmBIXwIVAMgP
-kpr7Sq3O7sHdb8D601DRjoExAoGAMOQxDfB2Fd8ouz6G96f/UOzRMI/Kdv8kYYKW
-JIGY+pRYrLPyYzUeJznwZreOJgrczAX+luHnKFWJ2Dnk5CyeXk67Wsr7pJ/4MBMD
-OKeIS0S8qoSBN8+Krp79fgA+yS3IfqbkJLtLu4EBaCX4mKQIX4++k44d4U5lc8pt
-+9hlEI8CgYEAznKxx9kyC6bVo7LUYKaGhofRFt0SYFc5PVmT2VUGRs1R6+6DPD+e
-uEO6IhFct7JFSRbP9p0JD4Uk+3zlZF+XX6b2PsZkeV8f/02xlNGUSmEzCSiNg1AX
-Cy/WusYhul0MncWCHMcOZB5rIvU/aP5EJJtn3xrRaz6u0SThF6AnT34CFQC63czE
-ZU8w8Q+H7z0j+a+70x2iAw==
------END DSA PRIVATE KEY-----
-
diff --git a/lib/ssh/test/ssh_renegotiate_SUITE_data/id_rsa b/lib/ssh/test/ssh_renegotiate_SUITE_data/id_rsa
deleted file mode 100644
index 9d7e0dd5fb..0000000000
--- a/lib/ssh/test/ssh_renegotiate_SUITE_data/id_rsa
+++ /dev/null
@@ -1,15 +0,0 @@
------BEGIN RSA PRIVATE KEY-----
-MIICXAIBAAKBgQD1OET+3O/Bvj/dtjxDTXmj1oiJt4sIph5kGy0RfjoPrZfaS+CU
-DhakCmS6t2ivxWFgtpKWaoGMZMJqWj6F6ZsumyFl3FPBtujwY/35cgifrI9Ns4Tl
-zR1uuengNBmV+WRQ5cd9F2qS6Z8aDQihzt0r8JUqLcK+VQbrmNzboCCQQwIDAQAB
-AoGAPQEyqPTt8JUT7mRXuaacjFXiweAXhp9NEDpyi9eLOjtFe9lElZCrsUOkq47V
-TGUeRKEm9qSodfTbKPoqc8YaBJGJPhUaTAcha+7QcDdfHBvIsgxvU7ePVnlpXRp3
-CCUEMPhlnx6xBoTYP+fRU0e3+xJIPVyVCqX1jAdUMkzfRoECQQD6ux7B1QJAIWyK
-SGkbDUbBilNmzCFNgIpOP6PA+bwfi5d16diTpra5AX09keQABAo/KaP1PdV8Vg0p
-z4P3A7G3AkEA+l+AKG6m0kQTTBMJDqOdVPYwe+5GxunMaqmhokpEbuGsrZBl5Dvd
-WpcBjR7jmenrhKZRIuA+Fz5HPo/UQJPl1QJBAKxstDkeED8j/S2XoFhPKAJ+6t39
-sUVICVTIZQeXdmzHJXCcUSkw8+WEhakqw/3SyW0oaK2FSWQJFWJUZ+8eJj8CQEh3
-xeduB5kKnS9CvzdeghZqX6QvVosSdtlUmfUYW/BgH5PpHKTP8wTaeld3XldZTpMJ
-dKiMkUw2+XYROVUrubUCQD+Na1LhULlpn4ISEtIEfqpdlUhxDgO15Wg8USmsng+x
-ICliVOSQtwaZjm8kwaFt0W7XnpnDxbRs37vIEbIMWak=
------END RSA PRIVATE KEY-----
diff --git a/lib/ssh/test/ssh_renegotiate_SUITE_data/ssh_host_dsa_key b/lib/ssh/test/ssh_renegotiate_SUITE_data/ssh_host_dsa_key
deleted file mode 100644
index 51ab6fbd88..0000000000
--- a/lib/ssh/test/ssh_renegotiate_SUITE_data/ssh_host_dsa_key
+++ /dev/null
@@ -1,13 +0,0 @@
------BEGIN DSA PRIVATE KEY-----
-MIIBuwIBAAKBgQCClaHzE2ul0gKSUxah5W0W8UiJLy4hXngKEqpaUq9SSdVdY2LK
-wVfKH1gt5iuaf1FfzOhsIC9G/GLnjYttXZc92cv/Gfe3gR+s0ni2++MX+T++mE/Q
-diltXv/Hp27PybS67SmiFW7I+RWnT2OKlMPtw2oUuKeztCe5UWjaj/y5FQIVAPLA
-l9RpiU30Z87NRAHY3NTRaqtrAoGANMRxw8UfdtNVR0CrQj3AgPaXOGE4d+G4Gp4X
-skvnCHycSVAjtYxebUkzUzt5Q6f/IabuLUdge3gXrc8BetvrcKbp+XZgM0/Vj2CF
-Ymmy3in6kzGZq7Fw1sZaku6AOU8vLa5woBT2vAcHLLT1bLAzj7viL048T6MfjrOP
-ef8nHvACgYBhDWFQJ1mf99sg92LalVq1dHLmVXb3PTJDfCO/Gz5NFmj9EZbAtdah
-/XcF3DeRF+eEoz48wQF/ExVxSMIhLdL+o+ElpVhlM7Yii+T7dPhkQfEul6zZXu+U
-ykSTXYUbtsfTNRFQGBW2/GfnEc0mnIxfn9v10NEWMzlq5z9wT9P0CgIVAN4wtL5W
-Lv62jKcdskxNyz2NQoBx
------END DSA PRIVATE KEY-----
-
diff --git a/lib/ssh/test/ssh_renegotiate_SUITE_data/ssh_host_dsa_key.pub b/lib/ssh/test/ssh_renegotiate_SUITE_data/ssh_host_dsa_key.pub
deleted file mode 100644
index 4dbb1305b0..0000000000
--- a/lib/ssh/test/ssh_renegotiate_SUITE_data/ssh_host_dsa_key.pub
+++ /dev/null
@@ -1,11 +0,0 @@
----- BEGIN SSH2 PUBLIC KEY ----
-AAAAB3NzaC1kc3MAAACBAIKVofMTa6XSApJTFqHlbRbxSIkvLiFeeAoSqlpSr1JJ1V1j
-YsrBV8ofWC3mK5p/UV/M6GwgL0b8YueNi21dlz3Zy/8Z97eBH6zSeLb74xf5P76YT9B2
-KW1e/8enbs/JtLrtKaIVbsj5FadPY4qUw+3DahS4p7O0J7lRaNqP/LkVAAAAFQDywJfU
-aYlN9GfOzUQB2NzU0WqrawAAAIA0xHHDxR9201VHQKtCPcCA9pc4YTh34bganheyS+cI
-fJxJUCO1jF5tSTNTO3lDp/8hpu4tR2B7eBetzwF62+twpun5dmAzT9WPYIViabLeKfqT
-MZmrsXDWxlqS7oA5Ty8trnCgFPa8BwcstPVssDOPu+IvTjxPox+Os495/yce8AAAAIBh
-DWFQJ1mf99sg92LalVq1dHLmVXb3PTJDfCO/Gz5NFmj9EZbAtdah/XcF3DeRF+eEoz48
-wQF/ExVxSMIhLdL+o+ElpVhlM7Yii+T7dPhkQfEul6zZXu+UykSTXYUbtsfTNRFQGBW2
-/GfnEc0mnIxfn9v10NEWMzlq5z9wT9P0Cg==
----- END SSH2 PUBLIC KEY ----
diff --git a/lib/ssh/test/ssh_renegotiate_SUITE_data/ssh_host_rsa_key b/lib/ssh/test/ssh_renegotiate_SUITE_data/ssh_host_rsa_key
deleted file mode 100644
index 79968bdd7d..0000000000
--- a/lib/ssh/test/ssh_renegotiate_SUITE_data/ssh_host_rsa_key
+++ /dev/null
@@ -1,16 +0,0 @@
------BEGIN RSA PRIVATE KEY-----
-MIICXQIBAAKBgQDCZX+4FBDwZIh9y/Uxee1VJnEXlowpz2yDKwj8semM4q843337
-zbNfxHmladB1lpz2NqyxI175xMIJuDxogyZdsOxGnFAzAnthR4dqL/RWRWzjaxSB
-6IAO9SPYVVlrpZ+1hsjLW79fwXK/yc8VdhRuWTeQiRgYY2ek8+OKbOqz4QIDAQAB
-AoGANmvJzJO5hkLuvyDZHKfAnGTtpifcR1wtSa9DjdKUyn8vhKF0mIimnbnYQEmW
-NUUb3gXCZLi9PvkpRSVRrASDOZwcjoU/Kvww163vBUVb2cOZfFhyn6o2Sk88Tt++
-udH3hdjpf9i7jTtUkUe+QYPsia+wgvvrmn4QrahLAH86+kECQQDx5gFeXTME3cnW
-WMpFz3PPumduzjqgqMMWEccX4FtQkMX/gyGa5UC7OHFyh0N/gSWvPbRHa8A6YgIt
-n8DO+fh5AkEAzbqX4DOn8NY6xJIi42q7l/2jIA0RkB6P7YugW5NblhqBZ0XDnpA5
-sMt+rz+K07u9XZtxgh1xi7mNfwY6lEAMqQJBAJBEauCKmRj35Z6OyeQku59SPsnY
-+SJEREVvSNw2lH9SOKQQ4wPsYlTGbvKtNVZgAcen91L5MmYfeckYE/fdIZECQQCt
-64zxsTnM1I8iFxj/gP/OYlJBikrKt8udWmjaghzvLMEw+T2DExJyb9ZNeT53+UMB
-m6O+B/4xzU/djvp+0hbhAkAemIt+rA5kTmYlFndhpvzkSSM8a2EXsO4XIPgGWCTT
-tQKS/tTly0ADMjN/TVy11+9d6zcqadNVuHXHGtR4W0GR
------END RSA PRIVATE KEY-----
-
diff --git a/lib/ssh/test/ssh_renegotiate_SUITE_data/ssh_host_rsa_key.pub b/lib/ssh/test/ssh_renegotiate_SUITE_data/ssh_host_rsa_key.pub
deleted file mode 100644
index 75d2025c71..0000000000
--- a/lib/ssh/test/ssh_renegotiate_SUITE_data/ssh_host_rsa_key.pub
+++ /dev/null
@@ -1,5 +0,0 @@
----- BEGIN SSH2 PUBLIC KEY ----
-AAAAB3NzaC1yc2EAAAADAQABAAAAgQDCZX+4FBDwZIh9y/Uxee1VJnEXlowpz2yDKwj8
-semM4q843337zbNfxHmladB1lpz2NqyxI175xMIJuDxogyZdsOxGnFAzAnthR4dqL/RW
-RWzjaxSB6IAO9SPYVVlrpZ+1hsjLW79fwXK/yc8VdhRuWTeQiRgYY2ek8+OKbOqz4Q==
----- END SSH2 PUBLIC KEY ----
-- 
2.16.3

openSUSE Build Service is sponsored by