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

import Amazonka.AutoScaling.Types.EnabledMetric
import Amazonka.AutoScaling.Types.Instance
import Amazonka.AutoScaling.Types.LaunchTemplateSpecification
import Amazonka.AutoScaling.Types.MixedInstancesPolicy
import Amazonka.AutoScaling.Types.SuspendedProcess
import Amazonka.AutoScaling.Types.TagDescription
import Amazonka.AutoScaling.Types.TrafficSourceIdentifier
import Amazonka.AutoScaling.Types.WarmPoolConfiguration
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 an Auto Scaling group.
--
-- /See:/ 'newAutoScalingGroup' smart constructor.
data AutoScalingGroup = AutoScalingGroup'
  { -- | The Amazon Resource Name (ARN) of the Auto Scaling group.
    AutoScalingGroup -> Maybe Text
autoScalingGroupARN :: Prelude.Maybe Prelude.Text,
    -- | Indicates whether Capacity Rebalancing is enabled.
    AutoScalingGroup -> Maybe Bool
capacityRebalance :: Prelude.Maybe Prelude.Bool,
    -- | Reserved.
    AutoScalingGroup -> Maybe Text
context :: Prelude.Maybe Prelude.Text,
    -- | The duration of the default instance warmup, in seconds.
    AutoScalingGroup -> Maybe Int
defaultInstanceWarmup :: Prelude.Maybe Prelude.Int,
    -- | The unit of measurement for the value specified for desired capacity.
    -- Amazon EC2 Auto Scaling supports @DesiredCapacityType@ for
    -- attribute-based instance type selection only.
    AutoScalingGroup -> Maybe Text
desiredCapacityType :: Prelude.Maybe Prelude.Text,
    -- | The metrics enabled for the group.
    AutoScalingGroup -> Maybe [EnabledMetric]
enabledMetrics :: Prelude.Maybe [EnabledMetric],
    -- | The duration of the health check grace period, in seconds.
    AutoScalingGroup -> Maybe Int
healthCheckGracePeriod :: Prelude.Maybe Prelude.Int,
    -- | The EC2 instances associated with the group.
    AutoScalingGroup -> Maybe [Instance]
instances :: Prelude.Maybe [Instance],
    -- | The name of the associated launch configuration.
    AutoScalingGroup -> Maybe Text
launchConfigurationName :: Prelude.Maybe Prelude.Text,
    -- | The launch template for the group.
    AutoScalingGroup -> Maybe LaunchTemplateSpecification
launchTemplate :: Prelude.Maybe LaunchTemplateSpecification,
    -- | One or more load balancers associated with the group.
    AutoScalingGroup -> Maybe [Text]
loadBalancerNames :: Prelude.Maybe [Prelude.Text],
    -- | The maximum amount of time, in seconds, that an instance can be in
    -- service.
    --
    -- Valid Range: Minimum value of 0.
    AutoScalingGroup -> Maybe Int
maxInstanceLifetime :: Prelude.Maybe Prelude.Int,
    -- | The mixed instances policy for the group.
    AutoScalingGroup -> Maybe MixedInstancesPolicy
mixedInstancesPolicy :: Prelude.Maybe MixedInstancesPolicy,
    -- | Indicates whether newly launched instances are protected from
    -- termination by Amazon EC2 Auto Scaling when scaling in.
    AutoScalingGroup -> Maybe Bool
newInstancesProtectedFromScaleIn' :: Prelude.Maybe Prelude.Bool,
    -- | The name of the placement group into which to launch your instances, if
    -- any.
    AutoScalingGroup -> Maybe Text
placementGroup :: Prelude.Maybe Prelude.Text,
    -- | The predicted capacity of the group when it has a predictive scaling
    -- policy.
    AutoScalingGroup -> Maybe Int
predictedCapacity :: Prelude.Maybe Prelude.Int,
    -- | The Amazon Resource Name (ARN) of the service-linked role that the Auto
    -- Scaling group uses to call other Amazon Web Services on your behalf.
    AutoScalingGroup -> Maybe Text
serviceLinkedRoleARN :: Prelude.Maybe Prelude.Text,
    -- | The current state of the group when the DeleteAutoScalingGroup operation
    -- is in progress.
    AutoScalingGroup -> Maybe Text
status :: Prelude.Maybe Prelude.Text,
    -- | The suspended processes associated with the group.
    AutoScalingGroup -> Maybe [SuspendedProcess]
suspendedProcesses :: Prelude.Maybe [SuspendedProcess],
    -- | The tags for the group.
    AutoScalingGroup -> Maybe [TagDescription]
tags :: Prelude.Maybe [TagDescription],
    -- | The Amazon Resource Names (ARN) of the target groups for your load
    -- balancer.
    AutoScalingGroup -> Maybe [Text]
targetGroupARNs :: Prelude.Maybe [Prelude.Text],
    -- | The termination policies for the group.
    AutoScalingGroup -> Maybe [Text]
terminationPolicies :: Prelude.Maybe [Prelude.Text],
    -- | The unique identifiers of the traffic sources.
    AutoScalingGroup -> Maybe [TrafficSourceIdentifier]
trafficSources :: Prelude.Maybe [TrafficSourceIdentifier],
    -- | One or more subnet IDs, if applicable, separated by commas.
    AutoScalingGroup -> Maybe Text
vPCZoneIdentifier :: Prelude.Maybe Prelude.Text,
    -- | The warm pool for the group.
    AutoScalingGroup -> Maybe WarmPoolConfiguration
warmPoolConfiguration :: Prelude.Maybe WarmPoolConfiguration,
    -- | The current size of the warm pool.
    AutoScalingGroup -> Maybe Int
warmPoolSize :: Prelude.Maybe Prelude.Int,
    -- | The name of the Auto Scaling group.
    AutoScalingGroup -> Text
autoScalingGroupName :: Prelude.Text,
    -- | The minimum size of the group.
    AutoScalingGroup -> Int
minSize :: Prelude.Int,
    -- | The maximum size of the group.
    AutoScalingGroup -> Int
maxSize :: Prelude.Int,
    -- | The desired size of the group.
    AutoScalingGroup -> Int
desiredCapacity :: Prelude.Int,
    -- | The duration of the default cooldown period, in seconds.
    AutoScalingGroup -> Int
defaultCooldown :: Prelude.Int,
    -- | One or more Availability Zones for the group.
    AutoScalingGroup -> [Text]
availabilityZones :: [Prelude.Text],
    -- | Determines whether any additional health checks are performed on the
    -- instances in this group. Amazon EC2 health checks are always on.
    --
    -- The valid values are @EC2@ (default), @ELB@, and @VPC_LATTICE@. The
    -- @VPC_LATTICE@ health check type is reserved for use with VPC Lattice,
    -- which is in preview release and is subject to change.
    AutoScalingGroup -> Text
healthCheckType :: Prelude.Text,
    -- | The date and time the group was created.
    AutoScalingGroup -> ISO8601
createdTime :: Data.ISO8601
  }
  deriving (AutoScalingGroup -> AutoScalingGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AutoScalingGroup -> AutoScalingGroup -> Bool
$c/= :: AutoScalingGroup -> AutoScalingGroup -> Bool
== :: AutoScalingGroup -> AutoScalingGroup -> Bool
$c== :: AutoScalingGroup -> AutoScalingGroup -> Bool
Prelude.Eq, ReadPrec [AutoScalingGroup]
ReadPrec AutoScalingGroup
Int -> ReadS AutoScalingGroup
ReadS [AutoScalingGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AutoScalingGroup]
$creadListPrec :: ReadPrec [AutoScalingGroup]
readPrec :: ReadPrec AutoScalingGroup
$creadPrec :: ReadPrec AutoScalingGroup
readList :: ReadS [AutoScalingGroup]
$creadList :: ReadS [AutoScalingGroup]
readsPrec :: Int -> ReadS AutoScalingGroup
$creadsPrec :: Int -> ReadS AutoScalingGroup
Prelude.Read, Int -> AutoScalingGroup -> ShowS
[AutoScalingGroup] -> ShowS
AutoScalingGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AutoScalingGroup] -> ShowS
$cshowList :: [AutoScalingGroup] -> ShowS
show :: AutoScalingGroup -> String
$cshow :: AutoScalingGroup -> String
showsPrec :: Int -> AutoScalingGroup -> ShowS
$cshowsPrec :: Int -> AutoScalingGroup -> ShowS
Prelude.Show, forall x. Rep AutoScalingGroup x -> AutoScalingGroup
forall x. AutoScalingGroup -> Rep AutoScalingGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AutoScalingGroup x -> AutoScalingGroup
$cfrom :: forall x. AutoScalingGroup -> Rep AutoScalingGroup x
Prelude.Generic)

-- |
-- Create a value of 'AutoScalingGroup' 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:
--
-- 'autoScalingGroupARN', 'autoScalingGroup_autoScalingGroupARN' - The Amazon Resource Name (ARN) of the Auto Scaling group.
--
-- 'capacityRebalance', 'autoScalingGroup_capacityRebalance' - Indicates whether Capacity Rebalancing is enabled.
--
-- 'context', 'autoScalingGroup_context' - Reserved.
--
-- 'defaultInstanceWarmup', 'autoScalingGroup_defaultInstanceWarmup' - The duration of the default instance warmup, in seconds.
--
-- 'desiredCapacityType', 'autoScalingGroup_desiredCapacityType' - The unit of measurement for the value specified for desired capacity.
-- Amazon EC2 Auto Scaling supports @DesiredCapacityType@ for
-- attribute-based instance type selection only.
--
-- 'enabledMetrics', 'autoScalingGroup_enabledMetrics' - The metrics enabled for the group.
--
-- 'healthCheckGracePeriod', 'autoScalingGroup_healthCheckGracePeriod' - The duration of the health check grace period, in seconds.
--
-- 'instances', 'autoScalingGroup_instances' - The EC2 instances associated with the group.
--
-- 'launchConfigurationName', 'autoScalingGroup_launchConfigurationName' - The name of the associated launch configuration.
--
-- 'launchTemplate', 'autoScalingGroup_launchTemplate' - The launch template for the group.
--
-- 'loadBalancerNames', 'autoScalingGroup_loadBalancerNames' - One or more load balancers associated with the group.
--
-- 'maxInstanceLifetime', 'autoScalingGroup_maxInstanceLifetime' - The maximum amount of time, in seconds, that an instance can be in
-- service.
--
-- Valid Range: Minimum value of 0.
--
-- 'mixedInstancesPolicy', 'autoScalingGroup_mixedInstancesPolicy' - The mixed instances policy for the group.
--
-- 'newInstancesProtectedFromScaleIn'', 'autoScalingGroup_newInstancesProtectedFromScaleIn' - Indicates whether newly launched instances are protected from
-- termination by Amazon EC2 Auto Scaling when scaling in.
--
-- 'placementGroup', 'autoScalingGroup_placementGroup' - The name of the placement group into which to launch your instances, if
-- any.
--
-- 'predictedCapacity', 'autoScalingGroup_predictedCapacity' - The predicted capacity of the group when it has a predictive scaling
-- policy.
--
-- 'serviceLinkedRoleARN', 'autoScalingGroup_serviceLinkedRoleARN' - The Amazon Resource Name (ARN) of the service-linked role that the Auto
-- Scaling group uses to call other Amazon Web Services on your behalf.
--
-- 'status', 'autoScalingGroup_status' - The current state of the group when the DeleteAutoScalingGroup operation
-- is in progress.
--
-- 'suspendedProcesses', 'autoScalingGroup_suspendedProcesses' - The suspended processes associated with the group.
--
-- 'tags', 'autoScalingGroup_tags' - The tags for the group.
--
-- 'targetGroupARNs', 'autoScalingGroup_targetGroupARNs' - The Amazon Resource Names (ARN) of the target groups for your load
-- balancer.
--
-- 'terminationPolicies', 'autoScalingGroup_terminationPolicies' - The termination policies for the group.
--
-- 'trafficSources', 'autoScalingGroup_trafficSources' - The unique identifiers of the traffic sources.
--
-- 'vPCZoneIdentifier', 'autoScalingGroup_vPCZoneIdentifier' - One or more subnet IDs, if applicable, separated by commas.
--
-- 'warmPoolConfiguration', 'autoScalingGroup_warmPoolConfiguration' - The warm pool for the group.
--
-- 'warmPoolSize', 'autoScalingGroup_warmPoolSize' - The current size of the warm pool.
--
-- 'autoScalingGroupName', 'autoScalingGroup_autoScalingGroupName' - The name of the Auto Scaling group.
--
-- 'minSize', 'autoScalingGroup_minSize' - The minimum size of the group.
--
-- 'maxSize', 'autoScalingGroup_maxSize' - The maximum size of the group.
--
-- 'desiredCapacity', 'autoScalingGroup_desiredCapacity' - The desired size of the group.
--
-- 'defaultCooldown', 'autoScalingGroup_defaultCooldown' - The duration of the default cooldown period, in seconds.
--
-- 'availabilityZones', 'autoScalingGroup_availabilityZones' - One or more Availability Zones for the group.
--
-- 'healthCheckType', 'autoScalingGroup_healthCheckType' - Determines whether any additional health checks are performed on the
-- instances in this group. Amazon EC2 health checks are always on.
--
-- The valid values are @EC2@ (default), @ELB@, and @VPC_LATTICE@. The
-- @VPC_LATTICE@ health check type is reserved for use with VPC Lattice,
-- which is in preview release and is subject to change.
--
-- 'createdTime', 'autoScalingGroup_createdTime' - The date and time the group was created.
newAutoScalingGroup ::
  -- | 'autoScalingGroupName'
  Prelude.Text ->
  -- | 'minSize'
  Prelude.Int ->
  -- | 'maxSize'
  Prelude.Int ->
  -- | 'desiredCapacity'
  Prelude.Int ->
  -- | 'defaultCooldown'
  Prelude.Int ->
  -- | 'healthCheckType'
  Prelude.Text ->
  -- | 'createdTime'
  Prelude.UTCTime ->
  AutoScalingGroup
newAutoScalingGroup :: Text
-> Int -> Int -> Int -> Int -> Text -> UTCTime -> AutoScalingGroup
newAutoScalingGroup
  Text
pAutoScalingGroupName_
  Int
pMinSize_
  Int
pMaxSize_
  Int
pDesiredCapacity_
  Int
pDefaultCooldown_
  Text
pHealthCheckType_
  UTCTime
pCreatedTime_ =
    AutoScalingGroup'
      { $sel:autoScalingGroupARN:AutoScalingGroup' :: Maybe Text
autoScalingGroupARN =
          forall a. Maybe a
Prelude.Nothing,
        $sel:capacityRebalance:AutoScalingGroup' :: Maybe Bool
capacityRebalance = forall a. Maybe a
Prelude.Nothing,
        $sel:context:AutoScalingGroup' :: Maybe Text
context = forall a. Maybe a
Prelude.Nothing,
        $sel:defaultInstanceWarmup:AutoScalingGroup' :: Maybe Int
defaultInstanceWarmup = forall a. Maybe a
Prelude.Nothing,
        $sel:desiredCapacityType:AutoScalingGroup' :: Maybe Text
desiredCapacityType = forall a. Maybe a
Prelude.Nothing,
        $sel:enabledMetrics:AutoScalingGroup' :: Maybe [EnabledMetric]
enabledMetrics = forall a. Maybe a
Prelude.Nothing,
        $sel:healthCheckGracePeriod:AutoScalingGroup' :: Maybe Int
healthCheckGracePeriod = forall a. Maybe a
Prelude.Nothing,
        $sel:instances:AutoScalingGroup' :: Maybe [Instance]
instances = forall a. Maybe a
Prelude.Nothing,
        $sel:launchConfigurationName:AutoScalingGroup' :: Maybe Text
launchConfigurationName = forall a. Maybe a
Prelude.Nothing,
        $sel:launchTemplate:AutoScalingGroup' :: Maybe LaunchTemplateSpecification
launchTemplate = forall a. Maybe a
Prelude.Nothing,
        $sel:loadBalancerNames:AutoScalingGroup' :: Maybe [Text]
loadBalancerNames = forall a. Maybe a
Prelude.Nothing,
        $sel:maxInstanceLifetime:AutoScalingGroup' :: Maybe Int
maxInstanceLifetime = forall a. Maybe a
Prelude.Nothing,
        $sel:mixedInstancesPolicy:AutoScalingGroup' :: Maybe MixedInstancesPolicy
mixedInstancesPolicy = forall a. Maybe a
Prelude.Nothing,
        $sel:newInstancesProtectedFromScaleIn':AutoScalingGroup' :: Maybe Bool
newInstancesProtectedFromScaleIn' = forall a. Maybe a
Prelude.Nothing,
        $sel:placementGroup:AutoScalingGroup' :: Maybe Text
placementGroup = forall a. Maybe a
Prelude.Nothing,
        $sel:predictedCapacity:AutoScalingGroup' :: Maybe Int
predictedCapacity = forall a. Maybe a
Prelude.Nothing,
        $sel:serviceLinkedRoleARN:AutoScalingGroup' :: Maybe Text
serviceLinkedRoleARN = forall a. Maybe a
Prelude.Nothing,
        $sel:status:AutoScalingGroup' :: Maybe Text
status = forall a. Maybe a
Prelude.Nothing,
        $sel:suspendedProcesses:AutoScalingGroup' :: Maybe [SuspendedProcess]
suspendedProcesses = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:AutoScalingGroup' :: Maybe [TagDescription]
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:targetGroupARNs:AutoScalingGroup' :: Maybe [Text]
targetGroupARNs = forall a. Maybe a
Prelude.Nothing,
        $sel:terminationPolicies:AutoScalingGroup' :: Maybe [Text]
terminationPolicies = forall a. Maybe a
Prelude.Nothing,
        $sel:trafficSources:AutoScalingGroup' :: Maybe [TrafficSourceIdentifier]
trafficSources = forall a. Maybe a
Prelude.Nothing,
        $sel:vPCZoneIdentifier:AutoScalingGroup' :: Maybe Text
vPCZoneIdentifier = forall a. Maybe a
Prelude.Nothing,
        $sel:warmPoolConfiguration:AutoScalingGroup' :: Maybe WarmPoolConfiguration
warmPoolConfiguration = forall a. Maybe a
Prelude.Nothing,
        $sel:warmPoolSize:AutoScalingGroup' :: Maybe Int
warmPoolSize = forall a. Maybe a
Prelude.Nothing,
        $sel:autoScalingGroupName:AutoScalingGroup' :: Text
autoScalingGroupName = Text
pAutoScalingGroupName_,
        $sel:minSize:AutoScalingGroup' :: Int
minSize = Int
pMinSize_,
        $sel:maxSize:AutoScalingGroup' :: Int
maxSize = Int
pMaxSize_,
        $sel:desiredCapacity:AutoScalingGroup' :: Int
desiredCapacity = Int
pDesiredCapacity_,
        $sel:defaultCooldown:AutoScalingGroup' :: Int
defaultCooldown = Int
pDefaultCooldown_,
        $sel:availabilityZones:AutoScalingGroup' :: [Text]
availabilityZones = forall a. Monoid a => a
Prelude.mempty,
        $sel:healthCheckType:AutoScalingGroup' :: Text
healthCheckType = Text
pHealthCheckType_,
        $sel:createdTime:AutoScalingGroup' :: ISO8601
createdTime = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pCreatedTime_
      }

-- | The Amazon Resource Name (ARN) of the Auto Scaling group.
autoScalingGroup_autoScalingGroupARN :: Lens.Lens' AutoScalingGroup (Prelude.Maybe Prelude.Text)
autoScalingGroup_autoScalingGroupARN :: Lens' AutoScalingGroup (Maybe Text)
autoScalingGroup_autoScalingGroupARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingGroup' {Maybe Text
autoScalingGroupARN :: Maybe Text
$sel:autoScalingGroupARN:AutoScalingGroup' :: AutoScalingGroup -> Maybe Text
autoScalingGroupARN} -> Maybe Text
autoScalingGroupARN) (\s :: AutoScalingGroup
s@AutoScalingGroup' {} Maybe Text
a -> AutoScalingGroup
s {$sel:autoScalingGroupARN:AutoScalingGroup' :: Maybe Text
autoScalingGroupARN = Maybe Text
a} :: AutoScalingGroup)

-- | Indicates whether Capacity Rebalancing is enabled.
autoScalingGroup_capacityRebalance :: Lens.Lens' AutoScalingGroup (Prelude.Maybe Prelude.Bool)
autoScalingGroup_capacityRebalance :: Lens' AutoScalingGroup (Maybe Bool)
autoScalingGroup_capacityRebalance = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingGroup' {Maybe Bool
capacityRebalance :: Maybe Bool
$sel:capacityRebalance:AutoScalingGroup' :: AutoScalingGroup -> Maybe Bool
capacityRebalance} -> Maybe Bool
capacityRebalance) (\s :: AutoScalingGroup
s@AutoScalingGroup' {} Maybe Bool
a -> AutoScalingGroup
s {$sel:capacityRebalance:AutoScalingGroup' :: Maybe Bool
capacityRebalance = Maybe Bool
a} :: AutoScalingGroup)

-- | Reserved.
autoScalingGroup_context :: Lens.Lens' AutoScalingGroup (Prelude.Maybe Prelude.Text)
autoScalingGroup_context :: Lens' AutoScalingGroup (Maybe Text)
autoScalingGroup_context = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingGroup' {Maybe Text
context :: Maybe Text
$sel:context:AutoScalingGroup' :: AutoScalingGroup -> Maybe Text
context} -> Maybe Text
context) (\s :: AutoScalingGroup
s@AutoScalingGroup' {} Maybe Text
a -> AutoScalingGroup
s {$sel:context:AutoScalingGroup' :: Maybe Text
context = Maybe Text
a} :: AutoScalingGroup)

-- | The duration of the default instance warmup, in seconds.
autoScalingGroup_defaultInstanceWarmup :: Lens.Lens' AutoScalingGroup (Prelude.Maybe Prelude.Int)
autoScalingGroup_defaultInstanceWarmup :: Lens' AutoScalingGroup (Maybe Int)
autoScalingGroup_defaultInstanceWarmup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingGroup' {Maybe Int
defaultInstanceWarmup :: Maybe Int
$sel:defaultInstanceWarmup:AutoScalingGroup' :: AutoScalingGroup -> Maybe Int
defaultInstanceWarmup} -> Maybe Int
defaultInstanceWarmup) (\s :: AutoScalingGroup
s@AutoScalingGroup' {} Maybe Int
a -> AutoScalingGroup
s {$sel:defaultInstanceWarmup:AutoScalingGroup' :: Maybe Int
defaultInstanceWarmup = Maybe Int
a} :: AutoScalingGroup)

-- | The unit of measurement for the value specified for desired capacity.
-- Amazon EC2 Auto Scaling supports @DesiredCapacityType@ for
-- attribute-based instance type selection only.
autoScalingGroup_desiredCapacityType :: Lens.Lens' AutoScalingGroup (Prelude.Maybe Prelude.Text)
autoScalingGroup_desiredCapacityType :: Lens' AutoScalingGroup (Maybe Text)
autoScalingGroup_desiredCapacityType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingGroup' {Maybe Text
desiredCapacityType :: Maybe Text
$sel:desiredCapacityType:AutoScalingGroup' :: AutoScalingGroup -> Maybe Text
desiredCapacityType} -> Maybe Text
desiredCapacityType) (\s :: AutoScalingGroup
s@AutoScalingGroup' {} Maybe Text
a -> AutoScalingGroup
s {$sel:desiredCapacityType:AutoScalingGroup' :: Maybe Text
desiredCapacityType = Maybe Text
a} :: AutoScalingGroup)

-- | The metrics enabled for the group.
autoScalingGroup_enabledMetrics :: Lens.Lens' AutoScalingGroup (Prelude.Maybe [EnabledMetric])
autoScalingGroup_enabledMetrics :: Lens' AutoScalingGroup (Maybe [EnabledMetric])
autoScalingGroup_enabledMetrics = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingGroup' {Maybe [EnabledMetric]
enabledMetrics :: Maybe [EnabledMetric]
$sel:enabledMetrics:AutoScalingGroup' :: AutoScalingGroup -> Maybe [EnabledMetric]
enabledMetrics} -> Maybe [EnabledMetric]
enabledMetrics) (\s :: AutoScalingGroup
s@AutoScalingGroup' {} Maybe [EnabledMetric]
a -> AutoScalingGroup
s {$sel:enabledMetrics:AutoScalingGroup' :: Maybe [EnabledMetric]
enabledMetrics = Maybe [EnabledMetric]
a} :: AutoScalingGroup) 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 duration of the health check grace period, in seconds.
autoScalingGroup_healthCheckGracePeriod :: Lens.Lens' AutoScalingGroup (Prelude.Maybe Prelude.Int)
autoScalingGroup_healthCheckGracePeriod :: Lens' AutoScalingGroup (Maybe Int)
autoScalingGroup_healthCheckGracePeriod = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingGroup' {Maybe Int
healthCheckGracePeriod :: Maybe Int
$sel:healthCheckGracePeriod:AutoScalingGroup' :: AutoScalingGroup -> Maybe Int
healthCheckGracePeriod} -> Maybe Int
healthCheckGracePeriod) (\s :: AutoScalingGroup
s@AutoScalingGroup' {} Maybe Int
a -> AutoScalingGroup
s {$sel:healthCheckGracePeriod:AutoScalingGroup' :: Maybe Int
healthCheckGracePeriod = Maybe Int
a} :: AutoScalingGroup)

-- | The EC2 instances associated with the group.
autoScalingGroup_instances :: Lens.Lens' AutoScalingGroup (Prelude.Maybe [Instance])
autoScalingGroup_instances :: Lens' AutoScalingGroup (Maybe [Instance])
autoScalingGroup_instances = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingGroup' {Maybe [Instance]
instances :: Maybe [Instance]
$sel:instances:AutoScalingGroup' :: AutoScalingGroup -> Maybe [Instance]
instances} -> Maybe [Instance]
instances) (\s :: AutoScalingGroup
s@AutoScalingGroup' {} Maybe [Instance]
a -> AutoScalingGroup
s {$sel:instances:AutoScalingGroup' :: Maybe [Instance]
instances = Maybe [Instance]
a} :: AutoScalingGroup) 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 associated launch configuration.
autoScalingGroup_launchConfigurationName :: Lens.Lens' AutoScalingGroup (Prelude.Maybe Prelude.Text)
autoScalingGroup_launchConfigurationName :: Lens' AutoScalingGroup (Maybe Text)
autoScalingGroup_launchConfigurationName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingGroup' {Maybe Text
launchConfigurationName :: Maybe Text
$sel:launchConfigurationName:AutoScalingGroup' :: AutoScalingGroup -> Maybe Text
launchConfigurationName} -> Maybe Text
launchConfigurationName) (\s :: AutoScalingGroup
s@AutoScalingGroup' {} Maybe Text
a -> AutoScalingGroup
s {$sel:launchConfigurationName:AutoScalingGroup' :: Maybe Text
launchConfigurationName = Maybe Text
a} :: AutoScalingGroup)

-- | The launch template for the group.
autoScalingGroup_launchTemplate :: Lens.Lens' AutoScalingGroup (Prelude.Maybe LaunchTemplateSpecification)
autoScalingGroup_launchTemplate :: Lens' AutoScalingGroup (Maybe LaunchTemplateSpecification)
autoScalingGroup_launchTemplate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingGroup' {Maybe LaunchTemplateSpecification
launchTemplate :: Maybe LaunchTemplateSpecification
$sel:launchTemplate:AutoScalingGroup' :: AutoScalingGroup -> Maybe LaunchTemplateSpecification
launchTemplate} -> Maybe LaunchTemplateSpecification
launchTemplate) (\s :: AutoScalingGroup
s@AutoScalingGroup' {} Maybe LaunchTemplateSpecification
a -> AutoScalingGroup
s {$sel:launchTemplate:AutoScalingGroup' :: Maybe LaunchTemplateSpecification
launchTemplate = Maybe LaunchTemplateSpecification
a} :: AutoScalingGroup)

-- | One or more load balancers associated with the group.
autoScalingGroup_loadBalancerNames :: Lens.Lens' AutoScalingGroup (Prelude.Maybe [Prelude.Text])
autoScalingGroup_loadBalancerNames :: Lens' AutoScalingGroup (Maybe [Text])
autoScalingGroup_loadBalancerNames = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingGroup' {Maybe [Text]
loadBalancerNames :: Maybe [Text]
$sel:loadBalancerNames:AutoScalingGroup' :: AutoScalingGroup -> Maybe [Text]
loadBalancerNames} -> Maybe [Text]
loadBalancerNames) (\s :: AutoScalingGroup
s@AutoScalingGroup' {} Maybe [Text]
a -> AutoScalingGroup
s {$sel:loadBalancerNames:AutoScalingGroup' :: Maybe [Text]
loadBalancerNames = Maybe [Text]
a} :: AutoScalingGroup) 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 maximum amount of time, in seconds, that an instance can be in
-- service.
--
-- Valid Range: Minimum value of 0.
autoScalingGroup_maxInstanceLifetime :: Lens.Lens' AutoScalingGroup (Prelude.Maybe Prelude.Int)
autoScalingGroup_maxInstanceLifetime :: Lens' AutoScalingGroup (Maybe Int)
autoScalingGroup_maxInstanceLifetime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingGroup' {Maybe Int
maxInstanceLifetime :: Maybe Int
$sel:maxInstanceLifetime:AutoScalingGroup' :: AutoScalingGroup -> Maybe Int
maxInstanceLifetime} -> Maybe Int
maxInstanceLifetime) (\s :: AutoScalingGroup
s@AutoScalingGroup' {} Maybe Int
a -> AutoScalingGroup
s {$sel:maxInstanceLifetime:AutoScalingGroup' :: Maybe Int
maxInstanceLifetime = Maybe Int
a} :: AutoScalingGroup)

-- | The mixed instances policy for the group.
autoScalingGroup_mixedInstancesPolicy :: Lens.Lens' AutoScalingGroup (Prelude.Maybe MixedInstancesPolicy)
autoScalingGroup_mixedInstancesPolicy :: Lens' AutoScalingGroup (Maybe MixedInstancesPolicy)
autoScalingGroup_mixedInstancesPolicy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingGroup' {Maybe MixedInstancesPolicy
mixedInstancesPolicy :: Maybe MixedInstancesPolicy
$sel:mixedInstancesPolicy:AutoScalingGroup' :: AutoScalingGroup -> Maybe MixedInstancesPolicy
mixedInstancesPolicy} -> Maybe MixedInstancesPolicy
mixedInstancesPolicy) (\s :: AutoScalingGroup
s@AutoScalingGroup' {} Maybe MixedInstancesPolicy
a -> AutoScalingGroup
s {$sel:mixedInstancesPolicy:AutoScalingGroup' :: Maybe MixedInstancesPolicy
mixedInstancesPolicy = Maybe MixedInstancesPolicy
a} :: AutoScalingGroup)

-- | Indicates whether newly launched instances are protected from
-- termination by Amazon EC2 Auto Scaling when scaling in.
autoScalingGroup_newInstancesProtectedFromScaleIn :: Lens.Lens' AutoScalingGroup (Prelude.Maybe Prelude.Bool)
autoScalingGroup_newInstancesProtectedFromScaleIn :: Lens' AutoScalingGroup (Maybe Bool)
autoScalingGroup_newInstancesProtectedFromScaleIn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingGroup' {Maybe Bool
newInstancesProtectedFromScaleIn' :: Maybe Bool
$sel:newInstancesProtectedFromScaleIn':AutoScalingGroup' :: AutoScalingGroup -> Maybe Bool
newInstancesProtectedFromScaleIn'} -> Maybe Bool
newInstancesProtectedFromScaleIn') (\s :: AutoScalingGroup
s@AutoScalingGroup' {} Maybe Bool
a -> AutoScalingGroup
s {$sel:newInstancesProtectedFromScaleIn':AutoScalingGroup' :: Maybe Bool
newInstancesProtectedFromScaleIn' = Maybe Bool
a} :: AutoScalingGroup)

-- | The name of the placement group into which to launch your instances, if
-- any.
autoScalingGroup_placementGroup :: Lens.Lens' AutoScalingGroup (Prelude.Maybe Prelude.Text)
autoScalingGroup_placementGroup :: Lens' AutoScalingGroup (Maybe Text)
autoScalingGroup_placementGroup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingGroup' {Maybe Text
placementGroup :: Maybe Text
$sel:placementGroup:AutoScalingGroup' :: AutoScalingGroup -> Maybe Text
placementGroup} -> Maybe Text
placementGroup) (\s :: AutoScalingGroup
s@AutoScalingGroup' {} Maybe Text
a -> AutoScalingGroup
s {$sel:placementGroup:AutoScalingGroup' :: Maybe Text
placementGroup = Maybe Text
a} :: AutoScalingGroup)

-- | The predicted capacity of the group when it has a predictive scaling
-- policy.
autoScalingGroup_predictedCapacity :: Lens.Lens' AutoScalingGroup (Prelude.Maybe Prelude.Int)
autoScalingGroup_predictedCapacity :: Lens' AutoScalingGroup (Maybe Int)
autoScalingGroup_predictedCapacity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingGroup' {Maybe Int
predictedCapacity :: Maybe Int
$sel:predictedCapacity:AutoScalingGroup' :: AutoScalingGroup -> Maybe Int
predictedCapacity} -> Maybe Int
predictedCapacity) (\s :: AutoScalingGroup
s@AutoScalingGroup' {} Maybe Int
a -> AutoScalingGroup
s {$sel:predictedCapacity:AutoScalingGroup' :: Maybe Int
predictedCapacity = Maybe Int
a} :: AutoScalingGroup)

-- | The Amazon Resource Name (ARN) of the service-linked role that the Auto
-- Scaling group uses to call other Amazon Web Services on your behalf.
autoScalingGroup_serviceLinkedRoleARN :: Lens.Lens' AutoScalingGroup (Prelude.Maybe Prelude.Text)
autoScalingGroup_serviceLinkedRoleARN :: Lens' AutoScalingGroup (Maybe Text)
autoScalingGroup_serviceLinkedRoleARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingGroup' {Maybe Text
serviceLinkedRoleARN :: Maybe Text
$sel:serviceLinkedRoleARN:AutoScalingGroup' :: AutoScalingGroup -> Maybe Text
serviceLinkedRoleARN} -> Maybe Text
serviceLinkedRoleARN) (\s :: AutoScalingGroup
s@AutoScalingGroup' {} Maybe Text
a -> AutoScalingGroup
s {$sel:serviceLinkedRoleARN:AutoScalingGroup' :: Maybe Text
serviceLinkedRoleARN = Maybe Text
a} :: AutoScalingGroup)

-- | The current state of the group when the DeleteAutoScalingGroup operation
-- is in progress.
autoScalingGroup_status :: Lens.Lens' AutoScalingGroup (Prelude.Maybe Prelude.Text)
autoScalingGroup_status :: Lens' AutoScalingGroup (Maybe Text)
autoScalingGroup_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingGroup' {Maybe Text
status :: Maybe Text
$sel:status:AutoScalingGroup' :: AutoScalingGroup -> Maybe Text
status} -> Maybe Text
status) (\s :: AutoScalingGroup
s@AutoScalingGroup' {} Maybe Text
a -> AutoScalingGroup
s {$sel:status:AutoScalingGroup' :: Maybe Text
status = Maybe Text
a} :: AutoScalingGroup)

-- | The suspended processes associated with the group.
autoScalingGroup_suspendedProcesses :: Lens.Lens' AutoScalingGroup (Prelude.Maybe [SuspendedProcess])
autoScalingGroup_suspendedProcesses :: Lens' AutoScalingGroup (Maybe [SuspendedProcess])
autoScalingGroup_suspendedProcesses = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingGroup' {Maybe [SuspendedProcess]
suspendedProcesses :: Maybe [SuspendedProcess]
$sel:suspendedProcesses:AutoScalingGroup' :: AutoScalingGroup -> Maybe [SuspendedProcess]
suspendedProcesses} -> Maybe [SuspendedProcess]
suspendedProcesses) (\s :: AutoScalingGroup
s@AutoScalingGroup' {} Maybe [SuspendedProcess]
a -> AutoScalingGroup
s {$sel:suspendedProcesses:AutoScalingGroup' :: Maybe [SuspendedProcess]
suspendedProcesses = Maybe [SuspendedProcess]
a} :: AutoScalingGroup) 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 tags for the group.
autoScalingGroup_tags :: Lens.Lens' AutoScalingGroup (Prelude.Maybe [TagDescription])
autoScalingGroup_tags :: Lens' AutoScalingGroup (Maybe [TagDescription])
autoScalingGroup_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingGroup' {Maybe [TagDescription]
tags :: Maybe [TagDescription]
$sel:tags:AutoScalingGroup' :: AutoScalingGroup -> Maybe [TagDescription]
tags} -> Maybe [TagDescription]
tags) (\s :: AutoScalingGroup
s@AutoScalingGroup' {} Maybe [TagDescription]
a -> AutoScalingGroup
s {$sel:tags:AutoScalingGroup' :: Maybe [TagDescription]
tags = Maybe [TagDescription]
a} :: AutoScalingGroup) 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 Amazon Resource Names (ARN) of the target groups for your load
-- balancer.
autoScalingGroup_targetGroupARNs :: Lens.Lens' AutoScalingGroup (Prelude.Maybe [Prelude.Text])
autoScalingGroup_targetGroupARNs :: Lens' AutoScalingGroup (Maybe [Text])
autoScalingGroup_targetGroupARNs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingGroup' {Maybe [Text]
targetGroupARNs :: Maybe [Text]
$sel:targetGroupARNs:AutoScalingGroup' :: AutoScalingGroup -> Maybe [Text]
targetGroupARNs} -> Maybe [Text]
targetGroupARNs) (\s :: AutoScalingGroup
s@AutoScalingGroup' {} Maybe [Text]
a -> AutoScalingGroup
s {$sel:targetGroupARNs:AutoScalingGroup' :: Maybe [Text]
targetGroupARNs = Maybe [Text]
a} :: AutoScalingGroup) 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 termination policies for the group.
autoScalingGroup_terminationPolicies :: Lens.Lens' AutoScalingGroup (Prelude.Maybe [Prelude.Text])
autoScalingGroup_terminationPolicies :: Lens' AutoScalingGroup (Maybe [Text])
autoScalingGroup_terminationPolicies = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingGroup' {Maybe [Text]
terminationPolicies :: Maybe [Text]
$sel:terminationPolicies:AutoScalingGroup' :: AutoScalingGroup -> Maybe [Text]
terminationPolicies} -> Maybe [Text]
terminationPolicies) (\s :: AutoScalingGroup
s@AutoScalingGroup' {} Maybe [Text]
a -> AutoScalingGroup
s {$sel:terminationPolicies:AutoScalingGroup' :: Maybe [Text]
terminationPolicies = Maybe [Text]
a} :: AutoScalingGroup) 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 unique identifiers of the traffic sources.
autoScalingGroup_trafficSources :: Lens.Lens' AutoScalingGroup (Prelude.Maybe [TrafficSourceIdentifier])
autoScalingGroup_trafficSources :: Lens' AutoScalingGroup (Maybe [TrafficSourceIdentifier])
autoScalingGroup_trafficSources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingGroup' {Maybe [TrafficSourceIdentifier]
trafficSources :: Maybe [TrafficSourceIdentifier]
$sel:trafficSources:AutoScalingGroup' :: AutoScalingGroup -> Maybe [TrafficSourceIdentifier]
trafficSources} -> Maybe [TrafficSourceIdentifier]
trafficSources) (\s :: AutoScalingGroup
s@AutoScalingGroup' {} Maybe [TrafficSourceIdentifier]
a -> AutoScalingGroup
s {$sel:trafficSources:AutoScalingGroup' :: Maybe [TrafficSourceIdentifier]
trafficSources = Maybe [TrafficSourceIdentifier]
a} :: AutoScalingGroup) 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

-- | One or more subnet IDs, if applicable, separated by commas.
autoScalingGroup_vPCZoneIdentifier :: Lens.Lens' AutoScalingGroup (Prelude.Maybe Prelude.Text)
autoScalingGroup_vPCZoneIdentifier :: Lens' AutoScalingGroup (Maybe Text)
autoScalingGroup_vPCZoneIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingGroup' {Maybe Text
vPCZoneIdentifier :: Maybe Text
$sel:vPCZoneIdentifier:AutoScalingGroup' :: AutoScalingGroup -> Maybe Text
vPCZoneIdentifier} -> Maybe Text
vPCZoneIdentifier) (\s :: AutoScalingGroup
s@AutoScalingGroup' {} Maybe Text
a -> AutoScalingGroup
s {$sel:vPCZoneIdentifier:AutoScalingGroup' :: Maybe Text
vPCZoneIdentifier = Maybe Text
a} :: AutoScalingGroup)

-- | The warm pool for the group.
autoScalingGroup_warmPoolConfiguration :: Lens.Lens' AutoScalingGroup (Prelude.Maybe WarmPoolConfiguration)
autoScalingGroup_warmPoolConfiguration :: Lens' AutoScalingGroup (Maybe WarmPoolConfiguration)
autoScalingGroup_warmPoolConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingGroup' {Maybe WarmPoolConfiguration
warmPoolConfiguration :: Maybe WarmPoolConfiguration
$sel:warmPoolConfiguration:AutoScalingGroup' :: AutoScalingGroup -> Maybe WarmPoolConfiguration
warmPoolConfiguration} -> Maybe WarmPoolConfiguration
warmPoolConfiguration) (\s :: AutoScalingGroup
s@AutoScalingGroup' {} Maybe WarmPoolConfiguration
a -> AutoScalingGroup
s {$sel:warmPoolConfiguration:AutoScalingGroup' :: Maybe WarmPoolConfiguration
warmPoolConfiguration = Maybe WarmPoolConfiguration
a} :: AutoScalingGroup)

-- | The current size of the warm pool.
autoScalingGroup_warmPoolSize :: Lens.Lens' AutoScalingGroup (Prelude.Maybe Prelude.Int)
autoScalingGroup_warmPoolSize :: Lens' AutoScalingGroup (Maybe Int)
autoScalingGroup_warmPoolSize = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingGroup' {Maybe Int
warmPoolSize :: Maybe Int
$sel:warmPoolSize:AutoScalingGroup' :: AutoScalingGroup -> Maybe Int
warmPoolSize} -> Maybe Int
warmPoolSize) (\s :: AutoScalingGroup
s@AutoScalingGroup' {} Maybe Int
a -> AutoScalingGroup
s {$sel:warmPoolSize:AutoScalingGroup' :: Maybe Int
warmPoolSize = Maybe Int
a} :: AutoScalingGroup)

-- | The name of the Auto Scaling group.
autoScalingGroup_autoScalingGroupName :: Lens.Lens' AutoScalingGroup Prelude.Text
autoScalingGroup_autoScalingGroupName :: Lens' AutoScalingGroup Text
autoScalingGroup_autoScalingGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingGroup' {Text
autoScalingGroupName :: Text
$sel:autoScalingGroupName:AutoScalingGroup' :: AutoScalingGroup -> Text
autoScalingGroupName} -> Text
autoScalingGroupName) (\s :: AutoScalingGroup
s@AutoScalingGroup' {} Text
a -> AutoScalingGroup
s {$sel:autoScalingGroupName:AutoScalingGroup' :: Text
autoScalingGroupName = Text
a} :: AutoScalingGroup)

-- | The minimum size of the group.
autoScalingGroup_minSize :: Lens.Lens' AutoScalingGroup Prelude.Int
autoScalingGroup_minSize :: Lens' AutoScalingGroup Int
autoScalingGroup_minSize = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingGroup' {Int
minSize :: Int
$sel:minSize:AutoScalingGroup' :: AutoScalingGroup -> Int
minSize} -> Int
minSize) (\s :: AutoScalingGroup
s@AutoScalingGroup' {} Int
a -> AutoScalingGroup
s {$sel:minSize:AutoScalingGroup' :: Int
minSize = Int
a} :: AutoScalingGroup)

-- | The maximum size of the group.
autoScalingGroup_maxSize :: Lens.Lens' AutoScalingGroup Prelude.Int
autoScalingGroup_maxSize :: Lens' AutoScalingGroup Int
autoScalingGroup_maxSize = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingGroup' {Int
maxSize :: Int
$sel:maxSize:AutoScalingGroup' :: AutoScalingGroup -> Int
maxSize} -> Int
maxSize) (\s :: AutoScalingGroup
s@AutoScalingGroup' {} Int
a -> AutoScalingGroup
s {$sel:maxSize:AutoScalingGroup' :: Int
maxSize = Int
a} :: AutoScalingGroup)

-- | The desired size of the group.
autoScalingGroup_desiredCapacity :: Lens.Lens' AutoScalingGroup Prelude.Int
autoScalingGroup_desiredCapacity :: Lens' AutoScalingGroup Int
autoScalingGroup_desiredCapacity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingGroup' {Int
desiredCapacity :: Int
$sel:desiredCapacity:AutoScalingGroup' :: AutoScalingGroup -> Int
desiredCapacity} -> Int
desiredCapacity) (\s :: AutoScalingGroup
s@AutoScalingGroup' {} Int
a -> AutoScalingGroup
s {$sel:desiredCapacity:AutoScalingGroup' :: Int
desiredCapacity = Int
a} :: AutoScalingGroup)

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

-- | One or more Availability Zones for the group.
autoScalingGroup_availabilityZones :: Lens.Lens' AutoScalingGroup [Prelude.Text]
autoScalingGroup_availabilityZones :: Lens' AutoScalingGroup [Text]
autoScalingGroup_availabilityZones = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingGroup' {[Text]
availabilityZones :: [Text]
$sel:availabilityZones:AutoScalingGroup' :: AutoScalingGroup -> [Text]
availabilityZones} -> [Text]
availabilityZones) (\s :: AutoScalingGroup
s@AutoScalingGroup' {} [Text]
a -> AutoScalingGroup
s {$sel:availabilityZones:AutoScalingGroup' :: [Text]
availabilityZones = [Text]
a} :: AutoScalingGroup) 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

-- | Determines whether any additional health checks are performed on the
-- instances in this group. Amazon EC2 health checks are always on.
--
-- The valid values are @EC2@ (default), @ELB@, and @VPC_LATTICE@. The
-- @VPC_LATTICE@ health check type is reserved for use with VPC Lattice,
-- which is in preview release and is subject to change.
autoScalingGroup_healthCheckType :: Lens.Lens' AutoScalingGroup Prelude.Text
autoScalingGroup_healthCheckType :: Lens' AutoScalingGroup Text
autoScalingGroup_healthCheckType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingGroup' {Text
healthCheckType :: Text
$sel:healthCheckType:AutoScalingGroup' :: AutoScalingGroup -> Text
healthCheckType} -> Text
healthCheckType) (\s :: AutoScalingGroup
s@AutoScalingGroup' {} Text
a -> AutoScalingGroup
s {$sel:healthCheckType:AutoScalingGroup' :: Text
healthCheckType = Text
a} :: AutoScalingGroup)

-- | The date and time the group was created.
autoScalingGroup_createdTime :: Lens.Lens' AutoScalingGroup Prelude.UTCTime
autoScalingGroup_createdTime :: Lens' AutoScalingGroup UTCTime
autoScalingGroup_createdTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingGroup' {ISO8601
createdTime :: ISO8601
$sel:createdTime:AutoScalingGroup' :: AutoScalingGroup -> ISO8601
createdTime} -> ISO8601
createdTime) (\s :: AutoScalingGroup
s@AutoScalingGroup' {} ISO8601
a -> AutoScalingGroup
s {$sel:createdTime:AutoScalingGroup' :: ISO8601
createdTime = ISO8601
a} :: AutoScalingGroup) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

instance Data.FromXML AutoScalingGroup where
  parseXML :: [Node] -> Either String AutoScalingGroup
parseXML [Node]
x =
    Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe [EnabledMetric]
-> Maybe Int
-> Maybe [Instance]
-> Maybe Text
-> Maybe LaunchTemplateSpecification
-> Maybe [Text]
-> Maybe Int
-> Maybe MixedInstancesPolicy
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe [SuspendedProcess]
-> Maybe [TagDescription]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [TrafficSourceIdentifier]
-> Maybe Text
-> Maybe WarmPoolConfiguration
-> Maybe Int
-> Text
-> Int
-> Int
-> Int
-> Int
-> [Text]
-> Text
-> ISO8601
-> AutoScalingGroup
AutoScalingGroup'
      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
"AutoScalingGroupARN")
      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
"CapacityRebalance")
      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
"Context")
      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
"DefaultInstanceWarmup")
      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
"DesiredCapacityType")
      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
"EnabledMetrics"
                      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
"HealthCheckGracePeriod")
      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
"Instances"
                      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
"LaunchConfigurationName")
      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
"LaunchTemplate")
      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
"LoadBalancerNames"
                      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
"MaxInstanceLifetime")
      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
"MixedInstancesPolicy")
      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
"NewInstancesProtectedFromScaleIn")
      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
"PlacementGroup")
      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
"PredictedCapacity")
      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
"ServiceLinkedRoleARN")
      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
"Status")
      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
"SuspendedProcesses"
                      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
"Tags"
                      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
"TargetGroupARNs"
                      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
"TerminationPolicies"
                      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
"TrafficSources"
                      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
"VPCZoneIdentifier")
      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
"WarmPoolConfiguration")
      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
"WarmPoolSize")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String 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 a
Data..@ Text
"MinSize")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"MaxSize")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"DesiredCapacity")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"DefaultCooldown")
      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
"AvailabilityZones"
                      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"
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"HealthCheckType")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"CreatedTime")

instance Prelude.Hashable AutoScalingGroup where
  hashWithSalt :: Int -> AutoScalingGroup -> Int
hashWithSalt Int
_salt AutoScalingGroup' {Int
[Text]
Maybe Bool
Maybe Int
Maybe [Text]
Maybe [EnabledMetric]
Maybe [Instance]
Maybe [SuspendedProcess]
Maybe [TagDescription]
Maybe [TrafficSourceIdentifier]
Maybe Text
Maybe LaunchTemplateSpecification
Maybe MixedInstancesPolicy
Maybe WarmPoolConfiguration
Text
ISO8601
createdTime :: ISO8601
healthCheckType :: Text
availabilityZones :: [Text]
defaultCooldown :: Int
desiredCapacity :: Int
maxSize :: Int
minSize :: Int
autoScalingGroupName :: Text
warmPoolSize :: Maybe Int
warmPoolConfiguration :: Maybe WarmPoolConfiguration
vPCZoneIdentifier :: Maybe Text
trafficSources :: Maybe [TrafficSourceIdentifier]
terminationPolicies :: Maybe [Text]
targetGroupARNs :: Maybe [Text]
tags :: Maybe [TagDescription]
suspendedProcesses :: Maybe [SuspendedProcess]
status :: Maybe Text
serviceLinkedRoleARN :: Maybe Text
predictedCapacity :: Maybe Int
placementGroup :: Maybe Text
newInstancesProtectedFromScaleIn' :: Maybe Bool
mixedInstancesPolicy :: Maybe MixedInstancesPolicy
maxInstanceLifetime :: Maybe Int
loadBalancerNames :: Maybe [Text]
launchTemplate :: Maybe LaunchTemplateSpecification
launchConfigurationName :: Maybe Text
instances :: Maybe [Instance]
healthCheckGracePeriod :: Maybe Int
enabledMetrics :: Maybe [EnabledMetric]
desiredCapacityType :: Maybe Text
defaultInstanceWarmup :: Maybe Int
context :: Maybe Text
capacityRebalance :: Maybe Bool
autoScalingGroupARN :: Maybe Text
$sel:createdTime:AutoScalingGroup' :: AutoScalingGroup -> ISO8601
$sel:healthCheckType:AutoScalingGroup' :: AutoScalingGroup -> Text
$sel:availabilityZones:AutoScalingGroup' :: AutoScalingGroup -> [Text]
$sel:defaultCooldown:AutoScalingGroup' :: AutoScalingGroup -> Int
$sel:desiredCapacity:AutoScalingGroup' :: AutoScalingGroup -> Int
$sel:maxSize:AutoScalingGroup' :: AutoScalingGroup -> Int
$sel:minSize:AutoScalingGroup' :: AutoScalingGroup -> Int
$sel:autoScalingGroupName:AutoScalingGroup' :: AutoScalingGroup -> Text
$sel:warmPoolSize:AutoScalingGroup' :: AutoScalingGroup -> Maybe Int
$sel:warmPoolConfiguration:AutoScalingGroup' :: AutoScalingGroup -> Maybe WarmPoolConfiguration
$sel:vPCZoneIdentifier:AutoScalingGroup' :: AutoScalingGroup -> Maybe Text
$sel:trafficSources:AutoScalingGroup' :: AutoScalingGroup -> Maybe [TrafficSourceIdentifier]
$sel:terminationPolicies:AutoScalingGroup' :: AutoScalingGroup -> Maybe [Text]
$sel:targetGroupARNs:AutoScalingGroup' :: AutoScalingGroup -> Maybe [Text]
$sel:tags:AutoScalingGroup' :: AutoScalingGroup -> Maybe [TagDescription]
$sel:suspendedProcesses:AutoScalingGroup' :: AutoScalingGroup -> Maybe [SuspendedProcess]
$sel:status:AutoScalingGroup' :: AutoScalingGroup -> Maybe Text
$sel:serviceLinkedRoleARN:AutoScalingGroup' :: AutoScalingGroup -> Maybe Text
$sel:predictedCapacity:AutoScalingGroup' :: AutoScalingGroup -> Maybe Int
$sel:placementGroup:AutoScalingGroup' :: AutoScalingGroup -> Maybe Text
$sel:newInstancesProtectedFromScaleIn':AutoScalingGroup' :: AutoScalingGroup -> Maybe Bool
$sel:mixedInstancesPolicy:AutoScalingGroup' :: AutoScalingGroup -> Maybe MixedInstancesPolicy
$sel:maxInstanceLifetime:AutoScalingGroup' :: AutoScalingGroup -> Maybe Int
$sel:loadBalancerNames:AutoScalingGroup' :: AutoScalingGroup -> Maybe [Text]
$sel:launchTemplate:AutoScalingGroup' :: AutoScalingGroup -> Maybe LaunchTemplateSpecification
$sel:launchConfigurationName:AutoScalingGroup' :: AutoScalingGroup -> Maybe Text
$sel:instances:AutoScalingGroup' :: AutoScalingGroup -> Maybe [Instance]
$sel:healthCheckGracePeriod:AutoScalingGroup' :: AutoScalingGroup -> Maybe Int
$sel:enabledMetrics:AutoScalingGroup' :: AutoScalingGroup -> Maybe [EnabledMetric]
$sel:desiredCapacityType:AutoScalingGroup' :: AutoScalingGroup -> Maybe Text
$sel:defaultInstanceWarmup:AutoScalingGroup' :: AutoScalingGroup -> Maybe Int
$sel:context:AutoScalingGroup' :: AutoScalingGroup -> Maybe Text
$sel:capacityRebalance:AutoScalingGroup' :: AutoScalingGroup -> Maybe Bool
$sel:autoScalingGroupARN:AutoScalingGroup' :: AutoScalingGroup -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
autoScalingGroupARN
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
capacityRebalance
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
context
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
defaultInstanceWarmup
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
desiredCapacityType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [EnabledMetric]
enabledMetrics
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
healthCheckGracePeriod
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Instance]
instances
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
launchConfigurationName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LaunchTemplateSpecification
launchTemplate
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
loadBalancerNames
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxInstanceLifetime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MixedInstancesPolicy
mixedInstancesPolicy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
newInstancesProtectedFromScaleIn'
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
placementGroup
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
predictedCapacity
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
serviceLinkedRoleARN
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [SuspendedProcess]
suspendedProcesses
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [TagDescription]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
targetGroupARNs
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
terminationPolicies
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [TrafficSourceIdentifier]
trafficSources
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
vPCZoneIdentifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe WarmPoolConfiguration
warmPoolConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
warmPoolSize
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
autoScalingGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Int
minSize
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Int
maxSize
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Int
desiredCapacity
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Int
defaultCooldown
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
availabilityZones
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
healthCheckType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ISO8601
createdTime

instance Prelude.NFData AutoScalingGroup where
  rnf :: AutoScalingGroup -> ()
rnf AutoScalingGroup' {Int
[Text]
Maybe Bool
Maybe Int
Maybe [Text]
Maybe [EnabledMetric]
Maybe [Instance]
Maybe [SuspendedProcess]
Maybe [TagDescription]
Maybe [TrafficSourceIdentifier]
Maybe Text
Maybe LaunchTemplateSpecification
Maybe MixedInstancesPolicy
Maybe WarmPoolConfiguration
Text
ISO8601
createdTime :: ISO8601
healthCheckType :: Text
availabilityZones :: [Text]
defaultCooldown :: Int
desiredCapacity :: Int
maxSize :: Int
minSize :: Int
autoScalingGroupName :: Text
warmPoolSize :: Maybe Int
warmPoolConfiguration :: Maybe WarmPoolConfiguration
vPCZoneIdentifier :: Maybe Text
trafficSources :: Maybe [TrafficSourceIdentifier]
terminationPolicies :: Maybe [Text]
targetGroupARNs :: Maybe [Text]
tags :: Maybe [TagDescription]
suspendedProcesses :: Maybe [SuspendedProcess]
status :: Maybe Text
serviceLinkedRoleARN :: Maybe Text
predictedCapacity :: Maybe Int
placementGroup :: Maybe Text
newInstancesProtectedFromScaleIn' :: Maybe Bool
mixedInstancesPolicy :: Maybe MixedInstancesPolicy
maxInstanceLifetime :: Maybe Int
loadBalancerNames :: Maybe [Text]
launchTemplate :: Maybe LaunchTemplateSpecification
launchConfigurationName :: Maybe Text
instances :: Maybe [Instance]
healthCheckGracePeriod :: Maybe Int
enabledMetrics :: Maybe [EnabledMetric]
desiredCapacityType :: Maybe Text
defaultInstanceWarmup :: Maybe Int
context :: Maybe Text
capacityRebalance :: Maybe Bool
autoScalingGroupARN :: Maybe Text
$sel:createdTime:AutoScalingGroup' :: AutoScalingGroup -> ISO8601
$sel:healthCheckType:AutoScalingGroup' :: AutoScalingGroup -> Text
$sel:availabilityZones:AutoScalingGroup' :: AutoScalingGroup -> [Text]
$sel:defaultCooldown:AutoScalingGroup' :: AutoScalingGroup -> Int
$sel:desiredCapacity:AutoScalingGroup' :: AutoScalingGroup -> Int
$sel:maxSize:AutoScalingGroup' :: AutoScalingGroup -> Int
$sel:minSize:AutoScalingGroup' :: AutoScalingGroup -> Int
$sel:autoScalingGroupName:AutoScalingGroup' :: AutoScalingGroup -> Text
$sel:warmPoolSize:AutoScalingGroup' :: AutoScalingGroup -> Maybe Int
$sel:warmPoolConfiguration:AutoScalingGroup' :: AutoScalingGroup -> Maybe WarmPoolConfiguration
$sel:vPCZoneIdentifier:AutoScalingGroup' :: AutoScalingGroup -> Maybe Text
$sel:trafficSources:AutoScalingGroup' :: AutoScalingGroup -> Maybe [TrafficSourceIdentifier]
$sel:terminationPolicies:AutoScalingGroup' :: AutoScalingGroup -> Maybe [Text]
$sel:targetGroupARNs:AutoScalingGroup' :: AutoScalingGroup -> Maybe [Text]
$sel:tags:AutoScalingGroup' :: AutoScalingGroup -> Maybe [TagDescription]
$sel:suspendedProcesses:AutoScalingGroup' :: AutoScalingGroup -> Maybe [SuspendedProcess]
$sel:status:AutoScalingGroup' :: AutoScalingGroup -> Maybe Text
$sel:serviceLinkedRoleARN:AutoScalingGroup' :: AutoScalingGroup -> Maybe Text
$sel:predictedCapacity:AutoScalingGroup' :: AutoScalingGroup -> Maybe Int
$sel:placementGroup:AutoScalingGroup' :: AutoScalingGroup -> Maybe Text
$sel:newInstancesProtectedFromScaleIn':AutoScalingGroup' :: AutoScalingGroup -> Maybe Bool
$sel:mixedInstancesPolicy:AutoScalingGroup' :: AutoScalingGroup -> Maybe MixedInstancesPolicy
$sel:maxInstanceLifetime:AutoScalingGroup' :: AutoScalingGroup -> Maybe Int
$sel:loadBalancerNames:AutoScalingGroup' :: AutoScalingGroup -> Maybe [Text]
$sel:launchTemplate:AutoScalingGroup' :: AutoScalingGroup -> Maybe LaunchTemplateSpecification
$sel:launchConfigurationName:AutoScalingGroup' :: AutoScalingGroup -> Maybe Text
$sel:instances:AutoScalingGroup' :: AutoScalingGroup -> Maybe [Instance]
$sel:healthCheckGracePeriod:AutoScalingGroup' :: AutoScalingGroup -> Maybe Int
$sel:enabledMetrics:AutoScalingGroup' :: AutoScalingGroup -> Maybe [EnabledMetric]
$sel:desiredCapacityType:AutoScalingGroup' :: AutoScalingGroup -> Maybe Text
$sel:defaultInstanceWarmup:AutoScalingGroup' :: AutoScalingGroup -> Maybe Int
$sel:context:AutoScalingGroup' :: AutoScalingGroup -> Maybe Text
$sel:capacityRebalance:AutoScalingGroup' :: AutoScalingGroup -> Maybe Bool
$sel:autoScalingGroupARN:AutoScalingGroup' :: AutoScalingGroup -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
autoScalingGroupARN
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
capacityRebalance
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
context
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
defaultInstanceWarmup
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
desiredCapacityType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [EnabledMetric]
enabledMetrics
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
healthCheckGracePeriod
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Instance]
instances
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
launchConfigurationName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LaunchTemplateSpecification
launchTemplate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
loadBalancerNames
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
maxInstanceLifetime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MixedInstancesPolicy
mixedInstancesPolicy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Bool
newInstancesProtectedFromScaleIn'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
placementGroup
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
predictedCapacity
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
serviceLinkedRoleARN
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [SuspendedProcess]
suspendedProcesses
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [TagDescription]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
targetGroupARNs
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe [Text]
terminationPolicies
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe [TrafficSourceIdentifier]
trafficSources
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
vPCZoneIdentifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe WarmPoolConfiguration
warmPoolConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Int
warmPoolSize
      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
        Int
minSize
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Int
maxSize
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Int
desiredCapacity
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Int
defaultCooldown
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        [Text]
availabilityZones
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Text
healthCheckType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        ISO8601
createdTime