Skip to content

Commit e9eaa44

Browse files
author
Erlang/OTP
committed
Merge branch 'kuba/ssh/early_rce/OTP-19595' into maint-27
* kuba/ssh/early_rce/OTP-19595: ssh: early RCE fix
2 parents 79ebb2b + 6eef041 commit e9eaa44

File tree

2 files changed

+67
-47
lines changed

2 files changed

+67
-47
lines changed

lib/ssh/src/ssh_connection.erl

Lines changed: 22 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -53,6 +53,8 @@ these messages are handled by
5353
{type,<<"Signals">>},
5454
{type,<<"Exit Status">>}]}).
5555

56+
-include_lib("kernel/include/logger.hrl").
57+
5658
-include("ssh.hrl").
5759
-include("ssh_connect.hrl").
5860
-include("ssh_transport.hrl").
@@ -756,6 +758,25 @@ channel_data(ChannelId, DataType, Data0,
756758
%%%
757759

758760
-doc false.
761+
handle_msg(#ssh_msg_disconnect{code = Code, description = Description}, Connection, _, _SSH) ->
762+
{disconnect, {Code, Description}, handle_stop(Connection)};
763+
764+
handle_msg(Msg, Connection, server, Ssh = #ssh{authenticated = false}) ->
765+
%% See RFC4252 6.
766+
%% Message numbers of 80 and higher are reserved for protocols running
767+
%% after this authentication protocol, so receiving one of them before
768+
%% authentication is complete is an error, to which the server MUST
769+
%% respond by disconnecting, preferably with a proper disconnect message
770+
%% sent to ease troubleshooting.
771+
MsgFun = fun(M) ->
772+
MaxLogItemLen = ?GET_OPT(max_log_item_len, Ssh#ssh.opts),
773+
io_lib:format("Connection terminated. Unexpected message for unauthenticated user."
774+
" Message: ~w", [M],
775+
[{chars_limit, MaxLogItemLen}])
776+
end,
777+
?LOG_DEBUG(MsgFun, [Msg]),
778+
{disconnect, {?SSH_DISCONNECT_PROTOCOL_ERROR, "Connection refused"}, handle_stop(Connection)};
779+
759780
handle_msg(#ssh_msg_channel_open_confirmation{recipient_channel = ChannelId,
760781
sender_channel = RemoteId,
761782
initial_window_size = WindowSz,
@@ -1260,12 +1281,7 @@ handle_msg(#ssh_msg_request_success{data = Data},
12601281
#connection{requests = [{_, From, Fun} | Rest]} = Connection0, _, _SSH) ->
12611282
Connection = Fun({success,Data}, Connection0),
12621283
{[{channel_request_reply, From, {success, Data}}],
1263-
Connection#connection{requests = Rest}};
1264-
1265-
handle_msg(#ssh_msg_disconnect{code = Code,
1266-
description = Description},
1267-
Connection, _, _SSH) ->
1268-
{disconnect, {Code, Description}, handle_stop(Connection)}.
1284+
Connection#connection{requests = Rest}}.
12691285

12701286

12711287
%%%----------------------------------------------------------------

lib/ssh/test/ssh_protocol_SUITE.erl

Lines changed: 45 additions & 41 deletions
Original file line numberDiff line numberDiff line change
@@ -75,6 +75,7 @@
7575
no_common_alg_client_disconnects/1,
7676
no_common_alg_server_disconnects/1,
7777
custom_kexinit/1,
78+
early_rce/1,
7879
no_ext_info_s1/1,
7980
no_ext_info_s2/1,
8081
packet_length_too_large/1,
@@ -113,6 +114,7 @@ suite() ->
113114
all() ->
114115
[{group,tool_tests},
115116
client_info_line,
117+
early_rce,
116118
{group,kex},
117119
{group,service_requests},
118120
{group,authentication},
@@ -131,10 +133,8 @@ groups() ->
131133
]},
132134
{packet_size_error, [], [packet_length_too_large,
133135
packet_length_too_short]},
134-
135136
{field_size_error, [], [service_name_length_too_large,
136137
service_name_length_too_short]},
137-
138138
{kex, [], [custom_kexinit,
139139
no_common_alg_server_disconnects,
140140
no_common_alg_client_disconnects,
@@ -178,7 +178,8 @@ init_per_suite(Config) ->
178178
end_per_suite(Config) ->
179179
stop_apps(Config).
180180

181-
init_per_testcase(Tc, Config) when Tc == no_common_alg_server_disconnects; Tc == custom_kexinit ->
181+
init_per_testcase(Tc, Config) when Tc == no_common_alg_server_disconnects;
182+
Tc == custom_kexinit ->
182183
start_std_daemon(Config, [{preferred_algorithms,[{public_key,['ssh-rsa']},
183184
{cipher,?DEFAULT_CIPHERS}
184185
]}]);
@@ -224,7 +225,8 @@ init_per_testcase(TC, Config) when TC == gex_client_init_option_groups ;
224225
init_per_testcase(_TestCase, Config) ->
225226
check_std_daemon_works(Config, ?LINE).
226227

227-
end_per_testcase(Tc, Config) when Tc == no_common_alg_server_disconnects; Tc == custom_kexinit ->
228+
end_per_testcase(Tc, Config) when Tc == no_common_alg_server_disconnects;
229+
Tc == custom_kexinit ->
228230
stop_std_daemon(Config);
229231
end_per_testcase(kex_strict_negotiated, Config) ->
230232
Config;
@@ -385,6 +387,44 @@ no_common_alg_server_disconnects(Config) ->
385387
]
386388
).
387389

390+
early_rce(Config) ->
391+
{ok,InitialState} =
392+
ssh_trpt_test_lib:exec([{set_options, [print_ops, print_seqnums, print_messages]}]),
393+
TypeOpen = "session",
394+
ChannelId = 0,
395+
WinSz = 425984,
396+
PktSz = 65536,
397+
DataOpen = <<>>,
398+
SshMsgChannelOpen = ssh_connection:channel_open_msg(TypeOpen, ChannelId, WinSz, PktSz, DataOpen),
399+
400+
Id = 0,
401+
TypeReq = "exec",
402+
WantReply = true,
403+
DataReq = <<?STRING(<<"lists:seq(1,10).">>)>>,
404+
SshMsgChannelRequest =
405+
ssh_connection:channel_request_msg(Id, TypeReq, WantReply, DataReq),
406+
{ok,AfterKexState} =
407+
ssh_trpt_test_lib:exec(
408+
[{connect,
409+
server_host(Config),server_port(Config),
410+
[{preferred_algorithms,[{kex,[?DEFAULT_KEX]},
411+
{cipher,?DEFAULT_CIPHERS}
412+
]},
413+
{silently_accept_hosts, true},
414+
{recv_ext_info, false},
415+
{user_dir, user_dir(Config)},
416+
{user_interaction, false}
417+
| proplists:get_value(extra_options,Config,[])]},
418+
receive_hello,
419+
{send, hello},
420+
{send, ssh_msg_kexinit},
421+
{match, #ssh_msg_kexinit{_='_'}, receive_msg},
422+
{send, SshMsgChannelOpen},
423+
{send, SshMsgChannelRequest},
424+
{match, disconnect(), receive_msg}
425+
], InitialState),
426+
ok.
427+
388428
custom_kexinit(Config) ->
389429
%% 16#C0 value causes unicode:characters_to_list to return a big error value
390430
Trash = lists:duplicate(260_000, 16#C0),
@@ -411,11 +451,6 @@ custom_kexinit(Config) ->
411451
first_kex_packet_follows = false,
412452
reserved = 0
413453
},
414-
PacketFun =
415-
fun(Msg, Ssh) ->
416-
BinMsg = custom_encode(Msg),
417-
ssh_transport:pack(BinMsg, Ssh, 0)
418-
end,
419454
{ok,_} =
420455
ssh_trpt_test_lib:exec(
421456
[{set_options, [print_ops, {print_messages,detail}]},
@@ -431,42 +466,11 @@ custom_kexinit(Config) ->
431466
receive_hello,
432467
{send, hello},
433468
{match, #ssh_msg_kexinit{_='_'}, receive_msg},
434-
{send, {special, KexInit, PacketFun}}, % with server unsupported 'ssh-dss' !
469+
{send, KexInit}, % with server unsupported 'ssh-dss' !
435470
{match, disconnect(), receive_msg}
436471
]
437472
).
438473

439-
custom_encode(#ssh_msg_kexinit{
440-
cookie = Cookie,
441-
kex_algorithms = KeyAlgs,
442-
server_host_key_algorithms = HostKeyAlgs,
443-
encryption_algorithms_client_to_server = EncAlgC2S,
444-
encryption_algorithms_server_to_client = EncAlgS2C,
445-
mac_algorithms_client_to_server = MacAlgC2S,
446-
mac_algorithms_server_to_client = MacAlgS2C,
447-
compression_algorithms_client_to_server = CompAlgS2C,
448-
compression_algorithms_server_to_client = CompAlgC2S,
449-
languages_client_to_server = LangC2S,
450-
languages_server_to_client = LangS2C,
451-
first_kex_packet_follows = Bool,
452-
reserved = Reserved
453-
}) ->
454-
KeyAlgsBin0 = <<?Ename_list(KeyAlgs)>>,
455-
<<?UINT32(Len0), Data:Len0/binary>> = KeyAlgsBin0,
456-
KeyAlgsBin = <<?UINT32(Len0), Data/binary>>,
457-
<<?Ebyte(?SSH_MSG_KEXINIT), Cookie/binary,
458-
KeyAlgsBin/binary,
459-
?Ename_list(HostKeyAlgs),
460-
?Ename_list(EncAlgC2S),
461-
?Ename_list(EncAlgS2C),
462-
?Ename_list(MacAlgC2S),
463-
?Ename_list(MacAlgS2C),
464-
?Ename_list(CompAlgS2C),
465-
?Ename_list(CompAlgC2S),
466-
?Ename_list(LangC2S),
467-
?Ename_list(LangS2C),
468-
?Eboolean(Bool), ?Euint32(Reserved)>>.
469-
470474
%%--------------------------------------------------------------------
471475
%%% Algo negotiation fail. This should result in a ssh_msg_disconnect
472476
%%% being sent from the client.

0 commit comments

Comments
 (0)