{-# 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.Connect.SearchVocabularies
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Searches for vocabularies within a specific Amazon Connect instance
-- using @State@, @NameStartsWith@, and @LanguageCode@.
--
-- This operation returns paginated results.
module Amazonka.Connect.SearchVocabularies
  ( -- * Creating a Request
    SearchVocabularies (..),
    newSearchVocabularies,

    -- * Request Lenses
    searchVocabularies_languageCode,
    searchVocabularies_maxResults,
    searchVocabularies_nameStartsWith,
    searchVocabularies_nextToken,
    searchVocabularies_state,
    searchVocabularies_instanceId,

    -- * Destructuring the Response
    SearchVocabulariesResponse (..),
    newSearchVocabulariesResponse,

    -- * Response Lenses
    searchVocabulariesResponse_nextToken,
    searchVocabulariesResponse_vocabularySummaryList,
    searchVocabulariesResponse_httpStatus,
  )
where

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

-- | /See:/ 'newSearchVocabularies' smart constructor.
data SearchVocabularies = SearchVocabularies'
  { -- | The language code of the vocabulary entries. For a list of languages and
    -- their corresponding language codes, see
    -- <https://docs.aws.amazon.com/transcribe/latest/dg/transcribe-whatis.html What is Amazon Transcribe?>
    SearchVocabularies -> Maybe VocabularyLanguageCode
languageCode :: Prelude.Maybe VocabularyLanguageCode,
    -- | The maximum number of results to return per page.
    SearchVocabularies -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The starting pattern of the name of the vocabulary.
    SearchVocabularies -> Maybe Text
nameStartsWith :: Prelude.Maybe Prelude.Text,
    -- | The token for the next set of results. Use the value returned in the
    -- previous response in the next request to retrieve the next set of
    -- results.
    SearchVocabularies -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The current state of the custom vocabulary.
    SearchVocabularies -> Maybe VocabularyState
state :: Prelude.Maybe VocabularyState,
    -- | The identifier of the Amazon Connect instance. You can find the
    -- instanceId in the ARN of the instance.
    SearchVocabularies -> Text
instanceId :: Prelude.Text
  }
  deriving (SearchVocabularies -> SearchVocabularies -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchVocabularies -> SearchVocabularies -> Bool
$c/= :: SearchVocabularies -> SearchVocabularies -> Bool
== :: SearchVocabularies -> SearchVocabularies -> Bool
$c== :: SearchVocabularies -> SearchVocabularies -> Bool
Prelude.Eq, ReadPrec [SearchVocabularies]
ReadPrec SearchVocabularies
Int -> ReadS SearchVocabularies
ReadS [SearchVocabularies]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SearchVocabularies]
$creadListPrec :: ReadPrec [SearchVocabularies]
readPrec :: ReadPrec SearchVocabularies
$creadPrec :: ReadPrec SearchVocabularies
readList :: ReadS [SearchVocabularies]
$creadList :: ReadS [SearchVocabularies]
readsPrec :: Int -> ReadS SearchVocabularies
$creadsPrec :: Int -> ReadS SearchVocabularies
Prelude.Read, Int -> SearchVocabularies -> ShowS
[SearchVocabularies] -> ShowS
SearchVocabularies -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchVocabularies] -> ShowS
$cshowList :: [SearchVocabularies] -> ShowS
show :: SearchVocabularies -> String
$cshow :: SearchVocabularies -> String
showsPrec :: Int -> SearchVocabularies -> ShowS
$cshowsPrec :: Int -> SearchVocabularies -> ShowS
Prelude.Show, forall x. Rep SearchVocabularies x -> SearchVocabularies
forall x. SearchVocabularies -> Rep SearchVocabularies x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SearchVocabularies x -> SearchVocabularies
$cfrom :: forall x. SearchVocabularies -> Rep SearchVocabularies x
Prelude.Generic)

-- |
-- Create a value of 'SearchVocabularies' 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:
--
-- 'languageCode', 'searchVocabularies_languageCode' - The language code of the vocabulary entries. For a list of languages and
-- their corresponding language codes, see
-- <https://docs.aws.amazon.com/transcribe/latest/dg/transcribe-whatis.html What is Amazon Transcribe?>
--
-- 'maxResults', 'searchVocabularies_maxResults' - The maximum number of results to return per page.
--
-- 'nameStartsWith', 'searchVocabularies_nameStartsWith' - The starting pattern of the name of the vocabulary.
--
-- 'nextToken', 'searchVocabularies_nextToken' - The token for the next set of results. Use the value returned in the
-- previous response in the next request to retrieve the next set of
-- results.
--
-- 'state', 'searchVocabularies_state' - The current state of the custom vocabulary.
--
-- 'instanceId', 'searchVocabularies_instanceId' - The identifier of the Amazon Connect instance. You can find the
-- instanceId in the ARN of the instance.
newSearchVocabularies ::
  -- | 'instanceId'
  Prelude.Text ->
  SearchVocabularies
newSearchVocabularies :: Text -> SearchVocabularies
newSearchVocabularies Text
pInstanceId_ =
  SearchVocabularies'
    { $sel:languageCode:SearchVocabularies' :: Maybe VocabularyLanguageCode
languageCode = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:SearchVocabularies' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nameStartsWith:SearchVocabularies' :: Maybe Text
nameStartsWith = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:SearchVocabularies' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:state:SearchVocabularies' :: Maybe VocabularyState
state = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceId:SearchVocabularies' :: Text
instanceId = Text
pInstanceId_
    }

-- | The language code of the vocabulary entries. For a list of languages and
-- their corresponding language codes, see
-- <https://docs.aws.amazon.com/transcribe/latest/dg/transcribe-whatis.html What is Amazon Transcribe?>
searchVocabularies_languageCode :: Lens.Lens' SearchVocabularies (Prelude.Maybe VocabularyLanguageCode)
searchVocabularies_languageCode :: Lens' SearchVocabularies (Maybe VocabularyLanguageCode)
searchVocabularies_languageCode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchVocabularies' {Maybe VocabularyLanguageCode
languageCode :: Maybe VocabularyLanguageCode
$sel:languageCode:SearchVocabularies' :: SearchVocabularies -> Maybe VocabularyLanguageCode
languageCode} -> Maybe VocabularyLanguageCode
languageCode) (\s :: SearchVocabularies
s@SearchVocabularies' {} Maybe VocabularyLanguageCode
a -> SearchVocabularies
s {$sel:languageCode:SearchVocabularies' :: Maybe VocabularyLanguageCode
languageCode = Maybe VocabularyLanguageCode
a} :: SearchVocabularies)

-- | The maximum number of results to return per page.
searchVocabularies_maxResults :: Lens.Lens' SearchVocabularies (Prelude.Maybe Prelude.Natural)
searchVocabularies_maxResults :: Lens' SearchVocabularies (Maybe Natural)
searchVocabularies_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchVocabularies' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:SearchVocabularies' :: SearchVocabularies -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: SearchVocabularies
s@SearchVocabularies' {} Maybe Natural
a -> SearchVocabularies
s {$sel:maxResults:SearchVocabularies' :: Maybe Natural
maxResults = Maybe Natural
a} :: SearchVocabularies)

-- | The starting pattern of the name of the vocabulary.
searchVocabularies_nameStartsWith :: Lens.Lens' SearchVocabularies (Prelude.Maybe Prelude.Text)
searchVocabularies_nameStartsWith :: Lens' SearchVocabularies (Maybe Text)
searchVocabularies_nameStartsWith = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchVocabularies' {Maybe Text
nameStartsWith :: Maybe Text
$sel:nameStartsWith:SearchVocabularies' :: SearchVocabularies -> Maybe Text
nameStartsWith} -> Maybe Text
nameStartsWith) (\s :: SearchVocabularies
s@SearchVocabularies' {} Maybe Text
a -> SearchVocabularies
s {$sel:nameStartsWith:SearchVocabularies' :: Maybe Text
nameStartsWith = Maybe Text
a} :: SearchVocabularies)

-- | The token for the next set of results. Use the value returned in the
-- previous response in the next request to retrieve the next set of
-- results.
searchVocabularies_nextToken :: Lens.Lens' SearchVocabularies (Prelude.Maybe Prelude.Text)
searchVocabularies_nextToken :: Lens' SearchVocabularies (Maybe Text)
searchVocabularies_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchVocabularies' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:SearchVocabularies' :: SearchVocabularies -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: SearchVocabularies
s@SearchVocabularies' {} Maybe Text
a -> SearchVocabularies
s {$sel:nextToken:SearchVocabularies' :: Maybe Text
nextToken = Maybe Text
a} :: SearchVocabularies)

-- | The current state of the custom vocabulary.
searchVocabularies_state :: Lens.Lens' SearchVocabularies (Prelude.Maybe VocabularyState)
searchVocabularies_state :: Lens' SearchVocabularies (Maybe VocabularyState)
searchVocabularies_state = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchVocabularies' {Maybe VocabularyState
state :: Maybe VocabularyState
$sel:state:SearchVocabularies' :: SearchVocabularies -> Maybe VocabularyState
state} -> Maybe VocabularyState
state) (\s :: SearchVocabularies
s@SearchVocabularies' {} Maybe VocabularyState
a -> SearchVocabularies
s {$sel:state:SearchVocabularies' :: Maybe VocabularyState
state = Maybe VocabularyState
a} :: SearchVocabularies)

-- | The identifier of the Amazon Connect instance. You can find the
-- instanceId in the ARN of the instance.
searchVocabularies_instanceId :: Lens.Lens' SearchVocabularies Prelude.Text
searchVocabularies_instanceId :: Lens' SearchVocabularies Text
searchVocabularies_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchVocabularies' {Text
instanceId :: Text
$sel:instanceId:SearchVocabularies' :: SearchVocabularies -> Text
instanceId} -> Text
instanceId) (\s :: SearchVocabularies
s@SearchVocabularies' {} Text
a -> SearchVocabularies
s {$sel:instanceId:SearchVocabularies' :: Text
instanceId = Text
a} :: SearchVocabularies)

instance Core.AWSPager SearchVocabularies where
  page :: SearchVocabularies
-> AWSResponse SearchVocabularies -> Maybe SearchVocabularies
page SearchVocabularies
rq AWSResponse SearchVocabularies
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse SearchVocabularies
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' SearchVocabulariesResponse (Maybe Text)
searchVocabulariesResponse_nextToken
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse SearchVocabularies
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' SearchVocabulariesResponse (Maybe [VocabularySummary])
searchVocabulariesResponse_vocabularySummaryList
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ SearchVocabularies
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' SearchVocabularies (Maybe Text)
searchVocabularies_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse SearchVocabularies
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' SearchVocabulariesResponse (Maybe Text)
searchVocabulariesResponse_nextToken
          forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just

instance Core.AWSRequest SearchVocabularies where
  type
    AWSResponse SearchVocabularies =
      SearchVocabulariesResponse
  request :: (Service -> Service)
-> SearchVocabularies -> Request SearchVocabularies
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 SearchVocabularies
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse SearchVocabularies)))
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 [VocabularySummary] -> Int -> SearchVocabulariesResponse
SearchVocabulariesResponse'
            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
"VocabularySummaryList"
                            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 SearchVocabularies where
  hashWithSalt :: Int -> SearchVocabularies -> Int
hashWithSalt Int
_salt SearchVocabularies' {Maybe Natural
Maybe Text
Maybe VocabularyLanguageCode
Maybe VocabularyState
Text
instanceId :: Text
state :: Maybe VocabularyState
nextToken :: Maybe Text
nameStartsWith :: Maybe Text
maxResults :: Maybe Natural
languageCode :: Maybe VocabularyLanguageCode
$sel:instanceId:SearchVocabularies' :: SearchVocabularies -> Text
$sel:state:SearchVocabularies' :: SearchVocabularies -> Maybe VocabularyState
$sel:nextToken:SearchVocabularies' :: SearchVocabularies -> Maybe Text
$sel:nameStartsWith:SearchVocabularies' :: SearchVocabularies -> Maybe Text
$sel:maxResults:SearchVocabularies' :: SearchVocabularies -> Maybe Natural
$sel:languageCode:SearchVocabularies' :: SearchVocabularies -> Maybe VocabularyLanguageCode
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe VocabularyLanguageCode
languageCode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nameStartsWith
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe VocabularyState
state
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
instanceId

instance Prelude.NFData SearchVocabularies where
  rnf :: SearchVocabularies -> ()
rnf SearchVocabularies' {Maybe Natural
Maybe Text
Maybe VocabularyLanguageCode
Maybe VocabularyState
Text
instanceId :: Text
state :: Maybe VocabularyState
nextToken :: Maybe Text
nameStartsWith :: Maybe Text
maxResults :: Maybe Natural
languageCode :: Maybe VocabularyLanguageCode
$sel:instanceId:SearchVocabularies' :: SearchVocabularies -> Text
$sel:state:SearchVocabularies' :: SearchVocabularies -> Maybe VocabularyState
$sel:nextToken:SearchVocabularies' :: SearchVocabularies -> Maybe Text
$sel:nameStartsWith:SearchVocabularies' :: SearchVocabularies -> Maybe Text
$sel:maxResults:SearchVocabularies' :: SearchVocabularies -> Maybe Natural
$sel:languageCode:SearchVocabularies' :: SearchVocabularies -> Maybe VocabularyLanguageCode
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe VocabularyLanguageCode
languageCode
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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
nameStartsWith
      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 Maybe VocabularyState
state
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
instanceId

instance Data.ToHeaders SearchVocabularies where
  toHeaders :: SearchVocabularies -> 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 SearchVocabularies where
  toJSON :: SearchVocabularies -> Value
toJSON SearchVocabularies' {Maybe Natural
Maybe Text
Maybe VocabularyLanguageCode
Maybe VocabularyState
Text
instanceId :: Text
state :: Maybe VocabularyState
nextToken :: Maybe Text
nameStartsWith :: Maybe Text
maxResults :: Maybe Natural
languageCode :: Maybe VocabularyLanguageCode
$sel:instanceId:SearchVocabularies' :: SearchVocabularies -> Text
$sel:state:SearchVocabularies' :: SearchVocabularies -> Maybe VocabularyState
$sel:nextToken:SearchVocabularies' :: SearchVocabularies -> Maybe Text
$sel:nameStartsWith:SearchVocabularies' :: SearchVocabularies -> Maybe Text
$sel:maxResults:SearchVocabularies' :: SearchVocabularies -> Maybe Natural
$sel:languageCode:SearchVocabularies' :: SearchVocabularies -> Maybe VocabularyLanguageCode
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"LanguageCode" 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 VocabularyLanguageCode
languageCode,
            (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
"NameStartsWith" 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
nameStartsWith,
            (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,
            (Key
"State" 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 VocabularyState
state
          ]
      )

instance Data.ToPath SearchVocabularies where
  toPath :: SearchVocabularies -> ByteString
toPath SearchVocabularies' {Maybe Natural
Maybe Text
Maybe VocabularyLanguageCode
Maybe VocabularyState
Text
instanceId :: Text
state :: Maybe VocabularyState
nextToken :: Maybe Text
nameStartsWith :: Maybe Text
maxResults :: Maybe Natural
languageCode :: Maybe VocabularyLanguageCode
$sel:instanceId:SearchVocabularies' :: SearchVocabularies -> Text
$sel:state:SearchVocabularies' :: SearchVocabularies -> Maybe VocabularyState
$sel:nextToken:SearchVocabularies' :: SearchVocabularies -> Maybe Text
$sel:nameStartsWith:SearchVocabularies' :: SearchVocabularies -> Maybe Text
$sel:maxResults:SearchVocabularies' :: SearchVocabularies -> Maybe Natural
$sel:languageCode:SearchVocabularies' :: SearchVocabularies -> Maybe VocabularyLanguageCode
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/vocabulary-summary/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
instanceId]

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

-- | /See:/ 'newSearchVocabulariesResponse' smart constructor.
data SearchVocabulariesResponse = SearchVocabulariesResponse'
  { -- | If there are additional results, this is the token for the next set of
    -- results.
    SearchVocabulariesResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The list of the available custom vocabularies.
    SearchVocabulariesResponse -> Maybe [VocabularySummary]
vocabularySummaryList :: Prelude.Maybe [VocabularySummary],
    -- | The response's http status code.
    SearchVocabulariesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (SearchVocabulariesResponse -> SearchVocabulariesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchVocabulariesResponse -> SearchVocabulariesResponse -> Bool
$c/= :: SearchVocabulariesResponse -> SearchVocabulariesResponse -> Bool
== :: SearchVocabulariesResponse -> SearchVocabulariesResponse -> Bool
$c== :: SearchVocabulariesResponse -> SearchVocabulariesResponse -> Bool
Prelude.Eq, ReadPrec [SearchVocabulariesResponse]
ReadPrec SearchVocabulariesResponse
Int -> ReadS SearchVocabulariesResponse
ReadS [SearchVocabulariesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SearchVocabulariesResponse]
$creadListPrec :: ReadPrec [SearchVocabulariesResponse]
readPrec :: ReadPrec SearchVocabulariesResponse
$creadPrec :: ReadPrec SearchVocabulariesResponse
readList :: ReadS [SearchVocabulariesResponse]
$creadList :: ReadS [SearchVocabulariesResponse]
readsPrec :: Int -> ReadS SearchVocabulariesResponse
$creadsPrec :: Int -> ReadS SearchVocabulariesResponse
Prelude.Read, Int -> SearchVocabulariesResponse -> ShowS
[SearchVocabulariesResponse] -> ShowS
SearchVocabulariesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchVocabulariesResponse] -> ShowS
$cshowList :: [SearchVocabulariesResponse] -> ShowS
show :: SearchVocabulariesResponse -> String
$cshow :: SearchVocabulariesResponse -> String
showsPrec :: Int -> SearchVocabulariesResponse -> ShowS
$cshowsPrec :: Int -> SearchVocabulariesResponse -> ShowS
Prelude.Show, forall x.
Rep SearchVocabulariesResponse x -> SearchVocabulariesResponse
forall x.
SearchVocabulariesResponse -> Rep SearchVocabulariesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SearchVocabulariesResponse x -> SearchVocabulariesResponse
$cfrom :: forall x.
SearchVocabulariesResponse -> Rep SearchVocabulariesResponse x
Prelude.Generic)

-- |
-- Create a value of 'SearchVocabulariesResponse' 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', 'searchVocabulariesResponse_nextToken' - If there are additional results, this is the token for the next set of
-- results.
--
-- 'vocabularySummaryList', 'searchVocabulariesResponse_vocabularySummaryList' - The list of the available custom vocabularies.
--
-- 'httpStatus', 'searchVocabulariesResponse_httpStatus' - The response's http status code.
newSearchVocabulariesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  SearchVocabulariesResponse
newSearchVocabulariesResponse :: Int -> SearchVocabulariesResponse
newSearchVocabulariesResponse Int
pHttpStatus_ =
  SearchVocabulariesResponse'
    { $sel:nextToken:SearchVocabulariesResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:vocabularySummaryList:SearchVocabulariesResponse' :: Maybe [VocabularySummary]
vocabularySummaryList = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:SearchVocabulariesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | If there are additional results, this is the token for the next set of
-- results.
searchVocabulariesResponse_nextToken :: Lens.Lens' SearchVocabulariesResponse (Prelude.Maybe Prelude.Text)
searchVocabulariesResponse_nextToken :: Lens' SearchVocabulariesResponse (Maybe Text)
searchVocabulariesResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchVocabulariesResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:SearchVocabulariesResponse' :: SearchVocabulariesResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: SearchVocabulariesResponse
s@SearchVocabulariesResponse' {} Maybe Text
a -> SearchVocabulariesResponse
s {$sel:nextToken:SearchVocabulariesResponse' :: Maybe Text
nextToken = Maybe Text
a} :: SearchVocabulariesResponse)

-- | The list of the available custom vocabularies.
searchVocabulariesResponse_vocabularySummaryList :: Lens.Lens' SearchVocabulariesResponse (Prelude.Maybe [VocabularySummary])
searchVocabulariesResponse_vocabularySummaryList :: Lens' SearchVocabulariesResponse (Maybe [VocabularySummary])
searchVocabulariesResponse_vocabularySummaryList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchVocabulariesResponse' {Maybe [VocabularySummary]
vocabularySummaryList :: Maybe [VocabularySummary]
$sel:vocabularySummaryList:SearchVocabulariesResponse' :: SearchVocabulariesResponse -> Maybe [VocabularySummary]
vocabularySummaryList} -> Maybe [VocabularySummary]
vocabularySummaryList) (\s :: SearchVocabulariesResponse
s@SearchVocabulariesResponse' {} Maybe [VocabularySummary]
a -> SearchVocabulariesResponse
s {$sel:vocabularySummaryList:SearchVocabulariesResponse' :: Maybe [VocabularySummary]
vocabularySummaryList = Maybe [VocabularySummary]
a} :: SearchVocabulariesResponse) 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.
searchVocabulariesResponse_httpStatus :: Lens.Lens' SearchVocabulariesResponse Prelude.Int
searchVocabulariesResponse_httpStatus :: Lens' SearchVocabulariesResponse Int
searchVocabulariesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchVocabulariesResponse' {Int
httpStatus :: Int
$sel:httpStatus:SearchVocabulariesResponse' :: SearchVocabulariesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: SearchVocabulariesResponse
s@SearchVocabulariesResponse' {} Int
a -> SearchVocabulariesResponse
s {$sel:httpStatus:SearchVocabulariesResponse' :: Int
httpStatus = Int
a} :: SearchVocabulariesResponse)

instance Prelude.NFData SearchVocabulariesResponse where
  rnf :: SearchVocabulariesResponse -> ()
rnf SearchVocabulariesResponse' {Int
Maybe [VocabularySummary]
Maybe Text
httpStatus :: Int
vocabularySummaryList :: Maybe [VocabularySummary]
nextToken :: Maybe Text
$sel:httpStatus:SearchVocabulariesResponse' :: SearchVocabulariesResponse -> Int
$sel:vocabularySummaryList:SearchVocabulariesResponse' :: SearchVocabulariesResponse -> Maybe [VocabularySummary]
$sel:nextToken:SearchVocabulariesResponse' :: SearchVocabulariesResponse -> 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 [VocabularySummary]
vocabularySummaryList
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus