{-# 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.ListBotVersions
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets information about all of the versions of a bot.
--
-- The @ListBotVersions@ operation returns a summary of each version of a
-- bot. For example, if a bot has three numbered versions, the
-- @ListBotVersions@ operation returns for summaries, one for each numbered
-- version and one for the @DRAFT@ version.
--
-- The @ListBotVersions@ operation always returns at least one version, the
-- @DRAFT@ version.
module Amazonka.LexV2Models.ListBotVersions
  ( -- * Creating a Request
    ListBotVersions (..),
    newListBotVersions,

    -- * Request Lenses
    listBotVersions_maxResults,
    listBotVersions_nextToken,
    listBotVersions_sortBy,
    listBotVersions_botId,

    -- * Destructuring the Response
    ListBotVersionsResponse (..),
    newListBotVersionsResponse,

    -- * Response Lenses
    listBotVersionsResponse_botId,
    listBotVersionsResponse_botVersionSummaries,
    listBotVersionsResponse_nextToken,
    listBotVersionsResponse_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:/ 'newListBotVersions' smart constructor.
data ListBotVersions = ListBotVersions'
  { -- | The maximum number of versions 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.
    ListBotVersions -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | If the response to the @ListBotVersion@ operation contains more results
    -- than specified in the @maxResults@ parameter, a token is returned in the
    -- response. Use that token in the @nextToken@ parameter to return the next
    -- page of results.
    ListBotVersions -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Specifies sorting parameters for the list of versions. You can specify
    -- that the list be sorted by version name in either ascending or
    -- descending order.
    ListBotVersions -> Maybe BotVersionSortBy
sortBy :: Prelude.Maybe BotVersionSortBy,
    -- | The identifier of the bot to list versions for.
    ListBotVersions -> Text
botId :: Prelude.Text
  }
  deriving (ListBotVersions -> ListBotVersions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListBotVersions -> ListBotVersions -> Bool
$c/= :: ListBotVersions -> ListBotVersions -> Bool
== :: ListBotVersions -> ListBotVersions -> Bool
$c== :: ListBotVersions -> ListBotVersions -> Bool
Prelude.Eq, ReadPrec [ListBotVersions]
ReadPrec ListBotVersions
Int -> ReadS ListBotVersions
ReadS [ListBotVersions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListBotVersions]
$creadListPrec :: ReadPrec [ListBotVersions]
readPrec :: ReadPrec ListBotVersions
$creadPrec :: ReadPrec ListBotVersions
readList :: ReadS [ListBotVersions]
$creadList :: ReadS [ListBotVersions]
readsPrec :: Int -> ReadS ListBotVersions
$creadsPrec :: Int -> ReadS ListBotVersions
Prelude.Read, Int -> ListBotVersions -> ShowS
[ListBotVersions] -> ShowS
ListBotVersions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListBotVersions] -> ShowS
$cshowList :: [ListBotVersions] -> ShowS
show :: ListBotVersions -> String
$cshow :: ListBotVersions -> String
showsPrec :: Int -> ListBotVersions -> ShowS
$cshowsPrec :: Int -> ListBotVersions -> ShowS
Prelude.Show, forall x. Rep ListBotVersions x -> ListBotVersions
forall x. ListBotVersions -> Rep ListBotVersions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListBotVersions x -> ListBotVersions
$cfrom :: forall x. ListBotVersions -> Rep ListBotVersions x
Prelude.Generic)

-- |
-- Create a value of 'ListBotVersions' 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', 'listBotVersions_maxResults' - The maximum number of versions 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.
--
-- 'nextToken', 'listBotVersions_nextToken' - If the response to the @ListBotVersion@ operation contains more results
-- than specified in the @maxResults@ parameter, a token is returned in the
-- response. Use that token in the @nextToken@ parameter to return the next
-- page of results.
--
-- 'sortBy', 'listBotVersions_sortBy' - Specifies sorting parameters for the list of versions. You can specify
-- that the list be sorted by version name in either ascending or
-- descending order.
--
-- 'botId', 'listBotVersions_botId' - The identifier of the bot to list versions for.
newListBotVersions ::
  -- | 'botId'
  Prelude.Text ->
  ListBotVersions
newListBotVersions :: Text -> ListBotVersions
newListBotVersions Text
pBotId_ =
  ListBotVersions'
    { $sel:maxResults:ListBotVersions' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListBotVersions' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:sortBy:ListBotVersions' :: Maybe BotVersionSortBy
sortBy = forall a. Maybe a
Prelude.Nothing,
      $sel:botId:ListBotVersions' :: Text
botId = Text
pBotId_
    }

-- | The maximum number of versions 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.
listBotVersions_maxResults :: Lens.Lens' ListBotVersions (Prelude.Maybe Prelude.Natural)
listBotVersions_maxResults :: Lens' ListBotVersions (Maybe Natural)
listBotVersions_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListBotVersions' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListBotVersions' :: ListBotVersions -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListBotVersions
s@ListBotVersions' {} Maybe Natural
a -> ListBotVersions
s {$sel:maxResults:ListBotVersions' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListBotVersions)

-- | If the response to the @ListBotVersion@ operation contains more results
-- than specified in the @maxResults@ parameter, a token is returned in the
-- response. Use that token in the @nextToken@ parameter to return the next
-- page of results.
listBotVersions_nextToken :: Lens.Lens' ListBotVersions (Prelude.Maybe Prelude.Text)
listBotVersions_nextToken :: Lens' ListBotVersions (Maybe Text)
listBotVersions_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListBotVersions' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListBotVersions' :: ListBotVersions -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListBotVersions
s@ListBotVersions' {} Maybe Text
a -> ListBotVersions
s {$sel:nextToken:ListBotVersions' :: Maybe Text
nextToken = Maybe Text
a} :: ListBotVersions)

-- | Specifies sorting parameters for the list of versions. You can specify
-- that the list be sorted by version name in either ascending or
-- descending order.
listBotVersions_sortBy :: Lens.Lens' ListBotVersions (Prelude.Maybe BotVersionSortBy)
listBotVersions_sortBy :: Lens' ListBotVersions (Maybe BotVersionSortBy)
listBotVersions_sortBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListBotVersions' {Maybe BotVersionSortBy
sortBy :: Maybe BotVersionSortBy
$sel:sortBy:ListBotVersions' :: ListBotVersions -> Maybe BotVersionSortBy
sortBy} -> Maybe BotVersionSortBy
sortBy) (\s :: ListBotVersions
s@ListBotVersions' {} Maybe BotVersionSortBy
a -> ListBotVersions
s {$sel:sortBy:ListBotVersions' :: Maybe BotVersionSortBy
sortBy = Maybe BotVersionSortBy
a} :: ListBotVersions)

-- | The identifier of the bot to list versions for.
listBotVersions_botId :: Lens.Lens' ListBotVersions Prelude.Text
listBotVersions_botId :: Lens' ListBotVersions Text
listBotVersions_botId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListBotVersions' {Text
botId :: Text
$sel:botId:ListBotVersions' :: ListBotVersions -> Text
botId} -> Text
botId) (\s :: ListBotVersions
s@ListBotVersions' {} Text
a -> ListBotVersions
s {$sel:botId:ListBotVersions' :: Text
botId = Text
a} :: ListBotVersions)

instance Core.AWSRequest ListBotVersions where
  type
    AWSResponse ListBotVersions =
      ListBotVersionsResponse
  request :: (Service -> Service) -> ListBotVersions -> Request ListBotVersions
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 ListBotVersions
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListBotVersions)))
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 [BotVersionSummary]
-> Maybe Text
-> Int
-> ListBotVersionsResponse
ListBotVersionsResponse'
            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
"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
"botVersionSummaries"
                            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 ListBotVersions where
  hashWithSalt :: Int -> ListBotVersions -> Int
hashWithSalt Int
_salt ListBotVersions' {Maybe Natural
Maybe Text
Maybe BotVersionSortBy
Text
botId :: Text
sortBy :: Maybe BotVersionSortBy
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:botId:ListBotVersions' :: ListBotVersions -> Text
$sel:sortBy:ListBotVersions' :: ListBotVersions -> Maybe BotVersionSortBy
$sel:nextToken:ListBotVersions' :: ListBotVersions -> Maybe Text
$sel:maxResults:ListBotVersions' :: ListBotVersions -> 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` Maybe BotVersionSortBy
sortBy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
botId

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

instance Data.ToHeaders ListBotVersions where
  toHeaders :: ListBotVersions -> 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 ListBotVersions where
  toJSON :: ListBotVersions -> Value
toJSON ListBotVersions' {Maybe Natural
Maybe Text
Maybe BotVersionSortBy
Text
botId :: Text
sortBy :: Maybe BotVersionSortBy
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:botId:ListBotVersions' :: ListBotVersions -> Text
$sel:sortBy:ListBotVersions' :: ListBotVersions -> Maybe BotVersionSortBy
$sel:nextToken:ListBotVersions' :: ListBotVersions -> Maybe Text
$sel:maxResults:ListBotVersions' :: ListBotVersions -> Maybe Natural
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"maxResults" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
maxResults,
            (Key
"nextToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
nextToken,
            (Key
"sortBy" 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 BotVersionSortBy
sortBy
          ]
      )

instance Data.ToPath ListBotVersions where
  toPath :: ListBotVersions -> ByteString
toPath ListBotVersions' {Maybe Natural
Maybe Text
Maybe BotVersionSortBy
Text
botId :: Text
sortBy :: Maybe BotVersionSortBy
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:botId:ListBotVersions' :: ListBotVersions -> Text
$sel:sortBy:ListBotVersions' :: ListBotVersions -> Maybe BotVersionSortBy
$sel:nextToken:ListBotVersions' :: ListBotVersions -> Maybe Text
$sel:maxResults:ListBotVersions' :: ListBotVersions -> Maybe Natural
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/bots/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
botId, ByteString
"/botversions/"]

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

-- | /See:/ 'newListBotVersionsResponse' smart constructor.
data ListBotVersionsResponse = ListBotVersionsResponse'
  { -- | The identifier of the bot to list versions for.
    ListBotVersionsResponse -> Maybe Text
botId :: Prelude.Maybe Prelude.Text,
    -- | Summary information for the bot versions that meet the filter criteria
    -- specified in the request. The length of the list is specified in the
    -- @maxResults@ parameter of the request. If there are more versions
    -- available, the @nextToken@ field contains a token to get the next page
    -- of results.
    ListBotVersionsResponse -> Maybe [BotVersionSummary]
botVersionSummaries :: Prelude.Maybe [BotVersionSummary],
    -- | A token that indicates whether there are more results to return in a
    -- response to the @ListBotVersions@ operation. If the @nextToken@ field is
    -- present, you send the contents as the @nextToken@ parameter of a
    -- @ListBotAliases@ operation request to get the next page of results.
    ListBotVersionsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListBotVersionsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListBotVersionsResponse -> ListBotVersionsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListBotVersionsResponse -> ListBotVersionsResponse -> Bool
$c/= :: ListBotVersionsResponse -> ListBotVersionsResponse -> Bool
== :: ListBotVersionsResponse -> ListBotVersionsResponse -> Bool
$c== :: ListBotVersionsResponse -> ListBotVersionsResponse -> Bool
Prelude.Eq, ReadPrec [ListBotVersionsResponse]
ReadPrec ListBotVersionsResponse
Int -> ReadS ListBotVersionsResponse
ReadS [ListBotVersionsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListBotVersionsResponse]
$creadListPrec :: ReadPrec [ListBotVersionsResponse]
readPrec :: ReadPrec ListBotVersionsResponse
$creadPrec :: ReadPrec ListBotVersionsResponse
readList :: ReadS [ListBotVersionsResponse]
$creadList :: ReadS [ListBotVersionsResponse]
readsPrec :: Int -> ReadS ListBotVersionsResponse
$creadsPrec :: Int -> ReadS ListBotVersionsResponse
Prelude.Read, Int -> ListBotVersionsResponse -> ShowS
[ListBotVersionsResponse] -> ShowS
ListBotVersionsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListBotVersionsResponse] -> ShowS
$cshowList :: [ListBotVersionsResponse] -> ShowS
show :: ListBotVersionsResponse -> String
$cshow :: ListBotVersionsResponse -> String
showsPrec :: Int -> ListBotVersionsResponse -> ShowS
$cshowsPrec :: Int -> ListBotVersionsResponse -> ShowS
Prelude.Show, forall x. Rep ListBotVersionsResponse x -> ListBotVersionsResponse
forall x. ListBotVersionsResponse -> Rep ListBotVersionsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListBotVersionsResponse x -> ListBotVersionsResponse
$cfrom :: forall x. ListBotVersionsResponse -> Rep ListBotVersionsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListBotVersionsResponse' 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:
--
-- 'botId', 'listBotVersionsResponse_botId' - The identifier of the bot to list versions for.
--
-- 'botVersionSummaries', 'listBotVersionsResponse_botVersionSummaries' - Summary information for the bot versions that meet the filter criteria
-- specified in the request. The length of the list is specified in the
-- @maxResults@ parameter of the request. If there are more versions
-- available, the @nextToken@ field contains a token to get the next page
-- of results.
--
-- 'nextToken', 'listBotVersionsResponse_nextToken' - A token that indicates whether there are more results to return in a
-- response to the @ListBotVersions@ operation. If the @nextToken@ field is
-- present, you send the contents as the @nextToken@ parameter of a
-- @ListBotAliases@ operation request to get the next page of results.
--
-- 'httpStatus', 'listBotVersionsResponse_httpStatus' - The response's http status code.
newListBotVersionsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListBotVersionsResponse
newListBotVersionsResponse :: Int -> ListBotVersionsResponse
newListBotVersionsResponse Int
pHttpStatus_ =
  ListBotVersionsResponse'
    { $sel:botId:ListBotVersionsResponse' :: Maybe Text
botId = forall a. Maybe a
Prelude.Nothing,
      $sel:botVersionSummaries:ListBotVersionsResponse' :: Maybe [BotVersionSummary]
botVersionSummaries = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListBotVersionsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListBotVersionsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The identifier of the bot to list versions for.
listBotVersionsResponse_botId :: Lens.Lens' ListBotVersionsResponse (Prelude.Maybe Prelude.Text)
listBotVersionsResponse_botId :: Lens' ListBotVersionsResponse (Maybe Text)
listBotVersionsResponse_botId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListBotVersionsResponse' {Maybe Text
botId :: Maybe Text
$sel:botId:ListBotVersionsResponse' :: ListBotVersionsResponse -> Maybe Text
botId} -> Maybe Text
botId) (\s :: ListBotVersionsResponse
s@ListBotVersionsResponse' {} Maybe Text
a -> ListBotVersionsResponse
s {$sel:botId:ListBotVersionsResponse' :: Maybe Text
botId = Maybe Text
a} :: ListBotVersionsResponse)

-- | Summary information for the bot versions that meet the filter criteria
-- specified in the request. The length of the list is specified in the
-- @maxResults@ parameter of the request. If there are more versions
-- available, the @nextToken@ field contains a token to get the next page
-- of results.
listBotVersionsResponse_botVersionSummaries :: Lens.Lens' ListBotVersionsResponse (Prelude.Maybe [BotVersionSummary])
listBotVersionsResponse_botVersionSummaries :: Lens' ListBotVersionsResponse (Maybe [BotVersionSummary])
listBotVersionsResponse_botVersionSummaries = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListBotVersionsResponse' {Maybe [BotVersionSummary]
botVersionSummaries :: Maybe [BotVersionSummary]
$sel:botVersionSummaries:ListBotVersionsResponse' :: ListBotVersionsResponse -> Maybe [BotVersionSummary]
botVersionSummaries} -> Maybe [BotVersionSummary]
botVersionSummaries) (\s :: ListBotVersionsResponse
s@ListBotVersionsResponse' {} Maybe [BotVersionSummary]
a -> ListBotVersionsResponse
s {$sel:botVersionSummaries:ListBotVersionsResponse' :: Maybe [BotVersionSummary]
botVersionSummaries = Maybe [BotVersionSummary]
a} :: ListBotVersionsResponse) 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

-- | A token that indicates whether there are more results to return in a
-- response to the @ListBotVersions@ operation. If the @nextToken@ field is
-- present, you send the contents as the @nextToken@ parameter of a
-- @ListBotAliases@ operation request to get the next page of results.
listBotVersionsResponse_nextToken :: Lens.Lens' ListBotVersionsResponse (Prelude.Maybe Prelude.Text)
listBotVersionsResponse_nextToken :: Lens' ListBotVersionsResponse (Maybe Text)
listBotVersionsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListBotVersionsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListBotVersionsResponse' :: ListBotVersionsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListBotVersionsResponse
s@ListBotVersionsResponse' {} Maybe Text
a -> ListBotVersionsResponse
s {$sel:nextToken:ListBotVersionsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListBotVersionsResponse)

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

instance Prelude.NFData ListBotVersionsResponse where
  rnf :: ListBotVersionsResponse -> ()
rnf ListBotVersionsResponse' {Int
Maybe [BotVersionSummary]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
botVersionSummaries :: Maybe [BotVersionSummary]
botId :: Maybe Text
$sel:httpStatus:ListBotVersionsResponse' :: ListBotVersionsResponse -> Int
$sel:nextToken:ListBotVersionsResponse' :: ListBotVersionsResponse -> Maybe Text
$sel:botVersionSummaries:ListBotVersionsResponse' :: ListBotVersionsResponse -> Maybe [BotVersionSummary]
$sel:botId:ListBotVersionsResponse' :: ListBotVersionsResponse -> Maybe Text
..} =
    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 [BotVersionSummary]
botVersionSummaries
      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