{-# 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.ListFaqs
-- 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 a list of FAQ lists associated with an index.
module Amazonka.Kendra.ListFaqs
  ( -- * Creating a Request
    ListFaqs (..),
    newListFaqs,

    -- * Request Lenses
    listFaqs_maxResults,
    listFaqs_nextToken,
    listFaqs_indexId,

    -- * Destructuring the Response
    ListFaqsResponse (..),
    newListFaqsResponse,

    -- * Response Lenses
    listFaqsResponse_faqSummaryItems,
    listFaqsResponse_nextToken,
    listFaqsResponse_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:/ 'newListFaqs' smart constructor.
data ListFaqs = ListFaqs'
  { -- | The maximum number of FAQs to return in the response. If there are fewer
    -- results in the list, this response contains only the actual results.
    ListFaqs -> 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 FAQs.
    ListFaqs -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The index that contains the FAQ lists.
    ListFaqs -> Text
indexId :: Prelude.Text
  }
  deriving (ListFaqs -> ListFaqs -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListFaqs -> ListFaqs -> Bool
$c/= :: ListFaqs -> ListFaqs -> Bool
== :: ListFaqs -> ListFaqs -> Bool
$c== :: ListFaqs -> ListFaqs -> Bool
Prelude.Eq, ReadPrec [ListFaqs]
ReadPrec ListFaqs
Int -> ReadS ListFaqs
ReadS [ListFaqs]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListFaqs]
$creadListPrec :: ReadPrec [ListFaqs]
readPrec :: ReadPrec ListFaqs
$creadPrec :: ReadPrec ListFaqs
readList :: ReadS [ListFaqs]
$creadList :: ReadS [ListFaqs]
readsPrec :: Int -> ReadS ListFaqs
$creadsPrec :: Int -> ReadS ListFaqs
Prelude.Read, Int -> ListFaqs -> ShowS
[ListFaqs] -> ShowS
ListFaqs -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListFaqs] -> ShowS
$cshowList :: [ListFaqs] -> ShowS
show :: ListFaqs -> String
$cshow :: ListFaqs -> String
showsPrec :: Int -> ListFaqs -> ShowS
$cshowsPrec :: Int -> ListFaqs -> ShowS
Prelude.Show, forall x. Rep ListFaqs x -> ListFaqs
forall x. ListFaqs -> Rep ListFaqs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListFaqs x -> ListFaqs
$cfrom :: forall x. ListFaqs -> Rep ListFaqs x
Prelude.Generic)

-- |
-- Create a value of 'ListFaqs' 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', 'listFaqs_maxResults' - The maximum number of FAQs to return in the response. If there are fewer
-- results in the list, this response contains only the actual results.
--
-- 'nextToken', 'listFaqs_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 FAQs.
--
-- 'indexId', 'listFaqs_indexId' - The index that contains the FAQ lists.
newListFaqs ::
  -- | 'indexId'
  Prelude.Text ->
  ListFaqs
newListFaqs :: Text -> ListFaqs
newListFaqs Text
pIndexId_ =
  ListFaqs'
    { $sel:maxResults:ListFaqs' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListFaqs' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:indexId:ListFaqs' :: Text
indexId = Text
pIndexId_
    }

-- | The maximum number of FAQs to return in the response. If there are fewer
-- results in the list, this response contains only the actual results.
listFaqs_maxResults :: Lens.Lens' ListFaqs (Prelude.Maybe Prelude.Natural)
listFaqs_maxResults :: Lens' ListFaqs (Maybe Natural)
listFaqs_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFaqs' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListFaqs' :: ListFaqs -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListFaqs
s@ListFaqs' {} Maybe Natural
a -> ListFaqs
s {$sel:maxResults:ListFaqs' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListFaqs)

-- | 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 FAQs.
listFaqs_nextToken :: Lens.Lens' ListFaqs (Prelude.Maybe Prelude.Text)
listFaqs_nextToken :: Lens' ListFaqs (Maybe Text)
listFaqs_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFaqs' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListFaqs' :: ListFaqs -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListFaqs
s@ListFaqs' {} Maybe Text
a -> ListFaqs
s {$sel:nextToken:ListFaqs' :: Maybe Text
nextToken = Maybe Text
a} :: ListFaqs)

-- | The index that contains the FAQ lists.
listFaqs_indexId :: Lens.Lens' ListFaqs Prelude.Text
listFaqs_indexId :: Lens' ListFaqs Text
listFaqs_indexId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFaqs' {Text
indexId :: Text
$sel:indexId:ListFaqs' :: ListFaqs -> Text
indexId} -> Text
indexId) (\s :: ListFaqs
s@ListFaqs' {} Text
a -> ListFaqs
s {$sel:indexId:ListFaqs' :: Text
indexId = Text
a} :: ListFaqs)

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

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

instance Prelude.NFData ListFaqs where
  rnf :: ListFaqs -> ()
rnf ListFaqs' {Maybe Natural
Maybe Text
Text
indexId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:indexId:ListFaqs' :: ListFaqs -> Text
$sel:nextToken:ListFaqs' :: ListFaqs -> Maybe Text
$sel:maxResults:ListFaqs' :: ListFaqs -> Maybe Natural
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
indexId

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

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

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

-- | /See:/ 'newListFaqsResponse' smart constructor.
data ListFaqsResponse = ListFaqsResponse'
  { -- | information about the FAQs associated with the specified index.
    ListFaqsResponse -> Maybe [FaqSummary]
faqSummaryItems :: Prelude.Maybe [FaqSummary],
    -- | If the response is truncated, Amazon Kendra returns this token that you
    -- can use in the subsequent request to retrieve the next set of FAQs.
    ListFaqsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListFaqsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListFaqsResponse -> ListFaqsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListFaqsResponse -> ListFaqsResponse -> Bool
$c/= :: ListFaqsResponse -> ListFaqsResponse -> Bool
== :: ListFaqsResponse -> ListFaqsResponse -> Bool
$c== :: ListFaqsResponse -> ListFaqsResponse -> Bool
Prelude.Eq, ReadPrec [ListFaqsResponse]
ReadPrec ListFaqsResponse
Int -> ReadS ListFaqsResponse
ReadS [ListFaqsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListFaqsResponse]
$creadListPrec :: ReadPrec [ListFaqsResponse]
readPrec :: ReadPrec ListFaqsResponse
$creadPrec :: ReadPrec ListFaqsResponse
readList :: ReadS [ListFaqsResponse]
$creadList :: ReadS [ListFaqsResponse]
readsPrec :: Int -> ReadS ListFaqsResponse
$creadsPrec :: Int -> ReadS ListFaqsResponse
Prelude.Read, Int -> ListFaqsResponse -> ShowS
[ListFaqsResponse] -> ShowS
ListFaqsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListFaqsResponse] -> ShowS
$cshowList :: [ListFaqsResponse] -> ShowS
show :: ListFaqsResponse -> String
$cshow :: ListFaqsResponse -> String
showsPrec :: Int -> ListFaqsResponse -> ShowS
$cshowsPrec :: Int -> ListFaqsResponse -> ShowS
Prelude.Show, forall x. Rep ListFaqsResponse x -> ListFaqsResponse
forall x. ListFaqsResponse -> Rep ListFaqsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListFaqsResponse x -> ListFaqsResponse
$cfrom :: forall x. ListFaqsResponse -> Rep ListFaqsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListFaqsResponse' 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:
--
-- 'faqSummaryItems', 'listFaqsResponse_faqSummaryItems' - information about the FAQs associated with the specified index.
--
-- 'nextToken', 'listFaqsResponse_nextToken' - If the response is truncated, Amazon Kendra returns this token that you
-- can use in the subsequent request to retrieve the next set of FAQs.
--
-- 'httpStatus', 'listFaqsResponse_httpStatus' - The response's http status code.
newListFaqsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListFaqsResponse
newListFaqsResponse :: Int -> ListFaqsResponse
newListFaqsResponse Int
pHttpStatus_ =
  ListFaqsResponse'
    { $sel:faqSummaryItems:ListFaqsResponse' :: Maybe [FaqSummary]
faqSummaryItems =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListFaqsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListFaqsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | information about the FAQs associated with the specified index.
listFaqsResponse_faqSummaryItems :: Lens.Lens' ListFaqsResponse (Prelude.Maybe [FaqSummary])
listFaqsResponse_faqSummaryItems :: Lens' ListFaqsResponse (Maybe [FaqSummary])
listFaqsResponse_faqSummaryItems = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFaqsResponse' {Maybe [FaqSummary]
faqSummaryItems :: Maybe [FaqSummary]
$sel:faqSummaryItems:ListFaqsResponse' :: ListFaqsResponse -> Maybe [FaqSummary]
faqSummaryItems} -> Maybe [FaqSummary]
faqSummaryItems) (\s :: ListFaqsResponse
s@ListFaqsResponse' {} Maybe [FaqSummary]
a -> ListFaqsResponse
s {$sel:faqSummaryItems:ListFaqsResponse' :: Maybe [FaqSummary]
faqSummaryItems = Maybe [FaqSummary]
a} :: ListFaqsResponse) 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

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

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

instance Prelude.NFData ListFaqsResponse where
  rnf :: ListFaqsResponse -> ()
rnf ListFaqsResponse' {Int
Maybe [FaqSummary]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
faqSummaryItems :: Maybe [FaqSummary]
$sel:httpStatus:ListFaqsResponse' :: ListFaqsResponse -> Int
$sel:nextToken:ListFaqsResponse' :: ListFaqsResponse -> Maybe Text
$sel:faqSummaryItems:ListFaqsResponse' :: ListFaqsResponse -> Maybe [FaqSummary]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [FaqSummary]
faqSummaryItems
      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 Int
httpStatus