{-# 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.ListLexBots
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- This API is in preview release for Amazon Connect and is subject to
-- change.
--
-- Returns a paginated list of all the Amazon Lex V1 bots currently
-- associated with the instance. To return both Amazon Lex V1 and V2 bots,
-- use the
-- <https://docs.aws.amazon.com/connect/latest/APIReference/API_ListBots.html ListBots>
-- API.
--
-- This operation returns paginated results.
module Amazonka.Connect.ListLexBots
  ( -- * Creating a Request
    ListLexBots (..),
    newListLexBots,

    -- * Request Lenses
    listLexBots_maxResults,
    listLexBots_nextToken,
    listLexBots_instanceId,

    -- * Destructuring the Response
    ListLexBotsResponse (..),
    newListLexBotsResponse,

    -- * Response Lenses
    listLexBotsResponse_lexBots,
    listLexBotsResponse_nextToken,
    listLexBotsResponse_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:/ 'newListLexBots' smart constructor.
data ListLexBots = ListLexBots'
  { -- | The maximum number of results to return per page. If no value is
    -- specified, the default is 10.
    ListLexBots -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | 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.
    ListLexBots -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The identifier of the Amazon Connect instance. You can find the
    -- instanceId in the ARN of the instance.
    ListLexBots -> Text
instanceId :: Prelude.Text
  }
  deriving (ListLexBots -> ListLexBots -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListLexBots -> ListLexBots -> Bool
$c/= :: ListLexBots -> ListLexBots -> Bool
== :: ListLexBots -> ListLexBots -> Bool
$c== :: ListLexBots -> ListLexBots -> Bool
Prelude.Eq, ReadPrec [ListLexBots]
ReadPrec ListLexBots
Int -> ReadS ListLexBots
ReadS [ListLexBots]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListLexBots]
$creadListPrec :: ReadPrec [ListLexBots]
readPrec :: ReadPrec ListLexBots
$creadPrec :: ReadPrec ListLexBots
readList :: ReadS [ListLexBots]
$creadList :: ReadS [ListLexBots]
readsPrec :: Int -> ReadS ListLexBots
$creadsPrec :: Int -> ReadS ListLexBots
Prelude.Read, Int -> ListLexBots -> ShowS
[ListLexBots] -> ShowS
ListLexBots -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListLexBots] -> ShowS
$cshowList :: [ListLexBots] -> ShowS
show :: ListLexBots -> String
$cshow :: ListLexBots -> String
showsPrec :: Int -> ListLexBots -> ShowS
$cshowsPrec :: Int -> ListLexBots -> ShowS
Prelude.Show, forall x. Rep ListLexBots x -> ListLexBots
forall x. ListLexBots -> Rep ListLexBots x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListLexBots x -> ListLexBots
$cfrom :: forall x. ListLexBots -> Rep ListLexBots x
Prelude.Generic)

-- |
-- Create a value of 'ListLexBots' 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', 'listLexBots_maxResults' - The maximum number of results to return per page. If no value is
-- specified, the default is 10.
--
-- 'nextToken', 'listLexBots_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.
--
-- 'instanceId', 'listLexBots_instanceId' - The identifier of the Amazon Connect instance. You can find the
-- instanceId in the ARN of the instance.
newListLexBots ::
  -- | 'instanceId'
  Prelude.Text ->
  ListLexBots
newListLexBots :: Text -> ListLexBots
newListLexBots Text
pInstanceId_ =
  ListLexBots'
    { $sel:maxResults:ListLexBots' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListLexBots' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceId:ListLexBots' :: Text
instanceId = Text
pInstanceId_
    }

-- | The maximum number of results to return per page. If no value is
-- specified, the default is 10.
listLexBots_maxResults :: Lens.Lens' ListLexBots (Prelude.Maybe Prelude.Natural)
listLexBots_maxResults :: Lens' ListLexBots (Maybe Natural)
listLexBots_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListLexBots' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListLexBots' :: ListLexBots -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListLexBots
s@ListLexBots' {} Maybe Natural
a -> ListLexBots
s {$sel:maxResults:ListLexBots' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListLexBots)

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

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

instance Core.AWSPager ListLexBots where
  page :: ListLexBots -> AWSResponse ListLexBots -> Maybe ListLexBots
page ListLexBots
rq AWSResponse ListLexBots
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListLexBots
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListLexBotsResponse (Maybe Text)
listLexBotsResponse_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 ListLexBots
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListLexBotsResponse (Maybe [LexBot])
listLexBotsResponse_lexBots
            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.$ ListLexBots
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListLexBots (Maybe Text)
listLexBots_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListLexBots
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListLexBotsResponse (Maybe Text)
listLexBotsResponse_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 ListLexBots where
  type AWSResponse ListLexBots = ListLexBotsResponse
  request :: (Service -> Service) -> ListLexBots -> Request ListLexBots
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 ListLexBots
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListLexBots)))
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 [LexBot] -> Maybe Text -> Int -> ListLexBotsResponse
ListLexBotsResponse'
            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
"LexBots" 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 ListLexBots where
  hashWithSalt :: Int -> ListLexBots -> Int
hashWithSalt Int
_salt ListLexBots' {Maybe Natural
Maybe Text
Text
instanceId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:instanceId:ListLexBots' :: ListLexBots -> Text
$sel:nextToken:ListLexBots' :: ListLexBots -> Maybe Text
$sel:maxResults:ListLexBots' :: ListLexBots -> Maybe Natural
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
instanceId

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

instance Data.ToHeaders ListLexBots where
  toHeaders :: ListLexBots -> 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 ListLexBots where
  toPath :: ListLexBots -> ByteString
toPath ListLexBots' {Maybe Natural
Maybe Text
Text
instanceId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:instanceId:ListLexBots' :: ListLexBots -> Text
$sel:nextToken:ListLexBots' :: ListLexBots -> Maybe Text
$sel:maxResults:ListLexBots' :: ListLexBots -> Maybe Natural
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/instance/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
instanceId, ByteString
"/lex-bots"]

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

-- | /See:/ 'newListLexBotsResponse' smart constructor.
data ListLexBotsResponse = ListLexBotsResponse'
  { -- | The names and Amazon Web Services Regions of the Amazon Lex bots
    -- associated with the specified instance.
    ListLexBotsResponse -> Maybe [LexBot]
lexBots :: Prelude.Maybe [LexBot],
    -- | If there are additional results, this is the token for the next set of
    -- results.
    ListLexBotsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListLexBotsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListLexBotsResponse -> ListLexBotsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListLexBotsResponse -> ListLexBotsResponse -> Bool
$c/= :: ListLexBotsResponse -> ListLexBotsResponse -> Bool
== :: ListLexBotsResponse -> ListLexBotsResponse -> Bool
$c== :: ListLexBotsResponse -> ListLexBotsResponse -> Bool
Prelude.Eq, ReadPrec [ListLexBotsResponse]
ReadPrec ListLexBotsResponse
Int -> ReadS ListLexBotsResponse
ReadS [ListLexBotsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListLexBotsResponse]
$creadListPrec :: ReadPrec [ListLexBotsResponse]
readPrec :: ReadPrec ListLexBotsResponse
$creadPrec :: ReadPrec ListLexBotsResponse
readList :: ReadS [ListLexBotsResponse]
$creadList :: ReadS [ListLexBotsResponse]
readsPrec :: Int -> ReadS ListLexBotsResponse
$creadsPrec :: Int -> ReadS ListLexBotsResponse
Prelude.Read, Int -> ListLexBotsResponse -> ShowS
[ListLexBotsResponse] -> ShowS
ListLexBotsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListLexBotsResponse] -> ShowS
$cshowList :: [ListLexBotsResponse] -> ShowS
show :: ListLexBotsResponse -> String
$cshow :: ListLexBotsResponse -> String
showsPrec :: Int -> ListLexBotsResponse -> ShowS
$cshowsPrec :: Int -> ListLexBotsResponse -> ShowS
Prelude.Show, forall x. Rep ListLexBotsResponse x -> ListLexBotsResponse
forall x. ListLexBotsResponse -> Rep ListLexBotsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListLexBotsResponse x -> ListLexBotsResponse
$cfrom :: forall x. ListLexBotsResponse -> Rep ListLexBotsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListLexBotsResponse' 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:
--
-- 'lexBots', 'listLexBotsResponse_lexBots' - The names and Amazon Web Services Regions of the Amazon Lex bots
-- associated with the specified instance.
--
-- 'nextToken', 'listLexBotsResponse_nextToken' - If there are additional results, this is the token for the next set of
-- results.
--
-- 'httpStatus', 'listLexBotsResponse_httpStatus' - The response's http status code.
newListLexBotsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListLexBotsResponse
newListLexBotsResponse :: Int -> ListLexBotsResponse
newListLexBotsResponse Int
pHttpStatus_ =
  ListLexBotsResponse'
    { $sel:lexBots:ListLexBotsResponse' :: Maybe [LexBot]
lexBots = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListLexBotsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListLexBotsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The names and Amazon Web Services Regions of the Amazon Lex bots
-- associated with the specified instance.
listLexBotsResponse_lexBots :: Lens.Lens' ListLexBotsResponse (Prelude.Maybe [LexBot])
listLexBotsResponse_lexBots :: Lens' ListLexBotsResponse (Maybe [LexBot])
listLexBotsResponse_lexBots = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListLexBotsResponse' {Maybe [LexBot]
lexBots :: Maybe [LexBot]
$sel:lexBots:ListLexBotsResponse' :: ListLexBotsResponse -> Maybe [LexBot]
lexBots} -> Maybe [LexBot]
lexBots) (\s :: ListLexBotsResponse
s@ListLexBotsResponse' {} Maybe [LexBot]
a -> ListLexBotsResponse
s {$sel:lexBots:ListLexBotsResponse' :: Maybe [LexBot]
lexBots = Maybe [LexBot]
a} :: ListLexBotsResponse) 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 there are additional results, this is the token for the next set of
-- results.
listLexBotsResponse_nextToken :: Lens.Lens' ListLexBotsResponse (Prelude.Maybe Prelude.Text)
listLexBotsResponse_nextToken :: Lens' ListLexBotsResponse (Maybe Text)
listLexBotsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListLexBotsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListLexBotsResponse' :: ListLexBotsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListLexBotsResponse
s@ListLexBotsResponse' {} Maybe Text
a -> ListLexBotsResponse
s {$sel:nextToken:ListLexBotsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListLexBotsResponse)

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

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