{-# 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.DirectoryService.RegisterCertificate
-- 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 certificate for a secure LDAP or client certificate
-- authentication.
module Amazonka.DirectoryService.RegisterCertificate
  ( -- * Creating a Request
    RegisterCertificate (..),
    newRegisterCertificate,

    -- * Request Lenses
    registerCertificate_clientCertAuthSettings,
    registerCertificate_type,
    registerCertificate_directoryId,
    registerCertificate_certificateData,

    -- * Destructuring the Response
    RegisterCertificateResponse (..),
    newRegisterCertificateResponse,

    -- * Response Lenses
    registerCertificateResponse_certificateId,
    registerCertificateResponse_httpStatus,
  )
where

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

-- | /See:/ 'newRegisterCertificate' smart constructor.
data RegisterCertificate = RegisterCertificate'
  { -- | A @ClientCertAuthSettings@ object that contains client certificate
    -- authentication settings.
    RegisterCertificate -> Maybe ClientCertAuthSettings
clientCertAuthSettings :: Prelude.Maybe ClientCertAuthSettings,
    -- | The function that the registered certificate performs. Valid values
    -- include @ClientLDAPS@ or @ClientCertAuth@. The default value is
    -- @ClientLDAPS@.
    RegisterCertificate -> Maybe CertificateType
type' :: Prelude.Maybe CertificateType,
    -- | The identifier of the directory.
    RegisterCertificate -> Text
directoryId :: Prelude.Text,
    -- | The certificate PEM string that needs to be registered.
    RegisterCertificate -> Text
certificateData :: Prelude.Text
  }
  deriving (RegisterCertificate -> RegisterCertificate -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RegisterCertificate -> RegisterCertificate -> Bool
$c/= :: RegisterCertificate -> RegisterCertificate -> Bool
== :: RegisterCertificate -> RegisterCertificate -> Bool
$c== :: RegisterCertificate -> RegisterCertificate -> Bool
Prelude.Eq, ReadPrec [RegisterCertificate]
ReadPrec RegisterCertificate
Int -> ReadS RegisterCertificate
ReadS [RegisterCertificate]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RegisterCertificate]
$creadListPrec :: ReadPrec [RegisterCertificate]
readPrec :: ReadPrec RegisterCertificate
$creadPrec :: ReadPrec RegisterCertificate
readList :: ReadS [RegisterCertificate]
$creadList :: ReadS [RegisterCertificate]
readsPrec :: Int -> ReadS RegisterCertificate
$creadsPrec :: Int -> ReadS RegisterCertificate
Prelude.Read, Int -> RegisterCertificate -> ShowS
[RegisterCertificate] -> ShowS
RegisterCertificate -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RegisterCertificate] -> ShowS
$cshowList :: [RegisterCertificate] -> ShowS
show :: RegisterCertificate -> String
$cshow :: RegisterCertificate -> String
showsPrec :: Int -> RegisterCertificate -> ShowS
$cshowsPrec :: Int -> RegisterCertificate -> ShowS
Prelude.Show, forall x. Rep RegisterCertificate x -> RegisterCertificate
forall x. RegisterCertificate -> Rep RegisterCertificate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RegisterCertificate x -> RegisterCertificate
$cfrom :: forall x. RegisterCertificate -> Rep RegisterCertificate x
Prelude.Generic)

-- |
-- Create a value of 'RegisterCertificate' 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:
--
-- 'clientCertAuthSettings', 'registerCertificate_clientCertAuthSettings' - A @ClientCertAuthSettings@ object that contains client certificate
-- authentication settings.
--
-- 'type'', 'registerCertificate_type' - The function that the registered certificate performs. Valid values
-- include @ClientLDAPS@ or @ClientCertAuth@. The default value is
-- @ClientLDAPS@.
--
-- 'directoryId', 'registerCertificate_directoryId' - The identifier of the directory.
--
-- 'certificateData', 'registerCertificate_certificateData' - The certificate PEM string that needs to be registered.
newRegisterCertificate ::
  -- | 'directoryId'
  Prelude.Text ->
  -- | 'certificateData'
  Prelude.Text ->
  RegisterCertificate
newRegisterCertificate :: Text -> Text -> RegisterCertificate
newRegisterCertificate
  Text
pDirectoryId_
  Text
pCertificateData_ =
    RegisterCertificate'
      { $sel:clientCertAuthSettings:RegisterCertificate' :: Maybe ClientCertAuthSettings
clientCertAuthSettings =
          forall a. Maybe a
Prelude.Nothing,
        $sel:type':RegisterCertificate' :: Maybe CertificateType
type' = forall a. Maybe a
Prelude.Nothing,
        $sel:directoryId:RegisterCertificate' :: Text
directoryId = Text
pDirectoryId_,
        $sel:certificateData:RegisterCertificate' :: Text
certificateData = Text
pCertificateData_
      }

-- | A @ClientCertAuthSettings@ object that contains client certificate
-- authentication settings.
registerCertificate_clientCertAuthSettings :: Lens.Lens' RegisterCertificate (Prelude.Maybe ClientCertAuthSettings)
registerCertificate_clientCertAuthSettings :: Lens' RegisterCertificate (Maybe ClientCertAuthSettings)
registerCertificate_clientCertAuthSettings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterCertificate' {Maybe ClientCertAuthSettings
clientCertAuthSettings :: Maybe ClientCertAuthSettings
$sel:clientCertAuthSettings:RegisterCertificate' :: RegisterCertificate -> Maybe ClientCertAuthSettings
clientCertAuthSettings} -> Maybe ClientCertAuthSettings
clientCertAuthSettings) (\s :: RegisterCertificate
s@RegisterCertificate' {} Maybe ClientCertAuthSettings
a -> RegisterCertificate
s {$sel:clientCertAuthSettings:RegisterCertificate' :: Maybe ClientCertAuthSettings
clientCertAuthSettings = Maybe ClientCertAuthSettings
a} :: RegisterCertificate)

-- | The function that the registered certificate performs. Valid values
-- include @ClientLDAPS@ or @ClientCertAuth@. The default value is
-- @ClientLDAPS@.
registerCertificate_type :: Lens.Lens' RegisterCertificate (Prelude.Maybe CertificateType)
registerCertificate_type :: Lens' RegisterCertificate (Maybe CertificateType)
registerCertificate_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterCertificate' {Maybe CertificateType
type' :: Maybe CertificateType
$sel:type':RegisterCertificate' :: RegisterCertificate -> Maybe CertificateType
type'} -> Maybe CertificateType
type') (\s :: RegisterCertificate
s@RegisterCertificate' {} Maybe CertificateType
a -> RegisterCertificate
s {$sel:type':RegisterCertificate' :: Maybe CertificateType
type' = Maybe CertificateType
a} :: RegisterCertificate)

-- | The identifier of the directory.
registerCertificate_directoryId :: Lens.Lens' RegisterCertificate Prelude.Text
registerCertificate_directoryId :: Lens' RegisterCertificate Text
registerCertificate_directoryId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterCertificate' {Text
directoryId :: Text
$sel:directoryId:RegisterCertificate' :: RegisterCertificate -> Text
directoryId} -> Text
directoryId) (\s :: RegisterCertificate
s@RegisterCertificate' {} Text
a -> RegisterCertificate
s {$sel:directoryId:RegisterCertificate' :: Text
directoryId = Text
a} :: RegisterCertificate)

-- | The certificate PEM string that needs to be registered.
registerCertificate_certificateData :: Lens.Lens' RegisterCertificate Prelude.Text
registerCertificate_certificateData :: Lens' RegisterCertificate Text
registerCertificate_certificateData = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterCertificate' {Text
certificateData :: Text
$sel:certificateData:RegisterCertificate' :: RegisterCertificate -> Text
certificateData} -> Text
certificateData) (\s :: RegisterCertificate
s@RegisterCertificate' {} Text
a -> RegisterCertificate
s {$sel:certificateData:RegisterCertificate' :: Text
certificateData = Text
a} :: RegisterCertificate)

instance Core.AWSRequest RegisterCertificate where
  type
    AWSResponse RegisterCertificate =
      RegisterCertificateResponse
  request :: (Service -> Service)
-> RegisterCertificate -> Request RegisterCertificate
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 RegisterCertificate
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse RegisterCertificate)))
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 -> Int -> RegisterCertificateResponse
RegisterCertificateResponse'
            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
"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 RegisterCertificate where
  hashWithSalt :: Int -> RegisterCertificate -> Int
hashWithSalt Int
_salt RegisterCertificate' {Maybe CertificateType
Maybe ClientCertAuthSettings
Text
certificateData :: Text
directoryId :: Text
type' :: Maybe CertificateType
clientCertAuthSettings :: Maybe ClientCertAuthSettings
$sel:certificateData:RegisterCertificate' :: RegisterCertificate -> Text
$sel:directoryId:RegisterCertificate' :: RegisterCertificate -> Text
$sel:type':RegisterCertificate' :: RegisterCertificate -> Maybe CertificateType
$sel:clientCertAuthSettings:RegisterCertificate' :: RegisterCertificate -> Maybe ClientCertAuthSettings
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ClientCertAuthSettings
clientCertAuthSettings
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CertificateType
type'
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
directoryId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
certificateData

instance Prelude.NFData RegisterCertificate where
  rnf :: RegisterCertificate -> ()
rnf RegisterCertificate' {Maybe CertificateType
Maybe ClientCertAuthSettings
Text
certificateData :: Text
directoryId :: Text
type' :: Maybe CertificateType
clientCertAuthSettings :: Maybe ClientCertAuthSettings
$sel:certificateData:RegisterCertificate' :: RegisterCertificate -> Text
$sel:directoryId:RegisterCertificate' :: RegisterCertificate -> Text
$sel:type':RegisterCertificate' :: RegisterCertificate -> Maybe CertificateType
$sel:clientCertAuthSettings:RegisterCertificate' :: RegisterCertificate -> Maybe ClientCertAuthSettings
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ClientCertAuthSettings
clientCertAuthSettings
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CertificateType
type'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
directoryId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
certificateData

instance Data.ToHeaders RegisterCertificate where
  toHeaders :: RegisterCertificate -> ResponseHeaders
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 -> ResponseHeaders
Data.=# ( ByteString
"DirectoryService_20150416.RegisterCertificate" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON RegisterCertificate where
  toJSON :: RegisterCertificate -> Value
toJSON RegisterCertificate' {Maybe CertificateType
Maybe ClientCertAuthSettings
Text
certificateData :: Text
directoryId :: Text
type' :: Maybe CertificateType
clientCertAuthSettings :: Maybe ClientCertAuthSettings
$sel:certificateData:RegisterCertificate' :: RegisterCertificate -> Text
$sel:directoryId:RegisterCertificate' :: RegisterCertificate -> Text
$sel:type':RegisterCertificate' :: RegisterCertificate -> Maybe CertificateType
$sel:clientCertAuthSettings:RegisterCertificate' :: RegisterCertificate -> Maybe ClientCertAuthSettings
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ClientCertAuthSettings" 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 ClientCertAuthSettings
clientCertAuthSettings,
            (Key
"Type" 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 CertificateType
type',
            forall a. a -> Maybe a
Prelude.Just (Key
"DirectoryId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
directoryId),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"CertificateData" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
certificateData)
          ]
      )

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

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

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

-- |
-- Create a value of 'RegisterCertificateResponse' 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:
--
-- 'certificateId', 'registerCertificateResponse_certificateId' - The identifier of the certificate.
--
-- 'httpStatus', 'registerCertificateResponse_httpStatus' - The response's http status code.
newRegisterCertificateResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  RegisterCertificateResponse
newRegisterCertificateResponse :: Int -> RegisterCertificateResponse
newRegisterCertificateResponse Int
pHttpStatus_ =
  RegisterCertificateResponse'
    { $sel:certificateId:RegisterCertificateResponse' :: Maybe Text
certificateId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:RegisterCertificateResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

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

instance Prelude.NFData RegisterCertificateResponse where
  rnf :: RegisterCertificateResponse -> ()
rnf RegisterCertificateResponse' {Int
Maybe Text
httpStatus :: Int
certificateId :: Maybe Text
$sel:httpStatus:RegisterCertificateResponse' :: RegisterCertificateResponse -> Int
$sel:certificateId:RegisterCertificateResponse' :: RegisterCertificateResponse -> Maybe Text
..} =
    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