{-# 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.EnableClientAuthentication
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Enables alternative client authentication methods for the specified
-- directory.
module Amazonka.DirectoryService.EnableClientAuthentication
  ( -- * Creating a Request
    EnableClientAuthentication (..),
    newEnableClientAuthentication,

    -- * Request Lenses
    enableClientAuthentication_directoryId,
    enableClientAuthentication_type,

    -- * Destructuring the Response
    EnableClientAuthenticationResponse (..),
    newEnableClientAuthenticationResponse,

    -- * Response Lenses
    enableClientAuthenticationResponse_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:/ 'newEnableClientAuthentication' smart constructor.
data EnableClientAuthentication = EnableClientAuthentication'
  { -- | The identifier of the specified directory.
    EnableClientAuthentication -> Text
directoryId :: Prelude.Text,
    -- | The type of client authentication to enable. Currently only the value
    -- @SmartCard@ is supported. Smart card authentication in AD Connector
    -- requires that you enable Kerberos Constrained Delegation for the Service
    -- User to the LDAP service in your self-managed AD.
    EnableClientAuthentication -> ClientAuthenticationType
type' :: ClientAuthenticationType
  }
  deriving (EnableClientAuthentication -> EnableClientAuthentication -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnableClientAuthentication -> EnableClientAuthentication -> Bool
$c/= :: EnableClientAuthentication -> EnableClientAuthentication -> Bool
== :: EnableClientAuthentication -> EnableClientAuthentication -> Bool
$c== :: EnableClientAuthentication -> EnableClientAuthentication -> Bool
Prelude.Eq, ReadPrec [EnableClientAuthentication]
ReadPrec EnableClientAuthentication
Int -> ReadS EnableClientAuthentication
ReadS [EnableClientAuthentication]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnableClientAuthentication]
$creadListPrec :: ReadPrec [EnableClientAuthentication]
readPrec :: ReadPrec EnableClientAuthentication
$creadPrec :: ReadPrec EnableClientAuthentication
readList :: ReadS [EnableClientAuthentication]
$creadList :: ReadS [EnableClientAuthentication]
readsPrec :: Int -> ReadS EnableClientAuthentication
$creadsPrec :: Int -> ReadS EnableClientAuthentication
Prelude.Read, Int -> EnableClientAuthentication -> ShowS
[EnableClientAuthentication] -> ShowS
EnableClientAuthentication -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EnableClientAuthentication] -> ShowS
$cshowList :: [EnableClientAuthentication] -> ShowS
show :: EnableClientAuthentication -> String
$cshow :: EnableClientAuthentication -> String
showsPrec :: Int -> EnableClientAuthentication -> ShowS
$cshowsPrec :: Int -> EnableClientAuthentication -> ShowS
Prelude.Show, forall x.
Rep EnableClientAuthentication x -> EnableClientAuthentication
forall x.
EnableClientAuthentication -> Rep EnableClientAuthentication x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep EnableClientAuthentication x -> EnableClientAuthentication
$cfrom :: forall x.
EnableClientAuthentication -> Rep EnableClientAuthentication x
Prelude.Generic)

-- |
-- Create a value of 'EnableClientAuthentication' 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:
--
-- 'directoryId', 'enableClientAuthentication_directoryId' - The identifier of the specified directory.
--
-- 'type'', 'enableClientAuthentication_type' - The type of client authentication to enable. Currently only the value
-- @SmartCard@ is supported. Smart card authentication in AD Connector
-- requires that you enable Kerberos Constrained Delegation for the Service
-- User to the LDAP service in your self-managed AD.
newEnableClientAuthentication ::
  -- | 'directoryId'
  Prelude.Text ->
  -- | 'type''
  ClientAuthenticationType ->
  EnableClientAuthentication
newEnableClientAuthentication :: Text -> ClientAuthenticationType -> EnableClientAuthentication
newEnableClientAuthentication Text
pDirectoryId_ ClientAuthenticationType
pType_ =
  EnableClientAuthentication'
    { $sel:directoryId:EnableClientAuthentication' :: Text
directoryId =
        Text
pDirectoryId_,
      $sel:type':EnableClientAuthentication' :: ClientAuthenticationType
type' = ClientAuthenticationType
pType_
    }

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

-- | The type of client authentication to enable. Currently only the value
-- @SmartCard@ is supported. Smart card authentication in AD Connector
-- requires that you enable Kerberos Constrained Delegation for the Service
-- User to the LDAP service in your self-managed AD.
enableClientAuthentication_type :: Lens.Lens' EnableClientAuthentication ClientAuthenticationType
enableClientAuthentication_type :: Lens' EnableClientAuthentication ClientAuthenticationType
enableClientAuthentication_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnableClientAuthentication' {ClientAuthenticationType
type' :: ClientAuthenticationType
$sel:type':EnableClientAuthentication' :: EnableClientAuthentication -> ClientAuthenticationType
type'} -> ClientAuthenticationType
type') (\s :: EnableClientAuthentication
s@EnableClientAuthentication' {} ClientAuthenticationType
a -> EnableClientAuthentication
s {$sel:type':EnableClientAuthentication' :: ClientAuthenticationType
type' = ClientAuthenticationType
a} :: EnableClientAuthentication)

instance Core.AWSRequest EnableClientAuthentication where
  type
    AWSResponse EnableClientAuthentication =
      EnableClientAuthenticationResponse
  request :: (Service -> Service)
-> EnableClientAuthentication -> Request EnableClientAuthentication
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 EnableClientAuthentication
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse EnableClientAuthentication)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> EnableClientAuthenticationResponse
EnableClientAuthenticationResponse'
            forall (f :: * -> *) a b. Functor 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 EnableClientAuthentication where
  hashWithSalt :: Int -> EnableClientAuthentication -> Int
hashWithSalt Int
_salt EnableClientAuthentication' {Text
ClientAuthenticationType
type' :: ClientAuthenticationType
directoryId :: Text
$sel:type':EnableClientAuthentication' :: EnableClientAuthentication -> ClientAuthenticationType
$sel:directoryId:EnableClientAuthentication' :: EnableClientAuthentication -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
directoryId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ClientAuthenticationType
type'

instance Prelude.NFData EnableClientAuthentication where
  rnf :: EnableClientAuthentication -> ()
rnf EnableClientAuthentication' {Text
ClientAuthenticationType
type' :: ClientAuthenticationType
directoryId :: Text
$sel:type':EnableClientAuthentication' :: EnableClientAuthentication -> ClientAuthenticationType
$sel:directoryId:EnableClientAuthentication' :: EnableClientAuthentication -> Text
..} =
    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 ClientAuthenticationType
type'

instance Data.ToHeaders EnableClientAuthentication where
  toHeaders :: EnableClientAuthentication -> 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.EnableClientAuthentication" ::
                          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 EnableClientAuthentication where
  toJSON :: EnableClientAuthentication -> Value
toJSON EnableClientAuthentication' {Text
ClientAuthenticationType
type' :: ClientAuthenticationType
directoryId :: Text
$sel:type':EnableClientAuthentication' :: EnableClientAuthentication -> ClientAuthenticationType
$sel:directoryId:EnableClientAuthentication' :: EnableClientAuthentication -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ 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
"Type" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ClientAuthenticationType
type')
          ]
      )

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

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

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

-- |
-- Create a value of 'EnableClientAuthenticationResponse' 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:
--
-- 'httpStatus', 'enableClientAuthenticationResponse_httpStatus' - The response's http status code.
newEnableClientAuthenticationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  EnableClientAuthenticationResponse
newEnableClientAuthenticationResponse :: Int -> EnableClientAuthenticationResponse
newEnableClientAuthenticationResponse Int
pHttpStatus_ =
  EnableClientAuthenticationResponse'
    { $sel:httpStatus:EnableClientAuthenticationResponse' :: Int
httpStatus =
        Int
pHttpStatus_
    }

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

instance
  Prelude.NFData
    EnableClientAuthenticationResponse
  where
  rnf :: EnableClientAuthenticationResponse -> ()
rnf EnableClientAuthenticationResponse' {Int
httpStatus :: Int
$sel:httpStatus:EnableClientAuthenticationResponse' :: EnableClientAuthenticationResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus