{-# 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.Kendra.ListAccessControlConfigurations
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Lists one or more access control configurations for an index. This
-- includes user and group access information for your documents. This is
-- useful for user context filtering, where search results are filtered
-- based on the user or their group access to documents.
module Amazonka.Kendra.ListAccessControlConfigurations
  ( -- * Creating a Request
    ListAccessControlConfigurations (..),
    newListAccessControlConfigurations,

    -- * Request Lenses
    listAccessControlConfigurations_maxResults,
    listAccessControlConfigurations_nextToken,
    listAccessControlConfigurations_indexId,

    -- * Destructuring the Response
    ListAccessControlConfigurationsResponse (..),
    newListAccessControlConfigurationsResponse,

    -- * Response Lenses
    listAccessControlConfigurationsResponse_nextToken,
    listAccessControlConfigurationsResponse_httpStatus,
    listAccessControlConfigurationsResponse_accessControlConfigurations,
  )
where

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

-- | /See:/ 'newListAccessControlConfigurations' smart constructor.
data ListAccessControlConfigurations = ListAccessControlConfigurations'
  { -- | The maximum number of access control configurations to return.
    ListAccessControlConfigurations -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | If the previous response was incomplete (because there\'s more data to
    -- retrieve), Amazon Kendra returns a pagination token in the response. You
    -- can use this pagination token to retrieve the next set of access control
    -- configurations.
    ListAccessControlConfigurations -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The identifier of the index for the access control configuration.
    ListAccessControlConfigurations -> Text
indexId :: Prelude.Text
  }
  deriving (ListAccessControlConfigurations
-> ListAccessControlConfigurations -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListAccessControlConfigurations
-> ListAccessControlConfigurations -> Bool
$c/= :: ListAccessControlConfigurations
-> ListAccessControlConfigurations -> Bool
== :: ListAccessControlConfigurations
-> ListAccessControlConfigurations -> Bool
$c== :: ListAccessControlConfigurations
-> ListAccessControlConfigurations -> Bool
Prelude.Eq, ReadPrec [ListAccessControlConfigurations]
ReadPrec ListAccessControlConfigurations
Int -> ReadS ListAccessControlConfigurations
ReadS [ListAccessControlConfigurations]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListAccessControlConfigurations]
$creadListPrec :: ReadPrec [ListAccessControlConfigurations]
readPrec :: ReadPrec ListAccessControlConfigurations
$creadPrec :: ReadPrec ListAccessControlConfigurations
readList :: ReadS [ListAccessControlConfigurations]
$creadList :: ReadS [ListAccessControlConfigurations]
readsPrec :: Int -> ReadS ListAccessControlConfigurations
$creadsPrec :: Int -> ReadS ListAccessControlConfigurations
Prelude.Read, Int -> ListAccessControlConfigurations -> ShowS
[ListAccessControlConfigurations] -> ShowS
ListAccessControlConfigurations -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListAccessControlConfigurations] -> ShowS
$cshowList :: [ListAccessControlConfigurations] -> ShowS
show :: ListAccessControlConfigurations -> String
$cshow :: ListAccessControlConfigurations -> String
showsPrec :: Int -> ListAccessControlConfigurations -> ShowS
$cshowsPrec :: Int -> ListAccessControlConfigurations -> ShowS
Prelude.Show, forall x.
Rep ListAccessControlConfigurations x
-> ListAccessControlConfigurations
forall x.
ListAccessControlConfigurations
-> Rep ListAccessControlConfigurations x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListAccessControlConfigurations x
-> ListAccessControlConfigurations
$cfrom :: forall x.
ListAccessControlConfigurations
-> Rep ListAccessControlConfigurations x
Prelude.Generic)

-- |
-- Create a value of 'ListAccessControlConfigurations' 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:
--
-- 'maxResults', 'listAccessControlConfigurations_maxResults' - The maximum number of access control configurations to return.
--
-- 'nextToken', 'listAccessControlConfigurations_nextToken' - If the previous response was incomplete (because there\'s more data to
-- retrieve), Amazon Kendra returns a pagination token in the response. You
-- can use this pagination token to retrieve the next set of access control
-- configurations.
--
-- 'indexId', 'listAccessControlConfigurations_indexId' - The identifier of the index for the access control configuration.
newListAccessControlConfigurations ::
  -- | 'indexId'
  Prelude.Text ->
  ListAccessControlConfigurations
newListAccessControlConfigurations :: Text -> ListAccessControlConfigurations
newListAccessControlConfigurations Text
pIndexId_ =
  ListAccessControlConfigurations'
    { $sel:maxResults:ListAccessControlConfigurations' :: Maybe Natural
maxResults =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListAccessControlConfigurations' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:indexId:ListAccessControlConfigurations' :: Text
indexId = Text
pIndexId_
    }

-- | The maximum number of access control configurations to return.
listAccessControlConfigurations_maxResults :: Lens.Lens' ListAccessControlConfigurations (Prelude.Maybe Prelude.Natural)
listAccessControlConfigurations_maxResults :: Lens' ListAccessControlConfigurations (Maybe Natural)
listAccessControlConfigurations_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAccessControlConfigurations' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListAccessControlConfigurations' :: ListAccessControlConfigurations -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListAccessControlConfigurations
s@ListAccessControlConfigurations' {} Maybe Natural
a -> ListAccessControlConfigurations
s {$sel:maxResults:ListAccessControlConfigurations' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListAccessControlConfigurations)

-- | If the previous response was incomplete (because there\'s more data to
-- retrieve), Amazon Kendra returns a pagination token in the response. You
-- can use this pagination token to retrieve the next set of access control
-- configurations.
listAccessControlConfigurations_nextToken :: Lens.Lens' ListAccessControlConfigurations (Prelude.Maybe Prelude.Text)
listAccessControlConfigurations_nextToken :: Lens' ListAccessControlConfigurations (Maybe Text)
listAccessControlConfigurations_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAccessControlConfigurations' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListAccessControlConfigurations' :: ListAccessControlConfigurations -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListAccessControlConfigurations
s@ListAccessControlConfigurations' {} Maybe Text
a -> ListAccessControlConfigurations
s {$sel:nextToken:ListAccessControlConfigurations' :: Maybe Text
nextToken = Maybe Text
a} :: ListAccessControlConfigurations)

-- | The identifier of the index for the access control configuration.
listAccessControlConfigurations_indexId :: Lens.Lens' ListAccessControlConfigurations Prelude.Text
listAccessControlConfigurations_indexId :: Lens' ListAccessControlConfigurations Text
listAccessControlConfigurations_indexId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAccessControlConfigurations' {Text
indexId :: Text
$sel:indexId:ListAccessControlConfigurations' :: ListAccessControlConfigurations -> Text
indexId} -> Text
indexId) (\s :: ListAccessControlConfigurations
s@ListAccessControlConfigurations' {} Text
a -> ListAccessControlConfigurations
s {$sel:indexId:ListAccessControlConfigurations' :: Text
indexId = Text
a} :: ListAccessControlConfigurations)

instance
  Core.AWSRequest
    ListAccessControlConfigurations
  where
  type
    AWSResponse ListAccessControlConfigurations =
      ListAccessControlConfigurationsResponse
  request :: (Service -> Service)
-> ListAccessControlConfigurations
-> Request ListAccessControlConfigurations
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 ListAccessControlConfigurations
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse ListAccessControlConfigurations)))
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
-> [AccessControlConfigurationSummary]
-> ListAccessControlConfigurationsResponse
ListAccessControlConfigurationsResponse'
            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
"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))
            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
"AccessControlConfigurations"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
      )

instance
  Prelude.Hashable
    ListAccessControlConfigurations
  where
  hashWithSalt :: Int -> ListAccessControlConfigurations -> Int
hashWithSalt
    Int
_salt
    ListAccessControlConfigurations' {Maybe Natural
Maybe Text
Text
indexId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:indexId:ListAccessControlConfigurations' :: ListAccessControlConfigurations -> Text
$sel:nextToken:ListAccessControlConfigurations' :: ListAccessControlConfigurations -> Maybe Text
$sel:maxResults:ListAccessControlConfigurations' :: ListAccessControlConfigurations -> Maybe Natural
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
indexId

instance
  Prelude.NFData
    ListAccessControlConfigurations
  where
  rnf :: ListAccessControlConfigurations -> ()
rnf ListAccessControlConfigurations' {Maybe Natural
Maybe Text
Text
indexId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:indexId:ListAccessControlConfigurations' :: ListAccessControlConfigurations -> Text
$sel:nextToken:ListAccessControlConfigurations' :: ListAccessControlConfigurations -> Maybe Text
$sel:maxResults:ListAccessControlConfigurations' :: ListAccessControlConfigurations -> Maybe Natural
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxResults
      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 Text
indexId

instance
  Data.ToHeaders
    ListAccessControlConfigurations
  where
  toHeaders :: ListAccessControlConfigurations -> 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
"AWSKendraFrontendService.ListAccessControlConfigurations" ::
                          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 ListAccessControlConfigurations where
  toJSON :: ListAccessControlConfigurations -> Value
toJSON ListAccessControlConfigurations' {Maybe Natural
Maybe Text
Text
indexId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:indexId:ListAccessControlConfigurations' :: ListAccessControlConfigurations -> Text
$sel:nextToken:ListAccessControlConfigurations' :: ListAccessControlConfigurations -> Maybe Text
$sel:maxResults:ListAccessControlConfigurations' :: ListAccessControlConfigurations -> Maybe Natural
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"MaxResults" 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
maxResults,
            (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,
            forall a. a -> Maybe a
Prelude.Just (Key
"IndexId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
indexId)
          ]
      )

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

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

-- | /See:/ 'newListAccessControlConfigurationsResponse' smart constructor.
data ListAccessControlConfigurationsResponse = ListAccessControlConfigurationsResponse'
  { -- | If the response is truncated, Amazon Kendra returns this token, which
    -- you can use in the subsequent request to retrieve the next set of access
    -- control configurations.
    ListAccessControlConfigurationsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListAccessControlConfigurationsResponse -> Int
httpStatus :: Prelude.Int,
    -- | The details of your access control configurations.
    ListAccessControlConfigurationsResponse
-> [AccessControlConfigurationSummary]
accessControlConfigurations :: [AccessControlConfigurationSummary]
  }
  deriving (ListAccessControlConfigurationsResponse
-> ListAccessControlConfigurationsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListAccessControlConfigurationsResponse
-> ListAccessControlConfigurationsResponse -> Bool
$c/= :: ListAccessControlConfigurationsResponse
-> ListAccessControlConfigurationsResponse -> Bool
== :: ListAccessControlConfigurationsResponse
-> ListAccessControlConfigurationsResponse -> Bool
$c== :: ListAccessControlConfigurationsResponse
-> ListAccessControlConfigurationsResponse -> Bool
Prelude.Eq, ReadPrec [ListAccessControlConfigurationsResponse]
ReadPrec ListAccessControlConfigurationsResponse
Int -> ReadS ListAccessControlConfigurationsResponse
ReadS [ListAccessControlConfigurationsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListAccessControlConfigurationsResponse]
$creadListPrec :: ReadPrec [ListAccessControlConfigurationsResponse]
readPrec :: ReadPrec ListAccessControlConfigurationsResponse
$creadPrec :: ReadPrec ListAccessControlConfigurationsResponse
readList :: ReadS [ListAccessControlConfigurationsResponse]
$creadList :: ReadS [ListAccessControlConfigurationsResponse]
readsPrec :: Int -> ReadS ListAccessControlConfigurationsResponse
$creadsPrec :: Int -> ReadS ListAccessControlConfigurationsResponse
Prelude.Read, Int -> ListAccessControlConfigurationsResponse -> ShowS
[ListAccessControlConfigurationsResponse] -> ShowS
ListAccessControlConfigurationsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListAccessControlConfigurationsResponse] -> ShowS
$cshowList :: [ListAccessControlConfigurationsResponse] -> ShowS
show :: ListAccessControlConfigurationsResponse -> String
$cshow :: ListAccessControlConfigurationsResponse -> String
showsPrec :: Int -> ListAccessControlConfigurationsResponse -> ShowS
$cshowsPrec :: Int -> ListAccessControlConfigurationsResponse -> ShowS
Prelude.Show, forall x.
Rep ListAccessControlConfigurationsResponse x
-> ListAccessControlConfigurationsResponse
forall x.
ListAccessControlConfigurationsResponse
-> Rep ListAccessControlConfigurationsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListAccessControlConfigurationsResponse x
-> ListAccessControlConfigurationsResponse
$cfrom :: forall x.
ListAccessControlConfigurationsResponse
-> Rep ListAccessControlConfigurationsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListAccessControlConfigurationsResponse' 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:
--
-- 'nextToken', 'listAccessControlConfigurationsResponse_nextToken' - If the response is truncated, Amazon Kendra returns this token, which
-- you can use in the subsequent request to retrieve the next set of access
-- control configurations.
--
-- 'httpStatus', 'listAccessControlConfigurationsResponse_httpStatus' - The response's http status code.
--
-- 'accessControlConfigurations', 'listAccessControlConfigurationsResponse_accessControlConfigurations' - The details of your access control configurations.
newListAccessControlConfigurationsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListAccessControlConfigurationsResponse
newListAccessControlConfigurationsResponse :: Int -> ListAccessControlConfigurationsResponse
newListAccessControlConfigurationsResponse
  Int
pHttpStatus_ =
    ListAccessControlConfigurationsResponse'
      { $sel:nextToken:ListAccessControlConfigurationsResponse' :: Maybe Text
nextToken =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:ListAccessControlConfigurationsResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:accessControlConfigurations:ListAccessControlConfigurationsResponse' :: [AccessControlConfigurationSummary]
accessControlConfigurations =
          forall a. Monoid a => a
Prelude.mempty
      }

-- | If the response is truncated, Amazon Kendra returns this token, which
-- you can use in the subsequent request to retrieve the next set of access
-- control configurations.
listAccessControlConfigurationsResponse_nextToken :: Lens.Lens' ListAccessControlConfigurationsResponse (Prelude.Maybe Prelude.Text)
listAccessControlConfigurationsResponse_nextToken :: Lens' ListAccessControlConfigurationsResponse (Maybe Text)
listAccessControlConfigurationsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAccessControlConfigurationsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListAccessControlConfigurationsResponse' :: ListAccessControlConfigurationsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListAccessControlConfigurationsResponse
s@ListAccessControlConfigurationsResponse' {} Maybe Text
a -> ListAccessControlConfigurationsResponse
s {$sel:nextToken:ListAccessControlConfigurationsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListAccessControlConfigurationsResponse)

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

-- | The details of your access control configurations.
listAccessControlConfigurationsResponse_accessControlConfigurations :: Lens.Lens' ListAccessControlConfigurationsResponse [AccessControlConfigurationSummary]
listAccessControlConfigurationsResponse_accessControlConfigurations :: Lens'
  ListAccessControlConfigurationsResponse
  [AccessControlConfigurationSummary]
listAccessControlConfigurationsResponse_accessControlConfigurations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAccessControlConfigurationsResponse' {[AccessControlConfigurationSummary]
accessControlConfigurations :: [AccessControlConfigurationSummary]
$sel:accessControlConfigurations:ListAccessControlConfigurationsResponse' :: ListAccessControlConfigurationsResponse
-> [AccessControlConfigurationSummary]
accessControlConfigurations} -> [AccessControlConfigurationSummary]
accessControlConfigurations) (\s :: ListAccessControlConfigurationsResponse
s@ListAccessControlConfigurationsResponse' {} [AccessControlConfigurationSummary]
a -> ListAccessControlConfigurationsResponse
s {$sel:accessControlConfigurations:ListAccessControlConfigurationsResponse' :: [AccessControlConfigurationSummary]
accessControlConfigurations = [AccessControlConfigurationSummary]
a} :: ListAccessControlConfigurationsResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance
  Prelude.NFData
    ListAccessControlConfigurationsResponse
  where
  rnf :: ListAccessControlConfigurationsResponse -> ()
rnf ListAccessControlConfigurationsResponse' {Int
[AccessControlConfigurationSummary]
Maybe Text
accessControlConfigurations :: [AccessControlConfigurationSummary]
httpStatus :: Int
nextToken :: Maybe Text
$sel:accessControlConfigurations:ListAccessControlConfigurationsResponse' :: ListAccessControlConfigurationsResponse
-> [AccessControlConfigurationSummary]
$sel:httpStatus:ListAccessControlConfigurationsResponse' :: ListAccessControlConfigurationsResponse -> Int
$sel:nextToken:ListAccessControlConfigurationsResponse' :: ListAccessControlConfigurationsResponse -> Maybe Text
..} =
    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
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [AccessControlConfigurationSummary]
accessControlConfigurations