File 0200-public_key-Correct-mapping-of-encoding-module.patch of Package erlang
From b8929d1df60b71f3c2b77352d63ba45130b36d64 Mon Sep 17 00:00:00 2001
From: Ingela Anderton Andin <ingela@erlang.org>
Date: Fri, 9 Jan 2026 16:51:43 +0100
Subject: [PATCH 2/2] public_key: Correct mapping of encoding module
Add some basic property test to start improving code coverage.
---
lib/public_key/src/public_key.erl | 2 +-
lib/public_key/test/Makefile | 5 +-
lib/public_key/test/property_test/pkix.erl | 296 +++++++++++++++++++++
lib/public_key/test/pubkey_eqc_SUITE.erl | 90 +++++++
4 files changed, 390 insertions(+), 3 deletions(-)
create mode 100644 lib/public_key/test/property_test/pkix.erl
create mode 100644 lib/public_key/test/pubkey_eqc_SUITE.erl
diff --git a/lib/public_key/src/public_key.erl b/lib/public_key/src/public_key.erl
index 913b201541..fc91fa3e4f 100644
--- a/lib/public_key/src/public_key.erl
+++ b/lib/public_key/src/public_key.erl
@@ -659,6 +659,7 @@ get_asn1_module('AuthorityKeyIdentifier') -> 'PKIX1Implicit-2009';
get_asn1_module('BasicConstraints') -> 'PKIX1Implicit-2009';
get_asn1_module('ExtKeyUsageSyntax') -> 'PKIX1Implicit-2009';
get_asn1_module('KeyUsage') -> 'PKIX1Implicit-2009';
+get_asn1_module('KeyIdentifier') -> 'PKIX1Implicit-2009';
get_asn1_module('Certificate') -> 'PKIX1Explicit-2009';
get_asn1_module('TBSCertificate') -> 'PKIX1Explicit-2009';
get_asn1_module('CRLDistributionPoints') -> 'PKIX1Implicit-2009';
@@ -708,7 +709,6 @@ get_asn1_module('OriginatorPublicKey') -> 'CryptographicMessageSyntax-2009';
get_asn1_module('EncryptedContentInfo') -> 'CryptographicMessageSyntax-2009';
get_asn1_module('RecipientInfo') -> 'CryptographicMessageSyntax-2009';
get_asn1_module('KeyTransRecipientInfo') -> 'CryptographicMessageSyntax-2009';
-get_asn1_module('KeyIdentifier') -> 'CryptographicMessageSyntax-2009';
get_asn1_module('RecipientKeyIdentifier') -> 'CryptographicMessageSyntax-2009';
get_asn1_module('SubjectKeyIdentifier') -> 'CryptographicMessageSyntax-2009';
get_asn1_module('KeyAgreeRecipientInfo') -> 'CryptographicMessageSyntax-2009';
diff --git a/lib/public_key/test/Makefile b/lib/public_key/test/Makefile
index 5bc023f02f..05702af99c 100644
--- a/lib/public_key/test/Makefile
+++ b/lib/public_key/test/Makefile
@@ -37,7 +37,8 @@ MODULES= \
pkits_SUITE \
pubkey_cert_SUITE \
pubkey_policy_tree_SUITE \
- pubkey_ocsp_SUITE
+ pubkey_ocsp_SUITE \
+ pubkey_eqc_SUITE
ERL_FILES= $(MODULES:%=%.erl)
@@ -89,7 +90,7 @@ release_tests_spec: opt
$(INSTALL_DATA) $(SPEC_FILES) $(ERL_FILES) $(COVER_FILE) $(HRL_FILES) "$(RELSYSDIR)"
$(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)"
chmod -R u+w "$(RELSYSDIR)"
- @tar cf - *_SUITE_data | (cd "$(RELSYSDIR)"; tar xf -)
+ @tar cf - *_SUITE_data property_test | (cd "$(RELSYSDIR)"; tar xf -)
release_docs_spec:
diff --git a/lib/public_key/test/property_test/pkix.erl b/lib/public_key/test/property_test/pkix.erl
new file mode 100644
index 0000000000..45c6d1348e
--- /dev/null
+++ b/lib/public_key/test/property_test/pkix.erl
@@ -0,0 +1,296 @@
+%%
+%% %CopyrightBegin%
+%%
+%% SPDX-License-Identifier: Apache-2.0
+%%
+%% Copyright Ericsson AB 2026. All Rights Reserved.
+%%
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%%
+%% http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%%
+%% %CopyrightEnd%
+%%
+%%
+
+-module(pkix).
+
+-compile(export_all).
+
+-include_lib("common_test/include/ct_property_test.hrl").
+-include_lib("public_key/include/public_key.hrl").
+
+-define(EMPTY_PARAM, {asn1_OPENTYPE, <<5,0>>}).
+
+%%--------------------------------------------------------------------
+%% Properties --------------------------------------------------------
+%%--------------------------------------------------------------------
+
+implicit_encode_decode() ->
+ ?FORALL({PkixType, Decoded}, ?LET(Type, implicit_type(), {Type, implicit_value(Type)}),
+ encode_decode_check(PkixType, Decoded)).
+explicit_encode_decode() ->
+ ?FORALL({PkixType, Decoded}, ?LET(Type, explicit_type(), {Type, explicit_value(Type)}),
+ encode_decode_check(PkixType, Decoded)).
+ocsp_encode_decode() ->
+ ?FORALL({PkixType, Decoded}, ?LET(Type, ocsp_type(), {Type, ocsp_value(Type)}),
+ encode_decode_check(PkixType, Decoded)).
+
+encode_decode_check(PkixType, Decoded) ->
+ try
+ Encoded = public_key:der_encode(PkixType, Decoded),
+ NewDecoded = public_key:der_decode(PkixType, Encoded),
+ Decoded == NewDecoded
+ catch
+ _:_ ->
+ false
+ end.
+
+%%--------------------------------------------------------------------
+%% Generators --------------------------------------------------------
+%%--------------------------------------------------------------------
+implicit_type() ->
+ elements(['BasicConstraints',
+ 'ExtKeyUsageSyntax',
+ 'KeyUsage',
+ 'KeyIdentifier']).
+
+implicit_value('BasicConstraints') ->
+ #'BasicConstraints'{cA = ?LET(CA, bool(), CA),
+ pathLenConstraint = ?LET(Len, choose(1, 10), Len)
+ };
+implicit_value('ExtKeyUsageSyntax') ->
+ ?LET(Usages, list(ext_key_usages()), lists:usort(Usages));
+implicit_value('KeyUsage') ->
+ ?LET(Usages, list(choose(0,8)),
+ [key_usages_enum(Usage) || Usage <- lists:usort(Usages)]);
+implicit_value('KeyIdentifier') ->
+ ?LET(Bin, binary(), Bin).
+
+ext_key_usages() ->
+ elements([?'id-kp-serverAuth',
+ ?'id-kp-clientAuth',
+ ?'id-kp-codeSigning',
+ ?'id-kp-emailProtection',
+ ?'id-kp-timeStamping',
+ ?'id-kp-OCSPSigning'
+ ]).
+
+key_usages_enum(0) ->
+ digitalSignature;
+key_usages_enum(1) ->
+ nonRepudiation;
+key_usages_enum(2) ->
+ keyEncipherment;
+key_usages_enum(3) ->
+ dataEncipherment;
+key_usages_enum(4) ->
+ keyAgreement;
+key_usages_enum(5) ->
+ keyCertSign;
+key_usages_enum(6) ->
+ cRLSign;
+key_usages_enum(7) ->
+ encipherOnly;
+key_usages_enum(8) ->
+ decipherOnly.
+
+
+explicit_type() ->
+ elements(['Validity'
+ ]).
+
+explicit_value('Validity') ->
+ #'Validity'{
+ notBefore =
+ {utcTime,"080109082930Z"},
+ notAfter =
+ {utcTime,"171117082930Z"}
+ }.
+
+ocsp_type() ->
+ elements(['OCSPRequest'
+ ]).
+
+ocsp_value('OCSPRequest') ->
+ TBSRequest = #'TBSRequest'{
+ version = 0,
+ requestorName = directoryName(),
+ requestList = requestor_list(),
+ requestExtensions = extensions()
+ },
+ #'OCSPRequest'{
+ tbsRequest = TBSRequest,
+ optionalSignature = asn1_NOVALUE
+ }.
+
+directoryName() ->
+ ?LET(Ids, ?SUCHTHAT(X, list(id_attrs()), X =/= []),
+ {directoryName,
+ {rdnSequence, [[atter_value(Id)] || Id <- Ids]}}).
+
+requestor_list() ->
+ ?LET(HashAlgo, hash_algorithm(), requestor_list(HashAlgo)).
+
+requestor_list({HashAlgo, Params}) ->
+ [#'Request'{
+ reqCert =
+ #'CertID'{hashAlgorithm =
+ #'CertID_hashAlgorithm'{algorithm = HashAlgo,
+ parameters = Params},
+ issuerNameHash = hash(HashAlgo),
+ issuerKeyHash = hash(HashAlgo),
+ serialNumber = choose(1, 6553)},
+ singleRequestExtensions = asn1_NOVALUE}].
+
+hash_algorithm() ->
+ ?LET(HashAlgo, hash_algo(), HashAlgo).
+
+hash_algo() ->
+ %% Extend to support more hashes
+ elements([{?'id-sha1', ?EMPTY_PARAM}]).
+
+hash(?'id-sha1') ->
+ %% Dummy hash could be extended later to have another argument and
+ %% generate real hash values for more advanced tests.
+ ?LET(Value, binary(20), Value).
+
+extensions() ->
+ [#'Extension'{
+ extnID = ?'id-pkix-ocsp-nonce',
+ critical = false,
+ extnValue = ocsp_nonce()}].
+
+ocsp_nonce() ->
+ ?LET(Len, choose(1, 128), binary(Len)).
+
+id_attrs()->
+ elements([?'id-at-surname',
+ ?'id-at-givenName',
+ ?'id-at-initials',
+ ?'id-at-generationQualifier',
+ ?'id-at-commonName',
+ ?'id-at-localityName',
+ ?'id-at-stateOrProvinceName',
+ ?'id-at-organizationName',
+ ?'id-at-title',
+ ?'id-at-dnQualifier',
+ ?'id-at-countryName',
+ ?'id-at-serialNumber',
+ ?'id-at-pseudonym',
+ ?'id-domainComponent',
+ ?'id-emailAddress',
+ ?'id-at-organizationalUnitName'
+ ]).
+
+atter_value(?'id-at-countryName' = Name) ->
+ ?LET({Capital1, Capital2}, {upper_case(), upper_case()},
+ #'AttributeTypeAndValue'{
+
+ type = Name,
+ value = [Capital1, Capital2]
+ });
+atter_value(?'id-emailAddress' = Email) ->
+ End = "@example.com",
+ GenLen = ?'ub-emailaddress-length' - length(End),
+ ?LET(Len, choose(1, GenLen),
+ #'AttributeTypeAndValue'{
+ type = Email,
+ value = printable_string(Len, End)
+ });
+atter_value(Name) when Name == ?'id-at-surname';
+ Name == ?'id-at-givenName';
+ Name == ?'id-at-initials';
+ Name == ?'id-at-organizationName';
+ Name == ?'id-at-organizationalUnitName';
+ Name == ?'id-at-title' ->
+ ?LET(Size, choose(1, upper_bound(Name)),
+ #'AttributeTypeAndValue'{
+ type = Name,
+ value = {utf8String, utf8(Size)}
+ });
+atter_value(Name) when Name == ?'id-at-localityName';
+ Name == ?'id-at-stateOrProvinceName';
+ Name == ?'id-at-pseudonym';
+ Name == ?'id-at-generationQualifier';
+ Name == ?'id-at-commonName' ->
+ ?LET(Len, choose(1, upper_bound(Name)),
+ #'AttributeTypeAndValue'{
+ type = Name,
+ value = {printableString, printable_string(Len)}
+ });
+
+atter_value(Name) when Name == ?'id-domainComponent' ->
+ ?LET(Len, choose(1, upper_bound(Name)),
+ #'AttributeTypeAndValue'{
+ type = Name,
+ value = ia5_string(Len)
+ });
+atter_value(Name) when Name == ?'id-at-serialNumber';
+ Name == ?'id-at-dnQualifier'->
+ ?LET(Num, choose(1, upper_bound(Name)),
+ #'AttributeTypeAndValue'{
+ type = Name,
+ value = integer_to_list(Num)
+ }).
+
+upper_bound(?'id-at-surname') ->
+ ?'ub-surname-length';
+upper_bound(?'id-at-givenName') ->
+ ?'ub-given-name-length';
+upper_bound(?'id-at-initials') ->
+ ?'ub-initials-length';
+upper_bound(?'id-at-organizationalUnitName') ->
+ ?'ub-organizational-unit-name';
+upper_bound(?'id-at-organizationName') ->
+ ?'ub-organization-name-length';
+upper_bound(?'id-at-title') ->
+ ?'ub-title';
+upper_bound(?'id-at-localityName') ->
+ ?'ub-locality-name';
+upper_bound(?'id-at-stateOrProvinceName') ->
+ ?'ub-state-name';
+upper_bound(?'id-at-pseudonym') ->
+ ?'ub-pseudonym';
+upper_bound(?'id-at-generationQualifier') ->
+ ?'ub-generation-qualifier-length';
+upper_bound(?'id-at-commonName') ->
+ ?'ub-common-name';
+upper_bound(?'id-at-dnQualifier') ->
+ ?'ub-domain-defined-attribute-value-length';
+upper_bound(?'id-at-serialNumber') ->
+ ?'ub-serial-number';
+upper_bound(?'id-domainComponent') ->
+ ?'ub-domain-name-length'.
+
+upper_case() ->
+ ?LET(ASCII, choose($A, $Z), ASCII).
+
+lower_case() ->
+ ?LET(ASCII, choose($a, $z), ASCII).
+
+digits() ->
+ ?LET(ASCII, choose($0, $9), ASCII).
+
+misc_values() ->
+ ?LET(ASCII, elements([$\r, $.,$,]), ASCII).
+
+printable_string(Len)->
+ ?LET(Value,
+ ?SUCHTHAT(X, list(oneof([lower_case(), upper_case(), digits(), misc_values()])), X =/= []),
+ Value).
+
+printable_string(Len, Suffix)->
+ ?LET(Value, ?SUCHTHAT(X, list(lower_case()), X =/= []), Value ++ Suffix).
+
+ia5_string(Len)->
+ ?LET(Value, ?SUCHTHAT(X, list(oneof([upper_case(), lower_case()])), X =/= []),
+ Value).
diff --git a/lib/public_key/test/pubkey_eqc_SUITE.erl b/lib/public_key/test/pubkey_eqc_SUITE.erl
new file mode 100644
index 0000000000..15c06672ca
--- /dev/null
+++ b/lib/public_key/test/pubkey_eqc_SUITE.erl
@@ -0,0 +1,90 @@
+%%
+%% %CopyrightBegin%
+%%
+%% SPDX-License-Identifier: Apache-2.0
+%%
+%% Copyright Ericsson AB 2026-2026. All Rights Reserved.
+%%
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%%
+%% http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%%
+%% %CopyrightEnd%
+%%
+%%
+
+-module(pubkey_eqc_SUITE).
+
+-behaviour(ct_suite).
+
+%% Common test
+-export([all/0,
+ init_per_suite/1,
+ init_per_testcase/2,
+ end_per_suite/1,
+ end_per_testcase/2
+ ]).
+
+%% Test cases
+-export([pkix_implicit/1,
+ pkix_explicit/1,
+ pkix_ocsp/1
+ ]).
+
+%%--------------------------------------------------------------------
+%% Common Test interface functions -----------------------------------
+%%--------------------------------------------------------------------
+
+all() ->
+ [
+ pkix_implicit,
+ pkix_explicit,
+ pkix_ocsp
+ ].
+
+%%--------------------------------------------------------------------
+init_per_suite(Config) ->
+ ct:timetrap({seconds, 20}),
+ try application:ensure_all_started(public_key) of
+ {ok, _} ->
+ ct_property_test:init_per_suite(Config)
+ catch _:_ ->
+ {skip, "Crypto did not start"}
+ end.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_testcase(_, Config0) ->
+ Config0.
+
+end_per_testcase(_TestCase, Config) ->
+ Config.
+
+%%--------------------------------------------------------------------
+%% Test Cases --------------------------------------------------------
+%%--------------------------------------------------------------------
+
+pkix_implicit(Config) when is_list(Config) ->
+ %% manual test: eqc:quickcheck(pkix:implicit_encode_decode()).
+ %% proper:quickcheck(pkix:implicit_encode_decode()).
+ true = ct_property_test:quickcheck(pkix:implicit_encode_decode(),
+ Config).
+pkix_explicit(Config) when is_list(Config) ->
+ %% manual test: eqc:quickcheck(pkix:implicit_encode_decode()).
+ %% proper:quickcheck(pkix:explicit_encode_decode()).
+ true = ct_property_test:quickcheck(pkix:explicit_encode_decode(),
+ Config).
+pkix_ocsp(Config) when is_list(Config) ->
+ %% manual test: eqc:quickcheck(pkix:implicit_encode_decode()).
+ %% proper:quickcheck(pkix:explicit_encode_decode()).
+ true = ct_property_test:quickcheck(pkix:ocsp_encode_decode(),
+ Config).
--
2.51.0