{-# 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.DescribeQuerySuggestionsBlockList
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets information about a block list used for query suggestions for an
-- index.
--
-- This is used to check the current settings that are applied to a block
-- list.
--
-- @DescribeQuerySuggestionsBlockList@ is currently not supported in the
-- Amazon Web Services GovCloud (US-West) region.
module Amazonka.Kendra.DescribeQuerySuggestionsBlockList
  ( -- * Creating a Request
    DescribeQuerySuggestionsBlockList (..),
    newDescribeQuerySuggestionsBlockList,

    -- * Request Lenses
    describeQuerySuggestionsBlockList_indexId,
    describeQuerySuggestionsBlockList_id,

    -- * Destructuring the Response
    DescribeQuerySuggestionsBlockListResponse (..),
    newDescribeQuerySuggestionsBlockListResponse,

    -- * Response Lenses
    describeQuerySuggestionsBlockListResponse_createdAt,
    describeQuerySuggestionsBlockListResponse_description,
    describeQuerySuggestionsBlockListResponse_errorMessage,
    describeQuerySuggestionsBlockListResponse_fileSizeBytes,
    describeQuerySuggestionsBlockListResponse_id,
    describeQuerySuggestionsBlockListResponse_indexId,
    describeQuerySuggestionsBlockListResponse_itemCount,
    describeQuerySuggestionsBlockListResponse_name,
    describeQuerySuggestionsBlockListResponse_roleArn,
    describeQuerySuggestionsBlockListResponse_sourceS3Path,
    describeQuerySuggestionsBlockListResponse_status,
    describeQuerySuggestionsBlockListResponse_updatedAt,
    describeQuerySuggestionsBlockListResponse_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:/ 'newDescribeQuerySuggestionsBlockList' smart constructor.
data DescribeQuerySuggestionsBlockList = DescribeQuerySuggestionsBlockList'
  { -- | The identifier of the index for the block list.
    DescribeQuerySuggestionsBlockList -> Text
indexId :: Prelude.Text,
    -- | The identifier of the block list you want to get information on.
    DescribeQuerySuggestionsBlockList -> Text
id :: Prelude.Text
  }
  deriving (DescribeQuerySuggestionsBlockList
-> DescribeQuerySuggestionsBlockList -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeQuerySuggestionsBlockList
-> DescribeQuerySuggestionsBlockList -> Bool
$c/= :: DescribeQuerySuggestionsBlockList
-> DescribeQuerySuggestionsBlockList -> Bool
== :: DescribeQuerySuggestionsBlockList
-> DescribeQuerySuggestionsBlockList -> Bool
$c== :: DescribeQuerySuggestionsBlockList
-> DescribeQuerySuggestionsBlockList -> Bool
Prelude.Eq, ReadPrec [DescribeQuerySuggestionsBlockList]
ReadPrec DescribeQuerySuggestionsBlockList
Int -> ReadS DescribeQuerySuggestionsBlockList
ReadS [DescribeQuerySuggestionsBlockList]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeQuerySuggestionsBlockList]
$creadListPrec :: ReadPrec [DescribeQuerySuggestionsBlockList]
readPrec :: ReadPrec DescribeQuerySuggestionsBlockList
$creadPrec :: ReadPrec DescribeQuerySuggestionsBlockList
readList :: ReadS [DescribeQuerySuggestionsBlockList]
$creadList :: ReadS [DescribeQuerySuggestionsBlockList]
readsPrec :: Int -> ReadS DescribeQuerySuggestionsBlockList
$creadsPrec :: Int -> ReadS DescribeQuerySuggestionsBlockList
Prelude.Read, Int -> DescribeQuerySuggestionsBlockList -> ShowS
[DescribeQuerySuggestionsBlockList] -> ShowS
DescribeQuerySuggestionsBlockList -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeQuerySuggestionsBlockList] -> ShowS
$cshowList :: [DescribeQuerySuggestionsBlockList] -> ShowS
show :: DescribeQuerySuggestionsBlockList -> String
$cshow :: DescribeQuerySuggestionsBlockList -> String
showsPrec :: Int -> DescribeQuerySuggestionsBlockList -> ShowS
$cshowsPrec :: Int -> DescribeQuerySuggestionsBlockList -> ShowS
Prelude.Show, forall x.
Rep DescribeQuerySuggestionsBlockList x
-> DescribeQuerySuggestionsBlockList
forall x.
DescribeQuerySuggestionsBlockList
-> Rep DescribeQuerySuggestionsBlockList x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeQuerySuggestionsBlockList x
-> DescribeQuerySuggestionsBlockList
$cfrom :: forall x.
DescribeQuerySuggestionsBlockList
-> Rep DescribeQuerySuggestionsBlockList x
Prelude.Generic)

-- |
-- Create a value of 'DescribeQuerySuggestionsBlockList' 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:
--
-- 'indexId', 'describeQuerySuggestionsBlockList_indexId' - The identifier of the index for the block list.
--
-- 'id', 'describeQuerySuggestionsBlockList_id' - The identifier of the block list you want to get information on.
newDescribeQuerySuggestionsBlockList ::
  -- | 'indexId'
  Prelude.Text ->
  -- | 'id'
  Prelude.Text ->
  DescribeQuerySuggestionsBlockList
newDescribeQuerySuggestionsBlockList :: Text -> Text -> DescribeQuerySuggestionsBlockList
newDescribeQuerySuggestionsBlockList Text
pIndexId_ Text
pId_ =
  DescribeQuerySuggestionsBlockList'
    { $sel:indexId:DescribeQuerySuggestionsBlockList' :: Text
indexId =
        Text
pIndexId_,
      $sel:id:DescribeQuerySuggestionsBlockList' :: Text
id = Text
pId_
    }

-- | The identifier of the index for the block list.
describeQuerySuggestionsBlockList_indexId :: Lens.Lens' DescribeQuerySuggestionsBlockList Prelude.Text
describeQuerySuggestionsBlockList_indexId :: Lens' DescribeQuerySuggestionsBlockList Text
describeQuerySuggestionsBlockList_indexId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeQuerySuggestionsBlockList' {Text
indexId :: Text
$sel:indexId:DescribeQuerySuggestionsBlockList' :: DescribeQuerySuggestionsBlockList -> Text
indexId} -> Text
indexId) (\s :: DescribeQuerySuggestionsBlockList
s@DescribeQuerySuggestionsBlockList' {} Text
a -> DescribeQuerySuggestionsBlockList
s {$sel:indexId:DescribeQuerySuggestionsBlockList' :: Text
indexId = Text
a} :: DescribeQuerySuggestionsBlockList)

-- | The identifier of the block list you want to get information on.
describeQuerySuggestionsBlockList_id :: Lens.Lens' DescribeQuerySuggestionsBlockList Prelude.Text
describeQuerySuggestionsBlockList_id :: Lens' DescribeQuerySuggestionsBlockList Text
describeQuerySuggestionsBlockList_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeQuerySuggestionsBlockList' {Text
id :: Text
$sel:id:DescribeQuerySuggestionsBlockList' :: DescribeQuerySuggestionsBlockList -> Text
id} -> Text
id) (\s :: DescribeQuerySuggestionsBlockList
s@DescribeQuerySuggestionsBlockList' {} Text
a -> DescribeQuerySuggestionsBlockList
s {$sel:id:DescribeQuerySuggestionsBlockList' :: Text
id = Text
a} :: DescribeQuerySuggestionsBlockList)

instance
  Core.AWSRequest
    DescribeQuerySuggestionsBlockList
  where
  type
    AWSResponse DescribeQuerySuggestionsBlockList =
      DescribeQuerySuggestionsBlockListResponse
  request :: (Service -> Service)
-> DescribeQuerySuggestionsBlockList
-> Request DescribeQuerySuggestionsBlockList
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 DescribeQuerySuggestionsBlockList
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse DescribeQuerySuggestionsBlockList)))
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 POSIX
-> Maybe Text
-> Maybe Text
-> Maybe Integer
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe S3Path
-> Maybe QuerySuggestionsBlockListStatus
-> Maybe POSIX
-> Int
-> DescribeQuerySuggestionsBlockListResponse
DescribeQuerySuggestionsBlockListResponse'
            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
"CreatedAt")
            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
"Description")
            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
"ErrorMessage")
            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
"FileSizeBytes")
            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
"Id")
            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
"IndexId")
            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
"ItemCount")
            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
"Name")
            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
"RoleArn")
            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
"SourceS3Path")
            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
"Status")
            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
"UpdatedAt")
            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
    DescribeQuerySuggestionsBlockList
  where
  hashWithSalt :: Int -> DescribeQuerySuggestionsBlockList -> Int
hashWithSalt
    Int
_salt
    DescribeQuerySuggestionsBlockList' {Text
id :: Text
indexId :: Text
$sel:id:DescribeQuerySuggestionsBlockList' :: DescribeQuerySuggestionsBlockList -> Text
$sel:indexId:DescribeQuerySuggestionsBlockList' :: DescribeQuerySuggestionsBlockList -> Text
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
indexId
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id

instance
  Prelude.NFData
    DescribeQuerySuggestionsBlockList
  where
  rnf :: DescribeQuerySuggestionsBlockList -> ()
rnf DescribeQuerySuggestionsBlockList' {Text
id :: Text
indexId :: Text
$sel:id:DescribeQuerySuggestionsBlockList' :: DescribeQuerySuggestionsBlockList -> Text
$sel:indexId:DescribeQuerySuggestionsBlockList' :: DescribeQuerySuggestionsBlockList -> Text
..} =
    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 Text
id

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

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

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

-- | /See:/ 'newDescribeQuerySuggestionsBlockListResponse' smart constructor.
data DescribeQuerySuggestionsBlockListResponse = DescribeQuerySuggestionsBlockListResponse'
  { -- | The date-time a block list for query suggestions was created.
    DescribeQuerySuggestionsBlockListResponse -> Maybe POSIX
createdAt :: Prelude.Maybe Data.POSIX,
    -- | The description for the block list.
    DescribeQuerySuggestionsBlockListResponse -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The error message containing details if there are issues processing the
    -- block list.
    DescribeQuerySuggestionsBlockListResponse -> Maybe Text
errorMessage :: Prelude.Maybe Prelude.Text,
    -- | The current size of the block list text file in S3.
    DescribeQuerySuggestionsBlockListResponse -> Maybe Integer
fileSizeBytes :: Prelude.Maybe Prelude.Integer,
    -- | The identifier of the block list.
    DescribeQuerySuggestionsBlockListResponse -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | The identifier of the index for the block list.
    DescribeQuerySuggestionsBlockListResponse -> Maybe Text
indexId :: Prelude.Maybe Prelude.Text,
    -- | The current number of valid, non-empty words or phrases in the block
    -- list text file.
    DescribeQuerySuggestionsBlockListResponse -> Maybe Int
itemCount :: Prelude.Maybe Prelude.Int,
    -- | The name of the block list.
    DescribeQuerySuggestionsBlockListResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The IAM (Identity and Access Management) role used by Amazon Kendra to
    -- access the block list text file in S3.
    --
    -- The role needs S3 read permissions to your file in S3 and needs to give
    -- STS (Security Token Service) assume role permissions to Amazon Kendra.
    DescribeQuerySuggestionsBlockListResponse -> Maybe Text
roleArn :: Prelude.Maybe Prelude.Text,
    -- | Shows the current S3 path to your block list text file in your S3
    -- bucket.
    --
    -- Each block word or phrase should be on a separate line in a text file.
    --
    -- For information on the current quota limits for block lists, see
    -- <https://docs.aws.amazon.com/kendra/latest/dg/quotas.html Quotas for Amazon Kendra>.
    DescribeQuerySuggestionsBlockListResponse -> Maybe S3Path
sourceS3Path :: Prelude.Maybe S3Path,
    -- | The current status of the block list. When the value is @ACTIVE@, the
    -- block list is ready for use.
    DescribeQuerySuggestionsBlockListResponse
-> Maybe QuerySuggestionsBlockListStatus
status :: Prelude.Maybe QuerySuggestionsBlockListStatus,
    -- | The date-time a block list for query suggestions was last updated.
    DescribeQuerySuggestionsBlockListResponse -> Maybe POSIX
updatedAt :: Prelude.Maybe Data.POSIX,
    -- | The response's http status code.
    DescribeQuerySuggestionsBlockListResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeQuerySuggestionsBlockListResponse
-> DescribeQuerySuggestionsBlockListResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeQuerySuggestionsBlockListResponse
-> DescribeQuerySuggestionsBlockListResponse -> Bool
$c/= :: DescribeQuerySuggestionsBlockListResponse
-> DescribeQuerySuggestionsBlockListResponse -> Bool
== :: DescribeQuerySuggestionsBlockListResponse
-> DescribeQuerySuggestionsBlockListResponse -> Bool
$c== :: DescribeQuerySuggestionsBlockListResponse
-> DescribeQuerySuggestionsBlockListResponse -> Bool
Prelude.Eq, ReadPrec [DescribeQuerySuggestionsBlockListResponse]
ReadPrec DescribeQuerySuggestionsBlockListResponse
Int -> ReadS DescribeQuerySuggestionsBlockListResponse
ReadS [DescribeQuerySuggestionsBlockListResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeQuerySuggestionsBlockListResponse]
$creadListPrec :: ReadPrec [DescribeQuerySuggestionsBlockListResponse]
readPrec :: ReadPrec DescribeQuerySuggestionsBlockListResponse
$creadPrec :: ReadPrec DescribeQuerySuggestionsBlockListResponse
readList :: ReadS [DescribeQuerySuggestionsBlockListResponse]
$creadList :: ReadS [DescribeQuerySuggestionsBlockListResponse]
readsPrec :: Int -> ReadS DescribeQuerySuggestionsBlockListResponse
$creadsPrec :: Int -> ReadS DescribeQuerySuggestionsBlockListResponse
Prelude.Read, Int -> DescribeQuerySuggestionsBlockListResponse -> ShowS
[DescribeQuerySuggestionsBlockListResponse] -> ShowS
DescribeQuerySuggestionsBlockListResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeQuerySuggestionsBlockListResponse] -> ShowS
$cshowList :: [DescribeQuerySuggestionsBlockListResponse] -> ShowS
show :: DescribeQuerySuggestionsBlockListResponse -> String
$cshow :: DescribeQuerySuggestionsBlockListResponse -> String
showsPrec :: Int -> DescribeQuerySuggestionsBlockListResponse -> ShowS
$cshowsPrec :: Int -> DescribeQuerySuggestionsBlockListResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeQuerySuggestionsBlockListResponse x
-> DescribeQuerySuggestionsBlockListResponse
forall x.
DescribeQuerySuggestionsBlockListResponse
-> Rep DescribeQuerySuggestionsBlockListResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeQuerySuggestionsBlockListResponse x
-> DescribeQuerySuggestionsBlockListResponse
$cfrom :: forall x.
DescribeQuerySuggestionsBlockListResponse
-> Rep DescribeQuerySuggestionsBlockListResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeQuerySuggestionsBlockListResponse' 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:
--
-- 'createdAt', 'describeQuerySuggestionsBlockListResponse_createdAt' - The date-time a block list for query suggestions was created.
--
-- 'description', 'describeQuerySuggestionsBlockListResponse_description' - The description for the block list.
--
-- 'errorMessage', 'describeQuerySuggestionsBlockListResponse_errorMessage' - The error message containing details if there are issues processing the
-- block list.
--
-- 'fileSizeBytes', 'describeQuerySuggestionsBlockListResponse_fileSizeBytes' - The current size of the block list text file in S3.
--
-- 'id', 'describeQuerySuggestionsBlockListResponse_id' - The identifier of the block list.
--
-- 'indexId', 'describeQuerySuggestionsBlockListResponse_indexId' - The identifier of the index for the block list.
--
-- 'itemCount', 'describeQuerySuggestionsBlockListResponse_itemCount' - The current number of valid, non-empty words or phrases in the block
-- list text file.
--
-- 'name', 'describeQuerySuggestionsBlockListResponse_name' - The name of the block list.
--
-- 'roleArn', 'describeQuerySuggestionsBlockListResponse_roleArn' - The IAM (Identity and Access Management) role used by Amazon Kendra to
-- access the block list text file in S3.
--
-- The role needs S3 read permissions to your file in S3 and needs to give
-- STS (Security Token Service) assume role permissions to Amazon Kendra.
--
-- 'sourceS3Path', 'describeQuerySuggestionsBlockListResponse_sourceS3Path' - Shows the current S3 path to your block list text file in your S3
-- bucket.
--
-- Each block word or phrase should be on a separate line in a text file.
--
-- For information on the current quota limits for block lists, see
-- <https://docs.aws.amazon.com/kendra/latest/dg/quotas.html Quotas for Amazon Kendra>.
--
-- 'status', 'describeQuerySuggestionsBlockListResponse_status' - The current status of the block list. When the value is @ACTIVE@, the
-- block list is ready for use.
--
-- 'updatedAt', 'describeQuerySuggestionsBlockListResponse_updatedAt' - The date-time a block list for query suggestions was last updated.
--
-- 'httpStatus', 'describeQuerySuggestionsBlockListResponse_httpStatus' - The response's http status code.
newDescribeQuerySuggestionsBlockListResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeQuerySuggestionsBlockListResponse
newDescribeQuerySuggestionsBlockListResponse :: Int -> DescribeQuerySuggestionsBlockListResponse
newDescribeQuerySuggestionsBlockListResponse
  Int
pHttpStatus_ =
    DescribeQuerySuggestionsBlockListResponse'
      { $sel:createdAt:DescribeQuerySuggestionsBlockListResponse' :: Maybe POSIX
createdAt =
          forall a. Maybe a
Prelude.Nothing,
        $sel:description:DescribeQuerySuggestionsBlockListResponse' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
        $sel:errorMessage:DescribeQuerySuggestionsBlockListResponse' :: Maybe Text
errorMessage = forall a. Maybe a
Prelude.Nothing,
        $sel:fileSizeBytes:DescribeQuerySuggestionsBlockListResponse' :: Maybe Integer
fileSizeBytes = forall a. Maybe a
Prelude.Nothing,
        $sel:id:DescribeQuerySuggestionsBlockListResponse' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
        $sel:indexId:DescribeQuerySuggestionsBlockListResponse' :: Maybe Text
indexId = forall a. Maybe a
Prelude.Nothing,
        $sel:itemCount:DescribeQuerySuggestionsBlockListResponse' :: Maybe Int
itemCount = forall a. Maybe a
Prelude.Nothing,
        $sel:name:DescribeQuerySuggestionsBlockListResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
        $sel:roleArn:DescribeQuerySuggestionsBlockListResponse' :: Maybe Text
roleArn = forall a. Maybe a
Prelude.Nothing,
        $sel:sourceS3Path:DescribeQuerySuggestionsBlockListResponse' :: Maybe S3Path
sourceS3Path = forall a. Maybe a
Prelude.Nothing,
        $sel:status:DescribeQuerySuggestionsBlockListResponse' :: Maybe QuerySuggestionsBlockListStatus
status = forall a. Maybe a
Prelude.Nothing,
        $sel:updatedAt:DescribeQuerySuggestionsBlockListResponse' :: Maybe POSIX
updatedAt = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:DescribeQuerySuggestionsBlockListResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | The date-time a block list for query suggestions was created.
describeQuerySuggestionsBlockListResponse_createdAt :: Lens.Lens' DescribeQuerySuggestionsBlockListResponse (Prelude.Maybe Prelude.UTCTime)
describeQuerySuggestionsBlockListResponse_createdAt :: Lens' DescribeQuerySuggestionsBlockListResponse (Maybe UTCTime)
describeQuerySuggestionsBlockListResponse_createdAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeQuerySuggestionsBlockListResponse' {Maybe POSIX
createdAt :: Maybe POSIX
$sel:createdAt:DescribeQuerySuggestionsBlockListResponse' :: DescribeQuerySuggestionsBlockListResponse -> Maybe POSIX
createdAt} -> Maybe POSIX
createdAt) (\s :: DescribeQuerySuggestionsBlockListResponse
s@DescribeQuerySuggestionsBlockListResponse' {} Maybe POSIX
a -> DescribeQuerySuggestionsBlockListResponse
s {$sel:createdAt:DescribeQuerySuggestionsBlockListResponse' :: Maybe POSIX
createdAt = Maybe POSIX
a} :: DescribeQuerySuggestionsBlockListResponse) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The description for the block list.
describeQuerySuggestionsBlockListResponse_description :: Lens.Lens' DescribeQuerySuggestionsBlockListResponse (Prelude.Maybe Prelude.Text)
describeQuerySuggestionsBlockListResponse_description :: Lens' DescribeQuerySuggestionsBlockListResponse (Maybe Text)
describeQuerySuggestionsBlockListResponse_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeQuerySuggestionsBlockListResponse' {Maybe Text
description :: Maybe Text
$sel:description:DescribeQuerySuggestionsBlockListResponse' :: DescribeQuerySuggestionsBlockListResponse -> Maybe Text
description} -> Maybe Text
description) (\s :: DescribeQuerySuggestionsBlockListResponse
s@DescribeQuerySuggestionsBlockListResponse' {} Maybe Text
a -> DescribeQuerySuggestionsBlockListResponse
s {$sel:description:DescribeQuerySuggestionsBlockListResponse' :: Maybe Text
description = Maybe Text
a} :: DescribeQuerySuggestionsBlockListResponse)

-- | The error message containing details if there are issues processing the
-- block list.
describeQuerySuggestionsBlockListResponse_errorMessage :: Lens.Lens' DescribeQuerySuggestionsBlockListResponse (Prelude.Maybe Prelude.Text)
describeQuerySuggestionsBlockListResponse_errorMessage :: Lens' DescribeQuerySuggestionsBlockListResponse (Maybe Text)
describeQuerySuggestionsBlockListResponse_errorMessage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeQuerySuggestionsBlockListResponse' {Maybe Text
errorMessage :: Maybe Text
$sel:errorMessage:DescribeQuerySuggestionsBlockListResponse' :: DescribeQuerySuggestionsBlockListResponse -> Maybe Text
errorMessage} -> Maybe Text
errorMessage) (\s :: DescribeQuerySuggestionsBlockListResponse
s@DescribeQuerySuggestionsBlockListResponse' {} Maybe Text
a -> DescribeQuerySuggestionsBlockListResponse
s {$sel:errorMessage:DescribeQuerySuggestionsBlockListResponse' :: Maybe Text
errorMessage = Maybe Text
a} :: DescribeQuerySuggestionsBlockListResponse)

-- | The current size of the block list text file in S3.
describeQuerySuggestionsBlockListResponse_fileSizeBytes :: Lens.Lens' DescribeQuerySuggestionsBlockListResponse (Prelude.Maybe Prelude.Integer)
describeQuerySuggestionsBlockListResponse_fileSizeBytes :: Lens' DescribeQuerySuggestionsBlockListResponse (Maybe Integer)
describeQuerySuggestionsBlockListResponse_fileSizeBytes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeQuerySuggestionsBlockListResponse' {Maybe Integer
fileSizeBytes :: Maybe Integer
$sel:fileSizeBytes:DescribeQuerySuggestionsBlockListResponse' :: DescribeQuerySuggestionsBlockListResponse -> Maybe Integer
fileSizeBytes} -> Maybe Integer
fileSizeBytes) (\s :: DescribeQuerySuggestionsBlockListResponse
s@DescribeQuerySuggestionsBlockListResponse' {} Maybe Integer
a -> DescribeQuerySuggestionsBlockListResponse
s {$sel:fileSizeBytes:DescribeQuerySuggestionsBlockListResponse' :: Maybe Integer
fileSizeBytes = Maybe Integer
a} :: DescribeQuerySuggestionsBlockListResponse)

-- | The identifier of the block list.
describeQuerySuggestionsBlockListResponse_id :: Lens.Lens' DescribeQuerySuggestionsBlockListResponse (Prelude.Maybe Prelude.Text)
describeQuerySuggestionsBlockListResponse_id :: Lens' DescribeQuerySuggestionsBlockListResponse (Maybe Text)
describeQuerySuggestionsBlockListResponse_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeQuerySuggestionsBlockListResponse' {Maybe Text
id :: Maybe Text
$sel:id:DescribeQuerySuggestionsBlockListResponse' :: DescribeQuerySuggestionsBlockListResponse -> Maybe Text
id} -> Maybe Text
id) (\s :: DescribeQuerySuggestionsBlockListResponse
s@DescribeQuerySuggestionsBlockListResponse' {} Maybe Text
a -> DescribeQuerySuggestionsBlockListResponse
s {$sel:id:DescribeQuerySuggestionsBlockListResponse' :: Maybe Text
id = Maybe Text
a} :: DescribeQuerySuggestionsBlockListResponse)

-- | The identifier of the index for the block list.
describeQuerySuggestionsBlockListResponse_indexId :: Lens.Lens' DescribeQuerySuggestionsBlockListResponse (Prelude.Maybe Prelude.Text)
describeQuerySuggestionsBlockListResponse_indexId :: Lens' DescribeQuerySuggestionsBlockListResponse (Maybe Text)
describeQuerySuggestionsBlockListResponse_indexId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeQuerySuggestionsBlockListResponse' {Maybe Text
indexId :: Maybe Text
$sel:indexId:DescribeQuerySuggestionsBlockListResponse' :: DescribeQuerySuggestionsBlockListResponse -> Maybe Text
indexId} -> Maybe Text
indexId) (\s :: DescribeQuerySuggestionsBlockListResponse
s@DescribeQuerySuggestionsBlockListResponse' {} Maybe Text
a -> DescribeQuerySuggestionsBlockListResponse
s {$sel:indexId:DescribeQuerySuggestionsBlockListResponse' :: Maybe Text
indexId = Maybe Text
a} :: DescribeQuerySuggestionsBlockListResponse)

-- | The current number of valid, non-empty words or phrases in the block
-- list text file.
describeQuerySuggestionsBlockListResponse_itemCount :: Lens.Lens' DescribeQuerySuggestionsBlockListResponse (Prelude.Maybe Prelude.Int)
describeQuerySuggestionsBlockListResponse_itemCount :: Lens' DescribeQuerySuggestionsBlockListResponse (Maybe Int)
describeQuerySuggestionsBlockListResponse_itemCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeQuerySuggestionsBlockListResponse' {Maybe Int
itemCount :: Maybe Int
$sel:itemCount:DescribeQuerySuggestionsBlockListResponse' :: DescribeQuerySuggestionsBlockListResponse -> Maybe Int
itemCount} -> Maybe Int
itemCount) (\s :: DescribeQuerySuggestionsBlockListResponse
s@DescribeQuerySuggestionsBlockListResponse' {} Maybe Int
a -> DescribeQuerySuggestionsBlockListResponse
s {$sel:itemCount:DescribeQuerySuggestionsBlockListResponse' :: Maybe Int
itemCount = Maybe Int
a} :: DescribeQuerySuggestionsBlockListResponse)

-- | The name of the block list.
describeQuerySuggestionsBlockListResponse_name :: Lens.Lens' DescribeQuerySuggestionsBlockListResponse (Prelude.Maybe Prelude.Text)
describeQuerySuggestionsBlockListResponse_name :: Lens' DescribeQuerySuggestionsBlockListResponse (Maybe Text)
describeQuerySuggestionsBlockListResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeQuerySuggestionsBlockListResponse' {Maybe Text
name :: Maybe Text
$sel:name:DescribeQuerySuggestionsBlockListResponse' :: DescribeQuerySuggestionsBlockListResponse -> Maybe Text
name} -> Maybe Text
name) (\s :: DescribeQuerySuggestionsBlockListResponse
s@DescribeQuerySuggestionsBlockListResponse' {} Maybe Text
a -> DescribeQuerySuggestionsBlockListResponse
s {$sel:name:DescribeQuerySuggestionsBlockListResponse' :: Maybe Text
name = Maybe Text
a} :: DescribeQuerySuggestionsBlockListResponse)

-- | The IAM (Identity and Access Management) role used by Amazon Kendra to
-- access the block list text file in S3.
--
-- The role needs S3 read permissions to your file in S3 and needs to give
-- STS (Security Token Service) assume role permissions to Amazon Kendra.
describeQuerySuggestionsBlockListResponse_roleArn :: Lens.Lens' DescribeQuerySuggestionsBlockListResponse (Prelude.Maybe Prelude.Text)
describeQuerySuggestionsBlockListResponse_roleArn :: Lens' DescribeQuerySuggestionsBlockListResponse (Maybe Text)
describeQuerySuggestionsBlockListResponse_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeQuerySuggestionsBlockListResponse' {Maybe Text
roleArn :: Maybe Text
$sel:roleArn:DescribeQuerySuggestionsBlockListResponse' :: DescribeQuerySuggestionsBlockListResponse -> Maybe Text
roleArn} -> Maybe Text
roleArn) (\s :: DescribeQuerySuggestionsBlockListResponse
s@DescribeQuerySuggestionsBlockListResponse' {} Maybe Text
a -> DescribeQuerySuggestionsBlockListResponse
s {$sel:roleArn:DescribeQuerySuggestionsBlockListResponse' :: Maybe Text
roleArn = Maybe Text
a} :: DescribeQuerySuggestionsBlockListResponse)

-- | Shows the current S3 path to your block list text file in your S3
-- bucket.
--
-- Each block word or phrase should be on a separate line in a text file.
--
-- For information on the current quota limits for block lists, see
-- <https://docs.aws.amazon.com/kendra/latest/dg/quotas.html Quotas for Amazon Kendra>.
describeQuerySuggestionsBlockListResponse_sourceS3Path :: Lens.Lens' DescribeQuerySuggestionsBlockListResponse (Prelude.Maybe S3Path)
describeQuerySuggestionsBlockListResponse_sourceS3Path :: Lens' DescribeQuerySuggestionsBlockListResponse (Maybe S3Path)
describeQuerySuggestionsBlockListResponse_sourceS3Path = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeQuerySuggestionsBlockListResponse' {Maybe S3Path
sourceS3Path :: Maybe S3Path
$sel:sourceS3Path:DescribeQuerySuggestionsBlockListResponse' :: DescribeQuerySuggestionsBlockListResponse -> Maybe S3Path
sourceS3Path} -> Maybe S3Path
sourceS3Path) (\s :: DescribeQuerySuggestionsBlockListResponse
s@DescribeQuerySuggestionsBlockListResponse' {} Maybe S3Path
a -> DescribeQuerySuggestionsBlockListResponse
s {$sel:sourceS3Path:DescribeQuerySuggestionsBlockListResponse' :: Maybe S3Path
sourceS3Path = Maybe S3Path
a} :: DescribeQuerySuggestionsBlockListResponse)

-- | The current status of the block list. When the value is @ACTIVE@, the
-- block list is ready for use.
describeQuerySuggestionsBlockListResponse_status :: Lens.Lens' DescribeQuerySuggestionsBlockListResponse (Prelude.Maybe QuerySuggestionsBlockListStatus)
describeQuerySuggestionsBlockListResponse_status :: Lens'
  DescribeQuerySuggestionsBlockListResponse
  (Maybe QuerySuggestionsBlockListStatus)
describeQuerySuggestionsBlockListResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeQuerySuggestionsBlockListResponse' {Maybe QuerySuggestionsBlockListStatus
status :: Maybe QuerySuggestionsBlockListStatus
$sel:status:DescribeQuerySuggestionsBlockListResponse' :: DescribeQuerySuggestionsBlockListResponse
-> Maybe QuerySuggestionsBlockListStatus
status} -> Maybe QuerySuggestionsBlockListStatus
status) (\s :: DescribeQuerySuggestionsBlockListResponse
s@DescribeQuerySuggestionsBlockListResponse' {} Maybe QuerySuggestionsBlockListStatus
a -> DescribeQuerySuggestionsBlockListResponse
s {$sel:status:DescribeQuerySuggestionsBlockListResponse' :: Maybe QuerySuggestionsBlockListStatus
status = Maybe QuerySuggestionsBlockListStatus
a} :: DescribeQuerySuggestionsBlockListResponse)

-- | The date-time a block list for query suggestions was last updated.
describeQuerySuggestionsBlockListResponse_updatedAt :: Lens.Lens' DescribeQuerySuggestionsBlockListResponse (Prelude.Maybe Prelude.UTCTime)
describeQuerySuggestionsBlockListResponse_updatedAt :: Lens' DescribeQuerySuggestionsBlockListResponse (Maybe UTCTime)
describeQuerySuggestionsBlockListResponse_updatedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeQuerySuggestionsBlockListResponse' {Maybe POSIX
updatedAt :: Maybe POSIX
$sel:updatedAt:DescribeQuerySuggestionsBlockListResponse' :: DescribeQuerySuggestionsBlockListResponse -> Maybe POSIX
updatedAt} -> Maybe POSIX
updatedAt) (\s :: DescribeQuerySuggestionsBlockListResponse
s@DescribeQuerySuggestionsBlockListResponse' {} Maybe POSIX
a -> DescribeQuerySuggestionsBlockListResponse
s {$sel:updatedAt:DescribeQuerySuggestionsBlockListResponse' :: Maybe POSIX
updatedAt = Maybe POSIX
a} :: DescribeQuerySuggestionsBlockListResponse) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

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

instance
  Prelude.NFData
    DescribeQuerySuggestionsBlockListResponse
  where
  rnf :: DescribeQuerySuggestionsBlockListResponse -> ()
rnf DescribeQuerySuggestionsBlockListResponse' {Int
Maybe Int
Maybe Integer
Maybe Text
Maybe POSIX
Maybe QuerySuggestionsBlockListStatus
Maybe S3Path
httpStatus :: Int
updatedAt :: Maybe POSIX
status :: Maybe QuerySuggestionsBlockListStatus
sourceS3Path :: Maybe S3Path
roleArn :: Maybe Text
name :: Maybe Text
itemCount :: Maybe Int
indexId :: Maybe Text
id :: Maybe Text
fileSizeBytes :: Maybe Integer
errorMessage :: Maybe Text
description :: Maybe Text
createdAt :: Maybe POSIX
$sel:httpStatus:DescribeQuerySuggestionsBlockListResponse' :: DescribeQuerySuggestionsBlockListResponse -> Int
$sel:updatedAt:DescribeQuerySuggestionsBlockListResponse' :: DescribeQuerySuggestionsBlockListResponse -> Maybe POSIX
$sel:status:DescribeQuerySuggestionsBlockListResponse' :: DescribeQuerySuggestionsBlockListResponse
-> Maybe QuerySuggestionsBlockListStatus
$sel:sourceS3Path:DescribeQuerySuggestionsBlockListResponse' :: DescribeQuerySuggestionsBlockListResponse -> Maybe S3Path
$sel:roleArn:DescribeQuerySuggestionsBlockListResponse' :: DescribeQuerySuggestionsBlockListResponse -> Maybe Text
$sel:name:DescribeQuerySuggestionsBlockListResponse' :: DescribeQuerySuggestionsBlockListResponse -> Maybe Text
$sel:itemCount:DescribeQuerySuggestionsBlockListResponse' :: DescribeQuerySuggestionsBlockListResponse -> Maybe Int
$sel:indexId:DescribeQuerySuggestionsBlockListResponse' :: DescribeQuerySuggestionsBlockListResponse -> Maybe Text
$sel:id:DescribeQuerySuggestionsBlockListResponse' :: DescribeQuerySuggestionsBlockListResponse -> Maybe Text
$sel:fileSizeBytes:DescribeQuerySuggestionsBlockListResponse' :: DescribeQuerySuggestionsBlockListResponse -> Maybe Integer
$sel:errorMessage:DescribeQuerySuggestionsBlockListResponse' :: DescribeQuerySuggestionsBlockListResponse -> Maybe Text
$sel:description:DescribeQuerySuggestionsBlockListResponse' :: DescribeQuerySuggestionsBlockListResponse -> Maybe Text
$sel:createdAt:DescribeQuerySuggestionsBlockListResponse' :: DescribeQuerySuggestionsBlockListResponse -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
errorMessage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
fileSizeBytes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
id
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
indexId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
itemCount
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
roleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe S3Path
sourceS3Path
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe QuerySuggestionsBlockListStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
updatedAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus