{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.AutoScaling.UpdateAutoScalingGroup
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- __We strongly recommend that all Auto Scaling groups use launch
-- templates to ensure full functionality for Amazon EC2 Auto Scaling and
-- Amazon EC2.__
--
-- Updates the configuration for the specified Auto Scaling group.
--
-- To update an Auto Scaling group, specify the name of the group and the
-- property that you want to change. Any properties that you don\'t specify
-- are not changed by this update request. The new settings take effect on
-- any scaling activities after this call returns.
--
-- If you associate a new launch configuration or template with an Auto
-- Scaling group, all new instances will get the updated configuration.
-- Existing instances continue to run with the configuration that they were
-- originally launched with. When you update a group to specify a mixed
-- instances policy instead of a launch configuration or template, existing
-- instances may be replaced to match the new purchasing options that you
-- specified in the policy. For example, if the group currently has 100%
-- On-Demand capacity and the policy specifies 50% Spot capacity, this
-- means that half of your instances will be gradually terminated and
-- relaunched as Spot Instances. When replacing instances, Amazon EC2 Auto
-- Scaling launches new instances before terminating the old ones, so that
-- updating your group does not compromise the performance or availability
-- of your application.
--
-- Note the following about changing @DesiredCapacity@, @MaxSize@, or
-- @MinSize@:
--
-- -   If a scale-in activity occurs as a result of a new @DesiredCapacity@
--     value that is lower than the current size of the group, the Auto
--     Scaling group uses its termination policy to determine which
--     instances to terminate.
--
-- -   If you specify a new value for @MinSize@ without specifying a value
--     for @DesiredCapacity@, and the new @MinSize@ is larger than the
--     current size of the group, this sets the group\'s @DesiredCapacity@
--     to the new @MinSize@ value.
--
-- -   If you specify a new value for @MaxSize@ without specifying a value
--     for @DesiredCapacity@, and the new @MaxSize@ is smaller than the
--     current size of the group, this sets the group\'s @DesiredCapacity@
--     to the new @MaxSize@ value.
--
-- To see which properties have been set, call the
-- DescribeAutoScalingGroups API. To view the scaling policies for an Auto
-- Scaling group, call the DescribePolicies API. If the group has scaling
-- policies, you can update them by calling the PutScalingPolicy API.
module Amazonka.AutoScaling.UpdateAutoScalingGroup
  ( -- * Creating a Request
    UpdateAutoScalingGroup (..),
    newUpdateAutoScalingGroup,

    -- * Request Lenses
    updateAutoScalingGroup_availabilityZones,
    updateAutoScalingGroup_capacityRebalance,
    updateAutoScalingGroup_context,
    updateAutoScalingGroup_defaultCooldown,
    updateAutoScalingGroup_defaultInstanceWarmup,
    updateAutoScalingGroup_desiredCapacity,
    updateAutoScalingGroup_desiredCapacityType,
    updateAutoScalingGroup_healthCheckGracePeriod,
    updateAutoScalingGroup_healthCheckType,
    updateAutoScalingGroup_launchConfigurationName,
    updateAutoScalingGroup_launchTemplate,
    updateAutoScalingGroup_maxInstanceLifetime,
    updateAutoScalingGroup_maxSize,
    updateAutoScalingGroup_minSize,
    updateAutoScalingGroup_mixedInstancesPolicy,
    updateAutoScalingGroup_newInstancesProtectedFromScaleIn,
    updateAutoScalingGroup_placementGroup,
    updateAutoScalingGroup_serviceLinkedRoleARN,
    updateAutoScalingGroup_terminationPolicies,
    updateAutoScalingGroup_vPCZoneIdentifier,
    updateAutoScalingGroup_autoScalingGroupName,

    -- * Destructuring the Response
    UpdateAutoScalingGroupResponse (..),
    newUpdateAutoScalingGroupResponse,
  )
where

import Amazonka.AutoScaling.Types
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newUpdateAutoScalingGroup' smart constructor.
data UpdateAutoScalingGroup = UpdateAutoScalingGroup'
  { -- | One or more Availability Zones for the group.
    UpdateAutoScalingGroup -> Maybe [Text]
availabilityZones :: Prelude.Maybe [Prelude.Text],
    -- | Enables or disables Capacity Rebalancing. For more information, see
    -- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/ec2-auto-scaling-capacity-rebalancing.html Use Capacity Rebalancing to handle Amazon EC2 Spot Interruptions>
    -- in the /Amazon EC2 Auto Scaling User Guide/.
    UpdateAutoScalingGroup -> Maybe Bool
capacityRebalance :: Prelude.Maybe Prelude.Bool,
    -- | Reserved.
    UpdateAutoScalingGroup -> Maybe Text
context :: Prelude.Maybe Prelude.Text,
    -- | /Only needed if you use simple scaling policies./
    --
    -- The amount of time, in seconds, between one scaling activity ending and
    -- another one starting due to simple scaling policies. For more
    -- information, see
    -- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/Cooldown.html Scaling cooldowns for Amazon EC2 Auto Scaling>
    -- in the /Amazon EC2 Auto Scaling User Guide/.
    UpdateAutoScalingGroup -> Maybe Int
defaultCooldown :: Prelude.Maybe Prelude.Int,
    -- | The amount of time, in seconds, until a newly launched instance can
    -- contribute to the Amazon CloudWatch metrics. This delay lets an instance
    -- finish initializing before Amazon EC2 Auto Scaling aggregates instance
    -- metrics, resulting in more reliable usage data. Set this value equal to
    -- the amount of time that it takes for resource consumption to become
    -- stable after an instance reaches the @InService@ state. For more
    -- information, see
    -- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/ec2-auto-scaling-default-instance-warmup.html Set the default instance warmup for an Auto Scaling group>
    -- in the /Amazon EC2 Auto Scaling User Guide/.
    --
    -- To manage your warm-up settings at the group level, we recommend that
    -- you set the default instance warmup, /even if its value is set to 0
    -- seconds/. This also optimizes the performance of scaling policies that
    -- scale continuously, such as target tracking and step scaling policies.
    --
    -- If you need to remove a value that you previously set, include the
    -- property but specify @-1@ for the value. However, we strongly recommend
    -- keeping the default instance warmup enabled by specifying a minimum
    -- value of @0@.
    UpdateAutoScalingGroup -> Maybe Int
defaultInstanceWarmup :: Prelude.Maybe Prelude.Int,
    -- | The desired capacity is the initial capacity of the Auto Scaling group
    -- after this operation completes and the capacity it attempts to maintain.
    -- This number must be greater than or equal to the minimum size of the
    -- group and less than or equal to the maximum size of the group.
    UpdateAutoScalingGroup -> Maybe Int
desiredCapacity :: 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. For more information, see
    -- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/create-asg-instance-type-requirements.html Creating an Auto Scaling group using attribute-based instance type selection>
    -- in the /Amazon EC2 Auto Scaling User Guide/.
    --
    -- By default, Amazon EC2 Auto Scaling specifies @units@, which translates
    -- into number of instances.
    --
    -- Valid values: @units@ | @vcpu@ | @memory-mib@
    UpdateAutoScalingGroup -> Maybe Text
desiredCapacityType :: Prelude.Maybe Prelude.Text,
    -- | The amount of time, in seconds, that Amazon EC2 Auto Scaling waits
    -- before checking the health status of an EC2 instance that has come into
    -- service and marking it unhealthy due to a failed health check. This is
    -- useful if your instances do not immediately pass their health checks
    -- after they enter the @InService@ state. For more information, see
    -- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/health-check-grace-period.html Set the health check grace period for an Auto Scaling group>
    -- in the /Amazon EC2 Auto Scaling User Guide/.
    UpdateAutoScalingGroup -> Maybe Int
healthCheckGracePeriod :: Prelude.Maybe Prelude.Int,
    -- | 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.
    UpdateAutoScalingGroup -> Maybe Text
healthCheckType :: Prelude.Maybe Prelude.Text,
    -- | The name of the launch configuration. If you specify
    -- @LaunchConfigurationName@ in your update request, you can\'t specify
    -- @LaunchTemplate@ or @MixedInstancesPolicy@.
    UpdateAutoScalingGroup -> Maybe Text
launchConfigurationName :: Prelude.Maybe Prelude.Text,
    -- | The launch template and version to use to specify the updates. If you
    -- specify @LaunchTemplate@ in your update request, you can\'t specify
    -- @LaunchConfigurationName@ or @MixedInstancesPolicy@.
    UpdateAutoScalingGroup -> Maybe LaunchTemplateSpecification
launchTemplate :: Prelude.Maybe LaunchTemplateSpecification,
    -- | The maximum amount of time, in seconds, that an instance can be in
    -- service. The default is null. If specified, the value must be either 0
    -- or a number equal to or greater than 86,400 seconds (1 day). To clear a
    -- previously set value, specify a new value of 0. For more information,
    -- see
    -- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/asg-max-instance-lifetime.html Replacing Auto Scaling instances based on maximum instance lifetime>
    -- in the /Amazon EC2 Auto Scaling User Guide/.
    UpdateAutoScalingGroup -> Maybe Int
maxInstanceLifetime :: Prelude.Maybe Prelude.Int,
    -- | The maximum size of the Auto Scaling group.
    --
    -- With a mixed instances policy that uses instance weighting, Amazon EC2
    -- Auto Scaling may need to go above @MaxSize@ to meet your capacity
    -- requirements. In this event, Amazon EC2 Auto Scaling will never go above
    -- @MaxSize@ by more than your largest instance weight (weights that define
    -- how many units each instance contributes to the desired capacity of the
    -- group).
    UpdateAutoScalingGroup -> Maybe Int
maxSize :: Prelude.Maybe Prelude.Int,
    -- | The minimum size of the Auto Scaling group.
    UpdateAutoScalingGroup -> Maybe Int
minSize :: Prelude.Maybe Prelude.Int,
    -- | The mixed instances policy. For more information, see
    -- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/ec2-auto-scaling-mixed-instances-groups.html Auto Scaling groups with multiple instance types and purchase options>
    -- in the /Amazon EC2 Auto Scaling User Guide/.
    UpdateAutoScalingGroup -> Maybe MixedInstancesPolicy
mixedInstancesPolicy :: Prelude.Maybe MixedInstancesPolicy,
    -- | Indicates whether newly launched instances are protected from
    -- termination by Amazon EC2 Auto Scaling when scaling in. For more
    -- information about preventing instances from terminating on scale in, see
    -- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/ec2-auto-scaling-instance-protection.html Using instance scale-in protection>
    -- in the /Amazon EC2 Auto Scaling User Guide/.
    UpdateAutoScalingGroup -> Maybe Bool
newInstancesProtectedFromScaleIn' :: Prelude.Maybe Prelude.Bool,
    -- | The name of an existing placement group into which to launch your
    -- instances. For more information, see
    -- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/placement-groups.html Placement groups>
    -- in the /Amazon EC2 User Guide for Linux Instances/.
    --
    -- A /cluster/ placement group is a logical grouping of instances within a
    -- single Availability Zone. You cannot specify multiple Availability Zones
    -- and a cluster placement group.
    UpdateAutoScalingGroup -> Maybe Text
placementGroup :: Prelude.Maybe Prelude.Text,
    -- | 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. For
    -- more information, see
    -- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/autoscaling-service-linked-role.html Service-linked roles>
    -- in the /Amazon EC2 Auto Scaling User Guide/.
    UpdateAutoScalingGroup -> Maybe Text
serviceLinkedRoleARN :: Prelude.Maybe Prelude.Text,
    -- | A policy or a list of policies that are used to select the instances to
    -- terminate. The policies are executed in the order that you list them.
    -- For more information, see
    -- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/ec2-auto-scaling-termination-policies.html Work with Amazon EC2 Auto Scaling termination policies>
    -- in the /Amazon EC2 Auto Scaling User Guide/.
    --
    -- Valid values: @Default@ | @AllocationStrategy@ |
    -- @ClosestToNextInstanceHour@ | @NewestInstance@ | @OldestInstance@ |
    -- @OldestLaunchConfiguration@ | @OldestLaunchTemplate@ |
    -- @arn:aws:lambda:region:account-id:function:my-function:my-alias@
    UpdateAutoScalingGroup -> Maybe [Text]
terminationPolicies :: Prelude.Maybe [Prelude.Text],
    -- | A comma-separated list of subnet IDs for a virtual private cloud (VPC).
    -- If you specify @VPCZoneIdentifier@ with @AvailabilityZones@, the subnets
    -- that you specify must reside in those Availability Zones.
    UpdateAutoScalingGroup -> Maybe Text
vPCZoneIdentifier :: Prelude.Maybe Prelude.Text,
    -- | The name of the Auto Scaling group.
    UpdateAutoScalingGroup -> Text
autoScalingGroupName :: Prelude.Text
  }
  deriving (UpdateAutoScalingGroup -> UpdateAutoScalingGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateAutoScalingGroup -> UpdateAutoScalingGroup -> Bool
$c/= :: UpdateAutoScalingGroup -> UpdateAutoScalingGroup -> Bool
== :: UpdateAutoScalingGroup -> UpdateAutoScalingGroup -> Bool
$c== :: UpdateAutoScalingGroup -> UpdateAutoScalingGroup -> Bool
Prelude.Eq, ReadPrec [UpdateAutoScalingGroup]
ReadPrec UpdateAutoScalingGroup
Int -> ReadS UpdateAutoScalingGroup
ReadS [UpdateAutoScalingGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateAutoScalingGroup]
$creadListPrec :: ReadPrec [UpdateAutoScalingGroup]
readPrec :: ReadPrec UpdateAutoScalingGroup
$creadPrec :: ReadPrec UpdateAutoScalingGroup
readList :: ReadS [UpdateAutoScalingGroup]
$creadList :: ReadS [UpdateAutoScalingGroup]
readsPrec :: Int -> ReadS UpdateAutoScalingGroup
$creadsPrec :: Int -> ReadS UpdateAutoScalingGroup
Prelude.Read, Int -> UpdateAutoScalingGroup -> ShowS
[UpdateAutoScalingGroup] -> ShowS
UpdateAutoScalingGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateAutoScalingGroup] -> ShowS
$cshowList :: [UpdateAutoScalingGroup] -> ShowS
show :: UpdateAutoScalingGroup -> String
$cshow :: UpdateAutoScalingGroup -> String
showsPrec :: Int -> UpdateAutoScalingGroup -> ShowS
$cshowsPrec :: Int -> UpdateAutoScalingGroup -> ShowS
Prelude.Show, forall x. Rep UpdateAutoScalingGroup x -> UpdateAutoScalingGroup
forall x. UpdateAutoScalingGroup -> Rep UpdateAutoScalingGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateAutoScalingGroup x -> UpdateAutoScalingGroup
$cfrom :: forall x. UpdateAutoScalingGroup -> Rep UpdateAutoScalingGroup x
Prelude.Generic)

-- |
-- Create a value of 'UpdateAutoScalingGroup' 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:
--
-- 'availabilityZones', 'updateAutoScalingGroup_availabilityZones' - One or more Availability Zones for the group.
--
-- 'capacityRebalance', 'updateAutoScalingGroup_capacityRebalance' - Enables or disables Capacity Rebalancing. For more information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/ec2-auto-scaling-capacity-rebalancing.html Use Capacity Rebalancing to handle Amazon EC2 Spot Interruptions>
-- in the /Amazon EC2 Auto Scaling User Guide/.
--
-- 'context', 'updateAutoScalingGroup_context' - Reserved.
--
-- 'defaultCooldown', 'updateAutoScalingGroup_defaultCooldown' - /Only needed if you use simple scaling policies./
--
-- The amount of time, in seconds, between one scaling activity ending and
-- another one starting due to simple scaling policies. For more
-- information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/Cooldown.html Scaling cooldowns for Amazon EC2 Auto Scaling>
-- in the /Amazon EC2 Auto Scaling User Guide/.
--
-- 'defaultInstanceWarmup', 'updateAutoScalingGroup_defaultInstanceWarmup' - The amount of time, in seconds, until a newly launched instance can
-- contribute to the Amazon CloudWatch metrics. This delay lets an instance
-- finish initializing before Amazon EC2 Auto Scaling aggregates instance
-- metrics, resulting in more reliable usage data. Set this value equal to
-- the amount of time that it takes for resource consumption to become
-- stable after an instance reaches the @InService@ state. For more
-- information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/ec2-auto-scaling-default-instance-warmup.html Set the default instance warmup for an Auto Scaling group>
-- in the /Amazon EC2 Auto Scaling User Guide/.
--
-- To manage your warm-up settings at the group level, we recommend that
-- you set the default instance warmup, /even if its value is set to 0
-- seconds/. This also optimizes the performance of scaling policies that
-- scale continuously, such as target tracking and step scaling policies.
--
-- If you need to remove a value that you previously set, include the
-- property but specify @-1@ for the value. However, we strongly recommend
-- keeping the default instance warmup enabled by specifying a minimum
-- value of @0@.
--
-- 'desiredCapacity', 'updateAutoScalingGroup_desiredCapacity' - The desired capacity is the initial capacity of the Auto Scaling group
-- after this operation completes and the capacity it attempts to maintain.
-- This number must be greater than or equal to the minimum size of the
-- group and less than or equal to the maximum size of the group.
--
-- 'desiredCapacityType', 'updateAutoScalingGroup_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. For more information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/create-asg-instance-type-requirements.html Creating an Auto Scaling group using attribute-based instance type selection>
-- in the /Amazon EC2 Auto Scaling User Guide/.
--
-- By default, Amazon EC2 Auto Scaling specifies @units@, which translates
-- into number of instances.
--
-- Valid values: @units@ | @vcpu@ | @memory-mib@
--
-- 'healthCheckGracePeriod', 'updateAutoScalingGroup_healthCheckGracePeriod' - The amount of time, in seconds, that Amazon EC2 Auto Scaling waits
-- before checking the health status of an EC2 instance that has come into
-- service and marking it unhealthy due to a failed health check. This is
-- useful if your instances do not immediately pass their health checks
-- after they enter the @InService@ state. For more information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/health-check-grace-period.html Set the health check grace period for an Auto Scaling group>
-- in the /Amazon EC2 Auto Scaling User Guide/.
--
-- 'healthCheckType', 'updateAutoScalingGroup_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.
--
-- 'launchConfigurationName', 'updateAutoScalingGroup_launchConfigurationName' - The name of the launch configuration. If you specify
-- @LaunchConfigurationName@ in your update request, you can\'t specify
-- @LaunchTemplate@ or @MixedInstancesPolicy@.
--
-- 'launchTemplate', 'updateAutoScalingGroup_launchTemplate' - The launch template and version to use to specify the updates. If you
-- specify @LaunchTemplate@ in your update request, you can\'t specify
-- @LaunchConfigurationName@ or @MixedInstancesPolicy@.
--
-- 'maxInstanceLifetime', 'updateAutoScalingGroup_maxInstanceLifetime' - The maximum amount of time, in seconds, that an instance can be in
-- service. The default is null. If specified, the value must be either 0
-- or a number equal to or greater than 86,400 seconds (1 day). To clear a
-- previously set value, specify a new value of 0. For more information,
-- see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/asg-max-instance-lifetime.html Replacing Auto Scaling instances based on maximum instance lifetime>
-- in the /Amazon EC2 Auto Scaling User Guide/.
--
-- 'maxSize', 'updateAutoScalingGroup_maxSize' - The maximum size of the Auto Scaling group.
--
-- With a mixed instances policy that uses instance weighting, Amazon EC2
-- Auto Scaling may need to go above @MaxSize@ to meet your capacity
-- requirements. In this event, Amazon EC2 Auto Scaling will never go above
-- @MaxSize@ by more than your largest instance weight (weights that define
-- how many units each instance contributes to the desired capacity of the
-- group).
--
-- 'minSize', 'updateAutoScalingGroup_minSize' - The minimum size of the Auto Scaling group.
--
-- 'mixedInstancesPolicy', 'updateAutoScalingGroup_mixedInstancesPolicy' - The mixed instances policy. For more information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/ec2-auto-scaling-mixed-instances-groups.html Auto Scaling groups with multiple instance types and purchase options>
-- in the /Amazon EC2 Auto Scaling User Guide/.
--
-- 'newInstancesProtectedFromScaleIn'', 'updateAutoScalingGroup_newInstancesProtectedFromScaleIn' - Indicates whether newly launched instances are protected from
-- termination by Amazon EC2 Auto Scaling when scaling in. For more
-- information about preventing instances from terminating on scale in, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/ec2-auto-scaling-instance-protection.html Using instance scale-in protection>
-- in the /Amazon EC2 Auto Scaling User Guide/.
--
-- 'placementGroup', 'updateAutoScalingGroup_placementGroup' - The name of an existing placement group into which to launch your
-- instances. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/placement-groups.html Placement groups>
-- in the /Amazon EC2 User Guide for Linux Instances/.
--
-- A /cluster/ placement group is a logical grouping of instances within a
-- single Availability Zone. You cannot specify multiple Availability Zones
-- and a cluster placement group.
--
-- 'serviceLinkedRoleARN', 'updateAutoScalingGroup_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. For
-- more information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/autoscaling-service-linked-role.html Service-linked roles>
-- in the /Amazon EC2 Auto Scaling User Guide/.
--
-- 'terminationPolicies', 'updateAutoScalingGroup_terminationPolicies' - A policy or a list of policies that are used to select the instances to
-- terminate. The policies are executed in the order that you list them.
-- For more information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/ec2-auto-scaling-termination-policies.html Work with Amazon EC2 Auto Scaling termination policies>
-- in the /Amazon EC2 Auto Scaling User Guide/.
--
-- Valid values: @Default@ | @AllocationStrategy@ |
-- @ClosestToNextInstanceHour@ | @NewestInstance@ | @OldestInstance@ |
-- @OldestLaunchConfiguration@ | @OldestLaunchTemplate@ |
-- @arn:aws:lambda:region:account-id:function:my-function:my-alias@
--
-- 'vPCZoneIdentifier', 'updateAutoScalingGroup_vPCZoneIdentifier' - A comma-separated list of subnet IDs for a virtual private cloud (VPC).
-- If you specify @VPCZoneIdentifier@ with @AvailabilityZones@, the subnets
-- that you specify must reside in those Availability Zones.
--
-- 'autoScalingGroupName', 'updateAutoScalingGroup_autoScalingGroupName' - The name of the Auto Scaling group.
newUpdateAutoScalingGroup ::
  -- | 'autoScalingGroupName'
  Prelude.Text ->
  UpdateAutoScalingGroup
newUpdateAutoScalingGroup :: Text -> UpdateAutoScalingGroup
newUpdateAutoScalingGroup Text
pAutoScalingGroupName_ =
  UpdateAutoScalingGroup'
    { $sel:availabilityZones:UpdateAutoScalingGroup' :: Maybe [Text]
availabilityZones =
        forall a. Maybe a
Prelude.Nothing,
      $sel:capacityRebalance:UpdateAutoScalingGroup' :: Maybe Bool
capacityRebalance = forall a. Maybe a
Prelude.Nothing,
      $sel:context:UpdateAutoScalingGroup' :: Maybe Text
context = forall a. Maybe a
Prelude.Nothing,
      $sel:defaultCooldown:UpdateAutoScalingGroup' :: Maybe Int
defaultCooldown = forall a. Maybe a
Prelude.Nothing,
      $sel:defaultInstanceWarmup:UpdateAutoScalingGroup' :: Maybe Int
defaultInstanceWarmup = forall a. Maybe a
Prelude.Nothing,
      $sel:desiredCapacity:UpdateAutoScalingGroup' :: Maybe Int
desiredCapacity = forall a. Maybe a
Prelude.Nothing,
      $sel:desiredCapacityType:UpdateAutoScalingGroup' :: Maybe Text
desiredCapacityType = forall a. Maybe a
Prelude.Nothing,
      $sel:healthCheckGracePeriod:UpdateAutoScalingGroup' :: Maybe Int
healthCheckGracePeriod = forall a. Maybe a
Prelude.Nothing,
      $sel:healthCheckType:UpdateAutoScalingGroup' :: Maybe Text
healthCheckType = forall a. Maybe a
Prelude.Nothing,
      $sel:launchConfigurationName:UpdateAutoScalingGroup' :: Maybe Text
launchConfigurationName = forall a. Maybe a
Prelude.Nothing,
      $sel:launchTemplate:UpdateAutoScalingGroup' :: Maybe LaunchTemplateSpecification
launchTemplate = forall a. Maybe a
Prelude.Nothing,
      $sel:maxInstanceLifetime:UpdateAutoScalingGroup' :: Maybe Int
maxInstanceLifetime = forall a. Maybe a
Prelude.Nothing,
      $sel:maxSize:UpdateAutoScalingGroup' :: Maybe Int
maxSize = forall a. Maybe a
Prelude.Nothing,
      $sel:minSize:UpdateAutoScalingGroup' :: Maybe Int
minSize = forall a. Maybe a
Prelude.Nothing,
      $sel:mixedInstancesPolicy:UpdateAutoScalingGroup' :: Maybe MixedInstancesPolicy
mixedInstancesPolicy = forall a. Maybe a
Prelude.Nothing,
      $sel:newInstancesProtectedFromScaleIn':UpdateAutoScalingGroup' :: Maybe Bool
newInstancesProtectedFromScaleIn' = forall a. Maybe a
Prelude.Nothing,
      $sel:placementGroup:UpdateAutoScalingGroup' :: Maybe Text
placementGroup = forall a. Maybe a
Prelude.Nothing,
      $sel:serviceLinkedRoleARN:UpdateAutoScalingGroup' :: Maybe Text
serviceLinkedRoleARN = forall a. Maybe a
Prelude.Nothing,
      $sel:terminationPolicies:UpdateAutoScalingGroup' :: Maybe [Text]
terminationPolicies = forall a. Maybe a
Prelude.Nothing,
      $sel:vPCZoneIdentifier:UpdateAutoScalingGroup' :: Maybe Text
vPCZoneIdentifier = forall a. Maybe a
Prelude.Nothing,
      $sel:autoScalingGroupName:UpdateAutoScalingGroup' :: Text
autoScalingGroupName = Text
pAutoScalingGroupName_
    }

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

-- | Enables or disables Capacity Rebalancing. For more information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/ec2-auto-scaling-capacity-rebalancing.html Use Capacity Rebalancing to handle Amazon EC2 Spot Interruptions>
-- in the /Amazon EC2 Auto Scaling User Guide/.
updateAutoScalingGroup_capacityRebalance :: Lens.Lens' UpdateAutoScalingGroup (Prelude.Maybe Prelude.Bool)
updateAutoScalingGroup_capacityRebalance :: Lens' UpdateAutoScalingGroup (Maybe Bool)
updateAutoScalingGroup_capacityRebalance = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAutoScalingGroup' {Maybe Bool
capacityRebalance :: Maybe Bool
$sel:capacityRebalance:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Bool
capacityRebalance} -> Maybe Bool
capacityRebalance) (\s :: UpdateAutoScalingGroup
s@UpdateAutoScalingGroup' {} Maybe Bool
a -> UpdateAutoScalingGroup
s {$sel:capacityRebalance:UpdateAutoScalingGroup' :: Maybe Bool
capacityRebalance = Maybe Bool
a} :: UpdateAutoScalingGroup)

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

-- | /Only needed if you use simple scaling policies./
--
-- The amount of time, in seconds, between one scaling activity ending and
-- another one starting due to simple scaling policies. For more
-- information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/Cooldown.html Scaling cooldowns for Amazon EC2 Auto Scaling>
-- in the /Amazon EC2 Auto Scaling User Guide/.
updateAutoScalingGroup_defaultCooldown :: Lens.Lens' UpdateAutoScalingGroup (Prelude.Maybe Prelude.Int)
updateAutoScalingGroup_defaultCooldown :: Lens' UpdateAutoScalingGroup (Maybe Int)
updateAutoScalingGroup_defaultCooldown = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAutoScalingGroup' {Maybe Int
defaultCooldown :: Maybe Int
$sel:defaultCooldown:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Int
defaultCooldown} -> Maybe Int
defaultCooldown) (\s :: UpdateAutoScalingGroup
s@UpdateAutoScalingGroup' {} Maybe Int
a -> UpdateAutoScalingGroup
s {$sel:defaultCooldown:UpdateAutoScalingGroup' :: Maybe Int
defaultCooldown = Maybe Int
a} :: UpdateAutoScalingGroup)

-- | The amount of time, in seconds, until a newly launched instance can
-- contribute to the Amazon CloudWatch metrics. This delay lets an instance
-- finish initializing before Amazon EC2 Auto Scaling aggregates instance
-- metrics, resulting in more reliable usage data. Set this value equal to
-- the amount of time that it takes for resource consumption to become
-- stable after an instance reaches the @InService@ state. For more
-- information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/ec2-auto-scaling-default-instance-warmup.html Set the default instance warmup for an Auto Scaling group>
-- in the /Amazon EC2 Auto Scaling User Guide/.
--
-- To manage your warm-up settings at the group level, we recommend that
-- you set the default instance warmup, /even if its value is set to 0
-- seconds/. This also optimizes the performance of scaling policies that
-- scale continuously, such as target tracking and step scaling policies.
--
-- If you need to remove a value that you previously set, include the
-- property but specify @-1@ for the value. However, we strongly recommend
-- keeping the default instance warmup enabled by specifying a minimum
-- value of @0@.
updateAutoScalingGroup_defaultInstanceWarmup :: Lens.Lens' UpdateAutoScalingGroup (Prelude.Maybe Prelude.Int)
updateAutoScalingGroup_defaultInstanceWarmup :: Lens' UpdateAutoScalingGroup (Maybe Int)
updateAutoScalingGroup_defaultInstanceWarmup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAutoScalingGroup' {Maybe Int
defaultInstanceWarmup :: Maybe Int
$sel:defaultInstanceWarmup:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Int
defaultInstanceWarmup} -> Maybe Int
defaultInstanceWarmup) (\s :: UpdateAutoScalingGroup
s@UpdateAutoScalingGroup' {} Maybe Int
a -> UpdateAutoScalingGroup
s {$sel:defaultInstanceWarmup:UpdateAutoScalingGroup' :: Maybe Int
defaultInstanceWarmup = Maybe Int
a} :: UpdateAutoScalingGroup)

-- | The desired capacity is the initial capacity of the Auto Scaling group
-- after this operation completes and the capacity it attempts to maintain.
-- This number must be greater than or equal to the minimum size of the
-- group and less than or equal to the maximum size of the group.
updateAutoScalingGroup_desiredCapacity :: Lens.Lens' UpdateAutoScalingGroup (Prelude.Maybe Prelude.Int)
updateAutoScalingGroup_desiredCapacity :: Lens' UpdateAutoScalingGroup (Maybe Int)
updateAutoScalingGroup_desiredCapacity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAutoScalingGroup' {Maybe Int
desiredCapacity :: Maybe Int
$sel:desiredCapacity:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Int
desiredCapacity} -> Maybe Int
desiredCapacity) (\s :: UpdateAutoScalingGroup
s@UpdateAutoScalingGroup' {} Maybe Int
a -> UpdateAutoScalingGroup
s {$sel:desiredCapacity:UpdateAutoScalingGroup' :: Maybe Int
desiredCapacity = Maybe Int
a} :: UpdateAutoScalingGroup)

-- | The unit of measurement for the value specified for desired capacity.
-- Amazon EC2 Auto Scaling supports @DesiredCapacityType@ for
-- attribute-based instance type selection only. For more information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/create-asg-instance-type-requirements.html Creating an Auto Scaling group using attribute-based instance type selection>
-- in the /Amazon EC2 Auto Scaling User Guide/.
--
-- By default, Amazon EC2 Auto Scaling specifies @units@, which translates
-- into number of instances.
--
-- Valid values: @units@ | @vcpu@ | @memory-mib@
updateAutoScalingGroup_desiredCapacityType :: Lens.Lens' UpdateAutoScalingGroup (Prelude.Maybe Prelude.Text)
updateAutoScalingGroup_desiredCapacityType :: Lens' UpdateAutoScalingGroup (Maybe Text)
updateAutoScalingGroup_desiredCapacityType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAutoScalingGroup' {Maybe Text
desiredCapacityType :: Maybe Text
$sel:desiredCapacityType:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Text
desiredCapacityType} -> Maybe Text
desiredCapacityType) (\s :: UpdateAutoScalingGroup
s@UpdateAutoScalingGroup' {} Maybe Text
a -> UpdateAutoScalingGroup
s {$sel:desiredCapacityType:UpdateAutoScalingGroup' :: Maybe Text
desiredCapacityType = Maybe Text
a} :: UpdateAutoScalingGroup)

-- | The amount of time, in seconds, that Amazon EC2 Auto Scaling waits
-- before checking the health status of an EC2 instance that has come into
-- service and marking it unhealthy due to a failed health check. This is
-- useful if your instances do not immediately pass their health checks
-- after they enter the @InService@ state. For more information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/health-check-grace-period.html Set the health check grace period for an Auto Scaling group>
-- in the /Amazon EC2 Auto Scaling User Guide/.
updateAutoScalingGroup_healthCheckGracePeriod :: Lens.Lens' UpdateAutoScalingGroup (Prelude.Maybe Prelude.Int)
updateAutoScalingGroup_healthCheckGracePeriod :: Lens' UpdateAutoScalingGroup (Maybe Int)
updateAutoScalingGroup_healthCheckGracePeriod = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAutoScalingGroup' {Maybe Int
healthCheckGracePeriod :: Maybe Int
$sel:healthCheckGracePeriod:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Int
healthCheckGracePeriod} -> Maybe Int
healthCheckGracePeriod) (\s :: UpdateAutoScalingGroup
s@UpdateAutoScalingGroup' {} Maybe Int
a -> UpdateAutoScalingGroup
s {$sel:healthCheckGracePeriod:UpdateAutoScalingGroup' :: Maybe Int
healthCheckGracePeriod = Maybe Int
a} :: UpdateAutoScalingGroup)

-- | 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.
updateAutoScalingGroup_healthCheckType :: Lens.Lens' UpdateAutoScalingGroup (Prelude.Maybe Prelude.Text)
updateAutoScalingGroup_healthCheckType :: Lens' UpdateAutoScalingGroup (Maybe Text)
updateAutoScalingGroup_healthCheckType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAutoScalingGroup' {Maybe Text
healthCheckType :: Maybe Text
$sel:healthCheckType:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Text
healthCheckType} -> Maybe Text
healthCheckType) (\s :: UpdateAutoScalingGroup
s@UpdateAutoScalingGroup' {} Maybe Text
a -> UpdateAutoScalingGroup
s {$sel:healthCheckType:UpdateAutoScalingGroup' :: Maybe Text
healthCheckType = Maybe Text
a} :: UpdateAutoScalingGroup)

-- | The name of the launch configuration. If you specify
-- @LaunchConfigurationName@ in your update request, you can\'t specify
-- @LaunchTemplate@ or @MixedInstancesPolicy@.
updateAutoScalingGroup_launchConfigurationName :: Lens.Lens' UpdateAutoScalingGroup (Prelude.Maybe Prelude.Text)
updateAutoScalingGroup_launchConfigurationName :: Lens' UpdateAutoScalingGroup (Maybe Text)
updateAutoScalingGroup_launchConfigurationName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAutoScalingGroup' {Maybe Text
launchConfigurationName :: Maybe Text
$sel:launchConfigurationName:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Text
launchConfigurationName} -> Maybe Text
launchConfigurationName) (\s :: UpdateAutoScalingGroup
s@UpdateAutoScalingGroup' {} Maybe Text
a -> UpdateAutoScalingGroup
s {$sel:launchConfigurationName:UpdateAutoScalingGroup' :: Maybe Text
launchConfigurationName = Maybe Text
a} :: UpdateAutoScalingGroup)

-- | The launch template and version to use to specify the updates. If you
-- specify @LaunchTemplate@ in your update request, you can\'t specify
-- @LaunchConfigurationName@ or @MixedInstancesPolicy@.
updateAutoScalingGroup_launchTemplate :: Lens.Lens' UpdateAutoScalingGroup (Prelude.Maybe LaunchTemplateSpecification)
updateAutoScalingGroup_launchTemplate :: Lens' UpdateAutoScalingGroup (Maybe LaunchTemplateSpecification)
updateAutoScalingGroup_launchTemplate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAutoScalingGroup' {Maybe LaunchTemplateSpecification
launchTemplate :: Maybe LaunchTemplateSpecification
$sel:launchTemplate:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe LaunchTemplateSpecification
launchTemplate} -> Maybe LaunchTemplateSpecification
launchTemplate) (\s :: UpdateAutoScalingGroup
s@UpdateAutoScalingGroup' {} Maybe LaunchTemplateSpecification
a -> UpdateAutoScalingGroup
s {$sel:launchTemplate:UpdateAutoScalingGroup' :: Maybe LaunchTemplateSpecification
launchTemplate = Maybe LaunchTemplateSpecification
a} :: UpdateAutoScalingGroup)

-- | The maximum amount of time, in seconds, that an instance can be in
-- service. The default is null. If specified, the value must be either 0
-- or a number equal to or greater than 86,400 seconds (1 day). To clear a
-- previously set value, specify a new value of 0. For more information,
-- see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/asg-max-instance-lifetime.html Replacing Auto Scaling instances based on maximum instance lifetime>
-- in the /Amazon EC2 Auto Scaling User Guide/.
updateAutoScalingGroup_maxInstanceLifetime :: Lens.Lens' UpdateAutoScalingGroup (Prelude.Maybe Prelude.Int)
updateAutoScalingGroup_maxInstanceLifetime :: Lens' UpdateAutoScalingGroup (Maybe Int)
updateAutoScalingGroup_maxInstanceLifetime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAutoScalingGroup' {Maybe Int
maxInstanceLifetime :: Maybe Int
$sel:maxInstanceLifetime:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Int
maxInstanceLifetime} -> Maybe Int
maxInstanceLifetime) (\s :: UpdateAutoScalingGroup
s@UpdateAutoScalingGroup' {} Maybe Int
a -> UpdateAutoScalingGroup
s {$sel:maxInstanceLifetime:UpdateAutoScalingGroup' :: Maybe Int
maxInstanceLifetime = Maybe Int
a} :: UpdateAutoScalingGroup)

-- | The maximum size of the Auto Scaling group.
--
-- With a mixed instances policy that uses instance weighting, Amazon EC2
-- Auto Scaling may need to go above @MaxSize@ to meet your capacity
-- requirements. In this event, Amazon EC2 Auto Scaling will never go above
-- @MaxSize@ by more than your largest instance weight (weights that define
-- how many units each instance contributes to the desired capacity of the
-- group).
updateAutoScalingGroup_maxSize :: Lens.Lens' UpdateAutoScalingGroup (Prelude.Maybe Prelude.Int)
updateAutoScalingGroup_maxSize :: Lens' UpdateAutoScalingGroup (Maybe Int)
updateAutoScalingGroup_maxSize = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAutoScalingGroup' {Maybe Int
maxSize :: Maybe Int
$sel:maxSize:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Int
maxSize} -> Maybe Int
maxSize) (\s :: UpdateAutoScalingGroup
s@UpdateAutoScalingGroup' {} Maybe Int
a -> UpdateAutoScalingGroup
s {$sel:maxSize:UpdateAutoScalingGroup' :: Maybe Int
maxSize = Maybe Int
a} :: UpdateAutoScalingGroup)

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

-- | The mixed instances policy. For more information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/ec2-auto-scaling-mixed-instances-groups.html Auto Scaling groups with multiple instance types and purchase options>
-- in the /Amazon EC2 Auto Scaling User Guide/.
updateAutoScalingGroup_mixedInstancesPolicy :: Lens.Lens' UpdateAutoScalingGroup (Prelude.Maybe MixedInstancesPolicy)
updateAutoScalingGroup_mixedInstancesPolicy :: Lens' UpdateAutoScalingGroup (Maybe MixedInstancesPolicy)
updateAutoScalingGroup_mixedInstancesPolicy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAutoScalingGroup' {Maybe MixedInstancesPolicy
mixedInstancesPolicy :: Maybe MixedInstancesPolicy
$sel:mixedInstancesPolicy:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe MixedInstancesPolicy
mixedInstancesPolicy} -> Maybe MixedInstancesPolicy
mixedInstancesPolicy) (\s :: UpdateAutoScalingGroup
s@UpdateAutoScalingGroup' {} Maybe MixedInstancesPolicy
a -> UpdateAutoScalingGroup
s {$sel:mixedInstancesPolicy:UpdateAutoScalingGroup' :: Maybe MixedInstancesPolicy
mixedInstancesPolicy = Maybe MixedInstancesPolicy
a} :: UpdateAutoScalingGroup)

-- | Indicates whether newly launched instances are protected from
-- termination by Amazon EC2 Auto Scaling when scaling in. For more
-- information about preventing instances from terminating on scale in, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/ec2-auto-scaling-instance-protection.html Using instance scale-in protection>
-- in the /Amazon EC2 Auto Scaling User Guide/.
updateAutoScalingGroup_newInstancesProtectedFromScaleIn :: Lens.Lens' UpdateAutoScalingGroup (Prelude.Maybe Prelude.Bool)
updateAutoScalingGroup_newInstancesProtectedFromScaleIn :: Lens' UpdateAutoScalingGroup (Maybe Bool)
updateAutoScalingGroup_newInstancesProtectedFromScaleIn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAutoScalingGroup' {Maybe Bool
newInstancesProtectedFromScaleIn' :: Maybe Bool
$sel:newInstancesProtectedFromScaleIn':UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Bool
newInstancesProtectedFromScaleIn'} -> Maybe Bool
newInstancesProtectedFromScaleIn') (\s :: UpdateAutoScalingGroup
s@UpdateAutoScalingGroup' {} Maybe Bool
a -> UpdateAutoScalingGroup
s {$sel:newInstancesProtectedFromScaleIn':UpdateAutoScalingGroup' :: Maybe Bool
newInstancesProtectedFromScaleIn' = Maybe Bool
a} :: UpdateAutoScalingGroup)

-- | The name of an existing placement group into which to launch your
-- instances. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/placement-groups.html Placement groups>
-- in the /Amazon EC2 User Guide for Linux Instances/.
--
-- A /cluster/ placement group is a logical grouping of instances within a
-- single Availability Zone. You cannot specify multiple Availability Zones
-- and a cluster placement group.
updateAutoScalingGroup_placementGroup :: Lens.Lens' UpdateAutoScalingGroup (Prelude.Maybe Prelude.Text)
updateAutoScalingGroup_placementGroup :: Lens' UpdateAutoScalingGroup (Maybe Text)
updateAutoScalingGroup_placementGroup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAutoScalingGroup' {Maybe Text
placementGroup :: Maybe Text
$sel:placementGroup:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Text
placementGroup} -> Maybe Text
placementGroup) (\s :: UpdateAutoScalingGroup
s@UpdateAutoScalingGroup' {} Maybe Text
a -> UpdateAutoScalingGroup
s {$sel:placementGroup:UpdateAutoScalingGroup' :: Maybe Text
placementGroup = Maybe Text
a} :: UpdateAutoScalingGroup)

-- | 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. For
-- more information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/autoscaling-service-linked-role.html Service-linked roles>
-- in the /Amazon EC2 Auto Scaling User Guide/.
updateAutoScalingGroup_serviceLinkedRoleARN :: Lens.Lens' UpdateAutoScalingGroup (Prelude.Maybe Prelude.Text)
updateAutoScalingGroup_serviceLinkedRoleARN :: Lens' UpdateAutoScalingGroup (Maybe Text)
updateAutoScalingGroup_serviceLinkedRoleARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAutoScalingGroup' {Maybe Text
serviceLinkedRoleARN :: Maybe Text
$sel:serviceLinkedRoleARN:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Text
serviceLinkedRoleARN} -> Maybe Text
serviceLinkedRoleARN) (\s :: UpdateAutoScalingGroup
s@UpdateAutoScalingGroup' {} Maybe Text
a -> UpdateAutoScalingGroup
s {$sel:serviceLinkedRoleARN:UpdateAutoScalingGroup' :: Maybe Text
serviceLinkedRoleARN = Maybe Text
a} :: UpdateAutoScalingGroup)

-- | A policy or a list of policies that are used to select the instances to
-- terminate. The policies are executed in the order that you list them.
-- For more information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/ec2-auto-scaling-termination-policies.html Work with Amazon EC2 Auto Scaling termination policies>
-- in the /Amazon EC2 Auto Scaling User Guide/.
--
-- Valid values: @Default@ | @AllocationStrategy@ |
-- @ClosestToNextInstanceHour@ | @NewestInstance@ | @OldestInstance@ |
-- @OldestLaunchConfiguration@ | @OldestLaunchTemplate@ |
-- @arn:aws:lambda:region:account-id:function:my-function:my-alias@
updateAutoScalingGroup_terminationPolicies :: Lens.Lens' UpdateAutoScalingGroup (Prelude.Maybe [Prelude.Text])
updateAutoScalingGroup_terminationPolicies :: Lens' UpdateAutoScalingGroup (Maybe [Text])
updateAutoScalingGroup_terminationPolicies = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAutoScalingGroup' {Maybe [Text]
terminationPolicies :: Maybe [Text]
$sel:terminationPolicies:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe [Text]
terminationPolicies} -> Maybe [Text]
terminationPolicies) (\s :: UpdateAutoScalingGroup
s@UpdateAutoScalingGroup' {} Maybe [Text]
a -> UpdateAutoScalingGroup
s {$sel:terminationPolicies:UpdateAutoScalingGroup' :: Maybe [Text]
terminationPolicies = Maybe [Text]
a} :: UpdateAutoScalingGroup) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | A comma-separated list of subnet IDs for a virtual private cloud (VPC).
-- If you specify @VPCZoneIdentifier@ with @AvailabilityZones@, the subnets
-- that you specify must reside in those Availability Zones.
updateAutoScalingGroup_vPCZoneIdentifier :: Lens.Lens' UpdateAutoScalingGroup (Prelude.Maybe Prelude.Text)
updateAutoScalingGroup_vPCZoneIdentifier :: Lens' UpdateAutoScalingGroup (Maybe Text)
updateAutoScalingGroup_vPCZoneIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAutoScalingGroup' {Maybe Text
vPCZoneIdentifier :: Maybe Text
$sel:vPCZoneIdentifier:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Text
vPCZoneIdentifier} -> Maybe Text
vPCZoneIdentifier) (\s :: UpdateAutoScalingGroup
s@UpdateAutoScalingGroup' {} Maybe Text
a -> UpdateAutoScalingGroup
s {$sel:vPCZoneIdentifier:UpdateAutoScalingGroup' :: Maybe Text
vPCZoneIdentifier = Maybe Text
a} :: UpdateAutoScalingGroup)

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

instance Core.AWSRequest UpdateAutoScalingGroup where
  type
    AWSResponse UpdateAutoScalingGroup =
      UpdateAutoScalingGroupResponse
  request :: (Service -> Service)
-> UpdateAutoScalingGroup -> Request UpdateAutoScalingGroup
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateAutoScalingGroup
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateAutoScalingGroup)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull
      UpdateAutoScalingGroupResponse
UpdateAutoScalingGroupResponse'

instance Prelude.Hashable UpdateAutoScalingGroup where
  hashWithSalt :: Int -> UpdateAutoScalingGroup -> Int
hashWithSalt Int
_salt UpdateAutoScalingGroup' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe Text
Maybe LaunchTemplateSpecification
Maybe MixedInstancesPolicy
Text
autoScalingGroupName :: Text
vPCZoneIdentifier :: Maybe Text
terminationPolicies :: Maybe [Text]
serviceLinkedRoleARN :: Maybe Text
placementGroup :: Maybe Text
newInstancesProtectedFromScaleIn' :: Maybe Bool
mixedInstancesPolicy :: Maybe MixedInstancesPolicy
minSize :: Maybe Int
maxSize :: Maybe Int
maxInstanceLifetime :: Maybe Int
launchTemplate :: Maybe LaunchTemplateSpecification
launchConfigurationName :: Maybe Text
healthCheckType :: Maybe Text
healthCheckGracePeriod :: Maybe Int
desiredCapacityType :: Maybe Text
desiredCapacity :: Maybe Int
defaultInstanceWarmup :: Maybe Int
defaultCooldown :: Maybe Int
context :: Maybe Text
capacityRebalance :: Maybe Bool
availabilityZones :: Maybe [Text]
$sel:autoScalingGroupName:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Text
$sel:vPCZoneIdentifier:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Text
$sel:terminationPolicies:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe [Text]
$sel:serviceLinkedRoleARN:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Text
$sel:placementGroup:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Text
$sel:newInstancesProtectedFromScaleIn':UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Bool
$sel:mixedInstancesPolicy:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe MixedInstancesPolicy
$sel:minSize:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Int
$sel:maxSize:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Int
$sel:maxInstanceLifetime:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Int
$sel:launchTemplate:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe LaunchTemplateSpecification
$sel:launchConfigurationName:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Text
$sel:healthCheckType:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Text
$sel:healthCheckGracePeriod:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Int
$sel:desiredCapacityType:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Text
$sel:desiredCapacity:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Int
$sel:defaultInstanceWarmup:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Int
$sel:defaultCooldown:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Int
$sel:context:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Text
$sel:capacityRebalance:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Bool
$sel:availabilityZones:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe [Text]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
availabilityZones
      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
defaultCooldown
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
defaultInstanceWarmup
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
desiredCapacity
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
desiredCapacityType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
healthCheckGracePeriod
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
healthCheckType
      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 Int
maxInstanceLifetime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxSize
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
minSize
      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 Text
serviceLinkedRoleARN
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
terminationPolicies
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
vPCZoneIdentifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
autoScalingGroupName

instance Prelude.NFData UpdateAutoScalingGroup where
  rnf :: UpdateAutoScalingGroup -> ()
rnf UpdateAutoScalingGroup' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe Text
Maybe LaunchTemplateSpecification
Maybe MixedInstancesPolicy
Text
autoScalingGroupName :: Text
vPCZoneIdentifier :: Maybe Text
terminationPolicies :: Maybe [Text]
serviceLinkedRoleARN :: Maybe Text
placementGroup :: Maybe Text
newInstancesProtectedFromScaleIn' :: Maybe Bool
mixedInstancesPolicy :: Maybe MixedInstancesPolicy
minSize :: Maybe Int
maxSize :: Maybe Int
maxInstanceLifetime :: Maybe Int
launchTemplate :: Maybe LaunchTemplateSpecification
launchConfigurationName :: Maybe Text
healthCheckType :: Maybe Text
healthCheckGracePeriod :: Maybe Int
desiredCapacityType :: Maybe Text
desiredCapacity :: Maybe Int
defaultInstanceWarmup :: Maybe Int
defaultCooldown :: Maybe Int
context :: Maybe Text
capacityRebalance :: Maybe Bool
availabilityZones :: Maybe [Text]
$sel:autoScalingGroupName:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Text
$sel:vPCZoneIdentifier:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Text
$sel:terminationPolicies:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe [Text]
$sel:serviceLinkedRoleARN:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Text
$sel:placementGroup:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Text
$sel:newInstancesProtectedFromScaleIn':UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Bool
$sel:mixedInstancesPolicy:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe MixedInstancesPolicy
$sel:minSize:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Int
$sel:maxSize:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Int
$sel:maxInstanceLifetime:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Int
$sel:launchTemplate:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe LaunchTemplateSpecification
$sel:launchConfigurationName:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Text
$sel:healthCheckType:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Text
$sel:healthCheckGracePeriod:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Int
$sel:desiredCapacityType:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Text
$sel:desiredCapacity:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Int
$sel:defaultInstanceWarmup:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Int
$sel:defaultCooldown:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Int
$sel:context:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Text
$sel:capacityRebalance:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Bool
$sel:availabilityZones:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
availabilityZones
      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
defaultCooldown
      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 Int
desiredCapacity
      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 Int
healthCheckGracePeriod
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
healthCheckType
      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 Int
maxInstanceLifetime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
maxSize
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
minSize
      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 Text
serviceLinkedRoleARN
      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 Text
vPCZoneIdentifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Text
autoScalingGroupName

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

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

instance Data.ToQuery UpdateAutoScalingGroup where
  toQuery :: UpdateAutoScalingGroup -> QueryString
toQuery UpdateAutoScalingGroup' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe Text
Maybe LaunchTemplateSpecification
Maybe MixedInstancesPolicy
Text
autoScalingGroupName :: Text
vPCZoneIdentifier :: Maybe Text
terminationPolicies :: Maybe [Text]
serviceLinkedRoleARN :: Maybe Text
placementGroup :: Maybe Text
newInstancesProtectedFromScaleIn' :: Maybe Bool
mixedInstancesPolicy :: Maybe MixedInstancesPolicy
minSize :: Maybe Int
maxSize :: Maybe Int
maxInstanceLifetime :: Maybe Int
launchTemplate :: Maybe LaunchTemplateSpecification
launchConfigurationName :: Maybe Text
healthCheckType :: Maybe Text
healthCheckGracePeriod :: Maybe Int
desiredCapacityType :: Maybe Text
desiredCapacity :: Maybe Int
defaultInstanceWarmup :: Maybe Int
defaultCooldown :: Maybe Int
context :: Maybe Text
capacityRebalance :: Maybe Bool
availabilityZones :: Maybe [Text]
$sel:autoScalingGroupName:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Text
$sel:vPCZoneIdentifier:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Text
$sel:terminationPolicies:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe [Text]
$sel:serviceLinkedRoleARN:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Text
$sel:placementGroup:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Text
$sel:newInstancesProtectedFromScaleIn':UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Bool
$sel:mixedInstancesPolicy:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe MixedInstancesPolicy
$sel:minSize:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Int
$sel:maxSize:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Int
$sel:maxInstanceLifetime:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Int
$sel:launchTemplate:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe LaunchTemplateSpecification
$sel:launchConfigurationName:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Text
$sel:healthCheckType:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Text
$sel:healthCheckGracePeriod:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Int
$sel:desiredCapacityType:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Text
$sel:desiredCapacity:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Int
$sel:defaultInstanceWarmup:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Int
$sel:defaultCooldown:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Int
$sel:context:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Text
$sel:capacityRebalance:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe Bool
$sel:availabilityZones:UpdateAutoScalingGroup' :: UpdateAutoScalingGroup -> Maybe [Text]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"UpdateAutoScalingGroup" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2011-01-01" :: Prelude.ByteString),
        ByteString
"AvailabilityZones"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member"
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
availabilityZones
            ),
        ByteString
"CapacityRebalance" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
capacityRebalance,
        ByteString
"Context" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
context,
        ByteString
"DefaultCooldown" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
defaultCooldown,
        ByteString
"DefaultInstanceWarmup"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
defaultInstanceWarmup,
        ByteString
"DesiredCapacity" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
desiredCapacity,
        ByteString
"DesiredCapacityType" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
desiredCapacityType,
        ByteString
"HealthCheckGracePeriod"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
healthCheckGracePeriod,
        ByteString
"HealthCheckType" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
healthCheckType,
        ByteString
"LaunchConfigurationName"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
launchConfigurationName,
        ByteString
"LaunchTemplate" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe LaunchTemplateSpecification
launchTemplate,
        ByteString
"MaxInstanceLifetime" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
maxInstanceLifetime,
        ByteString
"MaxSize" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
maxSize,
        ByteString
"MinSize" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
minSize,
        ByteString
"MixedInstancesPolicy" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe MixedInstancesPolicy
mixedInstancesPolicy,
        ByteString
"NewInstancesProtectedFromScaleIn"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
newInstancesProtectedFromScaleIn',
        ByteString
"PlacementGroup" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
placementGroup,
        ByteString
"ServiceLinkedRoleARN" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
serviceLinkedRoleARN,
        ByteString
"TerminationPolicies"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member"
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
terminationPolicies
            ),
        ByteString
"VPCZoneIdentifier" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
vPCZoneIdentifier,
        ByteString
"AutoScalingGroupName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
autoScalingGroupName
      ]

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

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

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