Skip to content

Commit

Permalink
ssh: KEX strict
Browse files Browse the repository at this point in the history
- negotiate "strict KEX" OpenSSH feature
- when negotiated between peers apply strict KEX
- related tests
- print_seqnums fix in ssh_trtp test code
  • Loading branch information
u3s committed Dec 15, 2023
1 parent 0863bd3 commit ee67d46
Show file tree
Hide file tree
Showing 9 changed files with 335 additions and 66 deletions.
5 changes: 4 additions & 1 deletion lib/ssh/src/ssh.hrl
Expand Up @@ -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
Expand Down Expand Up @@ -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"
Expand Down
10 changes: 10 additions & 0 deletions lib/ssh/src/ssh_connection_handler.erl
Expand Up @@ -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;

Expand Down
2 changes: 1 addition & 1 deletion lib/ssh/src/ssh_fsm_kexinit.erl
Expand Up @@ -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;
Expand Down
104 changes: 83 additions & 21 deletions lib/ssh/src/ssh_transport.erl
Expand Up @@ -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,
Expand Down Expand Up @@ -235,14 +235,14 @@ 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}]},
{'aes128-gcm@openssh.com', [{ciphers,aes_128_gcm}]},
{'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}]},
Expand Down Expand Up @@ -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),
Expand Down Expand Up @@ -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 ->
Expand All @@ -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 ->
Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -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) ->
Expand Down Expand Up @@ -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),

Expand Down Expand Up @@ -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
}}.


Expand Down Expand Up @@ -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) ->
Expand All @@ -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),
Expand Down Expand Up @@ -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
Expand All @@ -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);
Expand All @@ -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)
];
Expand Down
4 changes: 3 additions & 1 deletion lib/ssh/src/ssh_transport.hrl
Expand Up @@ -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).

0 comments on commit ee67d46

Please sign in to comment.