File 1612-public_key-Add-SLH-DSA-support.patch of Package erlang
From 911ba4e99bc369499fa756c508ddddde7755b06e Mon Sep 17 00:00:00 2001
From: Ingela Anderton Andin <ingela@erlang.org>
Date: Wed, 8 Oct 2025 15:30:08 +0200
Subject: [PATCH 2/5] public_key: Add SLH-DSA support
Also remove white space errors in test suite
---
lib/public_key/asn1/Makefile | 1 +
lib/public_key/asn1/SLH-DSA-Module-2024.asn1 | 286 +++++++++++++++
lib/public_key/include/public_key.hrl | 35 +-
lib/public_key/src/pubkey_cert.erl | 22 +-
lib/public_key/src/pubkey_cert_records.erl | 99 +++++-
lib/public_key/src/public_key.app.src | 18 +-
lib/public_key/src/public_key.erl | 164 +++++++--
lib/public_key/src/public_key_internal.hrl | 24 +-
lib/public_key/test/public_key_SUITE.erl | 326 +++++++++++-------
.../public_key_SUITE_data/slh-dsa-cert.pem | 209 +++++++++++
.../slh-dsa-sha2-128s-pub.pem | 38 ++
.../slh-dsa-sha2-128s.pem | 38 ++
12 files changed, 1080 insertions(+), 180 deletions(-)
create mode 100644 lib/public_key/asn1/SLH-DSA-Module-2024.asn1
create mode 100644 lib/public_key/test/public_key_SUITE_data/slh-dsa-cert.pem
create mode 100644 lib/public_key/test/public_key_SUITE_data/slh-dsa-sha2-128s-pub.pem
create mode 100644 lib/public_key/test/public_key_SUITE_data/slh-dsa-sha2-128s.pem
diff --git a/lib/public_key/asn1/Makefile b/lib/public_key/asn1/Makefile
index 0c1d779292..f2e0991f4d 100644
--- a/lib/public_key/asn1/Makefile
+++ b/lib/public_key/asn1/Makefile
@@ -59,6 +59,7 @@ ASN_MODULES = \
ECPrivateKey \
KEMAlgorithmInformation-2023 \
X509-ML-DSA-2025 \
+ SLH-DSA-Module-2024 \
OCSP-2024-08 \
OTP-PKIX \
OTP-PKIX-Relaxed \
diff --git a/lib/public_key/asn1/SLH-DSA-Module-2024.asn1 b/lib/public_key/asn1/SLH-DSA-Module-2024.asn1
new file mode 100644
index 0000000000..af2365b46b
--- /dev/null
+++ b/lib/public_key/asn1/SLH-DSA-Module-2024.asn1
@@ -0,0 +1,286 @@
+-- %CopyrightBegin%
+--
+-- SPDX-License-Identifier: BSD-3-Clause
+--
+-- Copyright (c) 2010 IETF Trust and the persons identified as the document authors. All rights reserved.
+-- Copyright Ericsson AB 2025. All Rights Reserved.
+--
+-- Redistribution and use in source and binary forms, with or without
+-- modification, are permitted provided that the following conditions are met:
+--
+-- 1. Redistributions of source code must retain the above copyright notice,
+-- this list of conditions and the following disclaimer.
+--
+-- 2. Redistributions in binary form must reproduce the above copyright notice,
+-- this list of conditions and the following disclaimer in the documentation
+-- and/or other materials provided with the distribution.
+--
+-- 3. Neither the name of the copyright holder nor the names of its contributors
+-- may be used to endorse or promote products derived from this software
+-- without specific prior written permission.
+--
+-- THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS “AS IS”
+-- AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
+-- IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
+-- ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE
+-- LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
+-- CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
+-- SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
+-- INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
+-- CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
+-- ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
+-- POSSIBILITY OF SUCH DAMAGE.
+--
+-- %CopyrightEnd%
+
+SLH-DSA-Module-2024
+ { iso(1) member-body(2) us(840) rsadsi(113549) pkcs(1) pkcs9(9)
+ id-smime(16) id-mod(0) id-mod-slh-dsa-2024(81) }
+
+ DEFINITIONS IMPLICIT TAGS ::= BEGIN
+
+ EXPORTS ALL;
+
+ IMPORTS
+ PUBLIC-KEY, SIGNATURE-ALGORITHM, SMIME-CAPS
+ FROM AlgorithmInformation-2009 -- in [RFC5911]
+ { iso(1) identified-organization(3) dod(6) internet(1)
+ security(5) mechanisms(5) pkix(7) id-mod(0)
+ id-mod-algorithmInformation-02(58) } ;
+
+ --
+ -- Object Identifiers
+ --
+
+ nistAlgorithms OBJECT IDENTIFIER ::= { joint-iso-itu-t(2)
+ country(16) us(840) organization(1) gov(101) csor(3) 4 }
+
+ sigAlgs OBJECT IDENTIFIER ::= { nistAlgorithms 3 }
+
+ id-slh-dsa-sha2-128s OBJECT IDENTIFIER ::= { sigAlgs 20 }
+
+ id-slh-dsa-sha2-128f OBJECT IDENTIFIER ::= { sigAlgs 21 }
+
+ id-slh-dsa-sha2-192s OBJECT IDENTIFIER ::= { sigAlgs 22 }
+
+ id-slh-dsa-sha2-192f OBJECT IDENTIFIER ::= { sigAlgs 23 }
+
+ id-slh-dsa-sha2-256s OBJECT IDENTIFIER ::= { sigAlgs 24 }
+
+ id-slh-dsa-sha2-256f OBJECT IDENTIFIER ::= { sigAlgs 25 }
+
+ id-slh-dsa-shake-128s OBJECT IDENTIFIER ::= { sigAlgs 26 }
+
+ id-slh-dsa-shake-128f OBJECT IDENTIFIER ::= { sigAlgs 27 }
+
+ id-slh-dsa-shake-192s OBJECT IDENTIFIER ::= { sigAlgs 28 }
+
+ id-slh-dsa-shake-192f OBJECT IDENTIFIER ::= { sigAlgs 29 }
+
+ id-slh-dsa-shake-256s OBJECT IDENTIFIER ::= { sigAlgs 30 }
+
+ id-slh-dsa-shake-256f OBJECT IDENTIFIER ::= { sigAlgs 31 }
+
+ --
+ -- Signature Algorithm, Public Key, and Private Key
+ --
+
+ sa-slh-dsa-sha2-128s SIGNATURE-ALGORITHM ::= {
+ IDENTIFIER id-slh-dsa-sha2-128s
+ PARAMS ARE absent
+ PUBLIC-KEYS { pk-slh-dsa-sha2-128s }
+ SMIME-CAPS { IDENTIFIED BY id-slh-dsa-sha2-128s } }
+
+ sa-slh-dsa-sha2-128f SIGNATURE-ALGORITHM ::= {
+ IDENTIFIER id-slh-dsa-sha2-128f
+ PARAMS ARE absent
+ PUBLIC-KEYS { pk-slh-dsa-sha2-128f }
+ SMIME-CAPS { IDENTIFIED BY id-slh-dsa-sha2-128f } }
+
+ sa-slh-dsa-sha2-192s SIGNATURE-ALGORITHM ::= {
+ IDENTIFIER id-slh-dsa-sha2-192s
+ PARAMS ARE absent
+ PUBLIC-KEYS { pk-slh-dsa-sha2-192s }
+ SMIME-CAPS { IDENTIFIED BY id-slh-dsa-sha2-192s } }
+
+ sa-slh-dsa-sha2-192f SIGNATURE-ALGORITHM ::= {
+ IDENTIFIER id-slh-dsa-sha2-192f
+ PARAMS ARE absent
+ PUBLIC-KEYS { pk-slh-dsa-sha2-192f }
+ SMIME-CAPS { IDENTIFIED BY id-slh-dsa-sha2-192f } }
+
+ sa-slh-dsa-sha2-256s SIGNATURE-ALGORITHM ::= {
+ IDENTIFIER id-slh-dsa-sha2-256s
+ PARAMS ARE absent
+ PUBLIC-KEYS { pk-slh-dsa-sha2-256s }
+ SMIME-CAPS { IDENTIFIED BY id-slh-dsa-sha2-256s } }
+
+ sa-slh-dsa-sha2-256f SIGNATURE-ALGORITHM ::= {
+ IDENTIFIER id-slh-dsa-sha2-256f
+ PARAMS ARE absent
+ PUBLIC-KEYS { pk-slh-dsa-sha2-256f }
+ SMIME-CAPS { IDENTIFIED BY id-slh-dsa-sha2-256f } }
+
+ sa-slh-dsa-shake-128s SIGNATURE-ALGORITHM ::= {
+ IDENTIFIER id-slh-dsa-shake-128s
+ PARAMS ARE absent
+ PUBLIC-KEYS { pk-slh-dsa-shake-128s }
+ SMIME-CAPS { IDENTIFIED BY id-slh-dsa-shake-128s } }
+
+ sa-slh-dsa-shake-128f SIGNATURE-ALGORITHM ::= {
+ IDENTIFIER id-slh-dsa-shake-128f
+ PARAMS ARE absent
+ PUBLIC-KEYS { pk-slh-dsa-shake-128f }
+ SMIME-CAPS { IDENTIFIED BY id-slh-dsa-shake-128f } }
+
+ sa-slh-dsa-shake-192s SIGNATURE-ALGORITHM ::= {
+ IDENTIFIER id-slh-dsa-shake-192s
+ PARAMS ARE absent
+ PUBLIC-KEYS { pk-slh-dsa-shake-192s }
+ SMIME-CAPS { IDENTIFIED BY id-slh-dsa-shake-192s } }
+
+ sa-slh-dsa-shake-192f SIGNATURE-ALGORITHM ::= {
+ IDENTIFIER id-slh-dsa-shake-192f
+ PARAMS ARE absent
+ PUBLIC-KEYS { pk-slh-dsa-shake-192f }
+ SMIME-CAPS { IDENTIFIED BY id-slh-dsa-shake-192f } }
+
+ sa-slh-dsa-shake-256s SIGNATURE-ALGORITHM ::= {
+ IDENTIFIER id-slh-dsa-shake-256s
+ PARAMS ARE absent
+ PUBLIC-KEYS { pk-slh-dsa-shake-256s }
+ SMIME-CAPS { IDENTIFIED BY id-slh-dsa-shake-256s } }
+
+ sa-slh-dsa-shake-256f SIGNATURE-ALGORITHM ::= {
+ IDENTIFIER id-slh-dsa-shake-256f
+ PARAMS ARE absent
+ PUBLIC-KEYS { pk-slh-dsa-shake-256f }
+ SMIME-CAPS { IDENTIFIED BY id-slh-dsa-shake-256f } }
+
+ pk-slh-dsa-sha2-128s PUBLIC-KEY ::= {
+ IDENTIFIER id-slh-dsa-sha2-128s
+ -- KEY no ASN.1 wrapping --
+ CERT-KEY-USAGE
+ { digitalSignature, nonRepudiation, keyCertSign, cRLSign }
+ -- PRIVATE-KEY no ASN.1 wrapping -- }
+
+ pk-slh-dsa-sha2-128f PUBLIC-KEY ::= {
+ IDENTIFIER id-slh-dsa-sha2-128f
+ -- KEY no ASN.1 wrapping --
+ CERT-KEY-USAGE
+ { digitalSignature, nonRepudiation, keyCertSign, cRLSign }
+ -- PRIVATE-KEY no ASN.1 wrapping -- }
+
+ pk-slh-dsa-sha2-192s PUBLIC-KEY ::= {
+ IDENTIFIER id-slh-dsa-sha2-192s
+ -- KEY no ASN.1 wrapping --
+ CERT-KEY-USAGE
+ { digitalSignature, nonRepudiation, keyCertSign, cRLSign }
+ -- PRIVATE-KEY no ASN.1 wrapping -- }
+
+ pk-slh-dsa-sha2-192f PUBLIC-KEY ::= {
+ IDENTIFIER id-slh-dsa-sha2-192f
+ -- KEY no ASN.1 wrapping --
+ CERT-KEY-USAGE
+ { digitalSignature, nonRepudiation, keyCertSign, cRLSign }
+ -- PRIVATE-KEY no ASN.1 wrapping -- }
+
+ pk-slh-dsa-sha2-256s PUBLIC-KEY ::= {
+ IDENTIFIER id-slh-dsa-sha2-256s
+ -- KEY no ASN.1 wrapping --
+ CERT-KEY-USAGE
+ { digitalSignature, nonRepudiation, keyCertSign, cRLSign }
+ -- PRIVATE-KEY no ASN.1 wrapping -- }
+
+ pk-slh-dsa-sha2-256f PUBLIC-KEY ::= {
+ IDENTIFIER id-slh-dsa-sha2-256f
+ -- KEY no ASN.1 wrapping --
+ CERT-KEY-USAGE
+ { digitalSignature, nonRepudiation, keyCertSign, cRLSign }
+ -- PRIVATE-KEY no ASN.1 wrapping -- }
+
+ pk-slh-dsa-shake-128s PUBLIC-KEY ::= {
+ IDENTIFIER id-slh-dsa-shake-128s
+ -- KEY no ASN.1 wrapping --
+ CERT-KEY-USAGE
+ { digitalSignature, nonRepudiation, keyCertSign, cRLSign }
+ -- PRIVATE-KEY no ASN.1 wrapping -- }
+
+ pk-slh-dsa-shake-128f PUBLIC-KEY ::= {
+ IDENTIFIER id-slh-dsa-shake-128f
+ -- KEY no ASN.1 wrapping --
+ CERT-KEY-USAGE
+ { digitalSignature, nonRepudiation, keyCertSign, cRLSign }
+ -- PRIVATE-KEY no ASN.1 wrapping -- }
+
+ pk-slh-dsa-shake-192s PUBLIC-KEY ::= {
+ IDENTIFIER id-slh-dsa-shake-192s
+ -- KEY no ASN.1 wrapping --
+ CERT-KEY-USAGE
+ { digitalSignature, nonRepudiation, keyCertSign, cRLSign }
+ -- PRIVATE-KEY no ASN.1 wrapping -- }
+
+ pk-slh-dsa-shake-192f PUBLIC-KEY ::= {
+ IDENTIFIER id-slh-dsa-shake-192f
+ -- KEY no ASN.1 wrapping --
+ CERT-KEY-USAGE
+ { digitalSignature, nonRepudiation, keyCertSign, cRLSign }
+ -- PRIVATE-KEY no ASN.1 wrapping -- }
+
+ pk-slh-dsa-shake-256s PUBLIC-KEY ::= {
+ IDENTIFIER id-slh-dsa-shake-256s
+ -- KEY no ASN.1 wrapping --
+ CERT-KEY-USAGE
+ { digitalSignature, nonRepudiation, keyCertSign, cRLSign }
+ -- PRIVATE-KEY no ASN.1 wrapping -- }
+
+ pk-slh-dsa-shake-256f PUBLIC-KEY ::= {
+ IDENTIFIER id-slh-dsa-shake-256f
+ -- KEY no ASN.1 wrapping --
+ CERT-KEY-USAGE
+ { digitalSignature, nonRepudiation, keyCertSign, cRLSign }
+ -- PRIVATE-KEY no ASN.1 wrapping -- }
+
+ SLH-DSA-PublicKey ::= OCTET STRING (SIZE (32 | 48 | 64))
+
+ SLH-DSA-PrivateKey ::= OCTET STRING (SIZE (64 | 96 | 128))
+
+ --
+ -- Expand the signature algorithm set used by CMS [RFC5911]
+ --
+
+ SignatureAlgorithmSet SIGNATURE-ALGORITHM ::=
+ { sa-slh-dsa-sha2-128s |
+ sa-slh-dsa-sha2-128f |
+ sa-slh-dsa-sha2-192s |
+ sa-slh-dsa-sha2-192f |
+ sa-slh-dsa-sha2-256s |
+ sa-slh-dsa-sha2-256f |
+ sa-slh-dsa-shake-128s |
+ sa-slh-dsa-shake-128f |
+ sa-slh-dsa-shake-192s |
+ sa-slh-dsa-shake-192f |
+ sa-slh-dsa-shake-256s |
+ sa-slh-dsa-shake-256f,
+ ... }
+
+ --
+ -- Expand the S/MIME capabilities set used by CMS [RFC5911]
+ --
+
+ SMimeCaps SMIME-CAPS ::=
+ { sa-slh-dsa-sha2-128s.&smimeCaps |
+ sa-slh-dsa-sha2-128f.&smimeCaps |
+ sa-slh-dsa-sha2-192s.&smimeCaps |
+ sa-slh-dsa-sha2-192f.&smimeCaps |
+ sa-slh-dsa-sha2-256s.&smimeCaps |
+ sa-slh-dsa-sha2-256f.&smimeCaps |
+ sa-slh-dsa-shake-128s.&smimeCaps |
+ sa-slh-dsa-shake-128f.&smimeCaps |
+ sa-slh-dsa-shake-192s.&smimeCaps |
+ sa-slh-dsa-shake-192f.&smimeCaps |
+ sa-slh-dsa-shake-256s.&smimeCaps |
+ sa-slh-dsa-shake-256f.&smimeCaps,
+ ... }
+
+END
\ No newline at end of file
diff --git a/lib/public_key/include/public_key.hrl b/lib/public_key/include/public_key.hrl
index 20843f45d5..1716b3a3e4 100644
--- a/lib/public_key/include/public_key.hrl
+++ b/lib/public_key/include/public_key.hrl
@@ -117,14 +117,14 @@
%%%
-record('ML-DSAPrivateKey',
{
- algorithm :: mldsa44 | mldsa65 | mldsa87,
+ algorithm :: crypto:mldsa(),
seed = <<>> :: binary(),
expandedkey = <<>> :: binary()
}).
-record('ML-DSAPublicKey',
{
- algorithm :: mldsa44 | mldsa65 | mldsa87,
+ algorithm :: crypto:mldsa(),
key :: binary()
}).
@@ -133,6 +133,37 @@
-define('id-ml-dsa-87', {2,16,840,1,101,3,4,3,19}).
+
+%%%
+%%% SLH-DSA
+%%%
+-record('SLH-DSAPrivateKey',
+ {
+ algorithm :: crypto:slh_dsa(),
+ key :: binary()
+ }).
+
+-record('SLH-DSAPublicKey',
+ {
+ algorithm :: crypto:slh_dsa(),
+ key :: binary()
+ }).
+
+-define('id-slh-dsa-sha2-128s', {2,16,840,1,101,3,4,3,20}).
+-define('id-slh-dsa-sha2-128f', {2,16,840,1,101,3,4,3,21}).
+-define('id-slh-dsa-sha2-192s', {2,16,840,1,101,3,4,3,22}).
+-define('id-slh-dsa-sha2-192f', {2,16,840,1,101,3,4,3,23}).
+-define('id-slh-dsa-sha2-256s', {2,16,840,1,101,3,4,3,24}).
+-define('id-slh-dsa-sha2-256f', {2,16,840,1,101,3,4,3,25}).
+-define('id-slh-dsa-shake-128s', {2,16,840,1,101,3,4,3,26}).
+-define('id-slh-dsa-shake-128f', {2,16,840,1,101,3,4,3,27}).
+-define('id-slh-dsa-shake-192s', {2,16,840,1,101,3,4,3,28}).
+-define('id-slh-dsa-shake-192f', {2,16,840,1,101,3,4,3,29}).
+-define('id-slh-dsa-shake-256s', {2,16,840,1,101,3,4,3,30}).
+-define('id-slh-dsa-shake-256f', {2,16,840,1,101,3,4,3,31}).
+
+
+
%%%
%%% DSA
%%%
diff --git a/lib/public_key/src/pubkey_cert.erl b/lib/public_key/src/pubkey_cert.erl
index 1ee7160523..afc8479962 100644
--- a/lib/public_key/src/pubkey_cert.erl
+++ b/lib/public_key/src/pubkey_cert.erl
@@ -47,8 +47,7 @@
match_name/3,
extensions_list/1,
cert_auth_key_id/1,
- time_str_2_gregorian_sec/1,
- mldsa_algo_to_oid/1
+ time_str_2_gregorian_sec/1
]).
%% Generate test data
@@ -1736,7 +1735,9 @@ verify_signature(OtpCert, DerCert, Key, KeyParams) ->
asn1_NOVALUE ->
public_key:verify(PlainText, DigestType, Signature, Key)
end;
- _ ->
+ #'SLH-DSAPublicKey'{} ->
+ public_key:verify(PlainText, none, Signature, Key);
+ _ ->
public_key:verify(PlainText, DigestType, Signature, {Key, KeyParams})
end.
@@ -2001,16 +2002,12 @@ sign_algorithm(#'ECPrivateKey'{parameters = Parms}, Opts) ->
#'SignatureAlgorithm'{algorithm = Type,
parameters = Parms};
sign_algorithm(#'ML-DSAPrivateKey'{algorithm = Algo}, _) ->
- #'SignatureAlgorithm'{algorithm = mldsa_algo_to_oid(Algo),
+ #'SignatureAlgorithm'{algorithm = pubkey_cert_records:mldsa_algo_to_oid(Algo),
+ parameters = asn1_NOVALUE};
+sign_algorithm(#'SLH-DSAPrivateKey'{algorithm = Algo}, _) ->
+ #'SignatureAlgorithm'{algorithm = pubkey_cert_records:slh_dsa_algo_to_oid(Algo),
parameters = asn1_NOVALUE}.
-mldsa_algo_to_oid(mldsa44) ->
- ?'id-ml-dsa-44';
-mldsa_algo_to_oid(mldsa65) ->
- ?'id-ml-dsa-65';
-mldsa_algo_to_oid(mldsa87) ->
- ?'id-ml-dsa-87'.
-
rsa_sign_algo(#'RSAPrivateKey'{}, ?'id-RSASSA-PSS' = Type, #'RSASSA-PSS-params'{} = Params) ->
#'SignatureAlgorithm'{algorithm = Type,
parameters = Params};
@@ -2195,6 +2192,9 @@ key_info(Opts) ->
encode_key(#'ML-DSAPrivateKey'{} = Key) ->
{Asn1Type, DER, _} = public_key:pem_entry_encode('PrivateKeyInfo', Key),
{Asn1Type, DER};
+encode_key(#'SLH-DSAPrivateKey'{} = Key) ->
+ {Asn1Type, DER, _} = public_key:pem_entry_encode('PrivateKeyInfo', Key),
+ {Asn1Type, DER};
encode_key({#'RSAPrivateKey'{}, #'RSASSA-PSS-params'{}} = Key) ->
{Asn1Type, DER, _} = public_key:pem_entry_encode('PrivateKeyInfo', Key),
{Asn1Type, DER};
diff --git a/lib/public_key/src/pubkey_cert_records.erl b/lib/public_key/src/pubkey_cert_records.erl
index b82d47da74..28d330ac73 100644
--- a/lib/public_key/src/pubkey_cert_records.erl
+++ b/lib/public_key/src/pubkey_cert_records.erl
@@ -34,7 +34,11 @@
namedCurves/1,
encode_extensions/1,
decode_extensions/1,
- ext_oid/1
+ ext_oid/1,
+ oid_to_ml_dsa_algo/1,
+ oid_to_slh_dsa_algo/1,
+ mldsa_algo_to_oid/1,
+ slh_dsa_algo_to_oid/1
]).
%%====================================================================
@@ -195,7 +199,19 @@ supportedPublicKeyAlgorithms(?'id-X25519') -> 'ECPoint';
supportedPublicKeyAlgorithms(?'id-X448') -> 'ECPoint';
supportedPublicKeyAlgorithms(?'id-ml-dsa-44') -> 'ML-DSAPublicKey';
supportedPublicKeyAlgorithms(?'id-ml-dsa-65') -> 'ML-DSAPublicKey';
-supportedPublicKeyAlgorithms(?'id-ml-dsa-87') -> 'ML-DSAPublicKey'.
+supportedPublicKeyAlgorithms(?'id-ml-dsa-87') -> 'ML-DSAPublicKey';
+supportedPublicKeyAlgorithms(?'id-slh-dsa-sha2-128f') -> 'SLH-DSAPublicKey';
+supportedPublicKeyAlgorithms(?'id-slh-dsa-sha2-128s') -> 'SLH-DSAPublicKey';
+supportedPublicKeyAlgorithms(?'id-slh-dsa-sha2-192f') -> 'SLH-DSAPublicKey';
+supportedPublicKeyAlgorithms(?'id-slh-dsa-sha2-192s') -> 'SLH-DSAPublicKey';
+supportedPublicKeyAlgorithms(?'id-slh-dsa-sha2-256f') -> 'SLH-DSAPublicKey';
+supportedPublicKeyAlgorithms(?'id-slh-dsa-sha2-256s') -> 'SLH-DSAPublicKey';
+supportedPublicKeyAlgorithms(?'id-slh-dsa-shake-128f') -> 'SLH-DSAPublicKey';
+supportedPublicKeyAlgorithms(?'id-slh-dsa-shake-128s') -> 'SLH-DSAPublicKey';
+supportedPublicKeyAlgorithms(?'id-slh-dsa-shake-192f') -> 'SLH-DSAPublicKey';
+supportedPublicKeyAlgorithms(?'id-slh-dsa-shake-192s') -> 'SLH-DSAPublicKey';
+supportedPublicKeyAlgorithms(?'id-slh-dsa-shake-256f') -> 'SLH-DSAPublicKey';
+supportedPublicKeyAlgorithms(?'id-slh-dsa-shake-256s') -> 'SLH-DSAPublicKey'.
supportedCurvesTypes(?'characteristic-two-field') -> characteristic_two_field;
supportedCurvesTypes(?'prime-field') -> prime_field;
@@ -304,6 +320,71 @@ namedCurves(brainpoolP384t1) -> ?'brainpoolP384t1';
namedCurves(brainpoolP512r1) -> ?'brainpoolP512r1';
namedCurves(brainpoolP512t1) -> ?'brainpoolP512t1'.
+
+oid_to_ml_dsa_algo(?'id-ml-dsa-44') ->
+ mldsa44;
+oid_to_ml_dsa_algo(?'id-ml-dsa-65') ->
+ mldsa65;
+oid_to_ml_dsa_algo(?'id-ml-dsa-87') ->
+ mldsa87.
+
+oid_to_slh_dsa_algo(?'id-slh-dsa-sha2-128s') ->
+ slh_dsa_sha2_128s;
+oid_to_slh_dsa_algo(?'id-slh-dsa-sha2-128f') ->
+ slh_dsa_sha2_128f;
+oid_to_slh_dsa_algo(?'id-slh-dsa-sha2-192s') ->
+ slh_dsa_sha2_192s;
+oid_to_slh_dsa_algo(?'id-slh-dsa-sha2-192f') ->
+ slh_dsa_sha2_192f;
+oid_to_slh_dsa_algo(?'id-slh-dsa-sha2-256s') ->
+ slh_dsa_sha2_256s;
+oid_to_slh_dsa_algo(?'id-slh-dsa-sha2-256f') ->
+ slh_dsa_sha2_256f;
+oid_to_slh_dsa_algo(?'id-slh-dsa-shake-128s') ->
+ slh_dsa_shake_128s;
+oid_to_slh_dsa_algo(?'id-slh-dsa-shake-128f') ->
+ slh_dsa_shake_128f;
+oid_to_slh_dsa_algo(?'id-slh-dsa-shake-192s') ->
+ slh_dsa_shake_192s;
+oid_to_slh_dsa_algo(?'id-slh-dsa-shake-192f') ->
+ slh_dsa_shake_192f;
+oid_to_slh_dsa_algo(?'id-slh-dsa-shake-256s') ->
+ slh_dsa_shake_256s;
+oid_to_slh_dsa_algo(?'id-slh-dsa-shake-256f') ->
+ slh_dsa_shake_256f.
+
+mldsa_algo_to_oid(mldsa44) ->
+ ?'id-ml-dsa-44';
+mldsa_algo_to_oid(mldsa65) ->
+ ?'id-ml-dsa-65';
+mldsa_algo_to_oid(mldsa87) ->
+ ?'id-ml-dsa-87'.
+
+slh_dsa_algo_to_oid(slh_dsa_sha2_128s) ->
+ ?'id-slh-dsa-sha2-128s';
+slh_dsa_algo_to_oid(slh_dsa_sha2_128f) ->
+ ?'id-slh-dsa-sha2-128f';
+slh_dsa_algo_to_oid(slh_dsa_sha2_192s) ->
+ ?'id-slh-dsa-sha2-192s';
+slh_dsa_algo_to_oid(slh_dsa_sha2_192f) ->
+ ?'id-slh-dsa-sha2-192f';
+slh_dsa_algo_to_oid(slh_dsa_sha2_256s) ->
+ ?'id-slh-dsa-sha2-256s';
+slh_dsa_algo_to_oid(slh_dsa_sha2_256f) ->
+ ?'id-slh-dsa-sha2-256f';
+slh_dsa_algo_to_oid(slh_dsa_shake_128s) ->
+ ?'id-slh-dsa-shake-128s';
+slh_dsa_algo_to_oid(slh_dsa_shake_128f) ->
+ ?'id-slh-dsa-shake-128f';
+slh_dsa_algo_to_oid(slh_dsa_shake_192s) ->
+ ?'id-slh-dsa-shake-192s';
+slh_dsa_algo_to_oid(slh_dsa_shake_192f) ->
+ ?'id-slh-dsa-shake-192f';
+slh_dsa_algo_to_oid(slh_dsa_shake_256s) ->
+ ?'id-slh-dsa-shake-256s';
+slh_dsa_algo_to_oid(slh_dsa_shake_256f) ->
+ ?'id-slh-dsa-shake-256f'.
+
%%--------------------------------------------------------------------
%%% Internal functions
%%--------------------------------------------------------------------
@@ -319,6 +400,9 @@ decode_supportedPublicKey(#'SubjectPublicKeyInfo'{algorithm=PA,
'ML-DSAPublicKey' ->
#'ML-DSAPublicKey'{algorithm = oid_to_ml_dsa_algo(Algo),
key = SPK0};
+ 'SLH-DSAPublicKey' ->
+ #'SLH-DSAPublicKey'{algorithm = oid_to_slh_dsa_algo(Algo),
+ key = SPK0};
_ ->
public_key:der_decode(Type, SPK0)
end,
@@ -337,9 +421,12 @@ encode_supportedPublicKey(#'OTPSubjectPublicKeyInfo'{
SPK = case Type of
'ECPoint' ->
SPK0#'ECPoint'.point;
- 'ML-DSAPublicKey' ->
+ 'ML-DSAPublicKey' ->
#'ML-DSAPublicKey'{key = SPK1} = SPK0,
SPK1;
+ 'SLH-DSAPublicKey' ->
+ #'SLH-DSAPublicKey'{key = SPK1} = SPK0,
+ SPK1;
_ ->
public_key:der_encode(Type, SPK0)
end,
@@ -511,9 +598,3 @@ encode_extensions(Exts) ->
end
end, Exts).
-oid_to_ml_dsa_algo(?'id-ml-dsa-44') ->
- mldsa44;
-oid_to_ml_dsa_algo(?'id-ml-dsa-65') ->
- mldsa65;
-oid_to_ml_dsa_algo(?'id-ml-dsa-87') ->
- mldsa87.
diff --git a/lib/public_key/src/public_key.app.src b/lib/public_key/src/public_key.app.src
index adb73d86b9..e691da9f23 100644
--- a/lib/public_key/src/public_key.app.src
+++ b/lib/public_key/src/public_key.app.src
@@ -8,22 +8,22 @@
{application, public_key,
[{description, "Public key infrastructure"},
{vsn, "%VSN%"},
- {modules, ['AlgorithmInformation-2009',
+ {modules, [
+ 'AlgorithmInformation-2009',
'AttributeCertificateVersion1-2009',
'CMSAesRsaesOaep-2009',
'CryptographicMessageSyntax-2009',
'CryptographicMessageSyntaxAlgorithms-2009',
'DSS',
'ECPrivateKey',
+ 'EnrollmentMessageSyntax-2009',
'KEMAlgorithmInformation-2023',
'OCSP-2024-08',
'OTP-PKIX',
'OTP-PKIX-Relaxed',
- 'X509-ML-DSA-2025',
'PKCS-1',
'PKCS-10',
'PKCS-3',
- 'PKIXCMP-2023',
'PKCS-FRAME',
'PKIX-CommonTypes-2009',
'PKIX-X400Address-2009',
@@ -30,13 +30,14 @@
'PKIX1Explicit-2009',
'PKIX1Implicit-2009',
'PKIXAlgs-2009',
- 'PKIXCRMF-2009',
- 'EnrollmentMessageSyntax-2009',
'PKIXAttributeCertificate-2009',
+ 'PKIXCMP-2023',
+ 'PKIXCRMF-2009',
'RFC5639',
+ 'SLH-DSA-Module-2024',
'Safecurves-pkix-18',
'SecureMimeMessageV3dot1-2009',
- public_key,
+ 'X509-ML-DSA-2025',
pubkey_cert,
pubkey_cert_records,
pubkey_crl,
@@ -46,7 +47,8 @@
pubkey_pem,
pubkey_policy_tree,
pubkey_ssh,
- pubkey_translation
+ pubkey_translation,
+ public_key
]},
{applications, [asn1, crypto, kernel, stdlib]},
{registered, []},
diff --git a/lib/public_key/src/public_key.erl b/lib/public_key/src/public_key.erl
index fa34c0b473..255d761a67 100644
--- a/lib/public_key/src/public_key.erl
+++ b/lib/public_key/src/public_key.erl
@@ -140,6 +140,8 @@ macros described here and in the User's Guide:
eddsa_private_key/0,
mldsa_public_key/0,
mldsa_private_key/0,
+ slh_dsa_public_key/0,
+ slh_dsa_private_key/0,
custom_key_opts/0,
public_key_info/0,
%% Internal exports beneath do not document
@@ -161,7 +163,8 @@ macros described here and in the User's Guide:
dsa_public_key() |
ecdsa_public_key() |
eddsa_public_key() |
- mldsa_public_key().
+ mldsa_public_key() |
+ slh_dsa_public_key().
-doc(#{title => <<"Keys">>}).
-doc "Supported private keys".
-type private_key() :: rsa_private_key() |
@@ -170,7 +173,9 @@ macros described here and in the User's Guide:
ecdsa_private_key() |
eddsa_private_key() |
mldsa_private_key() |
- #{algorithm := mldsa | eddsa | rsa_pss_pss | ecdsa | rsa | dsa,
+ slh_dsa_private_key() |
+ #{algorithm := slh_dsa | mldsa | eddsa | rsa_pss_pss |
+ ecdsa | rsa | dsa,
sign_fun => fun()} .
-doc(#{group => <<"Keys">>}).
-doc """
@@ -217,6 +222,11 @@ ML-DSA public key
""".
-type mldsa_public_key() :: #'ML-DSAPublicKey'{}.
+-doc """
+SLH-DSA public key
+""".
+-type slh_dsa_public_key() :: #'SLH-DSAPublicKey'{}.
+
-doc(#{title => <<"Keys">>}).
-doc "ASN.1 defined private key format for the ECDSA algorithm.".
-type ecdsa_private_key() :: #'ECPrivateKey'{}.
@@ -239,6 +249,11 @@ ML-DSA private key
""".
-type mldsa_private_key() :: #'ML-DSAPrivateKey'{}.
+-doc """
+SLH-DSA private key
+""".
+-type slh_dsa_private_key() :: #'SLH-DSAPrivateKey'{}.
+
-doc(#{title => <<"Keys">>}).
-doc "ASN.1 defined parameters for public key algorithms.".
-type key_params() :: 'NULL' | #'RSASSA-PSS-params'{} | {namedCurve, oid()} | #'ECParameters'{} | #'Dss-Parms'{}.
@@ -277,7 +292,9 @@ Possible `Ciphers` are "RC2-CBC" | "DES-CBC" | "DES-EDE3-CBC" `Salt` could be ge
-doc(#{group => <<"Common">>}).
-doc "Hash function used to create a message digest".
--type digest_type() :: crypto:sha2() | crypto:sha1() | md5 | none.
+-type digest_type() :: crypto:sha2() | crypto:sha1() | legacy_digest_type() | none.
+
+-type legacy_digest_type() :: md5 | md2.
-doc(#{group => <<"Certificate Revocation">>}).
-doc """
@@ -426,7 +443,9 @@ pem_entry_decode({'SubjectPublicKeyInfo', Der, _}) ->
ECCParams = ec_decode_params(AlgId, Params0),
{#'ECPoint'{point = Key0}, ECCParams};
'ML-DSAPublicKey' ->
- mldsa_pub_key(AlgId, Key0)
+ mldsa_pub_key(AlgId, Key0);
+ 'SLH-DSAPublicKey' ->
+ slh_dsa_pub_key(AlgId, Key0)
end;
pem_entry_decode({Asn1Type, Der, not_encrypted}) when is_atom(Asn1Type),
is_binary(Der) ->
@@ -503,8 +522,13 @@ pem_entry_encode('SubjectPublicKeyInfo',
pem_entry_encode('SubjectPublicKeyInfo', Spki);
pem_entry_encode('SubjectPublicKeyInfo',
#'ML-DSAPublicKey'{algorithm = Algorithm, key = Key}) ->
- Spki = subject_public_key_info(#'AlgorithmIdentifier'{algorithm = pubkey_cert:mldsa_algo_to_oid(Algorithm)},
- Key),
+ AlgOid = pubkey_cert_records:mldsa_algo_to_oid(Algorithm),
+ Spki = subject_public_key_info(#'AlgorithmIdentifier'{algorithm = AlgOid}, Key),
+ pem_entry_encode('SubjectPublicKeyInfo', Spki);
+pem_entry_encode('SubjectPublicKeyInfo',
+ #'SLH-DSAPublicKey'{algorithm = Algorithm, key = Key}) ->
+ AlgOid = pubkey_cert_records:slh_dsa_algo_to_oid(Algorithm),
+ Spki = subject_public_key_info(#'AlgorithmIdentifier'{algorithm = AlgOid}, Key),
pem_entry_encode('SubjectPublicKeyInfo', Spki);
pem_entry_encode(Asn1Type, Entity) when is_atom(Asn1Type) ->
Der = der_encode(Asn1Type, Entity),
@@ -667,6 +691,7 @@ get_asn1_module('ECPrivateKey') -> 'ECPrivateKey';
get_asn1_module('ML-DSA-44-PrivateKey') -> 'X509-ML-DSA-2025';
get_asn1_module('ML-DSA-65-PrivateKey') -> 'X509-ML-DSA-2025';
get_asn1_module('ML-DSA-87-PrivateKey') -> 'X509-ML-DSA-2025';
+get_asn1_module('SLH-DSA-PrivateKey') -> 'SLH-DSA-Module-2024';
%% Certification Request Syntax Specification RFC 2986
get_asn1_module('CertificationRequest') -> 'PKCS-10';
get_asn1_module('CertificationRequestInfo') -> 'PKCS-10';
@@ -778,6 +803,22 @@ der_priv_key_decode(#'PrivateKeyInfo'{version = v1,
Alg == ?'id-ml-dsa-65';
Alg == ?'id-ml-dsa-87' ->
mldsa_priv_key_dec(Alg, PrivKey);
+der_priv_key_decode(#'PrivateKeyInfo'{version = v1,
+ privateKeyAlgorithm =
+ #'PrivateKeyAlgorithmIdentifier'{algorithm = Alg},
+ privateKey = PrivKey}) when Alg == ?'id-slh-dsa-sha2-128s';
+ Alg == ?'id-slh-dsa-sha2-128f';
+ Alg == ?'id-slh-dsa-sha2-192s';
+ Alg == ?'id-slh-dsa-sha2-192f';
+ Alg == ?'id-slh-dsa-sha2-256s';
+ Alg == ?'id-slh-dsa-sha2-256f';
+ Alg == ?'id-slh-dsa-shake-128s';
+ Alg == ?'id-slh-dsa-shake-128f';
+ Alg == ?'id-slh-dsa-shake-192s';
+ Alg == ?'id-slh-dsa-shake-192f';
+ Alg == ?'id-slh-dsa-shake-256s';
+ Alg == ?'id-slh-dsa-shake-256f' ->
+ slh_dsa_priv_key_dec(Alg, PrivKey);
der_priv_key_decode(#'OneAsymmetricKey'{
privateKeyAlgorithm = #'PrivateKeyAlgorithmIdentifier'{algorithm = CurveOId},
privateKey = CurvePrivKey,
@@ -882,12 +923,18 @@ der_encode('PrivateKeyInfo', #'ECPrivateKey'{parameters = Parameters} = PrivKey)
privateKeyAlgorithm = Alg,
privateKey = Key});
der_encode('PrivateKeyInfo', #'ML-DSAPrivateKey'{algorithm = Algorithm} = Key) ->
- Alg = #'PrivateKeyAlgorithmIdentifier'{algorithm = pubkey_cert:mldsa_algo_to_oid(Algorithm)},
+ Alg = #'PrivateKeyAlgorithmIdentifier'{algorithm = pubkey_cert_records:mldsa_algo_to_oid(Algorithm)},
PrivKey = mldsa_priv_key_enc(Key),
der_encode('OneAsymmetricKey',
#'OneAsymmetricKey'{version = v1,
privateKeyAlgorithm = Alg,
privateKey = PrivKey});
+der_encode('PrivateKeyInfo', #'SLH-DSAPrivateKey'{algorithm = Algorithm, key = Key}) ->
+ Alg = #'PrivateKeyAlgorithmIdentifier'{algorithm = pubkey_cert_records:slh_dsa_algo_to_oid(Algorithm)},
+ der_encode('OneAsymmetricKey',
+ #'OneAsymmetricKey'{version = v1,
+ privateKeyAlgorithm = Alg,
+ privateKey = Key});
der_encode('OneAsymmetricKey', #'ECPrivateKey'{parameters = {namedCurve, CurveOId},
privateKey = Key,
attributes = Attr,
@@ -1308,10 +1355,36 @@ generate_key({rsa, ModulusSize, PublicExponent}) ->
exponent1 = '?',
exponent2 = '?',
coefficient = '?'};
-
Other ->
Other
- end.
+ end;
+generate_key(KeyAlg) when KeyAlg == mldsa44;
+ KeyAlg == mldsa65;
+ KeyAlg == mldsa87 ->
+ {Public, Private} = crypto:generate_key(KeyAlg, []),
+ {#'ML-DSAPublicKey'{algorithm = KeyAlg,
+ key = Public},
+ #'ML-DSAPrivateKey'{algorithm = KeyAlg,
+ expandedkey = Private}
+ };
+generate_key(KeyAlg) when KeyAlg == slh_dsa_sha2_128s;
+ KeyAlg == slh_dsa_sha2_128f;
+ KeyAlg == slh_dsa_sha2_192s;
+ KeyAlg == slh_dsa_sha2_192f;
+ KeyAlg == slh_dsa_sha2_256s;
+ KeyAlg == slh_dsa_sha2_256f;
+ KeyAlg == slh_dsa_shake_128s;
+ KeyAlg == slh_dsa_shake_128f;
+ KeyAlg == slh_dsa_shake_192s;
+ KeyAlg == slh_dsa_shake_192f;
+ KeyAlg == slh_dsa_shake_256s;
+ KeyAlg == slh_dsa_shake_256f ->
+ {Public, Private} = crypto:generate_key(KeyAlg, []),
+ {#'SLH-DSAPublicKey'{algorithm = KeyAlg,
+ key = Public},
+ #'SLH-DSAPrivateKey'{algorithm = KeyAlg,
+ key = Private}
+ }.
%%--------------------------------------------------------------------
%% Description: Compute shared secret
@@ -1319,7 +1392,7 @@ generate_key({rsa, ModulusSize, PublicExponent}) ->
-doc(#{group => <<"Key API">>,
since => <<"OTP R16B01">>}).
-doc "Computes shared secret.".
--spec compute_key(OthersECDHkey, MyECDHkey) ->
+-spec compute_key(OthersECDHkey, MyECDHkey) ->
SharedSecret
when OthersECDHkey :: #'ECPoint'{},
MyECDHkey :: #'ECPrivateKey'{},
@@ -1357,11 +1430,12 @@ Translates signature algorithm OID to Erlang digest and signature types.
The `AlgorithmId` is the signature OID from a certificate or a certificate
revocation list.
""".
--spec pkix_sign_types(AlgorithmId) ->
+-spec pkix_sign_types(AlgorithmId) ->
{DigestType, SignatureType}
when AlgorithmId :: oid(),
DigestType :: digest_type(),
- SignatureType :: rsa | dsa | ecdsa | eddsa.
+ SignatureType :: rsa | dsa | ecdsa | eddsa |
+ crypto:mldsa() | crypto:slh_dsa().
%% Description:
%%--------------------------------------------------------------------
pkix_sign_types(?sha1WithRSAEncryption) ->
@@ -1403,14 +1477,38 @@ pkix_sign_types(?'id-ml-dsa-44') ->
pkix_sign_types(?'id-ml-dsa-65') ->
{none, mldsa65};
pkix_sign_types(?'id-ml-dsa-87') ->
- {none, mldsa87}.
+ {none, mldsa87};
+pkix_sign_types(?'id-slh-dsa-sha2-128s') ->
+ {none, slh_dsa_sha2_128s};
+pkix_sign_types(?'id-slh-dsa-sha2-128f') ->
+ {none, slh_dsa_sha2_128f};
+pkix_sign_types(?'id-slh-dsa-sha2-192s') ->
+ {none, slh_dsa_sha2_192s};
+pkix_sign_types(?'id-slh-dsa-sha2-192f') ->
+ {none, slh_dsa_sha2_192f};
+pkix_sign_types(?'id-slh-dsa-sha2-256s') ->
+ {none, slh_dsa_sha2_256s};
+pkix_sign_types(?'id-slh-dsa-sha2-256f') ->
+ {none, slh_dsa_sha2_256f};
+pkix_sign_types(?'id-slh-dsa-shake-128s') ->
+ {none, slh_dsa_shake_128s};
+pkix_sign_types(?'id-slh-dsa-shake-128f') ->
+ {none, slh_dsa_shake_128f};
+pkix_sign_types(?'id-slh-dsa-shake-192s') ->
+ {none, slh_dsa_shake_192s};
+pkix_sign_types(?'id-slh-dsa-shake-192f') ->
+ {none, slh_dsa_shake_192f};
+pkix_sign_types(?'id-slh-dsa-shake-256s') ->
+ {none, slh_dsa_shake_256s};
+pkix_sign_types(?'id-slh-dsa-shake-256f') ->
+ {none, slh_dsa_shake_256f}.
%%--------------------------------------------------------------------
-doc(#{group => <<"Certificate API">>,
since => <<"OTP 23.0">>}).
-doc "Translates OID to Erlang digest type".
--spec pkix_hash_type(HashOid::oid()) -> DigestType:: md5 | crypto:sha1() | crypto:sha2().
-
+-spec pkix_hash_type(HashOid::oid()) -> DigestType:: digest_type().
+
pkix_hash_type(?'id-sha1') ->
sha;
pkix_hash_type(?'id-sha512') ->
@@ -1652,6 +1750,9 @@ pkix_verify(DerCert, Key = {#'ECPoint'{}, _}) when is_binary(DerCert) ->
verify(PlainText, DigestType, Signature, Key)
end;
pkix_verify(DerCert, #'ML-DSAPublicKey'{} = Key) ->
+ {DigestType, PlainText, Signature} = pubkey_cert:verify_data(DerCert),
+ verify(PlainText, DigestType, Signature, Key);
+pkix_verify(DerCert, #'SLH-DSAPublicKey'{} = Key) ->
{DigestType, PlainText, Signature} = pubkey_cert:verify_data(DerCert),
verify(PlainText, DigestType, Signature, Key).
%%--------------------------------------------------------------------
@@ -2579,6 +2680,8 @@ format_sign_key(#'ML-DSAPrivateKey'{algorithm = Algo, seed = Key}) when Key =/=
{Algo, {seed, Key}};
format_sign_key(#'ML-DSAPrivateKey'{algorithm = Algo, expandedkey = Key}) when Key =/= undefined ->
{Algo, {expandedkey, Key}};
+format_sign_key(#'SLH-DSAPrivateKey'{algorithm = Algo, key = Key}) ->
+ {Algo, Key};
format_sign_key({ed_pri, Curve, _Pub, Priv}) ->
{eddsa, [Priv,Curve]};
format_sign_key(_) ->
@@ -2601,6 +2704,8 @@ format_verify_key(#'ML-DSAPublicKey'{algorithm = Algo, key = Key}) ->
{Algo, Key};
format_verify_key({#'ML-DSAPublicKey'{algorithm = Algo, key = Key},_}) ->
{Algo, Key};
+format_verify_key(#'SLH-DSAPublicKey'{algorithm = Algo, key = Key}) ->
+ {Algo, Key};
%% Convert private keys to public keys
format_verify_key(#'RSAPrivateKey'{modulus = Mod, publicExponent = Exp}) ->
format_verify_key(#'RSAPublicKey'{modulus = Mod, publicExponent = Exp});
@@ -2943,22 +3048,14 @@ ec_key({PubKey, PrivateKey}, Params) ->
parameters = Params,
publicKey = PubKey}.
-mldsa_pub_key(?'id-ml-dsa-44', PubKey) ->
- #'ML-DSAPublicKey'{algorithm = mldsa44,
- key = PubKey};
-mldsa_pub_key(?'id-ml-dsa-65', PubKey) ->
- #'ML-DSAPublicKey'{algorithm = mldsa65,
- key = PubKey};
-mldsa_pub_key(?'id-ml-dsa-87', PubKey) ->
- #'ML-DSAPublicKey'{algorithm = mldsa87,
+mldsa_pub_key(AlgOid, PubKey) ->
+ #'ML-DSAPublicKey'{algorithm = pubkey_cert_records:oid_to_ml_dsa_algo(AlgOid),
key = PubKey}.
-mldsa_priv_key_dec(?'id-ml-dsa-44', DERKey) ->
- mldsa_priv_key_dec('ML-DSA-44-PrivateKey', DERKey, #'ML-DSAPrivateKey'{algorithm = mldsa44});
-mldsa_priv_key_dec(?'id-ml-dsa-65', DERKey) ->
- mldsa_priv_key_dec('ML-DSA-65-PrivateKey', DERKey, #'ML-DSAPrivateKey'{algorithm = mldsa65});
-mldsa_priv_key_dec(?'id-ml-dsa-87', DERKey) ->
- mldsa_priv_key_dec('ML-DSA-87-PrivateKey', DERKey, #'ML-DSAPrivateKey'{algorithm = mldsa87}).
+mldsa_priv_key_dec(AlgOid, DERKey) ->
+ Alg = pubkey_cert_records:oid_to_ml_dsa_algo(AlgOid),
+ mldsa_priv_key_dec(mldsa_algo_to_type(Alg), DERKey,
+ #'ML-DSAPrivateKey'{algorithm = Alg}).
mldsa_priv_key_dec(Type, DERKey, PrivKey) ->
case der_decode(Type, DERKey) of
@@ -2971,7 +3068,6 @@ mldsa_priv_key_dec(Type, DERKey, PrivKey) ->
expandedkey = ExpandedKey}
end.
-
mldsa_priv_key_enc(#'ML-DSAPrivateKey'{algorithm = Alg,
seed = Seed,
expandedkey = <<>>}) ->
@@ -2993,6 +3089,14 @@ mldsa_algo_to_type(mldsa65) ->
mldsa_algo_to_type(mldsa87) ->
'ML-DSA-87-PrivateKey'.
+slh_dsa_pub_key(AlgOid, PubKey) ->
+ #'SLH-DSAPublicKey'{algorithm = pubkey_cert_records:oid_to_slh_dsa_algo(AlgOid),
+ key = PubKey}.
+
+slh_dsa_priv_key_dec(AlgOid, Key) ->
+ #'SLH-DSAPrivateKey'{algorithm = pubkey_cert_records:oid_to_slh_dsa_algo(AlgOid),
+ key = Key}.
+
encode_name_for_short_hash({rdnSequence, Attributes0}) ->
Attributes = lists:map(fun normalise_attribute/1, Attributes0),
{Encoded, _} = 'OTP-PKIX':enc_HashRDNSequence(Attributes, []),
diff --git a/lib/public_key/src/public_key_internal.hrl b/lib/public_key/src/public_key_internal.hrl
index 155d9a2408..8198ccacbb 100644
--- a/lib/public_key/src/public_key_internal.hrl
+++ b/lib/public_key/src/public_key_internal.hrl
@@ -34,6 +34,9 @@
-include("OTP-PKIX.hrl").
-include("PKCS-1.hrl").
+-include("SLH-DSA-Module-2024.hrl").
+-undef('nistAlgorithms').
+-undef('sigAlgs').
-include("X509-ML-DSA-2025.hrl").
%% Bug in ASN.1 compiler (hardcode the correct value)
@@ -137,15 +140,30 @@
-record('ML-DSAPrivateKey',
{
- algorithm :: mldsa44 | mldsa65 | mldsa87,
+ algorithm :: crypto:mldsa(),
seed = <<>> :: binary(),
expandedkey = <<>> :: binary()
}).
-record('ML-DSAPublicKey',
{
- algorithm :: mldsa44 | mldsa65 | mldsa87,
- key :: binary()
+ algorithm :: crypto:mldsa(),
+ key :: binary()
+ }).
+
+%%
+%%% SLH-DSA
+%%%
+-record('SLH-DSAPrivateKey',
+ {
+ algorithm :: crypto:slh_dsa(),
+ key :: binary()
+ }).
+
+-record('SLH-DSAPublicKey',
+ {
+ algorithm :: crypto:slh_dsa(),
+ key :: binary()
}).
-record('ECParameters',
diff --git a/lib/public_key/test/public_key_SUITE.erl b/lib/public_key/test/public_key_SUITE.erl
index fd15609a42..6524fa2ec7 100644
--- a/lib/public_key/test/public_key_SUITE.erl
+++ b/lib/public_key/test/public_key_SUITE.erl
@@ -69,6 +69,10 @@
mldsa_priv_pkcs8/1,
mldsa_pub_pem/0,
mldsa_pub_pem/1,
+ slh_dsa_priv_pkcs8/0,
+ slh_dsa_priv_pkcs8/1,
+ slh_dsa_pub_pem/0,
+ slh_dsa_pub_pem/1,
eddsa_sign_verify_24_compat/1,
init_ec_pem_encode_generated/1,
ec_pem_encode_generated/0,
@@ -98,8 +102,12 @@
mldsa_verify/1,
mldsa_sign/0,
mldsa_sign/1,
+ slh_dsa_verify/0,
+ slh_dsa_verify/1,
+ slh_dsa_sign/0,
+ slh_dsa_sign/1,
dsa_sign_verify/0,
- dsa_sign_verify/1,
+ dsa_sign_verify/1,
custom_sign_fun_verify/0,
custom_sign_fun_verify/1,
pkix/0,
@@ -183,11 +191,11 @@
%% Common Test interface functions -----------------------------------
%%--------------------------------------------------------------------
-suite() ->
+suite() ->
[].
-all() ->
- [app,
+all() ->
+ [app,
appup,
{group, pem_decode_encode},
encrypt_decrypt,
@@ -204,11 +212,11 @@ all() ->
pkix_ext_key_usage,
pkix_ext_key_usage_any,
pkix_path_validation_bad_date,
- pkix_iso_rsa_oid,
- pkix_iso_dsa_oid,
+ pkix_iso_rsa_oid,
+ pkix_iso_dsa_oid,
pkix_rsa_md2_oid,
pkix_dsa_sha2_oid,
- pkix_crl,
+ pkix_crl,
pkix_pss_params_in_signalg,
pkix_hash_type,
general_name,
@@ -221,23 +229,23 @@ all() ->
pkix_test_data,
pkix_is_issuer,
pkix_extensionreq,
- short_cert_issuer_hash,
+ short_cert_issuer_hash,
short_crl_issuer_hash,
cacerts_load,
ocsp_extensions,
pkix_ocsp_validate | maybe_more()
].
-groups() ->
- [{pem_decode_encode, [], [dsa_pem, rsa_pem, rsa_pss_pss_pem,
+groups() ->
+ [{pem_decode_encode, [], [dsa_pem, rsa_pem, rsa_pss_pss_pem,
rsa_pss_default_pem, ec_pem,
encrypted_pem_pwdstring, encrypted_pem_pwdfun,
dh_pem, cert_pem, pkcs7_pem, pkcs10_pem,
rsa_priv_pkcs8, dsa_priv_pkcs8, ec_priv_pkcs8,
eddsa_priv_pkcs8, eddsa_priv_rfc5958, mldsa_pub_pem,
- mldsa_priv_pkcs8]},
+ mldsa_priv_pkcs8, slh_dsa_pub_pem, slh_dsa_priv_pkcs8]},
{sign_verify, [], [rsa_sign_verify, rsa_pss_sign_verify, mldsa_verify,
- mldsa_sign, dsa_sign_verify,
+ mldsa_sign, slh_dsa_verify, slh_dsa_sign, dsa_sign_verify,
eddsa_sign_verify_24_compat, custom_sign_fun_verify]},
{explicit_ec_params,
[ec_pem2,
@@ -293,8 +301,8 @@ init_per_testcase(rsa_pss_sign_verify, Config) ->
Supports = crypto:supports(),
RSAOpts = proplists:get_value(rsa_opts, Supports),
- case lists:member(rsa_pkcs1_pss_padding, RSAOpts)
- andalso lists:member(rsa_pss_saltlen, RSAOpts)
+ case lists:member(rsa_pkcs1_pss_padding, RSAOpts)
+ andalso lists:member(rsa_pss_saltlen, RSAOpts)
andalso lists:member(rsa_mgf1_md, RSAOpts) of
true ->
Config;
@@ -321,13 +329,35 @@ init_per_testcase(TestCase, Config) when TestCase == mldsa_sign;
false ->
{skip, mldsa_not_supported_by_crypto}
end;
+init_per_testcase(TestCase, Config) when TestCase == slh_dsa_sign;
+ TestCase == slh_dsa_verify ->
+ PkAlgs = crypto:supports(public_keys),
+ case
+ lists:member(slh_dsa_sha2_128f, PkAlgs) andalso
+ lists:member(slh_dsa_sha2_128s, PkAlgs) andalso
+ lists:member(slh_dsa_sha2_192f, PkAlgs) andalso
+ lists:member(slh_dsa_sha2_192s, PkAlgs) andalso
+ lists:member(slh_dsa_sha2_256f, PkAlgs) andalso
+ lists:member(slh_dsa_sha2_256s, PkAlgs) andalso
+ lists:member(slh_dsa_shake_128f, PkAlgs) andalso
+ lists:member(slh_dsa_shake_128s, PkAlgs) andalso
+ lists:member(slh_dsa_shake_192f, PkAlgs) andalso
+ lists:member(slh_dsa_shake_192s, PkAlgs) andalso
+ lists:member(slh_dsa_shake_256f, PkAlgs) andalso
+ lists:member(slh_dsa_shake_256s, PkAlgs)
+ of
+ true ->
+ Config;
+ false ->
+ {skip, slhdsa_not_supported_by_crypto}
+ end;
init_per_testcase(TestCase, Config) ->
case TestCase of
ec_pem_encode_generated ->
init_ec_pem_encode_generated(Config);
_ -> init_common_per_testcase(Config)
end.
-
+
init_common_per_testcase(Config0) ->
Config = lists:keydelete(watchdog, 1, Config0),
Dog = ct:timetrap(?TIMEOUT),
@@ -401,7 +431,7 @@ rsa_pem(Config) when is_list(Config) ->
RSAKey0 = public_key:der_decode('RSAPrivateKey', DerRSAKey),
RSAKey0 = public_key:pem_entry_decode(Entry0),
-
+
[{'RSAPrivateKey', _, {_,_}} = Entry1] =
erl_make_certs:pem_to_der(filename:join(Datadir, "rsa.pem")),
@@ -478,11 +508,11 @@ ec_pem(Config) when is_list(Config) ->
PubEntry0 = public_key:pem_entry_encode('SubjectPublicKeyInfo', ECPubKey),
ECPubPemNoEndNewLines = strip_superfluous_newlines(ECPubPem),
ECPubPemNoEndNewLines = strip_superfluous_newlines(public_key:pem_encode([PubEntry0])),
-
+
{ok, ECPrivPem} = file:read_file(filename:join(Datadir, "ec_key.pem")),
[{'EcpkParameters', _, not_encrypted} = Entry1,
{'ECPrivateKey', _, not_encrypted} = Entry2] = public_key:pem_decode(ECPrivPem),
-
+
ECParams = public_key:pem_entry_decode(Entry1),
true = check_entry_type(ECParams, 'EcpkParameters'),
ECPrivKey = public_key:pem_entry_decode(Entry2),
@@ -567,6 +597,23 @@ eddsa_pub(Config) when is_list(Config) ->
ECPemNoEndNewLines = strip_superfluous_newlines(EDDSAPubPem),
ECPemNoEndNewLines = strip_superfluous_newlines(public_key:pem_encode([PemEntry0])).
+mldsa_priv_pkcs8() ->
+ [{doc, "ML-DSA PKCS8 private key decode/encode"}].
+mldsa_priv_pkcs8(Config) when is_list(Config) ->
+ ml_dsa_priv("mldsa-44.pem", ?'id-ml-dsa-44', Config),
+ ml_dsa_priv("mldsa-65.pem", ?'id-ml-dsa-65', Config),
+ ml_dsa_priv("mldsa-87.pem", ?'id-ml-dsa-87', Config).
+
+ml_dsa_priv(File, AlgOid, Config) ->
+ Datadir = proplists:get_value(data_dir, Config),
+ {ok, MLDSAPrivPem} = file:read_file(filename:join(Datadir, File)),
+ [{'PrivateKeyInfo', _, not_encrypted} = PKCS8Key] = public_key:pem_decode(MLDSAPrivPem),
+ MLDSAKey = #'ML-DSAPrivateKey'{} = public_key:pem_entry_decode(PKCS8Key),
+ true = check_entry_type(MLDSAKey, AlgOid),
+ PrivEntry0 = public_key:pem_entry_encode('PrivateKeyInfo', MLDSAKey),
+ MLDSAPemNoEndNewLines = strip_licence(strip_superfluous_newlines(MLDSAPrivPem)),
+ MLDSAPemNoEndNewLines = strip_superfluous_newlines(public_key:pem_encode([PrivEntry0])).
+
mldsa_pub_pem() ->
[{doc, "ML-DSA public_key decode/encode"}].
mldsa_pub_pem(Config) when is_list(Config) ->
@@ -586,22 +633,37 @@ ml_dsa_pub(File, AlgOid, Config) ->
MLDSAPemNoEndNewLines = strip_licence(strip_superfluous_newlines(MLDSAPubPem)),
MLDSAPemNoEndNewLines = strip_superfluous_newlines(public_key:pem_encode([PubEntry0])).
-mldsa_priv_pkcs8() ->
- [{doc, "ML-DSA PKCS8 private key decode/encode"}].
-mldsa_priv_pkcs8(Config) when is_list(Config) ->
- ml_dsa_priv("mldsa-44.pem", ?'id-ml-dsa-44', Config),
- ml_dsa_priv("mldsa-65.pem", ?'id-ml-dsa-65', Config),
- ml_dsa_priv("mldsa-87.pem", ?'id-ml-dsa-87', Config).
+slh_dsa_priv_pkcs8() ->
+ [{doc, "SLH-DSA PKCS8 private key decode/encode"}].
+slh_dsa_priv_pkcs8(Config) when is_list(Config) ->
+ slh_dsa_priv("slh-dsa-sha2-128s.pem", ?'id-slh-dsa-sha2-128s', Config).
-ml_dsa_priv(File, AlgOid, Config) ->
+slh_dsa_priv(File, AlgOid, Config) ->
Datadir = proplists:get_value(data_dir, Config),
- {ok, MLDSAPrivPem} = file:read_file(filename:join(Datadir, File)),
- [{'PrivateKeyInfo', _, not_encrypted} = PKCS8Key] = public_key:pem_decode(MLDSAPrivPem),
- MLDSAKey = #'ML-DSAPrivateKey'{} = public_key:pem_entry_decode(PKCS8Key),
- true = check_entry_type(MLDSAKey, AlgOid),
- PrivEntry0 = public_key:pem_entry_encode('PrivateKeyInfo', MLDSAKey),
- MLDSAPemNoEndNewLines = strip_licence(strip_superfluous_newlines(MLDSAPrivPem)),
- MLDSAPemNoEndNewLines = strip_superfluous_newlines(public_key:pem_encode([PrivEntry0])).
+ {ok, SLHDSAPrivPem} = file:read_file(filename:join(Datadir, File)),
+ [{'PrivateKeyInfo', _, not_encrypted} = PKCS8Key] = public_key:pem_decode(SLHDSAPrivPem),
+ SLHDSAKey = #'SLH-DSAPrivateKey'{} = public_key:pem_entry_decode(PKCS8Key),
+ true = check_entry_type(SLHDSAKey, AlgOid),
+ PrivEntry0 = public_key:pem_entry_encode('PrivateKeyInfo', SLHDSAKey),
+ SLHDSAPemNoEndNewLines = strip_licence(strip_superfluous_newlines(SLHDSAPrivPem)),
+ SLHDSAPemNoEndNewLines = strip_superfluous_newlines(public_key:pem_encode([PrivEntry0])).
+
+slh_dsa_pub_pem() ->
+ [{doc, "SLH-DSA public_key decode/encode"}].
+slh_dsa_pub_pem(Config) when is_list(Config) ->
+ slh_dsa_pub("slh-dsa-sha2-128s-pub.pem", ?'id-slh-dsa-sha2-128s', Config).
+
+slh_dsa_pub(File, AlgOid, Config) ->
+ Datadir = proplists:get_value(data_dir, Config),
+ {ok, SLHDSAPubPem} = file:read_file(filename:join(Datadir, File)),
+ [{'SubjectPublicKeyInfo', _, _} = PubEntry0] =
+ public_key:pem_decode(SLHDSAPubPem),
+ SLHDSAPubKey = #'SLH-DSAPublicKey'{} = public_key:pem_entry_decode(PubEntry0),
+ true = check_entry_type(SLHDSAPubKey, AlgOid),
+ PubEntry0 = public_key:pem_entry_encode('SubjectPublicKeyInfo', SLHDSAPubKey),
+
+ SLHDSAPemNoEndNewLines = strip_licence(strip_superfluous_newlines(SLHDSAPubPem)),
+ SLHDSAPemNoEndNewLines = strip_superfluous_newlines(public_key:pem_encode([PubEntry0])).
eddsa_sign_verify_24_compat(_Config) ->
Key =
@@ -760,22 +822,21 @@ pkcs7_pem(Config) when is_list(Config) ->
erl_make_certs:pem_to_der(filename:join(Datadir, "pkcs7_ext.pem")),
asn1_encode_decode(Entry0),
asn1_encode_decode(Entry1).
-
+
%%--------------------------------------------------------------------
cert_pem() ->
[{doc, "Certificate PEM-file decode/encode"}].
cert_pem(Config) when is_list(Config) ->
Datadir = proplists:get_value(data_dir, Config),
-
- [{'Certificate', _, not_encrypted} = Entry0] =
+
+ [{'Certificate', _, not_encrypted} = Entry0] =
erl_make_certs:pem_to_der(filename:join(Datadir, "client_cert.pem")),
-
+
asn1_encode_decode(Entry0),
-
- [{'Certificate', _, not_encrypted} = Entry1,
- {'Certificate', _, not_encrypted} = Entry2] =
+
+ [{'Certificate', _, not_encrypted} = Entry1,
+ {'Certificate', _, not_encrypted} = Entry2] =
erl_make_certs:pem_to_der(filename:join(Datadir, "cacerts.pem")),
-
asn1_encode_decode(Entry1),
asn1_encode_decode(Entry2).
@@ -843,7 +904,7 @@ ext_encoding(_Config) ->
%%--------------------------------------------------------------------
encrypt_decrypt() ->
[{doc, "Test public_key:encrypt_private and public_key:decrypt_public"}].
-encrypt_decrypt(Config) when is_list(Config) ->
+encrypt_decrypt(Config) when is_list(Config) ->
{PrivateKey, _DerKey} = erl_make_certs:gen_rsa(64),
#'RSAPrivateKey'{modulus=Mod, publicExponent=Exp} = PrivateKey,
PublicKey = #'RSAPublicKey'{modulus=Mod, publicExponent=Exp},
@@ -869,43 +930,43 @@ encrypt_decrypt_sign_fun(Config) when is_list(Config) ->
RsaEncrypted = public_key:encrypt_private(Msg, CustomPrivKey),
Msg = public_key:decrypt_public(RsaEncrypted, PublicKey),
ok.
-
+
%%--------------------------------------------------------------------
rsa_sign_verify() ->
[{doc, "Checks that we can sign and verify rsa signatures."}].
rsa_sign_verify(Config) when is_list(Config) ->
Ca = {_, CaKey} = erl_make_certs:make_cert([]),
{Cert1, _} = erl_make_certs:make_cert([{key, dsa}, {issuer, Ca}]),
- PrivateRSA = #'RSAPrivateKey'{modulus=Mod, publicExponent=Exp} =
+ PrivateRSA = #'RSAPrivateKey'{modulus=Mod, publicExponent=Exp} =
public_key:pem_entry_decode(CaKey),
PublicRSA = #'RSAPublicKey'{modulus=Mod, publicExponent=Exp},
true = public_key:pkix_verify(Cert1, PublicRSA),
Msg = list_to_binary(lists:duplicate(5, "Foo bar 100")),
RSASign = public_key:sign(Msg, sha, PrivateRSA),
- true = public_key:verify(Msg, sha, RSASign, PublicRSA),
- false = public_key:verify(<<1:8, Msg/binary>>, sha, RSASign, PublicRSA),
- false = public_key:verify(Msg, sha, <<1:8, RSASign/binary>>, PublicRSA),
+ true = public_key:verify(Msg, sha, RSASign, PublicRSA),
+ false = public_key:verify(<<1:8, Msg/binary>>, sha, RSASign, PublicRSA),
+ false = public_key:verify(Msg, sha, <<1:8, RSASign/binary>>, PublicRSA),
RSASign1 = public_key:sign(Msg, md5, PrivateRSA),
true = public_key:verify(Msg, md5, RSASign1, PublicRSA).
-
+
%%--------------------------------------------------------------------
rsa_pss_sign_verify() ->
[{doc, "Checks that we can sign and verify rsa pss signatures."}].
rsa_pss_sign_verify(Config) when is_list(Config) ->
- CertChainConf = #{server_chain =>
+ CertChainConf = #{server_chain =>
#{root => [],
intermediates => [],
peer => []},
- client_chain =>
+ client_chain =>
#{root => [{key, {hardcode_rsa_key(1), pss_params(sha256)}}],
intermediates => [],
peer => []}},
#{client_config := ClientConf} = public_key:pkix_test_data(CertChainConf),
Cert = proplists:get_value(cert, ClientConf),
{#'RSAPrivateKey'{modulus=Mod, publicExponent=Exp}, Parms} = {hardcode_rsa_key(1), pss_params(sha256)},
-
+
true = public_key:pkix_verify(Cert, {#'RSAPublicKey'{modulus=Mod, publicExponent=Exp}, Parms}).
%%--------------------------------------------------------------------
@@ -938,6 +999,36 @@ mldsa_sign(Config) when is_list(Config) ->
Signature = public_key:sign(Msg, none, MLDSAPrivKey),
public_key:verify(Msg, none, Signature, MLDSAPubKey).
+%--------------------------------------------------------------------
+slh_dsa_verify() ->
+ [{doc, "Checks that we can verify slh-dsa signatures."}].
+slh_dsa_verify(Config) when is_list(Config) ->
+ Datadir = proplists:get_value(data_dir, Config),
+ {ok, SLHDSAPubPem} = file:read_file(filename:join(Datadir, "slh-dsa-sha2-128s-pub.pem")),
+ [{'SubjectPublicKeyInfo', _, _} = PubEntry0] =
+ public_key:pem_decode(SLHDSAPubPem),
+ {ok, SLHDSACertPem} = file:read_file(filename:join(Datadir, "slh-dsa-cert.pem")),
+ [{_, Cert, _}] = public_key:pem_decode(SLHDSACertPem),
+ SLHDSAPubKey = #'SLH-DSAPublicKey'{} = public_key:pem_entry_decode(PubEntry0),
+ true = public_key:pkix_verify(Cert, SLHDSAPubKey).
+
+%%--------------------------------------------------------------------
+slh_dsa_sign() ->
+ [{doc, "Checks that we can sign and verify slh-dsa signatures."}].
+slh_dsa_sign(Config) when is_list(Config) ->
+ Datadir = proplists:get_value(data_dir, Config),
+ Msg = list_to_binary(lists:duplicate(5, "Foo bar 100")),
+ {ok, SLHDSAPubPem} = file:read_file(filename:join(Datadir, "slh-dsa-sha2-128s-pub.pem")),
+ [{'SubjectPublicKeyInfo', _, _} = PubEntry0] =
+ public_key:pem_decode(SLHDSAPubPem),
+ SLHDSAPubKey = #'SLH-DSAPublicKey'{} = public_key:pem_entry_decode(PubEntry0),
+ {ok, SLHDSAPrivPem} = file:read_file(filename:join(Datadir, "slh-dsa-sha2-128s.pem")),
+ [{'PrivateKeyInfo', _, _} = PubEntry1] =
+ public_key:pem_decode(SLHDSAPrivPem),
+ SLHDSAPrivKey = #'SLH-DSAPrivateKey'{} = public_key:pem_entry_decode(PubEntry1),
+ Signature = public_key:sign(Msg, none, SLHDSAPrivKey),
+ public_key:verify(Msg, none, Signature, SLHDSAPubKey).
+
%%--------------------------------------------------------------------
dsa_sign_verify() ->
[{doc, "Checks that we can sign and verify dsa signatures."}].
@@ -951,8 +1042,8 @@ dsa_sign_verify(Config) when is_list(Config) ->
true = public_key:pkix_verify(Cert2, {Y, #'Dss-Parms'{p=P, q=Q, g=G}}),
Datadir = proplists:get_value(data_dir, Config),
- [DsaKey = {'DSAPrivateKey', _, _}] =
- erl_make_certs:pem_to_der(filename:join(Datadir, "dsa.pem")),
+ [DsaKey = {'DSAPrivateKey', _, _}] =
+ erl_make_certs:pem_to_der(filename:join(Datadir, "dsa.pem")),
DSAPrivateKey = public_key:pem_entry_decode(DsaKey),
#'DSAPrivateKey'{p=P1, q=Q1, g=G1, y=Y1, x=_X1} = DSAPrivateKey,
@@ -960,19 +1051,19 @@ dsa_sign_verify(Config) when is_list(Config) ->
DSASign = public_key:sign(Msg, sha, DSAPrivateKey),
DSAPublicKey = Y1,
DSAParams = #'Dss-Parms'{p=P1, q=Q1, g=G1},
- true = public_key:verify(Msg, sha, DSASign, {DSAPublicKey, DSAParams}),
- false = public_key:verify(<<1:8, Msg/binary>>, sha, DSASign,
- {DSAPublicKey, DSAParams}),
- false = public_key:verify(Msg, sha, <<1:8, DSASign/binary>>,
- {DSAPublicKey, DSAParams}),
-
+ true = public_key:verify(Msg, sha, DSASign, {DSAPublicKey, DSAParams}),
+ false = public_key:verify(<<1:8, Msg/binary>>, sha, DSASign,
+ {DSAPublicKey, DSAParams}),
+ false = public_key:verify(Msg, sha, <<1:8, DSASign/binary>>,
+ {DSAPublicKey, DSAParams}),
+
Digest = crypto:hash(sha,Msg),
DigestSign = public_key:sign(Digest, none, DSAPrivateKey),
- true = public_key:verify(Digest, none, DigestSign, {DSAPublicKey, DSAParams}),
+ true = public_key:verify(Digest, none, DigestSign, {DSAPublicKey, DSAParams}),
<<_:8, RestDigest/binary>> = Digest,
- false = public_key:verify(<<1:8, RestDigest/binary>>, none, DigestSign,
- {DSAPublicKey, DSAParams}),
- false = public_key:verify(Digest, none, <<1:8, DigestSign/binary>>,
+ false = public_key:verify(<<1:8, RestDigest/binary>>, none, DigestSign,
+ {DSAPublicKey, DSAParams}),
+ false = public_key:verify(Digest, none, <<1:8, DigestSign/binary>>,
{DSAPublicKey, DSAParams}).
%%--------------------------------------------------------------------
@@ -1007,12 +1098,12 @@ pkix(Config) when is_list(Config) ->
TestTransform = fun({'Certificate', CertDer, not_encrypted}) ->
PlainCert = public_key:pkix_decode_cert(CertDer, plain),
OtpCert = public_key:pkix_decode_cert(CertDer, otp),
- CertDer =
+ CertDer =
public_key:pkix_encode('OTPCertificate', OtpCert, otp),
- CertDer =
+ CertDer =
public_key:pkix_encode('Certificate', PlainCert, plain),
OTPTBS = OtpCert#'OTPCertificate'.tbsCertificate,
- OTPSubj = OTPTBS#'OTPTBSCertificate'.subject,
+ OTPSubj = OTPTBS#'OTPTBSCertificate'.subject,
DNEncoded = public_key:pkix_encode('Name', OTPSubj, otp),
PlainTBS = PlainCert#'Certificate'.tbsCertificate,
Subj2 = PlainTBS#'TBSCertificate'.subject,
@@ -1023,31 +1114,30 @@ pkix(Config) when is_list(Config) ->
[TestTransform(Cert) || Cert <- Certs0 ++ Certs1],
Root = element(2, hd(Certs0)),
- Peer = element(2, hd(Certs1)),
+ Peer = element(2, hd(Certs1)),
true = public_key:pkix_is_self_signed(Root),
false = public_key:pkix_is_self_signed(Peer),
- CaIds = [element(2, public_key:pkix_issuer_id(Cert, self)) ||
+ CaIds = [element(2, public_key:pkix_issuer_id(Cert, self)) ||
{'Certificate', Cert, _} <- Certs0],
- {ok, IssuerId} =
+ {ok, IssuerId} =
public_key:pkix_issuer_id(Peer, other),
-
+
{ok, Id} = public_key:pkix_issuer_id(Root, self),
Id = public_key:pkix_subject_id(Root),
true = lists:member(IssuerId, CaIds),
%% Should be normalized already
- TestStr = {rdnSequence,
+ TestStr = {rdnSequence,
[[{'AttributeTypeAndValue', {2,5,4,3},{printableString,"ERLANGCA"}}],
[{'AttributeTypeAndValue', {2,5,4,3},{printableString," erlang ca "}}]]},
- VerifyStr = {rdnSequence,
+ VerifyStr = {rdnSequence,
[[{'AttributeTypeAndValue', {2,5,4,3},{printableString,"erlangca"}}],
- [{'AttributeTypeAndValue', {2,5,4,3},{printableString,"erlang ca"}}]]},
+ [{'AttributeTypeAndValue', {2,5,4,3},{printableString,"erlang ca"}}]]},
VerifyStr = public_key:pkix_normalize_name(TestStr).
-
-
+
%%--------------------------------------------------------------------
pkix_countryname() ->
[{doc, "Test workaround for certs that code x509countryname as utf8"}].
@@ -1087,7 +1177,7 @@ pkix_decode_cert(Config) when is_list(Config) ->
pkix_path_validation() ->
[{doc, "Test PKIX path validation"}].
pkix_path_validation(Config) when is_list(Config) ->
- CaK = {Trusted,_} =
+ CaK = {Trusted,_} =
erl_make_certs:make_cert([{key, dsa},
{subject, [
{name, "Public Key"},
@@ -1102,23 +1192,23 @@ pkix_path_validation(Config) when is_list(Config) ->
ok = erl_make_certs:write_pem("./", "public_key_cacert", CaK),
CertK1 = {Cert1, _} = erl_make_certs:make_cert([{issuer, CaK}]),
- CertK2 = {Cert2,_} = erl_make_certs:make_cert([{issuer, CertK1},
+ CertK2 = {Cert2,_} = erl_make_certs:make_cert([{issuer, CertK1},
{digest, md5}, {extensions, false}]),
ok = erl_make_certs:write_pem("./", "public_key_cert", CertK2),
-
+
{ok, _} = public_key:pkix_path_validation(Trusted, [Cert1], []),
-
- {error, {bad_cert,invalid_issuer}} =
+
+ {error, {bad_cert,invalid_issuer}} =
public_key:pkix_path_validation(Trusted, [Cert2], []),
-
- {ok, _} = public_key:pkix_path_validation(Trusted, [Cert1, Cert2], []),
+
+ {ok, _} = public_key:pkix_path_validation(Trusted, [Cert1, Cert2], []),
{error, {bad_cert, duplicate_cert_in_path}} =
public_key:pkix_path_validation(Trusted, [Cert1, Cert1, Cert2], []),
{error, issuer_not_found} = public_key:pkix_issuer_id(Cert2, other),
- CertK3 = {Cert3,_} = erl_make_certs:make_cert([{issuer, CertK1},
+ CertK3 = {Cert3,_} = erl_make_certs:make_cert([{issuer, CertK1},
{extensions, [{basic_constraints, false}]}]),
{Cert4,_} = erl_make_certs:make_cert([{issuer, CertK3}, {extensions, [{key_usage, undefined}]}]),
@@ -1193,19 +1283,19 @@ pkix_path_validation_root_expired() ->
[{doc, "Test root expiration so that it does not fall between chairs"}].
pkix_path_validation_root_expired(Config) when is_list(Config) ->
{Year, Month, Day} = date(),
- SRoot = public_key:pkix_test_root_cert("OTP test server ROOT", [{validity, {{Year-2, Month, Day},
+ SRoot = public_key:pkix_test_root_cert("OTP test server ROOT", [{validity, {{Year-2, Month, Day},
{Year-1, Month, Day}}}]),
#{server_config := Conf} = public_key:pkix_test_data(#{server_chain => #{root => SRoot,
intermediates => [],
peer => []},
- client_chain => #{root => [],
+ client_chain => #{root => [],
intermediates => [],
peer => []}}),
[ICA, Root] = proplists:get_value(cacerts, Conf),
true = public_key:pkix_is_self_signed(Root),
Peer = proplists:get_value(cert, Conf),
{error, {bad_cert, cert_expired}} = public_key:pkix_path_validation(Root, [ICA, Peer], []).
-
+
pkix_ext_key_usage() ->
[{doc, "If extended key usage is a critical extension in a CA (usually not included) make sure it is compatible with keyUsage extension"}].
pkix_ext_key_usage(Config) when is_list(Config) ->
@@ -1468,21 +1558,21 @@ pkix_verify_hostname_options(Config) ->
DataDir = proplists:get_value(data_dir, Config),
{ok,Bin} = file:read_file(filename:join(DataDir,"pkix_verify_hostname_cn.pem")),
Cert = public_key:pkix_decode_cert(element(2,hd(public_key:pem_decode(Bin))), otp),
-
+
%% Check that the fail_callback is called and is presented the correct certificate:
true = public_key:pkix_verify_hostname(Cert, [{dns_id,"erlang.org"}],
[{fail_callback,
- fun(#'OTPCertificate'{}=C) when C==Cert ->
+ fun(#'OTPCertificate'{}=C) when C==Cert ->
true; % To test the return value matters
- (#'OTPCertificate'{}=C) ->
+ (#'OTPCertificate'{}=C) ->
ct:log("~p:~p: Wrong cert:~n~p~nExpect~n~p",
[?MODULE, ?LINE, C, Cert]),
ct:fail("Wrong cert, see log");
- (C) ->
+ (C) ->
ct:log("~p:~p: Bad cert: ~p",[?MODULE,?LINE,C]),
ct:fail("Bad cert, see log")
end}]),
-
+
%% Check the callback for user-provided match functions:
true = public_key:pkix_verify_hostname(Cert, [{dns_id,"very.wrong.domain"}],
[{match_fun,
@@ -1538,7 +1628,7 @@ pkix_verify_hostname_subjAltName_IP(Config) ->
{ip, {10,67,16,75}}
],
[{match_fun,
- fun(Ref,Pres) ->
+ fun(Ref,Pres) ->
ct:log("~p:~p:~nRef : ~p~nPres: ~p",[?MODULE,?LINE,Ref,Pres]),
false
end}]),
@@ -1617,7 +1707,7 @@ pkix_dsa_sha2_oid() ->
pkix_dsa_sha2_oid(Config) when is_list(Config) ->
{sha224, dsa} = public_key:pkix_sign_types(?'id-dsa-with-sha224'),
{sha256, dsa} = public_key:pkix_sign_types(?'id-dsa-with-sha256').
-
+
%%--------------------------------------------------------------------
pkix_crl() ->
@@ -1633,7 +1723,7 @@ pkix_crl(Config) when is_list(Config) ->
{ok, SignPemCert} = file:read_file(filename:join(Datadir, "crl_signer.pem")),
[{_, SignCert, _}] = public_key:pem_decode(SignPemCert),
-
+
OTPIDPCert = public_key:pkix_decode_cert(IDPCert, otp),
OTPSignCert = public_key:pkix_decode_cert(SignCert, otp),
ERLCRL = public_key:der_decode('CertificateList',CRL),
@@ -1659,11 +1749,11 @@ general_name() ->
general_name(Config) when is_list(Config) ->
DummyRfc822Name = "CN=CNDummy, OU=OUDummy, O=ODummy, C=SE",
- {ok, {1, DummyRfc822Name}} =
+ {ok, {1, DummyRfc822Name}} =
pubkey_cert:cert_auth_key_id(
- #'AuthorityKeyIdentifier'{authorityCertIssuer =
+ #'AuthorityKeyIdentifier'{authorityCertIssuer =
[{rfc822Name, DummyRfc822Name}],
- authorityCertSerialNumber =
+ authorityCertSerialNumber =
1}).
%%--------------------------------------------------------------------
@@ -1700,10 +1790,10 @@ pkix_hash_type() ->
[{doc, "Test API function pkix_hash_type/1"}].
pkix_hash_type(Config) when is_list(Config) ->
- sha = public_key:pkix_hash_type(?'id-sha1'),
+ sha = public_key:pkix_hash_type(?'id-sha1'),
sha512 = public_key:pkix_hash_type(?'id-sha512'),
sha384 = public_key:pkix_hash_type(?'id-sha384'),
- sha256 = public_key:pkix_hash_type(?'id-sha256'),
+ sha256 = public_key:pkix_hash_type(?'id-sha256'),
sha224 = public_key:pkix_hash_type('id-sha224'),
md5 = public_key:pkix_hash_type('id-md5').
@@ -1715,33 +1805,33 @@ pkix_test_data_all_default() ->
pkix_test_data_all_default(Config) when is_list(Config) ->
#{server_config := ServerConf0,
- client_config := ClientConf0} = public_key:pkix_test_data(#{server_chain =>
+ client_config := ClientConf0} = public_key:pkix_test_data(#{server_chain =>
#{root => [],
intermediates => [[]],
peer => []},
- client_chain =>
+ client_chain =>
#{root => [],
intermediates => [[]],
peer => []}}),
check_conf_member(ServerConf0, [key, cert, cacerts]),
check_conf_member(ClientConf0, [key, cert, cacerts]),
-
+
3 = length(proplists:get_value(cacerts, ServerConf0)),
3 = length(proplists:get_value(cacerts, ServerConf0)),
#{server_config := ServerConf1,
- client_config := ClientConf1} = public_key:pkix_test_data(#{server_chain =>
+ client_config := ClientConf1} = public_key:pkix_test_data(#{server_chain =>
#{root => [],
peer => []},
- client_chain =>
+ client_chain =>
#{root => [],
peer => []}}),
2 = length(proplists:get_value(cacerts, ServerConf1)),
2 = length(proplists:get_value(cacerts, ServerConf1)),
-
+
check_conf_member(ServerConf1, [key, cert, cacerts]),
check_conf_member(ClientConf1, [key, cert, cacerts]).
-
+
%%--------------------------------------------------------------------
pkix_test_data() ->
@@ -1749,7 +1839,7 @@ pkix_test_data() ->
pkix_test_data(Config) when is_list(Config) ->
{Year, Month, Day} = date(),
- Keygen =
+ Keygen =
case crypto:ec_curves() of
[] ->
{rsa, 2048, 17};
@@ -1758,25 +1848,23 @@ pkix_test_data(Config) when is_list(Config) ->
{namedCurve, Oid}
end,
#{server_config := ServerConf0,
- client_config := ClientConf0} =
- public_key:pkix_test_data(#{server_chain =>
+ client_config := ClientConf0} =
+ public_key:pkix_test_data(#{server_chain =>
#{root => [],
intermediates => [],
peer => [{key, hardcode_rsa_key(1)}]},
- client_chain =>
- #{root => [{validity, {{Year-2, Month, Day},
+ client_chain =>
+ #{root => [{validity, {{Year-2, Month, Day},
{Year-1, Month, Day}}}],
- intermediates =>
+ intermediates =>
[[{extensions, [#'Extension'{extnID = ?'id-ce-basicConstraints',
- extnValue = #'BasicConstraints'{cA=true,
+ extnValue = #'BasicConstraints'{cA=true,
pathLenConstraint = 1},
critical = true}]}]],
peer => [{key, Keygen}, {digest, sha1}]}}),
check_conf_member(ServerConf0, [key, cert, cacerts]),
check_conf_member(ClientConf0, [key, cert, cacerts]).
-
-
check_conf_member(_, []) ->
true;
check_conf_member(Conf, [Member | Rest]) ->
@@ -1786,7 +1874,7 @@ check_conf_member(Conf, [Member | Rest]) ->
false ->
ct:fail({misssing_conf, Member})
end.
-
+
%%--------------------------------------------------------------------
pkix_is_issuer() ->
[{doc, "Test pubkey_cert:pkix_is_issuer with cert that have diffent cases on countryname"}].
@@ -2141,7 +2229,7 @@ asn1_encode_decode({Asn1Type, Der, not_encrypted} = Entry) ->
Decoded = public_key:pem_entry_decode(Entry),
Entry = public_key:pem_entry_encode(Asn1Type, Decoded),
ok.
-
+
check_countryname({rdnSequence,DirName}) ->
do_check_countryname(DirName).
do_check_countryname([]) ->
@@ -2194,12 +2282,16 @@ check_entry_type(#'ML-DSAPublicKey'{algorithm = mldsa65}, ?'id-ml-dsa-65') ->
true;
check_entry_type(#'ML-DSAPublicKey'{algorithm = mldsa87}, ?'id-ml-dsa-87') ->
true;
+check_entry_type(#'SLH-DSAPublicKey'{algorithm = slh_dsa_sha2_128s}, ?'id-slh-dsa-sha2-128s') ->
+ true;
check_entry_type(#'ML-DSAPrivateKey'{algorithm = mldsa44}, ?'id-ml-dsa-44') ->
true;
check_entry_type(#'ML-DSAPrivateKey'{algorithm = mldsa65}, ?'id-ml-dsa-65') ->
true;
check_entry_type(#'ML-DSAPrivateKey'{algorithm = mldsa87}, ?'id-ml-dsa-87') ->
true;
+check_entry_type(#'SLH-DSAPrivateKey'{algorithm = slh_dsa_sha2_128s}, ?'id-slh-dsa-sha2-128s') ->
+ true;
check_entry_type(_,_) ->
false.
@@ -2230,7 +2322,7 @@ strip_superfluous_newlines(Str0) ->
Str = string:strip(Str0, right, 10),
re:replace(Str,"\n\n","\n", [{return,list}, global]).
-do_gen_ec_param(File) ->
+do_gen_ec_param(File) ->
{ok, KeyPem} = file:read_file(File),
Entries = public_key:pem_decode(KeyPem),
[ParamInfo] = [Entry || Entry={'EcpkParameters', _, not_encrypted} <- Entries],
diff --git a/lib/public_key/test/public_key_SUITE_data/slh-dsa-cert.pem b/lib/public_key/test/public_key_SUITE_data/slh-dsa-cert.pem
new file mode 100644
index 0000000000..e43a1378ce
--- /dev/null
+++ b/lib/public_key/test/public_key_SUITE_data/slh-dsa-cert.pem
@@ -0,0 +1,209 @@
+// %CopyrightBegin%
+//
+// SPDX-License-Identifier: BSD-3-Clause
+//
+// Copyright (c) 2024 IETF Trust and the persons identified as the document authors. All rights reserved.
+// Copyright Ericsson AB 2025. All Rights Reserved.
+//
+// Redistribution and use in source and binary forms, with or without
+// modification, are permitted provided that the following conditions are met:
+//
+// 1. Redistributions of source code must retain the above copyright notice,
+// this list of conditions and the following disclaimer.
+//
+// 2. Redistributions in binary form must reproduce the above copyright notice,
+// this list of conditions and the following disclaimer in the documentation
+// and/or other materials provided with the distribution.
+//
+// 3. Neither the name of the copyright holder nor the names of its contributors
+// may be used to endorse or promote products derived from this software
+// without specific prior written permission.
+//
+// THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS “AS IS”
+// AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
+// IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
+// ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE
+// LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
+// CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
+// SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
+// INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
+// CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
+// ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
+// POSSIBILITY OF SUCH DAMAGE.
+//
+// %CopyrightEnd%
+
+-----BEGIN CERTIFICATE-----
+MIIgLTCCAWegAwIBAgIUQ4VjomkBmSw5z7xAVxtfo8zHiEUwCwYJYIZIAWUDBAMU
+MEIxCzAJBgNVBAYTAkZSMQ4wDAYDVQQHDAVQYXJpczEjMCEGA1UECgwaQm9ndXMg
+U0xILURTQS1TSEEyLTEyOHMgQ0EwHhcNMjQxMDE2MTM0MjEyWhcNMzQxMDE0MTM0
+MjEyWjBCMQswCQYDVQQGEwJGUjEOMAwGA1UEBwwFUGFyaXMxIzAhBgNVBAoMGkJv
+Z3VzIFNMSC1EU0EtU0hBMi0xMjhzIENBMDAwCwYJYIZIAWUDBAMUAyEAK4EJ7Hd8
+qk4fAkzPz5SX2ZGAUJKA9CVq8rB6+AKJtJSjYzBhMB0GA1UdDgQWBBTNWTaq/sQR
+x6RyaT8L6LOLIXsZ7TAfBgNVHSMEGDAWgBTNWTaq/sQRx6RyaT8L6LOLIXsZ7TAP
+BgNVHRMBAf8EBTADAQH/MA4GA1UdDwEB/wQEAwIBBjALBglghkgBZQMEAxQDgh6x
+AKqgUd6wwxTQzfsSRqIxIMntqz/cV6X7RfbwO3/jWoy1hx4fCxWfqlZoQ37qIwUh
+0TPLhGFVfjl0GDzqjgGkjZr7NXRpyWI1fw40ARyQQZcT/8WkZa4Pv5sy0iosl4Yt
+Seu6rppw5zVnPwp+Ot0LZk74RbLm2HCr+3Jg64WuYjykvzx65d1KJOJO0LU7w6zp
+JvhsyjvhRhV/GMVBQJBzuRljhiM6sn8SOl+7wxBsTrJi7jtLxeJpJHQ+boHiaEjI
+JyW8sqzaqK51WlwJIhy+lQoLXgwISUI6DS37iTuzFd7u57JeH6bwSvZlwV1eBXpt
+KufCwyA3zqsPbOrJOfMo0XWBMX8B4gnIVoFQz076ghpgPoe/YcqgQCeVv/hPBLH9
+H3/OKfoVXO+UmvbwDH8Jf+y2NiaDaaotaZ4XehWqm1FDwZB8yWk6WrHud8ko5yHY
+kwqAGZxet2FfFGyaACKqTbiGA7WDSunzWnbMozvkE5T3VpZWM90Z2T2NVauZ5QAk
+9//07ghHjUOz9OM61RLvBACZYqFezV+fkPPCjjWbikbsVE4TIFlfY9lhseLENtLl
+J1YfU1mcJOxqeSsdavKTONjres3XisiY1Idhv3k8KmRCD1sVtL3Ax8TeIEy72A9h
+Lqpn4af/DbfdBc9cywxGJuDZSMtFdieIUUnfTBZljBqEggnz1O7EKhepe8B3JP1P
+AJgS7RDnZ8N9VHgPyGd/9PKAKxs0DPpfxBKFHF/mhI3OEueu9e/rll9ib4c6NWfK
+2K21VQsNBpHTnRqWLmfYsQ6PBz971v61dmIZg/bSCDU7nx0K9xTSRVBwXJHMtQ9L
+73nv08e9Anr6i4PNMQew94p5xGgZ3gH4cxptisdUyEuaQFPjS+S9OlJQxt7eGdee
+qIhw8XCmEVWwRl5AN7KQXJF2vSAdJNtxM4G4R+/sfnjSJStL4m4BgdQS/0D/4NeQ
+KYWA5kr1WzJstwUcICfgmFeA56KXy5HO2cGjX9wkf7j1XNqRg+WujGVzhGpbyT+X
+UX3MP9Y54XHxVI0fTzNwzAf4A3C+jIHhXXPBnL58PWnAzHKQz2U4NXEWrh3ipgjI
+e93AMPS0KkX8BeYc76/zUwMvdrV78al9FjOxtcJPm1V7DSL2CEs4smdO2fjxZQPW
+Wh8fi8vaePx7UqXXGzWyzQZ+Hh2LYECRdC+RycbHxAH1LxDC6quE9vYu/HfBhSiQ
+pRHc7Qd4wnScYIZpQDwXmzrl6GUiwn/ZiL5DajGQ1SM365Nw5Lw0lE+vpMFv8zAb
+xuH18dh7pE5uab6C0ICorplE4db6ReUFpVIKXWAXOh4u3S60hpMxkw/KXwVSjjEV
+6IswiDPX2pFSQDzXGLxyjYiyZcX+CnxQRH4PtlJTiyj8W/qTVDbK4cFrf0YT3gV9
+vjONZ1K6ba9L7gELx1YhfRa9GYOQyBRRi/uDwaXKaVqu2fGn3PdTn/ajQ5T7OIYf
+Kg9Qz428NlHOjq+A/rWA+ENz6jrXoqS2czpaa0inMaPTQjr8LrAp0meKmtEmlQgL
+YT9x7rGW9EkM1ztQYWwVyjEx3A382F+hJtPiQ80TOUpQLWRXvwKoXFRK1DdF8gn9
+z1NnGemSpM0bggksTSkwgMEji8ocOMYRj6I8LH+GJcn+oxr8gqtp6bU3sQ6amRDN
+p7ZSn8bkbgjxkM0UuMLgqVguikxS39XuilfOglemiQ90IEwiHQLJBFJoePNZycNg
+hZIBMHWg6ykrZlW3SErfj7rfqLzZRVzrBKjDlLa7HQUZSJuujWMtutbTXuV6QLYF
+dKGwerfXtGfW1qz1BW9TRabt4AyzDDLGiftCexF0lCXcAXy7Tk9Pl1QosPtIZoc6
+0NoYv6oTDGrTxz4RJkPoQLNXKQBwAK9YsHWDnrlLWznxfz+JjR0LGnhN5YzmB4Z1
+IxsUH80ETZjRzfVPHQBV+/jHkvXuXsXzJIQi7hFIkUtR94eonKCaSLyT9Twcftms
+FRwft/m5Zp/05VhK+X5cP6NaIFS+V3R0ZYAN9DCpDVPmcVL5fvQCJOW0IQu8Ey5n
+AL1kVIuCtGT4Ukay8jddMkmKvhlOIafMmhkpyVeq/ttK7+ChBhpfWEyXrv6sFqDj
+p2Dvtr+AZzXIbP4RFhi9BJAytnVkE1WyLsbfL7c11jzxq0we2sJP/CTyks5k3e9w
+eq4mBwFhn+Yu/uQ1jNXu4r79O4/E3FxQTFouqhTEDrWBE1XQhYEWPc4D8CslObb5
+zv/A9U13YIYDJf/dV8v9KP3ijrt8+0lGnCwONHTP0rhFvv3BKmuOMEjDp0FnBHho
+nYEcNfSTWh9Hqzo0Xk4tQyv0UrxYNFIVUzYZybC8V3yVs4bufmifc7IJME/4kK4L
+jfT00Ucb6NEDhZItimCrMPPqJl436ZC2LfYIH7z9E1r9qSl8q1gQ2W07J3Ux9HSo
+6HAAo2PxjLSXIivQ+OCybk9KltXwPf5z4ci6+6iWvwHCY3D63ZflyY8ABF36wDlo
+uuXcqns9vSWqQ+ICoVcreHSA+NbqokR/HjVGy30vg9x6JYfgJ87fEhWDtiYq+U4i
+GMppfeNohghA+kUbpT1joaoZyoM9LksTTVgmYvLvPGsTzJmVIcLH9a8I76AhGkvp
+9BxNRnKIIouqtdz+O+aNuVGNRfRwE2iiKwqcghZk/DpaKhmm/pI0ZeJqnKWTJCG0
+tlC4BDECHN9PuJy2OxlmJqrAM/2b+wIvyAeMH2aK9vPFC3TOdcSUNIBgU8FCCS0h
++yW0/8EAMPHIrc5ixh3XlMwPeyoAvrPzyD/liK9tGZAxcZbWjFs0uIW1QvL7F6CD
+u2phhvDvH9vOAC+Qqu4Hl1lWhZYcl2vK1H2avdwBUt0cvIJegQiRNoV/PhJjWaoD
+ELMDLa0XfWGR1uG5LjlUJ4qkkYe6M1QoUg1G8OdjQG0VdhFRKBtflOowbwA0pthC
+xDKgNhtVBJCHji4ER/ElyPvUWHk2XLmBGMX/Fqv+uAEK+0qTPZvFgtUfv5Xqqjbv
+xfjYq/fKyEncMPs0nYHifGwGeDSpqkR0n0KlxZGfQcTxeX4NzTbVITJdgk2zgA1y
+GasqDt70Is5It7JEAvGZsb953UkLvz74uaXjKI2PibPYvJfLLvjAj/AQzQAv37y7
+q+B33tlEF45w8AfhncWl+5HuPe70mJ1nEAQ6pvID/OgFU+4AKTyE/zX035N0ghbs
+WCVDgQGyaNKnUe2X7cIGHuuNdc8RMLD3D8HSwfFDXUJw+sH5KuuirwAHy5nKy5pQ
+hcNjdtOt9e/U8Ml1pEuISzKBw0OXv6gLwFojtChGTARwNoju6/UmspkFzGsKDvkG
+c/3DvjfHJikRYtQg4AbyaMNX27+F5i/L8YGWiHCeompCAvx5kPbJsPuzbqVoxO67
+jIdsgSAVqH8buvcusvdfo8ADRM7iJ/IE0MCyfb6zEU7pd3y+g5QDE3UvxNSK6byj
++m1ccvpihhfi25eIymxMrWgrV8/1tpIuAi6C0VyfO47p5Y12fGWdV+Ur38nKsYzs
+hucJld5zV07sr2JHRXnG/Qky2Vtz3mdEOSij/x2PImEESIT78EQEDwEbrb+f/zQs
+gz3WhTybgu9Hx6ui4p6scevWXqfY4HlTOSkVDqa5VjmTFn8KSABtNgoqShHvgNdD
+xPAG4qJJmuYtxf1GlqiDRSK1x1Xczz+EjgtpfNzgMBofphTWQtMPkUtsPy/5ZCW7
+5IO5RICzbMfyPlijYXoaBGHYooznQ9fr9JBIkDDcwVWz60toCa9iedf2CWGJt2s3
+PglO1dfjBbFL8OUfaz7wa+sqjR2u9ofGcPJ0+pJGHdZ+1qsa094Rcb7woeMFgk46
+oS7SK8SSDqNwED/fxMxSl/dMplp7zOh0WkcSQnPYWwl+MaloM3f20XJyoyLi2W7F
+/PIw1YXFwlB5EKafFVAxpIfXy9q5Xzer/n8JJeXDHsDWeCCgISAQbzzQvUb+vK3f
+JSeN9A0MTbIwsXCOqiWfgLlgt3myJb6l3+7tjKyHyWk/6uXPTdFEc3+nTptpZN/a
+ildTEQ5U/a/KTG3grVYff8UHAIvkswlTr6Tb4aHE4cDWcNQt6NS9OJTHkzlkcVBt
+pTB9/h5h0KEmu2r4MmMFN2W7I5cGE8bWRrWD/dObo5TsZ46cu56vC9/oKO1F/6SM
+2fnjMN0g8j2tT9C5Kxe/0EqOA42iHxb6/ofrPFd9+Hj5LXTUgthT4JG2g29zecrZ
+yoPthHUQ4F76pw+hm2ch0JqwkINoPJmXaUIRLFG5b1wDHy7ueLc6FNvYnRdpmq2e
+gNXX3v47GO6mfZ87bzBndKH0//toreTsj39bAkZiJhBqiLGnidGHAKSVhJaetB+/
+8W9ntj/VwlwfQRDNBqXo/uIeUuNcRrnE6RiqeOBLeIJ4rD1Z/SRARAHWrWuHvRGh
+wb3yqcy+rgVSe72GY9aevVI8Jdyku3O8DAQEwQzpbtEmw1CsmPtLScVp7dgwu3zS
+btN2WhMMgijPQFwOFiTogl0q8IeJI5ktfmqFod2reBvmz3a8/iayJqWn4dREo/8g
+rYRzWyayOhXJxAKd+7Irz7Xyo36Z3vnZk/eLFuMET8S8TWebP7oteXpH8erYNs9d
+6/ezrgzgYvj2LNApkYr6aL8gV+95DXFi96clx3fyA0gtlXN7usD1Ynu7DQa2iHSk
+tH5IuaZtkng9h05oRNZFI8l7BAJ+x0B/oEH8JI7lQxn0ZbKl53MnA7RSDt4zEmLt
+tsMrGc2gaQvLY+uFg6EWqStywefGY3+kQW4ZYTt4uttqGFz0sV2lXd84/V+Az8/w
+leGxvHouLP8EAF7HeRxH4KdX3hvmaRN6O8+g2GkW8p5F5rF9n/dHJdkfUApu3dpT
+4E1SkTOHij8373rrGpigVeD55fIDH+Lr5TBsDEt1pM9Ah9owSSXhJf04zkQg43V/
+JSt73bIC1+IPlqS7zwzfFudbkUYxvE0YtsozoVvmcJUDQHmpEqkdCeg419R9w6gl
+bMKqC3gZWxbLiiRPsnrKh2iFmyIXUOr9KK5F97a6dt5Jzp+kSLG78br4iI4UHi8t
+U3m/Mg78GSCxuhJoXYzYPDzWY4oui+R8dQUnqOngW76Hd9WziHTbzV9ZEFycROHU
+fb827Ptwlb+nG9mo7v3XkU1ysdFyhwsCWCIjy7FyNgRHM6Y5mTT6c2rhuSEXegRb
+I2Rln78U5o1OcBueGa+bmD5vEy41pZCnxiSKttAKoWDrQM97xQOH4qd2ihBbTnXB
+Pq03Hv9GWaixbsT+ZYFhZ22DUZ8iWB+i4Tnd1DN0IpDLk79lplqNktuemmAell9d
+ZhO484L7E1rqPOkfXde0fxiZONMeSYMmqOzAE5ivos8tKkpKfjL8ILWEwC/WDEBa
+rTTb/NXzjF7OzRX7aNRgxA76nPF+C8KVz+Efa0u0i30bBUWOZWLYJE/JMfWeGzrT
+zUcFk+CRiZ9+h1CpCkso3wBVAX9Y9tSKF8JgGlYqSZyNESV+QudgkCD3PhIle4IF
+SdUviM9z2wl+D/F9xqQP3D1fJaQr4XR9cFqltGdsZnTEhgEwr9Xp+klyODsAld77
+xq7uyNCvshSPndoyX57nhXapGnzTaYsCSzz/UTuggGnwlQEQrrqUqVnOoJCvjfXb
+RWMLT4r7ltsmZtq44s9+FUfIEANGjDu/Rgwp5n2AQjrCjTi0SC0slqE3cROccgAC
+/6R5/3RaMbqmOiQIv45BtEhvvEOFMX25ygZgdvun0aOvrdCnywcCCLq3zqsGVihd
+MXks2xBSVUxlUxDOHl8O5RUlxOB4EjzSDInzYN3x74vsfoqbLFibH3vw091H10lf
+EfrtenIchGwGD3ZEqOYvJBs/ZkY858Z/4wYbXnzm1mcINPNkLP0wndjidRSVkdAP
+TNnwlUNCshXbTz0Vy2BsIvj74MRDHNBxnRCb9nbD1Ojx2GKzs4/04mml/eMKI+ZO
+mw+lLKEJAc4nJpSnkMDoDoKYQ0SHnTRXc7W3Nfqjr0fPCUgnedPGGwR6CN+meA9q
+LlzlxqYWrE9NbQbWRd5oOizyIjJhjObQ5WKpSf66hq3Lxr4pawtLzUxZTr0XbJvJ
+1tnNn6oBjMmj3a9rX+n1GCRtkOEUnlaGBC47okIh+AruBXExVfdWmV9yGIci/21P
+fMLCMoRdTB3aWRJxSJg3aMhsFIy2jNRJ5fYrDwSsZhv3xNAYbeNdEk2dNMZMNs+W
+K12u17F0yfBEtvDGRTJOt0JC0/m1w1FUPrhKcA6CLjkHvGapkZND8n/tpGHyNfrg
+n4YAyYdbaX47+NH653jm0EYn1YDUNA+PvxwnR2A/p7XE7bPCFTc3s4vRwacbRyRz
+ziJ02vvIP6FlTXln0YrbcXnUXX2hrgWTeDGY0/bMo0KT4REGUSw8TLdrXQf6qAhy
+TJomC68oHHBVsR3Igpg9pbRi/3cHE4SwEH7zMzchQS7NO9pO5vqtP+7zBTmNZSDc
+lEmY5OmhJrM6PclpH+ScKX0bkQJwJ4t33xh+UFBYBhv8N2tMAHHq7oJM4oukp4H4
+h1cHUNnQv/SFx0+bz+RR7tFrCqOneal/5Grrg1mC+OUyxmuTVxhh54mx/6f3MYtU
+Md8wyAsvflxNHZnizWGXtSgUNj82DrQnOMhhaOCVjSY81INdlp+mN5ZZ2xCkX5C2
+RPF+bIZEJUAK/O/XXJe6G0yVnuOekLkCWDAdYLeUMPV4taTqN4J69XNsDdOBynLM
+jM2/b/p/yzknGlmacVHY87NA09pmg/TylKWPtaB/csLI5xtBNv77bYHYq4ozQRi/
+QskaiiL6JZ7gt0VG7qs7VzqPZJZReh9mlflSlUB3UWn1br08l5VTkAmw/F+MytUt
+QKspwiExgHW5DMlXRvl+4fyVY8GRrRCQry2ihQJV0aEQdtskrDcdNb+KCSkht9rV
+Jm0Abnc/ZOCIawk36YL4x628BeoddaS6w9T7Q66ZKDoZ/YRTS4SKs3aupt2pu/5W
+wn0UBWI6pK99O82AxN2HWFQhniHyYKNCpt5VMY7JfAGu/YdnUkO6eqTuI59vClLb
+OBJBGMQtSoWENlmmI544jlHCiCOFOtxgUlZ5mYSwpamzG6wnyF1Ngo087ueExw1y
+rIDIglW7BXseM/SjDDlbK+2k9s+lFY9YvqC7mzUnzHt4qu6rD/reqruVlDe2RP8h
+4WRBc0Yi2bCJYSS0UwGZF0t56d3gPQrJPdUCHElOvSbZm7AyLmoiuHD1xu1RT+6g
+Nyl18xddNdKmO3FDi28imxp9oMX3f34kepNnuQtMhGHy3W1vYHtjVkfGzRyuJRip
+zyGqvNVwSHU4pxBevLyh4CdPbBi0QPiAAXQf/NKCWLPE8xzx5WZhwGxjTDu2YXoV
+nb51S8MENaOnA/nMUGLQOHTB4sjORht2QqA7/1w8BMdzPas2tBzvR36ZeQyHnVTJ
+RUphKUM0ck6m2SQsMHR1PRaHkQNYPnk789GLahCHGJLJDeWqY0UKYIPCgRE4tsPN
++LBx2OBbBMVXKlU82z+CJuvbCbcL8miQNL55QSWXndGXDq9MrkAhYV7zvpnao4Ix
+mJZbHIYgSGuvkt/nLfUNl1UESz1vEEeYafMGi6CaiHwKooSNcUpfI3Qu7bsoMtIz
+NKt3QOf41Bb+sHPkFKX1PD6g8OBCHc/Dw/i7B1pWIG1Pjqxj9jz99hErlyyGZmYR
+FutRwikGMIS65IGYVmhwQzFdwu/r5uWGy5vjN46j+q1GzWOd0qFtXd9lz3w5zSSu
+hkCwP9N3HVhUShG5fSXAiHnXNseqLNg/24aC//kPItBacYxbsiPqysvutlEtXkPa
+/RiERyKVMeDlaC1law/5lEDoRU0W0GusVyTe4sHrmWWRnnpsbG7HN6suToCACWDV
+EAtRmyR/ILJ9d7XhM6IuwHpi+6q8qLoH7yfEacBL2v+JgBOCHyVZO0DcEfRd3sWk
+oNVHwBntHtNnSrB224Ut30/rbhesnsxnDXQDEFuI097H4AVVSAG8vnqCLPtePffK
+LEIg7VD/PCsHxI3RE1eqJmeDAht5iATF7wpuyPikzZNXu0o5S57BF2dUn4Vei6QV
+84G6LYVkqJnqEQybg1KAAxjAHXKe0gvUjOVZCCilz4tG7+mCm1Tw4glwtC30MdHx
+6tpXHBu73rOFR/QZ5MQGhYdUI3Zs4T0owcAlALM001Gv2d8Pi7i1bchT/o1ZuvEO
+AAVOv1GbWRBZBw9fJ5mffGujFEAy2uSJjbXG0z/t4/ktFazRqBFBLSxyq6TV9Jyu
+1699OeIcj6j/PpJ95HY41P6imW4daxFw497yTR9N5cxEQ/hCyJkRxiki7vkT1QgV
+cfwOyoKXsRH7uYwnPL6k19hPPA08gl3PGAEJKMod8Pe6cYDrdnpY6ZG4hnHQcdIT
+PLdl58T/J/cv8j8k1cbfbNDdCu7eSxZmb2jOlLH5aWcMxBkgLCl0+KfiAAYTyS0d
+T3Z0AyhGebeAstrSOQpWR1/DgZruF5ENSfQjPzbbVUjYFkP/bG/6yqwXyqNiTd5g
+XO31o5YzNVMkBpmPMNakuAc94dnKB5tUcFDGDtJLk5wHFreeHtdCjMb9Qc2qTvws
+ERpuANtbJW6WyClDrGi+wNMsPBvUtpwqoJ+bFqMq3e0ALLmdk1llgd6pqbiWrMRD
+MJMhTDxCBo6r+jeWcsjsIhkbi8oic74I32od1+8TC0Ou/aDWoRCK914T5V2hgcCB
+Bj9f6rPheJn1LRxWC9/DHU4f9uointgzEyu76T+xF88zDoCFcnJywK1wtIGb2FfW
+pJ/3khXjctDuIqFHsJDj8RS2mf/8w8s0A/gAdt19xE0dwutIc01BQJ3hgFw3zGWn
+aoqwmjXVLMzzo81D9+dcRnrhX7Kgk9cAyp46FUxhq/xi5Dl51iIq2X6PpGUa6R2J
+K5zv1z82/JOc7OWmk87sMpFIRrAKsuMzGd+h+3gg4xNUE/P7ilrynro04f7rWOLE
+r7ZjVjJCz+N9xfDVb/ZkU0AXwIjwVI2cBY1SOWNoI4aGkTTynKTdF7omWn9zdxlb
+k1osiQdfJ0UrqoYamJhZKkbIjk91MNw66fYfwDPvChMwXDJFiBlnTk2o8fqJsO/k
+Qj4mYICTIXtGufRsvp/Gf8ZJyeFJyC0HNpNpFBjj+ztreTcAvfLh9gZ7LAfqhuIe
+YmRIQ1l9L/0kyKFPlKyNHn0VoTIBJbo/NdYWVyQo9mg104AhzJF2vRV/oUJrjqWQ
+e/pdAXouAiG0MfksQIg0dQHLgzkbPDiiwl0z44NVf/rw18/JZJ8GObIY80GBYP9Q
+XVASNw6CwNovavj8Fl+7IimDFEakAcr42Cx57c9AN0aoSH9mfQ6g/y8HwKNY7Cw6
+JzPjP1KslJkQKxWEEelxwDXDefclv/NbQkYXRF3BxKz8AWBqaV3MZQjgMcDbAe14
+cBgbk6/3sSwLH7Volrj5aZ/l5jXLvAZlZBHVq9Tm03kxobDi04B4wvaHdOM0SKuL
+XjBS1jsCcs0+pPnaym3abFkHOXPaCPDQPJ35UoN3YGdYn2cRJBP0hoaNKYnFToYi
+EoYRlA70xiY+D44GjVpgMNCpqL92P4g0eajaeBtxn4wzWY37a8+WRU++VOUVxtOb
+ferZYVN1kT3FEH2iXQDNSne6lmxRV6RodUMn7AtJSk0lyTj9zDMb2nC/G8PUWd2K
+Bf6HxY5ZFu8zS4gU9I4/ZUPr6qOcXOvcgdffe6UeTYRczTHiAqY3z4FPtZFBhwSS
+88FdYi5S8YaujRO/tsdWNu/ml7YFzDnbSa+1PuzKNy6kUcbXAy3IaTtY95Ht1IgO
+nAV//oxfDBgxOUutPCVNJiRCRZkY3w6sk0cLR2BYU2MPC7BnpQcSyqFk6aO+Ft72
+cI4jjWHXjUsxb3lIjLC+AUjyTj0qT+BVkHI+0wxc9/gVReQQ362c0CPDu6NScAji
++q66sHQ13aZL+5q3PCgXhwhwR0JeWDqmhKyUNEFcPNGsCrS/ocbawlmjIsym4+nV
+khWAuy4kkdOKAhPlUQX1VUp4QdXnYh231R/lNPexrsYP7DjCqCOO/122h4pPv3fW
+wa6hyIjVZuF3BsqRENsUIEygj9iLG3FmuJYJCGrs38FL1pEDjGbiyB3JDvOZPgq0
+YIOKvD3KGQCz/bBehGG3IwTbZDUGmqtKA0eieWzYC57Jd7tHXttm5PMz64ziSaTW
+oclhl0rmOqsWZLPfFlre5fm6XX3rBPX08PB95Bp0/H0DFqTK9uAFleD6nYAHWLQS
+XjRDBK2Qnz++Mco908nQt5HHXNArgXM0v8qlbiNPs/O0vwP0va/91wmLZaMMdtwe
+fJfSvoXUZW35PW6ubFf0EEAh1gQtm5vllZCcUqitYYvNsBLBEybDTY4igoKb/m0B
+5zxlebR5n56wEN1ealdDjGtB1earlLrHZ6W0QdgQDP0pd+ILzSmALq5epYWjogkx
+UYKYCyx6a5bvjcD1H5i09iK2IW4247sY2h0kRg1lKLZq
+-----END CERTIFICATE-----
\ No newline at end of file
diff --git a/lib/public_key/test/public_key_SUITE_data/slh-dsa-sha2-128s-pub.pem b/lib/public_key/test/public_key_SUITE_data/slh-dsa-sha2-128s-pub.pem
new file mode 100644
index 0000000000..af906eebfc
--- /dev/null
+++ b/lib/public_key/test/public_key_SUITE_data/slh-dsa-sha2-128s-pub.pem
@@ -0,0 +1,38 @@
+// %CopyrightBegin%
+//
+// SPDX-License-Identifier: BSD-3-Clause
+//
+// Copyright (c) 2024 IETF Trust and the persons identified as the document authors. All rights reserved.
+// Copyright Ericsson AB 2025. All Rights Reserved.
+//
+// Redistribution and use in source and binary forms, with or without
+// modification, are permitted provided that the following conditions are met:
+//
+// 1. Redistributions of source code must retain the above copyright notice,
+// this list of conditions and the following disclaimer.
+//
+// 2. Redistributions in binary form must reproduce the above copyright notice,
+// this list of conditions and the following disclaimer in the documentation
+// and/or other materials provided with the distribution.
+//
+// 3. Neither the name of the copyright holder nor the names of its contributors
+// may be used to endorse or promote products derived from this software
+// without specific prior written permission.
+//
+// THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS “AS IS”
+// AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
+// IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
+// ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE
+// LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
+// CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
+// SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
+// INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
+// CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
+// ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
+// POSSIBILITY OF SUCH DAMAGE.
+//
+// %CopyrightEnd%
+-----BEGIN PUBLIC KEY-----
+MDAwCwYJYIZIAWUDBAMUAyEAK4EJ7Hd8qk4fAkzPz5SX2ZGAUJKA9CVq8rB6+AKJ
+tJQ=
+-----END PUBLIC KEY-----
\ No newline at end of file
diff --git a/lib/public_key/test/public_key_SUITE_data/slh-dsa-sha2-128s.pem b/lib/public_key/test/public_key_SUITE_data/slh-dsa-sha2-128s.pem
new file mode 100644
index 0000000000..19177bcf85
--- /dev/null
+++ b/lib/public_key/test/public_key_SUITE_data/slh-dsa-sha2-128s.pem
@@ -0,0 +1,38 @@
+// %CopyrightBegin%
+//
+// SPDX-License-Identifier: BSD-3-Clause
+//
+// Copyright (c) 2024 IETF Trust and the persons identified as the document authors. All rights reserved.
+// Copyright Ericsson AB 2025. All Rights Reserved.
+//
+// Redistribution and use in source and binary forms, with or without
+// modification, are permitted provided that the following conditions are met:
+//
+// 1. Redistributions of source code must retain the above copyright notice,
+// this list of conditions and the following disclaimer.
+//
+// 2. Redistributions in binary form must reproduce the above copyright notice,
+// this list of conditions and the following disclaimer in the documentation
+// and/or other materials provided with the distribution.
+//
+// 3. Neither the name of the copyright holder nor the names of its contributors
+// may be used to endorse or promote products derived from this software
+// without specific prior written permission.
+//
+// THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS “AS IS”
+// AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
+// IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
+// ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE
+// LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
+// CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
+// SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
+// INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
+// CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
+// ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
+// POSSIBILITY OF SUCH DAMAGE.
+//
+// %CopyrightEnd%
+-----BEGIN PRIVATE KEY-----
+MFICAQAwCwYJYIZIAWUDBAMUBECiJjvKRYYINlIxYASVI9YhZ3+tkNUetgZ6Mn4N
+HmSlASuBCex3fKpOHwJMz8+Ul9mRgFCSgPQlavKwevgCibSU
+-----END PRIVATE KEY-----
\ No newline at end of file
--
2.51.0