Skip to content

Commit 7cd7abb

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 c388a2d commit 7cd7abb

File tree

6 files changed

+151
-81
lines changed

6 files changed

+151
-81
lines changed

lib/ssh/src/ssh_connection.erl

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -769,10 +769,9 @@ handle_msg(Msg, Connection, server, Ssh = #ssh{authenticated = false}) ->
769769
%% respond by disconnecting, preferably with a proper disconnect message
770770
%% sent to ease troubleshooting.
771771
MsgFun = fun(M) ->
772-
MaxLogItemLen = ?GET_OPT(max_log_item_len, Ssh#ssh.opts),
773772
io_lib:format("Connection terminated. Unexpected message for unauthenticated user."
774773
" Message: ~w", [M],
775-
[{chars_limit, MaxLogItemLen}])
774+
[{chars_limit, ssh_lib:max_log_len(Ssh)}])
776775
end,
777776
?LOG_DEBUG(MsgFun, [Msg]),
778777
{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
@@ -1173,12 +1173,21 @@ handle_event(info, {Proto, Sock, NewData}, StateName,
11731173
{next_event, internal, Msg}
11741174
]}
11751175
catch
1176-
C:E:ST ->
1177-
MaxLogItemLen = ?GET_OPT(max_log_item_len,SshParams#ssh.opts),
1176+
Class:Reason0:Stacktrace ->
1177+
Reason = ssh_lib:trim_reason(Reason0),
1178+
MsgFun =
1179+
fun(debug) ->
1180+
io_lib:format("Bad packet: Decrypted, but can't decode~n~p:~p~n~p",
1181+
[Class,Reason,Stacktrace],
1182+
[{chars_limit, ssh_lib:max_log_len(SshParams)}]);
1183+
(_) ->
1184+
io_lib:format("Bad packet: Decrypted, but can't decode ~p:~p",
1185+
[Class, Reason],
1186+
[{chars_limit, ssh_lib:max_log_len(SshParams)}])
1187+
end,
11781188
{Shutdown, D} =
11791189
?send_disconnect(?SSH_DISCONNECT_PROTOCOL_ERROR,
1180-
io_lib:format("Bad packet: Decrypted, but can't decode~n~p:~p~n~p",
1181-
[C,E,ST], [{chars_limit, MaxLogItemLen}]),
1190+
?SELECT_MSG(MsgFun),
11821191
StateName, D1),
11831192
{stop, Shutdown, D}
11841193
end;
@@ -1208,12 +1217,20 @@ handle_event(info, {Proto, Sock, NewData}, StateName,
12081217
StateName, D0),
12091218
{stop, Shutdown, D}
12101219
catch
1211-
C:E:ST ->
1212-
MaxLogItemLen = ?GET_OPT(max_log_item_len,SshParams#ssh.opts),
1220+
Class:Reason0:Stacktrace ->
1221+
MsgFun =
1222+
fun(debug) ->
1223+
io_lib:format("Bad packet: Couldn't decrypt~n~p:~p~n~p",
1224+
[Class,Reason0,Stacktrace],
1225+
[{chars_limit, ssh_lib:max_log_len(SshParams)}]);
1226+
(_) ->
1227+
Reason = ssh_lib:trim_reason(Reason0),
1228+
io_lib:format("Bad packet: Couldn't decrypt~n~p:~p",
1229+
[Class,Reason],
1230+
[{chars_limit, ssh_lib:max_log_len(SshParams)}])
1231+
end,
12131232
{Shutdown, D} =
1214-
?send_disconnect(?SSH_DISCONNECT_PROTOCOL_ERROR,
1215-
io_lib:format("Bad packet: Couldn't decrypt~n~p:~p~n~p",
1216-
[C,E,ST], [{chars_limit, MaxLogItemLen}]),
1233+
?send_disconnect(?SSH_DISCONNECT_PROTOCOL_ERROR, ?SELECT_MSG(MsgFun),
12171234
StateName, D0),
12181235
{stop, Shutdown, D}
12191236
end;

lib/ssh/src/ssh_lib.erl

Lines changed: 17 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -31,7 +31,9 @@
3131
format_time_ms/1,
3232
comp/2,
3333
set_label/1,
34-
set_label/2
34+
set_label/2,
35+
trim_reason/1,
36+
max_log_len/1
3537
]).
3638

3739
-include("ssh.hrl").
@@ -97,3 +99,17 @@ set_label(client, Details) ->
9799
proc_lib:set_label({sshc, Details});
98100
set_label(server, Details) ->
99101
proc_lib:set_label({sshd, Details}).
102+
103+
%% We don't want to process badmatch details, potentially containing
104+
%% malicious data of unknown size
105+
trim_reason({badmatch, V}) when is_binary(V) ->
106+
badmatch;
107+
trim_reason(E) ->
108+
E.
109+
110+
max_log_len(#ssh{opts = Opts}) ->
111+
?GET_OPT(max_log_item_len, Opts);
112+
max_log_len(Opts) when is_map(Opts) ->
113+
?GET_OPT(max_log_item_len, Opts).
114+
115+

lib/ssh/src/ssh_message.erl

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

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

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

843853

844854
%%%================================================================

lib/ssh/src/ssh_transport.erl

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

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

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

451459
alg_info(client, Alg) ->
@@ -597,14 +605,19 @@ handle_kexdh_init(#ssh_msg_kexdh_init{e = E},
597605
session_id = sid(Ssh1, H)}};
598606
{error,unsupported_sign_alg} ->
599607
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
600-
io_lib:format("Unsupported algorithm ~p", [SignAlg])
601-
)
608+
io_lib:format("Unsupported algorithm ~p", [SignAlg],
609+
[{chars_limit, ssh_lib:max_log_len(Opts)}]))
602610
end;
603611
true ->
604-
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
612+
MsgFun =
613+
fun(debug) ->
605614
io_lib:format("Kexdh init failed, received 'e' out of bounds~n E=~p~n P=~p",
606-
[E,P])
607-
)
615+
[E,P], [{chars_limit, ssh_lib:max_log_len(Opts)}]);
616+
(_) ->
617+
io_lib:format("Kexdh init failed, received 'e' out of bounds", [],
618+
[{chars_limit, ssh_lib:max_log_len(Opts)}] )
619+
end,
620+
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED, ?SELECT_MSG(MsgFun))
608621
end.
609622

610623
handle_kexdh_reply(#ssh_msg_kexdh_reply{public_host_key = PeerPubHostKey,
@@ -625,14 +638,15 @@ handle_kexdh_reply(#ssh_msg_kexdh_reply{public_host_key = PeerPubHostKey,
625638
session_id = sid(Ssh, H)})};
626639
Error ->
627640
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
628-
io_lib:format("Kexdh init failed. Verify host key: ~p",[Error])
641+
io_lib:format("Kexdh init failed. Verify host key: ~p",[Error],
642+
[{chars_limit, ssh_lib:max_log_len(Ssh0)}])
629643
)
630644
end;
631645

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

@@ -658,7 +672,8 @@ handle_kex_dh_gex_request(#ssh_msg_kex_dh_gex_request{min = Min0,
658672
}};
659673
{error,_} ->
660674
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
661-
io_lib:format("No possible diffie-hellman-group-exchange group found",[])
675+
io_lib:format("No possible diffie-hellman-group-exchange group found",[],
676+
[{chars_limit, ssh_lib:max_log_len(Opts)}])
662677
)
663678
end;
664679

@@ -690,8 +705,8 @@ handle_kex_dh_gex_request(#ssh_msg_kex_dh_gex_request_old{n = NBits},
690705
}};
691706
{error,_} ->
692707
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
693-
io_lib:format("No possible diffie-hellman-group-exchange group found",[])
694-
)
708+
io_lib:format("No possible diffie-hellman-group-exchange group found",[],
709+
[{chars_limit, ssh_lib:max_log_len(Opts)}]))
695710
end;
696711

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

@@ -748,19 +762,22 @@ handle_kex_dh_gex_init(#ssh_msg_kex_dh_gex_init{e = E},
748762
}};
749763
{error,unsupported_sign_alg} ->
750764
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
751-
io_lib:format("Unsupported algorithm ~p", [SignAlg])
752-
)
765+
io_lib:format("Unsupported algorithm ~p", [SignAlg],
766+
[{chars_limit, ssh_lib:max_log_len(Opts)}]))
753767
end;
754768
true ->
755769
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
756-
"Kexdh init failed, received 'k' out of bounds"
757-
)
770+
"Kexdh init failed, received 'k' out of bounds")
758771
end;
759772
true ->
760-
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
761-
io_lib:format("Kexdh gex init failed, received 'e' out of bounds~n E=~p~n P=~p",
762-
[E,P])
763-
)
773+
MsgFun =
774+
fun(debug) ->
775+
io_lib:format("Kexdh gex init failed, received 'e' out of bounds~n"
776+
" E=~p~n P=~p", [E,P]);
777+
(_) ->
778+
io_lib:format("Kexdh gex init failed, received 'e' out of bounds", [])
779+
end,
780+
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED, ?SELECT_MSG(MsgFun))
764781
end.
765782

766783
handle_kex_dh_gex_reply(#ssh_msg_kex_dh_gex_reply{public_host_key = PeerPubHostKey,
@@ -785,20 +802,18 @@ handle_kex_dh_gex_reply(#ssh_msg_kex_dh_gex_reply{public_host_key = PeerPubHostK
785802
session_id = sid(Ssh, H)})};
786803
Error ->
787804
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
788-
io_lib:format("Kexdh gex reply failed. Verify host key: ~p",[Error])
789-
)
805+
io_lib:format("Kexdh gex reply failed. Verify host key: ~p",
806+
[Error], [{chars_limit, ssh_lib:max_log_len(Ssh0)}]))
790807
end;
791808

792809
true ->
793810
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
794-
"Kexdh gex init failed, 'K' out of bounds"
795-
)
811+
"Kexdh gex init failed, 'K' out of bounds")
796812
end;
797813
true ->
798814
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
799815
io_lib:format("Kexdh gex init failed, received 'f' out of bounds~n F=~p~n P=~p",
800-
[F,P])
801-
)
816+
[F,P], [{chars_limit, ssh_lib:max_log_len(Ssh0)}]))
802817
end.
803818

804819
%%%----------------------------------------------------------------
@@ -832,17 +847,25 @@ handle_kex_ecdh_init(#ssh_msg_kex_ecdh_init{q_c = PeerPublic},
832847
session_id = sid(Ssh1, H)}};
833848
{error,unsupported_sign_alg} ->
834849
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
835-
io_lib:format("Unsupported algorithm ~p", [SignAlg])
836-
)
850+
io_lib:format("Unsupported algorithm ~p", [SignAlg],
851+
[{chars_limit, ssh_lib:max_log_len(Opts)}]))
837852
end
838853
catch
839-
Class:Error ->
840-
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
854+
Class:Reason0 ->
855+
Reason = ssh_lib:trim_reason(Reason0),
856+
MsgFun =
857+
fun(debug) ->
841858
io_lib:format("ECDH compute key failed in server: ~p:~p~n"
842859
"Kex: ~p, Curve: ~p~n"
843860
"PeerPublic: ~p",
844-
[Class,Error,Kex,Curve,PeerPublic])
845-
)
861+
[Class,Reason,Kex,Curve,PeerPublic],
862+
[{chars_limit, ssh_lib:max_log_len(Ssh0)}]);
863+
(_) ->
864+
io_lib:format("ECDH compute key failed in server: ~p:~p",
865+
[Class,Reason],
866+
[{chars_limit, ssh_lib:max_log_len(Ssh0)}])
867+
end,
868+
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED, ?SELECT_MSG(MsgFun))
846869
end.
847870

848871
handle_kex_ecdh_reply(#ssh_msg_kex_ecdh_reply{public_host_key = PeerPubHostKey,
@@ -865,15 +888,14 @@ handle_kex_ecdh_reply(#ssh_msg_kex_ecdh_reply{public_host_key = PeerPubHostKey,
865888
session_id = sid(Ssh, H)})};
866889
Error ->
867890
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
868-
io_lib:format("ECDH reply failed. Verify host key: ~p",[Error])
869-
)
891+
io_lib:format("ECDH reply failed. Verify host key: ~p",[Error],
892+
[{chars_limit, ssh_lib:max_log_len(Ssh0)}]))
870893
end
871894
catch
872895
Class:Error ->
873896
?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
874897
io_lib:format("Peer ECDH public key seem invalid: ~p:~p",
875-
[Class,Error])
876-
)
898+
[Class,Error], [{chars_limit, ssh_lib:max_log_len(Ssh0)}]))
877899
end.
878900

879901

0 commit comments

Comments
 (0)