{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# 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.Types.ScalingPolicy
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.AutoScaling.Types.ScalingPolicy where

import Amazonka.AutoScaling.Types.Alarm
import Amazonka.AutoScaling.Types.PredictiveScalingConfiguration
import Amazonka.AutoScaling.Types.StepAdjustment
import Amazonka.AutoScaling.Types.TargetTrackingConfiguration
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

-- | Describes a scaling policy.
--
-- /See:/ 'newScalingPolicy' smart constructor.
data ScalingPolicy = ScalingPolicy'
  { -- | Specifies how the scaling adjustment is interpreted (for example, an
    -- absolute number or a percentage). The valid values are
    -- @ChangeInCapacity@, @ExactCapacity@, and @PercentChangeInCapacity@.
    ScalingPolicy -> Maybe Text
adjustmentType :: Prelude.Maybe Prelude.Text,
    -- | The CloudWatch alarms related to the policy.
    ScalingPolicy -> Maybe [Alarm]
alarms :: Prelude.Maybe [Alarm],
    -- | The name of the Auto Scaling group.
    ScalingPolicy -> Maybe Text
autoScalingGroupName :: Prelude.Maybe Prelude.Text,
    -- | The duration of the policy\'s cooldown period, in seconds.
    ScalingPolicy -> Maybe Int
cooldown :: Prelude.Maybe Prelude.Int,
    -- | Indicates whether the policy is enabled (@true@) or disabled (@false@).
    ScalingPolicy -> Maybe Bool
enabled :: Prelude.Maybe Prelude.Bool,
    -- | The estimated time, in seconds, until a newly launched instance can
    -- contribute to the CloudWatch metrics.
    ScalingPolicy -> Maybe Int
estimatedInstanceWarmup :: Prelude.Maybe Prelude.Int,
    -- | The aggregation type for the CloudWatch metrics. The valid values are
    -- @Minimum@, @Maximum@, and @Average@.
    ScalingPolicy -> Maybe Text
metricAggregationType :: Prelude.Maybe Prelude.Text,
    -- | The minimum value to scale by when the adjustment type is
    -- @PercentChangeInCapacity@.
    ScalingPolicy -> Maybe Int
minAdjustmentMagnitude :: Prelude.Maybe Prelude.Int,
    -- | Available for backward compatibility. Use @MinAdjustmentMagnitude@
    -- instead.
    ScalingPolicy -> Maybe Int
minAdjustmentStep :: Prelude.Maybe Prelude.Int,
    -- | The Amazon Resource Name (ARN) of the policy.
    ScalingPolicy -> Maybe Text
policyARN :: Prelude.Maybe Prelude.Text,
    -- | The name of the scaling policy.
    ScalingPolicy -> Maybe Text
policyName :: Prelude.Maybe Prelude.Text,
    -- | One of the following policy types:
    --
    -- -   @TargetTrackingScaling@
    --
    -- -   @StepScaling@
    --
    -- -   @SimpleScaling@ (default)
    --
    -- -   @PredictiveScaling@
    --
    -- For more information, see
    -- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/as-scaling-target-tracking.html Target tracking scaling policies>
    -- and
    -- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/as-scaling-simple-step.html Step and simple scaling policies>
    -- in the /Amazon EC2 Auto Scaling User Guide/.
    ScalingPolicy -> Maybe Text
policyType :: Prelude.Maybe Prelude.Text,
    -- | A predictive scaling policy.
    ScalingPolicy -> Maybe PredictiveScalingConfiguration
predictiveScalingConfiguration :: Prelude.Maybe PredictiveScalingConfiguration,
    -- | The amount by which to scale, based on the specified adjustment type. A
    -- positive value adds to the current capacity while a negative number
    -- removes from the current capacity.
    ScalingPolicy -> Maybe Int
scalingAdjustment :: Prelude.Maybe Prelude.Int,
    -- | A set of adjustments that enable you to scale based on the size of the
    -- alarm breach.
    ScalingPolicy -> Maybe [StepAdjustment]
stepAdjustments :: Prelude.Maybe [StepAdjustment],
    -- | A target tracking scaling policy.
    ScalingPolicy -> Maybe TargetTrackingConfiguration
targetTrackingConfiguration :: Prelude.Maybe TargetTrackingConfiguration
  }
  deriving (ScalingPolicy -> ScalingPolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ScalingPolicy -> ScalingPolicy -> Bool
$c/= :: ScalingPolicy -> ScalingPolicy -> Bool
== :: ScalingPolicy -> ScalingPolicy -> Bool
$c== :: ScalingPolicy -> ScalingPolicy -> Bool
Prelude.Eq, ReadPrec [ScalingPolicy]
ReadPrec ScalingPolicy
Int -> ReadS ScalingPolicy
ReadS [ScalingPolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ScalingPolicy]
$creadListPrec :: ReadPrec [ScalingPolicy]
readPrec :: ReadPrec ScalingPolicy
$creadPrec :: ReadPrec ScalingPolicy
readList :: ReadS [ScalingPolicy]
$creadList :: ReadS [ScalingPolicy]
readsPrec :: Int -> ReadS ScalingPolicy
$creadsPrec :: Int -> ReadS ScalingPolicy
Prelude.Read, Int -> ScalingPolicy -> ShowS
[ScalingPolicy] -> ShowS
ScalingPolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ScalingPolicy] -> ShowS
$cshowList :: [ScalingPolicy] -> ShowS
show :: ScalingPolicy -> String
$cshow :: ScalingPolicy -> String
showsPrec :: Int -> ScalingPolicy -> ShowS
$cshowsPrec :: Int -> ScalingPolicy -> ShowS
Prelude.Show, forall x. Rep ScalingPolicy x -> ScalingPolicy
forall x. ScalingPolicy -> Rep ScalingPolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ScalingPolicy x -> ScalingPolicy
$cfrom :: forall x. ScalingPolicy -> Rep ScalingPolicy x
Prelude.Generic)

-- |
-- Create a value of 'ScalingPolicy' 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:
--
-- 'adjustmentType', 'scalingPolicy_adjustmentType' - Specifies how the scaling adjustment is interpreted (for example, an
-- absolute number or a percentage). The valid values are
-- @ChangeInCapacity@, @ExactCapacity@, and @PercentChangeInCapacity@.
--
-- 'alarms', 'scalingPolicy_alarms' - The CloudWatch alarms related to the policy.
--
-- 'autoScalingGroupName', 'scalingPolicy_autoScalingGroupName' - The name of the Auto Scaling group.
--
-- 'cooldown', 'scalingPolicy_cooldown' - The duration of the policy\'s cooldown period, in seconds.
--
-- 'enabled', 'scalingPolicy_enabled' - Indicates whether the policy is enabled (@true@) or disabled (@false@).
--
-- 'estimatedInstanceWarmup', 'scalingPolicy_estimatedInstanceWarmup' - The estimated time, in seconds, until a newly launched instance can
-- contribute to the CloudWatch metrics.
--
-- 'metricAggregationType', 'scalingPolicy_metricAggregationType' - The aggregation type for the CloudWatch metrics. The valid values are
-- @Minimum@, @Maximum@, and @Average@.
--
-- 'minAdjustmentMagnitude', 'scalingPolicy_minAdjustmentMagnitude' - The minimum value to scale by when the adjustment type is
-- @PercentChangeInCapacity@.
--
-- 'minAdjustmentStep', 'scalingPolicy_minAdjustmentStep' - Available for backward compatibility. Use @MinAdjustmentMagnitude@
-- instead.
--
-- 'policyARN', 'scalingPolicy_policyARN' - The Amazon Resource Name (ARN) of the policy.
--
-- 'policyName', 'scalingPolicy_policyName' - The name of the scaling policy.
--
-- 'policyType', 'scalingPolicy_policyType' - One of the following policy types:
--
-- -   @TargetTrackingScaling@
--
-- -   @StepScaling@
--
-- -   @SimpleScaling@ (default)
--
-- -   @PredictiveScaling@
--
-- For more information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/as-scaling-target-tracking.html Target tracking scaling policies>
-- and
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/as-scaling-simple-step.html Step and simple scaling policies>
-- in the /Amazon EC2 Auto Scaling User Guide/.
--
-- 'predictiveScalingConfiguration', 'scalingPolicy_predictiveScalingConfiguration' - A predictive scaling policy.
--
-- 'scalingAdjustment', 'scalingPolicy_scalingAdjustment' - The amount by which to scale, based on the specified adjustment type. A
-- positive value adds to the current capacity while a negative number
-- removes from the current capacity.
--
-- 'stepAdjustments', 'scalingPolicy_stepAdjustments' - A set of adjustments that enable you to scale based on the size of the
-- alarm breach.
--
-- 'targetTrackingConfiguration', 'scalingPolicy_targetTrackingConfiguration' - A target tracking scaling policy.
newScalingPolicy ::
  ScalingPolicy
newScalingPolicy :: ScalingPolicy
newScalingPolicy =
  ScalingPolicy'
    { $sel:adjustmentType:ScalingPolicy' :: Maybe Text
adjustmentType = forall a. Maybe a
Prelude.Nothing,
      $sel:alarms:ScalingPolicy' :: Maybe [Alarm]
alarms = forall a. Maybe a
Prelude.Nothing,
      $sel:autoScalingGroupName:ScalingPolicy' :: Maybe Text
autoScalingGroupName = forall a. Maybe a
Prelude.Nothing,
      $sel:cooldown:ScalingPolicy' :: Maybe Int
cooldown = forall a. Maybe a
Prelude.Nothing,
      $sel:enabled:ScalingPolicy' :: Maybe Bool
enabled = forall a. Maybe a
Prelude.Nothing,
      $sel:estimatedInstanceWarmup:ScalingPolicy' :: Maybe Int
estimatedInstanceWarmup = forall a. Maybe a
Prelude.Nothing,
      $sel:metricAggregationType:ScalingPolicy' :: Maybe Text
metricAggregationType = forall a. Maybe a
Prelude.Nothing,
      $sel:minAdjustmentMagnitude:ScalingPolicy' :: Maybe Int
minAdjustmentMagnitude = forall a. Maybe a
Prelude.Nothing,
      $sel:minAdjustmentStep:ScalingPolicy' :: Maybe Int
minAdjustmentStep = forall a. Maybe a
Prelude.Nothing,
      $sel:policyARN:ScalingPolicy' :: Maybe Text
policyARN = forall a. Maybe a
Prelude.Nothing,
      $sel:policyName:ScalingPolicy' :: Maybe Text
policyName = forall a. Maybe a
Prelude.Nothing,
      $sel:policyType:ScalingPolicy' :: Maybe Text
policyType = forall a. Maybe a
Prelude.Nothing,
      $sel:predictiveScalingConfiguration:ScalingPolicy' :: Maybe PredictiveScalingConfiguration
predictiveScalingConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:scalingAdjustment:ScalingPolicy' :: Maybe Int
scalingAdjustment = forall a. Maybe a
Prelude.Nothing,
      $sel:stepAdjustments:ScalingPolicy' :: Maybe [StepAdjustment]
stepAdjustments = forall a. Maybe a
Prelude.Nothing,
      $sel:targetTrackingConfiguration:ScalingPolicy' :: Maybe TargetTrackingConfiguration
targetTrackingConfiguration = forall a. Maybe a
Prelude.Nothing
    }

-- | Specifies how the scaling adjustment is interpreted (for example, an
-- absolute number or a percentage). The valid values are
-- @ChangeInCapacity@, @ExactCapacity@, and @PercentChangeInCapacity@.
scalingPolicy_adjustmentType :: Lens.Lens' ScalingPolicy (Prelude.Maybe Prelude.Text)
scalingPolicy_adjustmentType :: Lens' ScalingPolicy (Maybe Text)
scalingPolicy_adjustmentType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ScalingPolicy' {Maybe Text
adjustmentType :: Maybe Text
$sel:adjustmentType:ScalingPolicy' :: ScalingPolicy -> Maybe Text
adjustmentType} -> Maybe Text
adjustmentType) (\s :: ScalingPolicy
s@ScalingPolicy' {} Maybe Text
a -> ScalingPolicy
s {$sel:adjustmentType:ScalingPolicy' :: Maybe Text
adjustmentType = Maybe Text
a} :: ScalingPolicy)

-- | The CloudWatch alarms related to the policy.
scalingPolicy_alarms :: Lens.Lens' ScalingPolicy (Prelude.Maybe [Alarm])
scalingPolicy_alarms :: Lens' ScalingPolicy (Maybe [Alarm])
scalingPolicy_alarms = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ScalingPolicy' {Maybe [Alarm]
alarms :: Maybe [Alarm]
$sel:alarms:ScalingPolicy' :: ScalingPolicy -> Maybe [Alarm]
alarms} -> Maybe [Alarm]
alarms) (\s :: ScalingPolicy
s@ScalingPolicy' {} Maybe [Alarm]
a -> ScalingPolicy
s {$sel:alarms:ScalingPolicy' :: Maybe [Alarm]
alarms = Maybe [Alarm]
a} :: ScalingPolicy) 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.
scalingPolicy_autoScalingGroupName :: Lens.Lens' ScalingPolicy (Prelude.Maybe Prelude.Text)
scalingPolicy_autoScalingGroupName :: Lens' ScalingPolicy (Maybe Text)
scalingPolicy_autoScalingGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ScalingPolicy' {Maybe Text
autoScalingGroupName :: Maybe Text
$sel:autoScalingGroupName:ScalingPolicy' :: ScalingPolicy -> Maybe Text
autoScalingGroupName} -> Maybe Text
autoScalingGroupName) (\s :: ScalingPolicy
s@ScalingPolicy' {} Maybe Text
a -> ScalingPolicy
s {$sel:autoScalingGroupName:ScalingPolicy' :: Maybe Text
autoScalingGroupName = Maybe Text
a} :: ScalingPolicy)

-- | The duration of the policy\'s cooldown period, in seconds.
scalingPolicy_cooldown :: Lens.Lens' ScalingPolicy (Prelude.Maybe Prelude.Int)
scalingPolicy_cooldown :: Lens' ScalingPolicy (Maybe Int)
scalingPolicy_cooldown = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ScalingPolicy' {Maybe Int
cooldown :: Maybe Int
$sel:cooldown:ScalingPolicy' :: ScalingPolicy -> Maybe Int
cooldown} -> Maybe Int
cooldown) (\s :: ScalingPolicy
s@ScalingPolicy' {} Maybe Int
a -> ScalingPolicy
s {$sel:cooldown:ScalingPolicy' :: Maybe Int
cooldown = Maybe Int
a} :: ScalingPolicy)

-- | Indicates whether the policy is enabled (@true@) or disabled (@false@).
scalingPolicy_enabled :: Lens.Lens' ScalingPolicy (Prelude.Maybe Prelude.Bool)
scalingPolicy_enabled :: Lens' ScalingPolicy (Maybe Bool)
scalingPolicy_enabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ScalingPolicy' {Maybe Bool
enabled :: Maybe Bool
$sel:enabled:ScalingPolicy' :: ScalingPolicy -> Maybe Bool
enabled} -> Maybe Bool
enabled) (\s :: ScalingPolicy
s@ScalingPolicy' {} Maybe Bool
a -> ScalingPolicy
s {$sel:enabled:ScalingPolicy' :: Maybe Bool
enabled = Maybe Bool
a} :: ScalingPolicy)

-- | The estimated time, in seconds, until a newly launched instance can
-- contribute to the CloudWatch metrics.
scalingPolicy_estimatedInstanceWarmup :: Lens.Lens' ScalingPolicy (Prelude.Maybe Prelude.Int)
scalingPolicy_estimatedInstanceWarmup :: Lens' ScalingPolicy (Maybe Int)
scalingPolicy_estimatedInstanceWarmup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ScalingPolicy' {Maybe Int
estimatedInstanceWarmup :: Maybe Int
$sel:estimatedInstanceWarmup:ScalingPolicy' :: ScalingPolicy -> Maybe Int
estimatedInstanceWarmup} -> Maybe Int
estimatedInstanceWarmup) (\s :: ScalingPolicy
s@ScalingPolicy' {} Maybe Int
a -> ScalingPolicy
s {$sel:estimatedInstanceWarmup:ScalingPolicy' :: Maybe Int
estimatedInstanceWarmup = Maybe Int
a} :: ScalingPolicy)

-- | The aggregation type for the CloudWatch metrics. The valid values are
-- @Minimum@, @Maximum@, and @Average@.
scalingPolicy_metricAggregationType :: Lens.Lens' ScalingPolicy (Prelude.Maybe Prelude.Text)
scalingPolicy_metricAggregationType :: Lens' ScalingPolicy (Maybe Text)
scalingPolicy_metricAggregationType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ScalingPolicy' {Maybe Text
metricAggregationType :: Maybe Text
$sel:metricAggregationType:ScalingPolicy' :: ScalingPolicy -> Maybe Text
metricAggregationType} -> Maybe Text
metricAggregationType) (\s :: ScalingPolicy
s@ScalingPolicy' {} Maybe Text
a -> ScalingPolicy
s {$sel:metricAggregationType:ScalingPolicy' :: Maybe Text
metricAggregationType = Maybe Text
a} :: ScalingPolicy)

-- | The minimum value to scale by when the adjustment type is
-- @PercentChangeInCapacity@.
scalingPolicy_minAdjustmentMagnitude :: Lens.Lens' ScalingPolicy (Prelude.Maybe Prelude.Int)
scalingPolicy_minAdjustmentMagnitude :: Lens' ScalingPolicy (Maybe Int)
scalingPolicy_minAdjustmentMagnitude = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ScalingPolicy' {Maybe Int
minAdjustmentMagnitude :: Maybe Int
$sel:minAdjustmentMagnitude:ScalingPolicy' :: ScalingPolicy -> Maybe Int
minAdjustmentMagnitude} -> Maybe Int
minAdjustmentMagnitude) (\s :: ScalingPolicy
s@ScalingPolicy' {} Maybe Int
a -> ScalingPolicy
s {$sel:minAdjustmentMagnitude:ScalingPolicy' :: Maybe Int
minAdjustmentMagnitude = Maybe Int
a} :: ScalingPolicy)

-- | Available for backward compatibility. Use @MinAdjustmentMagnitude@
-- instead.
scalingPolicy_minAdjustmentStep :: Lens.Lens' ScalingPolicy (Prelude.Maybe Prelude.Int)
scalingPolicy_minAdjustmentStep :: Lens' ScalingPolicy (Maybe Int)
scalingPolicy_minAdjustmentStep = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ScalingPolicy' {Maybe Int
minAdjustmentStep :: Maybe Int
$sel:minAdjustmentStep:ScalingPolicy' :: ScalingPolicy -> Maybe Int
minAdjustmentStep} -> Maybe Int
minAdjustmentStep) (\s :: ScalingPolicy
s@ScalingPolicy' {} Maybe Int
a -> ScalingPolicy
s {$sel:minAdjustmentStep:ScalingPolicy' :: Maybe Int
minAdjustmentStep = Maybe Int
a} :: ScalingPolicy)

-- | The Amazon Resource Name (ARN) of the policy.
scalingPolicy_policyARN :: Lens.Lens' ScalingPolicy (Prelude.Maybe Prelude.Text)
scalingPolicy_policyARN :: Lens' ScalingPolicy (Maybe Text)
scalingPolicy_policyARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ScalingPolicy' {Maybe Text
policyARN :: Maybe Text
$sel:policyARN:ScalingPolicy' :: ScalingPolicy -> Maybe Text
policyARN} -> Maybe Text
policyARN) (\s :: ScalingPolicy
s@ScalingPolicy' {} Maybe Text
a -> ScalingPolicy
s {$sel:policyARN:ScalingPolicy' :: Maybe Text
policyARN = Maybe Text
a} :: ScalingPolicy)

-- | The name of the scaling policy.
scalingPolicy_policyName :: Lens.Lens' ScalingPolicy (Prelude.Maybe Prelude.Text)
scalingPolicy_policyName :: Lens' ScalingPolicy (Maybe Text)
scalingPolicy_policyName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ScalingPolicy' {Maybe Text
policyName :: Maybe Text
$sel:policyName:ScalingPolicy' :: ScalingPolicy -> Maybe Text
policyName} -> Maybe Text
policyName) (\s :: ScalingPolicy
s@ScalingPolicy' {} Maybe Text
a -> ScalingPolicy
s {$sel:policyName:ScalingPolicy' :: Maybe Text
policyName = Maybe Text
a} :: ScalingPolicy)

-- | One of the following policy types:
--
-- -   @TargetTrackingScaling@
--
-- -   @StepScaling@
--
-- -   @SimpleScaling@ (default)
--
-- -   @PredictiveScaling@
--
-- For more information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/as-scaling-target-tracking.html Target tracking scaling policies>
-- and
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/as-scaling-simple-step.html Step and simple scaling policies>
-- in the /Amazon EC2 Auto Scaling User Guide/.
scalingPolicy_policyType :: Lens.Lens' ScalingPolicy (Prelude.Maybe Prelude.Text)
scalingPolicy_policyType :: Lens' ScalingPolicy (Maybe Text)
scalingPolicy_policyType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ScalingPolicy' {Maybe Text
policyType :: Maybe Text
$sel:policyType:ScalingPolicy' :: ScalingPolicy -> Maybe Text
policyType} -> Maybe Text
policyType) (\s :: ScalingPolicy
s@ScalingPolicy' {} Maybe Text
a -> ScalingPolicy
s {$sel:policyType:ScalingPolicy' :: Maybe Text
policyType = Maybe Text
a} :: ScalingPolicy)

-- | A predictive scaling policy.
scalingPolicy_predictiveScalingConfiguration :: Lens.Lens' ScalingPolicy (Prelude.Maybe PredictiveScalingConfiguration)
scalingPolicy_predictiveScalingConfiguration :: Lens' ScalingPolicy (Maybe PredictiveScalingConfiguration)
scalingPolicy_predictiveScalingConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ScalingPolicy' {Maybe PredictiveScalingConfiguration
predictiveScalingConfiguration :: Maybe PredictiveScalingConfiguration
$sel:predictiveScalingConfiguration:ScalingPolicy' :: ScalingPolicy -> Maybe PredictiveScalingConfiguration
predictiveScalingConfiguration} -> Maybe PredictiveScalingConfiguration
predictiveScalingConfiguration) (\s :: ScalingPolicy
s@ScalingPolicy' {} Maybe PredictiveScalingConfiguration
a -> ScalingPolicy
s {$sel:predictiveScalingConfiguration:ScalingPolicy' :: Maybe PredictiveScalingConfiguration
predictiveScalingConfiguration = Maybe PredictiveScalingConfiguration
a} :: ScalingPolicy)

-- | The amount by which to scale, based on the specified adjustment type. A
-- positive value adds to the current capacity while a negative number
-- removes from the current capacity.
scalingPolicy_scalingAdjustment :: Lens.Lens' ScalingPolicy (Prelude.Maybe Prelude.Int)
scalingPolicy_scalingAdjustment :: Lens' ScalingPolicy (Maybe Int)
scalingPolicy_scalingAdjustment = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ScalingPolicy' {Maybe Int
scalingAdjustment :: Maybe Int
$sel:scalingAdjustment:ScalingPolicy' :: ScalingPolicy -> Maybe Int
scalingAdjustment} -> Maybe Int
scalingAdjustment) (\s :: ScalingPolicy
s@ScalingPolicy' {} Maybe Int
a -> ScalingPolicy
s {$sel:scalingAdjustment:ScalingPolicy' :: Maybe Int
scalingAdjustment = Maybe Int
a} :: ScalingPolicy)

-- | A set of adjustments that enable you to scale based on the size of the
-- alarm breach.
scalingPolicy_stepAdjustments :: Lens.Lens' ScalingPolicy (Prelude.Maybe [StepAdjustment])
scalingPolicy_stepAdjustments :: Lens' ScalingPolicy (Maybe [StepAdjustment])
scalingPolicy_stepAdjustments = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ScalingPolicy' {Maybe [StepAdjustment]
stepAdjustments :: Maybe [StepAdjustment]
$sel:stepAdjustments:ScalingPolicy' :: ScalingPolicy -> Maybe [StepAdjustment]
stepAdjustments} -> Maybe [StepAdjustment]
stepAdjustments) (\s :: ScalingPolicy
s@ScalingPolicy' {} Maybe [StepAdjustment]
a -> ScalingPolicy
s {$sel:stepAdjustments:ScalingPolicy' :: Maybe [StepAdjustment]
stepAdjustments = Maybe [StepAdjustment]
a} :: ScalingPolicy) 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

-- | A target tracking scaling policy.
scalingPolicy_targetTrackingConfiguration :: Lens.Lens' ScalingPolicy (Prelude.Maybe TargetTrackingConfiguration)
scalingPolicy_targetTrackingConfiguration :: Lens' ScalingPolicy (Maybe TargetTrackingConfiguration)
scalingPolicy_targetTrackingConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ScalingPolicy' {Maybe TargetTrackingConfiguration
targetTrackingConfiguration :: Maybe TargetTrackingConfiguration
$sel:targetTrackingConfiguration:ScalingPolicy' :: ScalingPolicy -> Maybe TargetTrackingConfiguration
targetTrackingConfiguration} -> Maybe TargetTrackingConfiguration
targetTrackingConfiguration) (\s :: ScalingPolicy
s@ScalingPolicy' {} Maybe TargetTrackingConfiguration
a -> ScalingPolicy
s {$sel:targetTrackingConfiguration:ScalingPolicy' :: Maybe TargetTrackingConfiguration
targetTrackingConfiguration = Maybe TargetTrackingConfiguration
a} :: ScalingPolicy)

instance Data.FromXML ScalingPolicy where
  parseXML :: [Node] -> Either String ScalingPolicy
parseXML [Node]
x =
    Maybe Text
-> Maybe [Alarm]
-> Maybe Text
-> Maybe Int
-> Maybe Bool
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PredictiveScalingConfiguration
-> Maybe Int
-> Maybe [StepAdjustment]
-> Maybe TargetTrackingConfiguration
-> ScalingPolicy
ScalingPolicy'
      forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"AdjustmentType")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Alarms"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"AutoScalingGroupName")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Cooldown")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Enabled")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"EstimatedInstanceWarmup")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"MetricAggregationType")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"MinAdjustmentMagnitude")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"MinAdjustmentStep")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"PolicyARN")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"PolicyName")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"PolicyType")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"PredictiveScalingConfiguration")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ScalingAdjustment")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"StepAdjustments"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"TargetTrackingConfiguration")

instance Prelude.Hashable ScalingPolicy where
  hashWithSalt :: Int -> ScalingPolicy -> Int
hashWithSalt Int
_salt ScalingPolicy' {Maybe Bool
Maybe Int
Maybe [Alarm]
Maybe [StepAdjustment]
Maybe Text
Maybe PredictiveScalingConfiguration
Maybe TargetTrackingConfiguration
targetTrackingConfiguration :: Maybe TargetTrackingConfiguration
stepAdjustments :: Maybe [StepAdjustment]
scalingAdjustment :: Maybe Int
predictiveScalingConfiguration :: Maybe PredictiveScalingConfiguration
policyType :: Maybe Text
policyName :: Maybe Text
policyARN :: Maybe Text
minAdjustmentStep :: Maybe Int
minAdjustmentMagnitude :: Maybe Int
metricAggregationType :: Maybe Text
estimatedInstanceWarmup :: Maybe Int
enabled :: Maybe Bool
cooldown :: Maybe Int
autoScalingGroupName :: Maybe Text
alarms :: Maybe [Alarm]
adjustmentType :: Maybe Text
$sel:targetTrackingConfiguration:ScalingPolicy' :: ScalingPolicy -> Maybe TargetTrackingConfiguration
$sel:stepAdjustments:ScalingPolicy' :: ScalingPolicy -> Maybe [StepAdjustment]
$sel:scalingAdjustment:ScalingPolicy' :: ScalingPolicy -> Maybe Int
$sel:predictiveScalingConfiguration:ScalingPolicy' :: ScalingPolicy -> Maybe PredictiveScalingConfiguration
$sel:policyType:ScalingPolicy' :: ScalingPolicy -> Maybe Text
$sel:policyName:ScalingPolicy' :: ScalingPolicy -> Maybe Text
$sel:policyARN:ScalingPolicy' :: ScalingPolicy -> Maybe Text
$sel:minAdjustmentStep:ScalingPolicy' :: ScalingPolicy -> Maybe Int
$sel:minAdjustmentMagnitude:ScalingPolicy' :: ScalingPolicy -> Maybe Int
$sel:metricAggregationType:ScalingPolicy' :: ScalingPolicy -> Maybe Text
$sel:estimatedInstanceWarmup:ScalingPolicy' :: ScalingPolicy -> Maybe Int
$sel:enabled:ScalingPolicy' :: ScalingPolicy -> Maybe Bool
$sel:cooldown:ScalingPolicy' :: ScalingPolicy -> Maybe Int
$sel:autoScalingGroupName:ScalingPolicy' :: ScalingPolicy -> Maybe Text
$sel:alarms:ScalingPolicy' :: ScalingPolicy -> Maybe [Alarm]
$sel:adjustmentType:ScalingPolicy' :: ScalingPolicy -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
adjustmentType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Alarm]
alarms
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
autoScalingGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
cooldown
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
enabled
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
estimatedInstanceWarmup
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
metricAggregationType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
minAdjustmentMagnitude
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
minAdjustmentStep
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
policyARN
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
policyName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
policyType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe PredictiveScalingConfiguration
predictiveScalingConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
scalingAdjustment
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [StepAdjustment]
stepAdjustments
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TargetTrackingConfiguration
targetTrackingConfiguration

instance Prelude.NFData ScalingPolicy where
  rnf :: ScalingPolicy -> ()
rnf ScalingPolicy' {Maybe Bool
Maybe Int
Maybe [Alarm]
Maybe [StepAdjustment]
Maybe Text
Maybe PredictiveScalingConfiguration
Maybe TargetTrackingConfiguration
targetTrackingConfiguration :: Maybe TargetTrackingConfiguration
stepAdjustments :: Maybe [StepAdjustment]
scalingAdjustment :: Maybe Int
predictiveScalingConfiguration :: Maybe PredictiveScalingConfiguration
policyType :: Maybe Text
policyName :: Maybe Text
policyARN :: Maybe Text
minAdjustmentStep :: Maybe Int
minAdjustmentMagnitude :: Maybe Int
metricAggregationType :: Maybe Text
estimatedInstanceWarmup :: Maybe Int
enabled :: Maybe Bool
cooldown :: Maybe Int
autoScalingGroupName :: Maybe Text
alarms :: Maybe [Alarm]
adjustmentType :: Maybe Text
$sel:targetTrackingConfiguration:ScalingPolicy' :: ScalingPolicy -> Maybe TargetTrackingConfiguration
$sel:stepAdjustments:ScalingPolicy' :: ScalingPolicy -> Maybe [StepAdjustment]
$sel:scalingAdjustment:ScalingPolicy' :: ScalingPolicy -> Maybe Int
$sel:predictiveScalingConfiguration:ScalingPolicy' :: ScalingPolicy -> Maybe PredictiveScalingConfiguration
$sel:policyType:ScalingPolicy' :: ScalingPolicy -> Maybe Text
$sel:policyName:ScalingPolicy' :: ScalingPolicy -> Maybe Text
$sel:policyARN:ScalingPolicy' :: ScalingPolicy -> Maybe Text
$sel:minAdjustmentStep:ScalingPolicy' :: ScalingPolicy -> Maybe Int
$sel:minAdjustmentMagnitude:ScalingPolicy' :: ScalingPolicy -> Maybe Int
$sel:metricAggregationType:ScalingPolicy' :: ScalingPolicy -> Maybe Text
$sel:estimatedInstanceWarmup:ScalingPolicy' :: ScalingPolicy -> Maybe Int
$sel:enabled:ScalingPolicy' :: ScalingPolicy -> Maybe Bool
$sel:cooldown:ScalingPolicy' :: ScalingPolicy -> Maybe Int
$sel:autoScalingGroupName:ScalingPolicy' :: ScalingPolicy -> Maybe Text
$sel:alarms:ScalingPolicy' :: ScalingPolicy -> Maybe [Alarm]
$sel:adjustmentType:ScalingPolicy' :: ScalingPolicy -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
adjustmentType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Alarm]
alarms
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
autoScalingGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
cooldown
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
enabled
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
estimatedInstanceWarmup
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
metricAggregationType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
minAdjustmentMagnitude
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
minAdjustmentStep
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
policyARN
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
policyName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
policyType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe PredictiveScalingConfiguration
predictiveScalingConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
scalingAdjustment
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [StepAdjustment]
stepAdjustments
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe TargetTrackingConfiguration
targetTrackingConfiguration