Skip to content

Commit ecf4e0c

Browse files
committed
Fix ssh_compat_SUITE
1 parent 2af7bcc commit ecf4e0c

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

44 files changed

+901
-373
lines changed

lib/ssh/src/ssh.hrl

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1221,6 +1221,7 @@ Experimental options that should not to be used in products.
12211221
recv_ext_info, %% Expect ext-info from peer
12221222

12231223
kex_strict_negotiated = false,
1224+
ignore_next_kex_message = false, %% RFC 4253 section 7, peer's guess was wrong
12241225

12251226
algorithms, %% #alg{}
12261227

lib/ssh/src/ssh_fsm_kexinit.erl

Lines changed: 21 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -81,6 +81,27 @@ handle_event(internal, {#ssh_msg_kexinit{}=Kex, Payload}, {kexinit,Role,ReNeg},
8181
{next_state, {key_exchange,Role,ReNeg}, D#data{ssh_params=Ssh}};
8282

8383
%%% ######## {key_exchange, client|server, init|renegotiate} ####
84+
%%%---- RFC 4253 section 7 guess was wrong
85+
handle_event(internal, Msg, {key_exchange,server,_ReNeg},
86+
D = #data{ssh_params = Ssh0 = #ssh{ignore_next_kex_message = true}}) when
87+
is_record(Msg, ssh_msg_kexdh_init);
88+
is_record(Msg, ssh_msg_kex_dh_gex_request);
89+
is_record(Msg, ssh_msg_kex_dh_gex_request_old);
90+
is_record(Msg, ssh_msg_kex_ecdh_init) ->
91+
DebugMsg = ["server ignored ", element(1, Msg), " message due to wrong guess."],
92+
logger:debug(lists:concat(DebugMsg)),
93+
Ssh = Ssh0#ssh{ignore_next_kex_message = false},
94+
{keep_state, D#data{ssh_params = Ssh}};
95+
handle_event(internal, Msg, {key_exchange,client,_ReNeg},
96+
D = #data{ssh_params = Ssh0 = #ssh{ignore_next_kex_message = true}}) when
97+
is_record(Msg, ssh_msg_kexdh_reply);
98+
is_record(Msg, ssh_msg_kex_dh_gex_group);
99+
is_record(Msg, ssh_msg_kex_dh_gex_reply);
100+
is_record(Msg, ssh_msg_kex_ecdh_reply) ->
101+
DebugMsg = ["client ignored ", element(1, Msg), " message due to wrong guess."],
102+
logger:debug(lists:concat(DebugMsg)),
103+
Ssh = Ssh0#ssh{ignore_next_kex_message = false},
104+
{keep_state, D#data{ssh_params = Ssh}};
84105
%%%---- diffie-hellman
85106
handle_event(internal, #ssh_msg_kexdh_init{} = Msg, {key_exchange,server,ReNeg}, D) ->
86107
ok = check_kex_strict(Msg, D),

lib/ssh/src/ssh_transport.erl

Lines changed: 40 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -397,7 +397,7 @@ new_keys_message(Ssh0) ->
397397
{ok, SshPacket, Ssh}.
398398

399399

400-
handle_kexinit_msg(#ssh_msg_kexinit{} = CounterPart, #ssh_msg_kexinit{} = Own,
400+
handle_kexinit_msg(#ssh_msg_kexinit{first_kex_packet_follows = CounterGuess} = CounterPart, #ssh_msg_kexinit{} = Own,
401401
#ssh{role = client} = Ssh, ReNeg) ->
402402
try
403403
{ok, Algorithms} =
@@ -407,16 +407,17 @@ handle_kexinit_msg(#ssh_msg_kexinit{} = CounterPart, #ssh_msg_kexinit{} = Own,
407407
Algorithms
408408
of
409409
Algos ->
410+
IsGuessWrong = is_guess_wrong(CounterGuess, CounterPart, Own),
410411
key_exchange_first_msg(Algos#alg.kex,
411-
Ssh#ssh{algorithms = Algos})
412+
Ssh#ssh{algorithms = Algos, ignore_next_kex_message = IsGuessWrong})
412413
catch
413414
Class:Reason0 ->
414415
Reason = ssh_lib:trim_reason(Reason0),
415416
Msg = kexinit_error(Class, Reason, client, Own, CounterPart, Ssh),
416417
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED, Msg)
417418
end;
418419

419-
handle_kexinit_msg(#ssh_msg_kexinit{} = CounterPart, #ssh_msg_kexinit{} = Own,
420+
handle_kexinit_msg(#ssh_msg_kexinit{first_kex_packet_follows = CounterGuess} = CounterPart, #ssh_msg_kexinit{} = Own,
420421
#ssh{role = server} = Ssh, ReNeg) ->
421422
try
422423
{ok, Algorithms} =
@@ -426,14 +427,44 @@ handle_kexinit_msg(#ssh_msg_kexinit{} = CounterPart, #ssh_msg_kexinit{} = Own,
426427
Algorithms
427428
of
428429
Algos ->
429-
{ok, Ssh#ssh{algorithms = Algos}}
430+
IsGuessWrong = is_guess_wrong(CounterGuess, CounterPart, Own),
431+
{ok, Ssh#ssh{algorithms = Algos, ignore_next_kex_message = IsGuessWrong}}
430432
catch
431433
Class:Reason0 ->
432434
Reason = ssh_lib:trim_reason(Reason0),
433435
Msg = kexinit_error(Class, Reason, server, Own, CounterPart, Ssh),
434436
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED, Msg)
435437
end.
436438

439+
%% RFC 4253 section 7 check if guess is wrong
440+
is_guess_wrong(false, _, _) ->
441+
false;
442+
is_guess_wrong(true, CounterPart, Own) ->
443+
CounterPreferredKexAlgo = get_preferred_kex_algorithm(CounterPart),
444+
OwnPreferredKexAlgo = get_preferred_kex_algorithm(Own),
445+
CounterPreferredHostKeyAlgo = get_preferred_host_key_algorithm(CounterPart),
446+
OwnPreferredHostKeyAlgo = get_preferred_host_key_algorithm(Own),
447+
448+
is_different_algorithm(CounterPreferredKexAlgo, OwnPreferredKexAlgo) orelse
449+
is_different_algorithm(CounterPreferredHostKeyAlgo, OwnPreferredHostKeyAlgo).
450+
451+
is_different_algorithm(none, none) ->
452+
false;
453+
is_different_algorithm(Same, Same) ->
454+
false;
455+
is_different_algorithm(_, _) ->
456+
true.
457+
458+
get_preferred_kex_algorithm(#ssh_msg_kexinit{kex_algorithms = [Preferred | _]}) ->
459+
Preferred;
460+
get_preferred_kex_algorithm(_) ->
461+
none.
462+
463+
get_preferred_host_key_algorithm(#ssh_msg_kexinit{server_host_key_algorithms = [Preferred | _]}) ->
464+
Preferred;
465+
get_preferred_host_key_algorithm(_) ->
466+
none.
467+
437468
kexinit_error(Class, Error, Role, Own, CounterPart, Ssh) ->
438469
{Fmt,Args} =
439470
case {Class,Error} of
@@ -2211,7 +2242,11 @@ parallell_gen_key(Ssh = #ssh{keyex_key = {x, {G, P}},
22112242
generate_key(ecdh, Args) ->
22122243
crypto:generate_key(ecdh, Args);
22132244
generate_key(dh, [P,G,Sz2]) ->
2214-
{Public,Private} = crypto:generate_key(dh, [P, G, max(Sz2,?MIN_DH_KEY_SIZE)] ),
2245+
BitSize = fun(N) -> bit_size(binary:encode_unsigned(N)) end,
2246+
{Public,Private} =
2247+
crypto:generate_key(dh,
2248+
[P, G, max(min(BitSize(P)-1, Sz2),
2249+
?MIN_DH_KEY_SIZE)]),
22152250
{crypto:bytes_to_integer(Public), crypto:bytes_to_integer(Private)}.
22162251

22172252

0 commit comments

Comments
 (0)