{-# 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.ListEntityPersonas
-- 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 specific permissions of users and groups with access to your
-- Amazon Kendra experience.
module Amazonka.Kendra.ListEntityPersonas
  ( -- * Creating a Request
    ListEntityPersonas (..),
    newListEntityPersonas,

    -- * Request Lenses
    listEntityPersonas_maxResults,
    listEntityPersonas_nextToken,
    listEntityPersonas_id,
    listEntityPersonas_indexId,

    -- * Destructuring the Response
    ListEntityPersonasResponse (..),
    newListEntityPersonasResponse,

    -- * Response Lenses
    listEntityPersonasResponse_nextToken,
    listEntityPersonasResponse_summaryItems,
    listEntityPersonasResponse_httpStatus,
  )
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:/ 'newListEntityPersonas' smart constructor.
data ListEntityPersonas = ListEntityPersonas'
  { -- | The maximum number of returned users or groups.
    ListEntityPersonas -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | If the previous response was incomplete (because there is 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 users or
    -- groups.
    ListEntityPersonas -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The identifier of your Amazon Kendra experience.
    ListEntityPersonas -> Text
id :: Prelude.Text,
    -- | The identifier of the index for your Amazon Kendra experience.
    ListEntityPersonas -> Text
indexId :: Prelude.Text
  }
  deriving (ListEntityPersonas -> ListEntityPersonas -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListEntityPersonas -> ListEntityPersonas -> Bool
$c/= :: ListEntityPersonas -> ListEntityPersonas -> Bool
== :: ListEntityPersonas -> ListEntityPersonas -> Bool
$c== :: ListEntityPersonas -> ListEntityPersonas -> Bool
Prelude.Eq, ReadPrec [ListEntityPersonas]
ReadPrec ListEntityPersonas
Int -> ReadS ListEntityPersonas
ReadS [ListEntityPersonas]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListEntityPersonas]
$creadListPrec :: ReadPrec [ListEntityPersonas]
readPrec :: ReadPrec ListEntityPersonas
$creadPrec :: ReadPrec ListEntityPersonas
readList :: ReadS [ListEntityPersonas]
$creadList :: ReadS [ListEntityPersonas]
readsPrec :: Int -> ReadS ListEntityPersonas
$creadsPrec :: Int -> ReadS ListEntityPersonas
Prelude.Read, Int -> ListEntityPersonas -> ShowS
[ListEntityPersonas] -> ShowS
ListEntityPersonas -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListEntityPersonas] -> ShowS
$cshowList :: [ListEntityPersonas] -> ShowS
show :: ListEntityPersonas -> String
$cshow :: ListEntityPersonas -> String
showsPrec :: Int -> ListEntityPersonas -> ShowS
$cshowsPrec :: Int -> ListEntityPersonas -> ShowS
Prelude.Show, forall x. Rep ListEntityPersonas x -> ListEntityPersonas
forall x. ListEntityPersonas -> Rep ListEntityPersonas x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListEntityPersonas x -> ListEntityPersonas
$cfrom :: forall x. ListEntityPersonas -> Rep ListEntityPersonas x
Prelude.Generic)

-- |
-- Create a value of 'ListEntityPersonas' 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', 'listEntityPersonas_maxResults' - The maximum number of returned users or groups.
--
-- 'nextToken', 'listEntityPersonas_nextToken' - If the previous response was incomplete (because there is 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 users or
-- groups.
--
-- 'id', 'listEntityPersonas_id' - The identifier of your Amazon Kendra experience.
--
-- 'indexId', 'listEntityPersonas_indexId' - The identifier of the index for your Amazon Kendra experience.
newListEntityPersonas ::
  -- | 'id'
  Prelude.Text ->
  -- | 'indexId'
  Prelude.Text ->
  ListEntityPersonas
newListEntityPersonas :: Text -> Text -> ListEntityPersonas
newListEntityPersonas Text
pId_ Text
pIndexId_ =
  ListEntityPersonas'
    { $sel:maxResults:ListEntityPersonas' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListEntityPersonas' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:id:ListEntityPersonas' :: Text
id = Text
pId_,
      $sel:indexId:ListEntityPersonas' :: Text
indexId = Text
pIndexId_
    }

-- | The maximum number of returned users or groups.
listEntityPersonas_maxResults :: Lens.Lens' ListEntityPersonas (Prelude.Maybe Prelude.Natural)
listEntityPersonas_maxResults :: Lens' ListEntityPersonas (Maybe Natural)
listEntityPersonas_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListEntityPersonas' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListEntityPersonas' :: ListEntityPersonas -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListEntityPersonas
s@ListEntityPersonas' {} Maybe Natural
a -> ListEntityPersonas
s {$sel:maxResults:ListEntityPersonas' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListEntityPersonas)

-- | If the previous response was incomplete (because there is 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 users or
-- groups.
listEntityPersonas_nextToken :: Lens.Lens' ListEntityPersonas (Prelude.Maybe Prelude.Text)
listEntityPersonas_nextToken :: Lens' ListEntityPersonas (Maybe Text)
listEntityPersonas_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListEntityPersonas' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListEntityPersonas' :: ListEntityPersonas -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListEntityPersonas
s@ListEntityPersonas' {} Maybe Text
a -> ListEntityPersonas
s {$sel:nextToken:ListEntityPersonas' :: Maybe Text
nextToken = Maybe Text
a} :: ListEntityPersonas)

-- | The identifier of your Amazon Kendra experience.
listEntityPersonas_id :: Lens.Lens' ListEntityPersonas Prelude.Text
listEntityPersonas_id :: Lens' ListEntityPersonas Text
listEntityPersonas_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListEntityPersonas' {Text
id :: Text
$sel:id:ListEntityPersonas' :: ListEntityPersonas -> Text
id} -> Text
id) (\s :: ListEntityPersonas
s@ListEntityPersonas' {} Text
a -> ListEntityPersonas
s {$sel:id:ListEntityPersonas' :: Text
id = Text
a} :: ListEntityPersonas)

-- | The identifier of the index for your Amazon Kendra experience.
listEntityPersonas_indexId :: Lens.Lens' ListEntityPersonas Prelude.Text
listEntityPersonas_indexId :: Lens' ListEntityPersonas Text
listEntityPersonas_indexId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListEntityPersonas' {Text
indexId :: Text
$sel:indexId:ListEntityPersonas' :: ListEntityPersonas -> Text
indexId} -> Text
indexId) (\s :: ListEntityPersonas
s@ListEntityPersonas' {} Text
a -> ListEntityPersonas
s {$sel:indexId:ListEntityPersonas' :: Text
indexId = Text
a} :: ListEntityPersonas)

instance Core.AWSRequest ListEntityPersonas where
  type
    AWSResponse ListEntityPersonas =
      ListEntityPersonasResponse
  request :: (Service -> Service)
-> ListEntityPersonas -> Request ListEntityPersonas
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 ListEntityPersonas
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListEntityPersonas)))
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
-> Maybe [PersonasSummary] -> Int -> ListEntityPersonasResponse
ListEntityPersonasResponse'
            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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"SummaryItems" 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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable ListEntityPersonas where
  hashWithSalt :: Int -> ListEntityPersonas -> Int
hashWithSalt Int
_salt ListEntityPersonas' {Maybe Natural
Maybe Text
Text
indexId :: Text
id :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:indexId:ListEntityPersonas' :: ListEntityPersonas -> Text
$sel:id:ListEntityPersonas' :: ListEntityPersonas -> Text
$sel:nextToken:ListEntityPersonas' :: ListEntityPersonas -> Maybe Text
$sel:maxResults:ListEntityPersonas' :: ListEntityPersonas -> 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
id
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
indexId

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

instance Data.ToHeaders ListEntityPersonas where
  toHeaders :: ListEntityPersonas -> 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.ListEntityPersonas" ::
                          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 ListEntityPersonas where
  toJSON :: ListEntityPersonas -> Value
toJSON ListEntityPersonas' {Maybe Natural
Maybe Text
Text
indexId :: Text
id :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:indexId:ListEntityPersonas' :: ListEntityPersonas -> Text
$sel:id:ListEntityPersonas' :: ListEntityPersonas -> Text
$sel:nextToken:ListEntityPersonas' :: ListEntityPersonas -> Maybe Text
$sel:maxResults:ListEntityPersonas' :: ListEntityPersonas -> 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
"Id" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
id),
            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 ListEntityPersonas where
  toPath :: ListEntityPersonas -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newListEntityPersonasResponse' smart constructor.
data ListEntityPersonasResponse = ListEntityPersonasResponse'
  { -- | If the response is truncated, Amazon Kendra returns this token, which
    -- you can use in a later request to retrieve the next set of users or
    -- groups.
    ListEntityPersonasResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | An array of summary information for one or more users or groups.
    ListEntityPersonasResponse -> Maybe [PersonasSummary]
summaryItems :: Prelude.Maybe [PersonasSummary],
    -- | The response's http status code.
    ListEntityPersonasResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListEntityPersonasResponse -> ListEntityPersonasResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListEntityPersonasResponse -> ListEntityPersonasResponse -> Bool
$c/= :: ListEntityPersonasResponse -> ListEntityPersonasResponse -> Bool
== :: ListEntityPersonasResponse -> ListEntityPersonasResponse -> Bool
$c== :: ListEntityPersonasResponse -> ListEntityPersonasResponse -> Bool
Prelude.Eq, ReadPrec [ListEntityPersonasResponse]
ReadPrec ListEntityPersonasResponse
Int -> ReadS ListEntityPersonasResponse
ReadS [ListEntityPersonasResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListEntityPersonasResponse]
$creadListPrec :: ReadPrec [ListEntityPersonasResponse]
readPrec :: ReadPrec ListEntityPersonasResponse
$creadPrec :: ReadPrec ListEntityPersonasResponse
readList :: ReadS [ListEntityPersonasResponse]
$creadList :: ReadS [ListEntityPersonasResponse]
readsPrec :: Int -> ReadS ListEntityPersonasResponse
$creadsPrec :: Int -> ReadS ListEntityPersonasResponse
Prelude.Read, Int -> ListEntityPersonasResponse -> ShowS
[ListEntityPersonasResponse] -> ShowS
ListEntityPersonasResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListEntityPersonasResponse] -> ShowS
$cshowList :: [ListEntityPersonasResponse] -> ShowS
show :: ListEntityPersonasResponse -> String
$cshow :: ListEntityPersonasResponse -> String
showsPrec :: Int -> ListEntityPersonasResponse -> ShowS
$cshowsPrec :: Int -> ListEntityPersonasResponse -> ShowS
Prelude.Show, forall x.
Rep ListEntityPersonasResponse x -> ListEntityPersonasResponse
forall x.
ListEntityPersonasResponse -> Rep ListEntityPersonasResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListEntityPersonasResponse x -> ListEntityPersonasResponse
$cfrom :: forall x.
ListEntityPersonasResponse -> Rep ListEntityPersonasResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListEntityPersonasResponse' 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', 'listEntityPersonasResponse_nextToken' - If the response is truncated, Amazon Kendra returns this token, which
-- you can use in a later request to retrieve the next set of users or
-- groups.
--
-- 'summaryItems', 'listEntityPersonasResponse_summaryItems' - An array of summary information for one or more users or groups.
--
-- 'httpStatus', 'listEntityPersonasResponse_httpStatus' - The response's http status code.
newListEntityPersonasResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListEntityPersonasResponse
newListEntityPersonasResponse :: Int -> ListEntityPersonasResponse
newListEntityPersonasResponse Int
pHttpStatus_ =
  ListEntityPersonasResponse'
    { $sel:nextToken:ListEntityPersonasResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:summaryItems:ListEntityPersonasResponse' :: Maybe [PersonasSummary]
summaryItems = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListEntityPersonasResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

-- | An array of summary information for one or more users or groups.
listEntityPersonasResponse_summaryItems :: Lens.Lens' ListEntityPersonasResponse (Prelude.Maybe [PersonasSummary])
listEntityPersonasResponse_summaryItems :: Lens' ListEntityPersonasResponse (Maybe [PersonasSummary])
listEntityPersonasResponse_summaryItems = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListEntityPersonasResponse' {Maybe [PersonasSummary]
summaryItems :: Maybe [PersonasSummary]
$sel:summaryItems:ListEntityPersonasResponse' :: ListEntityPersonasResponse -> Maybe [PersonasSummary]
summaryItems} -> Maybe [PersonasSummary]
summaryItems) (\s :: ListEntityPersonasResponse
s@ListEntityPersonasResponse' {} Maybe [PersonasSummary]
a -> ListEntityPersonasResponse
s {$sel:summaryItems:ListEntityPersonasResponse' :: Maybe [PersonasSummary]
summaryItems = Maybe [PersonasSummary]
a} :: ListEntityPersonasResponse) 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 response's http status code.
listEntityPersonasResponse_httpStatus :: Lens.Lens' ListEntityPersonasResponse Prelude.Int
listEntityPersonasResponse_httpStatus :: Lens' ListEntityPersonasResponse Int
listEntityPersonasResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListEntityPersonasResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListEntityPersonasResponse' :: ListEntityPersonasResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListEntityPersonasResponse
s@ListEntityPersonasResponse' {} Int
a -> ListEntityPersonasResponse
s {$sel:httpStatus:ListEntityPersonasResponse' :: Int
httpStatus = Int
a} :: ListEntityPersonasResponse)

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