{-# 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.IoT.RegisterCACertificate
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Registers a CA certificate with Amazon Web Services IoT Core. There is
-- no limit to the number of CA certificates you can register in your
-- Amazon Web Services account. You can register up to 10 CA certificates
-- with the same @CA subject field@ per Amazon Web Services account.
--
-- Requires permission to access the
-- <https://docs.aws.amazon.com/service-authorization/latest/reference/list_awsiot.html#awsiot-actions-as-permissions RegisterCACertificate>
-- action.
module Amazonka.IoT.RegisterCACertificate
  ( -- * Creating a Request
    RegisterCACertificate (..),
    newRegisterCACertificate,

    -- * Request Lenses
    registerCACertificate_allowAutoRegistration,
    registerCACertificate_certificateMode,
    registerCACertificate_registrationConfig,
    registerCACertificate_setAsActive,
    registerCACertificate_tags,
    registerCACertificate_verificationCertificate,
    registerCACertificate_caCertificate,

    -- * Destructuring the Response
    RegisterCACertificateResponse (..),
    newRegisterCACertificateResponse,

    -- * Response Lenses
    registerCACertificateResponse_certificateArn,
    registerCACertificateResponse_certificateId,
    registerCACertificateResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.IoT.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | The input to the RegisterCACertificate operation.
--
-- /See:/ 'newRegisterCACertificate' smart constructor.
data RegisterCACertificate = RegisterCACertificate'
  { -- | Allows this CA certificate to be used for auto registration of device
    -- certificates.
    RegisterCACertificate -> Maybe Bool
allowAutoRegistration :: Prelude.Maybe Prelude.Bool,
    -- | Describes the certificate mode in which the Certificate Authority (CA)
    -- will be registered. If the @verificationCertificate@ field is not
    -- provided, set @certificateMode@ to be @SNI_ONLY@. If the
    -- @verificationCertificate@ field is provided, set @certificateMode@ to be
    -- @DEFAULT@. When @certificateMode@ is not provided, it defaults to
    -- @DEFAULT@. All the device certificates that are registered using this CA
    -- will be registered in the same certificate mode as the CA. For more
    -- information about certificate mode for device certificates, see
    -- <https://docs.aws.amazon.com/iot/latest/apireference/API_CertificateDescription.html#iot-Type-CertificateDescription-certificateMode certificate mode>.
    RegisterCACertificate -> Maybe CertificateMode
certificateMode :: Prelude.Maybe CertificateMode,
    -- | Information about the registration configuration.
    RegisterCACertificate -> Maybe RegistrationConfig
registrationConfig :: Prelude.Maybe RegistrationConfig,
    -- | A boolean value that specifies if the CA certificate is set to active.
    --
    -- Valid values: @ACTIVE | INACTIVE@
    RegisterCACertificate -> Maybe Bool
setAsActive :: Prelude.Maybe Prelude.Bool,
    -- | Metadata which can be used to manage the CA certificate.
    --
    -- For URI Request parameters use format: ...key1=value1&key2=value2...
    --
    -- For the CLI command-line parameter use format: &&tags
    -- \"key1=value1&key2=value2...\"
    --
    -- For the cli-input-json file use format: \"tags\":
    -- \"key1=value1&key2=value2...\"
    RegisterCACertificate -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The private key verification certificate. If @certificateMode@ is
    -- @SNI_ONLY@, the @verificationCertificate@ field must be empty. If
    -- @certificateMode@ is @DEFAULT@ or not provided, the
    -- @verificationCertificate@ field must not be empty.
    RegisterCACertificate -> Maybe Text
verificationCertificate :: Prelude.Maybe Prelude.Text,
    -- | The CA certificate.
    RegisterCACertificate -> Text
caCertificate :: Prelude.Text
  }
  deriving (RegisterCACertificate -> RegisterCACertificate -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RegisterCACertificate -> RegisterCACertificate -> Bool
$c/= :: RegisterCACertificate -> RegisterCACertificate -> Bool
== :: RegisterCACertificate -> RegisterCACertificate -> Bool
$c== :: RegisterCACertificate -> RegisterCACertificate -> Bool
Prelude.Eq, ReadPrec [RegisterCACertificate]
ReadPrec RegisterCACertificate
Int -> ReadS RegisterCACertificate
ReadS [RegisterCACertificate]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RegisterCACertificate]
$creadListPrec :: ReadPrec [RegisterCACertificate]
readPrec :: ReadPrec RegisterCACertificate
$creadPrec :: ReadPrec RegisterCACertificate
readList :: ReadS [RegisterCACertificate]
$creadList :: ReadS [RegisterCACertificate]
readsPrec :: Int -> ReadS RegisterCACertificate
$creadsPrec :: Int -> ReadS RegisterCACertificate
Prelude.Read, Int -> RegisterCACertificate -> ShowS
[RegisterCACertificate] -> ShowS
RegisterCACertificate -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RegisterCACertificate] -> ShowS
$cshowList :: [RegisterCACertificate] -> ShowS
show :: RegisterCACertificate -> String
$cshow :: RegisterCACertificate -> String
showsPrec :: Int -> RegisterCACertificate -> ShowS
$cshowsPrec :: Int -> RegisterCACertificate -> ShowS
Prelude.Show, forall x. Rep RegisterCACertificate x -> RegisterCACertificate
forall x. RegisterCACertificate -> Rep RegisterCACertificate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RegisterCACertificate x -> RegisterCACertificate
$cfrom :: forall x. RegisterCACertificate -> Rep RegisterCACertificate x
Prelude.Generic)

-- |
-- Create a value of 'RegisterCACertificate' 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:
--
-- 'allowAutoRegistration', 'registerCACertificate_allowAutoRegistration' - Allows this CA certificate to be used for auto registration of device
-- certificates.
--
-- 'certificateMode', 'registerCACertificate_certificateMode' - Describes the certificate mode in which the Certificate Authority (CA)
-- will be registered. If the @verificationCertificate@ field is not
-- provided, set @certificateMode@ to be @SNI_ONLY@. If the
-- @verificationCertificate@ field is provided, set @certificateMode@ to be
-- @DEFAULT@. When @certificateMode@ is not provided, it defaults to
-- @DEFAULT@. All the device certificates that are registered using this CA
-- will be registered in the same certificate mode as the CA. For more
-- information about certificate mode for device certificates, see
-- <https://docs.aws.amazon.com/iot/latest/apireference/API_CertificateDescription.html#iot-Type-CertificateDescription-certificateMode certificate mode>.
--
-- 'registrationConfig', 'registerCACertificate_registrationConfig' - Information about the registration configuration.
--
-- 'setAsActive', 'registerCACertificate_setAsActive' - A boolean value that specifies if the CA certificate is set to active.
--
-- Valid values: @ACTIVE | INACTIVE@
--
-- 'tags', 'registerCACertificate_tags' - Metadata which can be used to manage the CA certificate.
--
-- For URI Request parameters use format: ...key1=value1&key2=value2...
--
-- For the CLI command-line parameter use format: &&tags
-- \"key1=value1&key2=value2...\"
--
-- For the cli-input-json file use format: \"tags\":
-- \"key1=value1&key2=value2...\"
--
-- 'verificationCertificate', 'registerCACertificate_verificationCertificate' - The private key verification certificate. If @certificateMode@ is
-- @SNI_ONLY@, the @verificationCertificate@ field must be empty. If
-- @certificateMode@ is @DEFAULT@ or not provided, the
-- @verificationCertificate@ field must not be empty.
--
-- 'caCertificate', 'registerCACertificate_caCertificate' - The CA certificate.
newRegisterCACertificate ::
  -- | 'caCertificate'
  Prelude.Text ->
  RegisterCACertificate
newRegisterCACertificate :: Text -> RegisterCACertificate
newRegisterCACertificate Text
pCaCertificate_ =
  RegisterCACertificate'
    { $sel:allowAutoRegistration:RegisterCACertificate' :: Maybe Bool
allowAutoRegistration =
        forall a. Maybe a
Prelude.Nothing,
      $sel:certificateMode:RegisterCACertificate' :: Maybe CertificateMode
certificateMode = forall a. Maybe a
Prelude.Nothing,
      $sel:registrationConfig:RegisterCACertificate' :: Maybe RegistrationConfig
registrationConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:setAsActive:RegisterCACertificate' :: Maybe Bool
setAsActive = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:RegisterCACertificate' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:verificationCertificate:RegisterCACertificate' :: Maybe Text
verificationCertificate = forall a. Maybe a
Prelude.Nothing,
      $sel:caCertificate:RegisterCACertificate' :: Text
caCertificate = Text
pCaCertificate_
    }

-- | Allows this CA certificate to be used for auto registration of device
-- certificates.
registerCACertificate_allowAutoRegistration :: Lens.Lens' RegisterCACertificate (Prelude.Maybe Prelude.Bool)
registerCACertificate_allowAutoRegistration :: Lens' RegisterCACertificate (Maybe Bool)
registerCACertificate_allowAutoRegistration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterCACertificate' {Maybe Bool
allowAutoRegistration :: Maybe Bool
$sel:allowAutoRegistration:RegisterCACertificate' :: RegisterCACertificate -> Maybe Bool
allowAutoRegistration} -> Maybe Bool
allowAutoRegistration) (\s :: RegisterCACertificate
s@RegisterCACertificate' {} Maybe Bool
a -> RegisterCACertificate
s {$sel:allowAutoRegistration:RegisterCACertificate' :: Maybe Bool
allowAutoRegistration = Maybe Bool
a} :: RegisterCACertificate)

-- | Describes the certificate mode in which the Certificate Authority (CA)
-- will be registered. If the @verificationCertificate@ field is not
-- provided, set @certificateMode@ to be @SNI_ONLY@. If the
-- @verificationCertificate@ field is provided, set @certificateMode@ to be
-- @DEFAULT@. When @certificateMode@ is not provided, it defaults to
-- @DEFAULT@. All the device certificates that are registered using this CA
-- will be registered in the same certificate mode as the CA. For more
-- information about certificate mode for device certificates, see
-- <https://docs.aws.amazon.com/iot/latest/apireference/API_CertificateDescription.html#iot-Type-CertificateDescription-certificateMode certificate mode>.
registerCACertificate_certificateMode :: Lens.Lens' RegisterCACertificate (Prelude.Maybe CertificateMode)
registerCACertificate_certificateMode :: Lens' RegisterCACertificate (Maybe CertificateMode)
registerCACertificate_certificateMode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterCACertificate' {Maybe CertificateMode
certificateMode :: Maybe CertificateMode
$sel:certificateMode:RegisterCACertificate' :: RegisterCACertificate -> Maybe CertificateMode
certificateMode} -> Maybe CertificateMode
certificateMode) (\s :: RegisterCACertificate
s@RegisterCACertificate' {} Maybe CertificateMode
a -> RegisterCACertificate
s {$sel:certificateMode:RegisterCACertificate' :: Maybe CertificateMode
certificateMode = Maybe CertificateMode
a} :: RegisterCACertificate)

-- | Information about the registration configuration.
registerCACertificate_registrationConfig :: Lens.Lens' RegisterCACertificate (Prelude.Maybe RegistrationConfig)
registerCACertificate_registrationConfig :: Lens' RegisterCACertificate (Maybe RegistrationConfig)
registerCACertificate_registrationConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterCACertificate' {Maybe RegistrationConfig
registrationConfig :: Maybe RegistrationConfig
$sel:registrationConfig:RegisterCACertificate' :: RegisterCACertificate -> Maybe RegistrationConfig
registrationConfig} -> Maybe RegistrationConfig
registrationConfig) (\s :: RegisterCACertificate
s@RegisterCACertificate' {} Maybe RegistrationConfig
a -> RegisterCACertificate
s {$sel:registrationConfig:RegisterCACertificate' :: Maybe RegistrationConfig
registrationConfig = Maybe RegistrationConfig
a} :: RegisterCACertificate)

-- | A boolean value that specifies if the CA certificate is set to active.
--
-- Valid values: @ACTIVE | INACTIVE@
registerCACertificate_setAsActive :: Lens.Lens' RegisterCACertificate (Prelude.Maybe Prelude.Bool)
registerCACertificate_setAsActive :: Lens' RegisterCACertificate (Maybe Bool)
registerCACertificate_setAsActive = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterCACertificate' {Maybe Bool
setAsActive :: Maybe Bool
$sel:setAsActive:RegisterCACertificate' :: RegisterCACertificate -> Maybe Bool
setAsActive} -> Maybe Bool
setAsActive) (\s :: RegisterCACertificate
s@RegisterCACertificate' {} Maybe Bool
a -> RegisterCACertificate
s {$sel:setAsActive:RegisterCACertificate' :: Maybe Bool
setAsActive = Maybe Bool
a} :: RegisterCACertificate)

-- | Metadata which can be used to manage the CA certificate.
--
-- For URI Request parameters use format: ...key1=value1&key2=value2...
--
-- For the CLI command-line parameter use format: &&tags
-- \"key1=value1&key2=value2...\"
--
-- For the cli-input-json file use format: \"tags\":
-- \"key1=value1&key2=value2...\"
registerCACertificate_tags :: Lens.Lens' RegisterCACertificate (Prelude.Maybe [Tag])
registerCACertificate_tags :: Lens' RegisterCACertificate (Maybe [Tag])
registerCACertificate_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterCACertificate' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:RegisterCACertificate' :: RegisterCACertificate -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: RegisterCACertificate
s@RegisterCACertificate' {} Maybe [Tag]
a -> RegisterCACertificate
s {$sel:tags:RegisterCACertificate' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: RegisterCACertificate) 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 private key verification certificate. If @certificateMode@ is
-- @SNI_ONLY@, the @verificationCertificate@ field must be empty. If
-- @certificateMode@ is @DEFAULT@ or not provided, the
-- @verificationCertificate@ field must not be empty.
registerCACertificate_verificationCertificate :: Lens.Lens' RegisterCACertificate (Prelude.Maybe Prelude.Text)
registerCACertificate_verificationCertificate :: Lens' RegisterCACertificate (Maybe Text)
registerCACertificate_verificationCertificate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterCACertificate' {Maybe Text
verificationCertificate :: Maybe Text
$sel:verificationCertificate:RegisterCACertificate' :: RegisterCACertificate -> Maybe Text
verificationCertificate} -> Maybe Text
verificationCertificate) (\s :: RegisterCACertificate
s@RegisterCACertificate' {} Maybe Text
a -> RegisterCACertificate
s {$sel:verificationCertificate:RegisterCACertificate' :: Maybe Text
verificationCertificate = Maybe Text
a} :: RegisterCACertificate)

-- | The CA certificate.
registerCACertificate_caCertificate :: Lens.Lens' RegisterCACertificate Prelude.Text
registerCACertificate_caCertificate :: Lens' RegisterCACertificate Text
registerCACertificate_caCertificate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterCACertificate' {Text
caCertificate :: Text
$sel:caCertificate:RegisterCACertificate' :: RegisterCACertificate -> Text
caCertificate} -> Text
caCertificate) (\s :: RegisterCACertificate
s@RegisterCACertificate' {} Text
a -> RegisterCACertificate
s {$sel:caCertificate:RegisterCACertificate' :: Text
caCertificate = Text
a} :: RegisterCACertificate)

instance Core.AWSRequest RegisterCACertificate where
  type
    AWSResponse RegisterCACertificate =
      RegisterCACertificateResponse
  request :: (Service -> Service)
-> RegisterCACertificate -> Request RegisterCACertificate
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 RegisterCACertificate
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse RegisterCACertificate)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text -> Maybe Text -> Int -> RegisterCACertificateResponse
RegisterCACertificateResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (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 -> Either String (Maybe a)
Data..?> Key
"certificateId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable RegisterCACertificate where
  hashWithSalt :: Int -> RegisterCACertificate -> Int
hashWithSalt Int
_salt RegisterCACertificate' {Maybe Bool
Maybe [Tag]
Maybe Text
Maybe CertificateMode
Maybe RegistrationConfig
Text
caCertificate :: Text
verificationCertificate :: Maybe Text
tags :: Maybe [Tag]
setAsActive :: Maybe Bool
registrationConfig :: Maybe RegistrationConfig
certificateMode :: Maybe CertificateMode
allowAutoRegistration :: Maybe Bool
$sel:caCertificate:RegisterCACertificate' :: RegisterCACertificate -> Text
$sel:verificationCertificate:RegisterCACertificate' :: RegisterCACertificate -> Maybe Text
$sel:tags:RegisterCACertificate' :: RegisterCACertificate -> Maybe [Tag]
$sel:setAsActive:RegisterCACertificate' :: RegisterCACertificate -> Maybe Bool
$sel:registrationConfig:RegisterCACertificate' :: RegisterCACertificate -> Maybe RegistrationConfig
$sel:certificateMode:RegisterCACertificate' :: RegisterCACertificate -> Maybe CertificateMode
$sel:allowAutoRegistration:RegisterCACertificate' :: RegisterCACertificate -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
allowAutoRegistration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CertificateMode
certificateMode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RegistrationConfig
registrationConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
setAsActive
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
verificationCertificate
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
caCertificate

instance Prelude.NFData RegisterCACertificate where
  rnf :: RegisterCACertificate -> ()
rnf RegisterCACertificate' {Maybe Bool
Maybe [Tag]
Maybe Text
Maybe CertificateMode
Maybe RegistrationConfig
Text
caCertificate :: Text
verificationCertificate :: Maybe Text
tags :: Maybe [Tag]
setAsActive :: Maybe Bool
registrationConfig :: Maybe RegistrationConfig
certificateMode :: Maybe CertificateMode
allowAutoRegistration :: Maybe Bool
$sel:caCertificate:RegisterCACertificate' :: RegisterCACertificate -> Text
$sel:verificationCertificate:RegisterCACertificate' :: RegisterCACertificate -> Maybe Text
$sel:tags:RegisterCACertificate' :: RegisterCACertificate -> Maybe [Tag]
$sel:setAsActive:RegisterCACertificate' :: RegisterCACertificate -> Maybe Bool
$sel:registrationConfig:RegisterCACertificate' :: RegisterCACertificate -> Maybe RegistrationConfig
$sel:certificateMode:RegisterCACertificate' :: RegisterCACertificate -> Maybe CertificateMode
$sel:allowAutoRegistration:RegisterCACertificate' :: RegisterCACertificate -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
allowAutoRegistration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CertificateMode
certificateMode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RegistrationConfig
registrationConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
setAsActive
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
verificationCertificate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
caCertificate

instance Data.ToHeaders RegisterCACertificate where
  toHeaders :: RegisterCACertificate -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToJSON RegisterCACertificate where
  toJSON :: RegisterCACertificate -> Value
toJSON RegisterCACertificate' {Maybe Bool
Maybe [Tag]
Maybe Text
Maybe CertificateMode
Maybe RegistrationConfig
Text
caCertificate :: Text
verificationCertificate :: Maybe Text
tags :: Maybe [Tag]
setAsActive :: Maybe Bool
registrationConfig :: Maybe RegistrationConfig
certificateMode :: Maybe CertificateMode
allowAutoRegistration :: Maybe Bool
$sel:caCertificate:RegisterCACertificate' :: RegisterCACertificate -> Text
$sel:verificationCertificate:RegisterCACertificate' :: RegisterCACertificate -> Maybe Text
$sel:tags:RegisterCACertificate' :: RegisterCACertificate -> Maybe [Tag]
$sel:setAsActive:RegisterCACertificate' :: RegisterCACertificate -> Maybe Bool
$sel:registrationConfig:RegisterCACertificate' :: RegisterCACertificate -> Maybe RegistrationConfig
$sel:certificateMode:RegisterCACertificate' :: RegisterCACertificate -> Maybe CertificateMode
$sel:allowAutoRegistration:RegisterCACertificate' :: RegisterCACertificate -> Maybe Bool
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"certificateMode" 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 CertificateMode
certificateMode,
            (Key
"registrationConfig" 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 RegistrationConfig
registrationConfig,
            (Key
"tags" 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 [Tag]
tags,
            (Key
"verificationCertificate" 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 Text
verificationCertificate,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"caCertificate" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
caCertificate)
          ]
      )

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

instance Data.ToQuery RegisterCACertificate where
  toQuery :: RegisterCACertificate -> QueryString
toQuery RegisterCACertificate' {Maybe Bool
Maybe [Tag]
Maybe Text
Maybe CertificateMode
Maybe RegistrationConfig
Text
caCertificate :: Text
verificationCertificate :: Maybe Text
tags :: Maybe [Tag]
setAsActive :: Maybe Bool
registrationConfig :: Maybe RegistrationConfig
certificateMode :: Maybe CertificateMode
allowAutoRegistration :: Maybe Bool
$sel:caCertificate:RegisterCACertificate' :: RegisterCACertificate -> Text
$sel:verificationCertificate:RegisterCACertificate' :: RegisterCACertificate -> Maybe Text
$sel:tags:RegisterCACertificate' :: RegisterCACertificate -> Maybe [Tag]
$sel:setAsActive:RegisterCACertificate' :: RegisterCACertificate -> Maybe Bool
$sel:registrationConfig:RegisterCACertificate' :: RegisterCACertificate -> Maybe RegistrationConfig
$sel:certificateMode:RegisterCACertificate' :: RegisterCACertificate -> Maybe CertificateMode
$sel:allowAutoRegistration:RegisterCACertificate' :: RegisterCACertificate -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"allowAutoRegistration"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
allowAutoRegistration,
        ByteString
"setAsActive" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
setAsActive
      ]

-- | The output from the RegisterCACertificateResponse operation.
--
-- /See:/ 'newRegisterCACertificateResponse' smart constructor.
data RegisterCACertificateResponse = RegisterCACertificateResponse'
  { -- | The CA certificate ARN.
    RegisterCACertificateResponse -> Maybe Text
certificateArn :: Prelude.Maybe Prelude.Text,
    -- | The CA certificate identifier.
    RegisterCACertificateResponse -> Maybe Text
certificateId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    RegisterCACertificateResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (RegisterCACertificateResponse
-> RegisterCACertificateResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RegisterCACertificateResponse
-> RegisterCACertificateResponse -> Bool
$c/= :: RegisterCACertificateResponse
-> RegisterCACertificateResponse -> Bool
== :: RegisterCACertificateResponse
-> RegisterCACertificateResponse -> Bool
$c== :: RegisterCACertificateResponse
-> RegisterCACertificateResponse -> Bool
Prelude.Eq, ReadPrec [RegisterCACertificateResponse]
ReadPrec RegisterCACertificateResponse
Int -> ReadS RegisterCACertificateResponse
ReadS [RegisterCACertificateResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RegisterCACertificateResponse]
$creadListPrec :: ReadPrec [RegisterCACertificateResponse]
readPrec :: ReadPrec RegisterCACertificateResponse
$creadPrec :: ReadPrec RegisterCACertificateResponse
readList :: ReadS [RegisterCACertificateResponse]
$creadList :: ReadS [RegisterCACertificateResponse]
readsPrec :: Int -> ReadS RegisterCACertificateResponse
$creadsPrec :: Int -> ReadS RegisterCACertificateResponse
Prelude.Read, Int -> RegisterCACertificateResponse -> ShowS
[RegisterCACertificateResponse] -> ShowS
RegisterCACertificateResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RegisterCACertificateResponse] -> ShowS
$cshowList :: [RegisterCACertificateResponse] -> ShowS
show :: RegisterCACertificateResponse -> String
$cshow :: RegisterCACertificateResponse -> String
showsPrec :: Int -> RegisterCACertificateResponse -> ShowS
$cshowsPrec :: Int -> RegisterCACertificateResponse -> ShowS
Prelude.Show, forall x.
Rep RegisterCACertificateResponse x
-> RegisterCACertificateResponse
forall x.
RegisterCACertificateResponse
-> Rep RegisterCACertificateResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RegisterCACertificateResponse x
-> RegisterCACertificateResponse
$cfrom :: forall x.
RegisterCACertificateResponse
-> Rep RegisterCACertificateResponse x
Prelude.Generic)

-- |
-- Create a value of 'RegisterCACertificateResponse' 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', 'registerCACertificateResponse_certificateArn' - The CA certificate ARN.
--
-- 'certificateId', 'registerCACertificateResponse_certificateId' - The CA certificate identifier.
--
-- 'httpStatus', 'registerCACertificateResponse_httpStatus' - The response's http status code.
newRegisterCACertificateResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  RegisterCACertificateResponse
newRegisterCACertificateResponse :: Int -> RegisterCACertificateResponse
newRegisterCACertificateResponse Int
pHttpStatus_ =
  RegisterCACertificateResponse'
    { $sel:certificateArn:RegisterCACertificateResponse' :: Maybe Text
certificateArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:certificateId:RegisterCACertificateResponse' :: Maybe Text
certificateId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:RegisterCACertificateResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The CA certificate ARN.
registerCACertificateResponse_certificateArn :: Lens.Lens' RegisterCACertificateResponse (Prelude.Maybe Prelude.Text)
registerCACertificateResponse_certificateArn :: Lens' RegisterCACertificateResponse (Maybe Text)
registerCACertificateResponse_certificateArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterCACertificateResponse' {Maybe Text
certificateArn :: Maybe Text
$sel:certificateArn:RegisterCACertificateResponse' :: RegisterCACertificateResponse -> Maybe Text
certificateArn} -> Maybe Text
certificateArn) (\s :: RegisterCACertificateResponse
s@RegisterCACertificateResponse' {} Maybe Text
a -> RegisterCACertificateResponse
s {$sel:certificateArn:RegisterCACertificateResponse' :: Maybe Text
certificateArn = Maybe Text
a} :: RegisterCACertificateResponse)

-- | The CA certificate identifier.
registerCACertificateResponse_certificateId :: Lens.Lens' RegisterCACertificateResponse (Prelude.Maybe Prelude.Text)
registerCACertificateResponse_certificateId :: Lens' RegisterCACertificateResponse (Maybe Text)
registerCACertificateResponse_certificateId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterCACertificateResponse' {Maybe Text
certificateId :: Maybe Text
$sel:certificateId:RegisterCACertificateResponse' :: RegisterCACertificateResponse -> Maybe Text
certificateId} -> Maybe Text
certificateId) (\s :: RegisterCACertificateResponse
s@RegisterCACertificateResponse' {} Maybe Text
a -> RegisterCACertificateResponse
s {$sel:certificateId:RegisterCACertificateResponse' :: Maybe Text
certificateId = Maybe Text
a} :: RegisterCACertificateResponse)

-- | The response's http status code.
registerCACertificateResponse_httpStatus :: Lens.Lens' RegisterCACertificateResponse Prelude.Int
registerCACertificateResponse_httpStatus :: Lens' RegisterCACertificateResponse Int
registerCACertificateResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterCACertificateResponse' {Int
httpStatus :: Int
$sel:httpStatus:RegisterCACertificateResponse' :: RegisterCACertificateResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: RegisterCACertificateResponse
s@RegisterCACertificateResponse' {} Int
a -> RegisterCACertificateResponse
s {$sel:httpStatus:RegisterCACertificateResponse' :: Int
httpStatus = Int
a} :: RegisterCACertificateResponse)

instance Prelude.NFData RegisterCACertificateResponse where
  rnf :: RegisterCACertificateResponse -> ()
rnf RegisterCACertificateResponse' {Int
Maybe Text
httpStatus :: Int
certificateId :: Maybe Text
certificateArn :: Maybe Text
$sel:httpStatus:RegisterCACertificateResponse' :: RegisterCACertificateResponse -> Int
$sel:certificateId:RegisterCACertificateResponse' :: RegisterCACertificateResponse -> Maybe Text
$sel:certificateArn:RegisterCACertificateResponse' :: RegisterCACertificateResponse -> 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
certificateId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus