Skip to content

Commit 548f129

Browse files
committed
ssh: key exchange robustness improvements
- reduce untrusted data processing for non-debug logs - trim badmatch exceptions to avoid processing potentially malicious data - terminate with kexinit_error when too many algorithms are received in KEX init message
1 parent c1ce39f commit 548f129

File tree

6 files changed

+147
-80
lines changed

6 files changed

+147
-80
lines changed

lib/ssh/src/ssh_connection.erl

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -481,10 +481,9 @@ handle_msg(Msg, Connection, server, Ssh = #ssh{authenticated = false}) ->
481481
%% respond by disconnecting, preferably with a proper disconnect message
482482
%% sent to ease troubleshooting.
483483
MsgFun = fun(M) ->
484-
MaxLogItemLen = ?GET_OPT(max_log_item_len, Ssh#ssh.opts),
485484
io_lib:format("Connection terminated. Unexpected message for unauthenticated user."
486485
" Message: ~w", [M],
487-
[{chars_limit, MaxLogItemLen}])
486+
[{chars_limit, ssh_lib:max_log_len(Ssh)}])
488487
end,
489488
?LOG_DEBUG(MsgFun, [Msg]),
490489
{disconnect, {?SSH_DISCONNECT_PROTOCOL_ERROR, "Connection refused"}, handle_stop(Connection)};

lib/ssh/src/ssh_connection_handler.erl

Lines changed: 26 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -1182,12 +1182,21 @@ handle_event(info, {Proto, Sock, NewData}, StateName,
11821182
{next_event, internal, Msg}
11831183
]}
11841184
catch
1185-
C:E:ST ->
1186-
MaxLogItemLen = ?GET_OPT(max_log_item_len,SshParams#ssh.opts),
1185+
Class:Reason0:Stacktrace ->
1186+
Reason = ssh_lib:trim_reason(Reason0),
1187+
MsgFun =
1188+
fun(debug) ->
1189+
io_lib:format("Bad packet: Decrypted, but can't decode~n~p:~p~n~p",
1190+
[Class,Reason,Stacktrace],
1191+
[{chars_limit, ssh_lib:max_log_len(SshParams)}]);
1192+
(_) ->
1193+
io_lib:format("Bad packet: Decrypted, but can't decode ~p:~p",
1194+
[Class, Reason],
1195+
[{chars_limit, ssh_lib:max_log_len(SshParams)}])
1196+
end,
11871197
{Shutdown, D} =
11881198
?send_disconnect(?SSH_DISCONNECT_PROTOCOL_ERROR,
1189-
io_lib:format("Bad packet: Decrypted, but can't decode~n~p:~p~n~p",
1190-
[C,E,ST], [{chars_limit, MaxLogItemLen}]),
1199+
?SELECT_MSG(MsgFun),
11911200
StateName, D1),
11921201
{stop, Shutdown, D}
11931202
end;
@@ -1217,12 +1226,20 @@ handle_event(info, {Proto, Sock, NewData}, StateName,
12171226
StateName, D0),
12181227
{stop, Shutdown, D}
12191228
catch
1220-
C:E:ST ->
1221-
MaxLogItemLen = ?GET_OPT(max_log_item_len,SshParams#ssh.opts),
1229+
Class:Reason0:Stacktrace ->
1230+
MsgFun =
1231+
fun(debug) ->
1232+
io_lib:format("Bad packet: Couldn't decrypt~n~p:~p~n~p",
1233+
[Class,Reason0,Stacktrace],
1234+
[{chars_limit, ssh_lib:max_log_len(SshParams)}]);
1235+
(_) ->
1236+
Reason = ssh_lib:trim_reason(Reason0),
1237+
io_lib:format("Bad packet: Couldn't decrypt~n~p:~p",
1238+
[Class,Reason],
1239+
[{chars_limit, ssh_lib:max_log_len(SshParams)}])
1240+
end,
12221241
{Shutdown, D} =
1223-
?send_disconnect(?SSH_DISCONNECT_PROTOCOL_ERROR,
1224-
io_lib:format("Bad packet: Couldn't decrypt~n~p:~p~n~p",
1225-
[C,E,ST], [{chars_limit, MaxLogItemLen}]),
1242+
?send_disconnect(?SSH_DISCONNECT_PROTOCOL_ERROR, ?SELECT_MSG(MsgFun),
12261243
StateName, D0),
12271244
{stop, Shutdown, D}
12281245
end;

lib/ssh/src/ssh_lib.erl

Lines changed: 14 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,9 @@
2828
format_address_port/2, format_address_port/1,
2929
format_address/1,
3030
format_time_ms/1,
31-
comp/2
31+
comp/2,
32+
trim_reason/1,
33+
max_log_len/1
3234
]).
3335

3436
-include("ssh.hrl").
@@ -86,3 +88,14 @@ comp([], [], Truth) ->
8688

8789
comp(_, _, _) ->
8890
false.
91+
%% We don't want to process badmatch details, potentially containing
92+
%% malicious data of unknown size
93+
trim_reason({badmatch, V}) when is_binary(V) ->
94+
badmatch;
95+
trim_reason(E) ->
96+
E.
97+
98+
max_log_len(#ssh{opts = Opts}) ->
99+
?GET_OPT(max_log_item_len, Opts);
100+
max_log_len(Opts) when is_map(Opts) ->
101+
?GET_OPT(max_log_item_len, Opts).

lib/ssh/src/ssh_message.erl

Lines changed: 26 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -43,7 +43,7 @@
4343

4444
-behaviour(ssh_dbg).
4545
-export([ssh_dbg_trace_points/0, ssh_dbg_flags/1, ssh_dbg_on/1, ssh_dbg_off/1, ssh_dbg_format/2]).
46-
-define(ALG_NAME_LIMIT, 64).
46+
-define(ALG_NAME_LIMIT, 64). % RFC4251 sec6
4747

4848
ucl(B) ->
4949
try unicode:characters_to_list(B) of
@@ -821,23 +821,33 @@ decode_kex_init(<<?BYTE(Bool)>>, Acc, 0) ->
821821
%% See rfc 4253 7.1
822822
X = 0,
823823
list_to_tuple(lists:reverse([X, erl_boolean(Bool) | Acc]));
824-
decode_kex_init(<<?DEC_BIN(Data,__0), Rest/binary>>, Acc, N) ->
824+
decode_kex_init(<<?DEC_BIN(Data,__0), Rest/binary>>, Acc, N) when
825+
byte_size(Data) < ?MAX_NUM_ALGORITHMS * ?ALG_NAME_LIMIT ->
825826
BinParts = binary:split(Data, <<$,>>, [global]),
826-
Process =
827-
fun(<<>>, PAcc) ->
828-
PAcc;
829-
(Part, PAcc) ->
830-
case byte_size(Part) > ?ALG_NAME_LIMIT of
831-
true ->
832-
?LOG_DEBUG("Ignoring too long name", []),
827+
AlgCount = length(BinParts),
828+
case AlgCount =< ?MAX_NUM_ALGORITHMS of
829+
true ->
830+
Process =
831+
fun(<<>>, PAcc) ->
833832
PAcc;
834-
false ->
835-
Name = binary:bin_to_list(Part),
836-
[Name | PAcc]
837-
end
838-
end,
839-
Names = lists:foldr(Process, [], BinParts),
840-
decode_kex_init(Rest, [Names | Acc], N - 1).
833+
(Part, PAcc) ->
834+
case byte_size(Part) =< ?ALG_NAME_LIMIT of
835+
true ->
836+
Name = binary:bin_to_list(Part),
837+
[Name | PAcc];
838+
false ->
839+
?LOG_DEBUG("Ignoring too long name", []),
840+
PAcc
841+
end
842+
end,
843+
Names = lists:foldr(Process, [], BinParts),
844+
decode_kex_init(Rest, [Names | Acc], N - 1);
845+
false ->
846+
throw({error, {kexinit_error, N, {alg_count, AlgCount}}})
847+
end;
848+
decode_kex_init(<<?DEC_BIN(Data,__0), _Rest/binary>>, _Acc, N) ->
849+
throw({error, {kexinit, N, {string_size, byte_size(Data)}}}).
850+
841851

842852

843853
%%%================================================================

lib/ssh/src/ssh_transport.erl

Lines changed: 71 additions & 49 deletions
Original file line numberDiff line numberDiff line change
@@ -403,8 +403,9 @@ handle_kexinit_msg(#ssh_msg_kexinit{} = CounterPart, #ssh_msg_kexinit{} = Own,
403403
key_exchange_first_msg(Algos#alg.kex,
404404
Ssh#ssh{algorithms = Algos})
405405
catch
406-
Class:Error ->
407-
Msg = kexinit_error(Class, Error, client, Own, CounterPart),
406+
Class:Reason0 ->
407+
Reason = ssh_lib:trim_reason(Reason0),
408+
Msg = kexinit_error(Class, Reason, client, Own, CounterPart, Ssh),
408409
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED, Msg)
409410
end;
410411

@@ -420,31 +421,38 @@ handle_kexinit_msg(#ssh_msg_kexinit{} = CounterPart, #ssh_msg_kexinit{} = Own,
420421
Algos ->
421422
{ok, Ssh#ssh{algorithms = Algos}}
422423
catch
423-
Class:Error ->
424-
Msg = kexinit_error(Class, Error, server, Own, CounterPart),
424+
Class:Reason0 ->
425+
Reason = ssh_lib:trim_reason(Reason0),
426+
Msg = kexinit_error(Class, Reason, server, Own, CounterPart, Ssh),
425427
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED, Msg)
426428
end.
427429

428-
kexinit_error(Class, Error, Role, Own, CounterPart) ->
430+
kexinit_error(Class, Error, Role, Own, CounterPart, Ssh) ->
429431
{Fmt,Args} =
430432
case {Class,Error} of
431433
{error, {badmatch,{false,Alg}}} ->
432434
{Txt,W,C} = alg_info(Role, Alg),
433-
{"No common ~s algorithm,~n"
434-
" we have:~n ~s~n"
435-
" peer have:~n ~s~n",
436-
[Txt,
437-
lists:join(", ", element(W,Own)),
438-
lists:join(", ", element(C,CounterPart))
439-
]};
435+
MsgFun =
436+
fun(debug) ->
437+
{"No common ~s algorithm,~n"
438+
" we have:~n ~s~n"
439+
" peer have:~n ~s~n",
440+
[Txt,
441+
lists:join(", ", element(W,Own)),
442+
lists:join(", ", element(C,CounterPart))]};
443+
(_) ->
444+
{"No common ~s algorithm", [Txt]}
445+
end,
446+
?SELECT_MSG(MsgFun);
440447
_ ->
441448
{"Kexinit failed in ~p: ~p:~p", [Role,Class,Error]}
442449
end,
443-
try io_lib:format(Fmt, Args) of
450+
try io_lib:format(Fmt, Args, [{chars_limit, ssh_lib:max_log_len(Ssh)}]) of
444451
R -> R
445452
catch
446453
_:_ ->
447-
io_lib:format("Kexinit failed in ~p: ~p:~p", [Role, Class, Error])
454+
io_lib:format("Kexinit failed in ~p: ~p:~p", [Role, Class, Error],
455+
[{chars_limit, ssh_lib:max_log_len(Ssh)}])
448456
end.
449457

450458
alg_info(client, Alg) ->
@@ -596,14 +604,19 @@ handle_kexdh_init(#ssh_msg_kexdh_init{e = E},
596604
session_id = sid(Ssh1, H)}};
597605
{error,unsupported_sign_alg} ->
598606
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
599-
io_lib:format("Unsupported algorithm ~p", [SignAlg])
600-
)
607+
io_lib:format("Unsupported algorithm ~p", [SignAlg],
608+
[{chars_limit, ssh_lib:max_log_len(Opts)}]))
601609
end;
602610
true ->
603-
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
611+
MsgFun =
612+
fun(debug) ->
604613
io_lib:format("Kexdh init failed, received 'e' out of bounds~n E=~p~n P=~p",
605-
[E,P])
606-
)
614+
[E,P], [{chars_limit, ssh_lib:max_log_len(Opts)}]);
615+
(_) ->
616+
io_lib:format("Kexdh init failed, received 'e' out of bounds", [],
617+
[{chars_limit, ssh_lib:max_log_len(Opts)}] )
618+
end,
619+
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED, ?SELECT_MSG(MsgFun))
607620
end.
608621

609622
handle_kexdh_reply(#ssh_msg_kexdh_reply{public_host_key = PeerPubHostKey,
@@ -624,14 +637,15 @@ handle_kexdh_reply(#ssh_msg_kexdh_reply{public_host_key = PeerPubHostKey,
624637
session_id = sid(Ssh, H)})};
625638
Error ->
626639
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
627-
io_lib:format("Kexdh init failed. Verify host key: ~p",[Error])
640+
io_lib:format("Kexdh init failed. Verify host key: ~p",[Error],
641+
[{chars_limit, ssh_lib:max_log_len(Ssh0)}])
628642
)
629643
end;
630644

631645
true ->
632646
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
633647
io_lib:format("Kexdh init failed, received 'f' out of bounds~n F=~p~n P=~p",
634-
[F,P])
648+
[F,P], [{chars_limit, ssh_lib:max_log_len(Ssh0)}])
635649
)
636650
end.
637651

@@ -657,7 +671,8 @@ handle_kex_dh_gex_request(#ssh_msg_kex_dh_gex_request{min = Min0,
657671
}};
658672
{error,_} ->
659673
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
660-
io_lib:format("No possible diffie-hellman-group-exchange group found",[])
674+
io_lib:format("No possible diffie-hellman-group-exchange group found",[],
675+
[{chars_limit, ssh_lib:max_log_len(Opts)}])
661676
)
662677
end;
663678

@@ -689,8 +704,8 @@ handle_kex_dh_gex_request(#ssh_msg_kex_dh_gex_request_old{n = NBits},
689704
}};
690705
{error,_} ->
691706
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
692-
io_lib:format("No possible diffie-hellman-group-exchange group found",[])
693-
)
707+
io_lib:format("No possible diffie-hellman-group-exchange group found",[],
708+
[{chars_limit, ssh_lib:max_log_len(Opts)}]))
694709
end;
695710

696711
handle_kex_dh_gex_request(_, _) ->
@@ -716,7 +731,6 @@ handle_kex_dh_gex_group(#ssh_msg_kex_dh_gex_group{p = P, g = G}, Ssh0) ->
716731
{Public, Private} = generate_key(dh, [P,G,2*Sz]),
717732
{SshPacket, Ssh1} =
718733
ssh_packet(#ssh_msg_kex_dh_gex_init{e = Public}, Ssh0), % Pub = G^Priv mod P (def)
719-
720734
{ok, SshPacket,
721735
Ssh1#ssh{keyex_key = {{Private, Public}, {G, P}}}}.
722736

@@ -747,19 +761,22 @@ handle_kex_dh_gex_init(#ssh_msg_kex_dh_gex_init{e = E},
747761
}};
748762
{error,unsupported_sign_alg} ->
749763
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
750-
io_lib:format("Unsupported algorithm ~p", [SignAlg])
751-
)
764+
io_lib:format("Unsupported algorithm ~p", [SignAlg],
765+
[{chars_limit, ssh_lib:max_log_len(Opts)}]))
752766
end;
753767
true ->
754768
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
755-
"Kexdh init failed, received 'k' out of bounds"
756-
)
769+
"Kexdh init failed, received 'k' out of bounds")
757770
end;
758771
true ->
759-
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
760-
io_lib:format("Kexdh gex init failed, received 'e' out of bounds~n E=~p~n P=~p",
761-
[E,P])
762-
)
772+
MsgFun =
773+
fun(debug) ->
774+
io_lib:format("Kexdh gex init failed, received 'e' out of bounds~n"
775+
" E=~p~n P=~p", [E,P]);
776+
(_) ->
777+
io_lib:format("Kexdh gex init failed, received 'e' out of bounds", [])
778+
end,
779+
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED, ?SELECT_MSG(MsgFun))
763780
end.
764781

765782
handle_kex_dh_gex_reply(#ssh_msg_kex_dh_gex_reply{public_host_key = PeerPubHostKey,
@@ -784,20 +801,18 @@ handle_kex_dh_gex_reply(#ssh_msg_kex_dh_gex_reply{public_host_key = PeerPubHostK
784801
session_id = sid(Ssh, H)})};
785802
Error ->
786803
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
787-
io_lib:format("Kexdh gex reply failed. Verify host key: ~p",[Error])
788-
)
804+
io_lib:format("Kexdh gex reply failed. Verify host key: ~p",
805+
[Error], [{chars_limit, ssh_lib:max_log_len(Ssh0)}]))
789806
end;
790807

791808
true ->
792809
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
793-
"Kexdh gex init failed, 'K' out of bounds"
794-
)
810+
"Kexdh gex init failed, 'K' out of bounds")
795811
end;
796812
true ->
797813
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
798814
io_lib:format("Kexdh gex init failed, received 'f' out of bounds~n F=~p~n P=~p",
799-
[F,P])
800-
)
815+
[F,P], [{chars_limit, ssh_lib:max_log_len(Ssh0)}]))
801816
end.
802817

803818
%%%----------------------------------------------------------------
@@ -831,17 +846,25 @@ handle_kex_ecdh_init(#ssh_msg_kex_ecdh_init{q_c = PeerPublic},
831846
session_id = sid(Ssh1, H)}};
832847
{error,unsupported_sign_alg} ->
833848
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
834-
io_lib:format("Unsupported algorithm ~p", [SignAlg])
835-
)
849+
io_lib:format("Unsupported algorithm ~p", [SignAlg],
850+
[{chars_limit, ssh_lib:max_log_len(Opts)}]))
836851
end
837852
catch
838-
Class:Error ->
839-
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
853+
Class:Reason0 ->
854+
Reason = ssh_lib:trim_reason(Reason0),
855+
MsgFun =
856+
fun(debug) ->
840857
io_lib:format("ECDH compute key failed in server: ~p:~p~n"
841858
"Kex: ~p, Curve: ~p~n"
842859
"PeerPublic: ~p",
843-
[Class,Error,Kex,Curve,PeerPublic])
844-
)
860+
[Class,Reason,Kex,Curve,PeerPublic],
861+
[{chars_limit, ssh_lib:max_log_len(Ssh0)}]);
862+
(_) ->
863+
io_lib:format("ECDH compute key failed in server: ~p:~p",
864+
[Class,Reason],
865+
[{chars_limit, ssh_lib:max_log_len(Ssh0)}])
866+
end,
867+
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED, ?SELECT_MSG(MsgFun))
845868
end.
846869

847870
handle_kex_ecdh_reply(#ssh_msg_kex_ecdh_reply{public_host_key = PeerPubHostKey,
@@ -864,15 +887,14 @@ handle_kex_ecdh_reply(#ssh_msg_kex_ecdh_reply{public_host_key = PeerPubHostKey,
864887
session_id = sid(Ssh, H)})};
865888
Error ->
866889
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
867-
io_lib:format("ECDH reply failed. Verify host key: ~p",[Error])
868-
)
890+
io_lib:format("ECDH reply failed. Verify host key: ~p",[Error],
891+
[{chars_limit, ssh_lib:max_log_len(Ssh0)}]))
869892
end
870893
catch
871894
Class:Error ->
872895
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
873896
io_lib:format("Peer ECDH public key seem invalid: ~p:~p",
874-
[Class,Error])
875-
)
897+
[Class,Error], [{chars_limit, ssh_lib:max_log_len(Ssh0)}]))
876898
end.
877899

878900

0 commit comments

Comments
 (0)