{-# 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.AssociatePersonasToEntities
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Defines the specific permissions of users or groups in your IAM Identity
-- Center identity source with access to your Amazon Kendra experience. You
-- can create an Amazon Kendra experience such as a search application. For
-- more information on creating a search application experience, see
-- <https://docs.aws.amazon.com/kendra/latest/dg/deploying-search-experience-no-code.html Building a search experience with no code>.
module Amazonka.Kendra.AssociatePersonasToEntities
  ( -- * Creating a Request
    AssociatePersonasToEntities (..),
    newAssociatePersonasToEntities,

    -- * Request Lenses
    associatePersonasToEntities_id,
    associatePersonasToEntities_indexId,
    associatePersonasToEntities_personas,

    -- * Destructuring the Response
    AssociatePersonasToEntitiesResponse (..),
    newAssociatePersonasToEntitiesResponse,

    -- * Response Lenses
    associatePersonasToEntitiesResponse_failedEntityList,
    associatePersonasToEntitiesResponse_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:/ 'newAssociatePersonasToEntities' smart constructor.
data AssociatePersonasToEntities = AssociatePersonasToEntities'
  { -- | The identifier of your Amazon Kendra experience.
    AssociatePersonasToEntities -> Text
id :: Prelude.Text,
    -- | The identifier of the index for your Amazon Kendra experience.
    AssociatePersonasToEntities -> Text
indexId :: Prelude.Text,
    -- | The personas that define the specific permissions of users or groups in
    -- your IAM Identity Center identity source. The available personas or
    -- access roles are @Owner@ and @Viewer@. For more information on these
    -- personas, see
    -- <https://docs.aws.amazon.com/kendra/latest/dg/deploying-search-experience-no-code.html#access-search-experience Providing access to your search page>.
    AssociatePersonasToEntities -> NonEmpty EntityPersonaConfiguration
personas :: Prelude.NonEmpty EntityPersonaConfiguration
  }
  deriving (AssociatePersonasToEntities -> AssociatePersonasToEntities -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AssociatePersonasToEntities -> AssociatePersonasToEntities -> Bool
$c/= :: AssociatePersonasToEntities -> AssociatePersonasToEntities -> Bool
== :: AssociatePersonasToEntities -> AssociatePersonasToEntities -> Bool
$c== :: AssociatePersonasToEntities -> AssociatePersonasToEntities -> Bool
Prelude.Eq, ReadPrec [AssociatePersonasToEntities]
ReadPrec AssociatePersonasToEntities
Int -> ReadS AssociatePersonasToEntities
ReadS [AssociatePersonasToEntities]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AssociatePersonasToEntities]
$creadListPrec :: ReadPrec [AssociatePersonasToEntities]
readPrec :: ReadPrec AssociatePersonasToEntities
$creadPrec :: ReadPrec AssociatePersonasToEntities
readList :: ReadS [AssociatePersonasToEntities]
$creadList :: ReadS [AssociatePersonasToEntities]
readsPrec :: Int -> ReadS AssociatePersonasToEntities
$creadsPrec :: Int -> ReadS AssociatePersonasToEntities
Prelude.Read, Int -> AssociatePersonasToEntities -> ShowS
[AssociatePersonasToEntities] -> ShowS
AssociatePersonasToEntities -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AssociatePersonasToEntities] -> ShowS
$cshowList :: [AssociatePersonasToEntities] -> ShowS
show :: AssociatePersonasToEntities -> String
$cshow :: AssociatePersonasToEntities -> String
showsPrec :: Int -> AssociatePersonasToEntities -> ShowS
$cshowsPrec :: Int -> AssociatePersonasToEntities -> ShowS
Prelude.Show, forall x.
Rep AssociatePersonasToEntities x -> AssociatePersonasToEntities
forall x.
AssociatePersonasToEntities -> Rep AssociatePersonasToEntities x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AssociatePersonasToEntities x -> AssociatePersonasToEntities
$cfrom :: forall x.
AssociatePersonasToEntities -> Rep AssociatePersonasToEntities x
Prelude.Generic)

-- |
-- Create a value of 'AssociatePersonasToEntities' 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:
--
-- 'id', 'associatePersonasToEntities_id' - The identifier of your Amazon Kendra experience.
--
-- 'indexId', 'associatePersonasToEntities_indexId' - The identifier of the index for your Amazon Kendra experience.
--
-- 'personas', 'associatePersonasToEntities_personas' - The personas that define the specific permissions of users or groups in
-- your IAM Identity Center identity source. The available personas or
-- access roles are @Owner@ and @Viewer@. For more information on these
-- personas, see
-- <https://docs.aws.amazon.com/kendra/latest/dg/deploying-search-experience-no-code.html#access-search-experience Providing access to your search page>.
newAssociatePersonasToEntities ::
  -- | 'id'
  Prelude.Text ->
  -- | 'indexId'
  Prelude.Text ->
  -- | 'personas'
  Prelude.NonEmpty EntityPersonaConfiguration ->
  AssociatePersonasToEntities
newAssociatePersonasToEntities :: Text
-> Text
-> NonEmpty EntityPersonaConfiguration
-> AssociatePersonasToEntities
newAssociatePersonasToEntities
  Text
pId_
  Text
pIndexId_
  NonEmpty EntityPersonaConfiguration
pPersonas_ =
    AssociatePersonasToEntities'
      { $sel:id:AssociatePersonasToEntities' :: Text
id = Text
pId_,
        $sel:indexId:AssociatePersonasToEntities' :: Text
indexId = Text
pIndexId_,
        $sel:personas:AssociatePersonasToEntities' :: NonEmpty EntityPersonaConfiguration
personas = forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced forall t b. AReview t b -> b -> t
Lens.# NonEmpty EntityPersonaConfiguration
pPersonas_
      }

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

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

-- | The personas that define the specific permissions of users or groups in
-- your IAM Identity Center identity source. The available personas or
-- access roles are @Owner@ and @Viewer@. For more information on these
-- personas, see
-- <https://docs.aws.amazon.com/kendra/latest/dg/deploying-search-experience-no-code.html#access-search-experience Providing access to your search page>.
associatePersonasToEntities_personas :: Lens.Lens' AssociatePersonasToEntities (Prelude.NonEmpty EntityPersonaConfiguration)
associatePersonasToEntities_personas :: Lens'
  AssociatePersonasToEntities (NonEmpty EntityPersonaConfiguration)
associatePersonasToEntities_personas = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociatePersonasToEntities' {NonEmpty EntityPersonaConfiguration
personas :: NonEmpty EntityPersonaConfiguration
$sel:personas:AssociatePersonasToEntities' :: AssociatePersonasToEntities -> NonEmpty EntityPersonaConfiguration
personas} -> NonEmpty EntityPersonaConfiguration
personas) (\s :: AssociatePersonasToEntities
s@AssociatePersonasToEntities' {} NonEmpty EntityPersonaConfiguration
a -> AssociatePersonasToEntities
s {$sel:personas:AssociatePersonasToEntities' :: NonEmpty EntityPersonaConfiguration
personas = NonEmpty EntityPersonaConfiguration
a} :: AssociatePersonasToEntities) 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 Core.AWSRequest AssociatePersonasToEntities where
  type
    AWSResponse AssociatePersonasToEntities =
      AssociatePersonasToEntitiesResponse
  request :: (Service -> Service)
-> AssociatePersonasToEntities
-> Request AssociatePersonasToEntities
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 AssociatePersonasToEntities
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse AssociatePersonasToEntities)))
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 (NonEmpty FailedEntity)
-> Int -> AssociatePersonasToEntitiesResponse
AssociatePersonasToEntitiesResponse'
            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
"FailedEntityList")
            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 AssociatePersonasToEntities where
  hashWithSalt :: Int -> AssociatePersonasToEntities -> Int
hashWithSalt Int
_salt AssociatePersonasToEntities' {NonEmpty EntityPersonaConfiguration
Text
personas :: NonEmpty EntityPersonaConfiguration
indexId :: Text
id :: Text
$sel:personas:AssociatePersonasToEntities' :: AssociatePersonasToEntities -> NonEmpty EntityPersonaConfiguration
$sel:indexId:AssociatePersonasToEntities' :: AssociatePersonasToEntities -> Text
$sel:id:AssociatePersonasToEntities' :: AssociatePersonasToEntities -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
indexId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty EntityPersonaConfiguration
personas

instance Prelude.NFData AssociatePersonasToEntities where
  rnf :: AssociatePersonasToEntities -> ()
rnf AssociatePersonasToEntities' {NonEmpty EntityPersonaConfiguration
Text
personas :: NonEmpty EntityPersonaConfiguration
indexId :: Text
id :: Text
$sel:personas:AssociatePersonasToEntities' :: AssociatePersonasToEntities -> NonEmpty EntityPersonaConfiguration
$sel:indexId:AssociatePersonasToEntities' :: AssociatePersonasToEntities -> Text
$sel:id:AssociatePersonasToEntities' :: AssociatePersonasToEntities -> Text
..} =
    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
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf NonEmpty EntityPersonaConfiguration
personas

instance Data.ToHeaders AssociatePersonasToEntities where
  toHeaders :: AssociatePersonasToEntities -> 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.AssociatePersonasToEntities" ::
                          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 AssociatePersonasToEntities where
  toJSON :: AssociatePersonasToEntities -> Value
toJSON AssociatePersonasToEntities' {NonEmpty EntityPersonaConfiguration
Text
personas :: NonEmpty EntityPersonaConfiguration
indexId :: Text
id :: Text
$sel:personas:AssociatePersonasToEntities' :: AssociatePersonasToEntities -> NonEmpty EntityPersonaConfiguration
$sel:indexId:AssociatePersonasToEntities' :: AssociatePersonasToEntities -> Text
$sel:id:AssociatePersonasToEntities' :: AssociatePersonasToEntities -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ 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),
            forall a. a -> Maybe a
Prelude.Just (Key
"Personas" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= NonEmpty EntityPersonaConfiguration
personas)
          ]
      )

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

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

-- | /See:/ 'newAssociatePersonasToEntitiesResponse' smart constructor.
data AssociatePersonasToEntitiesResponse = AssociatePersonasToEntitiesResponse'
  { -- | Lists the users or groups in your IAM Identity Center identity source
    -- that failed to properly configure with your Amazon Kendra experience.
    AssociatePersonasToEntitiesResponse
-> Maybe (NonEmpty FailedEntity)
failedEntityList :: Prelude.Maybe (Prelude.NonEmpty FailedEntity),
    -- | The response's http status code.
    AssociatePersonasToEntitiesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (AssociatePersonasToEntitiesResponse
-> AssociatePersonasToEntitiesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AssociatePersonasToEntitiesResponse
-> AssociatePersonasToEntitiesResponse -> Bool
$c/= :: AssociatePersonasToEntitiesResponse
-> AssociatePersonasToEntitiesResponse -> Bool
== :: AssociatePersonasToEntitiesResponse
-> AssociatePersonasToEntitiesResponse -> Bool
$c== :: AssociatePersonasToEntitiesResponse
-> AssociatePersonasToEntitiesResponse -> Bool
Prelude.Eq, ReadPrec [AssociatePersonasToEntitiesResponse]
ReadPrec AssociatePersonasToEntitiesResponse
Int -> ReadS AssociatePersonasToEntitiesResponse
ReadS [AssociatePersonasToEntitiesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AssociatePersonasToEntitiesResponse]
$creadListPrec :: ReadPrec [AssociatePersonasToEntitiesResponse]
readPrec :: ReadPrec AssociatePersonasToEntitiesResponse
$creadPrec :: ReadPrec AssociatePersonasToEntitiesResponse
readList :: ReadS [AssociatePersonasToEntitiesResponse]
$creadList :: ReadS [AssociatePersonasToEntitiesResponse]
readsPrec :: Int -> ReadS AssociatePersonasToEntitiesResponse
$creadsPrec :: Int -> ReadS AssociatePersonasToEntitiesResponse
Prelude.Read, Int -> AssociatePersonasToEntitiesResponse -> ShowS
[AssociatePersonasToEntitiesResponse] -> ShowS
AssociatePersonasToEntitiesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AssociatePersonasToEntitiesResponse] -> ShowS
$cshowList :: [AssociatePersonasToEntitiesResponse] -> ShowS
show :: AssociatePersonasToEntitiesResponse -> String
$cshow :: AssociatePersonasToEntitiesResponse -> String
showsPrec :: Int -> AssociatePersonasToEntitiesResponse -> ShowS
$cshowsPrec :: Int -> AssociatePersonasToEntitiesResponse -> ShowS
Prelude.Show, forall x.
Rep AssociatePersonasToEntitiesResponse x
-> AssociatePersonasToEntitiesResponse
forall x.
AssociatePersonasToEntitiesResponse
-> Rep AssociatePersonasToEntitiesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AssociatePersonasToEntitiesResponse x
-> AssociatePersonasToEntitiesResponse
$cfrom :: forall x.
AssociatePersonasToEntitiesResponse
-> Rep AssociatePersonasToEntitiesResponse x
Prelude.Generic)

-- |
-- Create a value of 'AssociatePersonasToEntitiesResponse' 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:
--
-- 'failedEntityList', 'associatePersonasToEntitiesResponse_failedEntityList' - Lists the users or groups in your IAM Identity Center identity source
-- that failed to properly configure with your Amazon Kendra experience.
--
-- 'httpStatus', 'associatePersonasToEntitiesResponse_httpStatus' - The response's http status code.
newAssociatePersonasToEntitiesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  AssociatePersonasToEntitiesResponse
newAssociatePersonasToEntitiesResponse :: Int -> AssociatePersonasToEntitiesResponse
newAssociatePersonasToEntitiesResponse Int
pHttpStatus_ =
  AssociatePersonasToEntitiesResponse'
    { $sel:failedEntityList:AssociatePersonasToEntitiesResponse' :: Maybe (NonEmpty FailedEntity)
failedEntityList =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:AssociatePersonasToEntitiesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Lists the users or groups in your IAM Identity Center identity source
-- that failed to properly configure with your Amazon Kendra experience.
associatePersonasToEntitiesResponse_failedEntityList :: Lens.Lens' AssociatePersonasToEntitiesResponse (Prelude.Maybe (Prelude.NonEmpty FailedEntity))
associatePersonasToEntitiesResponse_failedEntityList :: Lens'
  AssociatePersonasToEntitiesResponse (Maybe (NonEmpty FailedEntity))
associatePersonasToEntitiesResponse_failedEntityList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociatePersonasToEntitiesResponse' {Maybe (NonEmpty FailedEntity)
failedEntityList :: Maybe (NonEmpty FailedEntity)
$sel:failedEntityList:AssociatePersonasToEntitiesResponse' :: AssociatePersonasToEntitiesResponse
-> Maybe (NonEmpty FailedEntity)
failedEntityList} -> Maybe (NonEmpty FailedEntity)
failedEntityList) (\s :: AssociatePersonasToEntitiesResponse
s@AssociatePersonasToEntitiesResponse' {} Maybe (NonEmpty FailedEntity)
a -> AssociatePersonasToEntitiesResponse
s {$sel:failedEntityList:AssociatePersonasToEntitiesResponse' :: Maybe (NonEmpty FailedEntity)
failedEntityList = Maybe (NonEmpty FailedEntity)
a} :: AssociatePersonasToEntitiesResponse) 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.
associatePersonasToEntitiesResponse_httpStatus :: Lens.Lens' AssociatePersonasToEntitiesResponse Prelude.Int
associatePersonasToEntitiesResponse_httpStatus :: Lens' AssociatePersonasToEntitiesResponse Int
associatePersonasToEntitiesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociatePersonasToEntitiesResponse' {Int
httpStatus :: Int
$sel:httpStatus:AssociatePersonasToEntitiesResponse' :: AssociatePersonasToEntitiesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: AssociatePersonasToEntitiesResponse
s@AssociatePersonasToEntitiesResponse' {} Int
a -> AssociatePersonasToEntitiesResponse
s {$sel:httpStatus:AssociatePersonasToEntitiesResponse' :: Int
httpStatus = Int
a} :: AssociatePersonasToEntitiesResponse)

instance
  Prelude.NFData
    AssociatePersonasToEntitiesResponse
  where
  rnf :: AssociatePersonasToEntitiesResponse -> ()
rnf AssociatePersonasToEntitiesResponse' {Int
Maybe (NonEmpty FailedEntity)
httpStatus :: Int
failedEntityList :: Maybe (NonEmpty FailedEntity)
$sel:httpStatus:AssociatePersonasToEntitiesResponse' :: AssociatePersonasToEntitiesResponse -> Int
$sel:failedEntityList:AssociatePersonasToEntitiesResponse' :: AssociatePersonasToEntitiesResponse
-> Maybe (NonEmpty FailedEntity)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty FailedEntity)
failedEntityList
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus