Skip to content
Draft
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
1 change: 1 addition & 0 deletions lib/ssh/src/ssh.hrl
Original file line number Diff line number Diff line change
Expand Up @@ -1221,6 +1221,7 @@ Experimental options that should not to be used in products.
recv_ext_info, %% Expect ext-info from peer

kex_strict_negotiated = false,
ignore_next_kex_message = false, %% RFC 4253 section 7, peer's guess was wrong
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

don't mix compat test fix PR with fix for Dropbear? have separate PR for PR-8676


algorithms, %% #alg{}

Expand Down
21 changes: 21 additions & 0 deletions lib/ssh/src/ssh_fsm_kexinit.erl
Original file line number Diff line number Diff line change
Expand Up @@ -81,6 +81,27 @@ handle_event(internal, {#ssh_msg_kexinit{}=Kex, Payload}, {kexinit,Role,ReNeg},
{next_state, {key_exchange,Role,ReNeg}, D#data{ssh_params=Ssh}};

%%% ######## {key_exchange, client|server, init|renegotiate} ####
%%%---- RFC 4253 section 7 guess was wrong
handle_event(internal, Msg, {key_exchange,server,_ReNeg},
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

consider testing guessing in ssh_protocol_SUITE with ssh_trpt_lib? in theory those are possibilities:

server guesses:

  1. correctly
  2. wrongly

client guesses:

  1. correctly
  2. wrongly

flavours: DH, DH GEX, ECDH.
let's discuss it further

Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I think you should align both function clauses. both client and server can be initiating key exchange and guessing.

AFAIK, it is ignoring replies is not needed, as we discussed, right? proper implementation should not send replies if guess was wrong.

Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

fix indentation, so that eyes don't bleed that much ;-)

D = #data{ssh_params = Ssh0 = #ssh{ignore_next_kex_message = true}}) when
is_record(Msg, ssh_msg_kexdh_init);
is_record(Msg, ssh_msg_kex_dh_gex_request);
is_record(Msg, ssh_msg_kex_dh_gex_request_old);
is_record(Msg, ssh_msg_kex_ecdh_init) ->
DebugMsg = ["server ignored ", element(1, Msg), " message due to wrong guess."],
logger:debug(lists:concat(DebugMsg)),
Ssh = Ssh0#ssh{ignore_next_kex_message = false},
{keep_state, D#data{ssh_params = Ssh}};
handle_event(internal, Msg, {key_exchange,client,_ReNeg},
D = #data{ssh_params = Ssh0 = #ssh{ignore_next_kex_message = true}}) when
is_record(Msg, ssh_msg_kexdh_reply);
is_record(Msg, ssh_msg_kex_dh_gex_group);
is_record(Msg, ssh_msg_kex_dh_gex_reply);
is_record(Msg, ssh_msg_kex_ecdh_reply) ->
DebugMsg = ["client ignored ", element(1, Msg), " message due to wrong guess."],
logger:debug(lists:concat(DebugMsg)),
Ssh = Ssh0#ssh{ignore_next_kex_message = false},
{keep_state, D#data{ssh_params = Ssh}};
%%%---- diffie-hellman
handle_event(internal, #ssh_msg_kexdh_init{} = Msg, {key_exchange,server,ReNeg}, D) ->
ok = check_kex_strict(Msg, D),
Expand Down
45 changes: 40 additions & 5 deletions lib/ssh/src/ssh_transport.erl
Original file line number Diff line number Diff line change
Expand Up @@ -397,7 +397,7 @@ new_keys_message(Ssh0) ->
{ok, SshPacket, Ssh}.


handle_kexinit_msg(#ssh_msg_kexinit{} = CounterPart, #ssh_msg_kexinit{} = Own,
handle_kexinit_msg(#ssh_msg_kexinit{first_kex_packet_follows = CounterGuess} = CounterPart, #ssh_msg_kexinit{} = Own,
#ssh{role = client} = Ssh, ReNeg) ->
try
{ok, Algorithms} =
Expand All @@ -407,16 +407,17 @@ handle_kexinit_msg(#ssh_msg_kexinit{} = CounterPart, #ssh_msg_kexinit{} = Own,
Algorithms
of
Algos ->
IsGuessWrong = is_guess_wrong(CounterGuess, CounterPart, Own),
key_exchange_first_msg(Algos#alg.kex,
Ssh#ssh{algorithms = Algos})
Ssh#ssh{algorithms = Algos, ignore_next_kex_message = IsGuessWrong})
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

rename to
ignore_initial_kex_message ?

catch
Class:Reason0 ->
Reason = ssh_lib:trim_reason(Reason0),
Msg = kexinit_error(Class, Reason, client, Own, CounterPart, Ssh),
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED, Msg)
end;

handle_kexinit_msg(#ssh_msg_kexinit{} = CounterPart, #ssh_msg_kexinit{} = Own,
handle_kexinit_msg(#ssh_msg_kexinit{first_kex_packet_follows = CounterGuess} = CounterPart, #ssh_msg_kexinit{} = Own,
#ssh{role = server} = Ssh, ReNeg) ->
try
{ok, Algorithms} =
Expand All @@ -426,14 +427,44 @@ handle_kexinit_msg(#ssh_msg_kexinit{} = CounterPart, #ssh_msg_kexinit{} = Own,
Algorithms
of
Algos ->
{ok, Ssh#ssh{algorithms = Algos}}
IsGuessWrong = is_guess_wrong(CounterGuess, CounterPart, Own),
{ok, Ssh#ssh{algorithms = Algos, ignore_next_kex_message = IsGuessWrong}}
catch
Class:Reason0 ->
Reason = ssh_lib:trim_reason(Reason0),
Msg = kexinit_error(Class, Reason, server, Own, CounterPart, Ssh),
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED, Msg)
end.

%% RFC 4253 section 7 check if guess is wrong
is_guess_wrong(false, _, _) ->
false;
is_guess_wrong(true, CounterPart, Own) ->
CounterPreferredKexAlgo = get_preferred_kex_algorithm(CounterPart),
OwnPreferredKexAlgo = get_preferred_kex_algorithm(Own),
CounterPreferredHostKeyAlgo = get_preferred_host_key_algorithm(CounterPart),
OwnPreferredHostKeyAlgo = get_preferred_host_key_algorithm(Own),

is_different_algorithm(CounterPreferredKexAlgo, OwnPreferredKexAlgo) orelse
is_different_algorithm(CounterPreferredHostKeyAlgo, OwnPreferredHostKeyAlgo).

is_different_algorithm(none, none) ->
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

is this function really better than some not equal operator?

false;
is_different_algorithm(Same, Same) ->
false;
is_different_algorithm(_, _) ->
true.

get_preferred_kex_algorithm(#ssh_msg_kexinit{kex_algorithms = [Preferred | _]}) ->
Preferred;
get_preferred_kex_algorithm(_) ->
none.

get_preferred_host_key_algorithm(#ssh_msg_kexinit{server_host_key_algorithms = [Preferred | _]}) ->
Preferred;
get_preferred_host_key_algorithm(_) ->
none.
Comment on lines +458 to +466
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

combine 2 get_preferred functions into one returning tuple {Kex, Host} ?

then simplify

    is_different_algorithm(CounterPreferredKexAlgo, OwnPreferredKexAlgo) orelse
        is_different_algorithm(CounterPreferredHostKeyAlgo, OwnPreferredHostKeyAlgo).

into {Kex1, Host1} =/ {Kex2, Host2} ?


kexinit_error(Class, Error, Role, Own, CounterPart, Ssh) ->
{Fmt,Args} =
case {Class,Error} of
Expand Down Expand Up @@ -2211,7 +2242,11 @@ parallell_gen_key(Ssh = #ssh{keyex_key = {x, {G, P}},
generate_key(ecdh, Args) ->
crypto:generate_key(ecdh, Args);
generate_key(dh, [P,G,Sz2]) ->
{Public,Private} = crypto:generate_key(dh, [P, G, max(Sz2,?MIN_DH_KEY_SIZE)] ),
BitSize = fun(N) -> bit_size(binary:encode_unsigned(N)) end,
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

not needed in final PR

{Public,Private} =
crypto:generate_key(dh,
[P, G, max(min(BitSize(P)-1, Sz2),
?MIN_DH_KEY_SIZE)]),
{crypto:bytes_to_integer(Public), crypto:bytes_to_integer(Private)}.


Expand Down
Loading
Loading