827 lines
35 KiB
Diff
827 lines
35 KiB
Diff
From ee67d46285394db95133709cef74b0c462d665aa Mon Sep 17 00:00:00 2001
|
|
From: Jakub Witczak <kuba@erlang.org>
|
|
Date: Fri, 15 Dec 2023 09:12:33 +0100
|
|
Subject: [PATCH] ssh: KEX strict
|
|
|
|
Origin: https://github.com/erlang/otp/commit/ee67d46285394db95133709cef74b0c462d665aa
|
|
|
|
- negotiate "strict KEX" OpenSSH feature
|
|
- when negotiated between peers apply strict KEX
|
|
- related tests
|
|
- print_seqnums fix in ssh_trtp test code
|
|
---
|
|
lib/ssh/src/ssh.hrl | 5 +-
|
|
lib/ssh/src/ssh_connection_handler.erl | 10 +++
|
|
lib/ssh/src/ssh_fsm_kexinit.erl | 2 +-
|
|
lib/ssh/src/ssh_transport.erl | 104 ++++++++++++++++++++-----
|
|
lib/ssh/src/ssh_transport.hrl | 4 +-
|
|
lib/ssh/test/ssh_protocol_SUITE.erl | 100 +++++++++++++++++++++---
|
|
lib/ssh/test/ssh_test_lib.erl | 52 ++++++++++++-
|
|
lib/ssh/test/ssh_to_openssh_SUITE.erl | 90 ++++++++++++++++-----
|
|
lib/ssh/test/ssh_trpt_test_lib.erl | 34 ++++----
|
|
9 files changed, 335 insertions(+), 66 deletions(-)
|
|
|
|
diff --git a/lib/ssh/src/ssh.hrl b/lib/ssh/src/ssh.hrl
|
|
index 2f6e9614577d..d667bfbcd270 100644
|
|
--- a/lib/ssh/src/ssh.hrl
|
|
+++ b/lib/ssh/src/ssh.hrl
|
|
@@ -437,6 +437,8 @@
|
|
send_ext_info, %% May send ext-info to peer
|
|
recv_ext_info, %% Expect ext-info from peer
|
|
|
|
+ kex_strict_negotiated = false,
|
|
+
|
|
algorithms, %% #alg{}
|
|
|
|
send_mac = none, %% send MAC algorithm
|
|
@@ -508,7 +510,8 @@
|
|
c_lng,
|
|
s_lng,
|
|
send_ext_info,
|
|
- recv_ext_info
|
|
+ recv_ext_info,
|
|
+ kex_strict_negotiated = false
|
|
}).
|
|
|
|
-record(ssh_pty, {c_version = "", % client version string, e.g "SSH-2.0-Erlang/4.10.5"
|
|
diff --git a/lib/ssh/src/ssh_connection_handler.erl b/lib/ssh/src/ssh_connection_handler.erl
|
|
index b2545c4db40b..7d20b94e873b 100644
|
|
--- a/lib/ssh/src/ssh_connection_handler.erl
|
|
+++ b/lib/ssh/src/ssh_connection_handler.erl
|
|
@@ -701,6 +701,16 @@ handle_event(internal, #ssh_msg_disconnect{description=Desc} = Msg, StateName, D
|
|
disconnect_fun("Received disconnect: "++Desc, D),
|
|
{stop_and_reply, {shutdown,Desc}, Actions, D};
|
|
|
|
+handle_event(internal, #ssh_msg_ignore{}, {_StateName, _Role, init},
|
|
+ #data{ssh_params = #ssh{kex_strict_negotiated = true,
|
|
+ send_sequence = SendSeq,
|
|
+ recv_sequence = RecvSeq}}) ->
|
|
+ ?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
|
|
+ io_lib:format("strict KEX violation: unexpected SSH_MSG_IGNORE "
|
|
+ "send_sequence = ~p recv_sequence = ~p",
|
|
+ [SendSeq, RecvSeq])
|
|
+ );
|
|
+
|
|
handle_event(internal, #ssh_msg_ignore{}, _StateName, _) ->
|
|
keep_state_and_data;
|
|
|
|
diff --git a/lib/ssh/src/ssh_fsm_kexinit.erl b/lib/ssh/src/ssh_fsm_kexinit.erl
|
|
index 6ac4ec798f21..b5ae0158158a 100644
|
|
--- a/lib/ssh/src/ssh_fsm_kexinit.erl
|
|
+++ b/lib/ssh/src/ssh_fsm_kexinit.erl
|
|
@@ -58,7 +58,7 @@ callback_mode() ->
|
|
handle_event(internal, {#ssh_msg_kexinit{}=Kex, Payload}, {kexinit,Role,ReNeg},
|
|
D = #data{key_exchange_init_msg = OwnKex}) ->
|
|
Ssh1 = ssh_transport:key_init(peer_role(Role), D#data.ssh_params, Payload),
|
|
- Ssh = case ssh_transport:handle_kexinit_msg(Kex, OwnKex, Ssh1) of
|
|
+ Ssh = case ssh_transport:handle_kexinit_msg(Kex, OwnKex, Ssh1, ReNeg) of
|
|
{ok, NextKexMsg, Ssh2} when Role==client ->
|
|
ssh_connection_handler:send_bytes(NextKexMsg, D),
|
|
Ssh2;
|
|
diff --git a/lib/ssh/src/ssh_transport.erl b/lib/ssh/src/ssh_transport.erl
|
|
index e43c345130b1..12575df8aa3c 100644
|
|
--- a/lib/ssh/src/ssh_transport.erl
|
|
+++ b/lib/ssh/src/ssh_transport.erl
|
|
@@ -42,7 +42,7 @@
|
|
key_exchange_init_msg/1,
|
|
key_init/3, new_keys_message/1,
|
|
ext_info_message/1,
|
|
- handle_kexinit_msg/3, handle_kexdh_init/2,
|
|
+ handle_kexinit_msg/4, handle_kexdh_init/2,
|
|
handle_kex_dh_gex_group/2, handle_kex_dh_gex_init/2, handle_kex_dh_gex_reply/2,
|
|
handle_new_keys/2, handle_kex_dh_gex_request/2,
|
|
handle_kexdh_reply/2,
|
|
@@ -235,7 +235,6 @@ supported_algorithms(cipher) ->
|
|
same(
|
|
select_crypto_supported(
|
|
[
|
|
- {'chacha20-poly1305@openssh.com', [{ciphers,chacha20}, {macs,poly1305}]},
|
|
{'aes256-gcm@openssh.com', [{ciphers,aes_256_gcm}]},
|
|
{'aes256-ctr', [{ciphers,aes_256_ctr}]},
|
|
{'aes192-ctr', [{ciphers,aes_192_ctr}]},
|
|
@@ -243,6 +242,7 @@ supported_algorithms(cipher) ->
|
|
{'aes128-ctr', [{ciphers,aes_128_ctr}]},
|
|
{'AEAD_AES_256_GCM', [{ciphers,aes_256_gcm}]},
|
|
{'AEAD_AES_128_GCM', [{ciphers,aes_128_gcm}]},
|
|
+ {'chacha20-poly1305@openssh.com', [{ciphers,chacha20}, {macs,poly1305}]},
|
|
{'aes256-cbc', [{ciphers,aes_256_cbc}]},
|
|
{'aes192-cbc', [{ciphers,aes_192_cbc}]},
|
|
{'aes128-cbc', [{ciphers,aes_128_cbc}]},
|
|
@@ -358,7 +358,8 @@ kexinit_message(Role, Random, Algs, HostKeyAlgs, Opts) ->
|
|
#ssh_msg_kexinit{
|
|
cookie = Random,
|
|
kex_algorithms = to_strings( get_algs(kex,Algs) )
|
|
- ++ kex_ext_info(Role,Opts),
|
|
+ ++ kex_ext_info(Role,Opts)
|
|
+ ++ kex_strict_alg(Role),
|
|
server_host_key_algorithms = HostKeyAlgs,
|
|
encryption_algorithms_client_to_server = c2s(cipher,Algs),
|
|
encryption_algorithms_server_to_client = s2c(cipher,Algs),
|
|
@@ -387,10 +388,12 @@ new_keys_message(Ssh0) ->
|
|
|
|
|
|
handle_kexinit_msg(#ssh_msg_kexinit{} = CounterPart, #ssh_msg_kexinit{} = Own,
|
|
- #ssh{role = client} = Ssh) ->
|
|
+ #ssh{role = client} = Ssh, ReNeg) ->
|
|
try
|
|
- {ok, Algorithms} = select_algorithm(client, Own, CounterPart, Ssh#ssh.opts),
|
|
+ {ok, Algorithms} =
|
|
+ select_algorithm(client, Own, CounterPart, Ssh, ReNeg),
|
|
true = verify_algorithm(Algorithms),
|
|
+ true = verify_kexinit_is_first_msg(Algorithms, Ssh, ReNeg),
|
|
Algorithms
|
|
of
|
|
Algos ->
|
|
@@ -403,10 +406,12 @@ handle_kexinit_msg(#ssh_msg_kexinit{} = CounterPart, #ssh_msg_kexinit{} = Own,
|
|
end;
|
|
|
|
handle_kexinit_msg(#ssh_msg_kexinit{} = CounterPart, #ssh_msg_kexinit{} = Own,
|
|
- #ssh{role = server} = Ssh) ->
|
|
+ #ssh{role = server} = Ssh, ReNeg) ->
|
|
try
|
|
- {ok, Algorithms} = select_algorithm(server, CounterPart, Own, Ssh#ssh.opts),
|
|
+ {ok, Algorithms} =
|
|
+ select_algorithm(server, CounterPart, Own, Ssh, ReNeg),
|
|
true = verify_algorithm(Algorithms),
|
|
+ true = verify_kexinit_is_first_msg(Algorithms, Ssh, ReNeg),
|
|
Algorithms
|
|
of
|
|
Algos ->
|
|
@@ -482,6 +487,21 @@ verify_algorithm(#alg{kex = Kex}) ->
|
|
false -> {false, "kex"}
|
|
end.
|
|
|
|
+verify_kexinit_is_first_msg(#alg{kex_strict_negotiated = false}, _, _) ->
|
|
+ true;
|
|
+verify_kexinit_is_first_msg(#alg{kex_strict_negotiated = true}, _, renegotiate) ->
|
|
+ true;
|
|
+verify_kexinit_is_first_msg(#alg{kex_strict_negotiated = true},
|
|
+ #ssh{send_sequence = 1, recv_sequence = 1},
|
|
+ init) ->
|
|
+ true;
|
|
+verify_kexinit_is_first_msg(#alg{kex_strict_negotiated = true},
|
|
+ #ssh{send_sequence = SendSequence,
|
|
+ recv_sequence = RecvSequence}, init) ->
|
|
+ error_logger:warning_report(
|
|
+ lists:concat(["KEX strict violation (", SendSequence, ", ", RecvSequence, ")."])),
|
|
+ {false, "kex_strict"}.
|
|
+
|
|
%%%----------------------------------------------------------------
|
|
%%%
|
|
%%% Key exchange initialization
|
|
@@ -861,6 +881,9 @@ handle_new_keys(#ssh_msg_newkeys{}, Ssh0) ->
|
|
)
|
|
end.
|
|
|
|
+%%%----------------------------------------------------------------
|
|
+kex_strict_alg(client) -> [?kex_strict_c];
|
|
+kex_strict_alg(server) -> [?kex_strict_s].
|
|
|
|
%%%----------------------------------------------------------------
|
|
kex_ext_info(Role, Opts) ->
|
|
@@ -1082,7 +1105,35 @@ known_host_key(#ssh{opts = Opts, peer = {PeerName,{IP,Port}}} = Ssh,
|
|
%%
|
|
%% The first algorithm in each list MUST be the preferred (guessed)
|
|
%% algorithm. Each string MUST contain at least one algorithm name.
|
|
-select_algorithm(Role, Client, Server, Opts) ->
|
|
+select_algorithm(Role, Client, Server,
|
|
+ #ssh{opts = Opts,
|
|
+ kex_strict_negotiated = KexStrictNegotiated0},
|
|
+ ReNeg) ->
|
|
+ KexStrictNegotiated =
|
|
+ case ReNeg of
|
|
+ %% KEX strict negotiated once per connection
|
|
+ init ->
|
|
+ Result =
|
|
+ case Role of
|
|
+ server ->
|
|
+ lists:member(?kex_strict_c,
|
|
+ Client#ssh_msg_kexinit.kex_algorithms);
|
|
+ client ->
|
|
+ lists:member(?kex_strict_s,
|
|
+ Server#ssh_msg_kexinit.kex_algorithms)
|
|
+ end,
|
|
+ case Result of
|
|
+ true ->
|
|
+ error_logger:info_report(
|
|
+ lists:concat([Role, " will use strict KEX ordering"]));
|
|
+ _ ->
|
|
+ ok
|
|
+ end,
|
|
+ Result;
|
|
+ _ ->
|
|
+ KexStrictNegotiated0
|
|
+ end,
|
|
+
|
|
{Encrypt0, Decrypt0} = select_encrypt_decrypt(Role, Client, Server),
|
|
{SendMac0, RecvMac0} = select_send_recv_mac(Role, Client, Server),
|
|
|
|
@@ -1133,7 +1184,8 @@ select_algorithm(Role, Client, Server, Opts) ->
|
|
c_lng = C_Lng,
|
|
s_lng = S_Lng,
|
|
send_ext_info = SendExtInfo,
|
|
- recv_ext_info = RecvExtInfo
|
|
+ recv_ext_info = RecvExtInfo,
|
|
+ kex_strict_negotiated = KexStrictNegotiated
|
|
}}.
|
|
|
|
|
|
@@ -1231,7 +1283,8 @@ alg_setup(snd, SSH) ->
|
|
c_lng = ALG#alg.c_lng,
|
|
s_lng = ALG#alg.s_lng,
|
|
send_ext_info = ALG#alg.send_ext_info,
|
|
- recv_ext_info = ALG#alg.recv_ext_info
|
|
+ recv_ext_info = ALG#alg.recv_ext_info,
|
|
+ kex_strict_negotiated = ALG#alg.kex_strict_negotiated
|
|
};
|
|
|
|
alg_setup(rcv, SSH) ->
|
|
@@ -1243,22 +1296,23 @@ alg_setup(rcv, SSH) ->
|
|
c_lng = ALG#alg.c_lng,
|
|
s_lng = ALG#alg.s_lng,
|
|
send_ext_info = ALG#alg.send_ext_info,
|
|
- recv_ext_info = ALG#alg.recv_ext_info
|
|
+ recv_ext_info = ALG#alg.recv_ext_info,
|
|
+ kex_strict_negotiated = ALG#alg.kex_strict_negotiated
|
|
}.
|
|
|
|
-
|
|
-alg_init(snd, SSH0) ->
|
|
+alg_init(Dir = snd, SSH0) ->
|
|
{ok,SSH1} = send_mac_init(SSH0),
|
|
{ok,SSH2} = encrypt_init(SSH1),
|
|
{ok,SSH3} = compress_init(SSH2),
|
|
- SSH3;
|
|
+ {ok,SSH4} = maybe_reset_sequence(Dir, SSH3),
|
|
+ SSH4;
|
|
|
|
-alg_init(rcv, SSH0) ->
|
|
+alg_init(Dir = rcv, SSH0) ->
|
|
{ok,SSH1} = recv_mac_init(SSH0),
|
|
{ok,SSH2} = decrypt_init(SSH1),
|
|
{ok,SSH3} = decompress_init(SSH2),
|
|
- SSH3.
|
|
-
|
|
+ {ok,SSH4} = maybe_reset_sequence(Dir, SSH3),
|
|
+ SSH4.
|
|
|
|
alg_final(snd, SSH0) ->
|
|
{ok,SSH1} = send_mac_final(SSH0),
|
|
@@ -2236,6 +2290,14 @@ crypto_name_supported(Tag, CryptoName, Supported) ->
|
|
|
|
same(Algs) -> [{client2server,Algs}, {server2client,Algs}].
|
|
|
|
+maybe_reset_sequence(snd, Ssh = #ssh{kex_strict_negotiated = true}) ->
|
|
+ {ok, Ssh#ssh{send_sequence = 0}};
|
|
+maybe_reset_sequence(rcv, Ssh = #ssh{kex_strict_negotiated = true}) ->
|
|
+ {ok, Ssh#ssh{recv_sequence = 0}};
|
|
+maybe_reset_sequence(_Dir, Ssh) ->
|
|
+ {ok, Ssh}.
|
|
+
|
|
+
|
|
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
|
%%
|
|
%% Other utils
|
|
@@ -2262,14 +2324,14 @@ ssh_dbg_flags(raw_messages) -> ssh_dbg_flags(hello);
|
|
ssh_dbg_flags(ssh_messages) -> ssh_dbg_flags(hello).
|
|
|
|
|
|
-ssh_dbg_on(alg) -> dbg:tpl(?MODULE,select_algorithm,4,x);
|
|
+ssh_dbg_on(alg) -> dbg:tpl(?MODULE,select_algorithm,5,x);
|
|
ssh_dbg_on(hello) -> dbg:tp(?MODULE,hello_version_msg,1,x),
|
|
dbg:tp(?MODULE,handle_hello_version,1,x);
|
|
ssh_dbg_on(raw_messages) -> ssh_dbg_on(hello);
|
|
ssh_dbg_on(ssh_messages) -> ssh_dbg_on(hello).
|
|
|
|
|
|
-ssh_dbg_off(alg) -> dbg:ctpl(?MODULE,select_algorithm,4);
|
|
+ssh_dbg_off(alg) -> dbg:ctpl(?MODULE,select_algorithm,5);
|
|
ssh_dbg_off(hello) -> dbg:ctpg(?MODULE,hello_version_msg,1),
|
|
dbg:ctpg(?MODULE,handle_hello_version,1);
|
|
ssh_dbg_off(raw_messages) -> ssh_dbg_off(hello);
|
|
@@ -2292,9 +2354,9 @@ ssh_dbg_format(hello, {call,{?MODULE,handle_hello_version,[Hello]}}) ->
|
|
ssh_dbg_format(hello, {return_from,{?MODULE,handle_hello_version,1},_Ret}) ->
|
|
skip;
|
|
|
|
-ssh_dbg_format(alg, {call,{?MODULE,select_algorithm,[_,_,_,_]}}) ->
|
|
+ssh_dbg_format(alg, {call,{?MODULE,select_algorithm,[_,_,_,_,_]}}) ->
|
|
skip;
|
|
-ssh_dbg_format(alg, {return_from,{?MODULE,select_algorithm,4},{ok,Alg}}) ->
|
|
+ssh_dbg_format(alg, {return_from,{?MODULE,select_algorithm,5},{ok,Alg}}) ->
|
|
["Negotiated algorithms:\n",
|
|
wr_record(Alg)
|
|
];
|
|
diff --git a/lib/ssh/src/ssh_transport.hrl b/lib/ssh/src/ssh_transport.hrl
|
|
index f424a4ff63c3..59ac9db1c1ba 100644
|
|
--- a/lib/ssh/src/ssh_transport.hrl
|
|
+++ b/lib/ssh/src/ssh_transport.hrl
|
|
@@ -266,5 +266,7 @@
|
|
-define(dh_group18,
|
|
{2, 16#FFFFFFFFFFFFFFFFC90FDAA22168C234C4C6628B80DC1CD129024E088A67CC74020BBEA63B139B22514A08798E3404DDEF9519B3CD3A431B302B0A6DF25F14374FE1356D6D51C245E485B576625E7EC6F44C42E9A637ED6B0BFF5CB6F406B7EDEE386BFB5A899FA5AE9F24117C4B1FE649286651ECE45B3DC2007CB8A163BF0598DA48361C55D39A69163FA8FD24CF5F83655D23DCA3AD961C62F356208552BB9ED529077096966D670C354E4ABC9804F1746C08CA18217C32905E462E36CE3BE39E772C180E86039B2783A2EC07A28FB5C55DF06F4C52C9DE2BCBF6955817183995497CEA956AE515D2261898FA051015728E5A8AAAC42DAD33170D04507A33A85521ABDF1CBA64ECFB850458DBEF0A8AEA71575D060C7DB3970F85A6E1E4C7ABF5AE8CDB0933D71E8C94E04A25619DCEE3D2261AD2EE6BF12FFA06D98A0864D87602733EC86A64521F2B18177B200CBBE117577A615D6C770988C0BAD946E208E24FA074E5AB3143DB5BFCE0FD108E4B82D120A92108011A723C12A787E6D788719A10BDBA5B2699C327186AF4E23C1A946834B6150BDA2583E9CA2AD44CE8DBBBC2DB04DE8EF92E8EFC141FBECAA6287C59474E6BC05D99B2964FA090C3A2233BA186515BE7ED1F612970CEE2D7AFB81BDD762170481CD0069127D5B05AA993B4EA988D8FDDC186FFB7DC90A6C08F4DF435C93402849236C3FAB4D27C7026C1D4DCB2602646DEC9751E763DBA37BDF8FF9406AD9E530EE5DB382F413001AEB06A53ED9027D831179727B0865A8918DA3EDBEBCF9B14ED44CE6CBACED4BB1BDB7F1447E6CC254B332051512BD7AF426FB8F401378CD2BF5983CA01C64B92ECF032EA15D1721D03F482D7CE6E74FEF6D55E702F46980C82B5A84031900B1C9E59E7C97FBEC7E8F323A97A7E36CC88BE0F1D45B7FF585AC54BD407B22B4154AACC8F6D7EBF48E1D814CC5ED20F8037E0A79715EEF29BE32806A1D58BB7C5DA76F550AA3D8A1FBFF0EB19CCB1A313D55CDA56C9EC2EF29632387FE8D76E3C0468043E8F663F4860EE12BF2D5B0B7474D6E694F91E6DBE115974A3926F12FEE5E438777CB6A932DF8CD8BEC4D073B931BA3BC832B68D9DD300741FA7BF8AFC47ED2576F6936BA424663AAB639C5AE4F5683423B4742BF1C978238F16CBE39D652DE3FDB8BEFC848AD922222E04A4037C0713EB57A81A23F0C73473FC646CEA306B4BCBC8862F8385DDFA9D4B7FA2C087E879683303ED5BDD3A062B3CF5B3A278A66D2A13F83F44F82DDF310EE074AB6A364597E899A0255DC164F31CC50846851DF9AB48195DED7EA1B1D510BD7EE74D73FAF36BC31ECFA268359046F4EB879F924009438B481C6CD7889A002ED5EE382BC9190DA6FC026E479558E4475677E9AA9E3050E2765694DFC81F56E880B96E7160C980DD98EDD3DFFFFFFFFFFFFFFFFF}).
|
|
|
|
-
|
|
+%%% OpenSSH KEX strict
|
|
+-define(kex_strict_c, "kex-strict-c-v00@openssh.com").
|
|
+-define(kex_strict_s, "kex-strict-s-v00@openssh.com").
|
|
-endif. % -ifdef(ssh_transport).
|
|
diff --git a/lib/ssh/test/ssh_protocol_SUITE.erl b/lib/ssh/test/ssh_protocol_SUITE.erl
|
|
index 7e94bf60c718..b4f765495fa6 100644
|
|
--- a/lib/ssh/test/ssh_protocol_SUITE.erl
|
|
+++ b/lib/ssh/test/ssh_protocol_SUITE.erl
|
|
@@ -53,6 +53,9 @@
|
|
empty_service_name/1,
|
|
ext_info_c/1,
|
|
ext_info_s/1,
|
|
+ kex_strict_negotiated/1,
|
|
+ kex_strict_msg_ignore/1,
|
|
+ kex_strict_msg_unknown/1,
|
|
gex_client_init_option_groups/1,
|
|
gex_client_init_option_groups_file/1,
|
|
gex_client_init_option_groups_moduli_file/1,
|
|
@@ -136,8 +139,10 @@ groups() ->
|
|
gex_client_init_option_groups_moduli_file,
|
|
gex_client_init_option_groups_file,
|
|
gex_client_old_request_exact,
|
|
- gex_client_old_request_noexact
|
|
- ]},
|
|
+ gex_client_old_request_noexact,
|
|
+ kex_strict_negotiated,
|
|
+ kex_strict_msg_ignore,
|
|
+ kex_strict_msg_unknown]},
|
|
{service_requests, [], [bad_service_name,
|
|
bad_long_service_name,
|
|
bad_very_long_service_name,
|
|
@@ -164,17 +169,16 @@ groups() ->
|
|
|
|
init_per_suite(Config) ->
|
|
?CHECK_CRYPTO(start_std_daemon( setup_dirs( start_apps(Config)))).
|
|
-
|
|
+
|
|
end_per_suite(Config) ->
|
|
stop_apps(Config).
|
|
|
|
-
|
|
-
|
|
init_per_testcase(no_common_alg_server_disconnects, Config) ->
|
|
start_std_daemon(Config, [{preferred_algorithms,[{public_key,['ssh-rsa']},
|
|
{cipher,?DEFAULT_CIPHERS}
|
|
]}]);
|
|
-
|
|
+init_per_testcase(kex_strict_negotiated, Config) ->
|
|
+ Config;
|
|
init_per_testcase(TC, Config) when TC == gex_client_init_option_groups ;
|
|
TC == gex_client_init_option_groups_moduli_file ;
|
|
TC == gex_client_init_option_groups_file ;
|
|
@@ -217,6 +221,8 @@ init_per_testcase(_TestCase, Config) ->
|
|
|
|
end_per_testcase(no_common_alg_server_disconnects, Config) ->
|
|
stop_std_daemon(Config);
|
|
+end_per_testcase(kex_strict_negotiated, Config) ->
|
|
+ Config;
|
|
end_per_testcase(TC, Config) when TC == gex_client_init_option_groups ;
|
|
TC == gex_client_init_option_groups_moduli_file ;
|
|
TC == gex_client_init_option_groups_file ;
|
|
@@ -818,6 +824,80 @@ ext_info_c(Config) ->
|
|
{result, Pid, Error} -> ct:fail("Error: ~p",[Error])
|
|
end.
|
|
|
|
+%%%--------------------------------------------------------------------
|
|
+%%%
|
|
+kex_strict_negotiated(Config0) ->
|
|
+ {ok,Pid} = ssh_test_lib:add_report_handler(),
|
|
+ Config = start_std_daemon(Config0, []),
|
|
+ {Server, Host, Port} = proplists:get_value(server, Config),
|
|
+ #{level := Level} = logger:get_primary_config(),
|
|
+ logger:set_primary_config(level, notice),
|
|
+ {ok, ConnRef} = std_connect({Host, Port}, Config, []),
|
|
+ {algorithms, A} = ssh:connection_info(ConnRef, algorithms),
|
|
+ ssh:stop_daemon(Server),
|
|
+ {ok, Reports} = ssh_test_lib:get_reports(Pid),
|
|
+ ct:log("Reports = ~p", [Reports]),
|
|
+ true = ssh_test_lib:kex_strict_negotiated(client, Reports),
|
|
+ true = ssh_test_lib:kex_strict_negotiated(server, Reports),
|
|
+ logger:set_primary_config(Level),
|
|
+ ok.
|
|
+
|
|
+%% Connect to an erlang server and inject unexpected SSH ignore
|
|
+kex_strict_msg_ignore(Config) ->
|
|
+ ct:log("START: ~p~n=================================", [?FUNCTION_NAME]),
|
|
+ ExpectedReason = "strict KEX violation: unexpected SSH_MSG_IGNORE",
|
|
+ TestMessages =
|
|
+ [{send, ssh_msg_ignore},
|
|
+ {match, #ssh_msg_kexdh_reply{_='_'}, receive_msg},
|
|
+ {match, disconnect(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED), receive_msg}],
|
|
+ kex_strict_helper(Config, TestMessages, ExpectedReason).
|
|
+
|
|
+%% Connect to an erlang server and inject unexpected non-SSH binary
|
|
+kex_strict_msg_unknown(Config) ->
|
|
+ ct:log("START: ~p~n=================================", [?FUNCTION_NAME]),
|
|
+ ExpectedReason = "Bad packet: Size",
|
|
+ TestMessages =
|
|
+ [{send, ssh_msg_unknown},
|
|
+ {match, #ssh_msg_kexdh_reply{_='_'}, receive_msg},
|
|
+ {match, disconnect(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED), receive_msg}],
|
|
+ kex_strict_helper(Config, TestMessages, ExpectedReason).
|
|
+
|
|
+kex_strict_helper(Config, TestMessages, ExpectedReason) ->
|
|
+ {ok,HandlerPid} = ssh_test_lib:add_report_handler(),
|
|
+ #{level := Level} = logger:get_primary_config(),
|
|
+ logger:set_primary_config(level, notice),
|
|
+ %% Connect and negotiate keys
|
|
+ {ok, InitialState} = ssh_trpt_test_lib:exec(
|
|
+ [{set_options, [print_ops, print_seqnums, print_messages]}]
|
|
+ ),
|
|
+ {ok, _AfterKexState} =
|
|
+ ssh_trpt_test_lib:exec(
|
|
+ [{connect,
|
|
+ server_host(Config),server_port(Config),
|
|
+ [{preferred_algorithms,[{kex,[?DEFAULT_KEX]},
|
|
+ {cipher,?DEFAULT_CIPHERS}
|
|
+ ]},
|
|
+ {silently_accept_hosts, true},
|
|
+ {recv_ext_info, false},
|
|
+ {user_dir, user_dir(Config)},
|
|
+ {user_interaction, false}
|
|
+ | proplists:get_value(extra_options,Config,[])
|
|
+ ]},
|
|
+ receive_hello,
|
|
+ {send, hello},
|
|
+ {send, ssh_msg_kexinit},
|
|
+ {match, #ssh_msg_kexinit{_='_'}, receive_msg},
|
|
+ {send, ssh_msg_kexdh_init}] ++
|
|
+ TestMessages,
|
|
+ InitialState),
|
|
+ ct:sleep(100),
|
|
+ {ok, Reports} = ssh_test_lib:get_reports(HandlerPid),
|
|
+ ct:log("HandlerPid = ~p~nReports = ~p", [HandlerPid, Reports]),
|
|
+ true = ssh_test_lib:kex_strict_negotiated(client, Reports),
|
|
+ true = ssh_test_lib:kex_strict_negotiated(server, Reports),
|
|
+ true = ssh_test_lib:event_logged(server, Reports, ExpectedReason),
|
|
+ logger:set_primary_config(Level),
|
|
+ ok.
|
|
|
|
%%%----------------------------------------------------------------
|
|
%%%
|
|
@@ -839,7 +919,7 @@ modify_append(Config) ->
|
|
Ciphers = filter_supported(cipher, ?CIPHERS),
|
|
{ok,_} =
|
|
chk_pref_algs(Config,
|
|
- [?DEFAULT_KEX, ?EXTRA_KEX],
|
|
+ [?DEFAULT_KEX, ?EXTRA_KEX, list_to_atom(?kex_strict_s)],
|
|
Ciphers,
|
|
[{preferred_algorithms, [{kex,[?DEFAULT_KEX]},
|
|
{cipher,Ciphers}
|
|
@@ -853,7 +933,7 @@ modify_prepend(Config) ->
|
|
Ciphers = filter_supported(cipher, ?CIPHERS),
|
|
{ok,_} =
|
|
chk_pref_algs(Config,
|
|
- [?EXTRA_KEX, ?DEFAULT_KEX],
|
|
+ [?EXTRA_KEX, ?DEFAULT_KEX, list_to_atom(?kex_strict_s)],
|
|
Ciphers,
|
|
[{preferred_algorithms, [{kex,[?DEFAULT_KEX]},
|
|
{cipher,Ciphers}
|
|
@@ -867,7 +947,7 @@ modify_rm(Config) ->
|
|
Ciphers = filter_supported(cipher, ?CIPHERS),
|
|
{ok,_} =
|
|
chk_pref_algs(Config,
|
|
- [?DEFAULT_KEX],
|
|
+ [?DEFAULT_KEX, list_to_atom(?kex_strict_s)],
|
|
tl(Ciphers),
|
|
[{preferred_algorithms, [{kex,[?DEFAULT_KEX,?EXTRA_KEX]},
|
|
{cipher,Ciphers}
|
|
@@ -886,7 +966,7 @@ modify_combo(Config) ->
|
|
LastC = lists:last(Ciphers),
|
|
{ok,_} =
|
|
chk_pref_algs(Config,
|
|
- [?DEFAULT_KEX],
|
|
+ [?DEFAULT_KEX, list_to_atom(?kex_strict_s)],
|
|
[LastC] ++ (tl(Ciphers)--[LastC]) ++ [hd(Ciphers)],
|
|
[{preferred_algorithms, [{kex,[?DEFAULT_KEX,?EXTRA_KEX]},
|
|
{cipher,Ciphers}
|
|
diff --git a/lib/ssh/test/ssh_test_lib.erl b/lib/ssh/test/ssh_test_lib.erl
|
|
index acabb66a4805..e8fe5b4203df 100644
|
|
--- a/lib/ssh/test/ssh_test_lib.erl
|
|
+++ b/lib/ssh/test/ssh_test_lib.erl
|
|
@@ -121,7 +121,11 @@ setup_host_key_create_dir/3,
|
|
setup_host_key/3,
|
|
setup_known_host/3,
|
|
get_addr_str/0,
|
|
-file_base_name/2
|
|
+file_base_name/2,
|
|
+add_report_handler/0,
|
|
+get_reports/1,
|
|
+kex_strict_negotiated/2,
|
|
+event_logged/3
|
|
]).
|
|
|
|
-include_lib("common_test/include/ct.hrl").
|
|
@@ -1267,3 +1271,49 @@ file_base_name(system_src, 'ecdsa-sha2-nistp521') -> "ssh_host_ecdsa_key521";
|
|
file_base_name(system_src, Alg) -> file_base_name(system, Alg).
|
|
|
|
%%%----------------------------------------------------------------
|
|
+add_report_handler() ->
|
|
+ ssh_eqc_event_handler:add_report_handler().
|
|
+
|
|
+get_reports(Pid) ->
|
|
+ ssh_eqc_event_handler:get_reports(Pid).
|
|
+
|
|
+-define(SEARCH_FUN(EXP),
|
|
+ begin
|
|
+ fun({info_report, _, {_, std_info, EXP}}) ->
|
|
+ true;
|
|
+ (_) ->
|
|
+ false
|
|
+ end
|
|
+ end).
|
|
+-define(SEARCH_SUFFIX, " will use strict KEX ordering").
|
|
+
|
|
+kex_strict_negotiated(client, Reports) ->
|
|
+ kex_strict_negotiated(?SEARCH_FUN("client" ++ ?SEARCH_SUFFIX), Reports);
|
|
+kex_strict_negotiated(server, Reports) ->
|
|
+ kex_strict_negotiated(?SEARCH_FUN("server" ++ ?SEARCH_SUFFIX), Reports);
|
|
+kex_strict_negotiated(SearchFun, Reports) when is_function(SearchFun) ->
|
|
+ case lists:search(SearchFun, Reports) of
|
|
+ {value, _} -> true;
|
|
+ _ -> false
|
|
+ end.
|
|
+
|
|
+event_logged(Role, Reports, Reason) ->
|
|
+ SearchF =
|
|
+ fun({info_msg, _, {_, _Format, Args}}) ->
|
|
+ AnyF = fun (E) when is_list(E) ->
|
|
+ case string:find(E, Reason) of
|
|
+ nomatch -> false;
|
|
+ _ -> true
|
|
+ end;
|
|
+ (_) ->
|
|
+ false
|
|
+ end,
|
|
+ lists:member(Role, Args) andalso
|
|
+ lists:any(AnyF, Args);
|
|
+ (_) ->
|
|
+ false
|
|
+ end,
|
|
+ case lists:search(SearchF, Reports) of
|
|
+ {value, _} -> true;
|
|
+ _ -> false
|
|
+ end.
|
|
diff --git a/lib/ssh/test/ssh_to_openssh_SUITE.erl b/lib/ssh/test/ssh_to_openssh_SUITE.erl
|
|
index a36b4036a527..fdc9a4f0d64f 100644
|
|
--- a/lib/ssh/test/ssh_to_openssh_SUITE.erl
|
|
+++ b/lib/ssh/test/ssh_to_openssh_SUITE.erl
|
|
@@ -23,6 +23,7 @@
|
|
|
|
-include_lib("common_test/include/ct.hrl").
|
|
-include("ssh_test_lib.hrl").
|
|
+-include_lib("ssh/src/ssh_transport.hrl").
|
|
|
|
-export([
|
|
suite/0,
|
|
@@ -38,7 +39,9 @@
|
|
|
|
-export([
|
|
erlang_server_openssh_client_renegotiate/1,
|
|
+ eserver_oclient_kex_strict/1,
|
|
erlang_shell_client_openssh_server/1,
|
|
+ eclient_oserver_kex_strict/1,
|
|
exec_direct_with_io_in_sshc/1,
|
|
exec_with_io_in_sshc/1,
|
|
tunnel_in_erlclient_erlserver/1,
|
|
@@ -73,12 +76,14 @@ groups() ->
|
|
[{erlang_client, [], [tunnel_in_erlclient_erlserver,
|
|
tunnel_out_erlclient_erlserver,
|
|
{group, tunnel_distro_server},
|
|
- erlang_shell_client_openssh_server
|
|
+ erlang_shell_client_openssh_server,
|
|
+ eclient_oserver_kex_strict
|
|
]},
|
|
{tunnel_distro_server, [], [tunnel_in_erlclient_openssh_server,
|
|
tunnel_out_erlclient_openssh_server]},
|
|
{erlang_server, [], [{group, tunnel_distro_client},
|
|
erlang_server_openssh_client_renegotiate,
|
|
+ eserver_oclient_kex_strict,
|
|
exec_with_io_in_sshc,
|
|
exec_direct_with_io_in_sshc
|
|
]
|
|
@@ -87,16 +92,15 @@ groups() ->
|
|
tunnel_out_non_erlclient_erlserver]}
|
|
].
|
|
|
|
-init_per_suite(Config) ->
|
|
+init_per_suite(Config0) ->
|
|
?CHECK_CRYPTO(
|
|
- case gen_tcp:connect("localhost", ?SSH_DEFAULT_PORT, []) of
|
|
+ case gen_tcp:connect("localhost", ?SSH_DEFAULT_PORT, [{active, false}]) of
|
|
{error,econnrefused} ->
|
|
- {skip,"No openssh daemon (econnrefused)"};
|
|
- _ ->
|
|
+ {skip,"No openssh daemon (econnrefused)"};
|
|
+ {ok, Sock} ->
|
|
ssh_test_lib:openssh_sanity_check(
|
|
- [{ptty_supported, ssh_test_lib:ptty_supported()}
|
|
- | Config]
|
|
- )
|
|
+ [{ptty_supported, ssh_test_lib:ptty_supported()},
|
|
+ {kex_strict, check_kex_strict(Sock)}| Config0])
|
|
end
|
|
).
|
|
|
|
@@ -142,6 +146,25 @@ end_per_testcase(_TestCase, _Config) ->
|
|
%% Test Cases --------------------------------------------------------
|
|
%%--------------------------------------------------------------------
|
|
erlang_shell_client_openssh_server(Config) when is_list(Config) ->
|
|
+ eclient_oserver_helper(Config).
|
|
+
|
|
+eclient_oserver_kex_strict(Config) when is_list(Config)->
|
|
+ case proplists:get_value(kex_strict, Config) of
|
|
+ true ->
|
|
+ {ok, HandlerPid} = ssh_test_lib:add_report_handler(),
|
|
+ #{level := Level} = logger:get_primary_config(),
|
|
+ logger:set_primary_config(level, notice),
|
|
+ Result = eclient_oserver_helper(Config),
|
|
+ {ok, Reports} = ssh_test_lib:get_reports(HandlerPid),
|
|
+ ct:pal("Reports = ~p", [Reports]),
|
|
+ true = ssh_test_lib:kex_strict_negotiated(client, Reports),
|
|
+ logger:set_primary_config(Level),
|
|
+ Result;
|
|
+ _ ->
|
|
+ {skip, "KEX strict not support by local OpenSSH"}
|
|
+ end.
|
|
+
|
|
+eclient_oserver_helper(Config) ->
|
|
process_flag(trap_exit, true),
|
|
IO = ssh_test_lib:start_io_server(),
|
|
Prev = lists:usort(supervisor:which_children(sshc_sup)),
|
|
@@ -166,7 +189,6 @@ erlang_shell_client_openssh_server(Config) when is_list(Config) ->
|
|
false
|
|
end)
|
|
end.
|
|
-
|
|
%%--------------------------------------------------------------------
|
|
%% Test that the server could redirect stdin and stdout from/to an
|
|
%% OpensSSH client when handling an exec request
|
|
@@ -231,6 +253,25 @@ exec_direct_with_io_in_sshc(Config) when is_list(Config) ->
|
|
%%--------------------------------------------------------------------
|
|
%% Test that the Erlang/OTP server can renegotiate with openSSH
|
|
erlang_server_openssh_client_renegotiate(Config) ->
|
|
+ eserver_oclient_renegotiate_helper(Config).
|
|
+
|
|
+eserver_oclient_kex_strict(Config) ->
|
|
+ case proplists:get_value(kex_strict, Config) of
|
|
+ true ->
|
|
+ {ok, HandlerPid} = ssh_test_lib:add_report_handler(),
|
|
+ #{level := Level} = logger:get_primary_config(),
|
|
+ logger:set_primary_config(level, notice),
|
|
+ Result = eserver_oclient_renegotiate_helper(Config),
|
|
+ {ok, Reports} = ssh_test_lib:get_reports(HandlerPid),
|
|
+ ct:log("Reports = ~p", [Reports]),
|
|
+ true = ssh_test_lib:kex_strict_negotiated(server, Reports),
|
|
+ logger:set_primary_config(Level),
|
|
+ Result;
|
|
+ _ ->
|
|
+ {skip, "KEX strict not support by local OpenSSH"}
|
|
+ end.
|
|
+
|
|
+eserver_oclient_renegotiate_helper(Config) ->
|
|
_PubKeyAlg = ssh_rsa,
|
|
SystemDir = proplists:get_value(data_dir, Config),
|
|
PrivDir = proplists:get_value(priv_dir, Config),
|
|
@@ -255,9 +296,9 @@ erlang_server_openssh_client_renegotiate(Config) ->
|
|
|
|
OpenSsh = ssh_test_lib:open_port({spawn, Cmd++" < "++DataFile}),
|
|
|
|
- Expect = fun({data,R}) ->
|
|
+ Expect = fun({data,R}) ->
|
|
try
|
|
- NonAlphaChars = [C || C<-lists:seq(1,255),
|
|
+ NonAlphaChars = [C || C<-lists:seq(1,255),
|
|
not lists:member(C,lists:seq($a,$z)),
|
|
not lists:member(C,lists:seq($A,$Z))
|
|
],
|
|
@@ -275,15 +316,14 @@ erlang_server_openssh_client_renegotiate(Config) ->
|
|
(_) ->
|
|
false
|
|
end,
|
|
-
|
|
- try
|
|
- ssh_test_lib:rcv_expected(Expect, OpenSsh, ?TIMEOUT)
|
|
+ try
|
|
+ ssh_test_lib:rcv_expected(Expect, OpenSsh, ?TIMEOUT)
|
|
of
|
|
- _ ->
|
|
- %% Unfortunately we can't check that there has been a renegotiation, just trust OpenSSH.
|
|
- ssh:stop_daemon(Pid)
|
|
+ _ ->
|
|
+ %% Unfortunately we can't check that there has been a renegotiation, just trust OpenSSH.
|
|
+ ssh:stop_daemon(Pid)
|
|
catch
|
|
- throw:{skip,R} -> {skip,R}
|
|
+ throw:{skip,R} -> {skip,R}
|
|
end.
|
|
|
|
%%--------------------------------------------------------------------
|
|
@@ -569,3 +609,17 @@ no_forwarding(Config) ->
|
|
"---- The function no_forwarding() returns ~p",
|
|
[Cmnd,TheText, FailRegExp, Result]),
|
|
Result.
|
|
+
|
|
+check_kex_strict(Sock) ->
|
|
+ %% Send some version, in order to receive KEXINIT from server
|
|
+ ok = gen_tcp:send(Sock, "SSH-2.0-OpenSSH_9.5\r\n"),
|
|
+ ct:sleep(100),
|
|
+ {ok, Packet} = gen_tcp:recv(Sock, 0),
|
|
+ case string:find(Packet, ?kex_strict_s) of
|
|
+ nomatch ->
|
|
+ ct:log("KEX strict NOT supported by local OpenSSH"),
|
|
+ false;
|
|
+ _ ->
|
|
+ ct:log("KEX strict supported by local OpenSSH"),
|
|
+ true
|
|
+ end.
|
|
diff --git a/lib/ssh/test/ssh_trpt_test_lib.erl b/lib/ssh/test/ssh_trpt_test_lib.erl
|
|
index eea392bd352a..80c570acb594 100644
|
|
--- a/lib/ssh/test/ssh_trpt_test_lib.erl
|
|
+++ b/lib/ssh/test/ssh_trpt_test_lib.erl
|
|
@@ -73,7 +73,7 @@ exec(L, S) when is_list(L) -> lists:foldl(fun exec/2, S, L);
|
|
exec(Op, S0=#s{}) ->
|
|
S1 = init_op_traces(Op, S0),
|
|
try seqnum_trace(
|
|
- op(Op, S1))
|
|
+ op(Op, S1), S1)
|
|
of
|
|
S = #s{} ->
|
|
case proplists:get_value(silent,S#s.opts) of
|
|
@@ -331,12 +331,20 @@ send(S0, ssh_msg_kexinit) ->
|
|
{Msg, _Bytes, _C0} = ssh_transport:key_exchange_init_msg(S0#s.ssh),
|
|
send(S0, Msg);
|
|
|
|
+send(S0, ssh_msg_ignore) ->
|
|
+ Msg = #ssh_msg_ignore{data = "unexpected_ignore_message"},
|
|
+ send(S0, Msg);
|
|
+
|
|
+send(S0, ssh_msg_unknown) ->
|
|
+ Msg = binary:encode_hex(<<"0000000C060900000000000000000000">>),
|
|
+ send(S0, Msg);
|
|
+
|
|
send(S0=#s{alg_neg={undefined,PeerMsg}}, Msg=#ssh_msg_kexinit{}) ->
|
|
S1 = opt(print_messages, S0,
|
|
fun(X) when X==true;X==detail -> {"Send~n~s~n",[format_msg(Msg)]} end),
|
|
S2 = case PeerMsg of
|
|
#ssh_msg_kexinit{} ->
|
|
- try ssh_transport:handle_kexinit_msg(PeerMsg, Msg, S1#s.ssh) of
|
|
+ try ssh_transport:handle_kexinit_msg(PeerMsg, Msg, S1#s.ssh, init) of
|
|
{ok,Cx} when ?role(S1) == server ->
|
|
S1#s{alg = Cx#ssh.algorithms};
|
|
{ok,_NextKexMsgBin,Cx} when ?role(S1) == client ->
|
|
@@ -358,7 +366,7 @@ send(S0=#s{alg_neg={undefined,PeerMsg}}, Msg=#ssh_msg_kexinit{}) ->
|
|
send(S0, ssh_msg_kexdh_init) when ?role(S0) == client ->
|
|
{OwnMsg, PeerMsg} = S0#s.alg_neg,
|
|
{ok, NextKexMsgBin, C} =
|
|
- try ssh_transport:handle_kexinit_msg(PeerMsg, OwnMsg, S0#s.ssh)
|
|
+ try ssh_transport:handle_kexinit_msg(PeerMsg, OwnMsg, S0#s.ssh, init)
|
|
catch
|
|
Class:Exc ->
|
|
fail("Algorithm negotiation failed!",
|
|
@@ -441,7 +449,7 @@ recv(S0 = #s{}) ->
|
|
fail("2 kexint received!!", S);
|
|
|
|
{OwnMsg, _} ->
|
|
- try ssh_transport:handle_kexinit_msg(PeerMsg, OwnMsg, S#s.ssh) of
|
|
+ try ssh_transport:handle_kexinit_msg(PeerMsg, OwnMsg, S#s.ssh, init) of
|
|
{ok,C} when ?role(S) == server ->
|
|
S#s{alg_neg = {OwnMsg, PeerMsg},
|
|
alg = C#ssh.algorithms,
|
|
@@ -725,23 +733,23 @@ report_trace(Class, Term, S) ->
|
|
fun(true) -> {"~s ~p",[Class,Term]} end)
|
|
).
|
|
|
|
-seqnum_trace(S) ->
|
|
+seqnum_trace(S, S0) ->
|
|
opt(print_seqnums, S,
|
|
- fun(true) when S#s.ssh#ssh.send_sequence =/= S#s.ssh#ssh.send_sequence,
|
|
- S#s.ssh#ssh.recv_sequence =/= S#s.ssh#ssh.recv_sequence ->
|
|
+ fun(true) when S0#s.ssh#ssh.send_sequence =/= S#s.ssh#ssh.send_sequence,
|
|
+ S0#s.ssh#ssh.recv_sequence =/= S#s.ssh#ssh.recv_sequence ->
|
|
{"~p seq num: send ~p->~p, recv ~p->~p~n",
|
|
[?role(S),
|
|
- S#s.ssh#ssh.send_sequence, S#s.ssh#ssh.send_sequence,
|
|
- S#s.ssh#ssh.recv_sequence, S#s.ssh#ssh.recv_sequence
|
|
+ S0#s.ssh#ssh.send_sequence, S#s.ssh#ssh.send_sequence,
|
|
+ S0#s.ssh#ssh.recv_sequence, S#s.ssh#ssh.recv_sequence
|
|
]};
|
|
- (true) when S#s.ssh#ssh.send_sequence =/= S#s.ssh#ssh.send_sequence ->
|
|
+ (true) when S0#s.ssh#ssh.send_sequence =/= S#s.ssh#ssh.send_sequence ->
|
|
{"~p seq num: send ~p->~p~n",
|
|
[?role(S),
|
|
- S#s.ssh#ssh.send_sequence, S#s.ssh#ssh.send_sequence]};
|
|
- (true) when S#s.ssh#ssh.recv_sequence =/= S#s.ssh#ssh.recv_sequence ->
|
|
+ S0#s.ssh#ssh.send_sequence, S#s.ssh#ssh.send_sequence]};
|
|
+ (true) when S0#s.ssh#ssh.recv_sequence =/= S#s.ssh#ssh.recv_sequence ->
|
|
{"~p seq num: recv ~p->~p~n",
|
|
[?role(S),
|
|
- S#s.ssh#ssh.recv_sequence, S#s.ssh#ssh.recv_sequence]}
|
|
+ S0#s.ssh#ssh.recv_sequence, S#s.ssh#ssh.recv_sequence]}
|
|
end).
|
|
|
|
print_traces(S) when S#s.prints == [] -> S;
|