{-# 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.CreateAutoScalingGroup
-- 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 using a launch template when calling this
-- operation to ensure full functionality for Amazon EC2 Auto Scaling and
-- Amazon EC2.__
--
-- Creates an Auto Scaling group with the specified name and attributes.
--
-- If you exceed your maximum limit of Auto Scaling groups, the call fails.
-- To query this limit, call the DescribeAccountLimits API. For information
-- about updating this limit, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/ec2-auto-scaling-quotas.html Quotas for Amazon EC2 Auto Scaling>
-- in the /Amazon EC2 Auto Scaling User Guide/.
--
-- For introductory exercises for creating an Auto Scaling group, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/GettingStartedTutorial.html Getting started with Amazon EC2 Auto Scaling>
-- and
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/as-register-lbs-with-asg.html Tutorial: Set up a scaled and load-balanced application>
-- in the /Amazon EC2 Auto Scaling User Guide/. For more information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/AutoScalingGroup.html Auto Scaling groups>
-- in the /Amazon EC2 Auto Scaling User Guide/.
--
-- Every Auto Scaling group has three size properties (@DesiredCapacity@,
-- @MaxSize@, and @MinSize@). Usually, you set these sizes based on a
-- specific number of instances. However, if you configure a mixed
-- instances policy that defines weights for the instance types, you must
-- specify these sizes with the same units that you use for weighting
-- instances.
module Amazonka.AutoScaling.CreateAutoScalingGroup
  ( -- * Creating a Request
    CreateAutoScalingGroup (..),
    newCreateAutoScalingGroup,

    -- * Request Lenses
    createAutoScalingGroup_availabilityZones,
    createAutoScalingGroup_capacityRebalance,
    createAutoScalingGroup_context,
    createAutoScalingGroup_defaultCooldown,
    createAutoScalingGroup_defaultInstanceWarmup,
    createAutoScalingGroup_desiredCapacity,
    createAutoScalingGroup_desiredCapacityType,
    createAutoScalingGroup_healthCheckGracePeriod,
    createAutoScalingGroup_healthCheckType,
    createAutoScalingGroup_instanceId,
    createAutoScalingGroup_launchConfigurationName,
    createAutoScalingGroup_launchTemplate,
    createAutoScalingGroup_lifecycleHookSpecificationList,
    createAutoScalingGroup_loadBalancerNames,
    createAutoScalingGroup_maxInstanceLifetime,
    createAutoScalingGroup_mixedInstancesPolicy,
    createAutoScalingGroup_newInstancesProtectedFromScaleIn,
    createAutoScalingGroup_placementGroup,
    createAutoScalingGroup_serviceLinkedRoleARN,
    createAutoScalingGroup_tags,
    createAutoScalingGroup_targetGroupARNs,
    createAutoScalingGroup_terminationPolicies,
    createAutoScalingGroup_trafficSources,
    createAutoScalingGroup_vPCZoneIdentifier,
    createAutoScalingGroup_autoScalingGroupName,
    createAutoScalingGroup_minSize,
    createAutoScalingGroup_maxSize,

    -- * Destructuring the Response
    CreateAutoScalingGroupResponse (..),
    newCreateAutoScalingGroupResponse,
  )
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:/ 'newCreateAutoScalingGroup' smart constructor.
data CreateAutoScalingGroup = CreateAutoScalingGroup'
  { -- | A list of Availability Zones where instances in the Auto Scaling group
    -- can be created. Used for launching into the default VPC subnet in each
    -- Availability Zone when not using the @VPCZoneIdentifier@ property, or
    -- for attaching a network interface when an existing network interface ID
    -- is specified in a launch template.
    CreateAutoScalingGroup -> Maybe [Text]
availabilityZones :: Prelude.Maybe [Prelude.Text],
    -- | Indicates whether Capacity Rebalancing is enabled. Otherwise, Capacity
    -- Rebalancing is disabled. When you turn on Capacity Rebalancing, Amazon
    -- EC2 Auto Scaling attempts to launch a Spot Instance whenever Amazon EC2
    -- notifies that a Spot Instance is at an elevated risk of interruption.
    -- After launching a new instance, it then terminates an old instance. 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 in the /Amazon EC2 Auto Scaling User Guide/.
    CreateAutoScalingGroup -> Maybe Bool
capacityRebalance :: Prelude.Maybe Prelude.Bool,
    -- | Reserved.
    CreateAutoScalingGroup -> 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/.
    --
    -- Default: @300@ seconds
    CreateAutoScalingGroup -> 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@.
    --
    -- Default: None
    CreateAutoScalingGroup -> Maybe Int
defaultInstanceWarmup :: Prelude.Maybe Prelude.Int,
    -- | The desired capacity is the initial capacity of the Auto Scaling group
    -- at the time of its creation and the capacity it attempts to maintain. It
    -- can scale beyond this capacity if you configure auto scaling. 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. If you do not
    -- specify a desired capacity, the default is the minimum size of the
    -- group.
    CreateAutoScalingGroup -> 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@
    CreateAutoScalingGroup -> 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/.
    --
    -- Default: @0@ seconds
    CreateAutoScalingGroup -> 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. For
    -- more information, see
    -- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/healthcheck.html Health checks for Auto Scaling instances>
    -- in the /Amazon EC2 Auto Scaling User Guide/.
    --
    -- 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.
    CreateAutoScalingGroup -> Maybe Text
healthCheckType :: Prelude.Maybe Prelude.Text,
    -- | The ID of the instance used to base the launch configuration on. If
    -- specified, Amazon EC2 Auto Scaling uses the configuration values from
    -- the specified instance to create a new launch configuration. To get the
    -- instance ID, use the Amazon EC2
    -- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_DescribeInstances.html DescribeInstances>
    -- API operation. For more information, see
    -- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/create-asg-from-instance.html Creating an Auto Scaling group using an EC2 instance>
    -- in the /Amazon EC2 Auto Scaling User Guide/.
    CreateAutoScalingGroup -> Maybe Text
instanceId :: Prelude.Maybe Prelude.Text,
    -- | The name of the launch configuration to use to launch instances.
    --
    -- Conditional: You must specify either a launch template (@LaunchTemplate@
    -- or @MixedInstancesPolicy@) or a launch configuration
    -- (@LaunchConfigurationName@ or @InstanceId@).
    CreateAutoScalingGroup -> Maybe Text
launchConfigurationName :: Prelude.Maybe Prelude.Text,
    -- | Information used to specify the launch template and version to use to
    -- launch instances.
    --
    -- Conditional: You must specify either a launch template (@LaunchTemplate@
    -- or @MixedInstancesPolicy@) or a launch configuration
    -- (@LaunchConfigurationName@ or @InstanceId@).
    --
    -- The launch template that is specified must be configured for use with an
    -- Auto Scaling group. For more information, see
    -- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/create-launch-template.html Creating a launch template for an Auto Scaling group>
    -- in the /Amazon EC2 Auto Scaling User Guide/.
    CreateAutoScalingGroup -> Maybe LaunchTemplateSpecification
launchTemplate :: Prelude.Maybe LaunchTemplateSpecification,
    -- | One or more lifecycle hooks to add to the Auto Scaling group before
    -- instances are launched.
    CreateAutoScalingGroup -> Maybe [LifecycleHookSpecification]
lifecycleHookSpecificationList :: Prelude.Maybe [LifecycleHookSpecification],
    -- | A list of Classic Load Balancers associated with this Auto Scaling
    -- group. For Application Load Balancers, Network Load Balancers, and
    -- Gateway Load Balancer, specify the @TargetGroupARNs@ property instead.
    CreateAutoScalingGroup -> Maybe [Text]
loadBalancerNames :: Prelude.Maybe [Prelude.Text],
    -- | 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). 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/.
    CreateAutoScalingGroup -> Maybe Int
maxInstanceLifetime :: 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/.
    CreateAutoScalingGroup -> 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/.
    CreateAutoScalingGroup -> Maybe Bool
newInstancesProtectedFromScaleIn' :: Prelude.Maybe Prelude.Bool,
    -- | The name of the 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.
    CreateAutoScalingGroup -> 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 service on your
    -- behalf. By default, Amazon EC2 Auto Scaling uses a service-linked role
    -- named @AWSServiceRoleForAutoScaling@, which it creates if it does not
    -- exist. 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/.
    CreateAutoScalingGroup -> Maybe Text
serviceLinkedRoleARN :: Prelude.Maybe Prelude.Text,
    -- | One or more tags. You can tag your Auto Scaling group and propagate the
    -- tags to the Amazon EC2 instances it launches. Tags are not propagated to
    -- Amazon EBS volumes. To add tags to Amazon EBS volumes, specify the tags
    -- in a launch template but use caution. If the launch template specifies
    -- an instance tag with a key that is also specified for the Auto Scaling
    -- group, Amazon EC2 Auto Scaling overrides the value of that instance tag
    -- with the value specified by the Auto Scaling group. For more
    -- information, see
    -- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/ec2-auto-scaling-tagging.html Tag Auto Scaling groups and instances>
    -- in the /Amazon EC2 Auto Scaling User Guide/.
    CreateAutoScalingGroup -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The Amazon Resource Names (ARN) of the Elastic Load Balancing target
    -- groups to associate with the Auto Scaling group. Instances are
    -- registered as targets with the target groups. The target groups receive
    -- incoming traffic and route requests to one or more registered targets.
    -- For more information, see
    -- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/autoscaling-load-balancer.html Use Elastic Load Balancing to distribute traffic across the instances in your Auto Scaling group>
    -- in the /Amazon EC2 Auto Scaling User Guide/.
    CreateAutoScalingGroup -> Maybe [Text]
targetGroupARNs :: Prelude.Maybe [Prelude.Text],
    -- | A policy or a list of policies that are used to select the instance to
    -- terminate. These 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@
    CreateAutoScalingGroup -> Maybe [Text]
terminationPolicies :: Prelude.Maybe [Prelude.Text],
    -- | __Reserved for use with Amazon VPC Lattice, which is in preview release
    -- and is subject to change. Do not use this parameter for production
    -- workloads. It is also subject to change.__
    --
    -- The unique identifiers of one or more traffic sources.
    --
    -- Currently, you must specify an Amazon Resource Name (ARN) for an
    -- existing VPC Lattice target group. Amazon EC2 Auto Scaling registers the
    -- running instances with the attached target groups. The target groups
    -- receive incoming traffic and route requests to one or more registered
    -- targets.
    CreateAutoScalingGroup -> Maybe [TrafficSourceIdentifier]
trafficSources :: Prelude.Maybe [TrafficSourceIdentifier],
    -- | A comma-separated list of subnet IDs for a virtual private cloud (VPC)
    -- where instances in the Auto Scaling group can be created. If you specify
    -- @VPCZoneIdentifier@ with @AvailabilityZones@, the subnets that you
    -- specify must reside in those Availability Zones.
    CreateAutoScalingGroup -> Maybe Text
vPCZoneIdentifier :: Prelude.Maybe Prelude.Text,
    -- | The name of the Auto Scaling group. This name must be unique per Region
    -- per account.
    --
    -- The name can contain any ASCII character 33 to 126 including most
    -- punctuation characters, digits, and upper and lowercased letters.
    --
    -- You cannot use a colon (:) in the name.
    CreateAutoScalingGroup -> Text
autoScalingGroupName :: Prelude.Text,
    -- | The minimum size of the group.
    CreateAutoScalingGroup -> Int
minSize :: Prelude.Int,
    -- | The maximum size of the 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).
    CreateAutoScalingGroup -> Int
maxSize :: Prelude.Int
  }
  deriving (CreateAutoScalingGroup -> CreateAutoScalingGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateAutoScalingGroup -> CreateAutoScalingGroup -> Bool
$c/= :: CreateAutoScalingGroup -> CreateAutoScalingGroup -> Bool
== :: CreateAutoScalingGroup -> CreateAutoScalingGroup -> Bool
$c== :: CreateAutoScalingGroup -> CreateAutoScalingGroup -> Bool
Prelude.Eq, ReadPrec [CreateAutoScalingGroup]
ReadPrec CreateAutoScalingGroup
Int -> ReadS CreateAutoScalingGroup
ReadS [CreateAutoScalingGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateAutoScalingGroup]
$creadListPrec :: ReadPrec [CreateAutoScalingGroup]
readPrec :: ReadPrec CreateAutoScalingGroup
$creadPrec :: ReadPrec CreateAutoScalingGroup
readList :: ReadS [CreateAutoScalingGroup]
$creadList :: ReadS [CreateAutoScalingGroup]
readsPrec :: Int -> ReadS CreateAutoScalingGroup
$creadsPrec :: Int -> ReadS CreateAutoScalingGroup
Prelude.Read, Int -> CreateAutoScalingGroup -> ShowS
[CreateAutoScalingGroup] -> ShowS
CreateAutoScalingGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateAutoScalingGroup] -> ShowS
$cshowList :: [CreateAutoScalingGroup] -> ShowS
show :: CreateAutoScalingGroup -> String
$cshow :: CreateAutoScalingGroup -> String
showsPrec :: Int -> CreateAutoScalingGroup -> ShowS
$cshowsPrec :: Int -> CreateAutoScalingGroup -> ShowS
Prelude.Show, forall x. Rep CreateAutoScalingGroup x -> CreateAutoScalingGroup
forall x. CreateAutoScalingGroup -> Rep CreateAutoScalingGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateAutoScalingGroup x -> CreateAutoScalingGroup
$cfrom :: forall x. CreateAutoScalingGroup -> Rep CreateAutoScalingGroup x
Prelude.Generic)

-- |
-- Create a value of 'CreateAutoScalingGroup' 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', 'createAutoScalingGroup_availabilityZones' - A list of Availability Zones where instances in the Auto Scaling group
-- can be created. Used for launching into the default VPC subnet in each
-- Availability Zone when not using the @VPCZoneIdentifier@ property, or
-- for attaching a network interface when an existing network interface ID
-- is specified in a launch template.
--
-- 'capacityRebalance', 'createAutoScalingGroup_capacityRebalance' - Indicates whether Capacity Rebalancing is enabled. Otherwise, Capacity
-- Rebalancing is disabled. When you turn on Capacity Rebalancing, Amazon
-- EC2 Auto Scaling attempts to launch a Spot Instance whenever Amazon EC2
-- notifies that a Spot Instance is at an elevated risk of interruption.
-- After launching a new instance, it then terminates an old instance. 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 in the /Amazon EC2 Auto Scaling User Guide/.
--
-- 'context', 'createAutoScalingGroup_context' - Reserved.
--
-- 'defaultCooldown', 'createAutoScalingGroup_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/.
--
-- Default: @300@ seconds
--
-- 'defaultInstanceWarmup', 'createAutoScalingGroup_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@.
--
-- Default: None
--
-- 'desiredCapacity', 'createAutoScalingGroup_desiredCapacity' - The desired capacity is the initial capacity of the Auto Scaling group
-- at the time of its creation and the capacity it attempts to maintain. It
-- can scale beyond this capacity if you configure auto scaling. 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. If you do not
-- specify a desired capacity, the default is the minimum size of the
-- group.
--
-- 'desiredCapacityType', 'createAutoScalingGroup_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', 'createAutoScalingGroup_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/.
--
-- Default: @0@ seconds
--
-- 'healthCheckType', 'createAutoScalingGroup_healthCheckType' - Determines whether any additional health checks are performed on the
-- instances in this group. Amazon EC2 health checks are always on. For
-- more information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/healthcheck.html Health checks for Auto Scaling instances>
-- in the /Amazon EC2 Auto Scaling User Guide/.
--
-- 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.
--
-- 'instanceId', 'createAutoScalingGroup_instanceId' - The ID of the instance used to base the launch configuration on. If
-- specified, Amazon EC2 Auto Scaling uses the configuration values from
-- the specified instance to create a new launch configuration. To get the
-- instance ID, use the Amazon EC2
-- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_DescribeInstances.html DescribeInstances>
-- API operation. For more information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/create-asg-from-instance.html Creating an Auto Scaling group using an EC2 instance>
-- in the /Amazon EC2 Auto Scaling User Guide/.
--
-- 'launchConfigurationName', 'createAutoScalingGroup_launchConfigurationName' - The name of the launch configuration to use to launch instances.
--
-- Conditional: You must specify either a launch template (@LaunchTemplate@
-- or @MixedInstancesPolicy@) or a launch configuration
-- (@LaunchConfigurationName@ or @InstanceId@).
--
-- 'launchTemplate', 'createAutoScalingGroup_launchTemplate' - Information used to specify the launch template and version to use to
-- launch instances.
--
-- Conditional: You must specify either a launch template (@LaunchTemplate@
-- or @MixedInstancesPolicy@) or a launch configuration
-- (@LaunchConfigurationName@ or @InstanceId@).
--
-- The launch template that is specified must be configured for use with an
-- Auto Scaling group. For more information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/create-launch-template.html Creating a launch template for an Auto Scaling group>
-- in the /Amazon EC2 Auto Scaling User Guide/.
--
-- 'lifecycleHookSpecificationList', 'createAutoScalingGroup_lifecycleHookSpecificationList' - One or more lifecycle hooks to add to the Auto Scaling group before
-- instances are launched.
--
-- 'loadBalancerNames', 'createAutoScalingGroup_loadBalancerNames' - A list of Classic Load Balancers associated with this Auto Scaling
-- group. For Application Load Balancers, Network Load Balancers, and
-- Gateway Load Balancer, specify the @TargetGroupARNs@ property instead.
--
-- 'maxInstanceLifetime', 'createAutoScalingGroup_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). 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/.
--
-- 'mixedInstancesPolicy', 'createAutoScalingGroup_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'', 'createAutoScalingGroup_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', 'createAutoScalingGroup_placementGroup' - The name of the 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', 'createAutoScalingGroup_serviceLinkedRoleARN' - The Amazon Resource Name (ARN) of the service-linked role that the Auto
-- Scaling group uses to call other Amazon Web Services service on your
-- behalf. By default, Amazon EC2 Auto Scaling uses a service-linked role
-- named @AWSServiceRoleForAutoScaling@, which it creates if it does not
-- exist. 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/.
--
-- 'tags', 'createAutoScalingGroup_tags' - One or more tags. You can tag your Auto Scaling group and propagate the
-- tags to the Amazon EC2 instances it launches. Tags are not propagated to
-- Amazon EBS volumes. To add tags to Amazon EBS volumes, specify the tags
-- in a launch template but use caution. If the launch template specifies
-- an instance tag with a key that is also specified for the Auto Scaling
-- group, Amazon EC2 Auto Scaling overrides the value of that instance tag
-- with the value specified by the Auto Scaling group. For more
-- information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/ec2-auto-scaling-tagging.html Tag Auto Scaling groups and instances>
-- in the /Amazon EC2 Auto Scaling User Guide/.
--
-- 'targetGroupARNs', 'createAutoScalingGroup_targetGroupARNs' - The Amazon Resource Names (ARN) of the Elastic Load Balancing target
-- groups to associate with the Auto Scaling group. Instances are
-- registered as targets with the target groups. The target groups receive
-- incoming traffic and route requests to one or more registered targets.
-- For more information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/autoscaling-load-balancer.html Use Elastic Load Balancing to distribute traffic across the instances in your Auto Scaling group>
-- in the /Amazon EC2 Auto Scaling User Guide/.
--
-- 'terminationPolicies', 'createAutoScalingGroup_terminationPolicies' - A policy or a list of policies that are used to select the instance to
-- terminate. These 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@
--
-- 'trafficSources', 'createAutoScalingGroup_trafficSources' - __Reserved for use with Amazon VPC Lattice, which is in preview release
-- and is subject to change. Do not use this parameter for production
-- workloads. It is also subject to change.__
--
-- The unique identifiers of one or more traffic sources.
--
-- Currently, you must specify an Amazon Resource Name (ARN) for an
-- existing VPC Lattice target group. Amazon EC2 Auto Scaling registers the
-- running instances with the attached target groups. The target groups
-- receive incoming traffic and route requests to one or more registered
-- targets.
--
-- 'vPCZoneIdentifier', 'createAutoScalingGroup_vPCZoneIdentifier' - A comma-separated list of subnet IDs for a virtual private cloud (VPC)
-- where instances in the Auto Scaling group can be created. If you specify
-- @VPCZoneIdentifier@ with @AvailabilityZones@, the subnets that you
-- specify must reside in those Availability Zones.
--
-- 'autoScalingGroupName', 'createAutoScalingGroup_autoScalingGroupName' - The name of the Auto Scaling group. This name must be unique per Region
-- per account.
--
-- The name can contain any ASCII character 33 to 126 including most
-- punctuation characters, digits, and upper and lowercased letters.
--
-- You cannot use a colon (:) in the name.
--
-- 'minSize', 'createAutoScalingGroup_minSize' - The minimum size of the group.
--
-- 'maxSize', 'createAutoScalingGroup_maxSize' - The maximum size of the 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).
newCreateAutoScalingGroup ::
  -- | 'autoScalingGroupName'
  Prelude.Text ->
  -- | 'minSize'
  Prelude.Int ->
  -- | 'maxSize'
  Prelude.Int ->
  CreateAutoScalingGroup
newCreateAutoScalingGroup :: Text -> Int -> Int -> CreateAutoScalingGroup
newCreateAutoScalingGroup
  Text
pAutoScalingGroupName_
  Int
pMinSize_
  Int
pMaxSize_ =
    CreateAutoScalingGroup'
      { $sel:availabilityZones:CreateAutoScalingGroup' :: Maybe [Text]
availabilityZones =
          forall a. Maybe a
Prelude.Nothing,
        $sel:capacityRebalance:CreateAutoScalingGroup' :: Maybe Bool
capacityRebalance = forall a. Maybe a
Prelude.Nothing,
        $sel:context:CreateAutoScalingGroup' :: Maybe Text
context = forall a. Maybe a
Prelude.Nothing,
        $sel:defaultCooldown:CreateAutoScalingGroup' :: Maybe Int
defaultCooldown = forall a. Maybe a
Prelude.Nothing,
        $sel:defaultInstanceWarmup:CreateAutoScalingGroup' :: Maybe Int
defaultInstanceWarmup = forall a. Maybe a
Prelude.Nothing,
        $sel:desiredCapacity:CreateAutoScalingGroup' :: Maybe Int
desiredCapacity = forall a. Maybe a
Prelude.Nothing,
        $sel:desiredCapacityType:CreateAutoScalingGroup' :: Maybe Text
desiredCapacityType = forall a. Maybe a
Prelude.Nothing,
        $sel:healthCheckGracePeriod:CreateAutoScalingGroup' :: Maybe Int
healthCheckGracePeriod = forall a. Maybe a
Prelude.Nothing,
        $sel:healthCheckType:CreateAutoScalingGroup' :: Maybe Text
healthCheckType = forall a. Maybe a
Prelude.Nothing,
        $sel:instanceId:CreateAutoScalingGroup' :: Maybe Text
instanceId = forall a. Maybe a
Prelude.Nothing,
        $sel:launchConfigurationName:CreateAutoScalingGroup' :: Maybe Text
launchConfigurationName = forall a. Maybe a
Prelude.Nothing,
        $sel:launchTemplate:CreateAutoScalingGroup' :: Maybe LaunchTemplateSpecification
launchTemplate = forall a. Maybe a
Prelude.Nothing,
        $sel:lifecycleHookSpecificationList:CreateAutoScalingGroup' :: Maybe [LifecycleHookSpecification]
lifecycleHookSpecificationList = forall a. Maybe a
Prelude.Nothing,
        $sel:loadBalancerNames:CreateAutoScalingGroup' :: Maybe [Text]
loadBalancerNames = forall a. Maybe a
Prelude.Nothing,
        $sel:maxInstanceLifetime:CreateAutoScalingGroup' :: Maybe Int
maxInstanceLifetime = forall a. Maybe a
Prelude.Nothing,
        $sel:mixedInstancesPolicy:CreateAutoScalingGroup' :: Maybe MixedInstancesPolicy
mixedInstancesPolicy = forall a. Maybe a
Prelude.Nothing,
        $sel:newInstancesProtectedFromScaleIn':CreateAutoScalingGroup' :: Maybe Bool
newInstancesProtectedFromScaleIn' = forall a. Maybe a
Prelude.Nothing,
        $sel:placementGroup:CreateAutoScalingGroup' :: Maybe Text
placementGroup = forall a. Maybe a
Prelude.Nothing,
        $sel:serviceLinkedRoleARN:CreateAutoScalingGroup' :: Maybe Text
serviceLinkedRoleARN = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:CreateAutoScalingGroup' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:targetGroupARNs:CreateAutoScalingGroup' :: Maybe [Text]
targetGroupARNs = forall a. Maybe a
Prelude.Nothing,
        $sel:terminationPolicies:CreateAutoScalingGroup' :: Maybe [Text]
terminationPolicies = forall a. Maybe a
Prelude.Nothing,
        $sel:trafficSources:CreateAutoScalingGroup' :: Maybe [TrafficSourceIdentifier]
trafficSources = forall a. Maybe a
Prelude.Nothing,
        $sel:vPCZoneIdentifier:CreateAutoScalingGroup' :: Maybe Text
vPCZoneIdentifier = forall a. Maybe a
Prelude.Nothing,
        $sel:autoScalingGroupName:CreateAutoScalingGroup' :: Text
autoScalingGroupName = Text
pAutoScalingGroupName_,
        $sel:minSize:CreateAutoScalingGroup' :: Int
minSize = Int
pMinSize_,
        $sel:maxSize:CreateAutoScalingGroup' :: Int
maxSize = Int
pMaxSize_
      }

-- | A list of Availability Zones where instances in the Auto Scaling group
-- can be created. Used for launching into the default VPC subnet in each
-- Availability Zone when not using the @VPCZoneIdentifier@ property, or
-- for attaching a network interface when an existing network interface ID
-- is specified in a launch template.
createAutoScalingGroup_availabilityZones :: Lens.Lens' CreateAutoScalingGroup (Prelude.Maybe [Prelude.Text])
createAutoScalingGroup_availabilityZones :: Lens' CreateAutoScalingGroup (Maybe [Text])
createAutoScalingGroup_availabilityZones = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAutoScalingGroup' {Maybe [Text]
availabilityZones :: Maybe [Text]
$sel:availabilityZones:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe [Text]
availabilityZones} -> Maybe [Text]
availabilityZones) (\s :: CreateAutoScalingGroup
s@CreateAutoScalingGroup' {} Maybe [Text]
a -> CreateAutoScalingGroup
s {$sel:availabilityZones:CreateAutoScalingGroup' :: Maybe [Text]
availabilityZones = Maybe [Text]
a} :: CreateAutoScalingGroup) 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

-- | Indicates whether Capacity Rebalancing is enabled. Otherwise, Capacity
-- Rebalancing is disabled. When you turn on Capacity Rebalancing, Amazon
-- EC2 Auto Scaling attempts to launch a Spot Instance whenever Amazon EC2
-- notifies that a Spot Instance is at an elevated risk of interruption.
-- After launching a new instance, it then terminates an old instance. 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 in the /Amazon EC2 Auto Scaling User Guide/.
createAutoScalingGroup_capacityRebalance :: Lens.Lens' CreateAutoScalingGroup (Prelude.Maybe Prelude.Bool)
createAutoScalingGroup_capacityRebalance :: Lens' CreateAutoScalingGroup (Maybe Bool)
createAutoScalingGroup_capacityRebalance = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAutoScalingGroup' {Maybe Bool
capacityRebalance :: Maybe Bool
$sel:capacityRebalance:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe Bool
capacityRebalance} -> Maybe Bool
capacityRebalance) (\s :: CreateAutoScalingGroup
s@CreateAutoScalingGroup' {} Maybe Bool
a -> CreateAutoScalingGroup
s {$sel:capacityRebalance:CreateAutoScalingGroup' :: Maybe Bool
capacityRebalance = Maybe Bool
a} :: CreateAutoScalingGroup)

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

-- | /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/.
--
-- Default: @300@ seconds
createAutoScalingGroup_defaultCooldown :: Lens.Lens' CreateAutoScalingGroup (Prelude.Maybe Prelude.Int)
createAutoScalingGroup_defaultCooldown :: Lens' CreateAutoScalingGroup (Maybe Int)
createAutoScalingGroup_defaultCooldown = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAutoScalingGroup' {Maybe Int
defaultCooldown :: Maybe Int
$sel:defaultCooldown:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe Int
defaultCooldown} -> Maybe Int
defaultCooldown) (\s :: CreateAutoScalingGroup
s@CreateAutoScalingGroup' {} Maybe Int
a -> CreateAutoScalingGroup
s {$sel:defaultCooldown:CreateAutoScalingGroup' :: Maybe Int
defaultCooldown = Maybe Int
a} :: CreateAutoScalingGroup)

-- | 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@.
--
-- Default: None
createAutoScalingGroup_defaultInstanceWarmup :: Lens.Lens' CreateAutoScalingGroup (Prelude.Maybe Prelude.Int)
createAutoScalingGroup_defaultInstanceWarmup :: Lens' CreateAutoScalingGroup (Maybe Int)
createAutoScalingGroup_defaultInstanceWarmup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAutoScalingGroup' {Maybe Int
defaultInstanceWarmup :: Maybe Int
$sel:defaultInstanceWarmup:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe Int
defaultInstanceWarmup} -> Maybe Int
defaultInstanceWarmup) (\s :: CreateAutoScalingGroup
s@CreateAutoScalingGroup' {} Maybe Int
a -> CreateAutoScalingGroup
s {$sel:defaultInstanceWarmup:CreateAutoScalingGroup' :: Maybe Int
defaultInstanceWarmup = Maybe Int
a} :: CreateAutoScalingGroup)

-- | The desired capacity is the initial capacity of the Auto Scaling group
-- at the time of its creation and the capacity it attempts to maintain. It
-- can scale beyond this capacity if you configure auto scaling. 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. If you do not
-- specify a desired capacity, the default is the minimum size of the
-- group.
createAutoScalingGroup_desiredCapacity :: Lens.Lens' CreateAutoScalingGroup (Prelude.Maybe Prelude.Int)
createAutoScalingGroup_desiredCapacity :: Lens' CreateAutoScalingGroup (Maybe Int)
createAutoScalingGroup_desiredCapacity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAutoScalingGroup' {Maybe Int
desiredCapacity :: Maybe Int
$sel:desiredCapacity:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe Int
desiredCapacity} -> Maybe Int
desiredCapacity) (\s :: CreateAutoScalingGroup
s@CreateAutoScalingGroup' {} Maybe Int
a -> CreateAutoScalingGroup
s {$sel:desiredCapacity:CreateAutoScalingGroup' :: Maybe Int
desiredCapacity = Maybe Int
a} :: CreateAutoScalingGroup)

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

-- | 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/.
--
-- Default: @0@ seconds
createAutoScalingGroup_healthCheckGracePeriod :: Lens.Lens' CreateAutoScalingGroup (Prelude.Maybe Prelude.Int)
createAutoScalingGroup_healthCheckGracePeriod :: Lens' CreateAutoScalingGroup (Maybe Int)
createAutoScalingGroup_healthCheckGracePeriod = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAutoScalingGroup' {Maybe Int
healthCheckGracePeriod :: Maybe Int
$sel:healthCheckGracePeriod:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe Int
healthCheckGracePeriod} -> Maybe Int
healthCheckGracePeriod) (\s :: CreateAutoScalingGroup
s@CreateAutoScalingGroup' {} Maybe Int
a -> CreateAutoScalingGroup
s {$sel:healthCheckGracePeriod:CreateAutoScalingGroup' :: Maybe Int
healthCheckGracePeriod = Maybe Int
a} :: CreateAutoScalingGroup)

-- | Determines whether any additional health checks are performed on the
-- instances in this group. Amazon EC2 health checks are always on. For
-- more information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/healthcheck.html Health checks for Auto Scaling instances>
-- in the /Amazon EC2 Auto Scaling User Guide/.
--
-- 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.
createAutoScalingGroup_healthCheckType :: Lens.Lens' CreateAutoScalingGroup (Prelude.Maybe Prelude.Text)
createAutoScalingGroup_healthCheckType :: Lens' CreateAutoScalingGroup (Maybe Text)
createAutoScalingGroup_healthCheckType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAutoScalingGroup' {Maybe Text
healthCheckType :: Maybe Text
$sel:healthCheckType:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe Text
healthCheckType} -> Maybe Text
healthCheckType) (\s :: CreateAutoScalingGroup
s@CreateAutoScalingGroup' {} Maybe Text
a -> CreateAutoScalingGroup
s {$sel:healthCheckType:CreateAutoScalingGroup' :: Maybe Text
healthCheckType = Maybe Text
a} :: CreateAutoScalingGroup)

-- | The ID of the instance used to base the launch configuration on. If
-- specified, Amazon EC2 Auto Scaling uses the configuration values from
-- the specified instance to create a new launch configuration. To get the
-- instance ID, use the Amazon EC2
-- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_DescribeInstances.html DescribeInstances>
-- API operation. For more information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/create-asg-from-instance.html Creating an Auto Scaling group using an EC2 instance>
-- in the /Amazon EC2 Auto Scaling User Guide/.
createAutoScalingGroup_instanceId :: Lens.Lens' CreateAutoScalingGroup (Prelude.Maybe Prelude.Text)
createAutoScalingGroup_instanceId :: Lens' CreateAutoScalingGroup (Maybe Text)
createAutoScalingGroup_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAutoScalingGroup' {Maybe Text
instanceId :: Maybe Text
$sel:instanceId:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe Text
instanceId} -> Maybe Text
instanceId) (\s :: CreateAutoScalingGroup
s@CreateAutoScalingGroup' {} Maybe Text
a -> CreateAutoScalingGroup
s {$sel:instanceId:CreateAutoScalingGroup' :: Maybe Text
instanceId = Maybe Text
a} :: CreateAutoScalingGroup)

-- | The name of the launch configuration to use to launch instances.
--
-- Conditional: You must specify either a launch template (@LaunchTemplate@
-- or @MixedInstancesPolicy@) or a launch configuration
-- (@LaunchConfigurationName@ or @InstanceId@).
createAutoScalingGroup_launchConfigurationName :: Lens.Lens' CreateAutoScalingGroup (Prelude.Maybe Prelude.Text)
createAutoScalingGroup_launchConfigurationName :: Lens' CreateAutoScalingGroup (Maybe Text)
createAutoScalingGroup_launchConfigurationName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAutoScalingGroup' {Maybe Text
launchConfigurationName :: Maybe Text
$sel:launchConfigurationName:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe Text
launchConfigurationName} -> Maybe Text
launchConfigurationName) (\s :: CreateAutoScalingGroup
s@CreateAutoScalingGroup' {} Maybe Text
a -> CreateAutoScalingGroup
s {$sel:launchConfigurationName:CreateAutoScalingGroup' :: Maybe Text
launchConfigurationName = Maybe Text
a} :: CreateAutoScalingGroup)

-- | Information used to specify the launch template and version to use to
-- launch instances.
--
-- Conditional: You must specify either a launch template (@LaunchTemplate@
-- or @MixedInstancesPolicy@) or a launch configuration
-- (@LaunchConfigurationName@ or @InstanceId@).
--
-- The launch template that is specified must be configured for use with an
-- Auto Scaling group. For more information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/create-launch-template.html Creating a launch template for an Auto Scaling group>
-- in the /Amazon EC2 Auto Scaling User Guide/.
createAutoScalingGroup_launchTemplate :: Lens.Lens' CreateAutoScalingGroup (Prelude.Maybe LaunchTemplateSpecification)
createAutoScalingGroup_launchTemplate :: Lens' CreateAutoScalingGroup (Maybe LaunchTemplateSpecification)
createAutoScalingGroup_launchTemplate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAutoScalingGroup' {Maybe LaunchTemplateSpecification
launchTemplate :: Maybe LaunchTemplateSpecification
$sel:launchTemplate:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe LaunchTemplateSpecification
launchTemplate} -> Maybe LaunchTemplateSpecification
launchTemplate) (\s :: CreateAutoScalingGroup
s@CreateAutoScalingGroup' {} Maybe LaunchTemplateSpecification
a -> CreateAutoScalingGroup
s {$sel:launchTemplate:CreateAutoScalingGroup' :: Maybe LaunchTemplateSpecification
launchTemplate = Maybe LaunchTemplateSpecification
a} :: CreateAutoScalingGroup)

-- | One or more lifecycle hooks to add to the Auto Scaling group before
-- instances are launched.
createAutoScalingGroup_lifecycleHookSpecificationList :: Lens.Lens' CreateAutoScalingGroup (Prelude.Maybe [LifecycleHookSpecification])
createAutoScalingGroup_lifecycleHookSpecificationList :: Lens' CreateAutoScalingGroup (Maybe [LifecycleHookSpecification])
createAutoScalingGroup_lifecycleHookSpecificationList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAutoScalingGroup' {Maybe [LifecycleHookSpecification]
lifecycleHookSpecificationList :: Maybe [LifecycleHookSpecification]
$sel:lifecycleHookSpecificationList:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe [LifecycleHookSpecification]
lifecycleHookSpecificationList} -> Maybe [LifecycleHookSpecification]
lifecycleHookSpecificationList) (\s :: CreateAutoScalingGroup
s@CreateAutoScalingGroup' {} Maybe [LifecycleHookSpecification]
a -> CreateAutoScalingGroup
s {$sel:lifecycleHookSpecificationList:CreateAutoScalingGroup' :: Maybe [LifecycleHookSpecification]
lifecycleHookSpecificationList = Maybe [LifecycleHookSpecification]
a} :: CreateAutoScalingGroup) 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 list of Classic Load Balancers associated with this Auto Scaling
-- group. For Application Load Balancers, Network Load Balancers, and
-- Gateway Load Balancer, specify the @TargetGroupARNs@ property instead.
createAutoScalingGroup_loadBalancerNames :: Lens.Lens' CreateAutoScalingGroup (Prelude.Maybe [Prelude.Text])
createAutoScalingGroup_loadBalancerNames :: Lens' CreateAutoScalingGroup (Maybe [Text])
createAutoScalingGroup_loadBalancerNames = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAutoScalingGroup' {Maybe [Text]
loadBalancerNames :: Maybe [Text]
$sel:loadBalancerNames:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe [Text]
loadBalancerNames} -> Maybe [Text]
loadBalancerNames) (\s :: CreateAutoScalingGroup
s@CreateAutoScalingGroup' {} Maybe [Text]
a -> CreateAutoScalingGroup
s {$sel:loadBalancerNames:CreateAutoScalingGroup' :: Maybe [Text]
loadBalancerNames = Maybe [Text]
a} :: CreateAutoScalingGroup) 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. 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). 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/.
createAutoScalingGroup_maxInstanceLifetime :: Lens.Lens' CreateAutoScalingGroup (Prelude.Maybe Prelude.Int)
createAutoScalingGroup_maxInstanceLifetime :: Lens' CreateAutoScalingGroup (Maybe Int)
createAutoScalingGroup_maxInstanceLifetime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAutoScalingGroup' {Maybe Int
maxInstanceLifetime :: Maybe Int
$sel:maxInstanceLifetime:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe Int
maxInstanceLifetime} -> Maybe Int
maxInstanceLifetime) (\s :: CreateAutoScalingGroup
s@CreateAutoScalingGroup' {} Maybe Int
a -> CreateAutoScalingGroup
s {$sel:maxInstanceLifetime:CreateAutoScalingGroup' :: Maybe Int
maxInstanceLifetime = Maybe Int
a} :: CreateAutoScalingGroup)

-- | 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/.
createAutoScalingGroup_mixedInstancesPolicy :: Lens.Lens' CreateAutoScalingGroup (Prelude.Maybe MixedInstancesPolicy)
createAutoScalingGroup_mixedInstancesPolicy :: Lens' CreateAutoScalingGroup (Maybe MixedInstancesPolicy)
createAutoScalingGroup_mixedInstancesPolicy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAutoScalingGroup' {Maybe MixedInstancesPolicy
mixedInstancesPolicy :: Maybe MixedInstancesPolicy
$sel:mixedInstancesPolicy:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe MixedInstancesPolicy
mixedInstancesPolicy} -> Maybe MixedInstancesPolicy
mixedInstancesPolicy) (\s :: CreateAutoScalingGroup
s@CreateAutoScalingGroup' {} Maybe MixedInstancesPolicy
a -> CreateAutoScalingGroup
s {$sel:mixedInstancesPolicy:CreateAutoScalingGroup' :: Maybe MixedInstancesPolicy
mixedInstancesPolicy = Maybe MixedInstancesPolicy
a} :: CreateAutoScalingGroup)

-- | 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/.
createAutoScalingGroup_newInstancesProtectedFromScaleIn :: Lens.Lens' CreateAutoScalingGroup (Prelude.Maybe Prelude.Bool)
createAutoScalingGroup_newInstancesProtectedFromScaleIn :: Lens' CreateAutoScalingGroup (Maybe Bool)
createAutoScalingGroup_newInstancesProtectedFromScaleIn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAutoScalingGroup' {Maybe Bool
newInstancesProtectedFromScaleIn' :: Maybe Bool
$sel:newInstancesProtectedFromScaleIn':CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe Bool
newInstancesProtectedFromScaleIn'} -> Maybe Bool
newInstancesProtectedFromScaleIn') (\s :: CreateAutoScalingGroup
s@CreateAutoScalingGroup' {} Maybe Bool
a -> CreateAutoScalingGroup
s {$sel:newInstancesProtectedFromScaleIn':CreateAutoScalingGroup' :: Maybe Bool
newInstancesProtectedFromScaleIn' = Maybe Bool
a} :: CreateAutoScalingGroup)

-- | The name of the 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.
createAutoScalingGroup_placementGroup :: Lens.Lens' CreateAutoScalingGroup (Prelude.Maybe Prelude.Text)
createAutoScalingGroup_placementGroup :: Lens' CreateAutoScalingGroup (Maybe Text)
createAutoScalingGroup_placementGroup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAutoScalingGroup' {Maybe Text
placementGroup :: Maybe Text
$sel:placementGroup:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe Text
placementGroup} -> Maybe Text
placementGroup) (\s :: CreateAutoScalingGroup
s@CreateAutoScalingGroup' {} Maybe Text
a -> CreateAutoScalingGroup
s {$sel:placementGroup:CreateAutoScalingGroup' :: Maybe Text
placementGroup = Maybe Text
a} :: CreateAutoScalingGroup)

-- | The Amazon Resource Name (ARN) of the service-linked role that the Auto
-- Scaling group uses to call other Amazon Web Services service on your
-- behalf. By default, Amazon EC2 Auto Scaling uses a service-linked role
-- named @AWSServiceRoleForAutoScaling@, which it creates if it does not
-- exist. 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/.
createAutoScalingGroup_serviceLinkedRoleARN :: Lens.Lens' CreateAutoScalingGroup (Prelude.Maybe Prelude.Text)
createAutoScalingGroup_serviceLinkedRoleARN :: Lens' CreateAutoScalingGroup (Maybe Text)
createAutoScalingGroup_serviceLinkedRoleARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAutoScalingGroup' {Maybe Text
serviceLinkedRoleARN :: Maybe Text
$sel:serviceLinkedRoleARN:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe Text
serviceLinkedRoleARN} -> Maybe Text
serviceLinkedRoleARN) (\s :: CreateAutoScalingGroup
s@CreateAutoScalingGroup' {} Maybe Text
a -> CreateAutoScalingGroup
s {$sel:serviceLinkedRoleARN:CreateAutoScalingGroup' :: Maybe Text
serviceLinkedRoleARN = Maybe Text
a} :: CreateAutoScalingGroup)

-- | One or more tags. You can tag your Auto Scaling group and propagate the
-- tags to the Amazon EC2 instances it launches. Tags are not propagated to
-- Amazon EBS volumes. To add tags to Amazon EBS volumes, specify the tags
-- in a launch template but use caution. If the launch template specifies
-- an instance tag with a key that is also specified for the Auto Scaling
-- group, Amazon EC2 Auto Scaling overrides the value of that instance tag
-- with the value specified by the Auto Scaling group. For more
-- information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/ec2-auto-scaling-tagging.html Tag Auto Scaling groups and instances>
-- in the /Amazon EC2 Auto Scaling User Guide/.
createAutoScalingGroup_tags :: Lens.Lens' CreateAutoScalingGroup (Prelude.Maybe [Tag])
createAutoScalingGroup_tags :: Lens' CreateAutoScalingGroup (Maybe [Tag])
createAutoScalingGroup_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAutoScalingGroup' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreateAutoScalingGroup
s@CreateAutoScalingGroup' {} Maybe [Tag]
a -> CreateAutoScalingGroup
s {$sel:tags:CreateAutoScalingGroup' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: CreateAutoScalingGroup) 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 Elastic Load Balancing target
-- groups to associate with the Auto Scaling group. Instances are
-- registered as targets with the target groups. The target groups receive
-- incoming traffic and route requests to one or more registered targets.
-- For more information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/autoscaling-load-balancer.html Use Elastic Load Balancing to distribute traffic across the instances in your Auto Scaling group>
-- in the /Amazon EC2 Auto Scaling User Guide/.
createAutoScalingGroup_targetGroupARNs :: Lens.Lens' CreateAutoScalingGroup (Prelude.Maybe [Prelude.Text])
createAutoScalingGroup_targetGroupARNs :: Lens' CreateAutoScalingGroup (Maybe [Text])
createAutoScalingGroup_targetGroupARNs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAutoScalingGroup' {Maybe [Text]
targetGroupARNs :: Maybe [Text]
$sel:targetGroupARNs:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe [Text]
targetGroupARNs} -> Maybe [Text]
targetGroupARNs) (\s :: CreateAutoScalingGroup
s@CreateAutoScalingGroup' {} Maybe [Text]
a -> CreateAutoScalingGroup
s {$sel:targetGroupARNs:CreateAutoScalingGroup' :: Maybe [Text]
targetGroupARNs = Maybe [Text]
a} :: CreateAutoScalingGroup) 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 policy or a list of policies that are used to select the instance to
-- terminate. These 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@
createAutoScalingGroup_terminationPolicies :: Lens.Lens' CreateAutoScalingGroup (Prelude.Maybe [Prelude.Text])
createAutoScalingGroup_terminationPolicies :: Lens' CreateAutoScalingGroup (Maybe [Text])
createAutoScalingGroup_terminationPolicies = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAutoScalingGroup' {Maybe [Text]
terminationPolicies :: Maybe [Text]
$sel:terminationPolicies:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe [Text]
terminationPolicies} -> Maybe [Text]
terminationPolicies) (\s :: CreateAutoScalingGroup
s@CreateAutoScalingGroup' {} Maybe [Text]
a -> CreateAutoScalingGroup
s {$sel:terminationPolicies:CreateAutoScalingGroup' :: Maybe [Text]
terminationPolicies = Maybe [Text]
a} :: CreateAutoScalingGroup) 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

-- | __Reserved for use with Amazon VPC Lattice, which is in preview release
-- and is subject to change. Do not use this parameter for production
-- workloads. It is also subject to change.__
--
-- The unique identifiers of one or more traffic sources.
--
-- Currently, you must specify an Amazon Resource Name (ARN) for an
-- existing VPC Lattice target group. Amazon EC2 Auto Scaling registers the
-- running instances with the attached target groups. The target groups
-- receive incoming traffic and route requests to one or more registered
-- targets.
createAutoScalingGroup_trafficSources :: Lens.Lens' CreateAutoScalingGroup (Prelude.Maybe [TrafficSourceIdentifier])
createAutoScalingGroup_trafficSources :: Lens' CreateAutoScalingGroup (Maybe [TrafficSourceIdentifier])
createAutoScalingGroup_trafficSources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAutoScalingGroup' {Maybe [TrafficSourceIdentifier]
trafficSources :: Maybe [TrafficSourceIdentifier]
$sel:trafficSources:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe [TrafficSourceIdentifier]
trafficSources} -> Maybe [TrafficSourceIdentifier]
trafficSources) (\s :: CreateAutoScalingGroup
s@CreateAutoScalingGroup' {} Maybe [TrafficSourceIdentifier]
a -> CreateAutoScalingGroup
s {$sel:trafficSources:CreateAutoScalingGroup' :: Maybe [TrafficSourceIdentifier]
trafficSources = Maybe [TrafficSourceIdentifier]
a} :: CreateAutoScalingGroup) 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)
-- where instances in the Auto Scaling group can be created. If you specify
-- @VPCZoneIdentifier@ with @AvailabilityZones@, the subnets that you
-- specify must reside in those Availability Zones.
createAutoScalingGroup_vPCZoneIdentifier :: Lens.Lens' CreateAutoScalingGroup (Prelude.Maybe Prelude.Text)
createAutoScalingGroup_vPCZoneIdentifier :: Lens' CreateAutoScalingGroup (Maybe Text)
createAutoScalingGroup_vPCZoneIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAutoScalingGroup' {Maybe Text
vPCZoneIdentifier :: Maybe Text
$sel:vPCZoneIdentifier:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe Text
vPCZoneIdentifier} -> Maybe Text
vPCZoneIdentifier) (\s :: CreateAutoScalingGroup
s@CreateAutoScalingGroup' {} Maybe Text
a -> CreateAutoScalingGroup
s {$sel:vPCZoneIdentifier:CreateAutoScalingGroup' :: Maybe Text
vPCZoneIdentifier = Maybe Text
a} :: CreateAutoScalingGroup)

-- | The name of the Auto Scaling group. This name must be unique per Region
-- per account.
--
-- The name can contain any ASCII character 33 to 126 including most
-- punctuation characters, digits, and upper and lowercased letters.
--
-- You cannot use a colon (:) in the name.
createAutoScalingGroup_autoScalingGroupName :: Lens.Lens' CreateAutoScalingGroup Prelude.Text
createAutoScalingGroup_autoScalingGroupName :: Lens' CreateAutoScalingGroup Text
createAutoScalingGroup_autoScalingGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAutoScalingGroup' {Text
autoScalingGroupName :: Text
$sel:autoScalingGroupName:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Text
autoScalingGroupName} -> Text
autoScalingGroupName) (\s :: CreateAutoScalingGroup
s@CreateAutoScalingGroup' {} Text
a -> CreateAutoScalingGroup
s {$sel:autoScalingGroupName:CreateAutoScalingGroup' :: Text
autoScalingGroupName = Text
a} :: CreateAutoScalingGroup)

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

-- | The maximum size of the 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).
createAutoScalingGroup_maxSize :: Lens.Lens' CreateAutoScalingGroup Prelude.Int
createAutoScalingGroup_maxSize :: Lens' CreateAutoScalingGroup Int
createAutoScalingGroup_maxSize = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAutoScalingGroup' {Int
maxSize :: Int
$sel:maxSize:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Int
maxSize} -> Int
maxSize) (\s :: CreateAutoScalingGroup
s@CreateAutoScalingGroup' {} Int
a -> CreateAutoScalingGroup
s {$sel:maxSize:CreateAutoScalingGroup' :: Int
maxSize = Int
a} :: CreateAutoScalingGroup)

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

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

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

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

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

instance Data.ToQuery CreateAutoScalingGroup where
  toQuery :: CreateAutoScalingGroup -> QueryString
toQuery CreateAutoScalingGroup' {Int
Maybe Bool
Maybe Int
Maybe [Text]
Maybe [LifecycleHookSpecification]
Maybe [Tag]
Maybe [TrafficSourceIdentifier]
Maybe Text
Maybe LaunchTemplateSpecification
Maybe MixedInstancesPolicy
Text
maxSize :: Int
minSize :: Int
autoScalingGroupName :: Text
vPCZoneIdentifier :: Maybe Text
trafficSources :: Maybe [TrafficSourceIdentifier]
terminationPolicies :: Maybe [Text]
targetGroupARNs :: Maybe [Text]
tags :: Maybe [Tag]
serviceLinkedRoleARN :: Maybe Text
placementGroup :: Maybe Text
newInstancesProtectedFromScaleIn' :: Maybe Bool
mixedInstancesPolicy :: Maybe MixedInstancesPolicy
maxInstanceLifetime :: Maybe Int
loadBalancerNames :: Maybe [Text]
lifecycleHookSpecificationList :: Maybe [LifecycleHookSpecification]
launchTemplate :: Maybe LaunchTemplateSpecification
launchConfigurationName :: Maybe Text
instanceId :: 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:maxSize:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Int
$sel:minSize:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Int
$sel:autoScalingGroupName:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Text
$sel:vPCZoneIdentifier:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe Text
$sel:trafficSources:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe [TrafficSourceIdentifier]
$sel:terminationPolicies:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe [Text]
$sel:targetGroupARNs:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe [Text]
$sel:tags:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe [Tag]
$sel:serviceLinkedRoleARN:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe Text
$sel:placementGroup:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe Text
$sel:newInstancesProtectedFromScaleIn':CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe Bool
$sel:mixedInstancesPolicy:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe MixedInstancesPolicy
$sel:maxInstanceLifetime:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe Int
$sel:loadBalancerNames:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe [Text]
$sel:lifecycleHookSpecificationList:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe [LifecycleHookSpecification]
$sel:launchTemplate:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe LaunchTemplateSpecification
$sel:launchConfigurationName:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe Text
$sel:instanceId:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe Text
$sel:healthCheckType:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe Text
$sel:healthCheckGracePeriod:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe Int
$sel:desiredCapacityType:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe Text
$sel:desiredCapacity:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe Int
$sel:defaultInstanceWarmup:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe Int
$sel:defaultCooldown:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe Int
$sel:context:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe Text
$sel:capacityRebalance:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe Bool
$sel:availabilityZones:CreateAutoScalingGroup' :: CreateAutoScalingGroup -> Maybe [Text]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"CreateAutoScalingGroup" :: 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
"InstanceId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
instanceId,
        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
"LifecycleHookSpecificationList"
          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 [LifecycleHookSpecification]
lifecycleHookSpecificationList
            ),
        ByteString
"LoadBalancerNames"
          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]
loadBalancerNames
            ),
        ByteString
"MaxInstanceLifetime" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
maxInstanceLifetime,
        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
"Tags"
          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 [Tag]
tags),
        ByteString
"TargetGroupARNs"
          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]
targetGroupARNs
            ),
        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
"TrafficSources"
          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 [TrafficSourceIdentifier]
trafficSources
            ),
        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,
        ByteString
"MinSize" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Int
minSize,
        ByteString
"MaxSize" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Int
maxSize
      ]

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

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

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