{-# 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.ECS.DescribeClusters
-- 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 clusters.
module Amazonka.ECS.DescribeClusters
  ( -- * Creating a Request
    DescribeClusters (..),
    newDescribeClusters,

    -- * Request Lenses
    describeClusters_clusters,
    describeClusters_include,

    -- * Destructuring the Response
    DescribeClustersResponse (..),
    newDescribeClustersResponse,

    -- * Response Lenses
    describeClustersResponse_clusters,
    describeClustersResponse_failures,
    describeClustersResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.ECS.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newDescribeClusters' smart constructor.
data DescribeClusters = DescribeClusters'
  { -- | A list of up to 100 cluster names or full cluster Amazon Resource Name
    -- (ARN) entries. If you do not specify a cluster, the default cluster is
    -- assumed.
    DescribeClusters -> Maybe [Text]
clusters :: Prelude.Maybe [Prelude.Text],
    -- | Determines whether to include additional information about the clusters
    -- in the response. If this field is omitted, this information isn\'t
    -- included.
    --
    -- If @ATTACHMENTS@ is specified, the attachments for the container
    -- instances or tasks within the cluster are included, for example the
    -- capacity providers.
    --
    -- If @SETTINGS@ is specified, the settings for the cluster are included.
    --
    -- If @CONFIGURATIONS@ is specified, the configuration for the cluster is
    -- included.
    --
    -- If @STATISTICS@ is specified, the task and service count is included,
    -- separated by launch type.
    --
    -- If @TAGS@ is specified, the metadata tags associated with the cluster
    -- are included.
    DescribeClusters -> Maybe [ClusterField]
include :: Prelude.Maybe [ClusterField]
  }
  deriving (DescribeClusters -> DescribeClusters -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeClusters -> DescribeClusters -> Bool
$c/= :: DescribeClusters -> DescribeClusters -> Bool
== :: DescribeClusters -> DescribeClusters -> Bool
$c== :: DescribeClusters -> DescribeClusters -> Bool
Prelude.Eq, ReadPrec [DescribeClusters]
ReadPrec DescribeClusters
Int -> ReadS DescribeClusters
ReadS [DescribeClusters]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeClusters]
$creadListPrec :: ReadPrec [DescribeClusters]
readPrec :: ReadPrec DescribeClusters
$creadPrec :: ReadPrec DescribeClusters
readList :: ReadS [DescribeClusters]
$creadList :: ReadS [DescribeClusters]
readsPrec :: Int -> ReadS DescribeClusters
$creadsPrec :: Int -> ReadS DescribeClusters
Prelude.Read, Int -> DescribeClusters -> ShowS
[DescribeClusters] -> ShowS
DescribeClusters -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeClusters] -> ShowS
$cshowList :: [DescribeClusters] -> ShowS
show :: DescribeClusters -> String
$cshow :: DescribeClusters -> String
showsPrec :: Int -> DescribeClusters -> ShowS
$cshowsPrec :: Int -> DescribeClusters -> ShowS
Prelude.Show, forall x. Rep DescribeClusters x -> DescribeClusters
forall x. DescribeClusters -> Rep DescribeClusters x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeClusters x -> DescribeClusters
$cfrom :: forall x. DescribeClusters -> Rep DescribeClusters x
Prelude.Generic)

-- |
-- Create a value of 'DescribeClusters' 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:
--
-- 'clusters', 'describeClusters_clusters' - A list of up to 100 cluster names or full cluster Amazon Resource Name
-- (ARN) entries. If you do not specify a cluster, the default cluster is
-- assumed.
--
-- 'include', 'describeClusters_include' - Determines whether to include additional information about the clusters
-- in the response. If this field is omitted, this information isn\'t
-- included.
--
-- If @ATTACHMENTS@ is specified, the attachments for the container
-- instances or tasks within the cluster are included, for example the
-- capacity providers.
--
-- If @SETTINGS@ is specified, the settings for the cluster are included.
--
-- If @CONFIGURATIONS@ is specified, the configuration for the cluster is
-- included.
--
-- If @STATISTICS@ is specified, the task and service count is included,
-- separated by launch type.
--
-- If @TAGS@ is specified, the metadata tags associated with the cluster
-- are included.
newDescribeClusters ::
  DescribeClusters
newDescribeClusters :: DescribeClusters
newDescribeClusters =
  DescribeClusters'
    { $sel:clusters:DescribeClusters' :: Maybe [Text]
clusters = forall a. Maybe a
Prelude.Nothing,
      $sel:include:DescribeClusters' :: Maybe [ClusterField]
include = forall a. Maybe a
Prelude.Nothing
    }

-- | A list of up to 100 cluster names or full cluster Amazon Resource Name
-- (ARN) entries. If you do not specify a cluster, the default cluster is
-- assumed.
describeClusters_clusters :: Lens.Lens' DescribeClusters (Prelude.Maybe [Prelude.Text])
describeClusters_clusters :: Lens' DescribeClusters (Maybe [Text])
describeClusters_clusters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeClusters' {Maybe [Text]
clusters :: Maybe [Text]
$sel:clusters:DescribeClusters' :: DescribeClusters -> Maybe [Text]
clusters} -> Maybe [Text]
clusters) (\s :: DescribeClusters
s@DescribeClusters' {} Maybe [Text]
a -> DescribeClusters
s {$sel:clusters:DescribeClusters' :: Maybe [Text]
clusters = Maybe [Text]
a} :: DescribeClusters) 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

-- | Determines whether to include additional information about the clusters
-- in the response. If this field is omitted, this information isn\'t
-- included.
--
-- If @ATTACHMENTS@ is specified, the attachments for the container
-- instances or tasks within the cluster are included, for example the
-- capacity providers.
--
-- If @SETTINGS@ is specified, the settings for the cluster are included.
--
-- If @CONFIGURATIONS@ is specified, the configuration for the cluster is
-- included.
--
-- If @STATISTICS@ is specified, the task and service count is included,
-- separated by launch type.
--
-- If @TAGS@ is specified, the metadata tags associated with the cluster
-- are included.
describeClusters_include :: Lens.Lens' DescribeClusters (Prelude.Maybe [ClusterField])
describeClusters_include :: Lens' DescribeClusters (Maybe [ClusterField])
describeClusters_include = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeClusters' {Maybe [ClusterField]
include :: Maybe [ClusterField]
$sel:include:DescribeClusters' :: DescribeClusters -> Maybe [ClusterField]
include} -> Maybe [ClusterField]
include) (\s :: DescribeClusters
s@DescribeClusters' {} Maybe [ClusterField]
a -> DescribeClusters
s {$sel:include:DescribeClusters' :: Maybe [ClusterField]
include = Maybe [ClusterField]
a} :: DescribeClusters) 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

instance Core.AWSRequest DescribeClusters where
  type
    AWSResponse DescribeClusters =
      DescribeClustersResponse
  request :: (Service -> Service)
-> DescribeClusters -> Request DescribeClusters
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 DescribeClusters
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DescribeClusters)))
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 [Cluster]
-> Maybe [Failure] -> Int -> DescribeClustersResponse
DescribeClustersResponse'
            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
"clusters" 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
"failures" 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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable DescribeClusters where
  hashWithSalt :: Int -> DescribeClusters -> Int
hashWithSalt Int
_salt DescribeClusters' {Maybe [Text]
Maybe [ClusterField]
include :: Maybe [ClusterField]
clusters :: Maybe [Text]
$sel:include:DescribeClusters' :: DescribeClusters -> Maybe [ClusterField]
$sel:clusters:DescribeClusters' :: DescribeClusters -> Maybe [Text]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
clusters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ClusterField]
include

instance Prelude.NFData DescribeClusters where
  rnf :: DescribeClusters -> ()
rnf DescribeClusters' {Maybe [Text]
Maybe [ClusterField]
include :: Maybe [ClusterField]
clusters :: Maybe [Text]
$sel:include:DescribeClusters' :: DescribeClusters -> Maybe [ClusterField]
$sel:clusters:DescribeClusters' :: DescribeClusters -> Maybe [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
clusters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ClusterField]
include

instance Data.ToHeaders DescribeClusters where
  toHeaders :: DescribeClusters -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"AmazonEC2ContainerServiceV20141113.DescribeClusters" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON DescribeClusters where
  toJSON :: DescribeClusters -> Value
toJSON DescribeClusters' {Maybe [Text]
Maybe [ClusterField]
include :: Maybe [ClusterField]
clusters :: Maybe [Text]
$sel:include:DescribeClusters' :: DescribeClusters -> Maybe [ClusterField]
$sel:clusters:DescribeClusters' :: DescribeClusters -> Maybe [Text]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"clusters" 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]
clusters,
            (Key
"include" 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 [ClusterField]
include
          ]
      )

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

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

-- | /See:/ 'newDescribeClustersResponse' smart constructor.
data DescribeClustersResponse = DescribeClustersResponse'
  { -- | The list of clusters.
    DescribeClustersResponse -> Maybe [Cluster]
clusters :: Prelude.Maybe [Cluster],
    -- | Any failures associated with the call.
    DescribeClustersResponse -> Maybe [Failure]
failures :: Prelude.Maybe [Failure],
    -- | The response's http status code.
    DescribeClustersResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeClustersResponse -> DescribeClustersResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeClustersResponse -> DescribeClustersResponse -> Bool
$c/= :: DescribeClustersResponse -> DescribeClustersResponse -> Bool
== :: DescribeClustersResponse -> DescribeClustersResponse -> Bool
$c== :: DescribeClustersResponse -> DescribeClustersResponse -> Bool
Prelude.Eq, ReadPrec [DescribeClustersResponse]
ReadPrec DescribeClustersResponse
Int -> ReadS DescribeClustersResponse
ReadS [DescribeClustersResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeClustersResponse]
$creadListPrec :: ReadPrec [DescribeClustersResponse]
readPrec :: ReadPrec DescribeClustersResponse
$creadPrec :: ReadPrec DescribeClustersResponse
readList :: ReadS [DescribeClustersResponse]
$creadList :: ReadS [DescribeClustersResponse]
readsPrec :: Int -> ReadS DescribeClustersResponse
$creadsPrec :: Int -> ReadS DescribeClustersResponse
Prelude.Read, Int -> DescribeClustersResponse -> ShowS
[DescribeClustersResponse] -> ShowS
DescribeClustersResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeClustersResponse] -> ShowS
$cshowList :: [DescribeClustersResponse] -> ShowS
show :: DescribeClustersResponse -> String
$cshow :: DescribeClustersResponse -> String
showsPrec :: Int -> DescribeClustersResponse -> ShowS
$cshowsPrec :: Int -> DescribeClustersResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeClustersResponse x -> DescribeClustersResponse
forall x.
DescribeClustersResponse -> Rep DescribeClustersResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeClustersResponse x -> DescribeClustersResponse
$cfrom :: forall x.
DescribeClustersResponse -> Rep DescribeClustersResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeClustersResponse' 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:
--
-- 'clusters', 'describeClustersResponse_clusters' - The list of clusters.
--
-- 'failures', 'describeClustersResponse_failures' - Any failures associated with the call.
--
-- 'httpStatus', 'describeClustersResponse_httpStatus' - The response's http status code.
newDescribeClustersResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeClustersResponse
newDescribeClustersResponse :: Int -> DescribeClustersResponse
newDescribeClustersResponse Int
pHttpStatus_ =
  DescribeClustersResponse'
    { $sel:clusters:DescribeClustersResponse' :: Maybe [Cluster]
clusters =
        forall a. Maybe a
Prelude.Nothing,
      $sel:failures:DescribeClustersResponse' :: Maybe [Failure]
failures = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeClustersResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The list of clusters.
describeClustersResponse_clusters :: Lens.Lens' DescribeClustersResponse (Prelude.Maybe [Cluster])
describeClustersResponse_clusters :: Lens' DescribeClustersResponse (Maybe [Cluster])
describeClustersResponse_clusters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeClustersResponse' {Maybe [Cluster]
clusters :: Maybe [Cluster]
$sel:clusters:DescribeClustersResponse' :: DescribeClustersResponse -> Maybe [Cluster]
clusters} -> Maybe [Cluster]
clusters) (\s :: DescribeClustersResponse
s@DescribeClustersResponse' {} Maybe [Cluster]
a -> DescribeClustersResponse
s {$sel:clusters:DescribeClustersResponse' :: Maybe [Cluster]
clusters = Maybe [Cluster]
a} :: DescribeClustersResponse) 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

-- | Any failures associated with the call.
describeClustersResponse_failures :: Lens.Lens' DescribeClustersResponse (Prelude.Maybe [Failure])
describeClustersResponse_failures :: Lens' DescribeClustersResponse (Maybe [Failure])
describeClustersResponse_failures = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeClustersResponse' {Maybe [Failure]
failures :: Maybe [Failure]
$sel:failures:DescribeClustersResponse' :: DescribeClustersResponse -> Maybe [Failure]
failures} -> Maybe [Failure]
failures) (\s :: DescribeClustersResponse
s@DescribeClustersResponse' {} Maybe [Failure]
a -> DescribeClustersResponse
s {$sel:failures:DescribeClustersResponse' :: Maybe [Failure]
failures = Maybe [Failure]
a} :: DescribeClustersResponse) 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.
describeClustersResponse_httpStatus :: Lens.Lens' DescribeClustersResponse Prelude.Int
describeClustersResponse_httpStatus :: Lens' DescribeClustersResponse Int
describeClustersResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeClustersResponse' {Int
httpStatus :: Int
$sel:httpStatus:DescribeClustersResponse' :: DescribeClustersResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DescribeClustersResponse
s@DescribeClustersResponse' {} Int
a -> DescribeClustersResponse
s {$sel:httpStatus:DescribeClustersResponse' :: Int
httpStatus = Int
a} :: DescribeClustersResponse)

instance Prelude.NFData DescribeClustersResponse where
  rnf :: DescribeClustersResponse -> ()
rnf DescribeClustersResponse' {Int
Maybe [Failure]
Maybe [Cluster]
httpStatus :: Int
failures :: Maybe [Failure]
clusters :: Maybe [Cluster]
$sel:httpStatus:DescribeClustersResponse' :: DescribeClustersResponse -> Int
$sel:failures:DescribeClustersResponse' :: DescribeClustersResponse -> Maybe [Failure]
$sel:clusters:DescribeClustersResponse' :: DescribeClustersResponse -> Maybe [Cluster]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Cluster]
clusters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Failure]
failures
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus