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

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

-- |
-- Module      : Amazonka.CertificateManagerPCA.UpdateCertificateAuthority
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates the status or configuration of a private certificate authority
-- (CA). Your private CA must be in the @ACTIVE@ or @DISABLED@ state before
-- you can update it. You can disable a private CA that is in the @ACTIVE@
-- state or make a CA that is in the @DISABLED@ state active again.
--
-- Both Amazon Web Services Private CA and the IAM principal must have
-- permission to write to the S3 bucket that you specify. If the IAM
-- principal making the call does not have permission to write to the
-- bucket, then an exception is thrown. For more information, see
-- <https://docs.aws.amazon.com/privateca/latest/userguide/crl-planning.html#s3-policies Access policies for CRLs in Amazon S3>.
module Amazonka.CertificateManagerPCA.UpdateCertificateAuthority
  ( -- * Creating a Request
    UpdateCertificateAuthority (..),
    newUpdateCertificateAuthority,

    -- * Request Lenses
    updateCertificateAuthority_revocationConfiguration,
    updateCertificateAuthority_status,
    updateCertificateAuthority_certificateAuthorityArn,

    -- * Destructuring the Response
    UpdateCertificateAuthorityResponse (..),
    newUpdateCertificateAuthorityResponse,
  )
where

import Amazonka.CertificateManagerPCA.Types
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
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newUpdateCertificateAuthority' smart constructor.
data UpdateCertificateAuthority = UpdateCertificateAuthority'
  { -- | Contains information to enable Online Certificate Status Protocol (OCSP)
    -- support, to enable a certificate revocation list (CRL), to enable both,
    -- or to enable neither. If this parameter is not supplied, existing
    -- capibilites remain unchanged. For more information, see the
    -- <https://docs.aws.amazon.com/privateca/latest/APIReference/API_OcspConfiguration.html OcspConfiguration>
    -- and
    -- <https://docs.aws.amazon.com/privateca/latest/APIReference/API_CrlConfiguration.html CrlConfiguration>
    -- types.
    --
    -- The following requirements apply to revocation configurations.
    --
    -- -   A configuration disabling CRLs or OCSP must contain only the
    --     @Enabled=False@ parameter, and will fail if other parameters such as
    --     @CustomCname@ or @ExpirationInDays@ are included.
    --
    -- -   In a CRL configuration, the @S3BucketName@ parameter must conform to
    --     <https://docs.aws.amazon.com/AmazonS3/latest/userguide/bucketnamingrules.html Amazon S3 bucket naming rules>.
    --
    -- -   A configuration containing a custom Canonical Name (CNAME) parameter
    --     for CRLs or OCSP must conform to
    --     <https://www.ietf.org/rfc/rfc2396.txt RFC2396> restrictions on the
    --     use of special characters in a CNAME.
    --
    -- -   In a CRL or OCSP configuration, the value of a CNAME parameter must
    --     not include a protocol prefix such as \"http:\/\/\" or
    --     \"https:\/\/\".
    UpdateCertificateAuthority -> Maybe RevocationConfiguration
revocationConfiguration :: Prelude.Maybe RevocationConfiguration,
    -- | Status of your private CA.
    UpdateCertificateAuthority -> Maybe CertificateAuthorityStatus
status :: Prelude.Maybe CertificateAuthorityStatus,
    -- | Amazon Resource Name (ARN) of the private CA that issued the certificate
    -- to be revoked. This must be of the form:
    --
    -- @arn:aws:acm-pca:@/@region@/@:@/@account@/@:certificate-authority\/@/@12345678-1234-1234-1234-123456789012@/@ @
    UpdateCertificateAuthority -> Text
certificateAuthorityArn :: Prelude.Text
  }
  deriving (UpdateCertificateAuthority -> UpdateCertificateAuthority -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateCertificateAuthority -> UpdateCertificateAuthority -> Bool
$c/= :: UpdateCertificateAuthority -> UpdateCertificateAuthority -> Bool
== :: UpdateCertificateAuthority -> UpdateCertificateAuthority -> Bool
$c== :: UpdateCertificateAuthority -> UpdateCertificateAuthority -> Bool
Prelude.Eq, ReadPrec [UpdateCertificateAuthority]
ReadPrec UpdateCertificateAuthority
Int -> ReadS UpdateCertificateAuthority
ReadS [UpdateCertificateAuthority]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateCertificateAuthority]
$creadListPrec :: ReadPrec [UpdateCertificateAuthority]
readPrec :: ReadPrec UpdateCertificateAuthority
$creadPrec :: ReadPrec UpdateCertificateAuthority
readList :: ReadS [UpdateCertificateAuthority]
$creadList :: ReadS [UpdateCertificateAuthority]
readsPrec :: Int -> ReadS UpdateCertificateAuthority
$creadsPrec :: Int -> ReadS UpdateCertificateAuthority
Prelude.Read, Int -> UpdateCertificateAuthority -> ShowS
[UpdateCertificateAuthority] -> ShowS
UpdateCertificateAuthority -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateCertificateAuthority] -> ShowS
$cshowList :: [UpdateCertificateAuthority] -> ShowS
show :: UpdateCertificateAuthority -> String
$cshow :: UpdateCertificateAuthority -> String
showsPrec :: Int -> UpdateCertificateAuthority -> ShowS
$cshowsPrec :: Int -> UpdateCertificateAuthority -> ShowS
Prelude.Show, forall x.
Rep UpdateCertificateAuthority x -> UpdateCertificateAuthority
forall x.
UpdateCertificateAuthority -> Rep UpdateCertificateAuthority x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateCertificateAuthority x -> UpdateCertificateAuthority
$cfrom :: forall x.
UpdateCertificateAuthority -> Rep UpdateCertificateAuthority x
Prelude.Generic)

-- |
-- Create a value of 'UpdateCertificateAuthority' 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:
--
-- 'revocationConfiguration', 'updateCertificateAuthority_revocationConfiguration' - Contains information to enable Online Certificate Status Protocol (OCSP)
-- support, to enable a certificate revocation list (CRL), to enable both,
-- or to enable neither. If this parameter is not supplied, existing
-- capibilites remain unchanged. For more information, see the
-- <https://docs.aws.amazon.com/privateca/latest/APIReference/API_OcspConfiguration.html OcspConfiguration>
-- and
-- <https://docs.aws.amazon.com/privateca/latest/APIReference/API_CrlConfiguration.html CrlConfiguration>
-- types.
--
-- The following requirements apply to revocation configurations.
--
-- -   A configuration disabling CRLs or OCSP must contain only the
--     @Enabled=False@ parameter, and will fail if other parameters such as
--     @CustomCname@ or @ExpirationInDays@ are included.
--
-- -   In a CRL configuration, the @S3BucketName@ parameter must conform to
--     <https://docs.aws.amazon.com/AmazonS3/latest/userguide/bucketnamingrules.html Amazon S3 bucket naming rules>.
--
-- -   A configuration containing a custom Canonical Name (CNAME) parameter
--     for CRLs or OCSP must conform to
--     <https://www.ietf.org/rfc/rfc2396.txt RFC2396> restrictions on the
--     use of special characters in a CNAME.
--
-- -   In a CRL or OCSP configuration, the value of a CNAME parameter must
--     not include a protocol prefix such as \"http:\/\/\" or
--     \"https:\/\/\".
--
-- 'status', 'updateCertificateAuthority_status' - Status of your private CA.
--
-- 'certificateAuthorityArn', 'updateCertificateAuthority_certificateAuthorityArn' - Amazon Resource Name (ARN) of the private CA that issued the certificate
-- to be revoked. This must be of the form:
--
-- @arn:aws:acm-pca:@/@region@/@:@/@account@/@:certificate-authority\/@/@12345678-1234-1234-1234-123456789012@/@ @
newUpdateCertificateAuthority ::
  -- | 'certificateAuthorityArn'
  Prelude.Text ->
  UpdateCertificateAuthority
newUpdateCertificateAuthority :: Text -> UpdateCertificateAuthority
newUpdateCertificateAuthority
  Text
pCertificateAuthorityArn_ =
    UpdateCertificateAuthority'
      { $sel:revocationConfiguration:UpdateCertificateAuthority' :: Maybe RevocationConfiguration
revocationConfiguration =
          forall a. Maybe a
Prelude.Nothing,
        $sel:status:UpdateCertificateAuthority' :: Maybe CertificateAuthorityStatus
status = forall a. Maybe a
Prelude.Nothing,
        $sel:certificateAuthorityArn:UpdateCertificateAuthority' :: Text
certificateAuthorityArn =
          Text
pCertificateAuthorityArn_
      }

-- | Contains information to enable Online Certificate Status Protocol (OCSP)
-- support, to enable a certificate revocation list (CRL), to enable both,
-- or to enable neither. If this parameter is not supplied, existing
-- capibilites remain unchanged. For more information, see the
-- <https://docs.aws.amazon.com/privateca/latest/APIReference/API_OcspConfiguration.html OcspConfiguration>
-- and
-- <https://docs.aws.amazon.com/privateca/latest/APIReference/API_CrlConfiguration.html CrlConfiguration>
-- types.
--
-- The following requirements apply to revocation configurations.
--
-- -   A configuration disabling CRLs or OCSP must contain only the
--     @Enabled=False@ parameter, and will fail if other parameters such as
--     @CustomCname@ or @ExpirationInDays@ are included.
--
-- -   In a CRL configuration, the @S3BucketName@ parameter must conform to
--     <https://docs.aws.amazon.com/AmazonS3/latest/userguide/bucketnamingrules.html Amazon S3 bucket naming rules>.
--
-- -   A configuration containing a custom Canonical Name (CNAME) parameter
--     for CRLs or OCSP must conform to
--     <https://www.ietf.org/rfc/rfc2396.txt RFC2396> restrictions on the
--     use of special characters in a CNAME.
--
-- -   In a CRL or OCSP configuration, the value of a CNAME parameter must
--     not include a protocol prefix such as \"http:\/\/\" or
--     \"https:\/\/\".
updateCertificateAuthority_revocationConfiguration :: Lens.Lens' UpdateCertificateAuthority (Prelude.Maybe RevocationConfiguration)
updateCertificateAuthority_revocationConfiguration :: Lens' UpdateCertificateAuthority (Maybe RevocationConfiguration)
updateCertificateAuthority_revocationConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCertificateAuthority' {Maybe RevocationConfiguration
revocationConfiguration :: Maybe RevocationConfiguration
$sel:revocationConfiguration:UpdateCertificateAuthority' :: UpdateCertificateAuthority -> Maybe RevocationConfiguration
revocationConfiguration} -> Maybe RevocationConfiguration
revocationConfiguration) (\s :: UpdateCertificateAuthority
s@UpdateCertificateAuthority' {} Maybe RevocationConfiguration
a -> UpdateCertificateAuthority
s {$sel:revocationConfiguration:UpdateCertificateAuthority' :: Maybe RevocationConfiguration
revocationConfiguration = Maybe RevocationConfiguration
a} :: UpdateCertificateAuthority)

-- | Status of your private CA.
updateCertificateAuthority_status :: Lens.Lens' UpdateCertificateAuthority (Prelude.Maybe CertificateAuthorityStatus)
updateCertificateAuthority_status :: Lens' UpdateCertificateAuthority (Maybe CertificateAuthorityStatus)
updateCertificateAuthority_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCertificateAuthority' {Maybe CertificateAuthorityStatus
status :: Maybe CertificateAuthorityStatus
$sel:status:UpdateCertificateAuthority' :: UpdateCertificateAuthority -> Maybe CertificateAuthorityStatus
status} -> Maybe CertificateAuthorityStatus
status) (\s :: UpdateCertificateAuthority
s@UpdateCertificateAuthority' {} Maybe CertificateAuthorityStatus
a -> UpdateCertificateAuthority
s {$sel:status:UpdateCertificateAuthority' :: Maybe CertificateAuthorityStatus
status = Maybe CertificateAuthorityStatus
a} :: UpdateCertificateAuthority)

-- | Amazon Resource Name (ARN) of the private CA that issued the certificate
-- to be revoked. This must be of the form:
--
-- @arn:aws:acm-pca:@/@region@/@:@/@account@/@:certificate-authority\/@/@12345678-1234-1234-1234-123456789012@/@ @
updateCertificateAuthority_certificateAuthorityArn :: Lens.Lens' UpdateCertificateAuthority Prelude.Text
updateCertificateAuthority_certificateAuthorityArn :: Lens' UpdateCertificateAuthority Text
updateCertificateAuthority_certificateAuthorityArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCertificateAuthority' {Text
certificateAuthorityArn :: Text
$sel:certificateAuthorityArn:UpdateCertificateAuthority' :: UpdateCertificateAuthority -> Text
certificateAuthorityArn} -> Text
certificateAuthorityArn) (\s :: UpdateCertificateAuthority
s@UpdateCertificateAuthority' {} Text
a -> UpdateCertificateAuthority
s {$sel:certificateAuthorityArn:UpdateCertificateAuthority' :: Text
certificateAuthorityArn = Text
a} :: UpdateCertificateAuthority)

instance Core.AWSRequest UpdateCertificateAuthority where
  type
    AWSResponse UpdateCertificateAuthority =
      UpdateCertificateAuthorityResponse
  request :: (Service -> Service)
-> UpdateCertificateAuthority -> Request UpdateCertificateAuthority
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateCertificateAuthority
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateCertificateAuthority)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull
      UpdateCertificateAuthorityResponse
UpdateCertificateAuthorityResponse'

instance Prelude.Hashable UpdateCertificateAuthority where
  hashWithSalt :: Int -> UpdateCertificateAuthority -> Int
hashWithSalt Int
_salt UpdateCertificateAuthority' {Maybe CertificateAuthorityStatus
Maybe RevocationConfiguration
Text
certificateAuthorityArn :: Text
status :: Maybe CertificateAuthorityStatus
revocationConfiguration :: Maybe RevocationConfiguration
$sel:certificateAuthorityArn:UpdateCertificateAuthority' :: UpdateCertificateAuthority -> Text
$sel:status:UpdateCertificateAuthority' :: UpdateCertificateAuthority -> Maybe CertificateAuthorityStatus
$sel:revocationConfiguration:UpdateCertificateAuthority' :: UpdateCertificateAuthority -> Maybe RevocationConfiguration
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RevocationConfiguration
revocationConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CertificateAuthorityStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
certificateAuthorityArn

instance Prelude.NFData UpdateCertificateAuthority where
  rnf :: UpdateCertificateAuthority -> ()
rnf UpdateCertificateAuthority' {Maybe CertificateAuthorityStatus
Maybe RevocationConfiguration
Text
certificateAuthorityArn :: Text
status :: Maybe CertificateAuthorityStatus
revocationConfiguration :: Maybe RevocationConfiguration
$sel:certificateAuthorityArn:UpdateCertificateAuthority' :: UpdateCertificateAuthority -> Text
$sel:status:UpdateCertificateAuthority' :: UpdateCertificateAuthority -> Maybe CertificateAuthorityStatus
$sel:revocationConfiguration:UpdateCertificateAuthority' :: UpdateCertificateAuthority -> Maybe RevocationConfiguration
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe RevocationConfiguration
revocationConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CertificateAuthorityStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
certificateAuthorityArn

instance Data.ToHeaders UpdateCertificateAuthority where
  toHeaders :: UpdateCertificateAuthority -> [Header]
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"ACMPrivateCA.UpdateCertificateAuthority" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdateCertificateAuthority where
  toJSON :: UpdateCertificateAuthority -> Value
toJSON UpdateCertificateAuthority' {Maybe CertificateAuthorityStatus
Maybe RevocationConfiguration
Text
certificateAuthorityArn :: Text
status :: Maybe CertificateAuthorityStatus
revocationConfiguration :: Maybe RevocationConfiguration
$sel:certificateAuthorityArn:UpdateCertificateAuthority' :: UpdateCertificateAuthority -> Text
$sel:status:UpdateCertificateAuthority' :: UpdateCertificateAuthority -> Maybe CertificateAuthorityStatus
$sel:revocationConfiguration:UpdateCertificateAuthority' :: UpdateCertificateAuthority -> Maybe RevocationConfiguration
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"RevocationConfiguration" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe RevocationConfiguration
revocationConfiguration,
            (Key
"Status" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe CertificateAuthorityStatus
status,
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"CertificateAuthorityArn"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
certificateAuthorityArn
              )
          ]
      )

instance Data.ToPath UpdateCertificateAuthority where
  toPath :: UpdateCertificateAuthority -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

instance Data.ToQuery UpdateCertificateAuthority where
  toQuery :: UpdateCertificateAuthority -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newUpdateCertificateAuthorityResponse' smart constructor.
data UpdateCertificateAuthorityResponse = UpdateCertificateAuthorityResponse'
  {
  }
  deriving (UpdateCertificateAuthorityResponse
-> UpdateCertificateAuthorityResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateCertificateAuthorityResponse
-> UpdateCertificateAuthorityResponse -> Bool
$c/= :: UpdateCertificateAuthorityResponse
-> UpdateCertificateAuthorityResponse -> Bool
== :: UpdateCertificateAuthorityResponse
-> UpdateCertificateAuthorityResponse -> Bool
$c== :: UpdateCertificateAuthorityResponse
-> UpdateCertificateAuthorityResponse -> Bool
Prelude.Eq, ReadPrec [UpdateCertificateAuthorityResponse]
ReadPrec UpdateCertificateAuthorityResponse
Int -> ReadS UpdateCertificateAuthorityResponse
ReadS [UpdateCertificateAuthorityResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateCertificateAuthorityResponse]
$creadListPrec :: ReadPrec [UpdateCertificateAuthorityResponse]
readPrec :: ReadPrec UpdateCertificateAuthorityResponse
$creadPrec :: ReadPrec UpdateCertificateAuthorityResponse
readList :: ReadS [UpdateCertificateAuthorityResponse]
$creadList :: ReadS [UpdateCertificateAuthorityResponse]
readsPrec :: Int -> ReadS UpdateCertificateAuthorityResponse
$creadsPrec :: Int -> ReadS UpdateCertificateAuthorityResponse
Prelude.Read, Int -> UpdateCertificateAuthorityResponse -> ShowS
[UpdateCertificateAuthorityResponse] -> ShowS
UpdateCertificateAuthorityResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateCertificateAuthorityResponse] -> ShowS
$cshowList :: [UpdateCertificateAuthorityResponse] -> ShowS
show :: UpdateCertificateAuthorityResponse -> String
$cshow :: UpdateCertificateAuthorityResponse -> String
showsPrec :: Int -> UpdateCertificateAuthorityResponse -> ShowS
$cshowsPrec :: Int -> UpdateCertificateAuthorityResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateCertificateAuthorityResponse x
-> UpdateCertificateAuthorityResponse
forall x.
UpdateCertificateAuthorityResponse
-> Rep UpdateCertificateAuthorityResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateCertificateAuthorityResponse x
-> UpdateCertificateAuthorityResponse
$cfrom :: forall x.
UpdateCertificateAuthorityResponse
-> Rep UpdateCertificateAuthorityResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateCertificateAuthorityResponse' 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.
newUpdateCertificateAuthorityResponse ::
  UpdateCertificateAuthorityResponse
newUpdateCertificateAuthorityResponse :: UpdateCertificateAuthorityResponse
newUpdateCertificateAuthorityResponse =
  UpdateCertificateAuthorityResponse
UpdateCertificateAuthorityResponse'

instance
  Prelude.NFData
    UpdateCertificateAuthorityResponse
  where
  rnf :: UpdateCertificateAuthorityResponse -> ()
rnf UpdateCertificateAuthorityResponse
_ = ()