{-# 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.SQS.ListQueues
-- 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 a list of your queues in the current region. The response
-- includes a maximum of 1,000 results. If you specify a value for the
-- optional @QueueNamePrefix@ parameter, only queues with a name that
-- begins with the specified value are returned.
--
-- The @listQueues@ methods supports pagination. Set parameter @MaxResults@
-- in the request to specify the maximum number of results to be returned
-- in the response. If you do not set @MaxResults@, the response includes a
-- maximum of 1,000 results. If you set @MaxResults@ and there are
-- additional results to display, the response includes a value for
-- @NextToken@. Use @NextToken@ as a parameter in your next request to
-- @listQueues@ to receive the next page of results.
--
-- Cross-account permissions don\'t apply to this action. For more
-- information, see
-- <https://docs.aws.amazon.com/AWSSimpleQueueService/latest/SQSDeveloperGuide/sqs-customer-managed-policy-examples.html#grant-cross-account-permissions-to-role-and-user-name Grant cross-account permissions to a role and a user name>
-- in the /Amazon SQS Developer Guide/.
--
-- This operation returns paginated results.
module Amazonka.SQS.ListQueues
  ( -- * Creating a Request
    ListQueues (..),
    newListQueues,

    -- * Request Lenses
    listQueues_maxResults,
    listQueues_nextToken,
    listQueues_queueNamePrefix,

    -- * Destructuring the Response
    ListQueuesResponse (..),
    newListQueuesResponse,

    -- * Response Lenses
    listQueuesResponse_nextToken,
    listQueuesResponse_queueUrls,
    listQueuesResponse_httpStatus,
  )
where

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
import Amazonka.SQS.Types

-- |
--
-- /See:/ 'newListQueues' smart constructor.
data ListQueues = ListQueues'
  { -- | Maximum number of results to include in the response. Value range is 1
    -- to 1000. You must set @MaxResults@ to receive a value for @NextToken@ in
    -- the response.
    ListQueues -> Maybe Int
maxResults :: Prelude.Maybe Prelude.Int,
    -- | Pagination token to request the next set of results.
    ListQueues -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | A string to use for filtering the list results. Only those queues whose
    -- name begins with the specified string are returned.
    --
    -- Queue URLs and names are case-sensitive.
    ListQueues -> Maybe Text
queueNamePrefix :: Prelude.Maybe Prelude.Text
  }
  deriving (ListQueues -> ListQueues -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListQueues -> ListQueues -> Bool
$c/= :: ListQueues -> ListQueues -> Bool
== :: ListQueues -> ListQueues -> Bool
$c== :: ListQueues -> ListQueues -> Bool
Prelude.Eq, ReadPrec [ListQueues]
ReadPrec ListQueues
Int -> ReadS ListQueues
ReadS [ListQueues]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListQueues]
$creadListPrec :: ReadPrec [ListQueues]
readPrec :: ReadPrec ListQueues
$creadPrec :: ReadPrec ListQueues
readList :: ReadS [ListQueues]
$creadList :: ReadS [ListQueues]
readsPrec :: Int -> ReadS ListQueues
$creadsPrec :: Int -> ReadS ListQueues
Prelude.Read, Int -> ListQueues -> ShowS
[ListQueues] -> ShowS
ListQueues -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListQueues] -> ShowS
$cshowList :: [ListQueues] -> ShowS
show :: ListQueues -> String
$cshow :: ListQueues -> String
showsPrec :: Int -> ListQueues -> ShowS
$cshowsPrec :: Int -> ListQueues -> ShowS
Prelude.Show, forall x. Rep ListQueues x -> ListQueues
forall x. ListQueues -> Rep ListQueues x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListQueues x -> ListQueues
$cfrom :: forall x. ListQueues -> Rep ListQueues x
Prelude.Generic)

-- |
-- Create a value of 'ListQueues' 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', 'listQueues_maxResults' - Maximum number of results to include in the response. Value range is 1
-- to 1000. You must set @MaxResults@ to receive a value for @NextToken@ in
-- the response.
--
-- 'nextToken', 'listQueues_nextToken' - Pagination token to request the next set of results.
--
-- 'queueNamePrefix', 'listQueues_queueNamePrefix' - A string to use for filtering the list results. Only those queues whose
-- name begins with the specified string are returned.
--
-- Queue URLs and names are case-sensitive.
newListQueues ::
  ListQueues
newListQueues :: ListQueues
newListQueues =
  ListQueues'
    { $sel:maxResults:ListQueues' :: Maybe Int
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListQueues' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:queueNamePrefix:ListQueues' :: Maybe Text
queueNamePrefix = forall a. Maybe a
Prelude.Nothing
    }

-- | Maximum number of results to include in the response. Value range is 1
-- to 1000. You must set @MaxResults@ to receive a value for @NextToken@ in
-- the response.
listQueues_maxResults :: Lens.Lens' ListQueues (Prelude.Maybe Prelude.Int)
listQueues_maxResults :: Lens' ListQueues (Maybe Int)
listQueues_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListQueues' {Maybe Int
maxResults :: Maybe Int
$sel:maxResults:ListQueues' :: ListQueues -> Maybe Int
maxResults} -> Maybe Int
maxResults) (\s :: ListQueues
s@ListQueues' {} Maybe Int
a -> ListQueues
s {$sel:maxResults:ListQueues' :: Maybe Int
maxResults = Maybe Int
a} :: ListQueues)

-- | Pagination token to request the next set of results.
listQueues_nextToken :: Lens.Lens' ListQueues (Prelude.Maybe Prelude.Text)
listQueues_nextToken :: Lens' ListQueues (Maybe Text)
listQueues_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListQueues' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListQueues' :: ListQueues -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListQueues
s@ListQueues' {} Maybe Text
a -> ListQueues
s {$sel:nextToken:ListQueues' :: Maybe Text
nextToken = Maybe Text
a} :: ListQueues)

-- | A string to use for filtering the list results. Only those queues whose
-- name begins with the specified string are returned.
--
-- Queue URLs and names are case-sensitive.
listQueues_queueNamePrefix :: Lens.Lens' ListQueues (Prelude.Maybe Prelude.Text)
listQueues_queueNamePrefix :: Lens' ListQueues (Maybe Text)
listQueues_queueNamePrefix = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListQueues' {Maybe Text
queueNamePrefix :: Maybe Text
$sel:queueNamePrefix:ListQueues' :: ListQueues -> Maybe Text
queueNamePrefix} -> Maybe Text
queueNamePrefix) (\s :: ListQueues
s@ListQueues' {} Maybe Text
a -> ListQueues
s {$sel:queueNamePrefix:ListQueues' :: Maybe Text
queueNamePrefix = Maybe Text
a} :: ListQueues)

instance Core.AWSPager ListQueues where
  page :: ListQueues -> AWSResponse ListQueues -> Maybe ListQueues
page ListQueues
rq AWSResponse ListQueues
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListQueues
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListQueuesResponse (Maybe Text)
listQueuesResponse_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 ListQueues
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListQueuesResponse (Maybe [Text])
listQueuesResponse_queueUrls
            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.$ ListQueues
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListQueues (Maybe Text)
listQueues_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListQueues
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListQueuesResponse (Maybe Text)
listQueuesResponse_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 ListQueues where
  type AWSResponse ListQueues = ListQueuesResponse
  request :: (Service -> Service) -> ListQueues -> Request ListQueues
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ListQueues
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListQueues)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"ListQueuesResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Text -> Maybe [Text] -> Int -> ListQueuesResponse
ListQueuesResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"NextToken")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"QueueUrl") [Node]
x)
            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 ListQueues where
  hashWithSalt :: Int -> ListQueues -> Int
hashWithSalt Int
_salt ListQueues' {Maybe Int
Maybe Text
queueNamePrefix :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Int
$sel:queueNamePrefix:ListQueues' :: ListQueues -> Maybe Text
$sel:nextToken:ListQueues' :: ListQueues -> Maybe Text
$sel:maxResults:ListQueues' :: ListQueues -> Maybe Int
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
queueNamePrefix

instance Prelude.NFData ListQueues where
  rnf :: ListQueues -> ()
rnf ListQueues' {Maybe Int
Maybe Text
queueNamePrefix :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Int
$sel:queueNamePrefix:ListQueues' :: ListQueues -> Maybe Text
$sel:nextToken:ListQueues' :: ListQueues -> Maybe Text
$sel:maxResults:ListQueues' :: ListQueues -> Maybe Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
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 Text
queueNamePrefix

instance Data.ToHeaders ListQueues where
  toHeaders :: ListQueues -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToPath ListQueues where
  toPath :: ListQueues -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

instance Data.ToQuery ListQueues where
  toQuery :: ListQueues -> QueryString
toQuery ListQueues' {Maybe Int
Maybe Text
queueNamePrefix :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Int
$sel:queueNamePrefix:ListQueues' :: ListQueues -> Maybe Text
$sel:nextToken:ListQueues' :: ListQueues -> Maybe Text
$sel:maxResults:ListQueues' :: ListQueues -> Maybe Int
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"ListQueues" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2012-11-05" :: Prelude.ByteString),
        ByteString
"MaxResults" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
maxResults,
        ByteString
"NextToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken,
        ByteString
"QueueNamePrefix" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
queueNamePrefix
      ]

-- | A list of your queues.
--
-- /See:/ 'newListQueuesResponse' smart constructor.
data ListQueuesResponse = ListQueuesResponse'
  { -- | Pagination token to include in the next request. Token value is @null@
    -- if there are no additional results to request, or if you did not set
    -- @MaxResults@ in the request.
    ListQueuesResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | A list of queue URLs, up to 1,000 entries, or the value of MaxResults
    -- that you sent in the request.
    ListQueuesResponse -> Maybe [Text]
queueUrls :: Prelude.Maybe [Prelude.Text],
    -- | The response's http status code.
    ListQueuesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListQueuesResponse -> ListQueuesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListQueuesResponse -> ListQueuesResponse -> Bool
$c/= :: ListQueuesResponse -> ListQueuesResponse -> Bool
== :: ListQueuesResponse -> ListQueuesResponse -> Bool
$c== :: ListQueuesResponse -> ListQueuesResponse -> Bool
Prelude.Eq, ReadPrec [ListQueuesResponse]
ReadPrec ListQueuesResponse
Int -> ReadS ListQueuesResponse
ReadS [ListQueuesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListQueuesResponse]
$creadListPrec :: ReadPrec [ListQueuesResponse]
readPrec :: ReadPrec ListQueuesResponse
$creadPrec :: ReadPrec ListQueuesResponse
readList :: ReadS [ListQueuesResponse]
$creadList :: ReadS [ListQueuesResponse]
readsPrec :: Int -> ReadS ListQueuesResponse
$creadsPrec :: Int -> ReadS ListQueuesResponse
Prelude.Read, Int -> ListQueuesResponse -> ShowS
[ListQueuesResponse] -> ShowS
ListQueuesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListQueuesResponse] -> ShowS
$cshowList :: [ListQueuesResponse] -> ShowS
show :: ListQueuesResponse -> String
$cshow :: ListQueuesResponse -> String
showsPrec :: Int -> ListQueuesResponse -> ShowS
$cshowsPrec :: Int -> ListQueuesResponse -> ShowS
Prelude.Show, forall x. Rep ListQueuesResponse x -> ListQueuesResponse
forall x. ListQueuesResponse -> Rep ListQueuesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListQueuesResponse x -> ListQueuesResponse
$cfrom :: forall x. ListQueuesResponse -> Rep ListQueuesResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListQueuesResponse' 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', 'listQueuesResponse_nextToken' - Pagination token to include in the next request. Token value is @null@
-- if there are no additional results to request, or if you did not set
-- @MaxResults@ in the request.
--
-- 'queueUrls', 'listQueuesResponse_queueUrls' - A list of queue URLs, up to 1,000 entries, or the value of MaxResults
-- that you sent in the request.
--
-- 'httpStatus', 'listQueuesResponse_httpStatus' - The response's http status code.
newListQueuesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListQueuesResponse
newListQueuesResponse :: Int -> ListQueuesResponse
newListQueuesResponse Int
pHttpStatus_ =
  ListQueuesResponse'
    { $sel:nextToken:ListQueuesResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:queueUrls:ListQueuesResponse' :: Maybe [Text]
queueUrls = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListQueuesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Pagination token to include in the next request. Token value is @null@
-- if there are no additional results to request, or if you did not set
-- @MaxResults@ in the request.
listQueuesResponse_nextToken :: Lens.Lens' ListQueuesResponse (Prelude.Maybe Prelude.Text)
listQueuesResponse_nextToken :: Lens' ListQueuesResponse (Maybe Text)
listQueuesResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListQueuesResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListQueuesResponse' :: ListQueuesResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListQueuesResponse
s@ListQueuesResponse' {} Maybe Text
a -> ListQueuesResponse
s {$sel:nextToken:ListQueuesResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListQueuesResponse)

-- | A list of queue URLs, up to 1,000 entries, or the value of MaxResults
-- that you sent in the request.
listQueuesResponse_queueUrls :: Lens.Lens' ListQueuesResponse (Prelude.Maybe [Prelude.Text])
listQueuesResponse_queueUrls :: Lens' ListQueuesResponse (Maybe [Text])
listQueuesResponse_queueUrls = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListQueuesResponse' {Maybe [Text]
queueUrls :: Maybe [Text]
$sel:queueUrls:ListQueuesResponse' :: ListQueuesResponse -> Maybe [Text]
queueUrls} -> Maybe [Text]
queueUrls) (\s :: ListQueuesResponse
s@ListQueuesResponse' {} Maybe [Text]
a -> ListQueuesResponse
s {$sel:queueUrls:ListQueuesResponse' :: Maybe [Text]
queueUrls = Maybe [Text]
a} :: ListQueuesResponse) 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.
listQueuesResponse_httpStatus :: Lens.Lens' ListQueuesResponse Prelude.Int
listQueuesResponse_httpStatus :: Lens' ListQueuesResponse Int
listQueuesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListQueuesResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListQueuesResponse' :: ListQueuesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListQueuesResponse
s@ListQueuesResponse' {} Int
a -> ListQueuesResponse
s {$sel:httpStatus:ListQueuesResponse' :: Int
httpStatus = Int
a} :: ListQueuesResponse)

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