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

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

-- |
-- Module      : Amazonka.AutoScaling.Types.LaunchTemplateOverrides
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.AutoScaling.Types.LaunchTemplateOverrides where

import Amazonka.AutoScaling.Types.InstanceRequirements
import Amazonka.AutoScaling.Types.LaunchTemplateSpecification
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

-- | Use this structure to let Amazon EC2 Auto Scaling do the following when
-- the Auto Scaling group has a mixed instances policy:
--
-- -   Override the instance type that is specified in the launch template.
--
-- -   Use multiple instance types.
--
-- Specify the instance types that you want, or define your instance
-- requirements instead and let Amazon EC2 Auto Scaling provision the
-- available instance types that meet your requirements. This can provide
-- Amazon EC2 Auto Scaling with a larger selection of instance types to
-- choose from when fulfilling Spot and On-Demand capacities. You can view
-- which instance types are matched before you apply the instance
-- requirements to your Auto Scaling group.
--
-- After you define your instance requirements, you don\'t have to keep
-- updating these settings to get new EC2 instance types automatically.
-- Amazon EC2 Auto Scaling uses the instance requirements of the Auto
-- Scaling group to determine whether a new EC2 instance type can be used.
--
-- /See:/ 'newLaunchTemplateOverrides' smart constructor.
data LaunchTemplateOverrides = LaunchTemplateOverrides'
  { -- | The instance requirements. Amazon EC2 Auto Scaling uses your specified
    -- requirements to identify instance types. Then, it uses your On-Demand
    -- and Spot allocation strategies to launch instances from these instance
    -- types.
    --
    -- You can specify up to four separate sets of instance requirements per
    -- Auto Scaling group. This is useful for provisioning instances from
    -- different Amazon Machine Images (AMIs) in the same Auto Scaling group.
    -- To do this, create the AMIs and create a new launch template for each
    -- AMI. Then, create a compatible set of instance requirements for each
    -- launch template.
    --
    -- If you specify @InstanceRequirements@, you can\'t specify
    -- @InstanceType@.
    LaunchTemplateOverrides -> Maybe InstanceRequirements
instanceRequirements :: Prelude.Maybe InstanceRequirements,
    -- | The instance type, such as @m3.xlarge@. You must specify an instance
    -- type that is supported in your requested Region and Availability Zones.
    -- For more information, see
    -- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/instance-types.html Instance types>
    -- in the /Amazon Elastic Compute Cloud User Guide/.
    --
    -- You can specify up to 40 instance types per Auto Scaling group.
    LaunchTemplateOverrides -> Maybe Text
instanceType :: Prelude.Maybe Prelude.Text,
    -- | Provides a launch template for the specified instance type or set of
    -- instance requirements. For example, some instance types might require a
    -- launch template with a different AMI. If not provided, Amazon EC2 Auto
    -- Scaling uses the launch template that\'s specified in the
    -- @LaunchTemplate@ definition. For more information, see
    -- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/ec2-auto-scaling-mixed-instances-groups-launch-template-overrides.html Specifying a different launch template for an instance type>
    -- in the /Amazon EC2 Auto Scaling User Guide/.
    --
    -- You can specify up to 20 launch templates per Auto Scaling group. The
    -- launch templates specified in the overrides and in the @LaunchTemplate@
    -- definition count towards this limit.
    LaunchTemplateOverrides -> Maybe LaunchTemplateSpecification
launchTemplateSpecification :: Prelude.Maybe LaunchTemplateSpecification,
    -- | If you provide a list of instance types to use, you can specify the
    -- number of capacity units provided by each instance type in terms of
    -- virtual CPUs, memory, storage, throughput, or other relative performance
    -- characteristic. When a Spot or On-Demand Instance is launched, the
    -- capacity units count toward the desired capacity. Amazon EC2 Auto
    -- Scaling launches instances until the desired capacity is totally
    -- fulfilled, even if this results in an overage. For example, if there are
    -- two units remaining to fulfill capacity, and Amazon EC2 Auto Scaling can
    -- only launch an instance with a @WeightedCapacity@ of five units, the
    -- instance is launched, and the desired capacity is exceeded by three
    -- units. For more information, see
    -- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/ec2-auto-scaling-mixed-instances-groups-instance-weighting.html Configuring instance weighting for Amazon EC2 Auto Scaling>
    -- in the /Amazon EC2 Auto Scaling User Guide/. Value must be in the range
    -- of 1–999.
    --
    -- If you specify a value for @WeightedCapacity@ for one instance type, you
    -- must specify a value for @WeightedCapacity@ for all of them.
    --
    -- Every Auto Scaling group has three size parameters (@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.
    LaunchTemplateOverrides -> Maybe Text
weightedCapacity :: Prelude.Maybe Prelude.Text
  }
  deriving (LaunchTemplateOverrides -> LaunchTemplateOverrides -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LaunchTemplateOverrides -> LaunchTemplateOverrides -> Bool
$c/= :: LaunchTemplateOverrides -> LaunchTemplateOverrides -> Bool
== :: LaunchTemplateOverrides -> LaunchTemplateOverrides -> Bool
$c== :: LaunchTemplateOverrides -> LaunchTemplateOverrides -> Bool
Prelude.Eq, ReadPrec [LaunchTemplateOverrides]
ReadPrec LaunchTemplateOverrides
Int -> ReadS LaunchTemplateOverrides
ReadS [LaunchTemplateOverrides]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [LaunchTemplateOverrides]
$creadListPrec :: ReadPrec [LaunchTemplateOverrides]
readPrec :: ReadPrec LaunchTemplateOverrides
$creadPrec :: ReadPrec LaunchTemplateOverrides
readList :: ReadS [LaunchTemplateOverrides]
$creadList :: ReadS [LaunchTemplateOverrides]
readsPrec :: Int -> ReadS LaunchTemplateOverrides
$creadsPrec :: Int -> ReadS LaunchTemplateOverrides
Prelude.Read, Int -> LaunchTemplateOverrides -> ShowS
[LaunchTemplateOverrides] -> ShowS
LaunchTemplateOverrides -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LaunchTemplateOverrides] -> ShowS
$cshowList :: [LaunchTemplateOverrides] -> ShowS
show :: LaunchTemplateOverrides -> String
$cshow :: LaunchTemplateOverrides -> String
showsPrec :: Int -> LaunchTemplateOverrides -> ShowS
$cshowsPrec :: Int -> LaunchTemplateOverrides -> ShowS
Prelude.Show, forall x. Rep LaunchTemplateOverrides x -> LaunchTemplateOverrides
forall x. LaunchTemplateOverrides -> Rep LaunchTemplateOverrides x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LaunchTemplateOverrides x -> LaunchTemplateOverrides
$cfrom :: forall x. LaunchTemplateOverrides -> Rep LaunchTemplateOverrides x
Prelude.Generic)

-- |
-- Create a value of 'LaunchTemplateOverrides' 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:
--
-- 'instanceRequirements', 'launchTemplateOverrides_instanceRequirements' - The instance requirements. Amazon EC2 Auto Scaling uses your specified
-- requirements to identify instance types. Then, it uses your On-Demand
-- and Spot allocation strategies to launch instances from these instance
-- types.
--
-- You can specify up to four separate sets of instance requirements per
-- Auto Scaling group. This is useful for provisioning instances from
-- different Amazon Machine Images (AMIs) in the same Auto Scaling group.
-- To do this, create the AMIs and create a new launch template for each
-- AMI. Then, create a compatible set of instance requirements for each
-- launch template.
--
-- If you specify @InstanceRequirements@, you can\'t specify
-- @InstanceType@.
--
-- 'instanceType', 'launchTemplateOverrides_instanceType' - The instance type, such as @m3.xlarge@. You must specify an instance
-- type that is supported in your requested Region and Availability Zones.
-- For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/instance-types.html Instance types>
-- in the /Amazon Elastic Compute Cloud User Guide/.
--
-- You can specify up to 40 instance types per Auto Scaling group.
--
-- 'launchTemplateSpecification', 'launchTemplateOverrides_launchTemplateSpecification' - Provides a launch template for the specified instance type or set of
-- instance requirements. For example, some instance types might require a
-- launch template with a different AMI. If not provided, Amazon EC2 Auto
-- Scaling uses the launch template that\'s specified in the
-- @LaunchTemplate@ definition. For more information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/ec2-auto-scaling-mixed-instances-groups-launch-template-overrides.html Specifying a different launch template for an instance type>
-- in the /Amazon EC2 Auto Scaling User Guide/.
--
-- You can specify up to 20 launch templates per Auto Scaling group. The
-- launch templates specified in the overrides and in the @LaunchTemplate@
-- definition count towards this limit.
--
-- 'weightedCapacity', 'launchTemplateOverrides_weightedCapacity' - If you provide a list of instance types to use, you can specify the
-- number of capacity units provided by each instance type in terms of
-- virtual CPUs, memory, storage, throughput, or other relative performance
-- characteristic. When a Spot or On-Demand Instance is launched, the
-- capacity units count toward the desired capacity. Amazon EC2 Auto
-- Scaling launches instances until the desired capacity is totally
-- fulfilled, even if this results in an overage. For example, if there are
-- two units remaining to fulfill capacity, and Amazon EC2 Auto Scaling can
-- only launch an instance with a @WeightedCapacity@ of five units, the
-- instance is launched, and the desired capacity is exceeded by three
-- units. For more information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/ec2-auto-scaling-mixed-instances-groups-instance-weighting.html Configuring instance weighting for Amazon EC2 Auto Scaling>
-- in the /Amazon EC2 Auto Scaling User Guide/. Value must be in the range
-- of 1–999.
--
-- If you specify a value for @WeightedCapacity@ for one instance type, you
-- must specify a value for @WeightedCapacity@ for all of them.
--
-- Every Auto Scaling group has three size parameters (@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.
newLaunchTemplateOverrides ::
  LaunchTemplateOverrides
newLaunchTemplateOverrides :: LaunchTemplateOverrides
newLaunchTemplateOverrides =
  LaunchTemplateOverrides'
    { $sel:instanceRequirements:LaunchTemplateOverrides' :: Maybe InstanceRequirements
instanceRequirements =
        forall a. Maybe a
Prelude.Nothing,
      $sel:instanceType:LaunchTemplateOverrides' :: Maybe Text
instanceType = forall a. Maybe a
Prelude.Nothing,
      $sel:launchTemplateSpecification:LaunchTemplateOverrides' :: Maybe LaunchTemplateSpecification
launchTemplateSpecification = forall a. Maybe a
Prelude.Nothing,
      $sel:weightedCapacity:LaunchTemplateOverrides' :: Maybe Text
weightedCapacity = forall a. Maybe a
Prelude.Nothing
    }

-- | The instance requirements. Amazon EC2 Auto Scaling uses your specified
-- requirements to identify instance types. Then, it uses your On-Demand
-- and Spot allocation strategies to launch instances from these instance
-- types.
--
-- You can specify up to four separate sets of instance requirements per
-- Auto Scaling group. This is useful for provisioning instances from
-- different Amazon Machine Images (AMIs) in the same Auto Scaling group.
-- To do this, create the AMIs and create a new launch template for each
-- AMI. Then, create a compatible set of instance requirements for each
-- launch template.
--
-- If you specify @InstanceRequirements@, you can\'t specify
-- @InstanceType@.
launchTemplateOverrides_instanceRequirements :: Lens.Lens' LaunchTemplateOverrides (Prelude.Maybe InstanceRequirements)
launchTemplateOverrides_instanceRequirements :: Lens' LaunchTemplateOverrides (Maybe InstanceRequirements)
launchTemplateOverrides_instanceRequirements = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LaunchTemplateOverrides' {Maybe InstanceRequirements
instanceRequirements :: Maybe InstanceRequirements
$sel:instanceRequirements:LaunchTemplateOverrides' :: LaunchTemplateOverrides -> Maybe InstanceRequirements
instanceRequirements} -> Maybe InstanceRequirements
instanceRequirements) (\s :: LaunchTemplateOverrides
s@LaunchTemplateOverrides' {} Maybe InstanceRequirements
a -> LaunchTemplateOverrides
s {$sel:instanceRequirements:LaunchTemplateOverrides' :: Maybe InstanceRequirements
instanceRequirements = Maybe InstanceRequirements
a} :: LaunchTemplateOverrides)

-- | The instance type, such as @m3.xlarge@. You must specify an instance
-- type that is supported in your requested Region and Availability Zones.
-- For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/instance-types.html Instance types>
-- in the /Amazon Elastic Compute Cloud User Guide/.
--
-- You can specify up to 40 instance types per Auto Scaling group.
launchTemplateOverrides_instanceType :: Lens.Lens' LaunchTemplateOverrides (Prelude.Maybe Prelude.Text)
launchTemplateOverrides_instanceType :: Lens' LaunchTemplateOverrides (Maybe Text)
launchTemplateOverrides_instanceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LaunchTemplateOverrides' {Maybe Text
instanceType :: Maybe Text
$sel:instanceType:LaunchTemplateOverrides' :: LaunchTemplateOverrides -> Maybe Text
instanceType} -> Maybe Text
instanceType) (\s :: LaunchTemplateOverrides
s@LaunchTemplateOverrides' {} Maybe Text
a -> LaunchTemplateOverrides
s {$sel:instanceType:LaunchTemplateOverrides' :: Maybe Text
instanceType = Maybe Text
a} :: LaunchTemplateOverrides)

-- | Provides a launch template for the specified instance type or set of
-- instance requirements. For example, some instance types might require a
-- launch template with a different AMI. If not provided, Amazon EC2 Auto
-- Scaling uses the launch template that\'s specified in the
-- @LaunchTemplate@ definition. For more information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/ec2-auto-scaling-mixed-instances-groups-launch-template-overrides.html Specifying a different launch template for an instance type>
-- in the /Amazon EC2 Auto Scaling User Guide/.
--
-- You can specify up to 20 launch templates per Auto Scaling group. The
-- launch templates specified in the overrides and in the @LaunchTemplate@
-- definition count towards this limit.
launchTemplateOverrides_launchTemplateSpecification :: Lens.Lens' LaunchTemplateOverrides (Prelude.Maybe LaunchTemplateSpecification)
launchTemplateOverrides_launchTemplateSpecification :: Lens' LaunchTemplateOverrides (Maybe LaunchTemplateSpecification)
launchTemplateOverrides_launchTemplateSpecification = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LaunchTemplateOverrides' {Maybe LaunchTemplateSpecification
launchTemplateSpecification :: Maybe LaunchTemplateSpecification
$sel:launchTemplateSpecification:LaunchTemplateOverrides' :: LaunchTemplateOverrides -> Maybe LaunchTemplateSpecification
launchTemplateSpecification} -> Maybe LaunchTemplateSpecification
launchTemplateSpecification) (\s :: LaunchTemplateOverrides
s@LaunchTemplateOverrides' {} Maybe LaunchTemplateSpecification
a -> LaunchTemplateOverrides
s {$sel:launchTemplateSpecification:LaunchTemplateOverrides' :: Maybe LaunchTemplateSpecification
launchTemplateSpecification = Maybe LaunchTemplateSpecification
a} :: LaunchTemplateOverrides)

-- | If you provide a list of instance types to use, you can specify the
-- number of capacity units provided by each instance type in terms of
-- virtual CPUs, memory, storage, throughput, or other relative performance
-- characteristic. When a Spot or On-Demand Instance is launched, the
-- capacity units count toward the desired capacity. Amazon EC2 Auto
-- Scaling launches instances until the desired capacity is totally
-- fulfilled, even if this results in an overage. For example, if there are
-- two units remaining to fulfill capacity, and Amazon EC2 Auto Scaling can
-- only launch an instance with a @WeightedCapacity@ of five units, the
-- instance is launched, and the desired capacity is exceeded by three
-- units. For more information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/ec2-auto-scaling-mixed-instances-groups-instance-weighting.html Configuring instance weighting for Amazon EC2 Auto Scaling>
-- in the /Amazon EC2 Auto Scaling User Guide/. Value must be in the range
-- of 1–999.
--
-- If you specify a value for @WeightedCapacity@ for one instance type, you
-- must specify a value for @WeightedCapacity@ for all of them.
--
-- Every Auto Scaling group has three size parameters (@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.
launchTemplateOverrides_weightedCapacity :: Lens.Lens' LaunchTemplateOverrides (Prelude.Maybe Prelude.Text)
launchTemplateOverrides_weightedCapacity :: Lens' LaunchTemplateOverrides (Maybe Text)
launchTemplateOverrides_weightedCapacity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LaunchTemplateOverrides' {Maybe Text
weightedCapacity :: Maybe Text
$sel:weightedCapacity:LaunchTemplateOverrides' :: LaunchTemplateOverrides -> Maybe Text
weightedCapacity} -> Maybe Text
weightedCapacity) (\s :: LaunchTemplateOverrides
s@LaunchTemplateOverrides' {} Maybe Text
a -> LaunchTemplateOverrides
s {$sel:weightedCapacity:LaunchTemplateOverrides' :: Maybe Text
weightedCapacity = Maybe Text
a} :: LaunchTemplateOverrides)

instance Data.FromXML LaunchTemplateOverrides where
  parseXML :: [Node] -> Either String LaunchTemplateOverrides
parseXML [Node]
x =
    Maybe InstanceRequirements
-> Maybe Text
-> Maybe LaunchTemplateSpecification
-> Maybe Text
-> LaunchTemplateOverrides
LaunchTemplateOverrides'
      forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"InstanceRequirements")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"InstanceType")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"LaunchTemplateSpecification")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"WeightedCapacity")

instance Prelude.Hashable LaunchTemplateOverrides where
  hashWithSalt :: Int -> LaunchTemplateOverrides -> Int
hashWithSalt Int
_salt LaunchTemplateOverrides' {Maybe Text
Maybe LaunchTemplateSpecification
Maybe InstanceRequirements
weightedCapacity :: Maybe Text
launchTemplateSpecification :: Maybe LaunchTemplateSpecification
instanceType :: Maybe Text
instanceRequirements :: Maybe InstanceRequirements
$sel:weightedCapacity:LaunchTemplateOverrides' :: LaunchTemplateOverrides -> Maybe Text
$sel:launchTemplateSpecification:LaunchTemplateOverrides' :: LaunchTemplateOverrides -> Maybe LaunchTemplateSpecification
$sel:instanceType:LaunchTemplateOverrides' :: LaunchTemplateOverrides -> Maybe Text
$sel:instanceRequirements:LaunchTemplateOverrides' :: LaunchTemplateOverrides -> Maybe InstanceRequirements
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe InstanceRequirements
instanceRequirements
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
instanceType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LaunchTemplateSpecification
launchTemplateSpecification
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
weightedCapacity

instance Prelude.NFData LaunchTemplateOverrides where
  rnf :: LaunchTemplateOverrides -> ()
rnf LaunchTemplateOverrides' {Maybe Text
Maybe LaunchTemplateSpecification
Maybe InstanceRequirements
weightedCapacity :: Maybe Text
launchTemplateSpecification :: Maybe LaunchTemplateSpecification
instanceType :: Maybe Text
instanceRequirements :: Maybe InstanceRequirements
$sel:weightedCapacity:LaunchTemplateOverrides' :: LaunchTemplateOverrides -> Maybe Text
$sel:launchTemplateSpecification:LaunchTemplateOverrides' :: LaunchTemplateOverrides -> Maybe LaunchTemplateSpecification
$sel:instanceType:LaunchTemplateOverrides' :: LaunchTemplateOverrides -> Maybe Text
$sel:instanceRequirements:LaunchTemplateOverrides' :: LaunchTemplateOverrides -> Maybe InstanceRequirements
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe InstanceRequirements
instanceRequirements
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
instanceType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LaunchTemplateSpecification
launchTemplateSpecification
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
weightedCapacity

instance Data.ToQuery LaunchTemplateOverrides where
  toQuery :: LaunchTemplateOverrides -> QueryString
toQuery LaunchTemplateOverrides' {Maybe Text
Maybe LaunchTemplateSpecification
Maybe InstanceRequirements
weightedCapacity :: Maybe Text
launchTemplateSpecification :: Maybe LaunchTemplateSpecification
instanceType :: Maybe Text
instanceRequirements :: Maybe InstanceRequirements
$sel:weightedCapacity:LaunchTemplateOverrides' :: LaunchTemplateOverrides -> Maybe Text
$sel:launchTemplateSpecification:LaunchTemplateOverrides' :: LaunchTemplateOverrides -> Maybe LaunchTemplateSpecification
$sel:instanceType:LaunchTemplateOverrides' :: LaunchTemplateOverrides -> Maybe Text
$sel:instanceRequirements:LaunchTemplateOverrides' :: LaunchTemplateOverrides -> Maybe InstanceRequirements
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"InstanceRequirements" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe InstanceRequirements
instanceRequirements,
        ByteString
"InstanceType" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
instanceType,
        ByteString
"LaunchTemplateSpecification"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe LaunchTemplateSpecification
launchTemplateSpecification,
        ByteString
"WeightedCapacity" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
weightedCapacity
      ]