{-# 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.LexV2Models.SearchAssociatedTranscripts
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Search for associated transcripts that meet the specified criteria.
module Amazonka.LexV2Models.SearchAssociatedTranscripts
  ( -- * Creating a Request
    SearchAssociatedTranscripts (..),
    newSearchAssociatedTranscripts,

    -- * Request Lenses
    searchAssociatedTranscripts_maxResults,
    searchAssociatedTranscripts_nextIndex,
    searchAssociatedTranscripts_searchOrder,
    searchAssociatedTranscripts_botId,
    searchAssociatedTranscripts_botVersion,
    searchAssociatedTranscripts_localeId,
    searchAssociatedTranscripts_botRecommendationId,
    searchAssociatedTranscripts_filters,

    -- * Destructuring the Response
    SearchAssociatedTranscriptsResponse (..),
    newSearchAssociatedTranscriptsResponse,

    -- * Response Lenses
    searchAssociatedTranscriptsResponse_associatedTranscripts,
    searchAssociatedTranscriptsResponse_botId,
    searchAssociatedTranscriptsResponse_botRecommendationId,
    searchAssociatedTranscriptsResponse_botVersion,
    searchAssociatedTranscriptsResponse_localeId,
    searchAssociatedTranscriptsResponse_nextIndex,
    searchAssociatedTranscriptsResponse_totalResults,
    searchAssociatedTranscriptsResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.LexV2Models.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newSearchAssociatedTranscripts' smart constructor.
data SearchAssociatedTranscripts = SearchAssociatedTranscripts'
  { -- | The maximum number of bot recommendations to return in each page of
    -- results. If there are fewer results than the max page size, only the
    -- actual number of results are returned.
    SearchAssociatedTranscripts -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | If the response from the SearchAssociatedTranscriptsRequest operation
    -- contains more results than specified in the maxResults parameter, an
    -- index is returned in the response. Use that index in the nextIndex
    -- parameter to return the next page of results.
    SearchAssociatedTranscripts -> Maybe Natural
nextIndex :: Prelude.Maybe Prelude.Natural,
    -- | How SearchResults are ordered. Valid values are Ascending or Descending.
    -- The default is Descending.
    SearchAssociatedTranscripts -> Maybe SearchOrder
searchOrder :: Prelude.Maybe SearchOrder,
    -- | The unique identifier of the bot associated with the transcripts that
    -- you are searching.
    SearchAssociatedTranscripts -> Text
botId :: Prelude.Text,
    -- | The version of the bot containing the transcripts that you are
    -- searching.
    SearchAssociatedTranscripts -> Text
botVersion :: Prelude.Text,
    -- | The identifier of the language and locale of the transcripts to search.
    -- The string must match one of the supported locales. For more
    -- information, see
    -- <https://docs.aws.amazon.com/lexv2/latest/dg/how-languages.html Supported languages>
    SearchAssociatedTranscripts -> Text
localeId :: Prelude.Text,
    -- | The unique identifier of the bot recommendation associated with the
    -- transcripts to search.
    SearchAssociatedTranscripts -> Text
botRecommendationId :: Prelude.Text,
    -- | A list of filter objects.
    SearchAssociatedTranscripts -> NonEmpty AssociatedTranscriptFilter
filters :: Prelude.NonEmpty AssociatedTranscriptFilter
  }
  deriving (SearchAssociatedTranscripts -> SearchAssociatedTranscripts -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchAssociatedTranscripts -> SearchAssociatedTranscripts -> Bool
$c/= :: SearchAssociatedTranscripts -> SearchAssociatedTranscripts -> Bool
== :: SearchAssociatedTranscripts -> SearchAssociatedTranscripts -> Bool
$c== :: SearchAssociatedTranscripts -> SearchAssociatedTranscripts -> Bool
Prelude.Eq, ReadPrec [SearchAssociatedTranscripts]
ReadPrec SearchAssociatedTranscripts
Int -> ReadS SearchAssociatedTranscripts
ReadS [SearchAssociatedTranscripts]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SearchAssociatedTranscripts]
$creadListPrec :: ReadPrec [SearchAssociatedTranscripts]
readPrec :: ReadPrec SearchAssociatedTranscripts
$creadPrec :: ReadPrec SearchAssociatedTranscripts
readList :: ReadS [SearchAssociatedTranscripts]
$creadList :: ReadS [SearchAssociatedTranscripts]
readsPrec :: Int -> ReadS SearchAssociatedTranscripts
$creadsPrec :: Int -> ReadS SearchAssociatedTranscripts
Prelude.Read, Int -> SearchAssociatedTranscripts -> ShowS
[SearchAssociatedTranscripts] -> ShowS
SearchAssociatedTranscripts -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchAssociatedTranscripts] -> ShowS
$cshowList :: [SearchAssociatedTranscripts] -> ShowS
show :: SearchAssociatedTranscripts -> String
$cshow :: SearchAssociatedTranscripts -> String
showsPrec :: Int -> SearchAssociatedTranscripts -> ShowS
$cshowsPrec :: Int -> SearchAssociatedTranscripts -> ShowS
Prelude.Show, forall x.
Rep SearchAssociatedTranscripts x -> SearchAssociatedTranscripts
forall x.
SearchAssociatedTranscripts -> Rep SearchAssociatedTranscripts x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SearchAssociatedTranscripts x -> SearchAssociatedTranscripts
$cfrom :: forall x.
SearchAssociatedTranscripts -> Rep SearchAssociatedTranscripts x
Prelude.Generic)

-- |
-- Create a value of 'SearchAssociatedTranscripts' 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', 'searchAssociatedTranscripts_maxResults' - The maximum number of bot recommendations to return in each page of
-- results. If there are fewer results than the max page size, only the
-- actual number of results are returned.
--
-- 'nextIndex', 'searchAssociatedTranscripts_nextIndex' - If the response from the SearchAssociatedTranscriptsRequest operation
-- contains more results than specified in the maxResults parameter, an
-- index is returned in the response. Use that index in the nextIndex
-- parameter to return the next page of results.
--
-- 'searchOrder', 'searchAssociatedTranscripts_searchOrder' - How SearchResults are ordered. Valid values are Ascending or Descending.
-- The default is Descending.
--
-- 'botId', 'searchAssociatedTranscripts_botId' - The unique identifier of the bot associated with the transcripts that
-- you are searching.
--
-- 'botVersion', 'searchAssociatedTranscripts_botVersion' - The version of the bot containing the transcripts that you are
-- searching.
--
-- 'localeId', 'searchAssociatedTranscripts_localeId' - The identifier of the language and locale of the transcripts to search.
-- The string must match one of the supported locales. For more
-- information, see
-- <https://docs.aws.amazon.com/lexv2/latest/dg/how-languages.html Supported languages>
--
-- 'botRecommendationId', 'searchAssociatedTranscripts_botRecommendationId' - The unique identifier of the bot recommendation associated with the
-- transcripts to search.
--
-- 'filters', 'searchAssociatedTranscripts_filters' - A list of filter objects.
newSearchAssociatedTranscripts ::
  -- | 'botId'
  Prelude.Text ->
  -- | 'botVersion'
  Prelude.Text ->
  -- | 'localeId'
  Prelude.Text ->
  -- | 'botRecommendationId'
  Prelude.Text ->
  -- | 'filters'
  Prelude.NonEmpty AssociatedTranscriptFilter ->
  SearchAssociatedTranscripts
newSearchAssociatedTranscripts :: Text
-> Text
-> Text
-> Text
-> NonEmpty AssociatedTranscriptFilter
-> SearchAssociatedTranscripts
newSearchAssociatedTranscripts
  Text
pBotId_
  Text
pBotVersion_
  Text
pLocaleId_
  Text
pBotRecommendationId_
  NonEmpty AssociatedTranscriptFilter
pFilters_ =
    SearchAssociatedTranscripts'
      { $sel:maxResults:SearchAssociatedTranscripts' :: Maybe Natural
maxResults =
          forall a. Maybe a
Prelude.Nothing,
        $sel:nextIndex:SearchAssociatedTranscripts' :: Maybe Natural
nextIndex = forall a. Maybe a
Prelude.Nothing,
        $sel:searchOrder:SearchAssociatedTranscripts' :: Maybe SearchOrder
searchOrder = forall a. Maybe a
Prelude.Nothing,
        $sel:botId:SearchAssociatedTranscripts' :: Text
botId = Text
pBotId_,
        $sel:botVersion:SearchAssociatedTranscripts' :: Text
botVersion = Text
pBotVersion_,
        $sel:localeId:SearchAssociatedTranscripts' :: Text
localeId = Text
pLocaleId_,
        $sel:botRecommendationId:SearchAssociatedTranscripts' :: Text
botRecommendationId = Text
pBotRecommendationId_,
        $sel:filters:SearchAssociatedTranscripts' :: NonEmpty AssociatedTranscriptFilter
filters = 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 AssociatedTranscriptFilter
pFilters_
      }

-- | The maximum number of bot recommendations to return in each page of
-- results. If there are fewer results than the max page size, only the
-- actual number of results are returned.
searchAssociatedTranscripts_maxResults :: Lens.Lens' SearchAssociatedTranscripts (Prelude.Maybe Prelude.Natural)
searchAssociatedTranscripts_maxResults :: Lens' SearchAssociatedTranscripts (Maybe Natural)
searchAssociatedTranscripts_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchAssociatedTranscripts' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: SearchAssociatedTranscripts
s@SearchAssociatedTranscripts' {} Maybe Natural
a -> SearchAssociatedTranscripts
s {$sel:maxResults:SearchAssociatedTranscripts' :: Maybe Natural
maxResults = Maybe Natural
a} :: SearchAssociatedTranscripts)

-- | If the response from the SearchAssociatedTranscriptsRequest operation
-- contains more results than specified in the maxResults parameter, an
-- index is returned in the response. Use that index in the nextIndex
-- parameter to return the next page of results.
searchAssociatedTranscripts_nextIndex :: Lens.Lens' SearchAssociatedTranscripts (Prelude.Maybe Prelude.Natural)
searchAssociatedTranscripts_nextIndex :: Lens' SearchAssociatedTranscripts (Maybe Natural)
searchAssociatedTranscripts_nextIndex = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchAssociatedTranscripts' {Maybe Natural
nextIndex :: Maybe Natural
$sel:nextIndex:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> Maybe Natural
nextIndex} -> Maybe Natural
nextIndex) (\s :: SearchAssociatedTranscripts
s@SearchAssociatedTranscripts' {} Maybe Natural
a -> SearchAssociatedTranscripts
s {$sel:nextIndex:SearchAssociatedTranscripts' :: Maybe Natural
nextIndex = Maybe Natural
a} :: SearchAssociatedTranscripts)

-- | How SearchResults are ordered. Valid values are Ascending or Descending.
-- The default is Descending.
searchAssociatedTranscripts_searchOrder :: Lens.Lens' SearchAssociatedTranscripts (Prelude.Maybe SearchOrder)
searchAssociatedTranscripts_searchOrder :: Lens' SearchAssociatedTranscripts (Maybe SearchOrder)
searchAssociatedTranscripts_searchOrder = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchAssociatedTranscripts' {Maybe SearchOrder
searchOrder :: Maybe SearchOrder
$sel:searchOrder:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> Maybe SearchOrder
searchOrder} -> Maybe SearchOrder
searchOrder) (\s :: SearchAssociatedTranscripts
s@SearchAssociatedTranscripts' {} Maybe SearchOrder
a -> SearchAssociatedTranscripts
s {$sel:searchOrder:SearchAssociatedTranscripts' :: Maybe SearchOrder
searchOrder = Maybe SearchOrder
a} :: SearchAssociatedTranscripts)

-- | The unique identifier of the bot associated with the transcripts that
-- you are searching.
searchAssociatedTranscripts_botId :: Lens.Lens' SearchAssociatedTranscripts Prelude.Text
searchAssociatedTranscripts_botId :: Lens' SearchAssociatedTranscripts Text
searchAssociatedTranscripts_botId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchAssociatedTranscripts' {Text
botId :: Text
$sel:botId:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> Text
botId} -> Text
botId) (\s :: SearchAssociatedTranscripts
s@SearchAssociatedTranscripts' {} Text
a -> SearchAssociatedTranscripts
s {$sel:botId:SearchAssociatedTranscripts' :: Text
botId = Text
a} :: SearchAssociatedTranscripts)

-- | The version of the bot containing the transcripts that you are
-- searching.
searchAssociatedTranscripts_botVersion :: Lens.Lens' SearchAssociatedTranscripts Prelude.Text
searchAssociatedTranscripts_botVersion :: Lens' SearchAssociatedTranscripts Text
searchAssociatedTranscripts_botVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchAssociatedTranscripts' {Text
botVersion :: Text
$sel:botVersion:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> Text
botVersion} -> Text
botVersion) (\s :: SearchAssociatedTranscripts
s@SearchAssociatedTranscripts' {} Text
a -> SearchAssociatedTranscripts
s {$sel:botVersion:SearchAssociatedTranscripts' :: Text
botVersion = Text
a} :: SearchAssociatedTranscripts)

-- | The identifier of the language and locale of the transcripts to search.
-- The string must match one of the supported locales. For more
-- information, see
-- <https://docs.aws.amazon.com/lexv2/latest/dg/how-languages.html Supported languages>
searchAssociatedTranscripts_localeId :: Lens.Lens' SearchAssociatedTranscripts Prelude.Text
searchAssociatedTranscripts_localeId :: Lens' SearchAssociatedTranscripts Text
searchAssociatedTranscripts_localeId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchAssociatedTranscripts' {Text
localeId :: Text
$sel:localeId:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> Text
localeId} -> Text
localeId) (\s :: SearchAssociatedTranscripts
s@SearchAssociatedTranscripts' {} Text
a -> SearchAssociatedTranscripts
s {$sel:localeId:SearchAssociatedTranscripts' :: Text
localeId = Text
a} :: SearchAssociatedTranscripts)

-- | The unique identifier of the bot recommendation associated with the
-- transcripts to search.
searchAssociatedTranscripts_botRecommendationId :: Lens.Lens' SearchAssociatedTranscripts Prelude.Text
searchAssociatedTranscripts_botRecommendationId :: Lens' SearchAssociatedTranscripts Text
searchAssociatedTranscripts_botRecommendationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchAssociatedTranscripts' {Text
botRecommendationId :: Text
$sel:botRecommendationId:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> Text
botRecommendationId} -> Text
botRecommendationId) (\s :: SearchAssociatedTranscripts
s@SearchAssociatedTranscripts' {} Text
a -> SearchAssociatedTranscripts
s {$sel:botRecommendationId:SearchAssociatedTranscripts' :: Text
botRecommendationId = Text
a} :: SearchAssociatedTranscripts)

-- | A list of filter objects.
searchAssociatedTranscripts_filters :: Lens.Lens' SearchAssociatedTranscripts (Prelude.NonEmpty AssociatedTranscriptFilter)
searchAssociatedTranscripts_filters :: Lens'
  SearchAssociatedTranscripts (NonEmpty AssociatedTranscriptFilter)
searchAssociatedTranscripts_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchAssociatedTranscripts' {NonEmpty AssociatedTranscriptFilter
filters :: NonEmpty AssociatedTranscriptFilter
$sel:filters:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> NonEmpty AssociatedTranscriptFilter
filters} -> NonEmpty AssociatedTranscriptFilter
filters) (\s :: SearchAssociatedTranscripts
s@SearchAssociatedTranscripts' {} NonEmpty AssociatedTranscriptFilter
a -> SearchAssociatedTranscripts
s {$sel:filters:SearchAssociatedTranscripts' :: NonEmpty AssociatedTranscriptFilter
filters = NonEmpty AssociatedTranscriptFilter
a} :: SearchAssociatedTranscripts) 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 SearchAssociatedTranscripts where
  type
    AWSResponse SearchAssociatedTranscripts =
      SearchAssociatedTranscriptsResponse
  request :: (Service -> Service)
-> SearchAssociatedTranscripts
-> Request SearchAssociatedTranscripts
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 SearchAssociatedTranscripts
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse SearchAssociatedTranscripts)))
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 [AssociatedTranscript]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Natural
-> Maybe Natural
-> Int
-> SearchAssociatedTranscriptsResponse
SearchAssociatedTranscriptsResponse'
            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
"associatedTranscripts"
                            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
"botId")
            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
"botRecommendationId")
            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
"botVersion")
            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
"localeId")
            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
"nextIndex")
            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
"totalResults")
            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 SearchAssociatedTranscripts where
  hashWithSalt :: Int -> SearchAssociatedTranscripts -> Int
hashWithSalt Int
_salt SearchAssociatedTranscripts' {Maybe Natural
Maybe SearchOrder
NonEmpty AssociatedTranscriptFilter
Text
filters :: NonEmpty AssociatedTranscriptFilter
botRecommendationId :: Text
localeId :: Text
botVersion :: Text
botId :: Text
searchOrder :: Maybe SearchOrder
nextIndex :: Maybe Natural
maxResults :: Maybe Natural
$sel:filters:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> NonEmpty AssociatedTranscriptFilter
$sel:botRecommendationId:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> Text
$sel:localeId:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> Text
$sel:botVersion:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> Text
$sel:botId:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> Text
$sel:searchOrder:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> Maybe SearchOrder
$sel:nextIndex:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> Maybe Natural
$sel:maxResults:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> 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 Natural
nextIndex
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SearchOrder
searchOrder
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
botId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
botVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
localeId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
botRecommendationId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty AssociatedTranscriptFilter
filters

instance Prelude.NFData SearchAssociatedTranscripts where
  rnf :: SearchAssociatedTranscripts -> ()
rnf SearchAssociatedTranscripts' {Maybe Natural
Maybe SearchOrder
NonEmpty AssociatedTranscriptFilter
Text
filters :: NonEmpty AssociatedTranscriptFilter
botRecommendationId :: Text
localeId :: Text
botVersion :: Text
botId :: Text
searchOrder :: Maybe SearchOrder
nextIndex :: Maybe Natural
maxResults :: Maybe Natural
$sel:filters:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> NonEmpty AssociatedTranscriptFilter
$sel:botRecommendationId:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> Text
$sel:localeId:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> Text
$sel:botVersion:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> Text
$sel:botId:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> Text
$sel:searchOrder:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> Maybe SearchOrder
$sel:nextIndex:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> Maybe Natural
$sel:maxResults:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> 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 Natural
nextIndex
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SearchOrder
searchOrder
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
botId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
botVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
localeId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
botRecommendationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf NonEmpty AssociatedTranscriptFilter
filters

instance Data.ToHeaders SearchAssociatedTranscripts where
  toHeaders :: SearchAssociatedTranscripts -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON SearchAssociatedTranscripts where
  toJSON :: SearchAssociatedTranscripts -> Value
toJSON SearchAssociatedTranscripts' {Maybe Natural
Maybe SearchOrder
NonEmpty AssociatedTranscriptFilter
Text
filters :: NonEmpty AssociatedTranscriptFilter
botRecommendationId :: Text
localeId :: Text
botVersion :: Text
botId :: Text
searchOrder :: Maybe SearchOrder
nextIndex :: Maybe Natural
maxResults :: Maybe Natural
$sel:filters:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> NonEmpty AssociatedTranscriptFilter
$sel:botRecommendationId:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> Text
$sel:localeId:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> Text
$sel:botVersion:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> Text
$sel:botId:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> Text
$sel:searchOrder:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> Maybe SearchOrder
$sel:nextIndex:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> Maybe Natural
$sel:maxResults:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> 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
"nextIndex" 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
nextIndex,
            (Key
"searchOrder" 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 SearchOrder
searchOrder,
            forall a. a -> Maybe a
Prelude.Just (Key
"filters" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= NonEmpty AssociatedTranscriptFilter
filters)
          ]
      )

instance Data.ToPath SearchAssociatedTranscripts where
  toPath :: SearchAssociatedTranscripts -> ByteString
toPath SearchAssociatedTranscripts' {Maybe Natural
Maybe SearchOrder
NonEmpty AssociatedTranscriptFilter
Text
filters :: NonEmpty AssociatedTranscriptFilter
botRecommendationId :: Text
localeId :: Text
botVersion :: Text
botId :: Text
searchOrder :: Maybe SearchOrder
nextIndex :: Maybe Natural
maxResults :: Maybe Natural
$sel:filters:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> NonEmpty AssociatedTranscriptFilter
$sel:botRecommendationId:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> Text
$sel:localeId:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> Text
$sel:botVersion:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> Text
$sel:botId:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> Text
$sel:searchOrder:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> Maybe SearchOrder
$sel:nextIndex:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> Maybe Natural
$sel:maxResults:SearchAssociatedTranscripts' :: SearchAssociatedTranscripts -> Maybe Natural
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/bots/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
botId,
        ByteString
"/botversions/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
botVersion,
        ByteString
"/botlocales/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
localeId,
        ByteString
"/botrecommendations/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
botRecommendationId,
        ByteString
"/associatedtranscripts"
      ]

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

-- | /See:/ 'newSearchAssociatedTranscriptsResponse' smart constructor.
data SearchAssociatedTranscriptsResponse = SearchAssociatedTranscriptsResponse'
  { -- | The object that contains the associated transcript that meet the
    -- criteria you specified.
    SearchAssociatedTranscriptsResponse -> Maybe [AssociatedTranscript]
associatedTranscripts :: Prelude.Maybe [AssociatedTranscript],
    -- | The unique identifier of the bot associated with the transcripts that
    -- you are searching.
    SearchAssociatedTranscriptsResponse -> Maybe Text
botId :: Prelude.Maybe Prelude.Text,
    -- | The unique identifier of the bot recommendation associated with the
    -- transcripts to search.
    SearchAssociatedTranscriptsResponse -> Maybe Text
botRecommendationId :: Prelude.Maybe Prelude.Text,
    -- | The version of the bot containing the transcripts that you are
    -- searching.
    SearchAssociatedTranscriptsResponse -> Maybe Text
botVersion :: Prelude.Maybe Prelude.Text,
    -- | The identifier of the language and locale of the transcripts to search.
    -- The string must match one of the supported locales. For more
    -- information, see
    -- <https://docs.aws.amazon.com/lexv2/latest/dg/how-languages.html Supported languages>
    SearchAssociatedTranscriptsResponse -> Maybe Text
localeId :: Prelude.Maybe Prelude.Text,
    -- | A index that indicates whether there are more results to return in a
    -- response to the SearchAssociatedTranscripts operation. If the nextIndex
    -- field is present, you send the contents as the nextIndex parameter of a
    -- SearchAssociatedTranscriptsRequest operation to get the next page of
    -- results.
    SearchAssociatedTranscriptsResponse -> Maybe Natural
nextIndex :: Prelude.Maybe Prelude.Natural,
    -- | The total number of transcripts returned by the search.
    SearchAssociatedTranscriptsResponse -> Maybe Natural
totalResults :: Prelude.Maybe Prelude.Natural,
    -- | The response's http status code.
    SearchAssociatedTranscriptsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (SearchAssociatedTranscriptsResponse
-> SearchAssociatedTranscriptsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchAssociatedTranscriptsResponse
-> SearchAssociatedTranscriptsResponse -> Bool
$c/= :: SearchAssociatedTranscriptsResponse
-> SearchAssociatedTranscriptsResponse -> Bool
== :: SearchAssociatedTranscriptsResponse
-> SearchAssociatedTranscriptsResponse -> Bool
$c== :: SearchAssociatedTranscriptsResponse
-> SearchAssociatedTranscriptsResponse -> Bool
Prelude.Eq, ReadPrec [SearchAssociatedTranscriptsResponse]
ReadPrec SearchAssociatedTranscriptsResponse
Int -> ReadS SearchAssociatedTranscriptsResponse
ReadS [SearchAssociatedTranscriptsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SearchAssociatedTranscriptsResponse]
$creadListPrec :: ReadPrec [SearchAssociatedTranscriptsResponse]
readPrec :: ReadPrec SearchAssociatedTranscriptsResponse
$creadPrec :: ReadPrec SearchAssociatedTranscriptsResponse
readList :: ReadS [SearchAssociatedTranscriptsResponse]
$creadList :: ReadS [SearchAssociatedTranscriptsResponse]
readsPrec :: Int -> ReadS SearchAssociatedTranscriptsResponse
$creadsPrec :: Int -> ReadS SearchAssociatedTranscriptsResponse
Prelude.Read, Int -> SearchAssociatedTranscriptsResponse -> ShowS
[SearchAssociatedTranscriptsResponse] -> ShowS
SearchAssociatedTranscriptsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchAssociatedTranscriptsResponse] -> ShowS
$cshowList :: [SearchAssociatedTranscriptsResponse] -> ShowS
show :: SearchAssociatedTranscriptsResponse -> String
$cshow :: SearchAssociatedTranscriptsResponse -> String
showsPrec :: Int -> SearchAssociatedTranscriptsResponse -> ShowS
$cshowsPrec :: Int -> SearchAssociatedTranscriptsResponse -> ShowS
Prelude.Show, forall x.
Rep SearchAssociatedTranscriptsResponse x
-> SearchAssociatedTranscriptsResponse
forall x.
SearchAssociatedTranscriptsResponse
-> Rep SearchAssociatedTranscriptsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SearchAssociatedTranscriptsResponse x
-> SearchAssociatedTranscriptsResponse
$cfrom :: forall x.
SearchAssociatedTranscriptsResponse
-> Rep SearchAssociatedTranscriptsResponse x
Prelude.Generic)

-- |
-- Create a value of 'SearchAssociatedTranscriptsResponse' 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:
--
-- 'associatedTranscripts', 'searchAssociatedTranscriptsResponse_associatedTranscripts' - The object that contains the associated transcript that meet the
-- criteria you specified.
--
-- 'botId', 'searchAssociatedTranscriptsResponse_botId' - The unique identifier of the bot associated with the transcripts that
-- you are searching.
--
-- 'botRecommendationId', 'searchAssociatedTranscriptsResponse_botRecommendationId' - The unique identifier of the bot recommendation associated with the
-- transcripts to search.
--
-- 'botVersion', 'searchAssociatedTranscriptsResponse_botVersion' - The version of the bot containing the transcripts that you are
-- searching.
--
-- 'localeId', 'searchAssociatedTranscriptsResponse_localeId' - The identifier of the language and locale of the transcripts to search.
-- The string must match one of the supported locales. For more
-- information, see
-- <https://docs.aws.amazon.com/lexv2/latest/dg/how-languages.html Supported languages>
--
-- 'nextIndex', 'searchAssociatedTranscriptsResponse_nextIndex' - A index that indicates whether there are more results to return in a
-- response to the SearchAssociatedTranscripts operation. If the nextIndex
-- field is present, you send the contents as the nextIndex parameter of a
-- SearchAssociatedTranscriptsRequest operation to get the next page of
-- results.
--
-- 'totalResults', 'searchAssociatedTranscriptsResponse_totalResults' - The total number of transcripts returned by the search.
--
-- 'httpStatus', 'searchAssociatedTranscriptsResponse_httpStatus' - The response's http status code.
newSearchAssociatedTranscriptsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  SearchAssociatedTranscriptsResponse
newSearchAssociatedTranscriptsResponse :: Int -> SearchAssociatedTranscriptsResponse
newSearchAssociatedTranscriptsResponse Int
pHttpStatus_ =
  SearchAssociatedTranscriptsResponse'
    { $sel:associatedTranscripts:SearchAssociatedTranscriptsResponse' :: Maybe [AssociatedTranscript]
associatedTranscripts =
        forall a. Maybe a
Prelude.Nothing,
      $sel:botId:SearchAssociatedTranscriptsResponse' :: Maybe Text
botId = forall a. Maybe a
Prelude.Nothing,
      $sel:botRecommendationId:SearchAssociatedTranscriptsResponse' :: Maybe Text
botRecommendationId = forall a. Maybe a
Prelude.Nothing,
      $sel:botVersion:SearchAssociatedTranscriptsResponse' :: Maybe Text
botVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:localeId:SearchAssociatedTranscriptsResponse' :: Maybe Text
localeId = forall a. Maybe a
Prelude.Nothing,
      $sel:nextIndex:SearchAssociatedTranscriptsResponse' :: Maybe Natural
nextIndex = forall a. Maybe a
Prelude.Nothing,
      $sel:totalResults:SearchAssociatedTranscriptsResponse' :: Maybe Natural
totalResults = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:SearchAssociatedTranscriptsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The object that contains the associated transcript that meet the
-- criteria you specified.
searchAssociatedTranscriptsResponse_associatedTranscripts :: Lens.Lens' SearchAssociatedTranscriptsResponse (Prelude.Maybe [AssociatedTranscript])
searchAssociatedTranscriptsResponse_associatedTranscripts :: Lens'
  SearchAssociatedTranscriptsResponse (Maybe [AssociatedTranscript])
searchAssociatedTranscriptsResponse_associatedTranscripts = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchAssociatedTranscriptsResponse' {Maybe [AssociatedTranscript]
associatedTranscripts :: Maybe [AssociatedTranscript]
$sel:associatedTranscripts:SearchAssociatedTranscriptsResponse' :: SearchAssociatedTranscriptsResponse -> Maybe [AssociatedTranscript]
associatedTranscripts} -> Maybe [AssociatedTranscript]
associatedTranscripts) (\s :: SearchAssociatedTranscriptsResponse
s@SearchAssociatedTranscriptsResponse' {} Maybe [AssociatedTranscript]
a -> SearchAssociatedTranscriptsResponse
s {$sel:associatedTranscripts:SearchAssociatedTranscriptsResponse' :: Maybe [AssociatedTranscript]
associatedTranscripts = Maybe [AssociatedTranscript]
a} :: SearchAssociatedTranscriptsResponse) 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 unique identifier of the bot associated with the transcripts that
-- you are searching.
searchAssociatedTranscriptsResponse_botId :: Lens.Lens' SearchAssociatedTranscriptsResponse (Prelude.Maybe Prelude.Text)
searchAssociatedTranscriptsResponse_botId :: Lens' SearchAssociatedTranscriptsResponse (Maybe Text)
searchAssociatedTranscriptsResponse_botId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchAssociatedTranscriptsResponse' {Maybe Text
botId :: Maybe Text
$sel:botId:SearchAssociatedTranscriptsResponse' :: SearchAssociatedTranscriptsResponse -> Maybe Text
botId} -> Maybe Text
botId) (\s :: SearchAssociatedTranscriptsResponse
s@SearchAssociatedTranscriptsResponse' {} Maybe Text
a -> SearchAssociatedTranscriptsResponse
s {$sel:botId:SearchAssociatedTranscriptsResponse' :: Maybe Text
botId = Maybe Text
a} :: SearchAssociatedTranscriptsResponse)

-- | The unique identifier of the bot recommendation associated with the
-- transcripts to search.
searchAssociatedTranscriptsResponse_botRecommendationId :: Lens.Lens' SearchAssociatedTranscriptsResponse (Prelude.Maybe Prelude.Text)
searchAssociatedTranscriptsResponse_botRecommendationId :: Lens' SearchAssociatedTranscriptsResponse (Maybe Text)
searchAssociatedTranscriptsResponse_botRecommendationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchAssociatedTranscriptsResponse' {Maybe Text
botRecommendationId :: Maybe Text
$sel:botRecommendationId:SearchAssociatedTranscriptsResponse' :: SearchAssociatedTranscriptsResponse -> Maybe Text
botRecommendationId} -> Maybe Text
botRecommendationId) (\s :: SearchAssociatedTranscriptsResponse
s@SearchAssociatedTranscriptsResponse' {} Maybe Text
a -> SearchAssociatedTranscriptsResponse
s {$sel:botRecommendationId:SearchAssociatedTranscriptsResponse' :: Maybe Text
botRecommendationId = Maybe Text
a} :: SearchAssociatedTranscriptsResponse)

-- | The version of the bot containing the transcripts that you are
-- searching.
searchAssociatedTranscriptsResponse_botVersion :: Lens.Lens' SearchAssociatedTranscriptsResponse (Prelude.Maybe Prelude.Text)
searchAssociatedTranscriptsResponse_botVersion :: Lens' SearchAssociatedTranscriptsResponse (Maybe Text)
searchAssociatedTranscriptsResponse_botVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchAssociatedTranscriptsResponse' {Maybe Text
botVersion :: Maybe Text
$sel:botVersion:SearchAssociatedTranscriptsResponse' :: SearchAssociatedTranscriptsResponse -> Maybe Text
botVersion} -> Maybe Text
botVersion) (\s :: SearchAssociatedTranscriptsResponse
s@SearchAssociatedTranscriptsResponse' {} Maybe Text
a -> SearchAssociatedTranscriptsResponse
s {$sel:botVersion:SearchAssociatedTranscriptsResponse' :: Maybe Text
botVersion = Maybe Text
a} :: SearchAssociatedTranscriptsResponse)

-- | The identifier of the language and locale of the transcripts to search.
-- The string must match one of the supported locales. For more
-- information, see
-- <https://docs.aws.amazon.com/lexv2/latest/dg/how-languages.html Supported languages>
searchAssociatedTranscriptsResponse_localeId :: Lens.Lens' SearchAssociatedTranscriptsResponse (Prelude.Maybe Prelude.Text)
searchAssociatedTranscriptsResponse_localeId :: Lens' SearchAssociatedTranscriptsResponse (Maybe Text)
searchAssociatedTranscriptsResponse_localeId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchAssociatedTranscriptsResponse' {Maybe Text
localeId :: Maybe Text
$sel:localeId:SearchAssociatedTranscriptsResponse' :: SearchAssociatedTranscriptsResponse -> Maybe Text
localeId} -> Maybe Text
localeId) (\s :: SearchAssociatedTranscriptsResponse
s@SearchAssociatedTranscriptsResponse' {} Maybe Text
a -> SearchAssociatedTranscriptsResponse
s {$sel:localeId:SearchAssociatedTranscriptsResponse' :: Maybe Text
localeId = Maybe Text
a} :: SearchAssociatedTranscriptsResponse)

-- | A index that indicates whether there are more results to return in a
-- response to the SearchAssociatedTranscripts operation. If the nextIndex
-- field is present, you send the contents as the nextIndex parameter of a
-- SearchAssociatedTranscriptsRequest operation to get the next page of
-- results.
searchAssociatedTranscriptsResponse_nextIndex :: Lens.Lens' SearchAssociatedTranscriptsResponse (Prelude.Maybe Prelude.Natural)
searchAssociatedTranscriptsResponse_nextIndex :: Lens' SearchAssociatedTranscriptsResponse (Maybe Natural)
searchAssociatedTranscriptsResponse_nextIndex = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchAssociatedTranscriptsResponse' {Maybe Natural
nextIndex :: Maybe Natural
$sel:nextIndex:SearchAssociatedTranscriptsResponse' :: SearchAssociatedTranscriptsResponse -> Maybe Natural
nextIndex} -> Maybe Natural
nextIndex) (\s :: SearchAssociatedTranscriptsResponse
s@SearchAssociatedTranscriptsResponse' {} Maybe Natural
a -> SearchAssociatedTranscriptsResponse
s {$sel:nextIndex:SearchAssociatedTranscriptsResponse' :: Maybe Natural
nextIndex = Maybe Natural
a} :: SearchAssociatedTranscriptsResponse)

-- | The total number of transcripts returned by the search.
searchAssociatedTranscriptsResponse_totalResults :: Lens.Lens' SearchAssociatedTranscriptsResponse (Prelude.Maybe Prelude.Natural)
searchAssociatedTranscriptsResponse_totalResults :: Lens' SearchAssociatedTranscriptsResponse (Maybe Natural)
searchAssociatedTranscriptsResponse_totalResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchAssociatedTranscriptsResponse' {Maybe Natural
totalResults :: Maybe Natural
$sel:totalResults:SearchAssociatedTranscriptsResponse' :: SearchAssociatedTranscriptsResponse -> Maybe Natural
totalResults} -> Maybe Natural
totalResults) (\s :: SearchAssociatedTranscriptsResponse
s@SearchAssociatedTranscriptsResponse' {} Maybe Natural
a -> SearchAssociatedTranscriptsResponse
s {$sel:totalResults:SearchAssociatedTranscriptsResponse' :: Maybe Natural
totalResults = Maybe Natural
a} :: SearchAssociatedTranscriptsResponse)

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

instance
  Prelude.NFData
    SearchAssociatedTranscriptsResponse
  where
  rnf :: SearchAssociatedTranscriptsResponse -> ()
rnf SearchAssociatedTranscriptsResponse' {Int
Maybe Natural
Maybe [AssociatedTranscript]
Maybe Text
httpStatus :: Int
totalResults :: Maybe Natural
nextIndex :: Maybe Natural
localeId :: Maybe Text
botVersion :: Maybe Text
botRecommendationId :: Maybe Text
botId :: Maybe Text
associatedTranscripts :: Maybe [AssociatedTranscript]
$sel:httpStatus:SearchAssociatedTranscriptsResponse' :: SearchAssociatedTranscriptsResponse -> Int
$sel:totalResults:SearchAssociatedTranscriptsResponse' :: SearchAssociatedTranscriptsResponse -> Maybe Natural
$sel:nextIndex:SearchAssociatedTranscriptsResponse' :: SearchAssociatedTranscriptsResponse -> Maybe Natural
$sel:localeId:SearchAssociatedTranscriptsResponse' :: SearchAssociatedTranscriptsResponse -> Maybe Text
$sel:botVersion:SearchAssociatedTranscriptsResponse' :: SearchAssociatedTranscriptsResponse -> Maybe Text
$sel:botRecommendationId:SearchAssociatedTranscriptsResponse' :: SearchAssociatedTranscriptsResponse -> Maybe Text
$sel:botId:SearchAssociatedTranscriptsResponse' :: SearchAssociatedTranscriptsResponse -> Maybe Text
$sel:associatedTranscripts:SearchAssociatedTranscriptsResponse' :: SearchAssociatedTranscriptsResponse -> Maybe [AssociatedTranscript]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [AssociatedTranscript]
associatedTranscripts
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
botId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
botRecommendationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
botVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
localeId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
nextIndex
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
totalResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus