{-# 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.DescribeComputeEnvironments
-- 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 compute environments.
--
-- If you\'re using an unmanaged compute environment, you can use the
-- @DescribeComputeEnvironment@ operation to determine the @ecsClusterArn@
-- that you launch your Amazon ECS container instances into.
--
-- This operation returns paginated results.
module Amazonka.Batch.DescribeComputeEnvironments
  ( -- * Creating a Request
    DescribeComputeEnvironments (..),
    newDescribeComputeEnvironments,

    -- * Request Lenses
    describeComputeEnvironments_computeEnvironments,
    describeComputeEnvironments_maxResults,
    describeComputeEnvironments_nextToken,

    -- * Destructuring the Response
    DescribeComputeEnvironmentsResponse (..),
    newDescribeComputeEnvironmentsResponse,

    -- * Response Lenses
    describeComputeEnvironmentsResponse_computeEnvironments,
    describeComputeEnvironmentsResponse_nextToken,
    describeComputeEnvironmentsResponse_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 @DescribeComputeEnvironments@.
--
-- /See:/ 'newDescribeComputeEnvironments' smart constructor.
data DescribeComputeEnvironments = DescribeComputeEnvironments'
  { -- | A list of up to 100 compute environment names or full Amazon Resource
    -- Name (ARN) entries.
    DescribeComputeEnvironments -> Maybe [Text]
computeEnvironments :: Prelude.Maybe [Prelude.Text],
    -- | The maximum number of cluster results returned by
    -- @DescribeComputeEnvironments@ in paginated output. When this parameter
    -- is used, @DescribeComputeEnvironments@ only returns @maxResults@ results
    -- in a single page along with a @nextToken@ response element. The
    -- remaining results of the initial request can be seen by sending another
    -- @DescribeComputeEnvironments@ request with the returned @nextToken@
    -- value. This value can be between 1 and 100. If this parameter isn\'t
    -- used, then @DescribeComputeEnvironments@ returns up to 100 results and a
    -- @nextToken@ value if applicable.
    DescribeComputeEnvironments -> Maybe Int
maxResults :: Prelude.Maybe Prelude.Int,
    -- | The @nextToken@ value returned from a previous paginated
    -- @DescribeComputeEnvironments@ 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.
    DescribeComputeEnvironments -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (DescribeComputeEnvironments -> DescribeComputeEnvironments -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeComputeEnvironments -> DescribeComputeEnvironments -> Bool
$c/= :: DescribeComputeEnvironments -> DescribeComputeEnvironments -> Bool
== :: DescribeComputeEnvironments -> DescribeComputeEnvironments -> Bool
$c== :: DescribeComputeEnvironments -> DescribeComputeEnvironments -> Bool
Prelude.Eq, ReadPrec [DescribeComputeEnvironments]
ReadPrec DescribeComputeEnvironments
Int -> ReadS DescribeComputeEnvironments
ReadS [DescribeComputeEnvironments]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeComputeEnvironments]
$creadListPrec :: ReadPrec [DescribeComputeEnvironments]
readPrec :: ReadPrec DescribeComputeEnvironments
$creadPrec :: ReadPrec DescribeComputeEnvironments
readList :: ReadS [DescribeComputeEnvironments]
$creadList :: ReadS [DescribeComputeEnvironments]
readsPrec :: Int -> ReadS DescribeComputeEnvironments
$creadsPrec :: Int -> ReadS DescribeComputeEnvironments
Prelude.Read, Int -> DescribeComputeEnvironments -> ShowS
[DescribeComputeEnvironments] -> ShowS
DescribeComputeEnvironments -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeComputeEnvironments] -> ShowS
$cshowList :: [DescribeComputeEnvironments] -> ShowS
show :: DescribeComputeEnvironments -> String
$cshow :: DescribeComputeEnvironments -> String
showsPrec :: Int -> DescribeComputeEnvironments -> ShowS
$cshowsPrec :: Int -> DescribeComputeEnvironments -> ShowS
Prelude.Show, forall x.
Rep DescribeComputeEnvironments x -> DescribeComputeEnvironments
forall x.
DescribeComputeEnvironments -> Rep DescribeComputeEnvironments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeComputeEnvironments x -> DescribeComputeEnvironments
$cfrom :: forall x.
DescribeComputeEnvironments -> Rep DescribeComputeEnvironments x
Prelude.Generic)

-- |
-- Create a value of 'DescribeComputeEnvironments' 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:
--
-- 'computeEnvironments', 'describeComputeEnvironments_computeEnvironments' - A list of up to 100 compute environment names or full Amazon Resource
-- Name (ARN) entries.
--
-- 'maxResults', 'describeComputeEnvironments_maxResults' - The maximum number of cluster results returned by
-- @DescribeComputeEnvironments@ in paginated output. When this parameter
-- is used, @DescribeComputeEnvironments@ only returns @maxResults@ results
-- in a single page along with a @nextToken@ response element. The
-- remaining results of the initial request can be seen by sending another
-- @DescribeComputeEnvironments@ request with the returned @nextToken@
-- value. This value can be between 1 and 100. If this parameter isn\'t
-- used, then @DescribeComputeEnvironments@ returns up to 100 results and a
-- @nextToken@ value if applicable.
--
-- 'nextToken', 'describeComputeEnvironments_nextToken' - The @nextToken@ value returned from a previous paginated
-- @DescribeComputeEnvironments@ 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.
newDescribeComputeEnvironments ::
  DescribeComputeEnvironments
newDescribeComputeEnvironments :: DescribeComputeEnvironments
newDescribeComputeEnvironments =
  DescribeComputeEnvironments'
    { $sel:computeEnvironments:DescribeComputeEnvironments' :: Maybe [Text]
computeEnvironments =
        forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:DescribeComputeEnvironments' :: Maybe Int
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:DescribeComputeEnvironments' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

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

-- | The @nextToken@ value returned from a previous paginated
-- @DescribeComputeEnvironments@ 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.
describeComputeEnvironments_nextToken :: Lens.Lens' DescribeComputeEnvironments (Prelude.Maybe Prelude.Text)
describeComputeEnvironments_nextToken :: Lens' DescribeComputeEnvironments (Maybe Text)
describeComputeEnvironments_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeComputeEnvironments' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeComputeEnvironments' :: DescribeComputeEnvironments -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeComputeEnvironments
s@DescribeComputeEnvironments' {} Maybe Text
a -> DescribeComputeEnvironments
s {$sel:nextToken:DescribeComputeEnvironments' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeComputeEnvironments)

instance Core.AWSPager DescribeComputeEnvironments where
  page :: DescribeComputeEnvironments
-> AWSResponse DescribeComputeEnvironments
-> Maybe DescribeComputeEnvironments
page DescribeComputeEnvironments
rq AWSResponse DescribeComputeEnvironments
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse DescribeComputeEnvironments
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeComputeEnvironmentsResponse (Maybe Text)
describeComputeEnvironmentsResponse_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 DescribeComputeEnvironments
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens'
  DescribeComputeEnvironmentsResponse
  (Maybe [ComputeEnvironmentDetail])
describeComputeEnvironmentsResponse_computeEnvironments
            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.$ DescribeComputeEnvironments
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' DescribeComputeEnvironments (Maybe Text)
describeComputeEnvironments_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse DescribeComputeEnvironments
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeComputeEnvironmentsResponse (Maybe Text)
describeComputeEnvironmentsResponse_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 DescribeComputeEnvironments where
  type
    AWSResponse DescribeComputeEnvironments =
      DescribeComputeEnvironmentsResponse
  request :: (Service -> Service)
-> DescribeComputeEnvironments
-> Request DescribeComputeEnvironments
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 DescribeComputeEnvironments
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeComputeEnvironments)))
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 [ComputeEnvironmentDetail]
-> Maybe Text -> Int -> DescribeComputeEnvironmentsResponse
DescribeComputeEnvironmentsResponse'
            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
"computeEnvironments"
                            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 DescribeComputeEnvironments where
  hashWithSalt :: Int -> DescribeComputeEnvironments -> Int
hashWithSalt Int
_salt DescribeComputeEnvironments' {Maybe Int
Maybe [Text]
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Int
computeEnvironments :: Maybe [Text]
$sel:nextToken:DescribeComputeEnvironments' :: DescribeComputeEnvironments -> Maybe Text
$sel:maxResults:DescribeComputeEnvironments' :: DescribeComputeEnvironments -> Maybe Int
$sel:computeEnvironments:DescribeComputeEnvironments' :: DescribeComputeEnvironments -> Maybe [Text]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
computeEnvironments
      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 DescribeComputeEnvironments where
  rnf :: DescribeComputeEnvironments -> ()
rnf DescribeComputeEnvironments' {Maybe Int
Maybe [Text]
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Int
computeEnvironments :: Maybe [Text]
$sel:nextToken:DescribeComputeEnvironments' :: DescribeComputeEnvironments -> Maybe Text
$sel:maxResults:DescribeComputeEnvironments' :: DescribeComputeEnvironments -> Maybe Int
$sel:computeEnvironments:DescribeComputeEnvironments' :: DescribeComputeEnvironments -> Maybe [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
computeEnvironments
      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 DescribeComputeEnvironments where
  toHeaders :: DescribeComputeEnvironments -> 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 DescribeComputeEnvironments where
  toJSON :: DescribeComputeEnvironments -> Value
toJSON DescribeComputeEnvironments' {Maybe Int
Maybe [Text]
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Int
computeEnvironments :: Maybe [Text]
$sel:nextToken:DescribeComputeEnvironments' :: DescribeComputeEnvironments -> Maybe Text
$sel:maxResults:DescribeComputeEnvironments' :: DescribeComputeEnvironments -> Maybe Int
$sel:computeEnvironments:DescribeComputeEnvironments' :: DescribeComputeEnvironments -> Maybe [Text]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"computeEnvironments" 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]
computeEnvironments,
            (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 DescribeComputeEnvironments where
  toPath :: DescribeComputeEnvironments -> ByteString
toPath =
    forall a b. a -> b -> a
Prelude.const ByteString
"/v1/describecomputeenvironments"

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

-- | /See:/ 'newDescribeComputeEnvironmentsResponse' smart constructor.
data DescribeComputeEnvironmentsResponse = DescribeComputeEnvironmentsResponse'
  { -- | The list of compute environments.
    DescribeComputeEnvironmentsResponse
-> Maybe [ComputeEnvironmentDetail]
computeEnvironments :: Prelude.Maybe [ComputeEnvironmentDetail],
    -- | The @nextToken@ value to include in a future
    -- @DescribeComputeEnvironments@ request. When the results of a
    -- @DescribeComputeEnvironments@ 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.
    DescribeComputeEnvironmentsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DescribeComputeEnvironmentsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeComputeEnvironmentsResponse
-> DescribeComputeEnvironmentsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeComputeEnvironmentsResponse
-> DescribeComputeEnvironmentsResponse -> Bool
$c/= :: DescribeComputeEnvironmentsResponse
-> DescribeComputeEnvironmentsResponse -> Bool
== :: DescribeComputeEnvironmentsResponse
-> DescribeComputeEnvironmentsResponse -> Bool
$c== :: DescribeComputeEnvironmentsResponse
-> DescribeComputeEnvironmentsResponse -> Bool
Prelude.Eq, ReadPrec [DescribeComputeEnvironmentsResponse]
ReadPrec DescribeComputeEnvironmentsResponse
Int -> ReadS DescribeComputeEnvironmentsResponse
ReadS [DescribeComputeEnvironmentsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeComputeEnvironmentsResponse]
$creadListPrec :: ReadPrec [DescribeComputeEnvironmentsResponse]
readPrec :: ReadPrec DescribeComputeEnvironmentsResponse
$creadPrec :: ReadPrec DescribeComputeEnvironmentsResponse
readList :: ReadS [DescribeComputeEnvironmentsResponse]
$creadList :: ReadS [DescribeComputeEnvironmentsResponse]
readsPrec :: Int -> ReadS DescribeComputeEnvironmentsResponse
$creadsPrec :: Int -> ReadS DescribeComputeEnvironmentsResponse
Prelude.Read, Int -> DescribeComputeEnvironmentsResponse -> ShowS
[DescribeComputeEnvironmentsResponse] -> ShowS
DescribeComputeEnvironmentsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeComputeEnvironmentsResponse] -> ShowS
$cshowList :: [DescribeComputeEnvironmentsResponse] -> ShowS
show :: DescribeComputeEnvironmentsResponse -> String
$cshow :: DescribeComputeEnvironmentsResponse -> String
showsPrec :: Int -> DescribeComputeEnvironmentsResponse -> ShowS
$cshowsPrec :: Int -> DescribeComputeEnvironmentsResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeComputeEnvironmentsResponse x
-> DescribeComputeEnvironmentsResponse
forall x.
DescribeComputeEnvironmentsResponse
-> Rep DescribeComputeEnvironmentsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeComputeEnvironmentsResponse x
-> DescribeComputeEnvironmentsResponse
$cfrom :: forall x.
DescribeComputeEnvironmentsResponse
-> Rep DescribeComputeEnvironmentsResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeComputeEnvironmentsResponse' 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:
--
-- 'computeEnvironments', 'describeComputeEnvironmentsResponse_computeEnvironments' - The list of compute environments.
--
-- 'nextToken', 'describeComputeEnvironmentsResponse_nextToken' - The @nextToken@ value to include in a future
-- @DescribeComputeEnvironments@ request. When the results of a
-- @DescribeComputeEnvironments@ 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', 'describeComputeEnvironmentsResponse_httpStatus' - The response's http status code.
newDescribeComputeEnvironmentsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeComputeEnvironmentsResponse
newDescribeComputeEnvironmentsResponse :: Int -> DescribeComputeEnvironmentsResponse
newDescribeComputeEnvironmentsResponse Int
pHttpStatus_ =
  DescribeComputeEnvironmentsResponse'
    { $sel:computeEnvironments:DescribeComputeEnvironmentsResponse' :: Maybe [ComputeEnvironmentDetail]
computeEnvironments =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:DescribeComputeEnvironmentsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeComputeEnvironmentsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The list of compute environments.
describeComputeEnvironmentsResponse_computeEnvironments :: Lens.Lens' DescribeComputeEnvironmentsResponse (Prelude.Maybe [ComputeEnvironmentDetail])
describeComputeEnvironmentsResponse_computeEnvironments :: Lens'
  DescribeComputeEnvironmentsResponse
  (Maybe [ComputeEnvironmentDetail])
describeComputeEnvironmentsResponse_computeEnvironments = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeComputeEnvironmentsResponse' {Maybe [ComputeEnvironmentDetail]
computeEnvironments :: Maybe [ComputeEnvironmentDetail]
$sel:computeEnvironments:DescribeComputeEnvironmentsResponse' :: DescribeComputeEnvironmentsResponse
-> Maybe [ComputeEnvironmentDetail]
computeEnvironments} -> Maybe [ComputeEnvironmentDetail]
computeEnvironments) (\s :: DescribeComputeEnvironmentsResponse
s@DescribeComputeEnvironmentsResponse' {} Maybe [ComputeEnvironmentDetail]
a -> DescribeComputeEnvironmentsResponse
s {$sel:computeEnvironments:DescribeComputeEnvironmentsResponse' :: Maybe [ComputeEnvironmentDetail]
computeEnvironments = Maybe [ComputeEnvironmentDetail]
a} :: DescribeComputeEnvironmentsResponse) 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
-- @DescribeComputeEnvironments@ request. When the results of a
-- @DescribeComputeEnvironments@ 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.
describeComputeEnvironmentsResponse_nextToken :: Lens.Lens' DescribeComputeEnvironmentsResponse (Prelude.Maybe Prelude.Text)
describeComputeEnvironmentsResponse_nextToken :: Lens' DescribeComputeEnvironmentsResponse (Maybe Text)
describeComputeEnvironmentsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeComputeEnvironmentsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeComputeEnvironmentsResponse' :: DescribeComputeEnvironmentsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeComputeEnvironmentsResponse
s@DescribeComputeEnvironmentsResponse' {} Maybe Text
a -> DescribeComputeEnvironmentsResponse
s {$sel:nextToken:DescribeComputeEnvironmentsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeComputeEnvironmentsResponse)

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

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