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

    -- * Request Lenses
    disableClientAuthentication_directoryId,
    disableClientAuthentication_type,

    -- * Destructuring the Response
    DisableClientAuthenticationResponse (..),
    newDisableClientAuthenticationResponse,

    -- * Response Lenses
    disableClientAuthenticationResponse_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:/ 'newDisableClientAuthentication' smart constructor.
data DisableClientAuthentication = DisableClientAuthentication'
  { -- | The identifier of the directory
    DisableClientAuthentication -> Text
directoryId :: Prelude.Text,
    -- | The type of client authentication to disable. Currently, only the
    -- parameter, @SmartCard@ is supported.
    DisableClientAuthentication -> ClientAuthenticationType
type' :: ClientAuthenticationType
  }
  deriving (DisableClientAuthentication -> DisableClientAuthentication -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisableClientAuthentication -> DisableClientAuthentication -> Bool
$c/= :: DisableClientAuthentication -> DisableClientAuthentication -> Bool
== :: DisableClientAuthentication -> DisableClientAuthentication -> Bool
$c== :: DisableClientAuthentication -> DisableClientAuthentication -> Bool
Prelude.Eq, ReadPrec [DisableClientAuthentication]
ReadPrec DisableClientAuthentication
Int -> ReadS DisableClientAuthentication
ReadS [DisableClientAuthentication]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DisableClientAuthentication]
$creadListPrec :: ReadPrec [DisableClientAuthentication]
readPrec :: ReadPrec DisableClientAuthentication
$creadPrec :: ReadPrec DisableClientAuthentication
readList :: ReadS [DisableClientAuthentication]
$creadList :: ReadS [DisableClientAuthentication]
readsPrec :: Int -> ReadS DisableClientAuthentication
$creadsPrec :: Int -> ReadS DisableClientAuthentication
Prelude.Read, Int -> DisableClientAuthentication -> ShowS
[DisableClientAuthentication] -> ShowS
DisableClientAuthentication -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisableClientAuthentication] -> ShowS
$cshowList :: [DisableClientAuthentication] -> ShowS
show :: DisableClientAuthentication -> String
$cshow :: DisableClientAuthentication -> String
showsPrec :: Int -> DisableClientAuthentication -> ShowS
$cshowsPrec :: Int -> DisableClientAuthentication -> ShowS
Prelude.Show, forall x.
Rep DisableClientAuthentication x -> DisableClientAuthentication
forall x.
DisableClientAuthentication -> Rep DisableClientAuthentication x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DisableClientAuthentication x -> DisableClientAuthentication
$cfrom :: forall x.
DisableClientAuthentication -> Rep DisableClientAuthentication x
Prelude.Generic)

-- |
-- Create a value of 'DisableClientAuthentication' 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', 'disableClientAuthentication_directoryId' - The identifier of the directory
--
-- 'type'', 'disableClientAuthentication_type' - The type of client authentication to disable. Currently, only the
-- parameter, @SmartCard@ is supported.
newDisableClientAuthentication ::
  -- | 'directoryId'
  Prelude.Text ->
  -- | 'type''
  ClientAuthenticationType ->
  DisableClientAuthentication
newDisableClientAuthentication :: Text -> ClientAuthenticationType -> DisableClientAuthentication
newDisableClientAuthentication Text
pDirectoryId_ ClientAuthenticationType
pType_ =
  DisableClientAuthentication'
    { $sel:directoryId:DisableClientAuthentication' :: Text
directoryId =
        Text
pDirectoryId_,
      $sel:type':DisableClientAuthentication' :: ClientAuthenticationType
type' = ClientAuthenticationType
pType_
    }

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

-- | The type of client authentication to disable. Currently, only the
-- parameter, @SmartCard@ is supported.
disableClientAuthentication_type :: Lens.Lens' DisableClientAuthentication ClientAuthenticationType
disableClientAuthentication_type :: Lens' DisableClientAuthentication ClientAuthenticationType
disableClientAuthentication_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisableClientAuthentication' {ClientAuthenticationType
type' :: ClientAuthenticationType
$sel:type':DisableClientAuthentication' :: DisableClientAuthentication -> ClientAuthenticationType
type'} -> ClientAuthenticationType
type') (\s :: DisableClientAuthentication
s@DisableClientAuthentication' {} ClientAuthenticationType
a -> DisableClientAuthentication
s {$sel:type':DisableClientAuthentication' :: ClientAuthenticationType
type' = ClientAuthenticationType
a} :: DisableClientAuthentication)

instance Core.AWSRequest DisableClientAuthentication where
  type
    AWSResponse DisableClientAuthentication =
      DisableClientAuthenticationResponse
  request :: (Service -> Service)
-> DisableClientAuthentication
-> Request DisableClientAuthentication
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 DisableClientAuthentication
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DisableClientAuthentication)))
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 -> DisableClientAuthenticationResponse
DisableClientAuthenticationResponse'
            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 DisableClientAuthentication where
  hashWithSalt :: Int -> DisableClientAuthentication -> Int
hashWithSalt Int
_salt DisableClientAuthentication' {Text
ClientAuthenticationType
type' :: ClientAuthenticationType
directoryId :: Text
$sel:type':DisableClientAuthentication' :: DisableClientAuthentication -> ClientAuthenticationType
$sel:directoryId:DisableClientAuthentication' :: DisableClientAuthentication -> 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 DisableClientAuthentication where
  rnf :: DisableClientAuthentication -> ()
rnf DisableClientAuthentication' {Text
ClientAuthenticationType
type' :: ClientAuthenticationType
directoryId :: Text
$sel:type':DisableClientAuthentication' :: DisableClientAuthentication -> ClientAuthenticationType
$sel:directoryId:DisableClientAuthentication' :: DisableClientAuthentication -> 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 DisableClientAuthentication where
  toHeaders :: DisableClientAuthentication -> 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.DisableClientAuthentication" ::
                          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 DisableClientAuthentication where
  toJSON :: DisableClientAuthentication -> Value
toJSON DisableClientAuthentication' {Text
ClientAuthenticationType
type' :: ClientAuthenticationType
directoryId :: Text
$sel:type':DisableClientAuthentication' :: DisableClientAuthentication -> ClientAuthenticationType
$sel:directoryId:DisableClientAuthentication' :: DisableClientAuthentication -> 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 DisableClientAuthentication where
  toPath :: DisableClientAuthentication -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

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

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

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