File 0217-ssh-strict-mlkem-message-decoding.patch of Package erlang
From 3f75201ddd9229e1df6b869948add087d67a274a Mon Sep 17 00:00:00 2001
From: Jakub Witczak <kuba@erlang.org>
Date: Mon, 26 Jan 2026 09:05:05 +0100
Subject: [PATCH 3/4] ssh: strict mlkem message decoding
---
lib/ssh/src/ssh.hrl | 11 +++++++++++
lib/ssh/src/ssh_message.erl | 20 ++++++++++++++++++--
lib/ssh/src/ssh_transport.erl | 8 +++++---
lib/ssh/src/ssh_transport.hrl | 1 -
lib/ssh/test/ssh_to_openssh_SUITE.erl | 4 +++-
5 files changed, 37 insertions(+), 7 deletions(-)
diff --git a/lib/ssh/src/ssh.hrl b/lib/ssh/src/ssh.hrl
index 48e73c065a..24ad26588e 100644
--- a/lib/ssh/src/ssh.hrl
+++ b/lib/ssh/src/ssh.hrl
@@ -42,6 +42,17 @@
-define(MAX_RND_PADDING_LEN, 15).
+%% Hybrid KEX limits
+-define(MLKEM768_PUBLICKEY_SIZE, 1184).
+-define(MLKEM768_CIPHERTEXT_SIZE, 1088).
+-define(X25519_PUBLICKEY_SIZE, 32).
+-define(MLKEM768_INIT_SIZE, ?MLKEM768_PUBLICKEY_SIZE + ?X25519_PUBLICKEY_SIZE). % NIST FIPS 203: 1184 + 32
+-define(MLKEM768_REPLY_SIZE, ?MLKEM768_CIPHERTEXT_SIZE + ?X25519_PUBLICKEY_SIZE). % NIST FIPS 203: 1088 + 32
+
+%% Cryptographic limits
+-define(MAX_HOST_KEY_SIZE, 4096). % RSA-4096 + ASN.1/SSH encoding
+-define(MAX_SIGNATURE_SIZE, 1536). % RSA-8192 (1044) + margin for future algorithms
+
-define(SUPPORTED_AUTH_METHODS, "publickey,keyboard-interactive,password").
-define(FALSE, 0).
diff --git a/lib/ssh/src/ssh_message.erl b/lib/ssh/src/ssh_message.erl
index 64422c973b..b67f4f970c 100644
--- a/lib/ssh/src/ssh_message.erl
+++ b/lib/ssh/src/ssh_message.erl
@@ -539,18 +539,34 @@ decode(<<"ecdh",?BYTE(?SSH_MSG_KEX_ECDH_REPLY),
h_sig = decode_signature(Sig)
};
-decode(<<"mlkem",?BYTE(?SSH_MSG_KEX_HYBRID_INIT), ?DEC_BIN(C_init,__0)>>) ->
+decode(<<"mlkem",?BYTE(?SSH_MSG_KEX_HYBRID_INIT), ?DEC_BIN(C_init, CLen)>>)
+ when CLen =:= ?MLKEM768_INIT_SIZE->
#ssh_msg_kex_hybrid_init{
c_init = C_init
};
+%% Reject invalid ML-KEM messages with proper error
+decode(<<"mlkem", ?BYTE(?SSH_MSG_KEX_HYBRID_INIT), ?DEC_BIN(_, CLen)>>) ->
+ throw({error, {mlkem_init_invalid_size, CLen, ?MLKEM768_INIT_SIZE}});
decode(<<"mlkem",?BYTE(?SSH_MSG_KEX_HYBRID_REPLY),
- ?DEC_BIN(Key,__1), ?DEC_BIN(S_reply,__2), ?DEC_BIN(Sig,__3)>>) ->
+ ?DEC_BIN(Key, KLen), ?DEC_BIN(S_reply, SLen), ?DEC_BIN(Sig, SigLen)>>)
+ when KLen =< ?MAX_HOST_KEY_SIZE,
+ SLen =:= ?MLKEM768_REPLY_SIZE,
+ SigLen =< ?MAX_SIGNATURE_SIZE ->
#ssh_msg_kex_hybrid_reply{
public_host_key = ssh2_pubkey_decode(Key),
s_reply = S_reply,
h_sig = decode_signature(Sig)
};
+decode(<<"mlkem",?BYTE(?SSH_MSG_KEX_HYBRID_REPLY),
+ ?DEC_BIN(_, KLen), ?DEC_BIN(_, SLen), ?DEC_BIN(_Sig, SigLen)>>) ->
+ Error = if
+ KLen > ?MAX_HOST_KEY_SIZE -> {mlkem_host_key_too_large, KLen, ?MAX_HOST_KEY_SIZE};
+ SLen =/= ?MLKEM768_REPLY_SIZE -> {mlkem_reply_invalid_size, SLen, ?MLKEM768_REPLY_SIZE};
+ SigLen > ?MAX_SIGNATURE_SIZE -> {mlkem_signature_too_large, SigLen, ?MAX_SIGNATURE_SIZE};
+ true -> {mlkem_reply_invalid, KLen, SLen, SigLen}
+ end,
+ throw({error, Error});
decode(<<?SSH_MSG_SERVICE_REQUEST, ?DEC_BIN(Service,__0)>>) ->
#ssh_msg_service_request{
diff --git a/lib/ssh/src/ssh_transport.erl b/lib/ssh/src/ssh_transport.erl
index 674d8db68c..cda0ad97e5 100644
--- a/lib/ssh/src/ssh_transport.erl
+++ b/lib/ssh/src/ssh_transport.erl
@@ -2305,12 +2305,14 @@ generate_key(dh, [P,G,Sz2]) ->
{crypto:bytes_to_integer(Public), crypto:bytes_to_integer(Private)}.
compute_key(hybrid_server, C_init, S_privkey1, Curve) ->
- <<C_publickey2:1184/binary, C_publickey1:32/binary>> = C_init,
+ <<C_publickey2:?MLKEM768_PUBLICKEY_SIZE/binary,
+ C_publickey1:32/binary>> = C_init,
{K_pq_secret, S_ciphertext2} = crypto:encapsulate_key(mlkem768, C_publickey2),
SharedSecret = hybrid_common(K_pq_secret, Curve, C_publickey1, S_privkey1),
{S_ciphertext2, <<?Ebinary(SharedSecret)>>};
compute_key(hybrid_client, S_reply, {C_privkey2, C_privkey1}, Curve) ->
- <<S_ciphertext2:1088/binary, S_publickey1:32/binary>> = S_reply,
+ <<S_ciphertext2:?MLKEM768_CIPHERTEXT_SIZE/binary,
+ S_publickey1:?X25519_PUBLICKEY_SIZE/binary>> = S_reply,
K_pq_secret = crypto:decapsulate_key(mlkem768, C_privkey2, S_ciphertext2),
SharedSecret = hybrid_common(K_pq_secret, Curve, S_publickey1, C_privkey1),
<<?Ebinary(SharedSecret)>>;
@@ -2322,7 +2324,7 @@ hybrid_common(K_pq_secret, Curve, PeerPublic, MyPrivate) ->
K_cl_secret = compute_key(ecdh, PeerPublic, MyPrivate, Curve),
K_cl_secret_mpint = <<?Empint(K_cl_secret)>>,
K_cl_secret_mpint_trim =
- binary:part(K_cl_secret_mpint, byte_size(K_cl_secret_mpint), -32),
+ binary:part(K_cl_secret_mpint, byte_size(K_cl_secret_mpint), -?X25519_PUBLICKEY_SIZE),
crypto:hash(sha(Curve), <<K_pq_secret/binary, K_cl_secret_mpint_trim/binary>>).
dh_bits(#alg{encrypt = Encrypt,
diff --git a/lib/ssh/src/ssh_transport.hrl b/lib/ssh/src/ssh_transport.hrl
index 3b947ea5fe..620a5941b1 100644
--- a/lib/ssh/src/ssh_transport.hrl
+++ b/lib/ssh/src/ssh_transport.hrl
@@ -238,7 +238,6 @@
h_sig % string (the signature on the exchange hash)
}).
-
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%%
%% error codes
diff --git a/lib/ssh/test/ssh_to_openssh_SUITE.erl b/lib/ssh/test/ssh_to_openssh_SUITE.erl
index 4e14e55f33..60832ef5b4 100644
--- a/lib/ssh/test/ssh_to_openssh_SUITE.erl
+++ b/lib/ssh/test/ssh_to_openssh_SUITE.erl
@@ -317,7 +317,9 @@ eserver_oclient_renegotiate_helper1(Config) ->
eserver_oclient_renegotiate_helper2({Data, OpenSsh, Pid}) ->
Expect = fun({data,R}) ->
- case binary:match(R, <<"post-quantum">>) of
+ Warning =
+ <<"WARNING: connection is not using a post-quantum key exchange algorithm">>,
+ case binary:match(R, Warning) of
nomatch -> ok;
_ ->
?CT_PAL("~p", [R]),
--
2.51.0