{-# 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.ListExperiences
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Lists one or more Amazon Kendra experiences. 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.ListExperiences
  ( -- * Creating a Request
    ListExperiences (..),
    newListExperiences,

    -- * Request Lenses
    listExperiences_maxResults,
    listExperiences_nextToken,
    listExperiences_indexId,

    -- * Destructuring the Response
    ListExperiencesResponse (..),
    newListExperiencesResponse,

    -- * Response Lenses
    listExperiencesResponse_nextToken,
    listExperiencesResponse_summaryItems,
    listExperiencesResponse_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:/ 'newListExperiences' smart constructor.
data ListExperiences = ListExperiences'
  { -- | The maximum number of returned Amazon Kendra experiences.
    ListExperiences -> 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 Amazon Kendra
    -- experiences.
    ListExperiences -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The identifier of the index for your Amazon Kendra experience.
    ListExperiences -> Text
indexId :: Prelude.Text
  }
  deriving (ListExperiences -> ListExperiences -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListExperiences -> ListExperiences -> Bool
$c/= :: ListExperiences -> ListExperiences -> Bool
== :: ListExperiences -> ListExperiences -> Bool
$c== :: ListExperiences -> ListExperiences -> Bool
Prelude.Eq, ReadPrec [ListExperiences]
ReadPrec ListExperiences
Int -> ReadS ListExperiences
ReadS [ListExperiences]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListExperiences]
$creadListPrec :: ReadPrec [ListExperiences]
readPrec :: ReadPrec ListExperiences
$creadPrec :: ReadPrec ListExperiences
readList :: ReadS [ListExperiences]
$creadList :: ReadS [ListExperiences]
readsPrec :: Int -> ReadS ListExperiences
$creadsPrec :: Int -> ReadS ListExperiences
Prelude.Read, Int -> ListExperiences -> ShowS
[ListExperiences] -> ShowS
ListExperiences -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListExperiences] -> ShowS
$cshowList :: [ListExperiences] -> ShowS
show :: ListExperiences -> String
$cshow :: ListExperiences -> String
showsPrec :: Int -> ListExperiences -> ShowS
$cshowsPrec :: Int -> ListExperiences -> ShowS
Prelude.Show, forall x. Rep ListExperiences x -> ListExperiences
forall x. ListExperiences -> Rep ListExperiences x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListExperiences x -> ListExperiences
$cfrom :: forall x. ListExperiences -> Rep ListExperiences x
Prelude.Generic)

-- |
-- Create a value of 'ListExperiences' 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', 'listExperiences_maxResults' - The maximum number of returned Amazon Kendra experiences.
--
-- 'nextToken', 'listExperiences_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 Amazon Kendra
-- experiences.
--
-- 'indexId', 'listExperiences_indexId' - The identifier of the index for your Amazon Kendra experience.
newListExperiences ::
  -- | 'indexId'
  Prelude.Text ->
  ListExperiences
newListExperiences :: Text -> ListExperiences
newListExperiences Text
pIndexId_ =
  ListExperiences'
    { $sel:maxResults:ListExperiences' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListExperiences' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:indexId:ListExperiences' :: Text
indexId = Text
pIndexId_
    }

-- | The maximum number of returned Amazon Kendra experiences.
listExperiences_maxResults :: Lens.Lens' ListExperiences (Prelude.Maybe Prelude.Natural)
listExperiences_maxResults :: Lens' ListExperiences (Maybe Natural)
listExperiences_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListExperiences' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListExperiences' :: ListExperiences -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListExperiences
s@ListExperiences' {} Maybe Natural
a -> ListExperiences
s {$sel:maxResults:ListExperiences' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListExperiences)

-- | 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 Amazon Kendra
-- experiences.
listExperiences_nextToken :: Lens.Lens' ListExperiences (Prelude.Maybe Prelude.Text)
listExperiences_nextToken :: Lens' ListExperiences (Maybe Text)
listExperiences_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListExperiences' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListExperiences' :: ListExperiences -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListExperiences
s@ListExperiences' {} Maybe Text
a -> ListExperiences
s {$sel:nextToken:ListExperiences' :: Maybe Text
nextToken = Maybe Text
a} :: ListExperiences)

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

instance Core.AWSRequest ListExperiences where
  type
    AWSResponse ListExperiences =
      ListExperiencesResponse
  request :: (Service -> Service) -> ListExperiences -> Request ListExperiences
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 ListExperiences
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListExperiences)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text
-> Maybe [ExperiencesSummary] -> Int -> ListExperiencesResponse
ListExperiencesResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"NextToken")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"SummaryItems" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable ListExperiences where
  hashWithSalt :: Int -> ListExperiences -> Int
hashWithSalt Int
_salt ListExperiences' {Maybe Natural
Maybe Text
Text
indexId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:indexId:ListExperiences' :: ListExperiences -> Text
$sel:nextToken:ListExperiences' :: ListExperiences -> Maybe Text
$sel:maxResults:ListExperiences' :: ListExperiences -> 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 ListExperiences where
  rnf :: ListExperiences -> ()
rnf ListExperiences' {Maybe Natural
Maybe Text
Text
indexId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:indexId:ListExperiences' :: ListExperiences -> Text
$sel:nextToken:ListExperiences' :: ListExperiences -> Maybe Text
$sel:maxResults:ListExperiences' :: ListExperiences -> 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 ListExperiences where
  toHeaders :: ListExperiences -> 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.ListExperiences" ::
                          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 ListExperiences where
  toJSON :: ListExperiences -> Value
toJSON ListExperiences' {Maybe Natural
Maybe Text
Text
indexId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:indexId:ListExperiences' :: ListExperiences -> Text
$sel:nextToken:ListExperiences' :: ListExperiences -> Maybe Text
$sel:maxResults:ListExperiences' :: ListExperiences -> 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 ListExperiences where
  toPath :: ListExperiences -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

-- |
-- Create a value of 'ListExperiencesResponse' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'nextToken', 'listExperiencesResponse_nextToken' - If the response is truncated, Amazon Kendra returns this token, which
-- you can use in a later request to retrieve the next set of Amazon Kendra
-- experiences.
--
-- 'summaryItems', 'listExperiencesResponse_summaryItems' - An array of summary information for one or more Amazon Kendra
-- experiences.
--
-- 'httpStatus', 'listExperiencesResponse_httpStatus' - The response's http status code.
newListExperiencesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListExperiencesResponse
newListExperiencesResponse :: Int -> ListExperiencesResponse
newListExperiencesResponse Int
pHttpStatus_ =
  ListExperiencesResponse'
    { $sel:nextToken:ListExperiencesResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:summaryItems:ListExperiencesResponse' :: Maybe [ExperiencesSummary]
summaryItems = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListExperiencesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

-- | An array of summary information for one or more Amazon Kendra
-- experiences.
listExperiencesResponse_summaryItems :: Lens.Lens' ListExperiencesResponse (Prelude.Maybe [ExperiencesSummary])
listExperiencesResponse_summaryItems :: Lens' ListExperiencesResponse (Maybe [ExperiencesSummary])
listExperiencesResponse_summaryItems = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListExperiencesResponse' {Maybe [ExperiencesSummary]
summaryItems :: Maybe [ExperiencesSummary]
$sel:summaryItems:ListExperiencesResponse' :: ListExperiencesResponse -> Maybe [ExperiencesSummary]
summaryItems} -> Maybe [ExperiencesSummary]
summaryItems) (\s :: ListExperiencesResponse
s@ListExperiencesResponse' {} Maybe [ExperiencesSummary]
a -> ListExperiencesResponse
s {$sel:summaryItems:ListExperiencesResponse' :: Maybe [ExperiencesSummary]
summaryItems = Maybe [ExperiencesSummary]
a} :: ListExperiencesResponse) 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.
listExperiencesResponse_httpStatus :: Lens.Lens' ListExperiencesResponse Prelude.Int
listExperiencesResponse_httpStatus :: Lens' ListExperiencesResponse Int
listExperiencesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListExperiencesResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListExperiencesResponse' :: ListExperiencesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListExperiencesResponse
s@ListExperiencesResponse' {} Int
a -> ListExperiencesResponse
s {$sel:httpStatus:ListExperiencesResponse' :: Int
httpStatus = Int
a} :: ListExperiencesResponse)

instance Prelude.NFData ListExperiencesResponse where
  rnf :: ListExperiencesResponse -> ()
rnf ListExperiencesResponse' {Int
Maybe [ExperiencesSummary]
Maybe Text
httpStatus :: Int
summaryItems :: Maybe [ExperiencesSummary]
nextToken :: Maybe Text
$sel:httpStatus:ListExperiencesResponse' :: ListExperiencesResponse -> Int
$sel:summaryItems:ListExperiencesResponse' :: ListExperiencesResponse -> Maybe [ExperiencesSummary]
$sel:nextToken:ListExperiencesResponse' :: ListExperiencesResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ExperiencesSummary]
summaryItems
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus