{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.CertificateManager.Types.CertificateDetail
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.CertificateManager.Types.CertificateDetail where

import Amazonka.CertificateManager.Types.CertificateOptions
import Amazonka.CertificateManager.Types.CertificateStatus
import Amazonka.CertificateManager.Types.CertificateType
import Amazonka.CertificateManager.Types.DomainValidation
import Amazonka.CertificateManager.Types.ExtendedKeyUsage
import Amazonka.CertificateManager.Types.FailureReason
import Amazonka.CertificateManager.Types.KeyAlgorithm
import Amazonka.CertificateManager.Types.KeyUsage
import Amazonka.CertificateManager.Types.RenewalEligibility
import Amazonka.CertificateManager.Types.RenewalSummary
import Amazonka.CertificateManager.Types.RevocationReason
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude

-- | Contains metadata about an ACM certificate. This structure is returned
-- in the response to a DescribeCertificate request.
--
-- /See:/ 'newCertificateDetail' smart constructor.
data CertificateDetail = CertificateDetail'
  { -- | The Amazon Resource Name (ARN) of the certificate. For more information
    -- about ARNs, see
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
    -- in the /Amazon Web Services General Reference/.
    CertificateDetail -> Maybe Text
certificateArn :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the private certificate authority (CA)
    -- that issued the certificate. This has the following format:
    --
    -- @arn:aws:acm-pca:region:account:certificate-authority\/12345678-1234-1234-1234-123456789012@
    CertificateDetail -> Maybe Text
certificateAuthorityArn :: Prelude.Maybe Prelude.Text,
    -- | The time at which the certificate was requested.
    CertificateDetail -> Maybe POSIX
createdAt :: Prelude.Maybe Data.POSIX,
    -- | The fully qualified domain name for the certificate, such as
    -- www.example.com or example.com.
    CertificateDetail -> Maybe Text
domainName :: Prelude.Maybe Prelude.Text,
    -- | Contains information about the initial validation of each domain name
    -- that occurs as a result of the RequestCertificate request. This field
    -- exists only when the certificate type is @AMAZON_ISSUED@.
    CertificateDetail -> Maybe (NonEmpty DomainValidation)
domainValidationOptions :: Prelude.Maybe (Prelude.NonEmpty DomainValidation),
    -- | Contains a list of Extended Key Usage X.509 v3 extension objects. Each
    -- object specifies a purpose for which the certificate public key can be
    -- used and consists of a name and an object identifier (OID).
    CertificateDetail -> Maybe [ExtendedKeyUsage]
extendedKeyUsages :: Prelude.Maybe [ExtendedKeyUsage],
    -- | The reason the certificate request failed. This value exists only when
    -- the certificate status is @FAILED@. For more information, see
    -- <https://docs.aws.amazon.com/acm/latest/userguide/troubleshooting.html#troubleshooting-failed Certificate Request Failed>
    -- in the /Certificate Manager User Guide/.
    CertificateDetail -> Maybe FailureReason
failureReason :: Prelude.Maybe FailureReason,
    -- | The date and time when the certificate was imported. This value exists
    -- only when the certificate type is @IMPORTED@.
    CertificateDetail -> Maybe POSIX
importedAt :: Prelude.Maybe Data.POSIX,
    -- | A list of ARNs for the Amazon Web Services resources that are using the
    -- certificate. A certificate can be used by multiple Amazon Web Services
    -- resources.
    CertificateDetail -> Maybe [Text]
inUseBy :: Prelude.Maybe [Prelude.Text],
    -- | The time at which the certificate was issued. This value exists only
    -- when the certificate type is @AMAZON_ISSUED@.
    CertificateDetail -> Maybe POSIX
issuedAt :: Prelude.Maybe Data.POSIX,
    -- | The name of the certificate authority that issued and signed the
    -- certificate.
    CertificateDetail -> Maybe Text
issuer :: Prelude.Maybe Prelude.Text,
    -- | The algorithm that was used to generate the public-private key pair.
    CertificateDetail -> Maybe KeyAlgorithm
keyAlgorithm :: Prelude.Maybe KeyAlgorithm,
    -- | A list of Key Usage X.509 v3 extension objects. Each object is a string
    -- value that identifies the purpose of the public key contained in the
    -- certificate. Possible extension values include DIGITAL_SIGNATURE,
    -- KEY_ENCHIPHERMENT, NON_REPUDIATION, and more.
    CertificateDetail -> Maybe [KeyUsage]
keyUsages :: Prelude.Maybe [KeyUsage],
    -- | The time after which the certificate is not valid.
    CertificateDetail -> Maybe POSIX
notAfter :: Prelude.Maybe Data.POSIX,
    -- | The time before which the certificate is not valid.
    CertificateDetail -> Maybe POSIX
notBefore :: Prelude.Maybe Data.POSIX,
    -- | Value that specifies whether to add the certificate to a transparency
    -- log. Certificate transparency makes it possible to detect SSL
    -- certificates that have been mistakenly or maliciously issued. A browser
    -- might respond to certificate that has not been logged by showing an
    -- error message. The logs are cryptographically secure.
    CertificateDetail -> Maybe CertificateOptions
options :: Prelude.Maybe CertificateOptions,
    -- | Specifies whether the certificate is eligible for renewal. At this time,
    -- only exported private certificates can be renewed with the
    -- RenewCertificate command.
    CertificateDetail -> Maybe RenewalEligibility
renewalEligibility :: Prelude.Maybe RenewalEligibility,
    -- | Contains information about the status of ACM\'s
    -- <https://docs.aws.amazon.com/acm/latest/userguide/acm-renewal.html managed renewal>
    -- for the certificate. This field exists only when the certificate type is
    -- @AMAZON_ISSUED@.
    CertificateDetail -> Maybe RenewalSummary
renewalSummary :: Prelude.Maybe RenewalSummary,
    -- | The reason the certificate was revoked. This value exists only when the
    -- certificate status is @REVOKED@.
    CertificateDetail -> Maybe RevocationReason
revocationReason :: Prelude.Maybe RevocationReason,
    -- | The time at which the certificate was revoked. This value exists only
    -- when the certificate status is @REVOKED@.
    CertificateDetail -> Maybe POSIX
revokedAt :: Prelude.Maybe Data.POSIX,
    -- | The serial number of the certificate.
    CertificateDetail -> Maybe Text
serial :: Prelude.Maybe Prelude.Text,
    -- | The algorithm that was used to sign the certificate.
    CertificateDetail -> Maybe Text
signatureAlgorithm :: Prelude.Maybe Prelude.Text,
    -- | The status of the certificate.
    --
    -- A certificate enters status PENDING_VALIDATION upon being requested,
    -- unless it fails for any of the reasons given in the troubleshooting
    -- topic
    -- <https://docs.aws.amazon.com/acm/latest/userguide/troubleshooting-failed.html Certificate request fails>.
    -- ACM makes repeated attempts to validate a certificate for 72 hours and
    -- then times out. If a certificate shows status FAILED or
    -- VALIDATION_TIMED_OUT, delete the request, correct the issue with
    -- <https://docs.aws.amazon.com/acm/latest/userguide/dns-validation.html DNS validation>
    -- or
    -- <https://docs.aws.amazon.com/acm/latest/userguide/email-validation.html Email validation>,
    -- and try again. If validation succeeds, the certificate enters status
    -- ISSUED.
    CertificateDetail -> Maybe CertificateStatus
status :: Prelude.Maybe CertificateStatus,
    -- | The name of the entity that is associated with the public key contained
    -- in the certificate.
    CertificateDetail -> Maybe Text
subject :: Prelude.Maybe Prelude.Text,
    -- | One or more domain names (subject alternative names) included in the
    -- certificate. This list contains the domain names that are bound to the
    -- public key that is contained in the certificate. The subject alternative
    -- names include the canonical domain name (CN) of the certificate and
    -- additional domain names that can be used to connect to the website.
    CertificateDetail -> Maybe (NonEmpty Text)
subjectAlternativeNames :: Prelude.Maybe (Prelude.NonEmpty Prelude.Text),
    -- | The source of the certificate. For certificates provided by ACM, this
    -- value is @AMAZON_ISSUED@. For certificates that you imported with
    -- ImportCertificate, this value is @IMPORTED@. ACM does not provide
    -- <https://docs.aws.amazon.com/acm/latest/userguide/acm-renewal.html managed renewal>
    -- for imported certificates. For more information about the differences
    -- between certificates that you import and those that ACM provides, see
    -- <https://docs.aws.amazon.com/acm/latest/userguide/import-certificate.html Importing Certificates>
    -- in the /Certificate Manager User Guide/.
    CertificateDetail -> Maybe CertificateType
type' :: Prelude.Maybe CertificateType
  }
  deriving (CertificateDetail -> CertificateDetail -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CertificateDetail -> CertificateDetail -> Bool
$c/= :: CertificateDetail -> CertificateDetail -> Bool
== :: CertificateDetail -> CertificateDetail -> Bool
$c== :: CertificateDetail -> CertificateDetail -> Bool
Prelude.Eq, ReadPrec [CertificateDetail]
ReadPrec CertificateDetail
Int -> ReadS CertificateDetail
ReadS [CertificateDetail]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CertificateDetail]
$creadListPrec :: ReadPrec [CertificateDetail]
readPrec :: ReadPrec CertificateDetail
$creadPrec :: ReadPrec CertificateDetail
readList :: ReadS [CertificateDetail]
$creadList :: ReadS [CertificateDetail]
readsPrec :: Int -> ReadS CertificateDetail
$creadsPrec :: Int -> ReadS CertificateDetail
Prelude.Read, Int -> CertificateDetail -> ShowS
[CertificateDetail] -> ShowS
CertificateDetail -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CertificateDetail] -> ShowS
$cshowList :: [CertificateDetail] -> ShowS
show :: CertificateDetail -> String
$cshow :: CertificateDetail -> String
showsPrec :: Int -> CertificateDetail -> ShowS
$cshowsPrec :: Int -> CertificateDetail -> ShowS
Prelude.Show, forall x. Rep CertificateDetail x -> CertificateDetail
forall x. CertificateDetail -> Rep CertificateDetail x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CertificateDetail x -> CertificateDetail
$cfrom :: forall x. CertificateDetail -> Rep CertificateDetail x
Prelude.Generic)

-- |
-- Create a value of 'CertificateDetail' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'certificateArn', 'certificateDetail_certificateArn' - The Amazon Resource Name (ARN) of the certificate. For more information
-- about ARNs, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
-- in the /Amazon Web Services General Reference/.
--
-- 'certificateAuthorityArn', 'certificateDetail_certificateAuthorityArn' - The Amazon Resource Name (ARN) of the private certificate authority (CA)
-- that issued the certificate. This has the following format:
--
-- @arn:aws:acm-pca:region:account:certificate-authority\/12345678-1234-1234-1234-123456789012@
--
-- 'createdAt', 'certificateDetail_createdAt' - The time at which the certificate was requested.
--
-- 'domainName', 'certificateDetail_domainName' - The fully qualified domain name for the certificate, such as
-- www.example.com or example.com.
--
-- 'domainValidationOptions', 'certificateDetail_domainValidationOptions' - Contains information about the initial validation of each domain name
-- that occurs as a result of the RequestCertificate request. This field
-- exists only when the certificate type is @AMAZON_ISSUED@.
--
-- 'extendedKeyUsages', 'certificateDetail_extendedKeyUsages' - Contains a list of Extended Key Usage X.509 v3 extension objects. Each
-- object specifies a purpose for which the certificate public key can be
-- used and consists of a name and an object identifier (OID).
--
-- 'failureReason', 'certificateDetail_failureReason' - The reason the certificate request failed. This value exists only when
-- the certificate status is @FAILED@. For more information, see
-- <https://docs.aws.amazon.com/acm/latest/userguide/troubleshooting.html#troubleshooting-failed Certificate Request Failed>
-- in the /Certificate Manager User Guide/.
--
-- 'importedAt', 'certificateDetail_importedAt' - The date and time when the certificate was imported. This value exists
-- only when the certificate type is @IMPORTED@.
--
-- 'inUseBy', 'certificateDetail_inUseBy' - A list of ARNs for the Amazon Web Services resources that are using the
-- certificate. A certificate can be used by multiple Amazon Web Services
-- resources.
--
-- 'issuedAt', 'certificateDetail_issuedAt' - The time at which the certificate was issued. This value exists only
-- when the certificate type is @AMAZON_ISSUED@.
--
-- 'issuer', 'certificateDetail_issuer' - The name of the certificate authority that issued and signed the
-- certificate.
--
-- 'keyAlgorithm', 'certificateDetail_keyAlgorithm' - The algorithm that was used to generate the public-private key pair.
--
-- 'keyUsages', 'certificateDetail_keyUsages' - A list of Key Usage X.509 v3 extension objects. Each object is a string
-- value that identifies the purpose of the public key contained in the
-- certificate. Possible extension values include DIGITAL_SIGNATURE,
-- KEY_ENCHIPHERMENT, NON_REPUDIATION, and more.
--
-- 'notAfter', 'certificateDetail_notAfter' - The time after which the certificate is not valid.
--
-- 'notBefore', 'certificateDetail_notBefore' - The time before which the certificate is not valid.
--
-- 'options', 'certificateDetail_options' - Value that specifies whether to add the certificate to a transparency
-- log. Certificate transparency makes it possible to detect SSL
-- certificates that have been mistakenly or maliciously issued. A browser
-- might respond to certificate that has not been logged by showing an
-- error message. The logs are cryptographically secure.
--
-- 'renewalEligibility', 'certificateDetail_renewalEligibility' - Specifies whether the certificate is eligible for renewal. At this time,
-- only exported private certificates can be renewed with the
-- RenewCertificate command.
--
-- 'renewalSummary', 'certificateDetail_renewalSummary' - Contains information about the status of ACM\'s
-- <https://docs.aws.amazon.com/acm/latest/userguide/acm-renewal.html managed renewal>
-- for the certificate. This field exists only when the certificate type is
-- @AMAZON_ISSUED@.
--
-- 'revocationReason', 'certificateDetail_revocationReason' - The reason the certificate was revoked. This value exists only when the
-- certificate status is @REVOKED@.
--
-- 'revokedAt', 'certificateDetail_revokedAt' - The time at which the certificate was revoked. This value exists only
-- when the certificate status is @REVOKED@.
--
-- 'serial', 'certificateDetail_serial' - The serial number of the certificate.
--
-- 'signatureAlgorithm', 'certificateDetail_signatureAlgorithm' - The algorithm that was used to sign the certificate.
--
-- 'status', 'certificateDetail_status' - The status of the certificate.
--
-- A certificate enters status PENDING_VALIDATION upon being requested,
-- unless it fails for any of the reasons given in the troubleshooting
-- topic
-- <https://docs.aws.amazon.com/acm/latest/userguide/troubleshooting-failed.html Certificate request fails>.
-- ACM makes repeated attempts to validate a certificate for 72 hours and
-- then times out. If a certificate shows status FAILED or
-- VALIDATION_TIMED_OUT, delete the request, correct the issue with
-- <https://docs.aws.amazon.com/acm/latest/userguide/dns-validation.html DNS validation>
-- or
-- <https://docs.aws.amazon.com/acm/latest/userguide/email-validation.html Email validation>,
-- and try again. If validation succeeds, the certificate enters status
-- ISSUED.
--
-- 'subject', 'certificateDetail_subject' - The name of the entity that is associated with the public key contained
-- in the certificate.
--
-- 'subjectAlternativeNames', 'certificateDetail_subjectAlternativeNames' - One or more domain names (subject alternative names) included in the
-- certificate. This list contains the domain names that are bound to the
-- public key that is contained in the certificate. The subject alternative
-- names include the canonical domain name (CN) of the certificate and
-- additional domain names that can be used to connect to the website.
--
-- 'type'', 'certificateDetail_type' - The source of the certificate. For certificates provided by ACM, this
-- value is @AMAZON_ISSUED@. For certificates that you imported with
-- ImportCertificate, this value is @IMPORTED@. ACM does not provide
-- <https://docs.aws.amazon.com/acm/latest/userguide/acm-renewal.html managed renewal>
-- for imported certificates. For more information about the differences
-- between certificates that you import and those that ACM provides, see
-- <https://docs.aws.amazon.com/acm/latest/userguide/import-certificate.html Importing Certificates>
-- in the /Certificate Manager User Guide/.
newCertificateDetail ::
  CertificateDetail
newCertificateDetail :: CertificateDetail
newCertificateDetail =
  CertificateDetail'
    { $sel:certificateArn:CertificateDetail' :: Maybe Text
certificateArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:certificateAuthorityArn:CertificateDetail' :: Maybe Text
certificateAuthorityArn = forall a. Maybe a
Prelude.Nothing,
      $sel:createdAt:CertificateDetail' :: Maybe POSIX
createdAt = forall a. Maybe a
Prelude.Nothing,
      $sel:domainName:CertificateDetail' :: Maybe Text
domainName = forall a. Maybe a
Prelude.Nothing,
      $sel:domainValidationOptions:CertificateDetail' :: Maybe (NonEmpty DomainValidation)
domainValidationOptions = forall a. Maybe a
Prelude.Nothing,
      $sel:extendedKeyUsages:CertificateDetail' :: Maybe [ExtendedKeyUsage]
extendedKeyUsages = forall a. Maybe a
Prelude.Nothing,
      $sel:failureReason:CertificateDetail' :: Maybe FailureReason
failureReason = forall a. Maybe a
Prelude.Nothing,
      $sel:importedAt:CertificateDetail' :: Maybe POSIX
importedAt = forall a. Maybe a
Prelude.Nothing,
      $sel:inUseBy:CertificateDetail' :: Maybe [Text]
inUseBy = forall a. Maybe a
Prelude.Nothing,
      $sel:issuedAt:CertificateDetail' :: Maybe POSIX
issuedAt = forall a. Maybe a
Prelude.Nothing,
      $sel:issuer:CertificateDetail' :: Maybe Text
issuer = forall a. Maybe a
Prelude.Nothing,
      $sel:keyAlgorithm:CertificateDetail' :: Maybe KeyAlgorithm
keyAlgorithm = forall a. Maybe a
Prelude.Nothing,
      $sel:keyUsages:CertificateDetail' :: Maybe [KeyUsage]
keyUsages = forall a. Maybe a
Prelude.Nothing,
      $sel:notAfter:CertificateDetail' :: Maybe POSIX
notAfter = forall a. Maybe a
Prelude.Nothing,
      $sel:notBefore:CertificateDetail' :: Maybe POSIX
notBefore = forall a. Maybe a
Prelude.Nothing,
      $sel:options:CertificateDetail' :: Maybe CertificateOptions
options = forall a. Maybe a
Prelude.Nothing,
      $sel:renewalEligibility:CertificateDetail' :: Maybe RenewalEligibility
renewalEligibility = forall a. Maybe a
Prelude.Nothing,
      $sel:renewalSummary:CertificateDetail' :: Maybe RenewalSummary
renewalSummary = forall a. Maybe a
Prelude.Nothing,
      $sel:revocationReason:CertificateDetail' :: Maybe RevocationReason
revocationReason = forall a. Maybe a
Prelude.Nothing,
      $sel:revokedAt:CertificateDetail' :: Maybe POSIX
revokedAt = forall a. Maybe a
Prelude.Nothing,
      $sel:serial:CertificateDetail' :: Maybe Text
serial = forall a. Maybe a
Prelude.Nothing,
      $sel:signatureAlgorithm:CertificateDetail' :: Maybe Text
signatureAlgorithm = forall a. Maybe a
Prelude.Nothing,
      $sel:status:CertificateDetail' :: Maybe CertificateStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:subject:CertificateDetail' :: Maybe Text
subject = forall a. Maybe a
Prelude.Nothing,
      $sel:subjectAlternativeNames:CertificateDetail' :: Maybe (NonEmpty Text)
subjectAlternativeNames = forall a. Maybe a
Prelude.Nothing,
      $sel:type':CertificateDetail' :: Maybe CertificateType
type' = forall a. Maybe a
Prelude.Nothing
    }

-- | The Amazon Resource Name (ARN) of the certificate. For more information
-- about ARNs, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
-- in the /Amazon Web Services General Reference/.
certificateDetail_certificateArn :: Lens.Lens' CertificateDetail (Prelude.Maybe Prelude.Text)
certificateDetail_certificateArn :: Lens' CertificateDetail (Maybe Text)
certificateDetail_certificateArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CertificateDetail' {Maybe Text
certificateArn :: Maybe Text
$sel:certificateArn:CertificateDetail' :: CertificateDetail -> Maybe Text
certificateArn} -> Maybe Text
certificateArn) (\s :: CertificateDetail
s@CertificateDetail' {} Maybe Text
a -> CertificateDetail
s {$sel:certificateArn:CertificateDetail' :: Maybe Text
certificateArn = Maybe Text
a} :: CertificateDetail)

-- | The Amazon Resource Name (ARN) of the private certificate authority (CA)
-- that issued the certificate. This has the following format:
--
-- @arn:aws:acm-pca:region:account:certificate-authority\/12345678-1234-1234-1234-123456789012@
certificateDetail_certificateAuthorityArn :: Lens.Lens' CertificateDetail (Prelude.Maybe Prelude.Text)
certificateDetail_certificateAuthorityArn :: Lens' CertificateDetail (Maybe Text)
certificateDetail_certificateAuthorityArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CertificateDetail' {Maybe Text
certificateAuthorityArn :: Maybe Text
$sel:certificateAuthorityArn:CertificateDetail' :: CertificateDetail -> Maybe Text
certificateAuthorityArn} -> Maybe Text
certificateAuthorityArn) (\s :: CertificateDetail
s@CertificateDetail' {} Maybe Text
a -> CertificateDetail
s {$sel:certificateAuthorityArn:CertificateDetail' :: Maybe Text
certificateAuthorityArn = Maybe Text
a} :: CertificateDetail)

-- | The time at which the certificate was requested.
certificateDetail_createdAt :: Lens.Lens' CertificateDetail (Prelude.Maybe Prelude.UTCTime)
certificateDetail_createdAt :: Lens' CertificateDetail (Maybe UTCTime)
certificateDetail_createdAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CertificateDetail' {Maybe POSIX
createdAt :: Maybe POSIX
$sel:createdAt:CertificateDetail' :: CertificateDetail -> Maybe POSIX
createdAt} -> Maybe POSIX
createdAt) (\s :: CertificateDetail
s@CertificateDetail' {} Maybe POSIX
a -> CertificateDetail
s {$sel:createdAt:CertificateDetail' :: Maybe POSIX
createdAt = Maybe POSIX
a} :: CertificateDetail) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The fully qualified domain name for the certificate, such as
-- www.example.com or example.com.
certificateDetail_domainName :: Lens.Lens' CertificateDetail (Prelude.Maybe Prelude.Text)
certificateDetail_domainName :: Lens' CertificateDetail (Maybe Text)
certificateDetail_domainName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CertificateDetail' {Maybe Text
domainName :: Maybe Text
$sel:domainName:CertificateDetail' :: CertificateDetail -> Maybe Text
domainName} -> Maybe Text
domainName) (\s :: CertificateDetail
s@CertificateDetail' {} Maybe Text
a -> CertificateDetail
s {$sel:domainName:CertificateDetail' :: Maybe Text
domainName = Maybe Text
a} :: CertificateDetail)

-- | Contains information about the initial validation of each domain name
-- that occurs as a result of the RequestCertificate request. This field
-- exists only when the certificate type is @AMAZON_ISSUED@.
certificateDetail_domainValidationOptions :: Lens.Lens' CertificateDetail (Prelude.Maybe (Prelude.NonEmpty DomainValidation))
certificateDetail_domainValidationOptions :: Lens' CertificateDetail (Maybe (NonEmpty DomainValidation))
certificateDetail_domainValidationOptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CertificateDetail' {Maybe (NonEmpty DomainValidation)
domainValidationOptions :: Maybe (NonEmpty DomainValidation)
$sel:domainValidationOptions:CertificateDetail' :: CertificateDetail -> Maybe (NonEmpty DomainValidation)
domainValidationOptions} -> Maybe (NonEmpty DomainValidation)
domainValidationOptions) (\s :: CertificateDetail
s@CertificateDetail' {} Maybe (NonEmpty DomainValidation)
a -> CertificateDetail
s {$sel:domainValidationOptions:CertificateDetail' :: Maybe (NonEmpty DomainValidation)
domainValidationOptions = Maybe (NonEmpty DomainValidation)
a} :: CertificateDetail) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | Contains a list of Extended Key Usage X.509 v3 extension objects. Each
-- object specifies a purpose for which the certificate public key can be
-- used and consists of a name and an object identifier (OID).
certificateDetail_extendedKeyUsages :: Lens.Lens' CertificateDetail (Prelude.Maybe [ExtendedKeyUsage])
certificateDetail_extendedKeyUsages :: Lens' CertificateDetail (Maybe [ExtendedKeyUsage])
certificateDetail_extendedKeyUsages = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CertificateDetail' {Maybe [ExtendedKeyUsage]
extendedKeyUsages :: Maybe [ExtendedKeyUsage]
$sel:extendedKeyUsages:CertificateDetail' :: CertificateDetail -> Maybe [ExtendedKeyUsage]
extendedKeyUsages} -> Maybe [ExtendedKeyUsage]
extendedKeyUsages) (\s :: CertificateDetail
s@CertificateDetail' {} Maybe [ExtendedKeyUsage]
a -> CertificateDetail
s {$sel:extendedKeyUsages:CertificateDetail' :: Maybe [ExtendedKeyUsage]
extendedKeyUsages = Maybe [ExtendedKeyUsage]
a} :: CertificateDetail) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The reason the certificate request failed. This value exists only when
-- the certificate status is @FAILED@. For more information, see
-- <https://docs.aws.amazon.com/acm/latest/userguide/troubleshooting.html#troubleshooting-failed Certificate Request Failed>
-- in the /Certificate Manager User Guide/.
certificateDetail_failureReason :: Lens.Lens' CertificateDetail (Prelude.Maybe FailureReason)
certificateDetail_failureReason :: Lens' CertificateDetail (Maybe FailureReason)
certificateDetail_failureReason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CertificateDetail' {Maybe FailureReason
failureReason :: Maybe FailureReason
$sel:failureReason:CertificateDetail' :: CertificateDetail -> Maybe FailureReason
failureReason} -> Maybe FailureReason
failureReason) (\s :: CertificateDetail
s@CertificateDetail' {} Maybe FailureReason
a -> CertificateDetail
s {$sel:failureReason:CertificateDetail' :: Maybe FailureReason
failureReason = Maybe FailureReason
a} :: CertificateDetail)

-- | The date and time when the certificate was imported. This value exists
-- only when the certificate type is @IMPORTED@.
certificateDetail_importedAt :: Lens.Lens' CertificateDetail (Prelude.Maybe Prelude.UTCTime)
certificateDetail_importedAt :: Lens' CertificateDetail (Maybe UTCTime)
certificateDetail_importedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CertificateDetail' {Maybe POSIX
importedAt :: Maybe POSIX
$sel:importedAt:CertificateDetail' :: CertificateDetail -> Maybe POSIX
importedAt} -> Maybe POSIX
importedAt) (\s :: CertificateDetail
s@CertificateDetail' {} Maybe POSIX
a -> CertificateDetail
s {$sel:importedAt:CertificateDetail' :: Maybe POSIX
importedAt = Maybe POSIX
a} :: CertificateDetail) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | A list of ARNs for the Amazon Web Services resources that are using the
-- certificate. A certificate can be used by multiple Amazon Web Services
-- resources.
certificateDetail_inUseBy :: Lens.Lens' CertificateDetail (Prelude.Maybe [Prelude.Text])
certificateDetail_inUseBy :: Lens' CertificateDetail (Maybe [Text])
certificateDetail_inUseBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CertificateDetail' {Maybe [Text]
inUseBy :: Maybe [Text]
$sel:inUseBy:CertificateDetail' :: CertificateDetail -> Maybe [Text]
inUseBy} -> Maybe [Text]
inUseBy) (\s :: CertificateDetail
s@CertificateDetail' {} Maybe [Text]
a -> CertificateDetail
s {$sel:inUseBy:CertificateDetail' :: Maybe [Text]
inUseBy = Maybe [Text]
a} :: CertificateDetail) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The time at which the certificate was issued. This value exists only
-- when the certificate type is @AMAZON_ISSUED@.
certificateDetail_issuedAt :: Lens.Lens' CertificateDetail (Prelude.Maybe Prelude.UTCTime)
certificateDetail_issuedAt :: Lens' CertificateDetail (Maybe UTCTime)
certificateDetail_issuedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CertificateDetail' {Maybe POSIX
issuedAt :: Maybe POSIX
$sel:issuedAt:CertificateDetail' :: CertificateDetail -> Maybe POSIX
issuedAt} -> Maybe POSIX
issuedAt) (\s :: CertificateDetail
s@CertificateDetail' {} Maybe POSIX
a -> CertificateDetail
s {$sel:issuedAt:CertificateDetail' :: Maybe POSIX
issuedAt = Maybe POSIX
a} :: CertificateDetail) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The name of the certificate authority that issued and signed the
-- certificate.
certificateDetail_issuer :: Lens.Lens' CertificateDetail (Prelude.Maybe Prelude.Text)
certificateDetail_issuer :: Lens' CertificateDetail (Maybe Text)
certificateDetail_issuer = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CertificateDetail' {Maybe Text
issuer :: Maybe Text
$sel:issuer:CertificateDetail' :: CertificateDetail -> Maybe Text
issuer} -> Maybe Text
issuer) (\s :: CertificateDetail
s@CertificateDetail' {} Maybe Text
a -> CertificateDetail
s {$sel:issuer:CertificateDetail' :: Maybe Text
issuer = Maybe Text
a} :: CertificateDetail)

-- | The algorithm that was used to generate the public-private key pair.
certificateDetail_keyAlgorithm :: Lens.Lens' CertificateDetail (Prelude.Maybe KeyAlgorithm)
certificateDetail_keyAlgorithm :: Lens' CertificateDetail (Maybe KeyAlgorithm)
certificateDetail_keyAlgorithm = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CertificateDetail' {Maybe KeyAlgorithm
keyAlgorithm :: Maybe KeyAlgorithm
$sel:keyAlgorithm:CertificateDetail' :: CertificateDetail -> Maybe KeyAlgorithm
keyAlgorithm} -> Maybe KeyAlgorithm
keyAlgorithm) (\s :: CertificateDetail
s@CertificateDetail' {} Maybe KeyAlgorithm
a -> CertificateDetail
s {$sel:keyAlgorithm:CertificateDetail' :: Maybe KeyAlgorithm
keyAlgorithm = Maybe KeyAlgorithm
a} :: CertificateDetail)

-- | A list of Key Usage X.509 v3 extension objects. Each object is a string
-- value that identifies the purpose of the public key contained in the
-- certificate. Possible extension values include DIGITAL_SIGNATURE,
-- KEY_ENCHIPHERMENT, NON_REPUDIATION, and more.
certificateDetail_keyUsages :: Lens.Lens' CertificateDetail (Prelude.Maybe [KeyUsage])
certificateDetail_keyUsages :: Lens' CertificateDetail (Maybe [KeyUsage])
certificateDetail_keyUsages = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CertificateDetail' {Maybe [KeyUsage]
keyUsages :: Maybe [KeyUsage]
$sel:keyUsages:CertificateDetail' :: CertificateDetail -> Maybe [KeyUsage]
keyUsages} -> Maybe [KeyUsage]
keyUsages) (\s :: CertificateDetail
s@CertificateDetail' {} Maybe [KeyUsage]
a -> CertificateDetail
s {$sel:keyUsages:CertificateDetail' :: Maybe [KeyUsage]
keyUsages = Maybe [KeyUsage]
a} :: CertificateDetail) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The time after which the certificate is not valid.
certificateDetail_notAfter :: Lens.Lens' CertificateDetail (Prelude.Maybe Prelude.UTCTime)
certificateDetail_notAfter :: Lens' CertificateDetail (Maybe UTCTime)
certificateDetail_notAfter = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CertificateDetail' {Maybe POSIX
notAfter :: Maybe POSIX
$sel:notAfter:CertificateDetail' :: CertificateDetail -> Maybe POSIX
notAfter} -> Maybe POSIX
notAfter) (\s :: CertificateDetail
s@CertificateDetail' {} Maybe POSIX
a -> CertificateDetail
s {$sel:notAfter:CertificateDetail' :: Maybe POSIX
notAfter = Maybe POSIX
a} :: CertificateDetail) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The time before which the certificate is not valid.
certificateDetail_notBefore :: Lens.Lens' CertificateDetail (Prelude.Maybe Prelude.UTCTime)
certificateDetail_notBefore :: Lens' CertificateDetail (Maybe UTCTime)
certificateDetail_notBefore = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CertificateDetail' {Maybe POSIX
notBefore :: Maybe POSIX
$sel:notBefore:CertificateDetail' :: CertificateDetail -> Maybe POSIX
notBefore} -> Maybe POSIX
notBefore) (\s :: CertificateDetail
s@CertificateDetail' {} Maybe POSIX
a -> CertificateDetail
s {$sel:notBefore:CertificateDetail' :: Maybe POSIX
notBefore = Maybe POSIX
a} :: CertificateDetail) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | Value that specifies whether to add the certificate to a transparency
-- log. Certificate transparency makes it possible to detect SSL
-- certificates that have been mistakenly or maliciously issued. A browser
-- might respond to certificate that has not been logged by showing an
-- error message. The logs are cryptographically secure.
certificateDetail_options :: Lens.Lens' CertificateDetail (Prelude.Maybe CertificateOptions)
certificateDetail_options :: Lens' CertificateDetail (Maybe CertificateOptions)
certificateDetail_options = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CertificateDetail' {Maybe CertificateOptions
options :: Maybe CertificateOptions
$sel:options:CertificateDetail' :: CertificateDetail -> Maybe CertificateOptions
options} -> Maybe CertificateOptions
options) (\s :: CertificateDetail
s@CertificateDetail' {} Maybe CertificateOptions
a -> CertificateDetail
s {$sel:options:CertificateDetail' :: Maybe CertificateOptions
options = Maybe CertificateOptions
a} :: CertificateDetail)

-- | Specifies whether the certificate is eligible for renewal. At this time,
-- only exported private certificates can be renewed with the
-- RenewCertificate command.
certificateDetail_renewalEligibility :: Lens.Lens' CertificateDetail (Prelude.Maybe RenewalEligibility)
certificateDetail_renewalEligibility :: Lens' CertificateDetail (Maybe RenewalEligibility)
certificateDetail_renewalEligibility = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CertificateDetail' {Maybe RenewalEligibility
renewalEligibility :: Maybe RenewalEligibility
$sel:renewalEligibility:CertificateDetail' :: CertificateDetail -> Maybe RenewalEligibility
renewalEligibility} -> Maybe RenewalEligibility
renewalEligibility) (\s :: CertificateDetail
s@CertificateDetail' {} Maybe RenewalEligibility
a -> CertificateDetail
s {$sel:renewalEligibility:CertificateDetail' :: Maybe RenewalEligibility
renewalEligibility = Maybe RenewalEligibility
a} :: CertificateDetail)

-- | Contains information about the status of ACM\'s
-- <https://docs.aws.amazon.com/acm/latest/userguide/acm-renewal.html managed renewal>
-- for the certificate. This field exists only when the certificate type is
-- @AMAZON_ISSUED@.
certificateDetail_renewalSummary :: Lens.Lens' CertificateDetail (Prelude.Maybe RenewalSummary)
certificateDetail_renewalSummary :: Lens' CertificateDetail (Maybe RenewalSummary)
certificateDetail_renewalSummary = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CertificateDetail' {Maybe RenewalSummary
renewalSummary :: Maybe RenewalSummary
$sel:renewalSummary:CertificateDetail' :: CertificateDetail -> Maybe RenewalSummary
renewalSummary} -> Maybe RenewalSummary
renewalSummary) (\s :: CertificateDetail
s@CertificateDetail' {} Maybe RenewalSummary
a -> CertificateDetail
s {$sel:renewalSummary:CertificateDetail' :: Maybe RenewalSummary
renewalSummary = Maybe RenewalSummary
a} :: CertificateDetail)

-- | The reason the certificate was revoked. This value exists only when the
-- certificate status is @REVOKED@.
certificateDetail_revocationReason :: Lens.Lens' CertificateDetail (Prelude.Maybe RevocationReason)
certificateDetail_revocationReason :: Lens' CertificateDetail (Maybe RevocationReason)
certificateDetail_revocationReason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CertificateDetail' {Maybe RevocationReason
revocationReason :: Maybe RevocationReason
$sel:revocationReason:CertificateDetail' :: CertificateDetail -> Maybe RevocationReason
revocationReason} -> Maybe RevocationReason
revocationReason) (\s :: CertificateDetail
s@CertificateDetail' {} Maybe RevocationReason
a -> CertificateDetail
s {$sel:revocationReason:CertificateDetail' :: Maybe RevocationReason
revocationReason = Maybe RevocationReason
a} :: CertificateDetail)

-- | The time at which the certificate was revoked. This value exists only
-- when the certificate status is @REVOKED@.
certificateDetail_revokedAt :: Lens.Lens' CertificateDetail (Prelude.Maybe Prelude.UTCTime)
certificateDetail_revokedAt :: Lens' CertificateDetail (Maybe UTCTime)
certificateDetail_revokedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CertificateDetail' {Maybe POSIX
revokedAt :: Maybe POSIX
$sel:revokedAt:CertificateDetail' :: CertificateDetail -> Maybe POSIX
revokedAt} -> Maybe POSIX
revokedAt) (\s :: CertificateDetail
s@CertificateDetail' {} Maybe POSIX
a -> CertificateDetail
s {$sel:revokedAt:CertificateDetail' :: Maybe POSIX
revokedAt = Maybe POSIX
a} :: CertificateDetail) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The serial number of the certificate.
certificateDetail_serial :: Lens.Lens' CertificateDetail (Prelude.Maybe Prelude.Text)
certificateDetail_serial :: Lens' CertificateDetail (Maybe Text)
certificateDetail_serial = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CertificateDetail' {Maybe Text
serial :: Maybe Text
$sel:serial:CertificateDetail' :: CertificateDetail -> Maybe Text
serial} -> Maybe Text
serial) (\s :: CertificateDetail
s@CertificateDetail' {} Maybe Text
a -> CertificateDetail
s {$sel:serial:CertificateDetail' :: Maybe Text
serial = Maybe Text
a} :: CertificateDetail)

-- | The algorithm that was used to sign the certificate.
certificateDetail_signatureAlgorithm :: Lens.Lens' CertificateDetail (Prelude.Maybe Prelude.Text)
certificateDetail_signatureAlgorithm :: Lens' CertificateDetail (Maybe Text)
certificateDetail_signatureAlgorithm = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CertificateDetail' {Maybe Text
signatureAlgorithm :: Maybe Text
$sel:signatureAlgorithm:CertificateDetail' :: CertificateDetail -> Maybe Text
signatureAlgorithm} -> Maybe Text
signatureAlgorithm) (\s :: CertificateDetail
s@CertificateDetail' {} Maybe Text
a -> CertificateDetail
s {$sel:signatureAlgorithm:CertificateDetail' :: Maybe Text
signatureAlgorithm = Maybe Text
a} :: CertificateDetail)

-- | The status of the certificate.
--
-- A certificate enters status PENDING_VALIDATION upon being requested,
-- unless it fails for any of the reasons given in the troubleshooting
-- topic
-- <https://docs.aws.amazon.com/acm/latest/userguide/troubleshooting-failed.html Certificate request fails>.
-- ACM makes repeated attempts to validate a certificate for 72 hours and
-- then times out. If a certificate shows status FAILED or
-- VALIDATION_TIMED_OUT, delete the request, correct the issue with
-- <https://docs.aws.amazon.com/acm/latest/userguide/dns-validation.html DNS validation>
-- or
-- <https://docs.aws.amazon.com/acm/latest/userguide/email-validation.html Email validation>,
-- and try again. If validation succeeds, the certificate enters status
-- ISSUED.
certificateDetail_status :: Lens.Lens' CertificateDetail (Prelude.Maybe CertificateStatus)
certificateDetail_status :: Lens' CertificateDetail (Maybe CertificateStatus)
certificateDetail_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CertificateDetail' {Maybe CertificateStatus
status :: Maybe CertificateStatus
$sel:status:CertificateDetail' :: CertificateDetail -> Maybe CertificateStatus
status} -> Maybe CertificateStatus
status) (\s :: CertificateDetail
s@CertificateDetail' {} Maybe CertificateStatus
a -> CertificateDetail
s {$sel:status:CertificateDetail' :: Maybe CertificateStatus
status = Maybe CertificateStatus
a} :: CertificateDetail)

-- | The name of the entity that is associated with the public key contained
-- in the certificate.
certificateDetail_subject :: Lens.Lens' CertificateDetail (Prelude.Maybe Prelude.Text)
certificateDetail_subject :: Lens' CertificateDetail (Maybe Text)
certificateDetail_subject = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CertificateDetail' {Maybe Text
subject :: Maybe Text
$sel:subject:CertificateDetail' :: CertificateDetail -> Maybe Text
subject} -> Maybe Text
subject) (\s :: CertificateDetail
s@CertificateDetail' {} Maybe Text
a -> CertificateDetail
s {$sel:subject:CertificateDetail' :: Maybe Text
subject = Maybe Text
a} :: CertificateDetail)

-- | One or more domain names (subject alternative names) included in the
-- certificate. This list contains the domain names that are bound to the
-- public key that is contained in the certificate. The subject alternative
-- names include the canonical domain name (CN) of the certificate and
-- additional domain names that can be used to connect to the website.
certificateDetail_subjectAlternativeNames :: Lens.Lens' CertificateDetail (Prelude.Maybe (Prelude.NonEmpty Prelude.Text))
certificateDetail_subjectAlternativeNames :: Lens' CertificateDetail (Maybe (NonEmpty Text))
certificateDetail_subjectAlternativeNames = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CertificateDetail' {Maybe (NonEmpty Text)
subjectAlternativeNames :: Maybe (NonEmpty Text)
$sel:subjectAlternativeNames:CertificateDetail' :: CertificateDetail -> Maybe (NonEmpty Text)
subjectAlternativeNames} -> Maybe (NonEmpty Text)
subjectAlternativeNames) (\s :: CertificateDetail
s@CertificateDetail' {} Maybe (NonEmpty Text)
a -> CertificateDetail
s {$sel:subjectAlternativeNames:CertificateDetail' :: Maybe (NonEmpty Text)
subjectAlternativeNames = Maybe (NonEmpty Text)
a} :: CertificateDetail) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The source of the certificate. For certificates provided by ACM, this
-- value is @AMAZON_ISSUED@. For certificates that you imported with
-- ImportCertificate, this value is @IMPORTED@. ACM does not provide
-- <https://docs.aws.amazon.com/acm/latest/userguide/acm-renewal.html managed renewal>
-- for imported certificates. For more information about the differences
-- between certificates that you import and those that ACM provides, see
-- <https://docs.aws.amazon.com/acm/latest/userguide/import-certificate.html Importing Certificates>
-- in the /Certificate Manager User Guide/.
certificateDetail_type :: Lens.Lens' CertificateDetail (Prelude.Maybe CertificateType)
certificateDetail_type :: Lens' CertificateDetail (Maybe CertificateType)
certificateDetail_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CertificateDetail' {Maybe CertificateType
type' :: Maybe CertificateType
$sel:type':CertificateDetail' :: CertificateDetail -> Maybe CertificateType
type'} -> Maybe CertificateType
type') (\s :: CertificateDetail
s@CertificateDetail' {} Maybe CertificateType
a -> CertificateDetail
s {$sel:type':CertificateDetail' :: Maybe CertificateType
type' = Maybe CertificateType
a} :: CertificateDetail)

instance Data.FromJSON CertificateDetail where
  parseJSON :: Value -> Parser CertificateDetail
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"CertificateDetail"
      ( \Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe POSIX
-> Maybe Text
-> Maybe (NonEmpty DomainValidation)
-> Maybe [ExtendedKeyUsage]
-> Maybe FailureReason
-> Maybe POSIX
-> Maybe [Text]
-> Maybe POSIX
-> Maybe Text
-> Maybe KeyAlgorithm
-> Maybe [KeyUsage]
-> Maybe POSIX
-> Maybe POSIX
-> Maybe CertificateOptions
-> Maybe RenewalEligibility
-> Maybe RenewalSummary
-> Maybe RevocationReason
-> Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Maybe CertificateStatus
-> Maybe Text
-> Maybe (NonEmpty Text)
-> Maybe CertificateType
-> CertificateDetail
CertificateDetail'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"CertificateArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"CertificateAuthorityArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"CreatedAt")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"DomainName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"DomainValidationOptions")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"ExtendedKeyUsages"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"FailureReason")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"ImportedAt")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"InUseBy" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"IssuedAt")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Issuer")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"KeyAlgorithm")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"KeyUsages" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"NotAfter")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"NotBefore")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Options")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"RenewalEligibility")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"RenewalSummary")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"RevocationReason")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"RevokedAt")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Serial")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"SignatureAlgorithm")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Status")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Subject")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"SubjectAlternativeNames")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Type")
      )

instance Prelude.Hashable CertificateDetail where
  hashWithSalt :: Int -> CertificateDetail -> Int
hashWithSalt Int
_salt CertificateDetail' {Maybe [Text]
Maybe [ExtendedKeyUsage]
Maybe [KeyUsage]
Maybe (NonEmpty Text)
Maybe (NonEmpty DomainValidation)
Maybe Text
Maybe POSIX
Maybe CertificateStatus
Maybe CertificateOptions
Maybe CertificateType
Maybe FailureReason
Maybe KeyAlgorithm
Maybe RenewalEligibility
Maybe RevocationReason
Maybe RenewalSummary
type' :: Maybe CertificateType
subjectAlternativeNames :: Maybe (NonEmpty Text)
subject :: Maybe Text
status :: Maybe CertificateStatus
signatureAlgorithm :: Maybe Text
serial :: Maybe Text
revokedAt :: Maybe POSIX
revocationReason :: Maybe RevocationReason
renewalSummary :: Maybe RenewalSummary
renewalEligibility :: Maybe RenewalEligibility
options :: Maybe CertificateOptions
notBefore :: Maybe POSIX
notAfter :: Maybe POSIX
keyUsages :: Maybe [KeyUsage]
keyAlgorithm :: Maybe KeyAlgorithm
issuer :: Maybe Text
issuedAt :: Maybe POSIX
inUseBy :: Maybe [Text]
importedAt :: Maybe POSIX
failureReason :: Maybe FailureReason
extendedKeyUsages :: Maybe [ExtendedKeyUsage]
domainValidationOptions :: Maybe (NonEmpty DomainValidation)
domainName :: Maybe Text
createdAt :: Maybe POSIX
certificateAuthorityArn :: Maybe Text
certificateArn :: Maybe Text
$sel:type':CertificateDetail' :: CertificateDetail -> Maybe CertificateType
$sel:subjectAlternativeNames:CertificateDetail' :: CertificateDetail -> Maybe (NonEmpty Text)
$sel:subject:CertificateDetail' :: CertificateDetail -> Maybe Text
$sel:status:CertificateDetail' :: CertificateDetail -> Maybe CertificateStatus
$sel:signatureAlgorithm:CertificateDetail' :: CertificateDetail -> Maybe Text
$sel:serial:CertificateDetail' :: CertificateDetail -> Maybe Text
$sel:revokedAt:CertificateDetail' :: CertificateDetail -> Maybe POSIX
$sel:revocationReason:CertificateDetail' :: CertificateDetail -> Maybe RevocationReason
$sel:renewalSummary:CertificateDetail' :: CertificateDetail -> Maybe RenewalSummary
$sel:renewalEligibility:CertificateDetail' :: CertificateDetail -> Maybe RenewalEligibility
$sel:options:CertificateDetail' :: CertificateDetail -> Maybe CertificateOptions
$sel:notBefore:CertificateDetail' :: CertificateDetail -> Maybe POSIX
$sel:notAfter:CertificateDetail' :: CertificateDetail -> Maybe POSIX
$sel:keyUsages:CertificateDetail' :: CertificateDetail -> Maybe [KeyUsage]
$sel:keyAlgorithm:CertificateDetail' :: CertificateDetail -> Maybe KeyAlgorithm
$sel:issuer:CertificateDetail' :: CertificateDetail -> Maybe Text
$sel:issuedAt:CertificateDetail' :: CertificateDetail -> Maybe POSIX
$sel:inUseBy:CertificateDetail' :: CertificateDetail -> Maybe [Text]
$sel:importedAt:CertificateDetail' :: CertificateDetail -> Maybe POSIX
$sel:failureReason:CertificateDetail' :: CertificateDetail -> Maybe FailureReason
$sel:extendedKeyUsages:CertificateDetail' :: CertificateDetail -> Maybe [ExtendedKeyUsage]
$sel:domainValidationOptions:CertificateDetail' :: CertificateDetail -> Maybe (NonEmpty DomainValidation)
$sel:domainName:CertificateDetail' :: CertificateDetail -> Maybe Text
$sel:createdAt:CertificateDetail' :: CertificateDetail -> Maybe POSIX
$sel:certificateAuthorityArn:CertificateDetail' :: CertificateDetail -> Maybe Text
$sel:certificateArn:CertificateDetail' :: CertificateDetail -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
certificateArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
certificateAuthorityArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
createdAt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
domainName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty DomainValidation)
domainValidationOptions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ExtendedKeyUsage]
extendedKeyUsages
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe FailureReason
failureReason
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
importedAt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
inUseBy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
issuedAt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
issuer
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe KeyAlgorithm
keyAlgorithm
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [KeyUsage]
keyUsages
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
notAfter
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
notBefore
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CertificateOptions
options
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RenewalEligibility
renewalEligibility
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RenewalSummary
renewalSummary
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RevocationReason
revocationReason
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
revokedAt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
serial
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
signatureAlgorithm
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CertificateStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
subject
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty Text)
subjectAlternativeNames
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CertificateType
type'

instance Prelude.NFData CertificateDetail where
  rnf :: CertificateDetail -> ()
rnf CertificateDetail' {Maybe [Text]
Maybe [ExtendedKeyUsage]
Maybe [KeyUsage]
Maybe (NonEmpty Text)
Maybe (NonEmpty DomainValidation)
Maybe Text
Maybe POSIX
Maybe CertificateStatus
Maybe CertificateOptions
Maybe CertificateType
Maybe FailureReason
Maybe KeyAlgorithm
Maybe RenewalEligibility
Maybe RevocationReason
Maybe RenewalSummary
type' :: Maybe CertificateType
subjectAlternativeNames :: Maybe (NonEmpty Text)
subject :: Maybe Text
status :: Maybe CertificateStatus
signatureAlgorithm :: Maybe Text
serial :: Maybe Text
revokedAt :: Maybe POSIX
revocationReason :: Maybe RevocationReason
renewalSummary :: Maybe RenewalSummary
renewalEligibility :: Maybe RenewalEligibility
options :: Maybe CertificateOptions
notBefore :: Maybe POSIX
notAfter :: Maybe POSIX
keyUsages :: Maybe [KeyUsage]
keyAlgorithm :: Maybe KeyAlgorithm
issuer :: Maybe Text
issuedAt :: Maybe POSIX
inUseBy :: Maybe [Text]
importedAt :: Maybe POSIX
failureReason :: Maybe FailureReason
extendedKeyUsages :: Maybe [ExtendedKeyUsage]
domainValidationOptions :: Maybe (NonEmpty DomainValidation)
domainName :: Maybe Text
createdAt :: Maybe POSIX
certificateAuthorityArn :: Maybe Text
certificateArn :: Maybe Text
$sel:type':CertificateDetail' :: CertificateDetail -> Maybe CertificateType
$sel:subjectAlternativeNames:CertificateDetail' :: CertificateDetail -> Maybe (NonEmpty Text)
$sel:subject:CertificateDetail' :: CertificateDetail -> Maybe Text
$sel:status:CertificateDetail' :: CertificateDetail -> Maybe CertificateStatus
$sel:signatureAlgorithm:CertificateDetail' :: CertificateDetail -> Maybe Text
$sel:serial:CertificateDetail' :: CertificateDetail -> Maybe Text
$sel:revokedAt:CertificateDetail' :: CertificateDetail -> Maybe POSIX
$sel:revocationReason:CertificateDetail' :: CertificateDetail -> Maybe RevocationReason
$sel:renewalSummary:CertificateDetail' :: CertificateDetail -> Maybe RenewalSummary
$sel:renewalEligibility:CertificateDetail' :: CertificateDetail -> Maybe RenewalEligibility
$sel:options:CertificateDetail' :: CertificateDetail -> Maybe CertificateOptions
$sel:notBefore:CertificateDetail' :: CertificateDetail -> Maybe POSIX
$sel:notAfter:CertificateDetail' :: CertificateDetail -> Maybe POSIX
$sel:keyUsages:CertificateDetail' :: CertificateDetail -> Maybe [KeyUsage]
$sel:keyAlgorithm:CertificateDetail' :: CertificateDetail -> Maybe KeyAlgorithm
$sel:issuer:CertificateDetail' :: CertificateDetail -> Maybe Text
$sel:issuedAt:CertificateDetail' :: CertificateDetail -> Maybe POSIX
$sel:inUseBy:CertificateDetail' :: CertificateDetail -> Maybe [Text]
$sel:importedAt:CertificateDetail' :: CertificateDetail -> Maybe POSIX
$sel:failureReason:CertificateDetail' :: CertificateDetail -> Maybe FailureReason
$sel:extendedKeyUsages:CertificateDetail' :: CertificateDetail -> Maybe [ExtendedKeyUsage]
$sel:domainValidationOptions:CertificateDetail' :: CertificateDetail -> Maybe (NonEmpty DomainValidation)
$sel:domainName:CertificateDetail' :: CertificateDetail -> Maybe Text
$sel:createdAt:CertificateDetail' :: CertificateDetail -> Maybe POSIX
$sel:certificateAuthorityArn:CertificateDetail' :: CertificateDetail -> Maybe Text
$sel:certificateArn:CertificateDetail' :: CertificateDetail -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
certificateArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
certificateAuthorityArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
domainName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty DomainValidation)
domainValidationOptions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ExtendedKeyUsage]
extendedKeyUsages
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe FailureReason
failureReason
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
importedAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
inUseBy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
issuedAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
issuer
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe KeyAlgorithm
keyAlgorithm
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [KeyUsage]
keyUsages
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
notAfter
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
notBefore
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CertificateOptions
options
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RenewalEligibility
renewalEligibility
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RenewalSummary
renewalSummary
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RevocationReason
revocationReason
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
revokedAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
serial
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
signatureAlgorithm
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CertificateStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
subject
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe (NonEmpty Text)
subjectAlternativeNames
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CertificateType
type'