{-# 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.PredictiveScalingConfiguration
-- 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.PredictiveScalingConfiguration where

import Amazonka.AutoScaling.Types.PredictiveScalingMaxCapacityBreachBehavior
import Amazonka.AutoScaling.Types.PredictiveScalingMetricSpecification
import Amazonka.AutoScaling.Types.PredictiveScalingMode
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

-- | Represents a predictive scaling policy configuration to use with Amazon
-- EC2 Auto Scaling.
--
-- /See:/ 'newPredictiveScalingConfiguration' smart constructor.
data PredictiveScalingConfiguration = PredictiveScalingConfiguration'
  { -- | Defines the behavior that should be applied if the forecast capacity
    -- approaches or exceeds the maximum capacity of the Auto Scaling group.
    -- Defaults to @HonorMaxCapacity@ if not specified.
    --
    -- The following are possible values:
    --
    -- -   @HonorMaxCapacity@ - Amazon EC2 Auto Scaling cannot scale out
    --     capacity higher than the maximum capacity. The maximum capacity is
    --     enforced as a hard limit.
    --
    -- -   @IncreaseMaxCapacity@ - Amazon EC2 Auto Scaling can scale out
    --     capacity higher than the maximum capacity when the forecast capacity
    --     is close to or exceeds the maximum capacity. The upper limit is
    --     determined by the forecasted capacity and the value for
    --     @MaxCapacityBuffer@.
    PredictiveScalingConfiguration
-> Maybe PredictiveScalingMaxCapacityBreachBehavior
maxCapacityBreachBehavior :: Prelude.Maybe PredictiveScalingMaxCapacityBreachBehavior,
    -- | The size of the capacity buffer to use when the forecast capacity is
    -- close to or exceeds the maximum capacity. The value is specified as a
    -- percentage relative to the forecast capacity. For example, if the buffer
    -- is 10, this means a 10 percent buffer, such that if the forecast
    -- capacity is 50, and the maximum capacity is 40, then the effective
    -- maximum capacity is 55.
    --
    -- If set to 0, Amazon EC2 Auto Scaling may scale capacity higher than the
    -- maximum capacity to equal but not exceed forecast capacity.
    --
    -- Required if the @MaxCapacityBreachBehavior@ property is set to
    -- @IncreaseMaxCapacity@, and cannot be used otherwise.
    PredictiveScalingConfiguration -> Maybe Natural
maxCapacityBuffer :: Prelude.Maybe Prelude.Natural,
    -- | The predictive scaling mode. Defaults to @ForecastOnly@ if not
    -- specified.
    PredictiveScalingConfiguration -> Maybe PredictiveScalingMode
mode :: Prelude.Maybe PredictiveScalingMode,
    -- | The amount of time, in seconds, by which the instance launch time can be
    -- advanced. For example, the forecast says to add capacity at 10:00 AM,
    -- and you choose to pre-launch instances by 5 minutes. In that case, the
    -- instances will be launched at 9:55 AM. The intention is to give
    -- resources time to be provisioned. It can take a few minutes to launch an
    -- EC2 instance. The actual amount of time required depends on several
    -- factors, such as the size of the instance and whether there are startup
    -- scripts to complete.
    --
    -- The value must be less than the forecast interval duration of 3600
    -- seconds (60 minutes). Defaults to 300 seconds if not specified.
    PredictiveScalingConfiguration -> Maybe Natural
schedulingBufferTime :: Prelude.Maybe Prelude.Natural,
    -- | This structure includes the metrics and target utilization to use for
    -- predictive scaling.
    --
    -- This is an array, but we currently only support a single metric
    -- specification. That is, you can specify a target value and a single
    -- metric pair, or a target value and one scaling metric and one load
    -- metric.
    PredictiveScalingConfiguration
-> [PredictiveScalingMetricSpecification]
metricSpecifications :: [PredictiveScalingMetricSpecification]
  }
  deriving (PredictiveScalingConfiguration
-> PredictiveScalingConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PredictiveScalingConfiguration
-> PredictiveScalingConfiguration -> Bool
$c/= :: PredictiveScalingConfiguration
-> PredictiveScalingConfiguration -> Bool
== :: PredictiveScalingConfiguration
-> PredictiveScalingConfiguration -> Bool
$c== :: PredictiveScalingConfiguration
-> PredictiveScalingConfiguration -> Bool
Prelude.Eq, ReadPrec [PredictiveScalingConfiguration]
ReadPrec PredictiveScalingConfiguration
Int -> ReadS PredictiveScalingConfiguration
ReadS [PredictiveScalingConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PredictiveScalingConfiguration]
$creadListPrec :: ReadPrec [PredictiveScalingConfiguration]
readPrec :: ReadPrec PredictiveScalingConfiguration
$creadPrec :: ReadPrec PredictiveScalingConfiguration
readList :: ReadS [PredictiveScalingConfiguration]
$creadList :: ReadS [PredictiveScalingConfiguration]
readsPrec :: Int -> ReadS PredictiveScalingConfiguration
$creadsPrec :: Int -> ReadS PredictiveScalingConfiguration
Prelude.Read, Int -> PredictiveScalingConfiguration -> ShowS
[PredictiveScalingConfiguration] -> ShowS
PredictiveScalingConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PredictiveScalingConfiguration] -> ShowS
$cshowList :: [PredictiveScalingConfiguration] -> ShowS
show :: PredictiveScalingConfiguration -> String
$cshow :: PredictiveScalingConfiguration -> String
showsPrec :: Int -> PredictiveScalingConfiguration -> ShowS
$cshowsPrec :: Int -> PredictiveScalingConfiguration -> ShowS
Prelude.Show, forall x.
Rep PredictiveScalingConfiguration x
-> PredictiveScalingConfiguration
forall x.
PredictiveScalingConfiguration
-> Rep PredictiveScalingConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep PredictiveScalingConfiguration x
-> PredictiveScalingConfiguration
$cfrom :: forall x.
PredictiveScalingConfiguration
-> Rep PredictiveScalingConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'PredictiveScalingConfiguration' 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:
--
-- 'maxCapacityBreachBehavior', 'predictiveScalingConfiguration_maxCapacityBreachBehavior' - Defines the behavior that should be applied if the forecast capacity
-- approaches or exceeds the maximum capacity of the Auto Scaling group.
-- Defaults to @HonorMaxCapacity@ if not specified.
--
-- The following are possible values:
--
-- -   @HonorMaxCapacity@ - Amazon EC2 Auto Scaling cannot scale out
--     capacity higher than the maximum capacity. The maximum capacity is
--     enforced as a hard limit.
--
-- -   @IncreaseMaxCapacity@ - Amazon EC2 Auto Scaling can scale out
--     capacity higher than the maximum capacity when the forecast capacity
--     is close to or exceeds the maximum capacity. The upper limit is
--     determined by the forecasted capacity and the value for
--     @MaxCapacityBuffer@.
--
-- 'maxCapacityBuffer', 'predictiveScalingConfiguration_maxCapacityBuffer' - The size of the capacity buffer to use when the forecast capacity is
-- close to or exceeds the maximum capacity. The value is specified as a
-- percentage relative to the forecast capacity. For example, if the buffer
-- is 10, this means a 10 percent buffer, such that if the forecast
-- capacity is 50, and the maximum capacity is 40, then the effective
-- maximum capacity is 55.
--
-- If set to 0, Amazon EC2 Auto Scaling may scale capacity higher than the
-- maximum capacity to equal but not exceed forecast capacity.
--
-- Required if the @MaxCapacityBreachBehavior@ property is set to
-- @IncreaseMaxCapacity@, and cannot be used otherwise.
--
-- 'mode', 'predictiveScalingConfiguration_mode' - The predictive scaling mode. Defaults to @ForecastOnly@ if not
-- specified.
--
-- 'schedulingBufferTime', 'predictiveScalingConfiguration_schedulingBufferTime' - The amount of time, in seconds, by which the instance launch time can be
-- advanced. For example, the forecast says to add capacity at 10:00 AM,
-- and you choose to pre-launch instances by 5 minutes. In that case, the
-- instances will be launched at 9:55 AM. The intention is to give
-- resources time to be provisioned. It can take a few minutes to launch an
-- EC2 instance. The actual amount of time required depends on several
-- factors, such as the size of the instance and whether there are startup
-- scripts to complete.
--
-- The value must be less than the forecast interval duration of 3600
-- seconds (60 minutes). Defaults to 300 seconds if not specified.
--
-- 'metricSpecifications', 'predictiveScalingConfiguration_metricSpecifications' - This structure includes the metrics and target utilization to use for
-- predictive scaling.
--
-- This is an array, but we currently only support a single metric
-- specification. That is, you can specify a target value and a single
-- metric pair, or a target value and one scaling metric and one load
-- metric.
newPredictiveScalingConfiguration ::
  PredictiveScalingConfiguration
newPredictiveScalingConfiguration :: PredictiveScalingConfiguration
newPredictiveScalingConfiguration =
  PredictiveScalingConfiguration'
    { $sel:maxCapacityBreachBehavior:PredictiveScalingConfiguration' :: Maybe PredictiveScalingMaxCapacityBreachBehavior
maxCapacityBreachBehavior =
        forall a. Maybe a
Prelude.Nothing,
      $sel:maxCapacityBuffer:PredictiveScalingConfiguration' :: Maybe Natural
maxCapacityBuffer = forall a. Maybe a
Prelude.Nothing,
      $sel:mode:PredictiveScalingConfiguration' :: Maybe PredictiveScalingMode
mode = forall a. Maybe a
Prelude.Nothing,
      $sel:schedulingBufferTime:PredictiveScalingConfiguration' :: Maybe Natural
schedulingBufferTime = forall a. Maybe a
Prelude.Nothing,
      $sel:metricSpecifications:PredictiveScalingConfiguration' :: [PredictiveScalingMetricSpecification]
metricSpecifications = forall a. Monoid a => a
Prelude.mempty
    }

-- | Defines the behavior that should be applied if the forecast capacity
-- approaches or exceeds the maximum capacity of the Auto Scaling group.
-- Defaults to @HonorMaxCapacity@ if not specified.
--
-- The following are possible values:
--
-- -   @HonorMaxCapacity@ - Amazon EC2 Auto Scaling cannot scale out
--     capacity higher than the maximum capacity. The maximum capacity is
--     enforced as a hard limit.
--
-- -   @IncreaseMaxCapacity@ - Amazon EC2 Auto Scaling can scale out
--     capacity higher than the maximum capacity when the forecast capacity
--     is close to or exceeds the maximum capacity. The upper limit is
--     determined by the forecasted capacity and the value for
--     @MaxCapacityBuffer@.
predictiveScalingConfiguration_maxCapacityBreachBehavior :: Lens.Lens' PredictiveScalingConfiguration (Prelude.Maybe PredictiveScalingMaxCapacityBreachBehavior)
predictiveScalingConfiguration_maxCapacityBreachBehavior :: Lens'
  PredictiveScalingConfiguration
  (Maybe PredictiveScalingMaxCapacityBreachBehavior)
predictiveScalingConfiguration_maxCapacityBreachBehavior = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PredictiveScalingConfiguration' {Maybe PredictiveScalingMaxCapacityBreachBehavior
maxCapacityBreachBehavior :: Maybe PredictiveScalingMaxCapacityBreachBehavior
$sel:maxCapacityBreachBehavior:PredictiveScalingConfiguration' :: PredictiveScalingConfiguration
-> Maybe PredictiveScalingMaxCapacityBreachBehavior
maxCapacityBreachBehavior} -> Maybe PredictiveScalingMaxCapacityBreachBehavior
maxCapacityBreachBehavior) (\s :: PredictiveScalingConfiguration
s@PredictiveScalingConfiguration' {} Maybe PredictiveScalingMaxCapacityBreachBehavior
a -> PredictiveScalingConfiguration
s {$sel:maxCapacityBreachBehavior:PredictiveScalingConfiguration' :: Maybe PredictiveScalingMaxCapacityBreachBehavior
maxCapacityBreachBehavior = Maybe PredictiveScalingMaxCapacityBreachBehavior
a} :: PredictiveScalingConfiguration)

-- | The size of the capacity buffer to use when the forecast capacity is
-- close to or exceeds the maximum capacity. The value is specified as a
-- percentage relative to the forecast capacity. For example, if the buffer
-- is 10, this means a 10 percent buffer, such that if the forecast
-- capacity is 50, and the maximum capacity is 40, then the effective
-- maximum capacity is 55.
--
-- If set to 0, Amazon EC2 Auto Scaling may scale capacity higher than the
-- maximum capacity to equal but not exceed forecast capacity.
--
-- Required if the @MaxCapacityBreachBehavior@ property is set to
-- @IncreaseMaxCapacity@, and cannot be used otherwise.
predictiveScalingConfiguration_maxCapacityBuffer :: Lens.Lens' PredictiveScalingConfiguration (Prelude.Maybe Prelude.Natural)
predictiveScalingConfiguration_maxCapacityBuffer :: Lens' PredictiveScalingConfiguration (Maybe Natural)
predictiveScalingConfiguration_maxCapacityBuffer = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PredictiveScalingConfiguration' {Maybe Natural
maxCapacityBuffer :: Maybe Natural
$sel:maxCapacityBuffer:PredictiveScalingConfiguration' :: PredictiveScalingConfiguration -> Maybe Natural
maxCapacityBuffer} -> Maybe Natural
maxCapacityBuffer) (\s :: PredictiveScalingConfiguration
s@PredictiveScalingConfiguration' {} Maybe Natural
a -> PredictiveScalingConfiguration
s {$sel:maxCapacityBuffer:PredictiveScalingConfiguration' :: Maybe Natural
maxCapacityBuffer = Maybe Natural
a} :: PredictiveScalingConfiguration)

-- | The predictive scaling mode. Defaults to @ForecastOnly@ if not
-- specified.
predictiveScalingConfiguration_mode :: Lens.Lens' PredictiveScalingConfiguration (Prelude.Maybe PredictiveScalingMode)
predictiveScalingConfiguration_mode :: Lens' PredictiveScalingConfiguration (Maybe PredictiveScalingMode)
predictiveScalingConfiguration_mode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PredictiveScalingConfiguration' {Maybe PredictiveScalingMode
mode :: Maybe PredictiveScalingMode
$sel:mode:PredictiveScalingConfiguration' :: PredictiveScalingConfiguration -> Maybe PredictiveScalingMode
mode} -> Maybe PredictiveScalingMode
mode) (\s :: PredictiveScalingConfiguration
s@PredictiveScalingConfiguration' {} Maybe PredictiveScalingMode
a -> PredictiveScalingConfiguration
s {$sel:mode:PredictiveScalingConfiguration' :: Maybe PredictiveScalingMode
mode = Maybe PredictiveScalingMode
a} :: PredictiveScalingConfiguration)

-- | The amount of time, in seconds, by which the instance launch time can be
-- advanced. For example, the forecast says to add capacity at 10:00 AM,
-- and you choose to pre-launch instances by 5 minutes. In that case, the
-- instances will be launched at 9:55 AM. The intention is to give
-- resources time to be provisioned. It can take a few minutes to launch an
-- EC2 instance. The actual amount of time required depends on several
-- factors, such as the size of the instance and whether there are startup
-- scripts to complete.
--
-- The value must be less than the forecast interval duration of 3600
-- seconds (60 minutes). Defaults to 300 seconds if not specified.
predictiveScalingConfiguration_schedulingBufferTime :: Lens.Lens' PredictiveScalingConfiguration (Prelude.Maybe Prelude.Natural)
predictiveScalingConfiguration_schedulingBufferTime :: Lens' PredictiveScalingConfiguration (Maybe Natural)
predictiveScalingConfiguration_schedulingBufferTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PredictiveScalingConfiguration' {Maybe Natural
schedulingBufferTime :: Maybe Natural
$sel:schedulingBufferTime:PredictiveScalingConfiguration' :: PredictiveScalingConfiguration -> Maybe Natural
schedulingBufferTime} -> Maybe Natural
schedulingBufferTime) (\s :: PredictiveScalingConfiguration
s@PredictiveScalingConfiguration' {} Maybe Natural
a -> PredictiveScalingConfiguration
s {$sel:schedulingBufferTime:PredictiveScalingConfiguration' :: Maybe Natural
schedulingBufferTime = Maybe Natural
a} :: PredictiveScalingConfiguration)

-- | This structure includes the metrics and target utilization to use for
-- predictive scaling.
--
-- This is an array, but we currently only support a single metric
-- specification. That is, you can specify a target value and a single
-- metric pair, or a target value and one scaling metric and one load
-- metric.
predictiveScalingConfiguration_metricSpecifications :: Lens.Lens' PredictiveScalingConfiguration [PredictiveScalingMetricSpecification]
predictiveScalingConfiguration_metricSpecifications :: Lens'
  PredictiveScalingConfiguration
  [PredictiveScalingMetricSpecification]
predictiveScalingConfiguration_metricSpecifications = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PredictiveScalingConfiguration' {[PredictiveScalingMetricSpecification]
metricSpecifications :: [PredictiveScalingMetricSpecification]
$sel:metricSpecifications:PredictiveScalingConfiguration' :: PredictiveScalingConfiguration
-> [PredictiveScalingMetricSpecification]
metricSpecifications} -> [PredictiveScalingMetricSpecification]
metricSpecifications) (\s :: PredictiveScalingConfiguration
s@PredictiveScalingConfiguration' {} [PredictiveScalingMetricSpecification]
a -> PredictiveScalingConfiguration
s {$sel:metricSpecifications:PredictiveScalingConfiguration' :: [PredictiveScalingMetricSpecification]
metricSpecifications = [PredictiveScalingMetricSpecification]
a} :: PredictiveScalingConfiguration) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Data.FromXML PredictiveScalingConfiguration where
  parseXML :: [Node] -> Either String PredictiveScalingConfiguration
parseXML [Node]
x =
    Maybe PredictiveScalingMaxCapacityBreachBehavior
-> Maybe Natural
-> Maybe PredictiveScalingMode
-> Maybe Natural
-> [PredictiveScalingMetricSpecification]
-> PredictiveScalingConfiguration
PredictiveScalingConfiguration'
      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
"MaxCapacityBreachBehavior")
      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
"MaxCapacityBuffer")
      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
"Mode")
      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
"SchedulingBufferTime")
      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
"MetricSpecifications"
                      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 a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member"
                  )

instance
  Prelude.Hashable
    PredictiveScalingConfiguration
  where
  hashWithSalt :: Int -> PredictiveScalingConfiguration -> Int
hashWithSalt
    Int
_salt
    PredictiveScalingConfiguration' {[PredictiveScalingMetricSpecification]
Maybe Natural
Maybe PredictiveScalingMaxCapacityBreachBehavior
Maybe PredictiveScalingMode
metricSpecifications :: [PredictiveScalingMetricSpecification]
schedulingBufferTime :: Maybe Natural
mode :: Maybe PredictiveScalingMode
maxCapacityBuffer :: Maybe Natural
maxCapacityBreachBehavior :: Maybe PredictiveScalingMaxCapacityBreachBehavior
$sel:metricSpecifications:PredictiveScalingConfiguration' :: PredictiveScalingConfiguration
-> [PredictiveScalingMetricSpecification]
$sel:schedulingBufferTime:PredictiveScalingConfiguration' :: PredictiveScalingConfiguration -> Maybe Natural
$sel:mode:PredictiveScalingConfiguration' :: PredictiveScalingConfiguration -> Maybe PredictiveScalingMode
$sel:maxCapacityBuffer:PredictiveScalingConfiguration' :: PredictiveScalingConfiguration -> Maybe Natural
$sel:maxCapacityBreachBehavior:PredictiveScalingConfiguration' :: PredictiveScalingConfiguration
-> Maybe PredictiveScalingMaxCapacityBreachBehavior
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe PredictiveScalingMaxCapacityBreachBehavior
maxCapacityBreachBehavior
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxCapacityBuffer
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe PredictiveScalingMode
mode
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
schedulingBufferTime
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [PredictiveScalingMetricSpecification]
metricSpecifications

instance
  Prelude.NFData
    PredictiveScalingConfiguration
  where
  rnf :: PredictiveScalingConfiguration -> ()
rnf PredictiveScalingConfiguration' {[PredictiveScalingMetricSpecification]
Maybe Natural
Maybe PredictiveScalingMaxCapacityBreachBehavior
Maybe PredictiveScalingMode
metricSpecifications :: [PredictiveScalingMetricSpecification]
schedulingBufferTime :: Maybe Natural
mode :: Maybe PredictiveScalingMode
maxCapacityBuffer :: Maybe Natural
maxCapacityBreachBehavior :: Maybe PredictiveScalingMaxCapacityBreachBehavior
$sel:metricSpecifications:PredictiveScalingConfiguration' :: PredictiveScalingConfiguration
-> [PredictiveScalingMetricSpecification]
$sel:schedulingBufferTime:PredictiveScalingConfiguration' :: PredictiveScalingConfiguration -> Maybe Natural
$sel:mode:PredictiveScalingConfiguration' :: PredictiveScalingConfiguration -> Maybe PredictiveScalingMode
$sel:maxCapacityBuffer:PredictiveScalingConfiguration' :: PredictiveScalingConfiguration -> Maybe Natural
$sel:maxCapacityBreachBehavior:PredictiveScalingConfiguration' :: PredictiveScalingConfiguration
-> Maybe PredictiveScalingMaxCapacityBreachBehavior
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe PredictiveScalingMaxCapacityBreachBehavior
maxCapacityBreachBehavior
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxCapacityBuffer
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe PredictiveScalingMode
mode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
schedulingBufferTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [PredictiveScalingMetricSpecification]
metricSpecifications

instance Data.ToQuery PredictiveScalingConfiguration where
  toQuery :: PredictiveScalingConfiguration -> QueryString
toQuery PredictiveScalingConfiguration' {[PredictiveScalingMetricSpecification]
Maybe Natural
Maybe PredictiveScalingMaxCapacityBreachBehavior
Maybe PredictiveScalingMode
metricSpecifications :: [PredictiveScalingMetricSpecification]
schedulingBufferTime :: Maybe Natural
mode :: Maybe PredictiveScalingMode
maxCapacityBuffer :: Maybe Natural
maxCapacityBreachBehavior :: Maybe PredictiveScalingMaxCapacityBreachBehavior
$sel:metricSpecifications:PredictiveScalingConfiguration' :: PredictiveScalingConfiguration
-> [PredictiveScalingMetricSpecification]
$sel:schedulingBufferTime:PredictiveScalingConfiguration' :: PredictiveScalingConfiguration -> Maybe Natural
$sel:mode:PredictiveScalingConfiguration' :: PredictiveScalingConfiguration -> Maybe PredictiveScalingMode
$sel:maxCapacityBuffer:PredictiveScalingConfiguration' :: PredictiveScalingConfiguration -> Maybe Natural
$sel:maxCapacityBreachBehavior:PredictiveScalingConfiguration' :: PredictiveScalingConfiguration
-> Maybe PredictiveScalingMaxCapacityBreachBehavior
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"MaxCapacityBreachBehavior"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe PredictiveScalingMaxCapacityBreachBehavior
maxCapacityBreachBehavior,
        ByteString
"MaxCapacityBuffer" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
maxCapacityBuffer,
        ByteString
"Mode" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe PredictiveScalingMode
mode,
        ByteString
"SchedulingBufferTime" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
schedulingBufferTime,
        ByteString
"MetricSpecifications"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member" [PredictiveScalingMetricSpecification]
metricSpecifications
      ]