{-# 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.AutoScaling.EnableMetricsCollection
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Enables group metrics collection for the specified Auto Scaling group.
--
-- You can use these metrics to track changes in an Auto Scaling group and
-- to set alarms on threshold values. You can view group metrics using the
-- Amazon EC2 Auto Scaling console or the CloudWatch console. For more
-- information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/ec2-auto-scaling-cloudwatch-monitoring.html Monitor CloudWatch metrics for your Auto Scaling groups and instances>
-- in the /Amazon EC2 Auto Scaling User Guide/.
module Amazonka.AutoScaling.EnableMetricsCollection
  ( -- * Creating a Request
    EnableMetricsCollection (..),
    newEnableMetricsCollection,

    -- * Request Lenses
    enableMetricsCollection_metrics,
    enableMetricsCollection_autoScalingGroupName,
    enableMetricsCollection_granularity,

    -- * Destructuring the Response
    EnableMetricsCollectionResponse (..),
    newEnableMetricsCollectionResponse,
  )
where

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

-- | /See:/ 'newEnableMetricsCollection' smart constructor.
data EnableMetricsCollection = EnableMetricsCollection'
  { -- | Identifies the metrics to enable.
    --
    -- You can specify one or more of the following metrics:
    --
    -- -   @GroupMinSize@
    --
    -- -   @GroupMaxSize@
    --
    -- -   @GroupDesiredCapacity@
    --
    -- -   @GroupInServiceInstances@
    --
    -- -   @GroupPendingInstances@
    --
    -- -   @GroupStandbyInstances@
    --
    -- -   @GroupTerminatingInstances@
    --
    -- -   @GroupTotalInstances@
    --
    -- -   @GroupInServiceCapacity@
    --
    -- -   @GroupPendingCapacity@
    --
    -- -   @GroupStandbyCapacity@
    --
    -- -   @GroupTerminatingCapacity@
    --
    -- -   @GroupTotalCapacity@
    --
    -- -   @WarmPoolDesiredCapacity@
    --
    -- -   @WarmPoolWarmedCapacity@
    --
    -- -   @WarmPoolPendingCapacity@
    --
    -- -   @WarmPoolTerminatingCapacity@
    --
    -- -   @WarmPoolTotalCapacity@
    --
    -- -   @GroupAndWarmPoolDesiredCapacity@
    --
    -- -   @GroupAndWarmPoolTotalCapacity@
    --
    -- If you specify @Granularity@ and don\'t specify any metrics, all metrics
    -- are enabled.
    --
    -- For more information, see
    -- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/ec2-auto-scaling-cloudwatch-monitoring.html#as-group-metrics Auto Scaling group metrics>
    -- in the /Amazon EC2 Auto Scaling User Guide/.
    EnableMetricsCollection -> Maybe [Text]
metrics :: Prelude.Maybe [Prelude.Text],
    -- | The name of the Auto Scaling group.
    EnableMetricsCollection -> Text
autoScalingGroupName :: Prelude.Text,
    -- | The frequency at which Amazon EC2 Auto Scaling sends aggregated data to
    -- CloudWatch. The only valid value is @1Minute@.
    EnableMetricsCollection -> Text
granularity :: Prelude.Text
  }
  deriving (EnableMetricsCollection -> EnableMetricsCollection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnableMetricsCollection -> EnableMetricsCollection -> Bool
$c/= :: EnableMetricsCollection -> EnableMetricsCollection -> Bool
== :: EnableMetricsCollection -> EnableMetricsCollection -> Bool
$c== :: EnableMetricsCollection -> EnableMetricsCollection -> Bool
Prelude.Eq, ReadPrec [EnableMetricsCollection]
ReadPrec EnableMetricsCollection
Int -> ReadS EnableMetricsCollection
ReadS [EnableMetricsCollection]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnableMetricsCollection]
$creadListPrec :: ReadPrec [EnableMetricsCollection]
readPrec :: ReadPrec EnableMetricsCollection
$creadPrec :: ReadPrec EnableMetricsCollection
readList :: ReadS [EnableMetricsCollection]
$creadList :: ReadS [EnableMetricsCollection]
readsPrec :: Int -> ReadS EnableMetricsCollection
$creadsPrec :: Int -> ReadS EnableMetricsCollection
Prelude.Read, Int -> EnableMetricsCollection -> ShowS
[EnableMetricsCollection] -> ShowS
EnableMetricsCollection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EnableMetricsCollection] -> ShowS
$cshowList :: [EnableMetricsCollection] -> ShowS
show :: EnableMetricsCollection -> String
$cshow :: EnableMetricsCollection -> String
showsPrec :: Int -> EnableMetricsCollection -> ShowS
$cshowsPrec :: Int -> EnableMetricsCollection -> ShowS
Prelude.Show, forall x. Rep EnableMetricsCollection x -> EnableMetricsCollection
forall x. EnableMetricsCollection -> Rep EnableMetricsCollection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EnableMetricsCollection x -> EnableMetricsCollection
$cfrom :: forall x. EnableMetricsCollection -> Rep EnableMetricsCollection x
Prelude.Generic)

-- |
-- Create a value of 'EnableMetricsCollection' 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:
--
-- 'metrics', 'enableMetricsCollection_metrics' - Identifies the metrics to enable.
--
-- You can specify one or more of the following metrics:
--
-- -   @GroupMinSize@
--
-- -   @GroupMaxSize@
--
-- -   @GroupDesiredCapacity@
--
-- -   @GroupInServiceInstances@
--
-- -   @GroupPendingInstances@
--
-- -   @GroupStandbyInstances@
--
-- -   @GroupTerminatingInstances@
--
-- -   @GroupTotalInstances@
--
-- -   @GroupInServiceCapacity@
--
-- -   @GroupPendingCapacity@
--
-- -   @GroupStandbyCapacity@
--
-- -   @GroupTerminatingCapacity@
--
-- -   @GroupTotalCapacity@
--
-- -   @WarmPoolDesiredCapacity@
--
-- -   @WarmPoolWarmedCapacity@
--
-- -   @WarmPoolPendingCapacity@
--
-- -   @WarmPoolTerminatingCapacity@
--
-- -   @WarmPoolTotalCapacity@
--
-- -   @GroupAndWarmPoolDesiredCapacity@
--
-- -   @GroupAndWarmPoolTotalCapacity@
--
-- If you specify @Granularity@ and don\'t specify any metrics, all metrics
-- are enabled.
--
-- For more information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/ec2-auto-scaling-cloudwatch-monitoring.html#as-group-metrics Auto Scaling group metrics>
-- in the /Amazon EC2 Auto Scaling User Guide/.
--
-- 'autoScalingGroupName', 'enableMetricsCollection_autoScalingGroupName' - The name of the Auto Scaling group.
--
-- 'granularity', 'enableMetricsCollection_granularity' - The frequency at which Amazon EC2 Auto Scaling sends aggregated data to
-- CloudWatch. The only valid value is @1Minute@.
newEnableMetricsCollection ::
  -- | 'autoScalingGroupName'
  Prelude.Text ->
  -- | 'granularity'
  Prelude.Text ->
  EnableMetricsCollection
newEnableMetricsCollection :: Text -> Text -> EnableMetricsCollection
newEnableMetricsCollection
  Text
pAutoScalingGroupName_
  Text
pGranularity_ =
    EnableMetricsCollection'
      { $sel:metrics:EnableMetricsCollection' :: Maybe [Text]
metrics = forall a. Maybe a
Prelude.Nothing,
        $sel:autoScalingGroupName:EnableMetricsCollection' :: Text
autoScalingGroupName = Text
pAutoScalingGroupName_,
        $sel:granularity:EnableMetricsCollection' :: Text
granularity = Text
pGranularity_
      }

-- | Identifies the metrics to enable.
--
-- You can specify one or more of the following metrics:
--
-- -   @GroupMinSize@
--
-- -   @GroupMaxSize@
--
-- -   @GroupDesiredCapacity@
--
-- -   @GroupInServiceInstances@
--
-- -   @GroupPendingInstances@
--
-- -   @GroupStandbyInstances@
--
-- -   @GroupTerminatingInstances@
--
-- -   @GroupTotalInstances@
--
-- -   @GroupInServiceCapacity@
--
-- -   @GroupPendingCapacity@
--
-- -   @GroupStandbyCapacity@
--
-- -   @GroupTerminatingCapacity@
--
-- -   @GroupTotalCapacity@
--
-- -   @WarmPoolDesiredCapacity@
--
-- -   @WarmPoolWarmedCapacity@
--
-- -   @WarmPoolPendingCapacity@
--
-- -   @WarmPoolTerminatingCapacity@
--
-- -   @WarmPoolTotalCapacity@
--
-- -   @GroupAndWarmPoolDesiredCapacity@
--
-- -   @GroupAndWarmPoolTotalCapacity@
--
-- If you specify @Granularity@ and don\'t specify any metrics, all metrics
-- are enabled.
--
-- For more information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/ec2-auto-scaling-cloudwatch-monitoring.html#as-group-metrics Auto Scaling group metrics>
-- in the /Amazon EC2 Auto Scaling User Guide/.
enableMetricsCollection_metrics :: Lens.Lens' EnableMetricsCollection (Prelude.Maybe [Prelude.Text])
enableMetricsCollection_metrics :: Lens' EnableMetricsCollection (Maybe [Text])
enableMetricsCollection_metrics = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnableMetricsCollection' {Maybe [Text]
metrics :: Maybe [Text]
$sel:metrics:EnableMetricsCollection' :: EnableMetricsCollection -> Maybe [Text]
metrics} -> Maybe [Text]
metrics) (\s :: EnableMetricsCollection
s@EnableMetricsCollection' {} Maybe [Text]
a -> EnableMetricsCollection
s {$sel:metrics:EnableMetricsCollection' :: Maybe [Text]
metrics = Maybe [Text]
a} :: EnableMetricsCollection) 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 name of the Auto Scaling group.
enableMetricsCollection_autoScalingGroupName :: Lens.Lens' EnableMetricsCollection Prelude.Text
enableMetricsCollection_autoScalingGroupName :: Lens' EnableMetricsCollection Text
enableMetricsCollection_autoScalingGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnableMetricsCollection' {Text
autoScalingGroupName :: Text
$sel:autoScalingGroupName:EnableMetricsCollection' :: EnableMetricsCollection -> Text
autoScalingGroupName} -> Text
autoScalingGroupName) (\s :: EnableMetricsCollection
s@EnableMetricsCollection' {} Text
a -> EnableMetricsCollection
s {$sel:autoScalingGroupName:EnableMetricsCollection' :: Text
autoScalingGroupName = Text
a} :: EnableMetricsCollection)

-- | The frequency at which Amazon EC2 Auto Scaling sends aggregated data to
-- CloudWatch. The only valid value is @1Minute@.
enableMetricsCollection_granularity :: Lens.Lens' EnableMetricsCollection Prelude.Text
enableMetricsCollection_granularity :: Lens' EnableMetricsCollection Text
enableMetricsCollection_granularity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnableMetricsCollection' {Text
granularity :: Text
$sel:granularity:EnableMetricsCollection' :: EnableMetricsCollection -> Text
granularity} -> Text
granularity) (\s :: EnableMetricsCollection
s@EnableMetricsCollection' {} Text
a -> EnableMetricsCollection
s {$sel:granularity:EnableMetricsCollection' :: Text
granularity = Text
a} :: EnableMetricsCollection)

instance Core.AWSRequest EnableMetricsCollection where
  type
    AWSResponse EnableMetricsCollection =
      EnableMetricsCollectionResponse
  request :: (Service -> Service)
-> EnableMetricsCollection -> Request EnableMetricsCollection
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 EnableMetricsCollection
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse EnableMetricsCollection)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull
      EnableMetricsCollectionResponse
EnableMetricsCollectionResponse'

instance Prelude.Hashable EnableMetricsCollection where
  hashWithSalt :: Int -> EnableMetricsCollection -> Int
hashWithSalt Int
_salt EnableMetricsCollection' {Maybe [Text]
Text
granularity :: Text
autoScalingGroupName :: Text
metrics :: Maybe [Text]
$sel:granularity:EnableMetricsCollection' :: EnableMetricsCollection -> Text
$sel:autoScalingGroupName:EnableMetricsCollection' :: EnableMetricsCollection -> Text
$sel:metrics:EnableMetricsCollection' :: EnableMetricsCollection -> Maybe [Text]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
metrics
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
autoScalingGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
granularity

instance Prelude.NFData EnableMetricsCollection where
  rnf :: EnableMetricsCollection -> ()
rnf EnableMetricsCollection' {Maybe [Text]
Text
granularity :: Text
autoScalingGroupName :: Text
metrics :: Maybe [Text]
$sel:granularity:EnableMetricsCollection' :: EnableMetricsCollection -> Text
$sel:autoScalingGroupName:EnableMetricsCollection' :: EnableMetricsCollection -> Text
$sel:metrics:EnableMetricsCollection' :: EnableMetricsCollection -> Maybe [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
metrics
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
autoScalingGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
granularity

instance Data.ToHeaders EnableMetricsCollection where
  toHeaders :: EnableMetricsCollection -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery EnableMetricsCollection where
  toQuery :: EnableMetricsCollection -> QueryString
toQuery EnableMetricsCollection' {Maybe [Text]
Text
granularity :: Text
autoScalingGroupName :: Text
metrics :: Maybe [Text]
$sel:granularity:EnableMetricsCollection' :: EnableMetricsCollection -> Text
$sel:autoScalingGroupName:EnableMetricsCollection' :: EnableMetricsCollection -> Text
$sel:metrics:EnableMetricsCollection' :: EnableMetricsCollection -> Maybe [Text]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"EnableMetricsCollection" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2011-01-01" :: Prelude.ByteString),
        ByteString
"Metrics"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            (forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
metrics),
        ByteString
"AutoScalingGroupName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
autoScalingGroupName,
        ByteString
"Granularity" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
granularity
      ]

-- | /See:/ 'newEnableMetricsCollectionResponse' smart constructor.
data EnableMetricsCollectionResponse = EnableMetricsCollectionResponse'
  {
  }
  deriving (EnableMetricsCollectionResponse
-> EnableMetricsCollectionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnableMetricsCollectionResponse
-> EnableMetricsCollectionResponse -> Bool
$c/= :: EnableMetricsCollectionResponse
-> EnableMetricsCollectionResponse -> Bool
== :: EnableMetricsCollectionResponse
-> EnableMetricsCollectionResponse -> Bool
$c== :: EnableMetricsCollectionResponse
-> EnableMetricsCollectionResponse -> Bool
Prelude.Eq, ReadPrec [EnableMetricsCollectionResponse]
ReadPrec EnableMetricsCollectionResponse
Int -> ReadS EnableMetricsCollectionResponse
ReadS [EnableMetricsCollectionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnableMetricsCollectionResponse]
$creadListPrec :: ReadPrec [EnableMetricsCollectionResponse]
readPrec :: ReadPrec EnableMetricsCollectionResponse
$creadPrec :: ReadPrec EnableMetricsCollectionResponse
readList :: ReadS [EnableMetricsCollectionResponse]
$creadList :: ReadS [EnableMetricsCollectionResponse]
readsPrec :: Int -> ReadS EnableMetricsCollectionResponse
$creadsPrec :: Int -> ReadS EnableMetricsCollectionResponse
Prelude.Read, Int -> EnableMetricsCollectionResponse -> ShowS
[EnableMetricsCollectionResponse] -> ShowS
EnableMetricsCollectionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EnableMetricsCollectionResponse] -> ShowS
$cshowList :: [EnableMetricsCollectionResponse] -> ShowS
show :: EnableMetricsCollectionResponse -> String
$cshow :: EnableMetricsCollectionResponse -> String
showsPrec :: Int -> EnableMetricsCollectionResponse -> ShowS
$cshowsPrec :: Int -> EnableMetricsCollectionResponse -> ShowS
Prelude.Show, forall x.
Rep EnableMetricsCollectionResponse x
-> EnableMetricsCollectionResponse
forall x.
EnableMetricsCollectionResponse
-> Rep EnableMetricsCollectionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep EnableMetricsCollectionResponse x
-> EnableMetricsCollectionResponse
$cfrom :: forall x.
EnableMetricsCollectionResponse
-> Rep EnableMetricsCollectionResponse x
Prelude.Generic)

-- |
-- Create a value of 'EnableMetricsCollectionResponse' 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.
newEnableMetricsCollectionResponse ::
  EnableMetricsCollectionResponse
newEnableMetricsCollectionResponse :: EnableMetricsCollectionResponse
newEnableMetricsCollectionResponse =
  EnableMetricsCollectionResponse
EnableMetricsCollectionResponse'

instance
  Prelude.NFData
    EnableMetricsCollectionResponse
  where
  rnf :: EnableMetricsCollectionResponse -> ()
rnf EnableMetricsCollectionResponse
_ = ()