File 2271-public_key-Add-support-for-ExtensionRequest.patch of Package erlang

From 5f88033ab49bad0c380129fda81ca26f3149cdf1 Mon Sep 17 00:00:00 2001
From: Ingela Anderton Andin <ingela@erlang.org>
Date: Mon, 7 Jul 2025 11:29:43 +0200
Subject: [PATCH] public_key: Add support for ExtensionRequest

Add modern ASN-1 specs to be able to retain support
for ExtensionRequest from legacy PKCS-9 spec.

This can open up for further support of EnrollmentMessageSyntax-2009 being added later.

Also add some missing backwards compatibility
for X520CommonName and legacy AttributeTypeAndValue

Closes #10028
---
 .../asn1/EnrollmentMessageSyntax-2009.asn1    |  575 +++++++++
 lib/public_key/asn1/Makefile                  |    2 +
 lib/public_key/asn1/PKIXCRMF-2009.asn1        | 1059 +++++++++++++++++
 lib/public_key/include/public_key.hrl         |    3 +-
 lib/public_key/src/public_key.app.src         |    2 +
 lib/public_key/src/public_key.erl             |   17 +
 lib/public_key/test/public_key_SUITE.erl      |   15 +
 7 files changed, 1671 insertions(+), 2 deletions(-)
 create mode 100644 lib/public_key/asn1/EnrollmentMessageSyntax-2009.asn1
 create mode 100644 lib/public_key/asn1/PKIXCRMF-2009.asn1

diff --git a/lib/public_key/asn1/EnrollmentMessageSyntax-2009.asn1 b/lib/public_key/asn1/EnrollmentMessageSyntax-2009.asn1
new file mode 100644
index 0000000000..6cc89b6fef
--- /dev/null
+++ b/lib/public_key/asn1/EnrollmentMessageSyntax-2009.asn1
@@ -0,0 +1,575 @@
+-- %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%
+
+-- RFC 5912
+EnrollmentMessageSyntax-2009
+      {iso(1) identified-organization(3) dod(6) internet(1)
+      security(5) mechanisms(5) pkix(7) id-mod(0) id-mod-cmc2002-02(53)}
+  DEFINITIONS IMPLICIT TAGS ::=
+  BEGIN
+  EXPORTS ALL;
+  IMPORTS
+
+  AttributeSet{}, Extension{}, EXTENSION, ATTRIBUTE
+  FROM PKIX-CommonTypes-2009
+      {iso(1) identified-organization(3) dod(6) internet(1) security(5)
+      mechanisms(5) pkix(7) id-mod(0) id-mod-pkixCommon-02(57)}
+  AlgorithmIdentifier{}, DIGEST-ALGORITHM, KEY-WRAP, KEY-DERIVATION,
+      MAC-ALGORITHM, SIGNATURE-ALGORITHM, PUBLIC-KEY
+  FROM AlgorithmInformation-2009
+      {iso(1) identified-organization(3) dod(6) internet(1) security(5)
+      mechanisms(5) pkix(7) id-mod(0)
+      id-mod-algorithmInformation-02(58)}
+
+  CertificateSerialNumber, GeneralName, CRLReason, ReasonFlags,
+      CertExtensions
+  FROM PKIX1Implicit-2009
+      {iso(1) identified-organization(3) dod(6) internet(1) security(5)
+      mechanisms(5) pkix(7) id-mod(0) id-mod-pkix1-implicit-02(59)}
+
+  Name, id-pkix, PublicKeyAlgorithms, SignatureAlgorithms
+  FROM PKIX1Explicit-2009
+      {iso(1) identified-organization(3) dod(6) internet(1) security(5)
+      mechanisms(5) pkix(7) id-mod(0) id-mod-pkix1-explicit-02(51)}
+
+  ContentInfo, IssuerAndSerialNumber, CONTENT-TYPE
+  FROM CryptographicMessageSyntax-2009
+      { iso(1) member-body(2) us(840) rsadsi(113549) pkcs(1) pkcs-9(9)
+      smime(16) modules(0) id-mod-cms-2004-02(41)}
+
+  CertReqMsg, PKIPublicationInfo, CertTemplate
+  FROM PKIXCRMF-2009
+   {iso(1) identified-organization(3) dod(6) internet(1) security(5)
+      mechanisms(5) pkix(7) id-mod(0) id-mod-crmf2005-02(55)}
+
+  mda-sha1
+  FROM PKIXAlgs-2009
+       { iso(1) identified-organization(3) dod(6)
+       internet(1) security(5) mechanisms(5) pkix(7) id-mod(0)
+       id-mod-pkix1-algorithms2008-02(56)}
+
+  kda-PBKDF2, maca-hMAC-SHA1
+  FROM CryptographicMessageSyntaxAlgorithms-2009
+      { iso(1) member-body(2) us(840) rsadsi(113549) pkcs(1) pkcs-9(9)
+      smime(16) modules(0) id-mod-cmsalg-2001-02(37) }
+
+  mda-sha256
+  FROM PKIX1-PSS-OAEP-Algorithms-2009
+       { iso(1) identified-organization(3) dod(6)
+         internet(1) security(5) mechanisms(5) pkix(7) id-mod(0)
+         id-mod-pkix1-rsa-pkalgs-02(54) } ;
+
+  --  CMS Content types defined in this document
+  CMC-ContentTypes CONTENT-TYPE ::= { ct-PKIData | ct-PKIResponse, ... }
+
+  --  Signature Algorithms defined in this document
+
+  SignatureAlgs SIGNATURE-ALGORITHM ::= { sa-noSignature }
+
+  --  CMS Unsigned Attributes
+
+  CMC-UnsignedAtts ATTRIBUTE ::= { aa-cmc-unsignedData }
+
+  --
+  --
+
+  id-cmc OBJECT IDENTIFIER ::= {id-pkix 7}   -- CMC controls
+  id-cct OBJECT IDENTIFIER ::= {id-pkix 12}  -- CMC content types
+
+  -- This is the content type for a request message in the protocol
+
+  ct-PKIData CONTENT-TYPE ::=
+      { PKIData IDENTIFIED BY id-cct-PKIData }
+  id-cct-PKIData OBJECT IDENTIFIER ::= { id-cct 2 }
+
+  PKIData ::= SEQUENCE {
+      controlSequence    SEQUENCE SIZE(0..MAX) OF TaggedAttribute,
+      reqSequence        SEQUENCE SIZE(0..MAX) OF TaggedRequest,
+      cmsSequence        SEQUENCE SIZE(0..MAX) OF TaggedContentInfo,
+      otherMsgSequence   SEQUENCE SIZE(0..MAX) OF OtherMsg
+       }
+
+  BodyPartID ::= INTEGER(0..4294967295)
+
+  TaggedAttribute ::= SEQUENCE {
+      bodyPartID         BodyPartID,
+      attrType           CMC-CONTROL.&id({Cmc-Control-Set}),
+      attrValues         SET OF CMC-CONTROL.
+                             &Type({Cmc-Control-Set}{@attrType})
+  }
+
+  Cmc-Control-Set CMC-CONTROL ::= {
+      cmc-identityProof | cmc-dataReturn | cmc-regInfo |
+      cmc-responseInfo | cmc-queryPending | cmc-popLinkRandom |
+      cmc-popLinkWitness | cmc-identification | cmc-transactionId |
+      cmc-senderNonce | cmc-recipientNonce | cmc-statusInfo |
+      cmc-addExtensions | cmc-encryptedPOP | cmc-decryptedPOP |
+      cmc-lraPOPWitness | cmc-getCert | cmc-getCRL |
+      cmc-revokeRequest | cmc-confirmCertAcceptance |
+      cmc-statusInfoV2 | cmc-trustedAnchors | cmc-authData |
+      cmc-batchRequests | cmc-batchResponses | cmc-publishCert |
+      cmc-modCertTemplate | cmc-controlProcessed |
+      cmc-identityProofV2 | cmc-popLinkWitnessV2, ... }
+
+  OTHER-REQUEST ::= TYPE-IDENTIFIER
+
+  --  We do not define any other requests in this document;
+  --     examples might be attribute certification requests
+
+  OtherRequests OTHER-REQUEST ::= {...}
+
+  TaggedRequest ::= CHOICE {
+      tcr               [0] TaggedCertificationRequest,
+      crm               [1] CertReqMsg,
+      orm               [2] SEQUENCE {
+          bodyPartID            BodyPartID,
+          requestMessageType    OTHER-REQUEST.&id({OtherRequests}),
+          requestMessageValue   OTHER-REQUEST.&Type({OtherRequests}
+                                    {@.requestMessageType})
+      }
+  }
+
+  TaggedCertificationRequest ::= SEQUENCE {
+      bodyPartID            BodyPartID,
+      certificationRequest  CertificationRequest
+  }
+
+  AttributeList ATTRIBUTE ::= {at-extension-req, ...}
+
+CertificationRequest ::= SEQUENCE {
+     certificationRequestInfo  SEQUENCE {
+         version                   INTEGER,
+         subject                   Name,
+         subjectPublicKeyInfo      SEQUENCE {
+             algorithm                 AlgorithmIdentifier{PUBLIC-KEY,
+                                           {PublicKeyAlgorithms}},
+             subjectPublicKey          BIT STRING
+         },
+         attributes                [0] IMPLICIT SET OF
+                                       AttributeSet{{AttributeList}}
+      },
+      signatureAlgorithm        AlgorithmIdentifier
+                                    {SIGNATURE-ALGORITHM,
+                                        {SignatureAlgorithms}},
+      signature                 BIT STRING
+  }
+
+  TaggedContentInfo ::= SEQUENCE {
+      bodyPartID              BodyPartID,
+      contentInfo             ContentInfo
+  }
+
+  OTHER-MSG ::= TYPE-IDENTIFIER
+
+  --  No other messages currently defined
+
+  OtherMsgSet OTHER-MSG ::= {...}
+
+  OtherMsg ::= SEQUENCE {
+      bodyPartID        BodyPartID,
+      otherMsgType      OTHER-MSG.&id({OtherMsgSet}),
+      otherMsgValue     OTHER-MSG.&Type({OtherMsgSet}{@otherMsgType}) }
+
+  --  This defines the response message in the protocol
+
+  ct-PKIResponse CONTENT-TYPE ::=
+      { PKIResponse IDENTIFIED BY id-cct-PKIResponse }
+  id-cct-PKIResponse OBJECT IDENTIFIER ::= { id-cct 3 }
+
+  ResponseBody ::= PKIResponse
+
+  PKIResponse ::= SEQUENCE {
+      controlSequence   SEQUENCE SIZE(0..MAX) OF TaggedAttribute,
+      cmsSequence       SEQUENCE SIZE(0..MAX) OF TaggedContentInfo,
+      otherMsgSequence  SEQUENCE SIZE(0..MAX) OF OtherMsg
+  }
+
+CMC-CONTROL ::= TYPE-IDENTIFIER
+
+  -- The following controls have the type OCTET STRING
+
+  cmc-identityProof CMC-CONTROL ::=
+      { OCTET STRING IDENTIFIED BY id-cmc-identityProof }
+  id-cmc-identityProof OBJECT IDENTIFIER ::= {id-cmc 3}
+
+  cmc-dataReturn CMC-CONTROL ::=
+      { OCTET STRING IDENTIFIED BY id-cmc-dataReturn }
+  id-cmc-dataReturn OBJECT IDENTIFIER ::= {id-cmc 4}
+
+  cmc-regInfo CMC-CONTROL ::=
+      { OCTET STRING IDENTIFIED BY id-cmc-regInfo }
+  id-cmc-regInfo OBJECT IDENTIFIER ::= {id-cmc 18}
+
+  cmc-responseInfo CMC-CONTROL ::=
+      { OCTET STRING IDENTIFIED BY id-cmc-responseInfo }
+  id-cmc-responseInfo OBJECT IDENTIFIER ::= {id-cmc 19}
+
+  cmc-queryPending CMC-CONTROL ::=
+      { OCTET STRING IDENTIFIED BY id-cmc-queryPending }
+  id-cmc-queryPending OBJECT IDENTIFIER ::= {id-cmc 21}
+
+  cmc-popLinkRandom CMC-CONTROL ::=
+      { OCTET STRING IDENTIFIED BY id-cmc-popLinkRandom }
+  id-cmc-popLinkRandom OBJECT IDENTIFIER ::= {id-cmc 22}
+
+  cmc-popLinkWitness CMC-CONTROL ::=
+      { OCTET STRING IDENTIFIED BY id-cmc-popLinkWitness }
+  id-cmc-popLinkWitness OBJECT IDENTIFIER ::= {id-cmc 23}
+
+  -- The following controls have the type UTF8String
+
+  cmc-identification CMC-CONTROL ::=
+      { UTF8String IDENTIFIED BY id-cmc-identification }
+  id-cmc-identification OBJECT IDENTIFIER ::= {id-cmc 2}
+
+  -- The following controls have the type INTEGER
+
+  cmc-transactionId CMC-CONTROL ::=
+      { INTEGER IDENTIFIED BY id-cmc-transactionId }
+  id-cmc-transactionId OBJECT IDENTIFIER ::= {id-cmc 5}
+
+  -- The following controls have the type OCTET STRING
+
+  cmc-senderNonce CMC-CONTROL ::=
+      { OCTET STRING IDENTIFIED BY id-cmc-senderNonce }
+       id-cmc-senderNonce OBJECT IDENTIFIER ::= {id-cmc 6}
+
+  cmc-recipientNonce CMC-CONTROL ::=
+      { OCTET STRING IDENTIFIED BY id-cmc-recipientNonce }
+  id-cmc-recipientNonce OBJECT IDENTIFIER ::= {id-cmc 7}
+
+  -- Used to return status in a response
+
+  cmc-statusInfo CMC-CONTROL ::=
+      { CMCStatusInfo IDENTIFIED BY id-cmc-statusInfo }
+  id-cmc-statusInfo OBJECT IDENTIFIER ::= {id-cmc 1}
+
+  CMCStatusInfo ::= SEQUENCE {
+      cMCStatus       CMCStatus,
+      bodyList        SEQUENCE SIZE (1..MAX) OF BodyPartID,
+      statusString    UTF8String OPTIONAL,
+      otherInfo       CHOICE {
+         failInfo         CMCFailInfo,
+         pendInfo         PendInfo
+      } OPTIONAL
+  }
+
+  PendInfo ::= SEQUENCE {
+      pendToken        OCTET STRING,
+      pendTime         GeneralizedTime
+  }
+
+  CMCStatus ::= INTEGER {
+      success         (0),
+      failed          (2),
+      pending         (3),
+      noSupport       (4),
+      confirmRequired (5),
+      popRequired     (6),
+      partial         (7)
+  }
+
+  -- Note:
+  -- The spelling of unsupportedExt is corrected in this version.
+  -- In RFC 2797, it was unsuportedExt.
+
+  CMCFailInfo ::= INTEGER {
+      badAlg          (0),
+      badMessageCheck (1),
+      badRequest      (2),
+      badTime         (3),
+      badCertId       (4),
+      unsuportedExt   (5),
+       mustArchiveKeys (6),
+      badIdentity     (7),
+      popRequired     (8),
+      popFailed       (9),
+      noKeyReuse      (10),
+      internalCAError (11),
+      tryLater        (12),
+      authDataFail    (13)
+  }
+
+  -- Used for RAs to add extensions to certification requests
+
+  cmc-addExtensions CMC-CONTROL ::=
+      { AddExtensions IDENTIFIED BY id-cmc-addExtensions }
+  id-cmc-addExtensions OBJECT IDENTIFIER ::= {id-cmc 8}
+
+  AddExtensions ::= SEQUENCE {
+      pkiDataReference    BodyPartID,
+      certReferences      SEQUENCE OF BodyPartID,
+      extensions          SEQUENCE OF Extension{{CertExtensions}}
+  }
+
+  cmc-encryptedPOP CMC-CONTROL ::=
+      { EncryptedPOP IDENTIFIED BY id-cmc-encryptedPOP }
+  cmc-decryptedPOP CMC-CONTROL ::=
+      { DecryptedPOP IDENTIFIED BY id-cmc-decryptedPOP }
+  id-cmc-encryptedPOP OBJECT IDENTIFIER ::= {id-cmc 9}
+  id-cmc-decryptedPOP OBJECT IDENTIFIER ::= {id-cmc 10}
+
+  EncryptedPOP ::= SEQUENCE {
+      request       TaggedRequest,
+      cms             ContentInfo,
+      thePOPAlgID     AlgorithmIdentifier{MAC-ALGORITHM, {POPAlgs}},
+      witnessAlgID    AlgorithmIdentifier{DIGEST-ALGORITHM,
+                          {WitnessAlgs}},
+      witness         OCTET STRING
+  }
+
+  POPAlgs MAC-ALGORITHM ::= {maca-hMAC-SHA1, ...}
+  WitnessAlgs DIGEST-ALGORITHM ::= {mda-sha1, ...}
+
+  DecryptedPOP ::= SEQUENCE {
+      bodyPartID      BodyPartID,
+      thePOPAlgID     AlgorithmIdentifier{MAC-ALGORITHM, {POPAlgs}},
+      thePOP          OCTET STRING
+  }
+
+  cmc-lraPOPWitness CMC-CONTROL ::=
+   { LraPopWitness IDENTIFIED BY id-cmc-lraPOPWitness }
+
+  id-cmc-lraPOPWitness OBJECT IDENTIFIER ::= {id-cmc 11}
+
+  LraPopWitness ::= SEQUENCE {
+      pkiDataBodyid   BodyPartID,
+      bodyIds         SEQUENCE OF BodyPartID
+  }
+
+  --
+
+  cmc-getCert CMC-CONTROL ::=
+      { GetCert IDENTIFIED BY id-cmc-getCert }
+  id-cmc-getCert OBJECT IDENTIFIER ::= {id-cmc 15}
+
+  GetCert ::= SEQUENCE {
+      issuerName      GeneralName,
+      serialNumber    INTEGER }
+
+  cmc-getCRL CMC-CONTROL ::=
+      { GetCRL IDENTIFIED BY id-cmc-getCRL }
+  id-cmc-getCRL OBJECT IDENTIFIER ::= {id-cmc 16}
+  GetCRL ::= SEQUENCE {
+      issuerName    Name,
+      cRLName       GeneralName OPTIONAL,
+      time          GeneralizedTime OPTIONAL,
+      reasons       ReasonFlags OPTIONAL }
+
+  cmc-revokeRequest CMC-CONTROL ::=
+      { RevokeRequest IDENTIFIED BY id-cmc-revokeRequest}
+  id-cmc-revokeRequest OBJECT IDENTIFIER ::= {id-cmc 17}
+
+  RevokeRequest ::= SEQUENCE {
+      issuerName            Name,
+      serialNumber          INTEGER,
+      reason                CRLReason,
+      invalidityDate         GeneralizedTime OPTIONAL,
+      passphrase            OCTET STRING OPTIONAL,
+      comment               UTF8String OPTIONAL }
+
+  cmc-confirmCertAcceptance CMC-CONTROL ::=
+      { CMCCertId IDENTIFIED BY id-cmc-confirmCertAcceptance }
+  id-cmc-confirmCertAcceptance OBJECT IDENTIFIER ::= {id-cmc 24}
+
+  CMCCertId ::= IssuerAndSerialNumber
+
+  -- The following is used to request v3 extensions be added
+  --     to a certificate
+  at-extension-req ATTRIBUTE ::=
+      { TYPE ExtensionReq IDENTIFIED BY id-ExtensionReq }
+  id-ExtensionReq OBJECT IDENTIFIER ::= {iso(1) member-body(2) us(840)
+      rsadsi(113549) pkcs(1) pkcs-9(9) 14}
+
+  ExtensionReq ::= SEQUENCE SIZE (1..MAX) OF
+      Extension{{CertExtensions}}
+
+  -- The following allows Diffie-Hellman Certification Request
+  --     Messages to be well-formed
+
+  sa-noSignature SIGNATURE-ALGORITHM ::= {
+      IDENTIFIER id-alg-noSignature
+      VALUE NoSignatureValue
+      PARAMS TYPE NULL ARE required
+      HASHES { mda-sha1 }
+  }
+  id-alg-noSignature OBJECT IDENTIFIER ::= {id-pkix id-alg(6) 2}
+
+  NoSignatureValue ::= OCTET STRING
+  --  Unauthenticated attribute to carry removable data.
+
+  id-aa OBJECT IDENTIFIER ::= { iso(1) member-body(2) us(840)
+      rsadsi(113549) pkcs(1) pkcs-9(9) smime(16) id-aa(2)}
+
+  aa-cmc-unsignedData ATTRIBUTE ::=
+      { TYPE CMCUnsignedData IDENTIFIED BY id-aa-cmc-unsignedData }
+  id-aa-cmc-unsignedData OBJECT IDENTIFIER ::= {id-aa 34}
+
+  CMCUnsignedData ::= SEQUENCE {
+      bodyPartPath        BodyPartPath,
+      identifier          TYPE-IDENTIFIER.&id,
+      content             TYPE-IDENTIFIER.&Type
+  }
+
+  --  Replaces CMC Status Info
+  --
+
+  cmc-statusInfoV2 CMC-CONTROL ::=
+      { CMCStatusInfoV2 IDENTIFIED BY id-cmc-statusInfoV2 }
+  id-cmc-statusInfoV2 OBJECT IDENTIFIER ::= {id-cmc 25}
+
+  EXTENDED-FAILURE-INFO ::= TYPE-IDENTIFIER
+
+  ExtendedFailures EXTENDED-FAILURE-INFO ::= {...}
+
+  CMCStatusInfoV2 ::= SEQUENCE {
+     cMCStatus             CMCStatus,
+      bodyList              SEQUENCE SIZE (1..MAX) OF
+                                    BodyPartReference,
+     statusString          UTF8String OPTIONAL,
+     otherInfo             CHOICE {
+         failInfo               CMCFailInfo,
+         pendInfo               PendInfo,
+         extendedFailInfo       [1] SEQUENCE {
+            failInfoOID            TYPE-IDENTIFIER.&id
+                                       ({ExtendedFailures}),
+            failInfoValue          TYPE-IDENTIFIER.&Type
+                                       ({ExtendedFailures}
+                                           {@.failInfoOID})
+         }
+      } OPTIONAL
+  }
+
+  BodyPartReference ::= CHOICE {
+     bodyPartID           BodyPartID,
+     bodyPartPath         BodyPartPath
+  }
+
+  BodyPartPath ::= SEQUENCE SIZE (1..MAX) OF BodyPartID
+
+  --  Allow for distribution of trust anchors
+  --
+
+  cmc-trustedAnchors CMC-CONTROL ::=
+      { PublishTrustAnchors IDENTIFIED BY id-cmc-trustedAnchors }
+  id-cmc-trustedAnchors OBJECT IDENTIFIER ::= {id-cmc 26}
+
+  PublishTrustAnchors ::= SEQUENCE {
+      seqNumber      INTEGER,
+      hashAlgorithm  AlgorithmIdentifier{DIGEST-ALGORITHM,
+                         {HashAlgorithms}},
+      anchorHashes   SEQUENCE OF OCTET STRING
+  }
+
+  HashAlgorithms DIGEST-ALGORITHM ::= {
+     mda-sha1 | mda-sha256, ...
+  }
+
+  cmc-authData CMC-CONTROL ::=
+      { AuthPublish IDENTIFIED BY id-cmc-authData }
+  id-cmc-authData OBJECT IDENTIFIER ::= {id-cmc 27}
+
+  AuthPublish ::= BodyPartID
+
+  --   These two items use BodyPartList
+  cmc-batchRequests CMC-CONTROL ::=
+      { BodyPartList IDENTIFIED BY id-cmc-batchRequests }
+  id-cmc-batchRequests OBJECT IDENTIFIER ::= {id-cmc 28}
+
+  cmc-batchResponses CMC-CONTROL ::=
+      { BodyPartList IDENTIFIED BY id-cmc-batchResponses }
+  id-cmc-batchResponses OBJECT IDENTIFIER ::= {id-cmc 29}
+
+  BodyPartList ::= SEQUENCE SIZE (1..MAX) OF BodyPartID
+
+  cmc-publishCert CMC-CONTROL ::=
+      { CMCPublicationInfo IDENTIFIED BY id-cmc-publishCert }
+  id-cmc-publishCert OBJECT IDENTIFIER ::= {id-cmc 30}
+
+  CMCPublicationInfo ::= SEQUENCE {
+      hashAlg        AlgorithmIdentifier{DIGEST-ALGORITHM,
+                           {HashAlgorithms}},
+      certHashes     SEQUENCE OF OCTET STRING,
+      pubInfo        PKIPublicationInfo
+  }
+
+  cmc-modCertTemplate CMC-CONTROL ::=
+      { ModCertTemplate IDENTIFIED BY id-cmc-modCertTemplate }
+  id-cmc-modCertTemplate OBJECT IDENTIFIER ::= {id-cmc 31}
+
+  ModCertTemplate ::= SEQUENCE {
+      pkiDataReference             BodyPartPath,
+      certReferences               BodyPartList,
+      replace                      BOOLEAN DEFAULT TRUE,
+      certTemplate                 CertTemplate
+  }
+
+  -- Inform follow-on servers that one or more controls have
+  --     already been processed
+
+  cmc-controlProcessed CMC-CONTROL ::=
+      { ControlsProcessed IDENTIFIED BY id-cmc-controlProcessed }
+  id-cmc-controlProcessed OBJECT IDENTIFIER ::= {id-cmc 32}
+
+  ControlsProcessed ::= SEQUENCE {
+      bodyList              SEQUENCE SIZE(1..MAX) OF BodyPartReference
+  }
+
+  --  Identity Proof control w/ algorithm agility
+
+  cmc-identityProofV2 CMC-CONTROL ::=
+      { IdentityProofV2 IDENTIFIED BY id-cmc-identityProofV2 }
+  id-cmc-identityProofV2 OBJECT IDENTIFIER ::= { id-cmc 33 }
+  IdentityProofV2 ::= SEQUENCE {
+      proofAlgID       AlgorithmIdentifier{DIGEST-ALGORITHM,
+                           {WitnessAlgs}},
+      macAlgId         AlgorithmIdentifier{MAC-ALGORITHM, {POPAlgs}},
+      witness          OCTET STRING
+  }
+
+  cmc-popLinkWitnessV2 CMC-CONTROL ::=
+      { PopLinkWitnessV2 IDENTIFIED BY id-cmc-popLinkWitnessV2 }
+  id-cmc-popLinkWitnessV2 OBJECT IDENTIFIER ::= { id-cmc 34 }
+
+  PopLinkWitnessV2 ::= SEQUENCE {
+      keyGenAlgorithm   AlgorithmIdentifier{KEY-DERIVATION,
+                            {KeyDevAlgs}},
+      macAlgorithm      AlgorithmIdentifier{MAC-ALGORITHM, {POPAlgs}},
+      witness           OCTET STRING
+  }
+
+  KeyDevAlgs KEY-DERIVATION ::= {kda-PBKDF2, ...}
+
+END
diff --git a/lib/public_key/asn1/Makefile b/lib/public_key/asn1/Makefile
index f7dd49fca6..3f5a38c4ee 100644
--- a/lib/public_key/asn1/Makefile
+++ b/lib/public_key/asn1/Makefile
@@ -66,6 +66,8 @@ ASN_MODULES = \
           PKIX1Explicit-2009 \
           PKIX1Implicit-2009 \
           PKIXAlgs-2009 \
+	  PKIXCRMF-2009 \
+          EnrollmentMessageSyntax-2009 \
           PKIXAttributeCertificate-2009 \
 	  RFC5639 \
           Safecurves-pkix-18 \
diff --git a/lib/public_key/asn1/PKIXCRMF-2009.asn1 b/lib/public_key/asn1/PKIXCRMF-2009.asn1
new file mode 100644
index 0000000000..b06b1c2bf3
--- /dev/null
+++ b/lib/public_key/asn1/PKIXCRMF-2009.asn1
@@ -0,0 +1,1059 @@
+-- %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%
+
+-- RFC 5912
+PKIXCRMF-2009
+      {iso(1) identified-organization(3) dod(6) internet(1) security(5)
+      mechanisms(5) pkix(7) id-mod(0) id-mod-crmf2005-02(55)}
+  DEFINITIONS IMPLICIT TAGS ::=
+  BEGIN
+  IMPORTS
+
+  AttributeSet{}, Extensions{}, EXTENSION, ATTRIBUTE,
+      SingleAttribute{}
+  FROM PKIX-CommonTypes-2009
+      {iso(1) identified-organization(3) dod(6) internet(1)
+      security(5) mechanisms(5) pkix(7) id-mod(0)
+      id-mod-pkixCommon-02(57) }
+
+  AlgorithmIdentifier{}, SIGNATURE-ALGORITHM, ALGORITHM,
+      DIGEST-ALGORITHM, MAC-ALGORITHM, PUBLIC-KEY
+  FROM AlgorithmInformation-2009
+      {iso(1) identified-organization(3) dod(6) internet(1) security(5)
+      mechanisms(5) pkix(7) id-mod(0)
+      id-mod-algorithmInformation-02(58)}
+
+  Version, Name, Time, SubjectPublicKeyInfo, UniqueIdentifier, id-pkix,
+      SignatureAlgorithms
+  FROM PKIX1Explicit-2009
+      {iso(1) identified-organization(3) dod(6) internet(1) security(5)
+      mechanisms(5) pkix(7) id-mod(0) id-mod-pkix1-explicit-02(51)}
+
+  GeneralName, CertExtensions
+  FROM PKIX1Implicit-2009
+      {iso(1) identified-organization(3) dod(6) internet(1) security(5)
+      mechanisms(5) pkix(7) id-mod(0) id-mod-pkix1-implicit-02(59)}
+
+  EnvelopedData, CONTENT-TYPE
+  FROM CryptographicMessageSyntax-2009
+      { iso(1) member-body(2) us(840) rsadsi(113549) pkcs(1) pkcs-9(9)
+      smime(16) modules(0) id-mod-cms-2004-02(41)}
+  maca-hMAC-SHA1
+  FROM CryptographicMessageSyntaxAlgorithms-2009
+      { iso(1) member-body(2) us(840) rsadsi(113549) pkcs(1) pkcs-9(9)
+      smime(16) modules(0) id-mod-cmsalg-2001-02(37) }
+
+  mda-sha1
+  FROM PKIXAlgs-2009
+      { iso(1) identified-organization(3) dod(6)
+      internet(1) security(5) mechanisms(5) pkix(7) id-mod(0)
+      id-mod-pkix1-algorithms2008-02(56) } ;
+
+  -- arc for Internet X.509 PKI protocols and their components
+
+  id-pkip  OBJECT IDENTIFIER ::= { id-pkix 5 }
+
+  id-smime OBJECT IDENTIFIER ::= { iso(1) member-body(2)
+       us(840) rsadsi(113549) pkcs(1) pkcs9(9) 16 }
+
+  id-ct   OBJECT IDENTIFIER ::= { id-smime  1 }  -- content types
+
+  -- Core definitions for this module
+
+  CertReqMessages ::= SEQUENCE SIZE (1..MAX) OF CertReqMsg
+
+  CertReqMsg ::= SEQUENCE {
+      certReq   CertRequest,
+      popo       ProofOfPossession  OPTIONAL,
+      -- content depends upon key type
+      regInfo   SEQUENCE SIZE(1..MAX) OF
+          SingleAttribute{{RegInfoSet}} OPTIONAL }
+
+  CertRequest ::= SEQUENCE {
+      certReqId     INTEGER,
+      -- ID for matching request and reply
+      certTemplate  CertTemplate,
+      -- Selected fields of cert to be issued
+      controls      Controls OPTIONAL }
+      -- Attributes affecting issuance
+
+  CertTemplate ::= SEQUENCE {
+      version      [0] Version               OPTIONAL,
+      serialNumber [1] INTEGER               OPTIONAL,
+      signingAlg   [2] AlgorithmIdentifier{SIGNATURE-ALGORITHM,
+                           {SignatureAlgorithms}}   OPTIONAL,
+      issuer       [3] Name                  OPTIONAL,
+      validity     [4] OptionalValidity      OPTIONAL,
+      subject      [5] Name                  OPTIONAL,
+      publicKey    [6] SubjectPublicKeyInfo  OPTIONAL,
+      issuerUID    [7] UniqueIdentifier      OPTIONAL,
+      subjectUID   [8] UniqueIdentifier      OPTIONAL,
+      extensions   [9] Extensions{{CertExtensions}}  OPTIONAL }
+
+  OptionalValidity ::= SEQUENCE {
+      notBefore  [0] Time OPTIONAL,
+      notAfter   [1] Time OPTIONAL } -- at least one MUST be present
+
+  Controls  ::= SEQUENCE SIZE(1..MAX) OF SingleAttribute
+                    {{RegControlSet}}
+		    ProofOfPossession ::= CHOICE {
+      raVerified        [0] NULL,
+      -- used if the RA has already verified that the requester is in
+      -- possession of the private key
+      signature         [1] POPOSigningKey,
+      keyEncipherment   [2] POPOPrivKey,
+      keyAgreement      [3] POPOPrivKey }
+
+  POPOSigningKey ::= SEQUENCE {
+      poposkInput           [0] POPOSigningKeyInput OPTIONAL,
+      algorithmIdentifier   AlgorithmIdentifier{SIGNATURE-ALGORITHM,
+                                {SignatureAlgorithms}},
+      signature             BIT STRING }
+      -- The signature (using "algorithmIdentifier") is on the
+      -- DER-encoded value of poposkInput.  NOTE: If the CertReqMsg
+      -- certReq CertTemplate contains the subject and publicKey values,
+      -- then poposkInput MUST be omitted and the signature MUST be
+      -- computed over the DER-encoded value of CertReqMsg certReq.  If
+      -- the CertReqMsg certReq CertTemplate does not contain both the
+      -- public key and subject values (i.e., if it contains only one
+      -- of these, or neither), then poposkInput MUST be present and
+      -- MUST be signed.
+
+  POPOSigningKeyInput ::= SEQUENCE {
+      authInfo            CHOICE {
+       sender              [0] GeneralName,
+       -- used only if an authenticated identity has been
+       -- established for the sender (e.g., a DN from a
+       -- previously-issued and currently-valid certificate)
+       publicKeyMAC        PKMACValue },
+       -- used if no authenticated GeneralName currently exists for
+       -- the sender; publicKeyMAC contains a password-based MAC
+       -- on the DER-encoded value of publicKey
+      publicKey           SubjectPublicKeyInfo }  -- from CertTemplate
+
+  PKMACValue ::= SEQUENCE {
+      algId  AlgorithmIdentifier{MAC-ALGORITHM,
+                 {Password-MACAlgorithms}},
+      value  BIT STRING }
+
+  --
+  --  Define the currently only acceptable MAC algorithm to be used
+  --  for the PKMACValue structure
+  --
+
+  id-PasswordBasedMac OBJECT IDENTIFIER ::= { iso(1) member-body(2)
+      usa(840) nt(113533) nsn(7) algorithms(66) 13 }
+
+Password-MACAlgorithms MAC-ALGORITHM ::= {
+      {IDENTIFIER id-PasswordBasedMac
+       PARAMS TYPE PBMParameter ARE required
+       IS-KEYED-MAC TRUE
+      }, ...
+  }
+
+  PBMParameter ::= SEQUENCE {
+     salt                OCTET STRING,
+     owf                 AlgorithmIdentifier{DIGEST-ALGORITHM,
+                             {DigestAlgorithms}},
+     -- AlgId for a One-Way Function (SHA-1 recommended)
+     iterationCount      INTEGER,
+     -- number of times the OWF is applied
+     mac                 AlgorithmIdentifier{MAC-ALGORITHM,
+                             {MACAlgorithms}}
+     -- the MAC AlgId (e.g., DES-MAC, Triple-DES-MAC, or HMAC
+  }
+
+  DigestAlgorithms DIGEST-ALGORITHM ::= {
+     mda-sha1, ...
+  }
+
+  MACAlgorithms MAC-ALGORITHM ::= {
+      -- The modules containing the ASN.1 for the DES and 3DES MAC
+      -- algorithms have not been updated at the time that this is
+      -- being published.  Users of this module should define the
+      -- appropriate MAC-ALGORITHM objects and uncomment the
+      -- following lines if they support these MAC algorithms.
+      -- maca-des-mac | maca-3des-mac --
+      maca-hMAC-SHA1,
+      ...
+  }
+
+  POPOPrivKey ::= CHOICE {
+      thisMessage       [0] BIT STRING,         -- Deprecated
+      -- possession is proven in this message (which contains
+      -- the private key itself (encrypted for the CA))
+      subsequentMessage [1] SubsequentMessage,
+      -- possession will be proven in a subsequent message
+      dhMAC             [2] BIT STRING,         -- Deprecated
+      agreeMAC          [3] PKMACValue,
+      encryptedKey      [4] EnvelopedData }
+      -- for keyAgreement (only), possession is proven in this message
+      -- (which contains a MAC (over the DER-encoded value of the
+      -- certReq parameter in CertReqMsg, which MUST include both
+      -- subject and publicKey) based on a key derived from the end
+      -- entity's private DH key and the CA's public DH key);
+SubsequentMessage ::= INTEGER {
+      encrCert (0),
+      -- requests that resulting certificate be encrypted for the
+      -- end entity (following which, POP will be proven in a
+      -- confirmation message)
+      challengeResp (1) }
+      -- requests that CA engage in challenge-response exchange with
+      -- end entity in order to prove private key possession
+
+  --
+  -- id-ct-encKeyWithID content type used as the content type for the
+  -- EnvelopedData in POPOPrivKey.
+  -- It contains both a private key and an identifier for key escrow
+  -- agents to check against recovery requestors.
+  --
+
+  ct-encKeyWithID CONTENT-TYPE ::=
+      { EncKeyWithID IDENTIFIED BY id-ct-encKeyWithID }
+
+  id-ct-encKeyWithID OBJECT IDENTIFIER ::= {id-ct 21}
+
+  EncKeyWithID ::= SEQUENCE {
+      privateKey           PrivateKeyInfo,
+      identifier CHOICE {
+          string             UTF8String,
+          generalName        GeneralName
+      } OPTIONAL
+  }
+
+  PrivateKeyInfo ::= SEQUENCE {
+     version                   INTEGER,
+     privateKeyAlgorithm       AlgorithmIdentifier{PUBLIC-KEY, {...}},
+     privateKey                OCTET STRING,
+               --  Structure of public key is in PUBLIC-KEY.&PrivateKey
+     attributes                [0] IMPLICIT Attributes OPTIONAL
+  }
+
+  Attributes ::= SET OF AttributeSet{{PrivateKeyAttributes}}
+  PrivateKeyAttributes ATTRIBUTE ::= {...}
+
+  --
+  -- 6.  Registration Controls in CRMF
+  --
+
+  id-regCtrl OBJECT IDENTIFIER ::= { id-pkip 1 }
+
+  RegControlSet ATTRIBUTE ::= {
+      regCtrl-regToken | regCtrl-authenticator |
+
+  regCtrl-pkiPublicationInfo | regCtrl-pkiArchiveOptions |
+      regCtrl-oldCertID | regCtrl-protocolEncrKey, ... }
+
+  --
+  --  6.1.  Registration Token Control
+  --
+
+  regCtrl-regToken ATTRIBUTE ::=
+      { TYPE RegToken IDENTIFIED BY id-regCtrl-regToken }
+
+  id-regCtrl-regToken OBJECT IDENTIFIER ::= { id-regCtrl 1 }
+
+  RegToken ::= UTF8String
+
+  --
+  --  6.2.  Authenticator Control
+  --
+
+  regCtrl-authenticator ATTRIBUTE ::=
+      { TYPE Authenticator IDENTIFIED BY id-regCtrl-authenticator }
+
+  id-regCtrl-authenticator OBJECT IDENTIFIER ::= { id-regCtrl 2 }
+
+  Authenticator ::= UTF8String
+
+  --
+  --  6.3.  Publication Information Control
+  --
+
+  regCtrl-pkiPublicationInfo ATTRIBUTE ::=
+      { TYPE PKIPublicationInfo IDENTIFIED BY
+          id-regCtrl-pkiPublicationInfo }
+
+  id-regCtrl-pkiPublicationInfo OBJECT IDENTIFIER ::= { id-regCtrl 3 }
+
+  PKIPublicationInfo ::= SEQUENCE {
+      action     INTEGER {
+                     dontPublish (0),
+                     pleasePublish (1) },
+      pubInfos  SEQUENCE SIZE (1..MAX) OF SinglePubInfo OPTIONAL }
+      -- pubInfos MUST NOT be present if action is "dontPublish"
+      -- (if action is "pleasePublish" and pubInfos is omitted,
+      -- "dontCare" is assumed)
+
+  SinglePubInfo ::= SEQUENCE {
+      pubMethod    INTEGER {
+          dontCare    (0),
+          x500        (1),
+	  web         (2),
+          ldap        (3) },
+      pubLocation  GeneralName OPTIONAL }
+
+  --
+  --  6.4.  Archive Options Control
+  --
+
+  regCtrl-pkiArchiveOptions ATTRIBUTE ::=
+      { TYPE PKIArchiveOptions IDENTIFIED BY
+          id-regCtrl-pkiArchiveOptions }
+
+  id-regCtrl-pkiArchiveOptions OBJECT IDENTIFIER ::= { id-regCtrl 4 }
+
+  PKIArchiveOptions ::= CHOICE {
+      encryptedPrivKey     [0] EncryptedKey,
+      -- the actual value of the private key
+      keyGenParameters     [1] KeyGenParameters,
+      -- parameters that allow the private key to be re-generated
+      archiveRemGenPrivKey [2] BOOLEAN }
+      -- set to TRUE if sender wishes receiver to archive the private
+      -- key of a key pair that the receiver generates in response to
+      -- this request; set to FALSE if no archive is desired.
+
+  EncryptedKey ::= CHOICE {
+      encryptedValue        EncryptedValue,   -- Deprecated
+      envelopedData     [0] EnvelopedData }
+      -- The encrypted private key MUST be placed in the envelopedData
+      -- encryptedContentInfo encryptedContent OCTET STRING.
+
+  --
+  --  We skipped doing the full constraints here since this structure
+  --      has been deprecated in favor of EnvelopedData
+  --
+
+  EncryptedValue ::= SEQUENCE {
+      intendedAlg   [0] AlgorithmIdentifier{ALGORITHM, {...}}  OPTIONAL,
+      -- the intended algorithm for which the value will be used
+      symmAlg       [1] AlgorithmIdentifier{ALGORITHM, {...}}  OPTIONAL,
+      -- the symmetric algorithm used to encrypt the value
+      encSymmKey    [2] BIT STRING           OPTIONAL,
+      -- the (encrypted) symmetric key used to encrypt the value
+      keyAlg        [3] AlgorithmIdentifier{ALGORITHM, {...}}  OPTIONAL,
+      -- algorithm used to encrypt the symmetric key
+      valueHint     [4] OCTET STRING         OPTIONAL,
+      -- a brief description or identifier of the encValue content
+      -- (may be meaningful only to the sending entity, and used only
+      -- if EncryptedValue might be re-examined by the sending entity
+-- in the future)
+      encValue       BIT STRING }
+      -- the encrypted value itself
+  -- When EncryptedValue is used to carry a private key (as opposed to
+  -- a certificate), implementations MUST support the encValue field
+  -- containing an encrypted PrivateKeyInfo as defined in [PKCS11],
+  -- section 12.11.  If encValue contains some other format/encoding
+  -- for the private key, the first octet of valueHint MAY be used
+  -- to indicate the format/encoding (but note that the possible values
+  -- of this octet are not specified at this time).  In all cases, the
+  -- intendedAlg field MUST be used to indicate at least the OID of
+  -- the intended algorithm of the private key, unless this information
+  -- is known a priori to both sender and receiver by some other means.
+
+  KeyGenParameters ::= OCTET STRING
+
+  --
+  --  6.5.  OldCert ID Control
+  --
+
+  regCtrl-oldCertID ATTRIBUTE ::=
+      { TYPE OldCertId IDENTIFIED BY id-regCtrl-oldCertID }
+
+  id-regCtrl-oldCertID  OBJECT IDENTIFIER ::= { id-regCtrl 5 }
+
+  OldCertId ::= CertId
+
+  CertId ::= SEQUENCE {
+      issuer           GeneralName,
+      serialNumber     INTEGER }
+
+  --
+  -- 6.6.  Protocol Encryption Key Control
+  --
+
+  regCtrl-protocolEncrKey ATTRIBUTE ::=
+      { TYPE ProtocolEncrKey IDENTIFIED BY id-regCtrl-protocolEncrKey }
+  id-regCtrl-protocolEncrKey    OBJECT IDENTIFIER ::= { id-regCtrl 6 }
+
+  ProtocolEncrKey ::= SubjectPublicKeyInfo
+
+  --
+  -- 7.  Registration Info in CRMF
+  --
+
+  id-regInfo OBJECT IDENTIFIER ::= { id-pkip 2 }
+
+  RegInfoSet ATTRIBUTE ::=
+  { regInfo-utf8Pairs | regInfo-certReq }
+
+  --
+  -- 7.1.  utf8Pairs RegInfo Control
+  --
+
+  regInfo-utf8Pairs ATTRIBUTE ::=
+      { TYPE UTF8Pairs IDENTIFIED BY id-regInfo-utf8Pairs }
+
+  id-regInfo-utf8Pairs    OBJECT IDENTIFIER ::= { id-regInfo 1 }
+  --with syntax
+  UTF8Pairs ::= UTF8String
+
+  --
+  --  7.2.  certReq RegInfo Control
+  --
+
+  regInfo-certReq ATTRIBUTE ::=
+      { TYPE CertReq IDENTIFIED BY id-regInfo-certReq }
+
+  id-regInfo-certReq       OBJECT IDENTIFIER ::= { id-regInfo 2 }
+  --with syntax
+  CertReq ::= CertRequest
+
+  END
+
+11.  ASN.1 Module for RFC 5055
+
+  SCVP-2009
+      { iso(1) identified-organization(3) dod(6) internet(1) security(5)
+      mechanisms(5) pkix(7) id-mod(0) id-mod-scvp-02(52) }
+  DEFINITIONS IMPLICIT TAGS ::=
+  BEGIN
+  IMPORTS
+
+  Extensions{}, EXTENSION, ATTRIBUTE
+  FROM PKIX-CommonTypes-2009
+      {iso(1) identified-organization(3) dod(6) internet(1) security(5)
+      mechanisms(5) pkix(7) id-mod(0) id-mod-pkixCommon-02(57) }
+
+  AlgorithmIdentifier{}, SIGNATURE-ALGORITHM, PUBLIC-KEY, KEY-AGREE,
+      DIGEST-ALGORITHM, KEY-DERIVATION, MAC-ALGORITHM
+  FROM AlgorithmInformation-2009
+      {iso(1) identified-organization(3) dod(6) internet(1) security(5)
+      mechanisms(5) pkix(7) id-mod(0)
+      id-mod-algorithmInformation-02(58)}
+
+  Certificate, CertificateList, CertificateSerialNumber,
+   SignatureAlgorithms, SubjectPublicKeyInfo
+  FROM PKIX1Explicit-2009
+      { iso(1) identified-organization(3) dod(6) internet(1) security(5)
+      mechanisms(5) pkix(7) id-mod(0) id-mod-pkix1-explicit-02(51) }
+
+  GeneralNames, GeneralName, KeyUsage, KeyPurposeId
+  FROM PKIX1Implicit-2009
+      { iso(1) identified-organization(3) dod(6) internet(1) security(5)
+      mechanisms(5) pkix(7) id-mod(0) id-mod-pkix1-implicit-02(59) }
+
+  AttributeCertificate
+  FROM PKIXAttributeCertificate-2009
+      { iso(1) identified-organization(3) dod(6) internet(1) security(5)
+      mechanisms(5) pkix(7) id-mod(0) id-mod-attribute-cert-02(47) }
+
+  OCSPResponse
+  FROM OCSP-2009
+      { iso(1) identified-organization(3) dod(6) internet(1) security(5)
+      mechanisms(5) pkix(7) id-mod(0) id-mod-ocsp-02(48) }
+
+  ContentInfo, CONTENT-TYPE
+  FROM CryptographicMessageSyntax-2009
+      { iso(1) member-body(2) us(840) rsadsi(113549) pkcs(1) pkcs-9(9)
+      smime(16) modules(0) id-mod-cms-2004-02(41) }
+
+  mda-sha1
+  FROM PKIXAlgs-2009
+      { iso(1) identified-organization(3) dod(6)
+      internet(1) security(5) mechanisms(5) pkix(7) id-mod(0)
+      id-mod-pkix1-algorithms2008-02(56) } ;
+
+  ContentTypes CONTENT-TYPE ::= {ct-scvp-certValRequest |
+      ct-scvp-certValResponse | ct-scvp-valPolRequest |
+      ct-scvp-valPolResponse, ... }
+
+  id-ct OBJECT IDENTIFIER ::=
+      { iso(1) member-body(2) us(840) rsadsi(113549) pkcs(1) pkcs9(9)
+      id-smime(16) 1 }
+
+  ct-scvp-certValRequest CONTENT-TYPE ::=
+      { CVRequest IDENTIFIED BY id-ct-scvp-certValRequest }
+
+  id-ct-scvp-certValRequest OBJECT IDENTIFIER ::= { id-ct 10 }
+
+  -- SCVP Certificate Validation Request
+
+  CVRequest ::= SEQUENCE {
+      cvRequestVersion           INTEGER DEFAULT 1,
+      query                      Query,
+      requestorRef           [0] GeneralNames OPTIONAL,
+      requestNonce           [1] OCTET STRING OPTIONAL,
+      requestorName          [2] GeneralName OPTIONAL,
+      responderName          [3] GeneralName OPTIONAL,
+      requestExtensions      [4] Extensions{{RequestExtensions}}
+                                     OPTIONAL,
+      signatureAlg           [5] AlgorithmIdentifier
+                                     {SIGNATURE-ALGORITHM,
+                                         {SignatureAlgorithms}}
+                                     OPTIONAL,
+      hashAlg                [6] OBJECT IDENTIFIER OPTIONAL,
+      requestorText          [7] UTF8String (SIZE (1..256)) OPTIONAL
+  }
+
+  -- Set of signature algorithms is coming from RFC 5280
+  -- SignatureAlgorithms SIGNATURE-ALGORITHM ::= {...}
+
+  -- Add supported request extensions here; all new items should
+  --      be added after the extension marker
+
+  RequestExtensions EXTENSION ::= {...}
+
+  Query ::= SEQUENCE {
+      queriedCerts             CertReferences,
+      checks                   CertChecks,
+      wantBack             [1] WantBack OPTIONAL,
+      validationPolicy         ValidationPolicy,
+      responseFlags            ResponseFlags OPTIONAL,
+      serverContextInfo    [2] OCTET STRING OPTIONAL,
+      validationTime       [3] GeneralizedTime OPTIONAL,
+      intermediateCerts    [4] CertBundle OPTIONAL,
+      revInfos             [5] RevocationInfos OPTIONAL,
+      producedAt           [6] GeneralizedTime OPTIONAL,
+      queryExtensions      [7] Extensions{{QueryExtensions}} OPTIONAL
+  }
+
+  -- Add supported query extensions here; all new items should be added
+  --      after the extension marker
+
+  QueryExtensions EXTENSION ::= {...}
+
+  CertReferences ::= CHOICE {
+      pkcRefs       [0] SEQUENCE SIZE (1..MAX) OF PKCReference,
+      acRefs        [1] SEQUENCE SIZE (1..MAX) OF ACReference
+  }
+
+  CertReference::= CHOICE {
+   pkc               PKCReference,
+      ac                ACReference
+  }
+
+  PKCReference ::= CHOICE {
+      cert          [0] Certificate,
+      pkcRef        [1] SCVPCertID
+  }
+
+  ACReference ::= CHOICE {
+      attrCert      [2] AttributeCertificate,
+      acRef         [3] SCVPCertID
+  }
+
+  HashAlgorithm ::= AlgorithmIdentifier{DIGEST-ALGORITHM,
+                        {mda-sha1, ...}}
+
+  SCVPCertID ::= SEQUENCE {
+     certHash        OCTET STRING,
+     issuerSerial    SCVPIssuerSerial,
+     hashAlgorithm   HashAlgorithm
+                         DEFAULT { algorithm mda-sha1.&id }
+  }
+
+  SCVPIssuerSerial ::= SEQUENCE {
+      issuer         GeneralNames,
+      serialNumber   CertificateSerialNumber
+  }
+
+  ValidationPolicy ::= SEQUENCE {
+      validationPolRef           ValidationPolRef,
+      validationAlg          [0] ValidationAlg OPTIONAL,
+      userPolicySet          [1] SEQUENCE SIZE (1..MAX) OF OBJECT
+                                IDENTIFIER OPTIONAL,
+      inhibitPolicyMapping   [2] BOOLEAN OPTIONAL,
+      requireExplicitPolicy  [3] BOOLEAN OPTIONAL,
+      inhibitAnyPolicy       [4] BOOLEAN OPTIONAL,
+      trustAnchors           [5] TrustAnchors OPTIONAL,
+      keyUsages              [6] SEQUENCE OF KeyUsage OPTIONAL,
+      extendedKeyUsages      [7] SEQUENCE OF KeyPurposeId OPTIONAL,
+      specifiedKeyUsages     [8] SEQUENCE OF KeyPurposeId OPTIONAL
+  }
+
+  CertChecks ::= SEQUENCE SIZE (1..MAX) OF
+      OBJECT IDENTIFIER (CertCheckSet | ACertCheckSet, ... )
+
+  WantBack ::= SEQUENCE SIZE (1..MAX) OF
+      WANT-BACK.&id ({AllWantBacks})
+POLICY ::= ATTRIBUTE
+
+  ValidationPolRefSet POLICY ::= {
+      svp-defaultValPolicy, ...
+  }
+
+  ValidationPolRef ::= SEQUENCE {
+     valPolId             POLICY.&id,
+     valPolParams         POLICY.&Type OPTIONAL
+  }
+
+  ValidationAlgSet POLICY ::= {
+          svp-basicValAlg, ...
+  }
+
+  ValidationAlg ::= SEQUENCE {
+      valAlgId               POLICY.&id,
+      parameters             POLICY.&Type OPTIONAL
+  }
+
+  NameValidationAlgSet POLICY ::= {
+      svp-nameValAlg, ...
+  }
+
+  NameValidationAlgParams ::= SEQUENCE {
+      nameCompAlgId          OBJECT IDENTIFIER (NameCompAlgSet, ... ),
+      validationNames        GeneralNames
+  }
+
+  TrustAnchors ::= SEQUENCE SIZE (1..MAX) OF PKCReference
+  KeyAgreePublicKey ::= SEQUENCE {
+      algorithm           AlgorithmIdentifier{KEY-AGREE,
+                              {SupportedKeyAgreePublicKeys}},
+      publicKey           BIT STRING,
+      macAlgorithm        AlgorithmIdentifier{MAC-ALGORITHM,
+                              {SupportedMACAlgorithms}},
+      kDF                 AlgorithmIdentifier{KEY-DERIVATION,
+                              {SupportedKeyDerivationFunctions}}
+                              OPTIONAL
+  }
+
+  SupportedKeyAgreePublicKeys KEY-AGREE ::= {...}
+  SupportedMACAlgorithms MAC-ALGORITHM ::= {...}
+  SupportedKeyDerivationFunctions KEY-DERIVATION ::= {...}
+
+  ResponseFlags ::= SEQUENCE {
+      fullRequestInResponse      [0] BOOLEAN DEFAULT FALSE,
+      responseValidationPolByRef [1] BOOLEAN DEFAULT TRUE,
+  protectResponse            [2] BOOLEAN DEFAULT TRUE,
+      cachedResponse             [3] BOOLEAN DEFAULT TRUE
+  }
+
+  CertBundle ::= SEQUENCE SIZE (1..MAX) OF Certificate
+
+  RevocationInfos ::= SEQUENCE SIZE (1..MAX) OF RevocationInfo
+
+  RevocationInfo ::= CHOICE {
+      crl                    [0] CertificateList,
+      delta-crl              [1] CertificateList,
+      ocsp                   [2] OCSPResponse,
+      other                  [3] OtherRevInfo
+  }
+
+  REV-INFO ::= TYPE-IDENTIFIER
+
+  OtherRevInfo ::= SEQUENCE {
+      riType                     REV-INFO.&id,
+      riValue                    REV-INFO.&Type
+  }
+
+  -- SCVP Certificate Validation Response
+
+  ct-scvp-certValResponse CONTENT-TYPE ::=
+      { CVResponse IDENTIFIED BY id-ct-scvp-certValResponse }
+
+  id-ct-scvp-certValResponse OBJECT IDENTIFIER ::= { id-ct 11 }
+
+  CVResponse ::= SEQUENCE {
+      cvResponseVersion          INTEGER,
+      serverConfigurationID      INTEGER,
+      producedAt                 GeneralizedTime,
+      responseStatus             ResponseStatus,
+      respValidationPolicy   [0] RespValidationPolicy OPTIONAL,
+      requestRef             [1] RequestReference OPTIONAL,
+      requestorRef           [2] GeneralNames OPTIONAL,
+      requestorName          [3] GeneralNames OPTIONAL,
+      replyObjects           [4] ReplyObjects OPTIONAL,
+      respNonce              [5] OCTET STRING OPTIONAL,
+      serverContextInfo      [6] OCTET STRING OPTIONAL,
+      cvResponseExtensions   [7] Extensions{{CVResponseExtensions}}
+                                     OPTIONAL,
+      requestorText          [8] UTF8String (SIZE (1..256)) OPTIONAL
+  }
+
+  --  This document defines no extensions
+  CVResponseExtensions EXTENSION ::= {...}
+  ResponseStatus ::= SEQUENCE {
+     statusCode               CVStatusCode DEFAULT  okay,
+     errorMessage             UTF8String OPTIONAL
+  }
+
+  CVStatusCode ::= ENUMERATED {
+     okay                               (0),
+     skipUnrecognizedItems              (1),
+     tooBusy                           (10),
+     invalidRequest                    (11),
+     internalError                     (12),
+     badStructure                      (20),
+     unsupportedVersion                (21),
+     abortUnrecognizedItems            (22),
+     unrecognizedSigKey                (23),
+     badSignatureOrMAC                 (24),
+     unableToDecode                    (25),
+     notAuthorized                     (26),
+     unsupportedChecks                 (27),
+     unsupportedWantBacks              (28),
+     unsupportedSignatureOrMAC         (29),
+     invalidSignatureOrMAC             (30),
+     protectedResponseUnsupported      (31),
+     unrecognizedResponderName         (32),
+     relayingLoop                      (40),
+     unrecognizedValPol                (50),
+     unrecognizedValAlg                (51),
+     fullRequestInResponseUnsupported  (52),
+     fullPolResponseUnsupported        (53),
+     inhibitPolicyMappingUnsupported   (54),
+     requireExplicitPolicyUnsupported  (55),
+     inhibitAnyPolicyUnsupported       (56),
+     validationTimeUnsupported         (57),
+     unrecognizedCritQueryExt          (63),
+     unrecognizedCritRequestExt        (64),
+     ...
+  }
+
+  RespValidationPolicy ::= ValidationPolicy
+
+  RequestReference ::= CHOICE {
+      requestHash   [0] HashValue, -- hash of CVRequest
+      fullRequest   [1] CVRequest }
+
+  HashValue ::= SEQUENCE {
+      algorithm         HashAlgorithm
+                            DEFAULT { algorithm mda-sha1.&id },
+      value             OCTET STRING }
+       ReplyObjects ::= SEQUENCE SIZE (1..MAX) OF CertReply
+
+  CertReply ::= SEQUENCE {
+      cert                       CertReference,
+      replyStatus                ReplyStatus DEFAULT success,
+      replyValTime               GeneralizedTime,
+      replyChecks                ReplyChecks,
+      replyWantBacks             ReplyWantBacks,
+      validationErrors       [0] SEQUENCE SIZE (1..MAX) OF
+          OBJECT IDENTIFIER ( BasicValidationErrorSet |
+                              NameValidationErrorSet,
+                              ... ) OPTIONAL,
+      nextUpdate             [1] GeneralizedTime OPTIONAL,
+      certReplyExtensions    [2] Extensions{{...}} OPTIONAL
+  }
+
+  ReplyStatus ::= ENUMERATED {
+      success                    (0),
+      malformedPKC               (1),
+      malformedAC                (2),
+      unavailableValidationTime  (3),
+      referenceCertHashFail      (4),
+      certPathConstructFail      (5),
+      certPathNotValid           (6),
+      certPathNotValidNow        (7),
+      wantBackUnsatisfied        (8)
+  }
+  ReplyChecks ::= SEQUENCE OF ReplyCheck
+
+  ReplyCheck ::= SEQUENCE {
+      check    OBJECT IDENTIFIER (CertCheckSet | ACertCheckSet, ... ),
+      status   INTEGER DEFAULT 0
+  }
+
+  ReplyWantBacks ::= SEQUENCE OF ReplyWantBack
+
+  ReplyWantBack::= SEQUENCE {
+      wb     WANT-BACK.&id({AllWantBacks}),
+      value  OCTET STRING
+                 (CONTAINING WANT-BACK.&Type({AllWantBacks}{@wb}))
+  }
+
+  WANT-BACK ::= TYPE-IDENTIFIER
+
+  AllWantBacks WANT-BACK ::= {
+      WantBackSet | ACertWantBackSet | AnyWantBackSet, ...
+  }
+  CertBundles ::= SEQUENCE SIZE (1..MAX) OF CertBundle
+
+  RevInfoWantBack ::= SEQUENCE {
+      revocationInfo             RevocationInfos,
+      extraCerts                 CertBundle OPTIONAL
+  }
+
+  SCVPResponses ::= SEQUENCE OF ContentInfo
+
+  -- SCVP Validation Policies Request
+
+  ct-scvp-valPolRequest CONTENT-TYPE ::=
+      { ValPolRequest IDENTIFIED BY id-ct-scvp-valPolRequest }
+
+  id-ct-scvp-valPolRequest OBJECT IDENTIFIER ::= { id-ct 12 }
+
+  ValPolRequest ::= SEQUENCE {
+      vpRequestVersion           INTEGER DEFAULT 1,
+      requestNonce               OCTET STRING
+  }
+
+  -- SCVP Validation Policies Response
+
+  ct-scvp-valPolResponse CONTENT-TYPE ::=
+      { ValPolResponse IDENTIFIED BY id-ct-scvp-valPolResponse }
+
+  id-ct-scvp-valPolResponse OBJECT IDENTIFIER ::= { id-ct 13 }
+  ValPolResponse ::= SEQUENCE {
+      vpResponseVersion       INTEGER,
+      maxCVRequestVersion     INTEGER,
+      maxVPRequestVersion     INTEGER,
+      serverConfigurationID   INTEGER,
+      thisUpdate              GeneralizedTime,
+      nextUpdate              GeneralizedTime OPTIONAL,
+      supportedChecks         CertChecks,
+      supportedWantBacks      WantBack,
+      validationPolicies      SEQUENCE OF OBJECT IDENTIFIER,
+      validationAlgs          SEQUENCE OF OBJECT IDENTIFIER,
+      authPolicies            SEQUENCE OF AuthPolicy,
+      responseTypes           ResponseTypes,
+      defaultPolicyValues     RespValidationPolicy,
+      revocationInfoTypes     RevocationInfoTypes,
+      signatureGeneration     SEQUENCE OF AlgorithmIdentifier
+                                  {SIGNATURE-ALGORITHM,
+                                      {SignatureAlgorithms}},
+      signatureVerification   SEQUENCE OF AlgorithmIdentifier
+                                  {SIGNATURE-ALGORITHM,
+                                      {SignatureAlgorithms}},
+
+ hashAlgorithms          SEQUENCE SIZE (1..MAX) OF
+                                 OBJECT IDENTIFIER,
+      serverPublicKeys        SEQUENCE OF KeyAgreePublicKey
+                                 OPTIONAL,
+      clockSkew               INTEGER DEFAULT 10,
+      requestNonce            OCTET STRING OPTIONAL
+  }
+
+  ResponseTypes  ::= ENUMERATED {
+      cached-only                (0),
+      non-cached-only            (1),
+      cached-and-non-cached      (2)
+  }
+
+  RevocationInfoTypes ::= BIT STRING {
+      fullCRLs                   (0),
+      deltaCRLs                  (1),
+      indirectCRLs               (2),
+      oCSPResponses              (3)
+  }
+
+  AuthPolicy ::= OBJECT IDENTIFIER
+
+  -- SCVP Check Identifiers
+
+  id-stc OBJECT IDENTIFIER ::=
+      { iso(1) identified-organization(3) dod(6) internet(1) security(5)
+      mechanisms(5) pkix(7) 17 }
+
+  CertCheckSet OBJECT IDENTIFIER ::= {
+      id-stc-build-pkc-path | id-stc-build-valid-pkc-path |
+      id-stc-build-status-checked-pkc-path, ... }
+
+  id-stc-build-pkc-path        OBJECT IDENTIFIER ::= { id-stc 1 }
+  id-stc-build-valid-pkc-path  OBJECT IDENTIFIER ::= { id-stc 2 }
+  id-stc-build-status-checked-pkc-path
+                              OBJECT IDENTIFIER ::= { id-stc 3 }
+
+  ACertCheckSet OBJECT IDENTIFIER ::= {
+      id-stc-build-aa-path | id-stc-build-valid-aa-path |
+      id-stc-build-status-checked-aa-path |
+      id-stc-status-check-ac-and-build-status-checked-aa-path
+  }
+
+  id-stc-build-aa-path         OBJECT IDENTIFIER ::= { id-stc 4 }
+  id-stc-build-valid-aa-path   OBJECT IDENTIFIER ::= { id-stc 5 }
+  id-stc-build-status-checked-aa-path
+                              OBJECT IDENTIFIER ::= { id-stc 6 }
+
+
+
+Hoffman & Schaad              Informational                    [Page 70]
+
+RFC 5912                   New ASN.1 for PKIX                  June 2010
+
+
+  id-stc-status-check-ac-and-build-status-checked-aa-path
+                              OBJECT IDENTIFIER ::= { id-stc 7 }
+
+  -- SCVP WantBack Identifiers
+
+  id-swb OBJECT IDENTIFIER ::=
+      { iso(1) identified-organization(3) dod(6) internet(1) security(5)
+      mechanisms(5) pkix(7) 18 }
+
+  WantBackSet WANT-BACK ::= {
+      swb-pkc-cert | swb-pkc-best-cert-path |
+      swb-pkc-revocation-info | swb-pkc-public-key-info |
+      swb-pkc-all-cert-paths | swb-pkc-ee-revocation-info |
+      swb-pkc-CAs-revocation-info
+  }
+
+  ACertWantBackSet WANT-BACK ::= {
+      swb-ac-cert | swb-aa-cert-path |
+      swb-aa-revocation-info | swb-ac-revocation-info
+  }
+
+  AnyWantBackSet WANT-BACK ::= { swb-relayed-responses }
+
+  swb-pkc-best-cert-path WANT-BACK ::=
+      { CertBundle IDENTIFIED BY id-swb-pkc-best-cert-path }
+  id-swb-pkc-best-cert-path       OBJECT IDENTIFIER ::= { id-swb 1 }
+  swb-pkc-revocation-info WANT-BACK ::=
+      { RevInfoWantBack IDENTIFIED BY id-swb-pkc-revocation-info }
+  id-swb-pkc-revocation-info      OBJECT IDENTIFIER ::= { id-swb 2 }
+
+  swb-pkc-public-key-info WANT-BACK ::=
+      { SubjectPublicKeyInfo IDENTIFIED BY id-swb-pkc-public-key-info }
+  id-swb-pkc-public-key-info      OBJECT IDENTIFIER ::= { id-swb 4 }
+
+  swb-aa-cert-path WANT-BACK ::=
+      {CertBundle IDENTIFIED BY id-swb-aa-cert-path }
+  id-swb-aa-cert-path             OBJECT IDENTIFIER ::= { id-swb 5 }
+
+  swb-aa-revocation-info WANT-BACK ::=
+      { RevInfoWantBack IDENTIFIED BY id-swb-aa-revocation-info }
+  id-swb-aa-revocation-info       OBJECT IDENTIFIER ::= { id-swb 6 }
+
+  swb-ac-revocation-info WANT-BACK ::=
+      { RevInfoWantBack IDENTIFIED BY id-swb-ac-revocation-info }
+  id-swb-ac-revocation-info       OBJECT IDENTIFIER ::= { id-swb 7 }
+
+  swb-relayed-responses WANT-BACK ::=
+      {SCVPResponses IDENTIFIED BY id-swb-relayed-responses }
+      id-swb-relayed-responses        OBJECT IDENTIFIER ::= { id-swb 9 }
+
+  swb-pkc-all-cert-paths WANT-BACK ::=
+      {CertBundles IDENTIFIED BY id-swb-pkc-all-cert-paths }
+  id-swb-pkc-all-cert-paths       OBJECT IDENTIFIER ::= { id-swb 12}
+
+  swb-pkc-ee-revocation-info WANT-BACK ::=
+      { RevInfoWantBack IDENTIFIED BY id-swb-pkc-ee-revocation-info }
+  id-swb-pkc-ee-revocation-info   OBJECT IDENTIFIER ::= { id-swb 13}
+
+  swb-pkc-CAs-revocation-info WANT-BACK ::=
+      { RevInfoWantBack IDENTIFIED BY id-swb-pkc-CAs-revocation-info }
+  id-swb-pkc-CAs-revocation-info  OBJECT IDENTIFIER ::= { id-swb 14}
+
+  swb-pkc-cert WANT-BACK ::=
+      { Certificate IDENTIFIED BY id-swb-pkc-cert }
+  id-swb-pkc-cert OBJECT IDENTIFIER ::= { id-swb 10}
+
+  swb-ac-cert WANT-BACK ::=
+      { AttributeCertificate IDENTIFIED BY id-swb-ac-cert }
+  id-swb-ac-cert OBJECT IDENTIFIER ::= { id-swb 11}
+
+  -- SCVP Validation Policy and Algorithm Identifiers
+
+  id-svp OBJECT IDENTIFIER ::=
+      { iso(1) identified-organization(3) dod(6) internet(1) security(5)
+      mechanisms(5) pkix(7) 19 }
+
+  svp-defaultValPolicy POLICY ::=
+      { IDENTIFIED BY id-svp-defaultValPolicy }
+
+  id-svp-defaultValPolicy OBJECT IDENTIFIER ::= { id-svp 1 }
+
+  -- SCVP Basic Validation Algorithm Identifier
+
+  svp-basicValAlg POLICY ::= {IDENTIFIED BY id-svp-basicValAlg }
+
+  id-svp-basicValAlg OBJECT IDENTIFIER ::= { id-svp 3 }
+
+  -- SCVP Basic Validation Algorithm Errors
+
+  id-bvae OBJECT IDENTIFIER ::= id-svp-basicValAlg
+
+  BasicValidationErrorSet OBJECT IDENTIFIER ::= {
+      id-bvae-expired | id-bvae-not-yet-valid |
+      id-bvae-wrongTrustAnchor | id-bvae-noValidCertPath |
+      id-bvae-revoked | id-bvae-invalidKeyPurpose |
+      id-bvae-invalidKeyUsage | id-bvae-invalidCertPolicy
+}
+
+  id-bvae-expired              OBJECT IDENTIFIER ::= { id-bvae 1 }
+  id-bvae-not-yet-valid        OBJECT IDENTIFIER ::= { id-bvae 2 }
+  id-bvae-wrongTrustAnchor     OBJECT IDENTIFIER ::= { id-bvae 3 }
+  id-bvae-noValidCertPath      OBJECT IDENTIFIER ::= { id-bvae 4 }
+  id-bvae-revoked              OBJECT IDENTIFIER ::= { id-bvae 5 }
+  id-bvae-invalidKeyPurpose    OBJECT IDENTIFIER ::= { id-bvae 9 }
+  id-bvae-invalidKeyUsage      OBJECT IDENTIFIER ::= { id-bvae 10 }
+  id-bvae-invalidCertPolicy    OBJECT IDENTIFIER ::= { id-bvae 11 }
+
+  -- SCVP Name Validation Algorithm Identifier
+
+  svp-nameValAlg POLICY ::=
+      {TYPE NameValidationAlgParams IDENTIFIED BY id-svp-nameValAlg }
+
+  id-svp-nameValAlg OBJECT IDENTIFIER ::= { id-svp 2 }
+
+  -- SCVP Name Validation Algorithm DN comparison algorithm
+
+  NameCompAlgSet OBJECT IDENTIFIER ::= {
+      id-nva-dnCompAlg
+  }
+
+  id-nva-dnCompAlg   OBJECT IDENTIFIER ::= { id-svp 4 }
+  -- SCVP Name Validation Algorithm Errors
+
+  id-nvae OBJECT IDENTIFIER ::= id-svp-nameValAlg
+
+  NameValidationErrorSet OBJECT IDENTIFIER ::= {
+      id-nvae-name-mismatch | id-nvae-no-name | id-nvae-unknown-alg |
+      id-nvae-bad-name | id-nvae-bad-name-type | id-nvae-mixed-names
+  }
+
+  id-nvae-name-mismatch   OBJECT IDENTIFIER ::= { id-nvae 1 }
+  id-nvae-no-name         OBJECT IDENTIFIER ::= { id-nvae 2 }
+  id-nvae-unknown-alg     OBJECT IDENTIFIER ::= { id-nvae 3 }
+  id-nvae-bad-name        OBJECT IDENTIFIER ::= { id-nvae 4 }
+  id-nvae-bad-name-type   OBJECT IDENTIFIER ::= { id-nvae 5 }
+  id-nvae-mixed-names     OBJECT IDENTIFIER ::= { id-nvae 6 }
+
+  -- SCVP Extended Key Usage Key Purpose Identifiers
+
+  id-kp OBJECT IDENTIFIER ::=
+      { iso(1) identified-organization(3) dod(6) internet(1) security(5)
+      mechanisms(5) pkix(7) 3 }
+
+  SvcpExtKeyUsageSet OBJECT IDENTIFIER ::= {
+     id-kp-scvpServer | id-kp-scvpClient
+  }
+
+  id-kp-scvpServer   OBJECT IDENTIFIER ::= { id-kp 15 }
+
+  id-kp-scvpClient   OBJECT IDENTIFIER ::= { id-kp 16 }
+
+  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 7ea04c48eb..33c7712a1d 100644
--- a/lib/public_key/include/public_key.hrl
+++ b/lib/public_key/include/public_key.hrl
@@ -548,10 +548,9 @@
          privateValueLength = asn1_NOVALUE
         }).
 
-%% PKCS-9
+%% From PKCS-9 (now part of CertificateEnrollmentMessageSyntax)
 -define('pkcs-9-at-extensionRequest', {1,2,840,113549,1,9,14}).
 
-
 %%% CRL and CRL Extensions Profile
 %%%
 
diff --git a/lib/public_key/src/public_key.app.src b/lib/public_key/src/public_key.app.src
index 570dd1d6e6..7705d7c9c7 100644
--- a/lib/public_key/src/public_key.app.src
+++ b/lib/public_key/src/public_key.app.src
@@ -27,6 +27,8 @@
               'PKIX1Explicit-2009',
               'PKIX1Implicit-2009',
               'PKIXAlgs-2009',
+              'PKIXCRMF-2009',
+              'EnrollmentMessageSyntax-2009',
               'PKIXAttributeCertificate-2009',
               'RFC5639',
               'Safecurves-pkix-18',
diff --git a/lib/public_key/src/public_key.erl b/lib/public_key/src/public_key.erl
index ad0920a1f5..798c0b03fd 100644
--- a/lib/public_key/src/public_key.erl
+++ b/lib/public_key/src/public_key.erl
@@ -563,6 +563,13 @@ der_decode('Dss-Sig-Value', Der) ->
 	error:{badmatch, {error, _}} = Error ->
 	    erlang:error(Error)
     end;
+%% Backwards compatibility
+der_decode('ExtensionRequest', Value) ->
+    der_decode('ExtensionReq', Value);
+%% Backwards compatibility
+der_decode('AttributeTypeAndValue', Der) ->
+    {ok, Decoded} = 'PKIX1Explicit-2009':decode('SingleAttribute', Der),
+    pubkey_cert_records:transform(Decoded, decode);
 der_decode(Asn1ExtType, Der) when Asn1ExtType == 'SubjectAltName';
                                   Asn1ExtType == 'IssuerAltName';
                                   Asn1ExtType == 'ExtKeyUsage';
@@ -605,6 +612,8 @@ get_asn1_module('CertificateList') -> 'PKIX1Explicit-2009';
 get_asn1_module('TBSCertList') -> 'PKIX1Explicit-2009';
 get_asn1_module('Name') -> 'PKIX1Explicit-2009';
 get_asn1_module('Validity') -> 'PKIX1Explicit-2009';
+get_asn1_module('X520CommonName') -> 'PKIX1Explicit-2009';
+get_asn1_module('ExtensionReq') -> 'EnrollmentMessageSyntax-2009';
 get_asn1_module('RSAPublicKey') -> 'PKIXAlgs-2009';
 get_asn1_module('DSA-Params') -> 'PKIXAlgs-2009';
 get_asn1_module('ECParameters') -> 'PKIXAlgs-2009';
@@ -815,6 +824,14 @@ der_encode('Dss-Sig-Value', Entity) ->
 	error:{badmatch, {error, _}} = Error ->
 	    erlang:error(Error)
     end;
+%% Backwards compatibility
+der_encode('ExtensionRequest', Value) ->
+    der_encode('ExtensionReq', Value);
+%% Backwards compatibility
+der_encode('AttributeTypeAndValue', Value) ->
+    Term = pubkey_cert_records:transform(Value, encode),
+    {ok, Encoded} = 'PKIX1Explicit-2009':encode('SingleAttribute', Term),
+    Encoded;
 der_encode(Asn1ExtType, Value) when Asn1ExtType == 'SubjectAltName';
                                     Asn1ExtType == 'IssuerAltName';
                                     Asn1ExtType == 'ExtKeyUsage';
diff --git a/lib/public_key/test/public_key_SUITE.erl b/lib/public_key/test/public_key_SUITE.erl
index abae147d7a..fc46b0f91f 100644
--- a/lib/public_key/test/public_key_SUITE.erl
+++ b/lib/public_key/test/public_key_SUITE.erl
@@ -107,6 +107,8 @@
          pkix_ext_key_usage/1,
          pkix_ext_key_usage_any/0,
          pkix_ext_key_usage_any/1,
+         pkix_extensionreq/0,
+         pkix_extensionreq/1,
          pkix_path_validation_bad_date/0,
          pkix_path_validation_bad_date/1,
          pkix_verify_hostname_cn/1,
@@ -201,6 +203,7 @@ all() ->
      pkix_test_data_all_default,
      pkix_test_data,
      pkix_is_issuer,
+     pkix_extensionreq,
      short_cert_issuer_hash, 
      short_crl_issuer_hash,
      cacerts_load,
@@ -1569,6 +1572,18 @@ pkix_is_issuer(Config) when is_list(Config) ->
               [{'AttributeTypeAndValue',{2,5,4,3},{utf8String,<<"INTERMEDIATE">>}}]]},
     true = pubkey_cert:is_issuer(Upper, Lower).
 
+%%--------------------------------------------------------------------
+pkix_extensionreq() ->
+    [{doc, "Basic test that asn1 for EnrollmentMessageSyntax is supported"}].
+
+pkix_extensionreq(Config) when is_list(Config) ->
+    Expected = <<48,0>>,
+    Expected = public_key:der_encode('ExtensionReq', []),
+    [] = public_key:der_decode('ExtensionReq', Expected),
+    %% Backwards compatibility
+    Expected = public_key:der_encode('ExtensionRequest', []),
+    [] = public_key:der_decode('ExtensionRequest', Expected).
+
 %%--------------------------------------------------------------------
 short_cert_issuer_hash() ->
     [{doc, "Test OpenSSL-style hash for certificate issuer"}].
-- 
2.43.0

openSUSE Build Service is sponsored by