{-# 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.DisableMetricsCollection
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Disables group metrics collection for the specified Auto Scaling group.
module Amazonka.AutoScaling.DisableMetricsCollection
  ( -- * Creating a Request
    DisableMetricsCollection (..),
    newDisableMetricsCollection,

    -- * Request Lenses
    disableMetricsCollection_metrics,
    disableMetricsCollection_autoScalingGroupName,

    -- * Destructuring the Response
    DisableMetricsCollectionResponse (..),
    newDisableMetricsCollectionResponse,
  )
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:/ 'newDisableMetricsCollection' smart constructor.
data DisableMetricsCollection = DisableMetricsCollection'
  { -- | Identifies the metrics to disable.
    --
    -- 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 omit this property, all metrics are disabled.
    --
    -- 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/.
    DisableMetricsCollection -> Maybe [Text]
metrics :: Prelude.Maybe [Prelude.Text],
    -- | The name of the Auto Scaling group.
    DisableMetricsCollection -> Text
autoScalingGroupName :: Prelude.Text
  }
  deriving (DisableMetricsCollection -> DisableMetricsCollection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisableMetricsCollection -> DisableMetricsCollection -> Bool
$c/= :: DisableMetricsCollection -> DisableMetricsCollection -> Bool
== :: DisableMetricsCollection -> DisableMetricsCollection -> Bool
$c== :: DisableMetricsCollection -> DisableMetricsCollection -> Bool
Prelude.Eq, ReadPrec [DisableMetricsCollection]
ReadPrec DisableMetricsCollection
Int -> ReadS DisableMetricsCollection
ReadS [DisableMetricsCollection]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DisableMetricsCollection]
$creadListPrec :: ReadPrec [DisableMetricsCollection]
readPrec :: ReadPrec DisableMetricsCollection
$creadPrec :: ReadPrec DisableMetricsCollection
readList :: ReadS [DisableMetricsCollection]
$creadList :: ReadS [DisableMetricsCollection]
readsPrec :: Int -> ReadS DisableMetricsCollection
$creadsPrec :: Int -> ReadS DisableMetricsCollection
Prelude.Read, Int -> DisableMetricsCollection -> ShowS
[DisableMetricsCollection] -> ShowS
DisableMetricsCollection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisableMetricsCollection] -> ShowS
$cshowList :: [DisableMetricsCollection] -> ShowS
show :: DisableMetricsCollection -> String
$cshow :: DisableMetricsCollection -> String
showsPrec :: Int -> DisableMetricsCollection -> ShowS
$cshowsPrec :: Int -> DisableMetricsCollection -> ShowS
Prelude.Show, forall x.
Rep DisableMetricsCollection x -> DisableMetricsCollection
forall x.
DisableMetricsCollection -> Rep DisableMetricsCollection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DisableMetricsCollection x -> DisableMetricsCollection
$cfrom :: forall x.
DisableMetricsCollection -> Rep DisableMetricsCollection x
Prelude.Generic)

-- |
-- Create a value of 'DisableMetricsCollection' 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', 'disableMetricsCollection_metrics' - Identifies the metrics to disable.
--
-- 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 omit this property, all metrics are disabled.
--
-- 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', 'disableMetricsCollection_autoScalingGroupName' - The name of the Auto Scaling group.
newDisableMetricsCollection ::
  -- | 'autoScalingGroupName'
  Prelude.Text ->
  DisableMetricsCollection
newDisableMetricsCollection :: Text -> DisableMetricsCollection
newDisableMetricsCollection Text
pAutoScalingGroupName_ =
  DisableMetricsCollection'
    { $sel:metrics:DisableMetricsCollection' :: Maybe [Text]
metrics =
        forall a. Maybe a
Prelude.Nothing,
      $sel:autoScalingGroupName:DisableMetricsCollection' :: Text
autoScalingGroupName = Text
pAutoScalingGroupName_
    }

-- | Identifies the metrics to disable.
--
-- 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 omit this property, all metrics are disabled.
--
-- 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/.
disableMetricsCollection_metrics :: Lens.Lens' DisableMetricsCollection (Prelude.Maybe [Prelude.Text])
disableMetricsCollection_metrics :: Lens' DisableMetricsCollection (Maybe [Text])
disableMetricsCollection_metrics = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisableMetricsCollection' {Maybe [Text]
metrics :: Maybe [Text]
$sel:metrics:DisableMetricsCollection' :: DisableMetricsCollection -> Maybe [Text]
metrics} -> Maybe [Text]
metrics) (\s :: DisableMetricsCollection
s@DisableMetricsCollection' {} Maybe [Text]
a -> DisableMetricsCollection
s {$sel:metrics:DisableMetricsCollection' :: Maybe [Text]
metrics = Maybe [Text]
a} :: DisableMetricsCollection) 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.
disableMetricsCollection_autoScalingGroupName :: Lens.Lens' DisableMetricsCollection Prelude.Text
disableMetricsCollection_autoScalingGroupName :: Lens' DisableMetricsCollection Text
disableMetricsCollection_autoScalingGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisableMetricsCollection' {Text
autoScalingGroupName :: Text
$sel:autoScalingGroupName:DisableMetricsCollection' :: DisableMetricsCollection -> Text
autoScalingGroupName} -> Text
autoScalingGroupName) (\s :: DisableMetricsCollection
s@DisableMetricsCollection' {} Text
a -> DisableMetricsCollection
s {$sel:autoScalingGroupName:DisableMetricsCollection' :: Text
autoScalingGroupName = Text
a} :: DisableMetricsCollection)

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

instance Prelude.Hashable DisableMetricsCollection where
  hashWithSalt :: Int -> DisableMetricsCollection -> Int
hashWithSalt Int
_salt DisableMetricsCollection' {Maybe [Text]
Text
autoScalingGroupName :: Text
metrics :: Maybe [Text]
$sel:autoScalingGroupName:DisableMetricsCollection' :: DisableMetricsCollection -> Text
$sel:metrics:DisableMetricsCollection' :: DisableMetricsCollection -> 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

instance Prelude.NFData DisableMetricsCollection where
  rnf :: DisableMetricsCollection -> ()
rnf DisableMetricsCollection' {Maybe [Text]
Text
autoScalingGroupName :: Text
metrics :: Maybe [Text]
$sel:autoScalingGroupName:DisableMetricsCollection' :: DisableMetricsCollection -> Text
$sel:metrics:DisableMetricsCollection' :: DisableMetricsCollection -> 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

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

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

instance Data.ToQuery DisableMetricsCollection where
  toQuery :: DisableMetricsCollection -> QueryString
toQuery DisableMetricsCollection' {Maybe [Text]
Text
autoScalingGroupName :: Text
metrics :: Maybe [Text]
$sel:autoScalingGroupName:DisableMetricsCollection' :: DisableMetricsCollection -> Text
$sel:metrics:DisableMetricsCollection' :: DisableMetricsCollection -> Maybe [Text]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DisableMetricsCollection" :: 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
      ]

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

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

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