{-# 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.Batch.DescribeJobQueues
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Describes one or more of your job queues.
--
-- This operation returns paginated results.
module Amazonka.Batch.DescribeJobQueues
  ( -- * Creating a Request
    DescribeJobQueues (..),
    newDescribeJobQueues,

    -- * Request Lenses
    describeJobQueues_jobQueues,
    describeJobQueues_maxResults,
    describeJobQueues_nextToken,

    -- * Destructuring the Response
    DescribeJobQueuesResponse (..),
    newDescribeJobQueuesResponse,

    -- * Response Lenses
    describeJobQueuesResponse_jobQueues,
    describeJobQueuesResponse_nextToken,
    describeJobQueuesResponse_httpStatus,
  )
where

import Amazonka.Batch.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

-- | Contains the parameters for @DescribeJobQueues@.
--
-- /See:/ 'newDescribeJobQueues' smart constructor.
data DescribeJobQueues = DescribeJobQueues'
  { -- | A list of up to 100 queue names or full queue Amazon Resource Name (ARN)
    -- entries.
    DescribeJobQueues -> Maybe [Text]
jobQueues :: Prelude.Maybe [Prelude.Text],
    -- | The maximum number of results returned by @DescribeJobQueues@ in
    -- paginated output. When this parameter is used, @DescribeJobQueues@ only
    -- returns @maxResults@ results in a single page and a @nextToken@ response
    -- element. The remaining results of the initial request can be seen by
    -- sending another @DescribeJobQueues@ request with the returned
    -- @nextToken@ value. This value can be between 1 and 100. If this
    -- parameter isn\'t used, then @DescribeJobQueues@ returns up to 100
    -- results and a @nextToken@ value if applicable.
    DescribeJobQueues -> Maybe Int
maxResults :: Prelude.Maybe Prelude.Int,
    -- | The @nextToken@ value returned from a previous paginated
    -- @DescribeJobQueues@ request where @maxResults@ was used and the results
    -- exceeded the value of that parameter. Pagination continues from the end
    -- of the previous results that returned the @nextToken@ value. This value
    -- is @null@ when there are no more results to return.
    --
    -- Treat this token as an opaque identifier that\'s only used to retrieve
    -- the next items in a list and not for other programmatic purposes.
    DescribeJobQueues -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (DescribeJobQueues -> DescribeJobQueues -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeJobQueues -> DescribeJobQueues -> Bool
$c/= :: DescribeJobQueues -> DescribeJobQueues -> Bool
== :: DescribeJobQueues -> DescribeJobQueues -> Bool
$c== :: DescribeJobQueues -> DescribeJobQueues -> Bool
Prelude.Eq, ReadPrec [DescribeJobQueues]
ReadPrec DescribeJobQueues
Int -> ReadS DescribeJobQueues
ReadS [DescribeJobQueues]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeJobQueues]
$creadListPrec :: ReadPrec [DescribeJobQueues]
readPrec :: ReadPrec DescribeJobQueues
$creadPrec :: ReadPrec DescribeJobQueues
readList :: ReadS [DescribeJobQueues]
$creadList :: ReadS [DescribeJobQueues]
readsPrec :: Int -> ReadS DescribeJobQueues
$creadsPrec :: Int -> ReadS DescribeJobQueues
Prelude.Read, Int -> DescribeJobQueues -> ShowS
[DescribeJobQueues] -> ShowS
DescribeJobQueues -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeJobQueues] -> ShowS
$cshowList :: [DescribeJobQueues] -> ShowS
show :: DescribeJobQueues -> String
$cshow :: DescribeJobQueues -> String
showsPrec :: Int -> DescribeJobQueues -> ShowS
$cshowsPrec :: Int -> DescribeJobQueues -> ShowS
Prelude.Show, forall x. Rep DescribeJobQueues x -> DescribeJobQueues
forall x. DescribeJobQueues -> Rep DescribeJobQueues x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeJobQueues x -> DescribeJobQueues
$cfrom :: forall x. DescribeJobQueues -> Rep DescribeJobQueues x
Prelude.Generic)

-- |
-- Create a value of 'DescribeJobQueues' 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:
--
-- 'jobQueues', 'describeJobQueues_jobQueues' - A list of up to 100 queue names or full queue Amazon Resource Name (ARN)
-- entries.
--
-- 'maxResults', 'describeJobQueues_maxResults' - The maximum number of results returned by @DescribeJobQueues@ in
-- paginated output. When this parameter is used, @DescribeJobQueues@ only
-- returns @maxResults@ results in a single page and a @nextToken@ response
-- element. The remaining results of the initial request can be seen by
-- sending another @DescribeJobQueues@ request with the returned
-- @nextToken@ value. This value can be between 1 and 100. If this
-- parameter isn\'t used, then @DescribeJobQueues@ returns up to 100
-- results and a @nextToken@ value if applicable.
--
-- 'nextToken', 'describeJobQueues_nextToken' - The @nextToken@ value returned from a previous paginated
-- @DescribeJobQueues@ request where @maxResults@ was used and the results
-- exceeded the value of that parameter. Pagination continues from the end
-- of the previous results that returned the @nextToken@ value. This value
-- is @null@ when there are no more results to return.
--
-- Treat this token as an opaque identifier that\'s only used to retrieve
-- the next items in a list and not for other programmatic purposes.
newDescribeJobQueues ::
  DescribeJobQueues
newDescribeJobQueues :: DescribeJobQueues
newDescribeJobQueues =
  DescribeJobQueues'
    { $sel:jobQueues:DescribeJobQueues' :: Maybe [Text]
jobQueues = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:DescribeJobQueues' :: Maybe Int
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:DescribeJobQueues' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | A list of up to 100 queue names or full queue Amazon Resource Name (ARN)
-- entries.
describeJobQueues_jobQueues :: Lens.Lens' DescribeJobQueues (Prelude.Maybe [Prelude.Text])
describeJobQueues_jobQueues :: Lens' DescribeJobQueues (Maybe [Text])
describeJobQueues_jobQueues = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeJobQueues' {Maybe [Text]
jobQueues :: Maybe [Text]
$sel:jobQueues:DescribeJobQueues' :: DescribeJobQueues -> Maybe [Text]
jobQueues} -> Maybe [Text]
jobQueues) (\s :: DescribeJobQueues
s@DescribeJobQueues' {} Maybe [Text]
a -> DescribeJobQueues
s {$sel:jobQueues:DescribeJobQueues' :: Maybe [Text]
jobQueues = Maybe [Text]
a} :: DescribeJobQueues) 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 maximum number of results returned by @DescribeJobQueues@ in
-- paginated output. When this parameter is used, @DescribeJobQueues@ only
-- returns @maxResults@ results in a single page and a @nextToken@ response
-- element. The remaining results of the initial request can be seen by
-- sending another @DescribeJobQueues@ request with the returned
-- @nextToken@ value. This value can be between 1 and 100. If this
-- parameter isn\'t used, then @DescribeJobQueues@ returns up to 100
-- results and a @nextToken@ value if applicable.
describeJobQueues_maxResults :: Lens.Lens' DescribeJobQueues (Prelude.Maybe Prelude.Int)
describeJobQueues_maxResults :: Lens' DescribeJobQueues (Maybe Int)
describeJobQueues_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeJobQueues' {Maybe Int
maxResults :: Maybe Int
$sel:maxResults:DescribeJobQueues' :: DescribeJobQueues -> Maybe Int
maxResults} -> Maybe Int
maxResults) (\s :: DescribeJobQueues
s@DescribeJobQueues' {} Maybe Int
a -> DescribeJobQueues
s {$sel:maxResults:DescribeJobQueues' :: Maybe Int
maxResults = Maybe Int
a} :: DescribeJobQueues)

-- | The @nextToken@ value returned from a previous paginated
-- @DescribeJobQueues@ request where @maxResults@ was used and the results
-- exceeded the value of that parameter. Pagination continues from the end
-- of the previous results that returned the @nextToken@ value. This value
-- is @null@ when there are no more results to return.
--
-- Treat this token as an opaque identifier that\'s only used to retrieve
-- the next items in a list and not for other programmatic purposes.
describeJobQueues_nextToken :: Lens.Lens' DescribeJobQueues (Prelude.Maybe Prelude.Text)
describeJobQueues_nextToken :: Lens' DescribeJobQueues (Maybe Text)
describeJobQueues_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeJobQueues' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeJobQueues' :: DescribeJobQueues -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeJobQueues
s@DescribeJobQueues' {} Maybe Text
a -> DescribeJobQueues
s {$sel:nextToken:DescribeJobQueues' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeJobQueues)

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

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

instance Data.ToHeaders DescribeJobQueues where
  toHeaders :: DescribeJobQueues -> 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 DescribeJobQueues where
  toJSON :: DescribeJobQueues -> Value
toJSON DescribeJobQueues' {Maybe Int
Maybe [Text]
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Int
jobQueues :: Maybe [Text]
$sel:nextToken:DescribeJobQueues' :: DescribeJobQueues -> Maybe Text
$sel:maxResults:DescribeJobQueues' :: DescribeJobQueues -> Maybe Int
$sel:jobQueues:DescribeJobQueues' :: DescribeJobQueues -> Maybe [Text]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"jobQueues" 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]
jobQueues,
            (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 Int
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 DescribeJobQueues where
  toPath :: DescribeJobQueues -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/v1/describejobqueues"

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

-- | /See:/ 'newDescribeJobQueuesResponse' smart constructor.
data DescribeJobQueuesResponse = DescribeJobQueuesResponse'
  { -- | The list of job queues.
    DescribeJobQueuesResponse -> Maybe [JobQueueDetail]
jobQueues :: Prelude.Maybe [JobQueueDetail],
    -- | The @nextToken@ value to include in a future @DescribeJobQueues@
    -- request. When the results of a @DescribeJobQueues@ request exceed
    -- @maxResults@, this value can be used to retrieve the next page of
    -- results. This value is @null@ when there are no more results to return.
    DescribeJobQueuesResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DescribeJobQueuesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeJobQueuesResponse -> DescribeJobQueuesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeJobQueuesResponse -> DescribeJobQueuesResponse -> Bool
$c/= :: DescribeJobQueuesResponse -> DescribeJobQueuesResponse -> Bool
== :: DescribeJobQueuesResponse -> DescribeJobQueuesResponse -> Bool
$c== :: DescribeJobQueuesResponse -> DescribeJobQueuesResponse -> Bool
Prelude.Eq, ReadPrec [DescribeJobQueuesResponse]
ReadPrec DescribeJobQueuesResponse
Int -> ReadS DescribeJobQueuesResponse
ReadS [DescribeJobQueuesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeJobQueuesResponse]
$creadListPrec :: ReadPrec [DescribeJobQueuesResponse]
readPrec :: ReadPrec DescribeJobQueuesResponse
$creadPrec :: ReadPrec DescribeJobQueuesResponse
readList :: ReadS [DescribeJobQueuesResponse]
$creadList :: ReadS [DescribeJobQueuesResponse]
readsPrec :: Int -> ReadS DescribeJobQueuesResponse
$creadsPrec :: Int -> ReadS DescribeJobQueuesResponse
Prelude.Read, Int -> DescribeJobQueuesResponse -> ShowS
[DescribeJobQueuesResponse] -> ShowS
DescribeJobQueuesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeJobQueuesResponse] -> ShowS
$cshowList :: [DescribeJobQueuesResponse] -> ShowS
show :: DescribeJobQueuesResponse -> String
$cshow :: DescribeJobQueuesResponse -> String
showsPrec :: Int -> DescribeJobQueuesResponse -> ShowS
$cshowsPrec :: Int -> DescribeJobQueuesResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeJobQueuesResponse x -> DescribeJobQueuesResponse
forall x.
DescribeJobQueuesResponse -> Rep DescribeJobQueuesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeJobQueuesResponse x -> DescribeJobQueuesResponse
$cfrom :: forall x.
DescribeJobQueuesResponse -> Rep DescribeJobQueuesResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeJobQueuesResponse' 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:
--
-- 'jobQueues', 'describeJobQueuesResponse_jobQueues' - The list of job queues.
--
-- 'nextToken', 'describeJobQueuesResponse_nextToken' - The @nextToken@ value to include in a future @DescribeJobQueues@
-- request. When the results of a @DescribeJobQueues@ request exceed
-- @maxResults@, this value can be used to retrieve the next page of
-- results. This value is @null@ when there are no more results to return.
--
-- 'httpStatus', 'describeJobQueuesResponse_httpStatus' - The response's http status code.
newDescribeJobQueuesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeJobQueuesResponse
newDescribeJobQueuesResponse :: Int -> DescribeJobQueuesResponse
newDescribeJobQueuesResponse Int
pHttpStatus_ =
  DescribeJobQueuesResponse'
    { $sel:jobQueues:DescribeJobQueuesResponse' :: Maybe [JobQueueDetail]
jobQueues =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:DescribeJobQueuesResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeJobQueuesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The list of job queues.
describeJobQueuesResponse_jobQueues :: Lens.Lens' DescribeJobQueuesResponse (Prelude.Maybe [JobQueueDetail])
describeJobQueuesResponse_jobQueues :: Lens' DescribeJobQueuesResponse (Maybe [JobQueueDetail])
describeJobQueuesResponse_jobQueues = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeJobQueuesResponse' {Maybe [JobQueueDetail]
jobQueues :: Maybe [JobQueueDetail]
$sel:jobQueues:DescribeJobQueuesResponse' :: DescribeJobQueuesResponse -> Maybe [JobQueueDetail]
jobQueues} -> Maybe [JobQueueDetail]
jobQueues) (\s :: DescribeJobQueuesResponse
s@DescribeJobQueuesResponse' {} Maybe [JobQueueDetail]
a -> DescribeJobQueuesResponse
s {$sel:jobQueues:DescribeJobQueuesResponse' :: Maybe [JobQueueDetail]
jobQueues = Maybe [JobQueueDetail]
a} :: DescribeJobQueuesResponse) 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 @nextToken@ value to include in a future @DescribeJobQueues@
-- request. When the results of a @DescribeJobQueues@ request exceed
-- @maxResults@, this value can be used to retrieve the next page of
-- results. This value is @null@ when there are no more results to return.
describeJobQueuesResponse_nextToken :: Lens.Lens' DescribeJobQueuesResponse (Prelude.Maybe Prelude.Text)
describeJobQueuesResponse_nextToken :: Lens' DescribeJobQueuesResponse (Maybe Text)
describeJobQueuesResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeJobQueuesResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeJobQueuesResponse' :: DescribeJobQueuesResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeJobQueuesResponse
s@DescribeJobQueuesResponse' {} Maybe Text
a -> DescribeJobQueuesResponse
s {$sel:nextToken:DescribeJobQueuesResponse' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeJobQueuesResponse)

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

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