{-# 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.DescribeClientAuthenticationSettings
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves information about the type of client authentication for the
-- specified directory, if the type is specified. If no type is specified,
-- information about all client authentication types that are supported for
-- the specified directory is retrieved. Currently, only @SmartCard@ is
-- supported.
--
-- This operation returns paginated results.
module Amazonka.DirectoryService.DescribeClientAuthenticationSettings
  ( -- * Creating a Request
    DescribeClientAuthenticationSettings (..),
    newDescribeClientAuthenticationSettings,

    -- * Request Lenses
    describeClientAuthenticationSettings_limit,
    describeClientAuthenticationSettings_nextToken,
    describeClientAuthenticationSettings_type,
    describeClientAuthenticationSettings_directoryId,

    -- * Destructuring the Response
    DescribeClientAuthenticationSettingsResponse (..),
    newDescribeClientAuthenticationSettingsResponse,

    -- * Response Lenses
    describeClientAuthenticationSettingsResponse_clientAuthenticationSettingsInfo,
    describeClientAuthenticationSettingsResponse_nextToken,
    describeClientAuthenticationSettingsResponse_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:/ 'newDescribeClientAuthenticationSettings' smart constructor.
data DescribeClientAuthenticationSettings = DescribeClientAuthenticationSettings'
  { -- | The maximum number of items to return. If this value is zero, the
    -- maximum number of items is specified by the limitations of the
    -- operation.
    DescribeClientAuthenticationSettings -> Maybe Natural
limit :: Prelude.Maybe Prelude.Natural,
    -- | The /DescribeClientAuthenticationSettingsResult.NextToken/ value from a
    -- previous call to DescribeClientAuthenticationSettings. Pass null if this
    -- is the first call.
    DescribeClientAuthenticationSettings -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The type of client authentication for which to retrieve information. If
    -- no type is specified, a list of all client authentication types that are
    -- supported for the specified directory is retrieved.
    DescribeClientAuthenticationSettings
-> Maybe ClientAuthenticationType
type' :: Prelude.Maybe ClientAuthenticationType,
    -- | The identifier of the directory for which to retrieve information.
    DescribeClientAuthenticationSettings -> Text
directoryId :: Prelude.Text
  }
  deriving (DescribeClientAuthenticationSettings
-> DescribeClientAuthenticationSettings -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeClientAuthenticationSettings
-> DescribeClientAuthenticationSettings -> Bool
$c/= :: DescribeClientAuthenticationSettings
-> DescribeClientAuthenticationSettings -> Bool
== :: DescribeClientAuthenticationSettings
-> DescribeClientAuthenticationSettings -> Bool
$c== :: DescribeClientAuthenticationSettings
-> DescribeClientAuthenticationSettings -> Bool
Prelude.Eq, ReadPrec [DescribeClientAuthenticationSettings]
ReadPrec DescribeClientAuthenticationSettings
Int -> ReadS DescribeClientAuthenticationSettings
ReadS [DescribeClientAuthenticationSettings]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeClientAuthenticationSettings]
$creadListPrec :: ReadPrec [DescribeClientAuthenticationSettings]
readPrec :: ReadPrec DescribeClientAuthenticationSettings
$creadPrec :: ReadPrec DescribeClientAuthenticationSettings
readList :: ReadS [DescribeClientAuthenticationSettings]
$creadList :: ReadS [DescribeClientAuthenticationSettings]
readsPrec :: Int -> ReadS DescribeClientAuthenticationSettings
$creadsPrec :: Int -> ReadS DescribeClientAuthenticationSettings
Prelude.Read, Int -> DescribeClientAuthenticationSettings -> ShowS
[DescribeClientAuthenticationSettings] -> ShowS
DescribeClientAuthenticationSettings -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeClientAuthenticationSettings] -> ShowS
$cshowList :: [DescribeClientAuthenticationSettings] -> ShowS
show :: DescribeClientAuthenticationSettings -> String
$cshow :: DescribeClientAuthenticationSettings -> String
showsPrec :: Int -> DescribeClientAuthenticationSettings -> ShowS
$cshowsPrec :: Int -> DescribeClientAuthenticationSettings -> ShowS
Prelude.Show, forall x.
Rep DescribeClientAuthenticationSettings x
-> DescribeClientAuthenticationSettings
forall x.
DescribeClientAuthenticationSettings
-> Rep DescribeClientAuthenticationSettings x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeClientAuthenticationSettings x
-> DescribeClientAuthenticationSettings
$cfrom :: forall x.
DescribeClientAuthenticationSettings
-> Rep DescribeClientAuthenticationSettings x
Prelude.Generic)

-- |
-- Create a value of 'DescribeClientAuthenticationSettings' 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:
--
-- 'limit', 'describeClientAuthenticationSettings_limit' - The maximum number of items to return. If this value is zero, the
-- maximum number of items is specified by the limitations of the
-- operation.
--
-- 'nextToken', 'describeClientAuthenticationSettings_nextToken' - The /DescribeClientAuthenticationSettingsResult.NextToken/ value from a
-- previous call to DescribeClientAuthenticationSettings. Pass null if this
-- is the first call.
--
-- 'type'', 'describeClientAuthenticationSettings_type' - The type of client authentication for which to retrieve information. If
-- no type is specified, a list of all client authentication types that are
-- supported for the specified directory is retrieved.
--
-- 'directoryId', 'describeClientAuthenticationSettings_directoryId' - The identifier of the directory for which to retrieve information.
newDescribeClientAuthenticationSettings ::
  -- | 'directoryId'
  Prelude.Text ->
  DescribeClientAuthenticationSettings
newDescribeClientAuthenticationSettings :: Text -> DescribeClientAuthenticationSettings
newDescribeClientAuthenticationSettings Text
pDirectoryId_ =
  DescribeClientAuthenticationSettings'
    { $sel:limit:DescribeClientAuthenticationSettings' :: Maybe Natural
limit =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:DescribeClientAuthenticationSettings' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:type':DescribeClientAuthenticationSettings' :: Maybe ClientAuthenticationType
type' = forall a. Maybe a
Prelude.Nothing,
      $sel:directoryId:DescribeClientAuthenticationSettings' :: Text
directoryId = Text
pDirectoryId_
    }

-- | The maximum number of items to return. If this value is zero, the
-- maximum number of items is specified by the limitations of the
-- operation.
describeClientAuthenticationSettings_limit :: Lens.Lens' DescribeClientAuthenticationSettings (Prelude.Maybe Prelude.Natural)
describeClientAuthenticationSettings_limit :: Lens' DescribeClientAuthenticationSettings (Maybe Natural)
describeClientAuthenticationSettings_limit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeClientAuthenticationSettings' {Maybe Natural
limit :: Maybe Natural
$sel:limit:DescribeClientAuthenticationSettings' :: DescribeClientAuthenticationSettings -> Maybe Natural
limit} -> Maybe Natural
limit) (\s :: DescribeClientAuthenticationSettings
s@DescribeClientAuthenticationSettings' {} Maybe Natural
a -> DescribeClientAuthenticationSettings
s {$sel:limit:DescribeClientAuthenticationSettings' :: Maybe Natural
limit = Maybe Natural
a} :: DescribeClientAuthenticationSettings)

-- | The /DescribeClientAuthenticationSettingsResult.NextToken/ value from a
-- previous call to DescribeClientAuthenticationSettings. Pass null if this
-- is the first call.
describeClientAuthenticationSettings_nextToken :: Lens.Lens' DescribeClientAuthenticationSettings (Prelude.Maybe Prelude.Text)
describeClientAuthenticationSettings_nextToken :: Lens' DescribeClientAuthenticationSettings (Maybe Text)
describeClientAuthenticationSettings_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeClientAuthenticationSettings' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeClientAuthenticationSettings' :: DescribeClientAuthenticationSettings -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeClientAuthenticationSettings
s@DescribeClientAuthenticationSettings' {} Maybe Text
a -> DescribeClientAuthenticationSettings
s {$sel:nextToken:DescribeClientAuthenticationSettings' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeClientAuthenticationSettings)

-- | The type of client authentication for which to retrieve information. If
-- no type is specified, a list of all client authentication types that are
-- supported for the specified directory is retrieved.
describeClientAuthenticationSettings_type :: Lens.Lens' DescribeClientAuthenticationSettings (Prelude.Maybe ClientAuthenticationType)
describeClientAuthenticationSettings_type :: Lens'
  DescribeClientAuthenticationSettings
  (Maybe ClientAuthenticationType)
describeClientAuthenticationSettings_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeClientAuthenticationSettings' {Maybe ClientAuthenticationType
type' :: Maybe ClientAuthenticationType
$sel:type':DescribeClientAuthenticationSettings' :: DescribeClientAuthenticationSettings
-> Maybe ClientAuthenticationType
type'} -> Maybe ClientAuthenticationType
type') (\s :: DescribeClientAuthenticationSettings
s@DescribeClientAuthenticationSettings' {} Maybe ClientAuthenticationType
a -> DescribeClientAuthenticationSettings
s {$sel:type':DescribeClientAuthenticationSettings' :: Maybe ClientAuthenticationType
type' = Maybe ClientAuthenticationType
a} :: DescribeClientAuthenticationSettings)

-- | The identifier of the directory for which to retrieve information.
describeClientAuthenticationSettings_directoryId :: Lens.Lens' DescribeClientAuthenticationSettings Prelude.Text
describeClientAuthenticationSettings_directoryId :: Lens' DescribeClientAuthenticationSettings Text
describeClientAuthenticationSettings_directoryId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeClientAuthenticationSettings' {Text
directoryId :: Text
$sel:directoryId:DescribeClientAuthenticationSettings' :: DescribeClientAuthenticationSettings -> Text
directoryId} -> Text
directoryId) (\s :: DescribeClientAuthenticationSettings
s@DescribeClientAuthenticationSettings' {} Text
a -> DescribeClientAuthenticationSettings
s {$sel:directoryId:DescribeClientAuthenticationSettings' :: Text
directoryId = Text
a} :: DescribeClientAuthenticationSettings)

instance
  Core.AWSPager
    DescribeClientAuthenticationSettings
  where
  page :: DescribeClientAuthenticationSettings
-> AWSResponse DescribeClientAuthenticationSettings
-> Maybe DescribeClientAuthenticationSettings
page DescribeClientAuthenticationSettings
rq AWSResponse DescribeClientAuthenticationSettings
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse DescribeClientAuthenticationSettings
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeClientAuthenticationSettingsResponse (Maybe Text)
describeClientAuthenticationSettingsResponse_nextToken
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse DescribeClientAuthenticationSettings
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens'
  DescribeClientAuthenticationSettingsResponse
  (Maybe [ClientAuthenticationSettingInfo])
describeClientAuthenticationSettingsResponse_clientAuthenticationSettingsInfo
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ DescribeClientAuthenticationSettings
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' DescribeClientAuthenticationSettings (Maybe Text)
describeClientAuthenticationSettings_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse DescribeClientAuthenticationSettings
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeClientAuthenticationSettingsResponse (Maybe Text)
describeClientAuthenticationSettingsResponse_nextToken
          forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just

instance
  Core.AWSRequest
    DescribeClientAuthenticationSettings
  where
  type
    AWSResponse DescribeClientAuthenticationSettings =
      DescribeClientAuthenticationSettingsResponse
  request :: (Service -> Service)
-> DescribeClientAuthenticationSettings
-> Request DescribeClientAuthenticationSettings
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 DescribeClientAuthenticationSettings
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse
           (AWSResponse DescribeClientAuthenticationSettings)))
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 [ClientAuthenticationSettingInfo]
-> Maybe Text
-> Int
-> DescribeClientAuthenticationSettingsResponse
DescribeClientAuthenticationSettingsResponse'
            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
"ClientAuthenticationSettingsInfo"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
            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
"NextToken")
            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
    DescribeClientAuthenticationSettings
  where
  hashWithSalt :: Int -> DescribeClientAuthenticationSettings -> Int
hashWithSalt
    Int
_salt
    DescribeClientAuthenticationSettings' {Maybe Natural
Maybe Text
Maybe ClientAuthenticationType
Text
directoryId :: Text
type' :: Maybe ClientAuthenticationType
nextToken :: Maybe Text
limit :: Maybe Natural
$sel:directoryId:DescribeClientAuthenticationSettings' :: DescribeClientAuthenticationSettings -> Text
$sel:type':DescribeClientAuthenticationSettings' :: DescribeClientAuthenticationSettings
-> Maybe ClientAuthenticationType
$sel:nextToken:DescribeClientAuthenticationSettings' :: DescribeClientAuthenticationSettings -> Maybe Text
$sel:limit:DescribeClientAuthenticationSettings' :: DescribeClientAuthenticationSettings -> Maybe Natural
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
limit
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ClientAuthenticationType
type'
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
directoryId

instance
  Prelude.NFData
    DescribeClientAuthenticationSettings
  where
  rnf :: DescribeClientAuthenticationSettings -> ()
rnf DescribeClientAuthenticationSettings' {Maybe Natural
Maybe Text
Maybe ClientAuthenticationType
Text
directoryId :: Text
type' :: Maybe ClientAuthenticationType
nextToken :: Maybe Text
limit :: Maybe Natural
$sel:directoryId:DescribeClientAuthenticationSettings' :: DescribeClientAuthenticationSettings -> Text
$sel:type':DescribeClientAuthenticationSettings' :: DescribeClientAuthenticationSettings
-> Maybe ClientAuthenticationType
$sel:nextToken:DescribeClientAuthenticationSettings' :: DescribeClientAuthenticationSettings -> Maybe Text
$sel:limit:DescribeClientAuthenticationSettings' :: DescribeClientAuthenticationSettings -> Maybe Natural
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
limit
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ClientAuthenticationType
type'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
directoryId

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

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

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

-- | /See:/ 'newDescribeClientAuthenticationSettingsResponse' smart constructor.
data DescribeClientAuthenticationSettingsResponse = DescribeClientAuthenticationSettingsResponse'
  { -- | Information about the type of client authentication for the specified
    -- directory. The following information is retrieved: The date and time
    -- when the status of the client authentication type was last updated,
    -- whether the client authentication type is enabled or disabled, and the
    -- type of client authentication.
    DescribeClientAuthenticationSettingsResponse
-> Maybe [ClientAuthenticationSettingInfo]
clientAuthenticationSettingsInfo :: Prelude.Maybe [ClientAuthenticationSettingInfo],
    -- | The next token used to retrieve the client authentication settings if
    -- the number of setting types exceeds page limit and there is another
    -- page.
    DescribeClientAuthenticationSettingsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DescribeClientAuthenticationSettingsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeClientAuthenticationSettingsResponse
-> DescribeClientAuthenticationSettingsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeClientAuthenticationSettingsResponse
-> DescribeClientAuthenticationSettingsResponse -> Bool
$c/= :: DescribeClientAuthenticationSettingsResponse
-> DescribeClientAuthenticationSettingsResponse -> Bool
== :: DescribeClientAuthenticationSettingsResponse
-> DescribeClientAuthenticationSettingsResponse -> Bool
$c== :: DescribeClientAuthenticationSettingsResponse
-> DescribeClientAuthenticationSettingsResponse -> Bool
Prelude.Eq, ReadPrec [DescribeClientAuthenticationSettingsResponse]
ReadPrec DescribeClientAuthenticationSettingsResponse
Int -> ReadS DescribeClientAuthenticationSettingsResponse
ReadS [DescribeClientAuthenticationSettingsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeClientAuthenticationSettingsResponse]
$creadListPrec :: ReadPrec [DescribeClientAuthenticationSettingsResponse]
readPrec :: ReadPrec DescribeClientAuthenticationSettingsResponse
$creadPrec :: ReadPrec DescribeClientAuthenticationSettingsResponse
readList :: ReadS [DescribeClientAuthenticationSettingsResponse]
$creadList :: ReadS [DescribeClientAuthenticationSettingsResponse]
readsPrec :: Int -> ReadS DescribeClientAuthenticationSettingsResponse
$creadsPrec :: Int -> ReadS DescribeClientAuthenticationSettingsResponse
Prelude.Read, Int -> DescribeClientAuthenticationSettingsResponse -> ShowS
[DescribeClientAuthenticationSettingsResponse] -> ShowS
DescribeClientAuthenticationSettingsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeClientAuthenticationSettingsResponse] -> ShowS
$cshowList :: [DescribeClientAuthenticationSettingsResponse] -> ShowS
show :: DescribeClientAuthenticationSettingsResponse -> String
$cshow :: DescribeClientAuthenticationSettingsResponse -> String
showsPrec :: Int -> DescribeClientAuthenticationSettingsResponse -> ShowS
$cshowsPrec :: Int -> DescribeClientAuthenticationSettingsResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeClientAuthenticationSettingsResponse x
-> DescribeClientAuthenticationSettingsResponse
forall x.
DescribeClientAuthenticationSettingsResponse
-> Rep DescribeClientAuthenticationSettingsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeClientAuthenticationSettingsResponse x
-> DescribeClientAuthenticationSettingsResponse
$cfrom :: forall x.
DescribeClientAuthenticationSettingsResponse
-> Rep DescribeClientAuthenticationSettingsResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeClientAuthenticationSettingsResponse' 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:
--
-- 'clientAuthenticationSettingsInfo', 'describeClientAuthenticationSettingsResponse_clientAuthenticationSettingsInfo' - Information about the type of client authentication for the specified
-- directory. The following information is retrieved: The date and time
-- when the status of the client authentication type was last updated,
-- whether the client authentication type is enabled or disabled, and the
-- type of client authentication.
--
-- 'nextToken', 'describeClientAuthenticationSettingsResponse_nextToken' - The next token used to retrieve the client authentication settings if
-- the number of setting types exceeds page limit and there is another
-- page.
--
-- 'httpStatus', 'describeClientAuthenticationSettingsResponse_httpStatus' - The response's http status code.
newDescribeClientAuthenticationSettingsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeClientAuthenticationSettingsResponse
newDescribeClientAuthenticationSettingsResponse :: Int -> DescribeClientAuthenticationSettingsResponse
newDescribeClientAuthenticationSettingsResponse
  Int
pHttpStatus_ =
    DescribeClientAuthenticationSettingsResponse'
      { $sel:clientAuthenticationSettingsInfo:DescribeClientAuthenticationSettingsResponse' :: Maybe [ClientAuthenticationSettingInfo]
clientAuthenticationSettingsInfo =
          forall a. Maybe a
Prelude.Nothing,
        $sel:nextToken:DescribeClientAuthenticationSettingsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:DescribeClientAuthenticationSettingsResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | Information about the type of client authentication for the specified
-- directory. The following information is retrieved: The date and time
-- when the status of the client authentication type was last updated,
-- whether the client authentication type is enabled or disabled, and the
-- type of client authentication.
describeClientAuthenticationSettingsResponse_clientAuthenticationSettingsInfo :: Lens.Lens' DescribeClientAuthenticationSettingsResponse (Prelude.Maybe [ClientAuthenticationSettingInfo])
describeClientAuthenticationSettingsResponse_clientAuthenticationSettingsInfo :: Lens'
  DescribeClientAuthenticationSettingsResponse
  (Maybe [ClientAuthenticationSettingInfo])
describeClientAuthenticationSettingsResponse_clientAuthenticationSettingsInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeClientAuthenticationSettingsResponse' {Maybe [ClientAuthenticationSettingInfo]
clientAuthenticationSettingsInfo :: Maybe [ClientAuthenticationSettingInfo]
$sel:clientAuthenticationSettingsInfo:DescribeClientAuthenticationSettingsResponse' :: DescribeClientAuthenticationSettingsResponse
-> Maybe [ClientAuthenticationSettingInfo]
clientAuthenticationSettingsInfo} -> Maybe [ClientAuthenticationSettingInfo]
clientAuthenticationSettingsInfo) (\s :: DescribeClientAuthenticationSettingsResponse
s@DescribeClientAuthenticationSettingsResponse' {} Maybe [ClientAuthenticationSettingInfo]
a -> DescribeClientAuthenticationSettingsResponse
s {$sel:clientAuthenticationSettingsInfo:DescribeClientAuthenticationSettingsResponse' :: Maybe [ClientAuthenticationSettingInfo]
clientAuthenticationSettingsInfo = Maybe [ClientAuthenticationSettingInfo]
a} :: DescribeClientAuthenticationSettingsResponse) 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 next token used to retrieve the client authentication settings if
-- the number of setting types exceeds page limit and there is another
-- page.
describeClientAuthenticationSettingsResponse_nextToken :: Lens.Lens' DescribeClientAuthenticationSettingsResponse (Prelude.Maybe Prelude.Text)
describeClientAuthenticationSettingsResponse_nextToken :: Lens' DescribeClientAuthenticationSettingsResponse (Maybe Text)
describeClientAuthenticationSettingsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeClientAuthenticationSettingsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeClientAuthenticationSettingsResponse' :: DescribeClientAuthenticationSettingsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeClientAuthenticationSettingsResponse
s@DescribeClientAuthenticationSettingsResponse' {} Maybe Text
a -> DescribeClientAuthenticationSettingsResponse
s {$sel:nextToken:DescribeClientAuthenticationSettingsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeClientAuthenticationSettingsResponse)

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

instance
  Prelude.NFData
    DescribeClientAuthenticationSettingsResponse
  where
  rnf :: DescribeClientAuthenticationSettingsResponse -> ()
rnf DescribeClientAuthenticationSettingsResponse' {Int
Maybe [ClientAuthenticationSettingInfo]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
clientAuthenticationSettingsInfo :: Maybe [ClientAuthenticationSettingInfo]
$sel:httpStatus:DescribeClientAuthenticationSettingsResponse' :: DescribeClientAuthenticationSettingsResponse -> Int
$sel:nextToken:DescribeClientAuthenticationSettingsResponse' :: DescribeClientAuthenticationSettingsResponse -> Maybe Text
$sel:clientAuthenticationSettingsInfo:DescribeClientAuthenticationSettingsResponse' :: DescribeClientAuthenticationSettingsResponse
-> Maybe [ClientAuthenticationSettingInfo]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [ClientAuthenticationSettingInfo]
clientAuthenticationSettingsInfo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus