{-# 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.LexModels.GetBots
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns bot information as follows:
--
-- -   If you provide the @nameContains@ field, the response includes
--     information for the @$LATEST@ version of all bots whose name
--     contains the specified string.
--
-- -   If you don\'t specify the @nameContains@ field, the operation
--     returns information about the @$LATEST@ version of all of your bots.
--
-- This operation requires permission for the @lex:GetBots@ action.
--
-- This operation returns paginated results.
module Amazonka.LexModels.GetBots
  ( -- * Creating a Request
    GetBots (..),
    newGetBots,

    -- * Request Lenses
    getBots_maxResults,
    getBots_nameContains,
    getBots_nextToken,

    -- * Destructuring the Response
    GetBotsResponse (..),
    newGetBotsResponse,

    -- * Response Lenses
    getBotsResponse_bots,
    getBotsResponse_nextToken,
    getBotsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newGetBots' smart constructor.
data GetBots = GetBots'
  { -- | The maximum number of bots to return in the response that the request
    -- will return. The default is 10.
    GetBots -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | Substring to match in bot names. A bot will be returned if any part of
    -- its name matches the substring. For example, \"xyz\" matches both
    -- \"xyzabc\" and \"abcxyz.\"
    GetBots -> Maybe Text
nameContains :: Prelude.Maybe Prelude.Text,
    -- | A pagination token that fetches the next page of bots. If the response
    -- to this call is truncated, Amazon Lex returns a pagination token in the
    -- response. To fetch the next page of bots, specify the pagination token
    -- in the next request.
    GetBots -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (GetBots -> GetBots -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetBots -> GetBots -> Bool
$c/= :: GetBots -> GetBots -> Bool
== :: GetBots -> GetBots -> Bool
$c== :: GetBots -> GetBots -> Bool
Prelude.Eq, ReadPrec [GetBots]
ReadPrec GetBots
Int -> ReadS GetBots
ReadS [GetBots]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetBots]
$creadListPrec :: ReadPrec [GetBots]
readPrec :: ReadPrec GetBots
$creadPrec :: ReadPrec GetBots
readList :: ReadS [GetBots]
$creadList :: ReadS [GetBots]
readsPrec :: Int -> ReadS GetBots
$creadsPrec :: Int -> ReadS GetBots
Prelude.Read, Int -> GetBots -> ShowS
[GetBots] -> ShowS
GetBots -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetBots] -> ShowS
$cshowList :: [GetBots] -> ShowS
show :: GetBots -> String
$cshow :: GetBots -> String
showsPrec :: Int -> GetBots -> ShowS
$cshowsPrec :: Int -> GetBots -> ShowS
Prelude.Show, forall x. Rep GetBots x -> GetBots
forall x. GetBots -> Rep GetBots x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetBots x -> GetBots
$cfrom :: forall x. GetBots -> Rep GetBots x
Prelude.Generic)

-- |
-- Create a value of 'GetBots' 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', 'getBots_maxResults' - The maximum number of bots to return in the response that the request
-- will return. The default is 10.
--
-- 'nameContains', 'getBots_nameContains' - Substring to match in bot names. A bot will be returned if any part of
-- its name matches the substring. For example, \"xyz\" matches both
-- \"xyzabc\" and \"abcxyz.\"
--
-- 'nextToken', 'getBots_nextToken' - A pagination token that fetches the next page of bots. If the response
-- to this call is truncated, Amazon Lex returns a pagination token in the
-- response. To fetch the next page of bots, specify the pagination token
-- in the next request.
newGetBots ::
  GetBots
newGetBots :: GetBots
newGetBots =
  GetBots'
    { $sel:maxResults:GetBots' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nameContains:GetBots' :: Maybe Text
nameContains = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:GetBots' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | The maximum number of bots to return in the response that the request
-- will return. The default is 10.
getBots_maxResults :: Lens.Lens' GetBots (Prelude.Maybe Prelude.Natural)
getBots_maxResults :: Lens' GetBots (Maybe Natural)
getBots_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBots' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:GetBots' :: GetBots -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: GetBots
s@GetBots' {} Maybe Natural
a -> GetBots
s {$sel:maxResults:GetBots' :: Maybe Natural
maxResults = Maybe Natural
a} :: GetBots)

-- | Substring to match in bot names. A bot will be returned if any part of
-- its name matches the substring. For example, \"xyz\" matches both
-- \"xyzabc\" and \"abcxyz.\"
getBots_nameContains :: Lens.Lens' GetBots (Prelude.Maybe Prelude.Text)
getBots_nameContains :: Lens' GetBots (Maybe Text)
getBots_nameContains = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBots' {Maybe Text
nameContains :: Maybe Text
$sel:nameContains:GetBots' :: GetBots -> Maybe Text
nameContains} -> Maybe Text
nameContains) (\s :: GetBots
s@GetBots' {} Maybe Text
a -> GetBots
s {$sel:nameContains:GetBots' :: Maybe Text
nameContains = Maybe Text
a} :: GetBots)

-- | A pagination token that fetches the next page of bots. If the response
-- to this call is truncated, Amazon Lex returns a pagination token in the
-- response. To fetch the next page of bots, specify the pagination token
-- in the next request.
getBots_nextToken :: Lens.Lens' GetBots (Prelude.Maybe Prelude.Text)
getBots_nextToken :: Lens' GetBots (Maybe Text)
getBots_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBots' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetBots' :: GetBots -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetBots
s@GetBots' {} Maybe Text
a -> GetBots
s {$sel:nextToken:GetBots' :: Maybe Text
nextToken = Maybe Text
a} :: GetBots)

instance Core.AWSPager GetBots where
  page :: GetBots -> AWSResponse GetBots -> Maybe GetBots
page GetBots
rq AWSResponse GetBots
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse GetBots
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetBotsResponse (Maybe Text)
getBotsResponse_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 GetBots
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetBotsResponse (Maybe [BotMetadata])
getBotsResponse_bots
            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.$ GetBots
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' GetBots (Maybe Text)
getBots_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse GetBots
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetBotsResponse (Maybe Text)
getBotsResponse_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 GetBots where
  type AWSResponse GetBots = GetBotsResponse
  request :: (Service -> Service) -> GetBots -> Request GetBots
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetBots
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetBots)))
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 [BotMetadata] -> Maybe Text -> Int -> GetBotsResponse
GetBotsResponse'
            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
"bots" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"nextToken")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable GetBots where
  hashWithSalt :: Int -> GetBots -> Int
hashWithSalt Int
_salt GetBots' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
nameContains :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:GetBots' :: GetBots -> Maybe Text
$sel:nameContains:GetBots' :: GetBots -> Maybe Text
$sel:maxResults:GetBots' :: GetBots -> 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
nameContains
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken

instance Prelude.NFData GetBots where
  rnf :: GetBots -> ()
rnf GetBots' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
nameContains :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:GetBots' :: GetBots -> Maybe Text
$sel:nameContains:GetBots' :: GetBots -> Maybe Text
$sel:maxResults:GetBots' :: GetBots -> 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
nameContains
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken

instance Data.ToHeaders GetBots where
  toHeaders :: GetBots -> 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.ToPath GetBots where
  toPath :: GetBots -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/bots/"

instance Data.ToQuery GetBots where
  toQuery :: GetBots -> QueryString
toQuery GetBots' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
nameContains :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:GetBots' :: GetBots -> Maybe Text
$sel:nameContains:GetBots' :: GetBots -> Maybe Text
$sel:maxResults:GetBots' :: GetBots -> Maybe Natural
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"maxResults" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
maxResults,
        ByteString
"nameContains" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nameContains,
        ByteString
"nextToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken
      ]

-- | /See:/ 'newGetBotsResponse' smart constructor.
data GetBotsResponse = GetBotsResponse'
  { -- | An array of @botMetadata@ objects, with one entry for each bot.
    GetBotsResponse -> Maybe [BotMetadata]
bots :: Prelude.Maybe [BotMetadata],
    -- | If the response is truncated, it includes a pagination token that you
    -- can specify in your next request to fetch the next page of bots.
    GetBotsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetBotsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetBotsResponse -> GetBotsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetBotsResponse -> GetBotsResponse -> Bool
$c/= :: GetBotsResponse -> GetBotsResponse -> Bool
== :: GetBotsResponse -> GetBotsResponse -> Bool
$c== :: GetBotsResponse -> GetBotsResponse -> Bool
Prelude.Eq, ReadPrec [GetBotsResponse]
ReadPrec GetBotsResponse
Int -> ReadS GetBotsResponse
ReadS [GetBotsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetBotsResponse]
$creadListPrec :: ReadPrec [GetBotsResponse]
readPrec :: ReadPrec GetBotsResponse
$creadPrec :: ReadPrec GetBotsResponse
readList :: ReadS [GetBotsResponse]
$creadList :: ReadS [GetBotsResponse]
readsPrec :: Int -> ReadS GetBotsResponse
$creadsPrec :: Int -> ReadS GetBotsResponse
Prelude.Read, Int -> GetBotsResponse -> ShowS
[GetBotsResponse] -> ShowS
GetBotsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetBotsResponse] -> ShowS
$cshowList :: [GetBotsResponse] -> ShowS
show :: GetBotsResponse -> String
$cshow :: GetBotsResponse -> String
showsPrec :: Int -> GetBotsResponse -> ShowS
$cshowsPrec :: Int -> GetBotsResponse -> ShowS
Prelude.Show, forall x. Rep GetBotsResponse x -> GetBotsResponse
forall x. GetBotsResponse -> Rep GetBotsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetBotsResponse x -> GetBotsResponse
$cfrom :: forall x. GetBotsResponse -> Rep GetBotsResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetBotsResponse' 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:
--
-- 'bots', 'getBotsResponse_bots' - An array of @botMetadata@ objects, with one entry for each bot.
--
-- 'nextToken', 'getBotsResponse_nextToken' - If the response is truncated, it includes a pagination token that you
-- can specify in your next request to fetch the next page of bots.
--
-- 'httpStatus', 'getBotsResponse_httpStatus' - The response's http status code.
newGetBotsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetBotsResponse
newGetBotsResponse :: Int -> GetBotsResponse
newGetBotsResponse Int
pHttpStatus_ =
  GetBotsResponse'
    { $sel:bots:GetBotsResponse' :: Maybe [BotMetadata]
bots = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:GetBotsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetBotsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An array of @botMetadata@ objects, with one entry for each bot.
getBotsResponse_bots :: Lens.Lens' GetBotsResponse (Prelude.Maybe [BotMetadata])
getBotsResponse_bots :: Lens' GetBotsResponse (Maybe [BotMetadata])
getBotsResponse_bots = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBotsResponse' {Maybe [BotMetadata]
bots :: Maybe [BotMetadata]
$sel:bots:GetBotsResponse' :: GetBotsResponse -> Maybe [BotMetadata]
bots} -> Maybe [BotMetadata]
bots) (\s :: GetBotsResponse
s@GetBotsResponse' {} Maybe [BotMetadata]
a -> GetBotsResponse
s {$sel:bots:GetBotsResponse' :: Maybe [BotMetadata]
bots = Maybe [BotMetadata]
a} :: GetBotsResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | If the response is truncated, it includes a pagination token that you
-- can specify in your next request to fetch the next page of bots.
getBotsResponse_nextToken :: Lens.Lens' GetBotsResponse (Prelude.Maybe Prelude.Text)
getBotsResponse_nextToken :: Lens' GetBotsResponse (Maybe Text)
getBotsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBotsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetBotsResponse' :: GetBotsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetBotsResponse
s@GetBotsResponse' {} Maybe Text
a -> GetBotsResponse
s {$sel:nextToken:GetBotsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: GetBotsResponse)

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

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