File 0572-Added-tests-and-additional-fix-for-public_key-pkix_v.patch of Package erlang
From a834684bc882a18bc513944aceb61066fce3eab9 Mon Sep 17 00:00:00 2001
From: Sergey Stolyarov <sergei@regolit.com>
Date: Thu, 22 Jul 2021 11:43:22 +0700
Subject: [PATCH 2/3] Added tests and additional fix for public_key:pkix_verify
---
lib/public_key/src/public_key.erl | 5 +++--
lib/public_key/test/erl_make_certs.erl | 19 ++++++++++++++++++-
lib/public_key/test/public_key_SUITE.erl | 22 ++++++++++++++++++++--
3 files changed, 41 insertions(+), 5 deletions(-)
diff --git a/lib/public_key/src/public_key.erl b/lib/public_key/src/public_key.erl
index 23883b6a39..e88c33c0db 100644
--- a/lib/public_key/src/public_key.erl
+++ b/lib/public_key/src/public_key.erl
@@ -1521,13 +1521,14 @@ format_verify_key(#'DSAPrivateKey'{y=Y, p=P, q=Q, g=G}) ->
format_verify_key(_) ->
badarg.
-rsa_opts(#'RSASSA-PSS-params'{maskGenAlgorithm =
+rsa_opts(#'RSASSA-PSS-params'{saltLength = SaltLen,
+ maskGenAlgorithm =
#'MaskGenAlgorithm'{algorithm = ?'id-mgf1',
parameters = #'HashAlgorithm'{algorithm = HashAlgoOid}
}}) ->
HashAlgo = pkix_hash_type(HashAlgoOid),
[{rsa_padding, rsa_pkcs1_pss_padding},
- {rsa_pss_saltlen, -1},
+ {rsa_pss_saltlen, SaltLen},
{rsa_mgf1_md, HashAlgo}].
do_pem_entry_encode(Asn1Type, Entity, CipherInfo, Password) ->
diff --git a/lib/public_key/test/erl_make_certs.erl b/lib/public_key/test/erl_make_certs.erl
index 4c0b60d543..040893cf95 100644
--- a/lib/public_key/test/erl_make_certs.erl
+++ b/lib/public_key/test/erl_make_certs.erl
@@ -111,6 +111,9 @@ gen_ec(Curve) when is_atom(Curve) ->
verify_signature(DerEncodedCert, DerKey, _KeyParams) ->
Key = decode_key(DerKey),
case Key of
+ {#'RSAPrivateKey'{modulus=Mod, publicExponent=Exp}, #'RSASSA-PSS-params'{}=P} ->
+ public_key:pkix_verify(DerEncodedCert,
+ {#'RSAPublicKey'{modulus=Mod, publicExponent=Exp}, P});
#'RSAPrivateKey'{modulus=Mod, publicExponent=Exp} ->
public_key:pkix_verify(DerEncodedCert,
#'RSAPublicKey'{modulus=Mod, publicExponent=Exp});
@@ -134,6 +137,8 @@ get_key(Opts) ->
decode_key(Key, Password)
end.
+decode_key({#'RSAPrivateKey'{},#'RSASSA-PSS-params'{}}=Key) ->
+ Key;
decode_key({Key, Pw}) ->
decode_key(Key, Pw);
decode_key(Key) ->
@@ -144,6 +149,8 @@ decode_key(#'RSAPublicKey'{} = Key,_) ->
Key;
decode_key(#'RSAPrivateKey'{} = Key,_) ->
Key;
+decode_key({#'RSAPrivateKey'{},#'RSASSA-PSS-params'{}} = Key,_) ->
+ Key;
decode_key(#'DSAPrivateKey'{} = Key,_) ->
Key;
decode_key(#'ECPrivateKey'{} = Key,_) ->
@@ -157,6 +164,9 @@ decode_key(PemBin, Pw) ->
encode_key(Key = #'RSAPrivateKey'{}) ->
{ok, Der} = 'OTP-PUB-KEY':encode('RSAPrivateKey', Key),
{'RSAPrivateKey', Der, not_encrypted};
+encode_key(Key = {#'RSAPrivateKey'{},#'RSASSA-PSS-params'{}}) ->
+ Der = public_key:der_encode('PrivateKeyInfo', Key),
+ {'PrivateKeyInfo', Der, not_encrypted};
encode_key(Key = #'DSAPrivateKey'{}) ->
{ok, Der} = 'OTP-PUB-KEY':encode('DSAPrivateKey', Key),
{'DSAPrivateKey', Der, not_encrypted};
@@ -171,7 +181,7 @@ make_tbs(SubjectKey, Opts) ->
{Issuer, IssuerKey} = issuer(IssuerProp, Opts, SubjectKey),
{Algo, Parameters} = sign_algorithm(IssuerKey, Opts),
-
+
SignAlgo = #'SignatureAlgorithm'{algorithm = Algo,
parameters = Parameters},
Subject = case IssuerProp of
@@ -295,6 +305,11 @@ publickey(#'RSAPrivateKey'{modulus=N, publicExponent=E}) ->
Algo = #'PublicKeyAlgorithm'{algorithm= ?rsaEncryption, parameters='NULL'},
#'OTPSubjectPublicKeyInfo'{algorithm = Algo,
subjectPublicKey = Public};
+publickey({#'RSAPrivateKey'{modulus=N, publicExponent=E},#'RSASSA-PSS-params'{}=P}) ->
+ Public = #'RSAPublicKey'{modulus=N, publicExponent=E},
+ Algo = #'PublicKeyAlgorithm'{algorithm= ?'id-RSASSA-PSS', parameters=P},
+ #'OTPSubjectPublicKeyInfo'{algorithm = Algo,
+ subjectPublicKey = Public};
publickey(#'DSAPrivateKey'{p=P, q=Q, g=G, y=Y}) ->
Algo = #'PublicKeyAlgorithm'{algorithm= ?'id-dsa',
parameters={params, #'Dss-Parms'{p=P, q=Q, g=G}}},
@@ -325,6 +340,8 @@ sign_algorithm(#'RSAPrivateKey'{}, Opts) ->
md2 -> ?'md2WithRSAEncryption'
end,
{Type, 'NULL'};
+sign_algorithm({#'RSAPrivateKey'{},#'RSASSA-PSS-params'{}=P}, Opts) ->
+ {?'id-RSASSA-PSS', P};
sign_algorithm(#'DSAPrivateKey'{p=P, q=Q, g=G}, _Opts) ->
{?'id-dsa-with-sha1', {params,#'Dss-Parms'{p=P, q=Q, g=G}}};
sign_algorithm(#'ECPrivateKey'{parameters = Parms}, Opts) ->
diff --git a/lib/public_key/test/public_key_SUITE.erl b/lib/public_key/test/public_key_SUITE.erl
index fda2c1e48c..3ec87b2ef6 100644
--- a/lib/public_key/test/public_key_SUITE.erl
+++ b/lib/public_key/test/public_key_SUITE.erl
@@ -776,7 +776,25 @@ pkix_path_validation(Config) when is_list(Config) ->
{error, custom_reason} =
public_key:pkix_path_validation(selfsigned_peer, [Trusted], [{verify_fun,
- VerifyFunAndState2}]).
+ VerifyFunAndState2}]),
+ % check RSASSA-PSS key
+ % RsaPssKey = {public_key:generate_key({rsa, 1024, 65537}), pss_params(sha256)},
+ RsaPssKey = {hardcode_rsa_key(1), pss_params(sha256)},
+
+ CaKPSS = {TrustedPSSCert,_} = erl_make_certs:make_cert([{key, RsaPssKey},
+ {subject, [
+ {name, "RSASSA-PSS Public Key"},
+ {?'id-at-name', {printableString, "public_key"}},
+ {?'id-at-pseudonym', {printableString, "pubkey"}},
+ {city, "Stockholm"},
+ {country, "SE"},
+ {org, "erlang"},
+ {org_unit, "testing dep"}
+ ]}
+ ]),
+ ChainPSSCert = {CertPSS, _} = erl_make_certs:make_cert([{issuer, {TrustedPSSCert,RsaPssKey}}]),
+ {ok, _} = public_key:pkix_path_validation(TrustedPSSCert, [CertPSS], []).
+
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) ->
@@ -1355,6 +1373,6 @@ pss_params(sha256) ->
maskGenAlgorithm = #'MaskGenAlgorithm'{algorithm = ?'id-mgf1',
parameters = #'HashAlgorithm'{algorithm = ?'id-sha256'}
},
- saltLength = 32,
+ saltLength = 20,
trailerField = 1}.
--
2.26.2