Skip to content

Commit beb2cb9

Browse files
author
Erlang/OTP
committed
Merge branch 'kuba/ssh/stricter_kex_strict/OTP-19625' into maint-27
* kuba/ssh/stricter_kex_strict/OTP-19625: ssh: ssh_test_lib add extra remove_handler to improve robustness in tests ssh: KEX strict implementation fixes
2 parents f9cdb55 + dc2223c commit beb2cb9

File tree

6 files changed

+314
-50
lines changed

6 files changed

+314
-50
lines changed

lib/ssh/src/ssh_connection_handler.erl

Lines changed: 8 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -35,7 +35,6 @@
3535
-include("ssh_transport.hrl").
3636
-include("ssh_auth.hrl").
3737
-include("ssh_connect.hrl").
38-
3938
-include("ssh_fsm.hrl").
4039

4140
%%====================================================================
@@ -732,16 +731,6 @@ handle_event(internal, #ssh_msg_disconnect{description=Desc} = Msg, StateName, D
732731
disconnect_fun("Received disconnect: "++Desc, D),
733732
{stop_and_reply, {shutdown,Desc}, Actions, D};
734733

735-
handle_event(internal, #ssh_msg_ignore{}, {_StateName, _Role, init},
736-
#data{ssh_params = #ssh{kex_strict_negotiated = true,
737-
send_sequence = SendSeq,
738-
recv_sequence = RecvSeq}}) ->
739-
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
740-
io_lib:format("strict KEX violation: unexpected SSH_MSG_IGNORE "
741-
"send_sequence = ~p recv_sequence = ~p",
742-
[SendSeq, RecvSeq])
743-
);
744-
745734
handle_event(internal, #ssh_msg_ignore{}, _StateName, _) ->
746735
keep_state_and_data;
747736

@@ -1145,11 +1134,14 @@ handle_event(info, {Proto, Sock, NewData}, StateName,
11451134
of
11461135
{packet_decrypted, DecryptedBytes, EncryptedDataRest, Ssh1} ->
11471136
D1 = D0#data{ssh_params =
1148-
Ssh1#ssh{recv_sequence = ssh_transport:next_seqnum(Ssh1#ssh.recv_sequence)},
1149-
decrypted_data_buffer = <<>>,
1150-
undecrypted_packet_length = undefined,
1151-
aead_data = <<>>,
1152-
encrypted_data_buffer = EncryptedDataRest},
1137+
Ssh1#ssh{recv_sequence =
1138+
ssh_transport:next_seqnum(StateName,
1139+
Ssh1#ssh.recv_sequence,
1140+
SshParams)},
1141+
decrypted_data_buffer = <<>>,
1142+
undecrypted_packet_length = undefined,
1143+
aead_data = <<>>,
1144+
encrypted_data_buffer = EncryptedDataRest},
11531145
try
11541146
ssh_message:decode(set_kex_overload_prefix(DecryptedBytes,D1))
11551147
of

lib/ssh/src/ssh_fsm_kexinit.erl

Lines changed: 120 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -44,6 +44,11 @@
4444
-export([callback_mode/0, handle_event/4, terminate/3,
4545
format_status/2, code_change/4]).
4646

47+
-behaviour(ssh_dbg).
48+
-export([ssh_dbg_trace_points/0, ssh_dbg_flags/1,
49+
ssh_dbg_on/1, ssh_dbg_off/1,
50+
ssh_dbg_format/2]).
51+
4752
%%====================================================================
4853
%% gen_statem callbacks
4954
%%====================================================================
@@ -54,8 +59,13 @@ callback_mode() ->
5459

5560
%%--------------------------------------------------------------------
5661

57-
%%% ######## {kexinit, client|server, init|renegotiate} ####
5862

63+
handle_event(Type, Event = prepare_next_packet, StateName, D) ->
64+
ssh_connection_handler:handle_event(Type, Event, StateName, D);
65+
handle_event(Type, Event = {send_disconnect, _, _, _, _}, StateName, D) ->
66+
ssh_connection_handler:handle_event(Type, Event, StateName, D);
67+
68+
%%% ######## {kexinit, client|server, init|renegotiate} ####
5969
handle_event(internal, {#ssh_msg_kexinit{}=Kex, Payload}, {kexinit,Role,ReNeg},
6070
D = #data{key_exchange_init_msg = OwnKex}) ->
6171
Ssh1 = ssh_transport:key_init(peer_role(Role), D#data.ssh_params, Payload),
@@ -68,11 +78,10 @@ handle_event(internal, {#ssh_msg_kexinit{}=Kex, Payload}, {kexinit,Role,ReNeg},
6878
end,
6979
{next_state, {key_exchange,Role,ReNeg}, D#data{ssh_params=Ssh}};
7080

71-
7281
%%% ######## {key_exchange, client|server, init|renegotiate} ####
73-
7482
%%%---- diffie-hellman
7583
handle_event(internal, #ssh_msg_kexdh_init{} = Msg, {key_exchange,server,ReNeg}, D) ->
84+
ok = check_kex_strict(Msg, D),
7685
{ok, KexdhReply, Ssh1} = ssh_transport:handle_kexdh_init(Msg, D#data.ssh_params),
7786
ssh_connection_handler:send_bytes(KexdhReply, D),
7887
{ok, NewKeys, Ssh2} = ssh_transport:new_keys_message(Ssh1),
@@ -82,6 +91,7 @@ handle_event(internal, #ssh_msg_kexdh_init{} = Msg, {key_exchange,server,ReNeg},
8291
{next_state, {new_keys,server,ReNeg}, D#data{ssh_params=Ssh}};
8392

8493
handle_event(internal, #ssh_msg_kexdh_reply{} = Msg, {key_exchange,client,ReNeg}, D) ->
94+
ok = check_kex_strict(Msg, D),
8595
{ok, NewKeys, Ssh1} = ssh_transport:handle_kexdh_reply(Msg, D#data.ssh_params),
8696
ssh_connection_handler:send_bytes(NewKeys, D),
8797
{ok, ExtInfo, Ssh} = ssh_transport:ext_info_message(Ssh1),
@@ -90,24 +100,28 @@ handle_event(internal, #ssh_msg_kexdh_reply{} = Msg, {key_exchange,client,ReNeg}
90100

91101
%%%---- diffie-hellman group exchange
92102
handle_event(internal, #ssh_msg_kex_dh_gex_request{} = Msg, {key_exchange,server,ReNeg}, D) ->
103+
ok = check_kex_strict(Msg, D),
93104
{ok, GexGroup, Ssh1} = ssh_transport:handle_kex_dh_gex_request(Msg, D#data.ssh_params),
94105
ssh_connection_handler:send_bytes(GexGroup, D),
95106
Ssh = ssh_transport:parallell_gen_key(Ssh1),
96107
{next_state, {key_exchange_dh_gex_init,server,ReNeg}, D#data{ssh_params=Ssh}};
97108

98109
handle_event(internal, #ssh_msg_kex_dh_gex_request_old{} = Msg, {key_exchange,server,ReNeg}, D) ->
110+
ok = check_kex_strict(Msg, D),
99111
{ok, GexGroup, Ssh1} = ssh_transport:handle_kex_dh_gex_request(Msg, D#data.ssh_params),
100112
ssh_connection_handler:send_bytes(GexGroup, D),
101113
Ssh = ssh_transport:parallell_gen_key(Ssh1),
102114
{next_state, {key_exchange_dh_gex_init,server,ReNeg}, D#data{ssh_params=Ssh}};
103115

104116
handle_event(internal, #ssh_msg_kex_dh_gex_group{} = Msg, {key_exchange,client,ReNeg}, D) ->
117+
ok = check_kex_strict(Msg, D),
105118
{ok, KexGexInit, Ssh} = ssh_transport:handle_kex_dh_gex_group(Msg, D#data.ssh_params),
106119
ssh_connection_handler:send_bytes(KexGexInit, D),
107120
{next_state, {key_exchange_dh_gex_reply,client,ReNeg}, D#data{ssh_params=Ssh}};
108121

109122
%%%---- elliptic curve diffie-hellman
110123
handle_event(internal, #ssh_msg_kex_ecdh_init{} = Msg, {key_exchange,server,ReNeg}, D) ->
124+
ok = check_kex_strict(Msg, D),
111125
{ok, KexEcdhReply, Ssh1} = ssh_transport:handle_kex_ecdh_init(Msg, D#data.ssh_params),
112126
ssh_connection_handler:send_bytes(KexEcdhReply, D),
113127
{ok, NewKeys, Ssh2} = ssh_transport:new_keys_message(Ssh1),
@@ -117,37 +131,59 @@ handle_event(internal, #ssh_msg_kex_ecdh_init{} = Msg, {key_exchange,server,ReNe
117131
{next_state, {new_keys,server,ReNeg}, D#data{ssh_params=Ssh}};
118132

119133
handle_event(internal, #ssh_msg_kex_ecdh_reply{} = Msg, {key_exchange,client,ReNeg}, D) ->
134+
ok = check_kex_strict(Msg, D),
120135
{ok, NewKeys, Ssh1} = ssh_transport:handle_kex_ecdh_reply(Msg, D#data.ssh_params),
121136
ssh_connection_handler:send_bytes(NewKeys, D),
122137
{ok, ExtInfo, Ssh} = ssh_transport:ext_info_message(Ssh1),
123138
ssh_connection_handler:send_bytes(ExtInfo, D),
124139
{next_state, {new_keys,client,ReNeg}, D#data{ssh_params=Ssh}};
125140

141+
%%% ######## handle KEX strict
142+
handle_event(internal, _Event, {key_exchange,_Role,init},
143+
#data{ssh_params = #ssh{algorithms = #alg{kex_strict_negotiated = true},
144+
send_sequence = SendSeq,
145+
recv_sequence = RecvSeq}}) ->
146+
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
147+
io_lib:format("KEX strict violation: send_sequence = ~p recv_sequence = ~p",
148+
[SendSeq, RecvSeq]));
126149

127150
%%% ######## {key_exchange_dh_gex_init, server, init|renegotiate} ####
128-
129151
handle_event(internal, #ssh_msg_kex_dh_gex_init{} = Msg, {key_exchange_dh_gex_init,server,ReNeg}, D) ->
152+
ok = check_kex_strict(Msg, D),
130153
{ok, KexGexReply, Ssh1} = ssh_transport:handle_kex_dh_gex_init(Msg, D#data.ssh_params),
131154
ssh_connection_handler:send_bytes(KexGexReply, D),
132155
{ok, NewKeys, Ssh2} = ssh_transport:new_keys_message(Ssh1),
133156
ssh_connection_handler:send_bytes(NewKeys, D),
134157
{ok, ExtInfo, Ssh} = ssh_transport:ext_info_message(Ssh2),
135158
ssh_connection_handler:send_bytes(ExtInfo, D),
136159
{next_state, {new_keys,server,ReNeg}, D#data{ssh_params=Ssh}};
137-
160+
%%% ######## handle KEX strict
161+
handle_event(internal, _Event, {key_exchange_dh_gex_init,_Role,init},
162+
#data{ssh_params = #ssh{algorithms = #alg{kex_strict_negotiated = true},
163+
send_sequence = SendSeq,
164+
recv_sequence = RecvSeq}}) ->
165+
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
166+
io_lib:format("KEX strict violation: send_sequence = ~p recv_sequence = ~p",
167+
[SendSeq, RecvSeq]));
138168

139169
%%% ######## {key_exchange_dh_gex_reply, client, init|renegotiate} ####
140-
141170
handle_event(internal, #ssh_msg_kex_dh_gex_reply{} = Msg, {key_exchange_dh_gex_reply,client,ReNeg}, D) ->
171+
ok = check_kex_strict(Msg, D),
142172
{ok, NewKeys, Ssh1} = ssh_transport:handle_kex_dh_gex_reply(Msg, D#data.ssh_params),
143173
ssh_connection_handler:send_bytes(NewKeys, D),
144174
{ok, ExtInfo, Ssh} = ssh_transport:ext_info_message(Ssh1),
145175
ssh_connection_handler:send_bytes(ExtInfo, D),
146176
{next_state, {new_keys,client,ReNeg}, D#data{ssh_params=Ssh}};
147-
177+
%%% ######## handle KEX strict
178+
handle_event(internal, _Event, {key_exchange_dh_gex_reply,_Role,init},
179+
#data{ssh_params = #ssh{algorithms = #alg{kex_strict_negotiated = true},
180+
send_sequence = SendSeq,
181+
recv_sequence = RecvSeq}}) ->
182+
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
183+
io_lib:format("KEX strict violation: send_sequence = ~p recv_sequence = ~p",
184+
[SendSeq, RecvSeq]));
148185

149186
%%% ######## {new_keys, client|server} ####
150-
151187
%% First key exchange round:
152188
handle_event(internal, #ssh_msg_newkeys{} = Msg, {new_keys,client,init}, D0) ->
153189
{ok, Ssh1} = ssh_transport:handle_new_keys(Msg, D0#data.ssh_params),
@@ -163,6 +199,15 @@ handle_event(internal, #ssh_msg_newkeys{} = Msg, {new_keys,server,init}, D) ->
163199
%% ssh_connection_handler:send_bytes(ExtInfo, D),
164200
{next_state, {ext_info,server,init}, D#data{ssh_params=Ssh}};
165201

202+
%%% ######## handle KEX strict
203+
handle_event(internal, _Event, {new_keys,_Role,init},
204+
#data{ssh_params = #ssh{algorithms = #alg{kex_strict_negotiated = true},
205+
send_sequence = SendSeq,
206+
recv_sequence = RecvSeq}}) ->
207+
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
208+
io_lib:format("KEX strict violation (send_sequence = ~p recv_sequence = ~p)",
209+
[SendSeq, RecvSeq]));
210+
166211
%% Subsequent key exchange rounds (renegotiation):
167212
handle_event(internal, #ssh_msg_newkeys{} = Msg, {new_keys,Role,renegotiate}, D) ->
168213
{ok, Ssh} = ssh_transport:handle_new_keys(Msg, D#data.ssh_params),
@@ -184,7 +229,6 @@ handle_event(internal, #ssh_msg_ext_info{}=Msg, {ext_info,Role,renegotiate}, D0)
184229
handle_event(internal, #ssh_msg_newkeys{}=Msg, {ext_info,_Role,renegotiate}, D) ->
185230
{ok, Ssh} = ssh_transport:handle_new_keys(Msg, D#data.ssh_params),
186231
{keep_state, D#data{ssh_params = Ssh}};
187-
188232

189233
handle_event(internal, Msg, {ext_info,Role,init}, D) when is_tuple(Msg) ->
190234
%% If something else arrives, goto next state and handle the event in that one
@@ -218,3 +262,70 @@ code_change(_OldVsn, StateName, State, _Extra) ->
218262
peer_role(client) -> server;
219263
peer_role(server) -> client.
220264

265+
check_kex_strict(Msg,
266+
#data{ssh_params =
267+
#ssh{algorithms =
268+
#alg{
269+
kex = Kex,
270+
kex_strict_negotiated = KexStrictNegotiated},
271+
send_sequence = SendSeq,
272+
recv_sequence = RecvSeq}}) ->
273+
case check_msg_group(Msg, get_alg_group(Kex), KexStrictNegotiated) of
274+
ok ->
275+
ok;
276+
error ->
277+
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
278+
io_lib:format("KEX strict violation: send_sequence = ~p recv_sequence = ~p",
279+
[SendSeq, RecvSeq]))
280+
end.
281+
282+
get_alg_group(Kex) when Kex == 'diffie-hellman-group16-sha512';
283+
Kex == 'diffie-hellman-group18-sha512';
284+
Kex == 'diffie-hellman-group14-sha256';
285+
Kex == 'diffie-hellman-group14-sha1';
286+
Kex == 'diffie-hellman-group1-sha1' ->
287+
dh_alg;
288+
get_alg_group(Kex) when Kex == 'diffie-hellman-group-exchange-sha256';
289+
Kex == 'diffie-hellman-group-exchange-sha1' ->
290+
dh_gex_alg;
291+
get_alg_group(Kex) when Kex == 'curve25519-sha256';
292+
293+
Kex == 'curve448-sha512';
294+
Kex == 'ecdh-sha2-nistp521';
295+
Kex == 'ecdh-sha2-nistp384';
296+
Kex == 'ecdh-sha2-nistp256' ->
297+
ecdh_alg.
298+
299+
check_msg_group(_Msg, _AlgGroup, false) -> ok;
300+
check_msg_group(#ssh_msg_kexdh_init{}, dh_alg, true) -> ok;
301+
check_msg_group(#ssh_msg_kexdh_reply{}, dh_alg, true) -> ok;
302+
check_msg_group(#ssh_msg_kex_dh_gex_request_old{}, dh_gex_alg, true) -> ok;
303+
check_msg_group(#ssh_msg_kex_dh_gex_request{}, dh_gex_alg, true) -> ok;
304+
check_msg_group(#ssh_msg_kex_dh_gex_group{}, dh_gex_alg, true) -> ok;
305+
check_msg_group(#ssh_msg_kex_dh_gex_init{}, dh_gex_alg, true) -> ok;
306+
check_msg_group(#ssh_msg_kex_dh_gex_reply{}, dh_gex_alg, true) -> ok;
307+
check_msg_group(#ssh_msg_kex_ecdh_init{}, ecdh_alg, true) -> ok;
308+
check_msg_group(#ssh_msg_kex_ecdh_reply{}, ecdh_alg, true) -> ok;
309+
check_msg_group(_Msg, _AlgGroup, _) -> error.
310+
311+
%%%################################################################
312+
%%%#
313+
%%%# Tracing
314+
%%%#
315+
316+
ssh_dbg_trace_points() -> [connection_events].
317+
318+
ssh_dbg_flags(connection_events) -> [c].
319+
320+
ssh_dbg_on(connection_events) -> dbg:tp(?MODULE, handle_event, 4, x).
321+
322+
ssh_dbg_off(connection_events) -> dbg:ctpg(?MODULE, handle_event, 4).
323+
324+
ssh_dbg_format(connection_events, {call, {?MODULE,handle_event, [EventType, EventContent, State, _Data]}}) ->
325+
["Connection event\n",
326+
io_lib:format("[~w] EventType: ~p~nEventContent: ~p~nState: ~p~n", [?MODULE, EventType, EventContent, State])
327+
];
328+
ssh_dbg_format(connection_events, {return_from, {?MODULE,handle_event,4}, Ret}) ->
329+
["Connection event result\n",
330+
io_lib:format("[~w] ~p~n", [?MODULE, ssh_dbg:reduce_state(Ret, #data{})])
331+
].

lib/ssh/src/ssh_transport.erl

Lines changed: 8 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -27,12 +27,11 @@
2727

2828
-include_lib("public_key/include/public_key.hrl").
2929
-include_lib("kernel/include/inet.hrl").
30-
3130
-include("ssh_transport.hrl").
3231
-include("ssh.hrl").
3332

3433
-export([versions/2, hello_version_msg/1]).
35-
-export([next_seqnum/1,
34+
-export([next_seqnum/3,
3635
supported_algorithms/0, supported_algorithms/1,
3736
default_algorithms/0, default_algorithms/1,
3837
clear_default_algorithms_env/0,
@@ -296,7 +295,12 @@ random_id(Nlo, Nup) ->
296295
hello_version_msg(Data) ->
297296
[Data,"\r\n"].
298297

299-
next_seqnum(SeqNum) ->
298+
next_seqnum({State, _Role, init}, 16#ffffffff,
299+
#ssh{algorithms = #alg{kex_strict_negotiated = true}})
300+
when State == kexinit; State == key_exchange; State == new_keys ->
301+
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
302+
io_lib:format("KEX strict violation: recv_sequence = 16#ffffffff", []));
303+
next_seqnum(_State, SeqNum, _) ->
300304
(SeqNum + 1) band 16#ffffffff.
301305

302306
is_valid_mac(_, _ , #ssh{recv_mac_size = 0}) ->
@@ -1081,7 +1085,7 @@ known_host_key(#ssh{opts = Opts, peer = {PeerName,{IP,Port}}} = Ssh,
10811085
%% algorithm. Each string MUST contain at least one algorithm name.
10821086
select_algorithm(Role, Client, Server,
10831087
#ssh{opts = Opts,
1084-
kex_strict_negotiated = KexStrictNegotiated0},
1088+
kex_strict_negotiated = KexStrictNegotiated0},
10851089
ReNeg) ->
10861090
KexStrictNegotiated =
10871091
case ReNeg of
@@ -1106,7 +1110,6 @@ select_algorithm(Role, Client, Server,
11061110
_ ->
11071111
KexStrictNegotiated0
11081112
end,
1109-
11101113
{Encrypt0, Decrypt0} = select_encrypt_decrypt(Role, Client, Server),
11111114
{SendMac0, RecvMac0} = select_send_recv_mac(Role, Client, Server),
11121115

0 commit comments

Comments
 (0)