{-# 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.AssociateEntitiesToExperience
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Grants users or groups in your IAM Identity Center identity source
-- 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.AssociateEntitiesToExperience
  ( -- * Creating a Request
    AssociateEntitiesToExperience (..),
    newAssociateEntitiesToExperience,

    -- * Request Lenses
    associateEntitiesToExperience_id,
    associateEntitiesToExperience_indexId,
    associateEntitiesToExperience_entityList,

    -- * Destructuring the Response
    AssociateEntitiesToExperienceResponse (..),
    newAssociateEntitiesToExperienceResponse,

    -- * Response Lenses
    associateEntitiesToExperienceResponse_failedEntityList,
    associateEntitiesToExperienceResponse_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:/ 'newAssociateEntitiesToExperience' smart constructor.
data AssociateEntitiesToExperience = AssociateEntitiesToExperience'
  { -- | The identifier of your Amazon Kendra experience.
    AssociateEntitiesToExperience -> Text
id :: Prelude.Text,
    -- | The identifier of the index for your Amazon Kendra experience.
    AssociateEntitiesToExperience -> Text
indexId :: Prelude.Text,
    -- | Lists users or groups in your IAM Identity Center identity source.
    AssociateEntitiesToExperience -> NonEmpty EntityConfiguration
entityList :: Prelude.NonEmpty EntityConfiguration
  }
  deriving (AssociateEntitiesToExperience
-> AssociateEntitiesToExperience -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AssociateEntitiesToExperience
-> AssociateEntitiesToExperience -> Bool
$c/= :: AssociateEntitiesToExperience
-> AssociateEntitiesToExperience -> Bool
== :: AssociateEntitiesToExperience
-> AssociateEntitiesToExperience -> Bool
$c== :: AssociateEntitiesToExperience
-> AssociateEntitiesToExperience -> Bool
Prelude.Eq, ReadPrec [AssociateEntitiesToExperience]
ReadPrec AssociateEntitiesToExperience
Int -> ReadS AssociateEntitiesToExperience
ReadS [AssociateEntitiesToExperience]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AssociateEntitiesToExperience]
$creadListPrec :: ReadPrec [AssociateEntitiesToExperience]
readPrec :: ReadPrec AssociateEntitiesToExperience
$creadPrec :: ReadPrec AssociateEntitiesToExperience
readList :: ReadS [AssociateEntitiesToExperience]
$creadList :: ReadS [AssociateEntitiesToExperience]
readsPrec :: Int -> ReadS AssociateEntitiesToExperience
$creadsPrec :: Int -> ReadS AssociateEntitiesToExperience
Prelude.Read, Int -> AssociateEntitiesToExperience -> ShowS
[AssociateEntitiesToExperience] -> ShowS
AssociateEntitiesToExperience -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AssociateEntitiesToExperience] -> ShowS
$cshowList :: [AssociateEntitiesToExperience] -> ShowS
show :: AssociateEntitiesToExperience -> String
$cshow :: AssociateEntitiesToExperience -> String
showsPrec :: Int -> AssociateEntitiesToExperience -> ShowS
$cshowsPrec :: Int -> AssociateEntitiesToExperience -> ShowS
Prelude.Show, forall x.
Rep AssociateEntitiesToExperience x
-> AssociateEntitiesToExperience
forall x.
AssociateEntitiesToExperience
-> Rep AssociateEntitiesToExperience x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AssociateEntitiesToExperience x
-> AssociateEntitiesToExperience
$cfrom :: forall x.
AssociateEntitiesToExperience
-> Rep AssociateEntitiesToExperience x
Prelude.Generic)

-- |
-- Create a value of 'AssociateEntitiesToExperience' 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', 'associateEntitiesToExperience_id' - The identifier of your Amazon Kendra experience.
--
-- 'indexId', 'associateEntitiesToExperience_indexId' - The identifier of the index for your Amazon Kendra experience.
--
-- 'entityList', 'associateEntitiesToExperience_entityList' - Lists users or groups in your IAM Identity Center identity source.
newAssociateEntitiesToExperience ::
  -- | 'id'
  Prelude.Text ->
  -- | 'indexId'
  Prelude.Text ->
  -- | 'entityList'
  Prelude.NonEmpty EntityConfiguration ->
  AssociateEntitiesToExperience
newAssociateEntitiesToExperience :: Text
-> Text
-> NonEmpty EntityConfiguration
-> AssociateEntitiesToExperience
newAssociateEntitiesToExperience
  Text
pId_
  Text
pIndexId_
  NonEmpty EntityConfiguration
pEntityList_ =
    AssociateEntitiesToExperience'
      { $sel:id:AssociateEntitiesToExperience' :: Text
id = Text
pId_,
        $sel:indexId:AssociateEntitiesToExperience' :: Text
indexId = Text
pIndexId_,
        $sel:entityList:AssociateEntitiesToExperience' :: NonEmpty EntityConfiguration
entityList =
          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 EntityConfiguration
pEntityList_
      }

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

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

-- | Lists users or groups in your IAM Identity Center identity source.
associateEntitiesToExperience_entityList :: Lens.Lens' AssociateEntitiesToExperience (Prelude.NonEmpty EntityConfiguration)
associateEntitiesToExperience_entityList :: Lens' AssociateEntitiesToExperience (NonEmpty EntityConfiguration)
associateEntitiesToExperience_entityList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateEntitiesToExperience' {NonEmpty EntityConfiguration
entityList :: NonEmpty EntityConfiguration
$sel:entityList:AssociateEntitiesToExperience' :: AssociateEntitiesToExperience -> NonEmpty EntityConfiguration
entityList} -> NonEmpty EntityConfiguration
entityList) (\s :: AssociateEntitiesToExperience
s@AssociateEntitiesToExperience' {} NonEmpty EntityConfiguration
a -> AssociateEntitiesToExperience
s {$sel:entityList:AssociateEntitiesToExperience' :: NonEmpty EntityConfiguration
entityList = NonEmpty EntityConfiguration
a} :: AssociateEntitiesToExperience) 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
    AssociateEntitiesToExperience
  where
  type
    AWSResponse AssociateEntitiesToExperience =
      AssociateEntitiesToExperienceResponse
  request :: (Service -> Service)
-> AssociateEntitiesToExperience
-> Request AssociateEntitiesToExperience
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 AssociateEntitiesToExperience
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse AssociateEntitiesToExperience)))
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 -> AssociateEntitiesToExperienceResponse
AssociateEntitiesToExperienceResponse'
            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
    AssociateEntitiesToExperience
  where
  hashWithSalt :: Int -> AssociateEntitiesToExperience -> Int
hashWithSalt Int
_salt AssociateEntitiesToExperience' {NonEmpty EntityConfiguration
Text
entityList :: NonEmpty EntityConfiguration
indexId :: Text
id :: Text
$sel:entityList:AssociateEntitiesToExperience' :: AssociateEntitiesToExperience -> NonEmpty EntityConfiguration
$sel:indexId:AssociateEntitiesToExperience' :: AssociateEntitiesToExperience -> Text
$sel:id:AssociateEntitiesToExperience' :: AssociateEntitiesToExperience -> 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 EntityConfiguration
entityList

instance Prelude.NFData AssociateEntitiesToExperience where
  rnf :: AssociateEntitiesToExperience -> ()
rnf AssociateEntitiesToExperience' {NonEmpty EntityConfiguration
Text
entityList :: NonEmpty EntityConfiguration
indexId :: Text
id :: Text
$sel:entityList:AssociateEntitiesToExperience' :: AssociateEntitiesToExperience -> NonEmpty EntityConfiguration
$sel:indexId:AssociateEntitiesToExperience' :: AssociateEntitiesToExperience -> Text
$sel:id:AssociateEntitiesToExperience' :: AssociateEntitiesToExperience -> 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 EntityConfiguration
entityList

instance Data.ToHeaders AssociateEntitiesToExperience where
  toHeaders :: AssociateEntitiesToExperience -> 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.AssociateEntitiesToExperience" ::
                          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 AssociateEntitiesToExperience where
  toJSON :: AssociateEntitiesToExperience -> Value
toJSON AssociateEntitiesToExperience' {NonEmpty EntityConfiguration
Text
entityList :: NonEmpty EntityConfiguration
indexId :: Text
id :: Text
$sel:entityList:AssociateEntitiesToExperience' :: AssociateEntitiesToExperience -> NonEmpty EntityConfiguration
$sel:indexId:AssociateEntitiesToExperience' :: AssociateEntitiesToExperience -> Text
$sel:id:AssociateEntitiesToExperience' :: AssociateEntitiesToExperience -> 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
"EntityList" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= NonEmpty EntityConfiguration
entityList)
          ]
      )

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

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

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

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

instance
  Prelude.NFData
    AssociateEntitiesToExperienceResponse
  where
  rnf :: AssociateEntitiesToExperienceResponse -> ()
rnf AssociateEntitiesToExperienceResponse' {Int
Maybe (NonEmpty FailedEntity)
httpStatus :: Int
failedEntityList :: Maybe (NonEmpty FailedEntity)
$sel:httpStatus:AssociateEntitiesToExperienceResponse' :: AssociateEntitiesToExperienceResponse -> Int
$sel:failedEntityList:AssociateEntitiesToExperienceResponse' :: AssociateEntitiesToExperienceResponse
-> 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