{-# 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.ListBotAliases
-- 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 a list of aliases for the specified bot.
module Amazonka.LexV2Models.ListBotAliases
  ( -- * Creating a Request
    ListBotAliases (..),
    newListBotAliases,

    -- * Request Lenses
    listBotAliases_maxResults,
    listBotAliases_nextToken,
    listBotAliases_botId,

    -- * Destructuring the Response
    ListBotAliasesResponse (..),
    newListBotAliasesResponse,

    -- * Response Lenses
    listBotAliasesResponse_botAliasSummaries,
    listBotAliasesResponse_botId,
    listBotAliasesResponse_nextToken,
    listBotAliasesResponse_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:/ 'newListBotAliases' smart constructor.
data ListBotAliases = ListBotAliases'
  { -- | The maximum number of aliases 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.
    ListBotAliases -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | If the response from the @ListBotAliases@ 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.
    ListBotAliases -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The identifier of the bot to list aliases for.
    ListBotAliases -> Text
botId :: Prelude.Text
  }
  deriving (ListBotAliases -> ListBotAliases -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListBotAliases -> ListBotAliases -> Bool
$c/= :: ListBotAliases -> ListBotAliases -> Bool
== :: ListBotAliases -> ListBotAliases -> Bool
$c== :: ListBotAliases -> ListBotAliases -> Bool
Prelude.Eq, ReadPrec [ListBotAliases]
ReadPrec ListBotAliases
Int -> ReadS ListBotAliases
ReadS [ListBotAliases]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListBotAliases]
$creadListPrec :: ReadPrec [ListBotAliases]
readPrec :: ReadPrec ListBotAliases
$creadPrec :: ReadPrec ListBotAliases
readList :: ReadS [ListBotAliases]
$creadList :: ReadS [ListBotAliases]
readsPrec :: Int -> ReadS ListBotAliases
$creadsPrec :: Int -> ReadS ListBotAliases
Prelude.Read, Int -> ListBotAliases -> ShowS
[ListBotAliases] -> ShowS
ListBotAliases -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListBotAliases] -> ShowS
$cshowList :: [ListBotAliases] -> ShowS
show :: ListBotAliases -> String
$cshow :: ListBotAliases -> String
showsPrec :: Int -> ListBotAliases -> ShowS
$cshowsPrec :: Int -> ListBotAliases -> ShowS
Prelude.Show, forall x. Rep ListBotAliases x -> ListBotAliases
forall x. ListBotAliases -> Rep ListBotAliases x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListBotAliases x -> ListBotAliases
$cfrom :: forall x. ListBotAliases -> Rep ListBotAliases x
Prelude.Generic)

-- |
-- Create a value of 'ListBotAliases' 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', 'listBotAliases_maxResults' - The maximum number of aliases 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', 'listBotAliases_nextToken' - If the response from the @ListBotAliases@ 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.
--
-- 'botId', 'listBotAliases_botId' - The identifier of the bot to list aliases for.
newListBotAliases ::
  -- | 'botId'
  Prelude.Text ->
  ListBotAliases
newListBotAliases :: Text -> ListBotAliases
newListBotAliases Text
pBotId_ =
  ListBotAliases'
    { $sel:maxResults:ListBotAliases' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListBotAliases' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:botId:ListBotAliases' :: Text
botId = Text
pBotId_
    }

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

-- | If the response from the @ListBotAliases@ 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.
listBotAliases_nextToken :: Lens.Lens' ListBotAliases (Prelude.Maybe Prelude.Text)
listBotAliases_nextToken :: Lens' ListBotAliases (Maybe Text)
listBotAliases_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListBotAliases' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListBotAliases' :: ListBotAliases -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListBotAliases
s@ListBotAliases' {} Maybe Text
a -> ListBotAliases
s {$sel:nextToken:ListBotAliases' :: Maybe Text
nextToken = Maybe Text
a} :: ListBotAliases)

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

instance Core.AWSRequest ListBotAliases where
  type
    AWSResponse ListBotAliases =
      ListBotAliasesResponse
  request :: (Service -> Service) -> ListBotAliases -> Request ListBotAliases
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 ListBotAliases
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListBotAliases)))
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 [BotAliasSummary]
-> Maybe Text -> Maybe Text -> Int -> ListBotAliasesResponse
ListBotAliasesResponse'
            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
"botAliasSummaries"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"botId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"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 ListBotAliases where
  hashWithSalt :: Int -> ListBotAliases -> Int
hashWithSalt Int
_salt ListBotAliases' {Maybe Natural
Maybe Text
Text
botId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:botId:ListBotAliases' :: ListBotAliases -> Text
$sel:nextToken:ListBotAliases' :: ListBotAliases -> Maybe Text
$sel:maxResults:ListBotAliases' :: ListBotAliases -> 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
botId

instance Prelude.NFData ListBotAliases where
  rnf :: ListBotAliases -> ()
rnf ListBotAliases' {Maybe Natural
Maybe Text
Text
botId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:botId:ListBotAliases' :: ListBotAliases -> Text
$sel:nextToken:ListBotAliases' :: ListBotAliases -> Maybe Text
$sel:maxResults:ListBotAliases' :: ListBotAliases -> 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
botId

instance Data.ToHeaders ListBotAliases where
  toHeaders :: ListBotAliases -> 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 ListBotAliases where
  toJSON :: ListBotAliases -> Value
toJSON ListBotAliases' {Maybe Natural
Maybe Text
Text
botId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:botId:ListBotAliases' :: ListBotAliases -> Text
$sel:nextToken:ListBotAliases' :: ListBotAliases -> Maybe Text
$sel:maxResults:ListBotAliases' :: ListBotAliases -> 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
          ]
      )

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

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

-- | /See:/ 'newListBotAliasesResponse' smart constructor.
data ListBotAliasesResponse = ListBotAliasesResponse'
  { -- | Summary information for the bot aliases 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 aliases
    -- available, the @nextToken@ field contains a token to get the next page
    -- of results.
    ListBotAliasesResponse -> Maybe [BotAliasSummary]
botAliasSummaries :: Prelude.Maybe [BotAliasSummary],
    -- | The identifier of the bot associated with the aliases.
    ListBotAliasesResponse -> Maybe Text
botId :: Prelude.Maybe Prelude.Text,
    -- | A token that indicates whether there are more results to return in a
    -- response to the @ListBotAliases@ 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.
    ListBotAliasesResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListBotAliasesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListBotAliasesResponse -> ListBotAliasesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListBotAliasesResponse -> ListBotAliasesResponse -> Bool
$c/= :: ListBotAliasesResponse -> ListBotAliasesResponse -> Bool
== :: ListBotAliasesResponse -> ListBotAliasesResponse -> Bool
$c== :: ListBotAliasesResponse -> ListBotAliasesResponse -> Bool
Prelude.Eq, ReadPrec [ListBotAliasesResponse]
ReadPrec ListBotAliasesResponse
Int -> ReadS ListBotAliasesResponse
ReadS [ListBotAliasesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListBotAliasesResponse]
$creadListPrec :: ReadPrec [ListBotAliasesResponse]
readPrec :: ReadPrec ListBotAliasesResponse
$creadPrec :: ReadPrec ListBotAliasesResponse
readList :: ReadS [ListBotAliasesResponse]
$creadList :: ReadS [ListBotAliasesResponse]
readsPrec :: Int -> ReadS ListBotAliasesResponse
$creadsPrec :: Int -> ReadS ListBotAliasesResponse
Prelude.Read, Int -> ListBotAliasesResponse -> ShowS
[ListBotAliasesResponse] -> ShowS
ListBotAliasesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListBotAliasesResponse] -> ShowS
$cshowList :: [ListBotAliasesResponse] -> ShowS
show :: ListBotAliasesResponse -> String
$cshow :: ListBotAliasesResponse -> String
showsPrec :: Int -> ListBotAliasesResponse -> ShowS
$cshowsPrec :: Int -> ListBotAliasesResponse -> ShowS
Prelude.Show, forall x. Rep ListBotAliasesResponse x -> ListBotAliasesResponse
forall x. ListBotAliasesResponse -> Rep ListBotAliasesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListBotAliasesResponse x -> ListBotAliasesResponse
$cfrom :: forall x. ListBotAliasesResponse -> Rep ListBotAliasesResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListBotAliasesResponse' 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:
--
-- 'botAliasSummaries', 'listBotAliasesResponse_botAliasSummaries' - Summary information for the bot aliases 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 aliases
-- available, the @nextToken@ field contains a token to get the next page
-- of results.
--
-- 'botId', 'listBotAliasesResponse_botId' - The identifier of the bot associated with the aliases.
--
-- 'nextToken', 'listBotAliasesResponse_nextToken' - A token that indicates whether there are more results to return in a
-- response to the @ListBotAliases@ 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', 'listBotAliasesResponse_httpStatus' - The response's http status code.
newListBotAliasesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListBotAliasesResponse
newListBotAliasesResponse :: Int -> ListBotAliasesResponse
newListBotAliasesResponse Int
pHttpStatus_ =
  ListBotAliasesResponse'
    { $sel:botAliasSummaries:ListBotAliasesResponse' :: Maybe [BotAliasSummary]
botAliasSummaries =
        forall a. Maybe a
Prelude.Nothing,
      $sel:botId:ListBotAliasesResponse' :: Maybe Text
botId = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListBotAliasesResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListBotAliasesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Summary information for the bot aliases 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 aliases
-- available, the @nextToken@ field contains a token to get the next page
-- of results.
listBotAliasesResponse_botAliasSummaries :: Lens.Lens' ListBotAliasesResponse (Prelude.Maybe [BotAliasSummary])
listBotAliasesResponse_botAliasSummaries :: Lens' ListBotAliasesResponse (Maybe [BotAliasSummary])
listBotAliasesResponse_botAliasSummaries = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListBotAliasesResponse' {Maybe [BotAliasSummary]
botAliasSummaries :: Maybe [BotAliasSummary]
$sel:botAliasSummaries:ListBotAliasesResponse' :: ListBotAliasesResponse -> Maybe [BotAliasSummary]
botAliasSummaries} -> Maybe [BotAliasSummary]
botAliasSummaries) (\s :: ListBotAliasesResponse
s@ListBotAliasesResponse' {} Maybe [BotAliasSummary]
a -> ListBotAliasesResponse
s {$sel:botAliasSummaries:ListBotAliasesResponse' :: Maybe [BotAliasSummary]
botAliasSummaries = Maybe [BotAliasSummary]
a} :: ListBotAliasesResponse) 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 identifier of the bot associated with the aliases.
listBotAliasesResponse_botId :: Lens.Lens' ListBotAliasesResponse (Prelude.Maybe Prelude.Text)
listBotAliasesResponse_botId :: Lens' ListBotAliasesResponse (Maybe Text)
listBotAliasesResponse_botId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListBotAliasesResponse' {Maybe Text
botId :: Maybe Text
$sel:botId:ListBotAliasesResponse' :: ListBotAliasesResponse -> Maybe Text
botId} -> Maybe Text
botId) (\s :: ListBotAliasesResponse
s@ListBotAliasesResponse' {} Maybe Text
a -> ListBotAliasesResponse
s {$sel:botId:ListBotAliasesResponse' :: Maybe Text
botId = Maybe Text
a} :: ListBotAliasesResponse)

-- | A token that indicates whether there are more results to return in a
-- response to the @ListBotAliases@ 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.
listBotAliasesResponse_nextToken :: Lens.Lens' ListBotAliasesResponse (Prelude.Maybe Prelude.Text)
listBotAliasesResponse_nextToken :: Lens' ListBotAliasesResponse (Maybe Text)
listBotAliasesResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListBotAliasesResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListBotAliasesResponse' :: ListBotAliasesResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListBotAliasesResponse
s@ListBotAliasesResponse' {} Maybe Text
a -> ListBotAliasesResponse
s {$sel:nextToken:ListBotAliasesResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListBotAliasesResponse)

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

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