File 4485-ssh-alive-renegotation-fix-and-tests.patch of Package erlang
From fed3db36a538f63380e1ef88b783a59613a64bbb Mon Sep 17 00:00:00 2001
From: Jakub Witczak <kuba@erlang.org>
Date: Wed, 22 Oct 2025 15:29:18 +0200
Subject: [PATCH 15/20] ssh: alive renegotation fix and tests
---
lib/ssh/src/ssh_connection_handler.erl | 21 +-
lib/ssh/src/ssh_info.erl | 11 +-
lib/ssh/test/ssh_protocol_SUITE.erl | 375 +++++++++++++------------
lib/ssh/test/ssh_trpt_test_lib.erl | 20 +-
4 files changed, 238 insertions(+), 189 deletions(-)
diff --git a/lib/ssh/src/ssh_connection_handler.erl b/lib/ssh/src/ssh_connection_handler.erl
index 99de76a134..77acaa9781 100644
--- a/lib/ssh/src/ssh_connection_handler.erl
+++ b/lib/ssh/src/ssh_connection_handler.erl
@@ -727,7 +727,11 @@ handle_event(internal, {#ssh_msg_kexinit{},_}, {connected,Role}, D0) ->
D = D0#data{ssh_params = Ssh,
key_exchange_init_msg = KeyInitMsg},
send_bytes(SshPacket, D),
- {next_state, {kexinit,Role,renegotiate}, D, [postpone, {change_callback_module,ssh_fsm_kexinit}]};
+ {next_state, {kexinit,Role,renegotiate}, D,
+ [postpone,
+ {change_callback_module,ssh_fsm_kexinit},
+ {{timeout, alive}, cancel},
+ {{timeout, renegotiation_alive}, renegotiation_alive_timeout(Ssh), none}]};
handle_event(internal, #ssh_msg_disconnect{description=Desc} = Msg, StateName, D0) ->
{disconnect, _, RepliesCon} =
@@ -2258,6 +2262,7 @@ ssh_dbg_flags(disconnect) -> [c].
ssh_dbg_on(alive) ->
dbg:tp(?MODULE, handle_event, 4, x),
dbg:tpl(?MODULE, init_ssh_record, 4, x),
+ dbg:tpl(?MODULE, start_rekeying, 2, x),
dbg:tpl(?MODULE, triggered_alive, 4, x);
ssh_dbg_on(connections) -> dbg:tp(?MODULE, init, 1, x),
ssh_dbg_on(terminate);
@@ -2282,6 +2287,7 @@ ssh_dbg_on(disconnect) -> dbg:tpl(?MODULE, send_disconnect, 7, x).
ssh_dbg_off(alive) ->
dbg:ctpg(?MODULE, handle_event, 4),
+ dbg:ctpl(?MODULE, start_rekeying, 2),
dbg:ctpl(?MODULE, init_ssh_record, 4),
dbg:ctpl(?MODULE, triggered_alive, 4);
ssh_dbg_off(disconnect) -> dbg:ctpl(?MODULE, send_disconnect, 7);
@@ -2327,9 +2333,20 @@ ssh_dbg_format(alive, {call, {?MODULE,F=triggered_alive,
ssh_dbg_format(alive, {return_from, {?MODULE, F=triggered_alive, 4}, {stop, Details, _}}) ->
Str = io_lib:format("~n0 alive probes left {stop, ~p, _}", [Details]),
?PRINT_ALIVE_EVENT(?MODULE, F, 4, Str);
+ssh_dbg_format(alive, {return_from, {?MODULE, Function, Arity},
+ _Return = {next_state, {kexinit, _Role_, renegotiate}, _, Actions}})
+ when (Function == handle_event andalso Arity == 4) orelse
+ (Function == start_rekeying andalso Arity == 2)->
+ case lists:keyfind({timeout, renegotiation_alive}, 1, Actions) of
+ false ->
+ skip;
+ {{timeout, renegotiation_alive}, Timeout, _} ->
+ Str = io_lib:format("~nRenegotiation timeout set to ~p ms", [Timeout]),
+ ?PRINT_ALIVE_EVENT(?MODULE, Function, Arity, Str)
+ end;
ssh_dbg_format(alive, {call, {?MODULE, _, _}}) ->
skip;
-ssh_dbg_format(alive, {return_from, {?MODULE, _, _}, _Ret}) ->
+ssh_dbg_format(alive, {return_from, {?MODULE, _, _}, _Return}) ->
skip;
ssh_dbg_format(connections, {call, {?MODULE,init, [[Role, Sock, Opts]]}}) ->
diff --git a/lib/ssh/src/ssh_info.erl b/lib/ssh/src/ssh_info.erl
index 50b1eb2711..4eaa7ed925 100644
--- a/lib/ssh/src/ssh_info.erl
+++ b/lib/ssh/src/ssh_info.erl
@@ -30,7 +30,8 @@
-export([print/0,
print/1,
- string/0
+ string/0,
+ get_subs_tree/1
]).
-include("ssh.hrl").
@@ -66,6 +67,10 @@ string() ->
io_lib:format("Ssh not found~n",[])
end.
+get_subs_tree(StartPid) ->
+ lists:foldl(fun({Id,_,worker,_}=C, Acc) -> [{C,chspec(StartPid,Id)}|Acc];
+ ({Id,Pid,supervisor,_}=C, Acc) -> [{C,chspec(StartPid,Id),get_subs_tree(Pid)}|Acc]
+ end, [], children(StartPid)).
%%%================================================================
-define(inc(N), (N+4)).
@@ -82,10 +87,6 @@ print_sups(Role, StartPid) ->
walk_tree(Role, get_subs_tree(StartPid)).
%%%================================================================
-get_subs_tree(StartPid) ->
- lists:foldl(fun({Id,_,worker,_}=C, Acc) -> [{C,chspec(StartPid,Id)}|Acc];
- ({Id,Pid,supervisor,_}=C, Acc) -> [{C,chspec(StartPid,Id),get_subs_tree(Pid)}|Acc]
- end, [], children(StartPid)).
chspec(Sup, Id) ->
try supervisor:get_childspec(Sup, Id)
diff --git a/lib/ssh/test/ssh_protocol_SUITE.erl b/lib/ssh/test/ssh_protocol_SUITE.erl
index 4243e61874..9b339e8fd2 100644
--- a/lib/ssh/test/ssh_protocol_SUITE.erl
+++ b/lib/ssh/test/ssh_protocol_SUITE.erl
@@ -60,11 +60,10 @@
empty_service_name/1,
ext_info_c/1,
ext_info_s/1,
- keep_alive_sent/1,
- keep_alive_maxcount_exceeded/1,
- keep_alive_renegotiate_timeout/1,
- keep_alive_sent_server/1,
- keep_alive_maxcount_exceeded_server/1,
+ alive_eserver_tclient/1,
+ alive_tserver_eclient/1,
+ alive_reneg_eserver_tclient/1,
+ alive_reneg_tserver_eclient/1,
kex_strict_negotiated/1,
kex_strict_violation_key_exchange/1,
kex_strict_violation_new_keys/1,
@@ -144,7 +143,7 @@ all() ->
{group,preferred_algorithms},
{group,client_close_early},
{group,channel_close},
- {group,keep_alive}
+ {group,alive}
].
groups() ->
@@ -197,13 +196,10 @@ groups() ->
]},
{client_close_early, [], [client_close_after_hello]},
{channel_close, [], [channel_close_timeout]},
- {keep_alive, [], [keep_alive_sent,
- keep_alive_maxcount_exceeded,
- keep_alive_renegotiate_timeout,
- keep_alive_sent_server,
- keep_alive_maxcount_exceeded_server]}
- ].
-
+ {alive, [], [alive_eserver_tclient,
+ alive_tserver_eclient,
+ alive_reneg_eserver_tclient,
+ alive_reneg_tserver_eclient]}].
init_per_suite(Config) ->
?CHECK_CRYPTO(start_std_daemon( setup_dirs( start_apps(Config)))).
@@ -1506,7 +1502,7 @@ extra_ssh_msg_service_request(Config) ->
], EndState),
ok.
-keep_alive_sent(Config) ->
+alive_eserver_tclient(Config) ->
User = "foo",
Pwd = "morot",
UserDir = user_dir(Config),
@@ -1514,10 +1510,9 @@ keep_alive_sent(Config) ->
{user_dir, UserDir},
{password, Pwd},
{failfun, fun ssh_test_lib:failfun/2},
- {alive_params, {1,1}}]),
-
+ {alive_params, {3,1}}]),
{ok,AfterUserAuthReqState} = connect_and_userauth_request(Host, Port, User, Pwd, UserDir),
- {ok,EndState} =
+ {ok, AliveOkState} =
ssh_trpt_test_lib:exec(
[{match, #ssh_msg_userauth_success{_='_'}, receive_msg},
{match, #ssh_msg_global_request{name = <<"keepalive@erlang.org">>,
@@ -1528,31 +1523,15 @@ keep_alive_sent(Config) ->
want_reply = true,
data = <<>>}, receive_msg},
%% Send success just to check that it works as well
- {send, #ssh_msg_request_success{data = <<>>}},
- {match, #ssh_msg_global_request{name = <<"keepalive@erlang.org">>,
- want_reply = true,
- data = <<>>}, receive_msg}
+ {send, #ssh_msg_request_success{data = <<>>}}
], AfterUserAuthReqState),
-
- {ok,_} = trpt_test_lib_send_disconnect(EndState),
-
- ssh:stop_daemon(Pid),
- Config.
-
-keep_alive_maxcount_exceeded(Config) ->
- User = "foo",
- Pwd = "morot",
- UserDir = user_dir(Config),
- {Pid, Host, Port} = ssh_test_lib:daemon([{system_dir, system_dir(Config)},
- {user_dir, UserDir},
- {password, Pwd},
- {failfun, fun ssh_test_lib:failfun/2},
- {alive_params, {2,1}}]),
-
- {ok,AfterUserAuthReqState} = connect_and_userauth_request(Host, Port, User, Pwd, UserDir),
- {ok,EndState} =
+ ?CT_LOG("[OK] Alive feature - normal conditions"),
+ {ok, _} =
ssh_trpt_test_lib:exec(
- [{match, #ssh_msg_userauth_success{_='_'}, receive_msg},
+ [
+ {match, #ssh_msg_global_request{name = <<"keepalive@erlang.org">>,
+ want_reply = true,
+ data = <<>>}, receive_msg},
{match, #ssh_msg_global_request{name = <<"keepalive@erlang.org">>,
want_reply = true,
data = <<>>}, receive_msg},
@@ -1560,89 +1539,25 @@ keep_alive_maxcount_exceeded(Config) ->
want_reply = true,
data = <<>>}, receive_msg},
{match, #ssh_msg_disconnect{_='_'}, receive_msg}
- ], AfterUserAuthReqState),
-
- {ok,_} = trpt_test_lib_send_disconnect(EndState),
-
+ ], AliveOkState),
+ ?CT_LOG("[OK] Alive feature - maxcount exceeded"),
ssh:stop_daemon(Pid),
- Config.
-
-keep_alive_renegotiate_timeout(Config) ->
- %% User = "foo",
- %% Pwd = "morot",
- %% UserDir = user_dir(Config),
- %% {Pid, Host, Port} = ssh_test_lib:daemon([{system_dir, system_dir(Config)},
- %% {user_dir, UserDir},
- %% {password, Pwd},
- %% {failfun, fun ssh_test_lib:failfun/2},
- %% {alive_params, {2,2}}]),
-
- %% {ok,AfterUserAuthReqState} = connect_and_userauth_request(Host, Port, User, Pwd, UserDir),
- %% {ok,EndState} =
- %% ssh_trpt_test_lib:exec(
- %% [{match, #ssh_msg_userauth_success{_='_'}, receive_msg},
- %% {match, #ssh_msg_global_request{name = <<"keepalive@erlang.org">>,
- %% want_reply = true,
- %% data = <<>>}, receive_msg},
- %% {send, #ssh_msg_request_failure{}},
- %% {send, ssh_msg_kexinit},
- %% {match, #ssh_msg_global_request{name = <<"keepalive@erlang.org">>,
- %% want_reply = true,
- %% data = <<>>}, receive_msg}
- %% ], AfterUserAuthReqState),
-
- %% {ok,_} = trpt_test_lib_send_disconnect(EndState),
-
- %% ssh:stop_daemon(Pid),
-
- %%% TODO: figure out why ssh_msg_kexinit can't be decoded by the server
- Config.
-
-keep_alive_sent_server(Config) ->
- {User,_Pwd} = server_user_password(Config),
+ ok.
+alive_tserver_eclient(Config) ->
%% Create a listening socket as server socket:
- {ok,InitialState} = ssh_trpt_test_lib:exec(listen),
+ {ok, InitialState} = ssh_trpt_test_lib:exec(listen),
HostPort = ssh_trpt_test_lib:server_host_port(InitialState),
-
Parent = self(),
%% Start a process handling one connection on the server side:
Pid = spawn_link(
fun() ->
- Result =
+ ConnectedState =
ssh_trpt_test_lib:exec(
- [{set_options, [print_ops, print_messages]},
- {accept, [{system_dir, system_dir(Config)},
- {user_dir, user_dir(Config)}]},
- receive_hello,
- {send, hello},
-
- {send, ssh_msg_kexinit},
- {match, #ssh_msg_kexinit{_='_'}, receive_msg},
-
- {match, #ssh_msg_kexdh_init{_='_'}, receive_msg},
- {send, ssh_msg_kexdh_reply},
-
- {send, #ssh_msg_newkeys{}},
- {match, #ssh_msg_newkeys{_='_'}, receive_msg},
-
- {match, #ssh_msg_service_request{name="ssh-userauth"}, receive_msg},
- {send, #ssh_msg_service_accept{name="ssh-userauth"}},
-
- {match, #ssh_msg_userauth_request{service="ssh-connection",
- method="none",
- user=User,
- _='_'}, receive_msg},
-
- {send, #ssh_msg_userauth_failure{authentications = "password",
- partial_success = false}},
-
- {match, #ssh_msg_userauth_request{service="ssh-connection",
- method="password",
- user=User,
- _='_'}, receive_msg},
- {send, #ssh_msg_userauth_success{}},
- %% Keep-alive matching
+ connect_and_userauth_server(Config), InitialState),
+ AliveOkState =
+ ssh_trpt_test_lib:exec(
+ [%% Keep-alive matching
{match, #ssh_msg_global_request{name = <<"keepalive@erlang.org">>,
want_reply = true,
data = <<>>}, receive_msg},
@@ -1651,103 +1566,182 @@ keep_alive_sent_server(Config) ->
want_reply = true,
data = <<>>}, receive_msg},
%% Send success just to check that it works as well
- {send, #ssh_msg_request_success{data = <<>>}},
+ {send, #ssh_msg_request_success{data = <<>>}}],
+ ConnectedState),
+ ?CT_LOG("[OK] Alive feature - normal conditions"),
+ AliveNokState =
+ ssh_trpt_test_lib:exec(
+ [%% Keep-alive matching
+ {match, #ssh_msg_global_request{name = <<"keepalive@erlang.org">>,
+ want_reply = true,
+ data = <<>>}, receive_msg},
+ {match, #ssh_msg_global_request{name = <<"keepalive@erlang.org">>,
+ want_reply = true,
+ data = <<>>}, receive_msg},
{match, #ssh_msg_global_request{name = <<"keepalive@erlang.org">>,
want_reply = true,
data = <<>>}, receive_msg},
- close_socket,
- print_state
- ],
- InitialState),
- Parent ! {result, self(), Result}
+ {match, #ssh_msg_disconnect{_='_'}, receive_msg}],
+ AliveOkState),
+ ?CT_LOG("[OK] Alive feature - max_count exceeded"),
+ Parent ! {result, self(), AliveNokState}
end),
-
%% and finally connect to it with a regular Erlang SSH client:
{ok,_} = std_connect(HostPort, Config,
[{preferred_algorithms,[{kex,[?DEFAULT_KEX]},
{cipher,?DEFAULT_CIPHERS}
]},
- {alive_params, {1,1}}
+ {alive_params, {3,1}}
]
),
%% Check that the daemon got expected result:
receive
{result, Pid, {ok,_}} -> ok;
- {result, _Pid, Error} -> ct:fail("Error: ~p",[Error])
+ {result, Pid, Error} -> ct:fail("Error: ~p",[Error])
end.
-keep_alive_maxcount_exceeded_server(Config) ->
- {User,_Pwd} = server_user_password(Config),
+alive_reneg_eserver_tclient(Config) ->
+ User = "foo",
+ Pwd = "morot",
+ UserDir = user_dir(Config),
+ {DaemonPid, Host, Port} = ssh_test_lib:daemon([{system_dir, system_dir(Config)},
+ {user_dir, UserDir},
+ {password, Pwd},
+ {max_log_item_len, 20000},
+ {failfun, fun ssh_test_lib:failfun/2},
+ {alive_params, {3,1}}]),
+ ?CT_LOG("[starting] Alive feature - normal conditions"),
+ {ok, TrptState0} = connect_and_userauth_request(Host, Port, User, Pwd, UserDir),
+ CheckAlive =
+ fun(State) ->
+ ssh_trpt_test_lib:exec(
+ [{match, #ssh_msg_userauth_success{_='_'}, receive_msg},
+ {match, #ssh_msg_global_request{name = <<"keepalive@erlang.org">>,
+ want_reply = true,
+ data = <<>>}, receive_msg},
+ {send, #ssh_msg_request_failure{}}],
+ State)
+ end,
+ {ok, TrptState1} = CheckAlive(TrptState0),
+ ?CT_LOG("[OK] Alive feature - normal conditions"),
+ ?CT_LOG("[starting] triggering incomplete, client triggered remotely key renegotiation"),
+ {ok, _} =
+ ssh_trpt_test_lib:exec(
+ [{send, start_incomplete_renegotiation},
+ {match, #ssh_msg_kexinit{_='_'}, receive_msg},
+ {match, disconnect(), receive_msg}],
+ TrptState1),
+ ?CT_LOG("[OK] triggering incomplete, client triggered remotely key renegotiation"),
+ ?CT_LOG("[starting] Alive feature - normal conditions 2"),
+ {ok, TrptState2} = connect_and_userauth_request(Host, Port, User, Pwd, UserDir),
+ {ok, TrptState3} = CheckAlive(TrptState2),
+ ?CT_LOG("[OK] Alive feature - normal conditions 2"),
+ ?CT_LOG("[starting] triggering incomplete, server triggered locally key renegotiation"),
+ ?CT_LOG("~n~s", [ssh_info:string()]),
+ CHandler =
+ fun F([], Acc) ->
+ lists:flatten(Acc);
+ F([{{_, CRefPid, worker, [ssh_connection_handler]}, _} | Tail], Acc) ->
+ F(Tail, [CRefPid | Acc]);
+ F([{{_, _, worker, _}, _} | Tail], Acc) ->
+ F(Tail, [Acc]);
+ F([{{_, _, supervisor, _}, _, SubTree} | Tail], Acc) ->
+ F(Tail, F(SubTree, Acc))
+ end,
+ [CHandlerPid] = CHandler(ssh_info:get_subs_tree(sshd_sup), []),
+ ?CT_LOG("Server side connection handler PID: ~p", [CHandlerPid]),
+ ssh_connection_handler:renegotiate(CHandlerPid),
+ {ok, _} =
+ ssh_trpt_test_lib:exec(
+ [{match, #ssh_msg_kexinit{_='_'}, receive_msg},
+ {match, disconnect(), receive_msg}],
+ TrptState3),
+ ?CT_LOG("[OK] triggering incomplete, server triggered locally key renegotiation"),
+ ssh:stop_daemon(DaemonPid),
+ ?CT_LOG("[OK] test case finished"),
+ ok.
+alive_reneg_tserver_eclient(Config) ->
%% Create a listening socket as server socket:
- {ok,InitialState} = ssh_trpt_test_lib:exec(listen),
- HostPort = ssh_trpt_test_lib:server_host_port(InitialState),
-
+ {ok, TrptState0} = ssh_trpt_test_lib:exec(listen),
+ HostPort0 = ssh_trpt_test_lib:server_host_port(TrptState0),
Parent = self(),
%% Start a process handling one connection on the server side:
- Pid = spawn_link(
+ TDaemonPid0 = spawn_link(
fun() ->
- Result =
+ ?CT_LOG("[starting] Alive feature - normal conditions"),
+ TrptState1 =
ssh_trpt_test_lib:exec(
- [{set_options, [print_ops, print_messages]},
- {accept, [{system_dir, system_dir(Config)},
- {user_dir, user_dir(Config)}]},
- receive_hello,
- {send, hello},
+ connect_and_userauth_server(Config), TrptState0),
+ TrptState2 =
+ ssh_trpt_test_lib:exec(
+ [{match, #ssh_msg_global_request{name = <<"keepalive@erlang.org">>,
+ want_reply = true,
+ data = <<>>}, receive_msg},
+ {send, #ssh_msg_request_failure{}}],
+ TrptState1),
+ ?CT_LOG("[OK] Alive feature - normal conditions"),
- {send, ssh_msg_kexinit},
+ ?CT_LOG("[starting] triggering incomplete, server triggered remotely key renegotiation"),
+ TrptState3 =
+ ssh_trpt_test_lib:exec(
+ [{send, start_incomplete_renegotiation},
{match, #ssh_msg_kexinit{_='_'}, receive_msg},
-
{match, #ssh_msg_kexdh_init{_='_'}, receive_msg},
- {send, ssh_msg_kexdh_reply},
-
- {send, #ssh_msg_newkeys{}},
- {match, #ssh_msg_newkeys{_='_'}, receive_msg},
-
- {match, #ssh_msg_service_request{name="ssh-userauth"}, receive_msg},
- {send, #ssh_msg_service_accept{name="ssh-userauth"}},
-
- {match, #ssh_msg_userauth_request{service="ssh-connection",
- method="none",
- user=User,
- _='_'}, receive_msg},
-
- {send, #ssh_msg_userauth_failure{authentications = "password",
- partial_success = false}},
-
- {match, #ssh_msg_userauth_request{service="ssh-connection",
- method="password",
- user=User,
- _='_'}, receive_msg},
- {send, #ssh_msg_userauth_success{}},
- %% Keep-alive matching
- {match, #ssh_msg_global_request{name = <<"keepalive@erlang.org">>,
- want_reply = true,
- data = <<>>}, receive_msg},
- {match, #ssh_msg_global_request{name = <<"keepalive@erlang.org">>,
- want_reply = true,
- data = <<>>}, receive_msg},
- {match, #ssh_msg_disconnect{_='_'}, receive_msg},
- close_socket,
- print_state
- ],
- InitialState),
- Parent ! {result, self(), Result}
+ {match, disconnect(), receive_msg}], TrptState2),
+ ?CT_LOG("[OK] triggering incomplete, server triggered remotely key renegotiation"),
+ Parent ! {result, self(), TrptState3}
end),
-
%% and finally connect to it with a regular Erlang SSH client:
- {ok,_} = std_connect(HostPort, Config,
+ {ok,_} = std_connect(HostPort0, Config,
[{preferred_algorithms,[{kex,[?DEFAULT_KEX]},
{cipher,?DEFAULT_CIPHERS}
]},
- {alive_params, {2,1}}
+ {alive_params, {3,1}}
]
),
%% Check that the daemon got expected result:
receive
- {result, Pid, {ok,_}} -> ok;
- {result, _Pid, Error} -> ct:fail("Error: ~p",[Error])
- end.
+ {result, TDaemonPid0, {ok,_}} -> ok;
+ {result, TDaemonPid0, Error0} -> ct:fail("Error: ~p",[Error0])
+ end,
+
+ %% Create a listening socket as server socket:
+ {ok, TrptState4} = ssh_trpt_test_lib:exec(listen),
+ HostPort1 = ssh_trpt_test_lib:server_host_port(TrptState4),
+ %% Start a process handling one connection on the server side:
+ TDaemonPid1 = spawn_link(
+ fun() ->
+ ?CT_LOG("[starting] Alive feature - normal conditions 2"),
+ TrptState5 =
+ ssh_trpt_test_lib:exec(
+ connect_and_userauth_server(Config), TrptState4),
+ ?CT_LOG("[OK] Alive feature - normal conditions 2"),
+ ?CT_LOG("[starting] triggering incomplete, client triggered locally key renegotiation"),
+ TrptState6 =
+ ssh_trpt_test_lib:exec(
+ [{match, #ssh_msg_kexinit{_='_'}, receive_msg},
+ {match, disconnect(), receive_msg}
+ ], TrptState5),
+ ?CT_LOG("[OK] triggering incomplete, client triggered locally key renegotiation"),
+ Parent ! {result, self(), TrptState6}
+ end),
+ %% and finally connect to it with a regular Erlang SSH client:
+ {ok, CHandlerPid} = std_connect(HostPort1, Config,
+ [{preferred_algorithms,[{kex,[?DEFAULT_KEX]},
+ {cipher,?DEFAULT_CIPHERS}
+ ]},
+ {alive_params, {3,1}}]),
+ ?CT_LOG("~n~s", [ssh_info:string()]),
+ ?CT_LOG("Client side connection handler PID: ~p", [CHandlerPid]),
+ ssh_connection_handler:renegotiate(CHandlerPid),
+ %% Check that the daemon got expected result:
+ receive
+ {result, TDaemonPid1, {ok,_}} -> ok;
+ {result, TDaemonPid1, Error1} -> ct:fail("Error: ~p",[Error1])
+ end,
+ ?CT_LOG("[OK] test case finished"),
+ ok.
%%%================================================================
%%%==== Internal functions ========================================
@@ -2042,3 +2036,30 @@ trpt_test_lib_send_disconnect(State) ->
}},
close_socket
], State).
+
+connect_and_userauth_server(Config) ->
+ {User,_Pwd} = server_user_password(Config),
+ [{set_options, [print_ops, print_messages]},
+ {accept, [{system_dir, system_dir(Config)},
+ {user_dir, user_dir(Config)}]},
+ receive_hello,
+ {send, hello},
+ {send, ssh_msg_kexinit},
+ {match, #ssh_msg_kexinit{_='_'}, receive_msg},
+ {match, #ssh_msg_kexdh_init{_='_'}, receive_msg},
+ {send, ssh_msg_kexdh_reply},
+ {send, #ssh_msg_newkeys{}},
+ {match, #ssh_msg_newkeys{_='_'}, receive_msg},
+ {match, #ssh_msg_service_request{name="ssh-userauth"}, receive_msg},
+ {send, #ssh_msg_service_accept{name="ssh-userauth"}},
+ {match, #ssh_msg_userauth_request{service="ssh-connection",
+ method="none",
+ user=User,
+ _='_'}, receive_msg},
+ {send, #ssh_msg_userauth_failure{authentications = "password",
+ partial_success = false}},
+ {match, #ssh_msg_userauth_request{service="ssh-connection",
+ method="password",
+ user=User,
+ _='_'}, receive_msg},
+ {send, #ssh_msg_userauth_success{}}].
diff --git a/lib/ssh/test/ssh_trpt_test_lib.erl b/lib/ssh/test/ssh_trpt_test_lib.erl
index 3b39285aea..992e20867a 100644
--- a/lib/ssh/test/ssh_trpt_test_lib.erl
+++ b/lib/ssh/test/ssh_trpt_test_lib.erl
@@ -336,6 +336,10 @@ send(S0, ssh_msg_kexinit) ->
{Msg, _Bytes, _C0} = ssh_transport:key_exchange_init_msg(S0#s.ssh),
send(S0, Msg);
+send(S0, start_incomplete_renegotiation) ->
+ {_Msg, Bytes, Ssh} = ssh_transport:key_exchange_init_msg(S0#s.ssh),
+ send(S0#s{ssh = Ssh}, Bytes);
+
send(S0, ssh_msg_ignore) ->
Msg = #ssh_msg_ignore{data = "unexpected_ignore_message"},
send(S0, Msg);
@@ -483,9 +487,15 @@ recv(S0 = #s{}) ->
{undefined,_} ->
fail("2 kexint received!!", S);
-
{OwnMsg, _} ->
- try ssh_transport:handle_kexinit_msg(PeerMsg, OwnMsg, S#s.ssh, init) of
+ ReNeg =
+ case S#s.alg of
+ undefined ->
+ init;
+ _ ->
+ renegotiate
+ end,
+ try ssh_transport:handle_kexinit_msg(PeerMsg, OwnMsg, S#s.ssh, ReNeg) of
{ok,C} when ?role(S) == server ->
S#s{alg_neg = {OwnMsg, PeerMsg},
alg = C#ssh.algorithms,
@@ -494,9 +504,9 @@ recv(S0 = #s{}) ->
S#s{alg_neg = {OwnMsg, PeerMsg},
alg = C#ssh.algorithms}
catch
- Class:Exc ->
- save_prints({"Algorithm negotiation failed at line ~p:~p~n~p:~s~nPeer: ~s~n Own: ~s~n",
- [?MODULE,?LINE,Class,format_msg(Exc),format_msg(PeerMsg),format_msg(OwnMsg)]},
+ Class:Exc:Stacktrace ->
+ save_prints({"Algorithm negotiation failed at line ~p:~p~n~p:~s~nPeer: ~s~n Own: ~s~nStacktrace: ~p~n",
+ [?MODULE,?LINE,Class,format_msg(Exc),format_msg(PeerMsg),format_msg(OwnMsg), Stacktrace]},
S#s{alg_neg = {OwnMsg, PeerMsg}})
end
end;
--
2.51.0