File 2881-ssh-test-Don-t-test-_every_-algorithm-on-renegotiati.patch of Package erlang
From 0e47ec26ebfcdb32d8e6f82e53189c35ad71de71 Mon Sep 17 00:00:00 2001
From: Hans Nilsson <hans@erlang.org>
Date: Mon, 25 May 2020 17:42:07 +0200
Subject: [PATCH 1/2] ssh/test: Don't test _every_ algorithm on renegotiation
with otp as server
Change test case
all_algorithms_sftp_exec_reneg_otp_is_server
to
renegotiation_otp_is_server
---
lib/ssh/test/ssh_compat_SUITE.erl | 168 ++++++++++++++++++++----------
lib/ssh/test/ssh_test_lib.erl | 4 +-
2 files changed, 115 insertions(+), 57 deletions(-)
diff --git a/lib/ssh/test/ssh_compat_SUITE.erl b/lib/ssh/test/ssh_compat_SUITE.erl
index f5f0a35bac..b1fa138716 100644
--- a/lib/ssh/test/ssh_compat_SUITE.erl
+++ b/lib/ssh/test/ssh_compat_SUITE.erl
@@ -53,7 +53,7 @@ groups() ->
send_recv_big_with_renegotiate_otp_is_client
]},
{otp_server, [], [login_otp_is_server,
- all_algorithms_sftp_exec_reneg_otp_is_server
+ renegotiation_otp_is_server
]} |
[{G, [], [{group,otp_client}, {group,otp_server}]} || G <- ssh_image_versions()]
].
@@ -292,46 +292,57 @@ all_algorithms_sftp_exec_reneg_otp_is_client(Config) ->
end).
%%--------------------------------------------------------------------
-all_algorithms_sftp_exec_reneg_otp_is_server(Config) ->
- CommonAlgs = proplists:get_value(common_remote_client_algs, Config),
- UserDir = setup_remote_priv_and_local_auth_keys('ssh-rsa', Config),
- chk_all_algos(?FUNCTION_NAME, CommonAlgs, Config,
- fun(Tag,Alg) ->
- HostKeyAlg = case Tag of
- public_key -> Alg;
- _ -> 'ssh-rsa'
- end,
- PrefAlgs =
- [{T,L} || {T,L} <- ssh_transport:supported_algorithms(),
- T =/= Tag],
- SftpRootDir = new_dir(Config),
- %% ct:log("Rootdir = ~p",[SftpRootDir]),
- {Server, Host, HostPort} =
- ssh_test_lib:daemon(0,
- [{preferred_algorithms, [{Tag,[Alg]} | PrefAlgs]},
- {system_dir, setup_local_hostdir(HostKeyAlg, Config)},
- {user_dir, UserDir},
- {user_passwords, [{?USER,?PASSWD}]},
- {failfun, fun ssh_test_lib:failfun/2},
- {subsystems,
- [ssh_sftpd:subsystem_spec([{cwd,SftpRootDir},
- {root,SftpRootDir}]),
- {"echo_10",{ssh_echo_server,[10,[{dbg,true}]]}}
- ]}
- ]),
- R = do([fun() ->
- exec_from_docker(Config, Host, HostPort,
- "hi_there.\r\n",
- [<<"hi_there">>],
- "")
- end,
- fun() ->
- sftp_tests_erl_server(Config, Host, HostPort, SftpRootDir, UserDir)
- end
- ]),
- ssh:stop_daemon(Server),
- R
- end).
+renegotiation_otp_is_server(Config) ->
+ PublicKeyAlgs = [A || {public_key,A} <- proplists:get_value(common_remote_client_algs, Config, [])],
+ UserDir = setup_remote_priv_and_local_auth_keys(hd(PublicKeyAlgs), Config),
+ SftpRootDir = new_dir(Config),
+ ct:log("Rootdir = ~p",[SftpRootDir]),
+ Parent = self(),
+ Ref = make_ref(),
+ {Server, Host, Port} =
+ ssh_test_lib:daemon(0,
+ [{system_dir, setup_local_hostdir(Config)},
+ {user_dir, UserDir},
+ {user_passwords, [{?USER,?PASSWD}]},
+ {failfun, fun ssh_test_lib:failfun/2},
+ {connectfun,
+ fun(_,_,_) ->
+ HostConnRef = self(),
+ reneg_tester(Parent, Ref, HostConnRef),
+ ct:log("Connected ~p",[HostConnRef]),
+ timer:sleep(1100), % Just a bit more than 1 s
+ ok
+ end},
+ {subsystems,
+ [ssh_sftpd:subsystem_spec([{cwd,SftpRootDir},
+ {root,SftpRootDir}])
+ ]}
+ ]),
+ case sftp_tests_erl_server(Config, Host, Port, SftpRootDir, UserDir, Ref) of
+ ok ->
+ ssh:stop_daemon(Server);
+ {error,Error} ->
+ ssh:stop_daemon(Server),
+ ct:log("Error: ~p", [Error]),
+ {fail, Error}
+ end.
+
+
+reneg_tester(Parent, Ref, HostConnRef) ->
+ spawn(fun() ->
+ reneg_tester_loop(Parent, Ref, HostConnRef, renegotiate_test(init,HostConnRef))
+ end).
+
+reneg_tester_loop(Parent, Ref, HostConnRef, Kex1) ->
+ case ssh_test_lib:get_kex_init(HostConnRef) of
+ Kex1 ->
+ timer:sleep(500),
+ reneg_tester_loop(Parent, Ref, HostConnRef, Kex1);
+ _OtherKex ->
+ ct:log("Kex is changed.", []),
+ Parent ! {kex_changed, Ref}
+ end.
+
%%--------------------------------------------------------------------
send_recv_big_with_renegotiate_otp_is_client(Config) ->
@@ -593,6 +604,24 @@ do([], _) ->
%% Functions to set up local and remote host's and user's keys and directories
%%
+setup_local_hostdir(Config) ->
+ KeyAlgs = lists:usort(
+ [A || From <- [common_remote_client_algs,
+ common_remote_server_algs],
+ {public_key,A} <- proplists:get_value(From, Config, [])]),
+ setup_local_hostdirs(KeyAlgs, new_dir(Config), Config).
+
+
+setup_local_hostdirs(KeyAlgs, Config) ->
+ setup_local_hostdirs(KeyAlgs, new_dir(Config), Config).
+setup_local_hostdirs(KeyAlgs, HostDir, Config) ->
+ lists:foreach(
+ fun(KeyAlg) ->
+ setup_local_hostdir(KeyAlg, HostDir, Config)
+ end, KeyAlgs),
+ HostDir.
+
+
setup_local_hostdir(KeyAlg, Config) ->
setup_local_hostdir(KeyAlg, new_dir(Config), Config).
setup_local_hostdir(KeyAlg, HostDir, Config) ->
@@ -1126,14 +1155,18 @@ receive_kexinit(S, Ack) ->
%%% Test of sftp from the OpenSSH client side
%%%
-sftp_tests_erl_server(Config, ServerIP, ServerPort, ServerRootDir, UserDir) ->
+sftp_tests_erl_server(Config, ServerIP, ServerPort, ServerRootDir, UserDir, Ref) ->
try
Cmnds = prepare_local_directory(ServerRootDir),
- call_sftp_in_docker(Config, ServerIP, ServerPort, Cmnds, UserDir),
- check_local_directory(ServerRootDir)
+ case call_sftp_in_docker(Config, ServerIP, ServerPort, Cmnds, UserDir, Ref) of
+ ok ->
+ check_local_directory(ServerRootDir);
+ {error,Error} ->
+ {error,Error}
+ end
catch
- Class:Error:ST ->
- {error, {Class,Error,ST}}
+ Class:Excep:ST ->
+ {error, {Class,Excep,ST}}
end.
@@ -1206,8 +1239,9 @@ do_check_local_directory(ServerRootDir) ->
end.
-call_sftp_in_docker(Config, ServerIP, ServerPort, Cmnds, UserDir) ->
+call_sftp_in_docker(Config, ServerIP, ServerPort, Cmnds, UserDir, Ref) ->
{DockerIP,DockerPort} = ip_port(Config),
+ ct:log("Going to connect ~p:~p", [DockerIP, DockerPort]),
{ok,C} = ssh:connect(DockerIP, DockerPort,
[{user,?USER},
{password,?PASSWD},
@@ -1225,7 +1259,7 @@ call_sftp_in_docker(Config, ServerIP, ServerPort, Cmnds, UserDir) ->
PostExpectCmnds= [],
ExpectCmnds =
PreExpectCmnds ++
- ["expect \"sftp>\" {send \""++Cmnd++"\n\"}\n" || Cmnd <- Cmnds] ++
+ ["expect \"sftp>\" {sleep 1; send \""++Cmnd++"\n\"}\n" || Cmnd <- Cmnds] ++
PostExpectCmnds,
%% Make an commands file in the docker
@@ -1235,14 +1269,30 @@ call_sftp_in_docker(Config, ServerIP, ServerPort, Cmnds, UserDir) ->
%% Call expect in the docker
{ok, Ch1} = ssh_connection:session_channel(C, infinity),
- Kex1 = renegotiate_test(init, C),
+ ct:log("Going to execute 'expect commands' in docker", []),
success = ssh_connection:exec(C, Ch1, "expect commands", infinity),
+ ct:log("'expect commands' in docker executed!", []),
+ case recv_log_msgs(C, Ch1) of
+ ok ->
+ receive
+ {kex_changed, Ref} ->
+ %% success
+ ct:log("Kex changed",[]),
+ ssh:close(C),
+ ok
+ after
+ 30000 ->
+ %% failure
+ ct:log("Kex NOT changed",[]),
+ ssh:close(C),
+ {error,"Kex NOT changed"}
+ end;
- renegotiate_test(Kex1, C),
- recv_log_msgs(C, Ch1),
+ {error,Error} ->
+ ssh:close(C),
+ {error,Error}
+ end.
- %% Done.
- ssh:close(C).
recv_log_msgs(C, Ch) ->
receive
@@ -1255,6 +1305,12 @@ recv_log_msgs(C, Ch) ->
{ssh_cm,C,_Msg} ->
%% ct:log("Got ~p",[_Msg]),
recv_log_msgs(C, Ch)
+ after
+ 30000 ->
+ %% failure
+ ct:log("Exec Channel ~p in ~p NOT closed properly", [Ch,C]),
+ ssh:close(C),
+ {error,"Exec channel NOT closed"}
end.
%%%----------------------------------------------------------------
@@ -1319,7 +1375,7 @@ one_test_erl_client(exec, Id, C) ->
{eof,<<"Hi there\n">>} ->
ok;
Other ->
- ct:pal("exec Got other ~p", [Other]),
+ ct:log("exec Got other ~p", [Other]),
{error, {exec,Id,bad_msg,Other,undefined}}
end;
@@ -1329,7 +1385,7 @@ one_test_erl_client(no_subsyst, Id, C) ->
failure ->
ok;
Other ->
- ct:pal("no_subsyst Got other ~p", [Other]),
+ ct:log("no_subsyst Got other ~p", [Other]),
{error, {no_subsyst,Id,bad_ret,Other,undefined}}
end;
@@ -1357,7 +1413,7 @@ one_test_erl_client(setenv, Id, C) ->
{eof,Env} ->
ok;
Other ->
- ct:pal("setenv Got other ~p", [Other]),
+ ct:log("setenv Got other ~p", [Other]),
{error, {setenv,Id,bad_msg,Other,undefined}}
end;
diff --git a/lib/ssh/test/ssh_test_lib.erl b/lib/ssh/test/ssh_test_lib.erl
index f16c0d6278..2645c956cf 100644
--- a/lib/ssh/test/ssh_test_lib.erl
+++ b/lib/ssh/test/ssh_test_lib.erl
@@ -728,12 +728,14 @@ get_kex_init(Conn, Ref, TRef) ->
end;
false ->
- ct:log("~p:~p Not in 'connected' state: ~p",[?MODULE,?LINE,State]),
receive
{reneg_timeout,Ref} ->
+ ct:log("~p:~p Not in 'connected' state: ~p but reneg_timeout received. Fail.",
+ [?MODULE,?LINE,State]),
ct:log("S = ~p", [S]),
ct:fail(reneg_timeout)
after 0 ->
+ ct:log("~p:~p Not in 'connected' state: ~p, Will try again after 100ms",[?MODULE,?LINE,State]),
timer:sleep(100), % If renegotiation is complete we do not
% want to exit on the reneg_timeout
get_kex_init(Conn, Ref, TRef)
--
2.26.2