{-# 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.EC2.Types.InstanceRequirements
-- 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.EC2.Types.InstanceRequirements where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.EC2.Internal
import Amazonka.EC2.Types.AcceleratorCount
import Amazonka.EC2.Types.AcceleratorManufacturer
import Amazonka.EC2.Types.AcceleratorName
import Amazonka.EC2.Types.AcceleratorTotalMemoryMiB
import Amazonka.EC2.Types.AcceleratorType
import Amazonka.EC2.Types.BareMetal
import Amazonka.EC2.Types.BaselineEbsBandwidthMbps
import Amazonka.EC2.Types.BurstablePerformance
import Amazonka.EC2.Types.CpuManufacturer
import Amazonka.EC2.Types.InstanceGeneration
import Amazonka.EC2.Types.LocalStorage
import Amazonka.EC2.Types.LocalStorageType
import Amazonka.EC2.Types.MemoryGiBPerVCpu
import Amazonka.EC2.Types.MemoryMiB
import Amazonka.EC2.Types.NetworkBandwidthGbps
import Amazonka.EC2.Types.NetworkInterfaceCount
import Amazonka.EC2.Types.TotalLocalStorageGB
import Amazonka.EC2.Types.VCpuCountRange
import qualified Amazonka.Prelude as Prelude

-- | The attributes for the instance types. When you specify instance
-- attributes, Amazon EC2 will identify instance types with these
-- attributes.
--
-- When you specify multiple attributes, you get instance types that
-- satisfy all of the specified attributes. If you specify multiple values
-- for an attribute, you get instance types that satisfy any of the
-- specified values.
--
-- To limit the list of instance types from which Amazon EC2 can identify
-- matching instance types, you can use one of the following parameters,
-- but not both in the same request:
--
-- -   @AllowedInstanceTypes@ - The instance types to include in the list.
--     All other instance types are ignored, even if they match your
--     specified attributes.
--
-- -   @ExcludedInstanceTypes@ - The instance types to exclude from the
--     list, even if they match your specified attributes.
--
-- You must specify @VCpuCount@ and @MemoryMiB@. All other attributes are
-- optional. Any unspecified optional attribute is set to its default.
--
-- For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/ec2-fleet-attribute-based-instance-type-selection.html Attribute-based instance type selection for EC2 Fleet>,
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/spot-fleet-attribute-based-instance-type-selection.html Attribute-based instance type selection for Spot Fleet>,
-- and
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/spot-placement-score.html Spot placement score>
-- in the /Amazon EC2 User Guide/.
--
-- /See:/ 'newInstanceRequirements' smart constructor.
data InstanceRequirements = InstanceRequirements'
  { -- | The minimum and maximum number of accelerators (GPUs, FPGAs, or Amazon
    -- Web Services Inferentia chips) on an instance.
    --
    -- To exclude accelerator-enabled instance types, set @Max@ to @0@.
    --
    -- Default: No minimum or maximum limits
    InstanceRequirements -> Maybe AcceleratorCount
acceleratorCount :: Prelude.Maybe AcceleratorCount,
    -- | Indicates whether instance types must have accelerators by specific
    -- manufacturers.
    --
    -- -   For instance types with NVIDIA devices, specify @nvidia@.
    --
    -- -   For instance types with AMD devices, specify @amd@.
    --
    -- -   For instance types with Amazon Web Services devices, specify
    --     @amazon-web-services@.
    --
    -- -   For instance types with Xilinx devices, specify @xilinx@.
    --
    -- Default: Any manufacturer
    InstanceRequirements -> Maybe [AcceleratorManufacturer]
acceleratorManufacturers :: Prelude.Maybe [AcceleratorManufacturer],
    -- | The accelerators that must be on the instance type.
    --
    -- -   For instance types with NVIDIA A100 GPUs, specify @a100@.
    --
    -- -   For instance types with NVIDIA V100 GPUs, specify @v100@.
    --
    -- -   For instance types with NVIDIA K80 GPUs, specify @k80@.
    --
    -- -   For instance types with NVIDIA T4 GPUs, specify @t4@.
    --
    -- -   For instance types with NVIDIA M60 GPUs, specify @m60@.
    --
    -- -   For instance types with AMD Radeon Pro V520 GPUs, specify
    --     @radeon-pro-v520@.
    --
    -- -   For instance types with Xilinx VU9P FPGAs, specify @vu9p@.
    --
    -- -   For instance types with Amazon Web Services Inferentia chips,
    --     specify @inferentia@.
    --
    -- -   For instance types with NVIDIA GRID K520 GPUs, specify @k520@.
    --
    -- Default: Any accelerator
    InstanceRequirements -> Maybe [AcceleratorName]
acceleratorNames :: Prelude.Maybe [AcceleratorName],
    -- | The minimum and maximum amount of total accelerator memory, in MiB.
    --
    -- Default: No minimum or maximum limits
    InstanceRequirements -> Maybe AcceleratorTotalMemoryMiB
acceleratorTotalMemoryMiB :: Prelude.Maybe AcceleratorTotalMemoryMiB,
    -- | The accelerator types that must be on the instance type.
    --
    -- -   For instance types with GPU accelerators, specify @gpu@.
    --
    -- -   For instance types with FPGA accelerators, specify @fpga@.
    --
    -- -   For instance types with inference accelerators, specify @inference@.
    --
    -- Default: Any accelerator type
    InstanceRequirements -> Maybe [AcceleratorType]
acceleratorTypes :: Prelude.Maybe [AcceleratorType],
    -- | The instance types to apply your specified attributes against. All other
    -- instance types are ignored, even if they match your specified
    -- attributes.
    --
    -- You can use strings with one or more wild cards, represented by an
    -- asterisk (@*@), to allow an instance type, size, or generation. The
    -- following are examples: @m5.8xlarge@, @c5*.*@, @m5a.*@, @r*@, @*3*@.
    --
    -- For example, if you specify @c5*@,Amazon EC2 will allow the entire C5
    -- instance family, which includes all C5a and C5n instance types. If you
    -- specify @m5a.*@, Amazon EC2 will allow all the M5a instance types, but
    -- not the M5n instance types.
    --
    -- If you specify @AllowedInstanceTypes@, you can\'t specify
    -- @ExcludedInstanceTypes@.
    --
    -- Default: All instance types
    InstanceRequirements -> Maybe [Text]
allowedInstanceTypes :: Prelude.Maybe [Prelude.Text],
    -- | Indicates whether bare metal instance types must be included, excluded,
    -- or required.
    --
    -- -   To include bare metal instance types, specify @included@.
    --
    -- -   To require only bare metal instance types, specify @required@.
    --
    -- -   To exclude bare metal instance types, specify @excluded@.
    --
    -- Default: @excluded@
    InstanceRequirements -> Maybe BareMetal
bareMetal :: Prelude.Maybe BareMetal,
    -- | The minimum and maximum baseline bandwidth to Amazon EBS, in Mbps. For
    -- more information, see
    -- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/ebs-optimized.html Amazon EBS–optimized instances>
    -- in the /Amazon EC2 User Guide/.
    --
    -- Default: No minimum or maximum limits
    InstanceRequirements -> Maybe BaselineEbsBandwidthMbps
baselineEbsBandwidthMbps :: Prelude.Maybe BaselineEbsBandwidthMbps,
    -- | Indicates whether burstable performance T instance types are included,
    -- excluded, or required. For more information, see
    -- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/burstable-performance-instances.html Burstable performance instances>.
    --
    -- -   To include burstable performance instance types, specify @included@.
    --
    -- -   To require only burstable performance instance types, specify
    --     @required@.
    --
    -- -   To exclude burstable performance instance types, specify @excluded@.
    --
    -- Default: @excluded@
    InstanceRequirements -> Maybe BurstablePerformance
burstablePerformance :: Prelude.Maybe BurstablePerformance,
    -- | The CPU manufacturers to include.
    --
    -- -   For instance types with Intel CPUs, specify @intel@.
    --
    -- -   For instance types with AMD CPUs, specify @amd@.
    --
    -- -   For instance types with Amazon Web Services CPUs, specify
    --     @amazon-web-services@.
    --
    -- Don\'t confuse the CPU manufacturer with the CPU architecture. Instances
    -- will be launched with a compatible CPU architecture based on the Amazon
    -- Machine Image (AMI) that you specify in your launch template.
    --
    -- Default: Any manufacturer
    InstanceRequirements -> Maybe [CpuManufacturer]
cpuManufacturers :: Prelude.Maybe [CpuManufacturer],
    -- | The instance types to exclude.
    --
    -- You can use strings with one or more wild cards, represented by an
    -- asterisk (@*@), to exclude an instance type, size, or generation. The
    -- following are examples: @m5.8xlarge@, @c5*.*@, @m5a.*@, @r*@, @*3*@.
    --
    -- For example, if you specify @c5*@,Amazon EC2 will exclude the entire C5
    -- instance family, which includes all C5a and C5n instance types. If you
    -- specify @m5a.*@, Amazon EC2 will exclude all the M5a instance types, but
    -- not the M5n instance types.
    --
    -- If you specify @ExcludedInstanceTypes@, you can\'t specify
    -- @AllowedInstanceTypes@.
    --
    -- Default: No excluded instance types
    InstanceRequirements -> Maybe [Text]
excludedInstanceTypes :: Prelude.Maybe [Prelude.Text],
    -- | Indicates whether current or previous generation instance types are
    -- included. The current generation instance types are recommended for use.
    -- Current generation instance types are typically the latest two to three
    -- generations in each instance family. For more information, see
    -- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/instance-types.html Instance types>
    -- in the /Amazon EC2 User Guide/.
    --
    -- For current generation instance types, specify @current@.
    --
    -- For previous generation instance types, specify @previous@.
    --
    -- Default: Current and previous generation instance types
    InstanceRequirements -> Maybe [InstanceGeneration]
instanceGenerations :: Prelude.Maybe [InstanceGeneration],
    -- | Indicates whether instance types with instance store volumes are
    -- included, excluded, or required. For more information,
    -- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/InstanceStorage.html Amazon EC2 instance store>
    -- in the /Amazon EC2 User Guide/.
    --
    -- -   To include instance types with instance store volumes, specify
    --     @included@.
    --
    -- -   To require only instance types with instance store volumes, specify
    --     @required@.
    --
    -- -   To exclude instance types with instance store volumes, specify
    --     @excluded@.
    --
    -- Default: @included@
    InstanceRequirements -> Maybe LocalStorage
localStorage :: Prelude.Maybe LocalStorage,
    -- | The type of local storage that is required.
    --
    -- -   For instance types with hard disk drive (HDD) storage, specify
    --     @hdd@.
    --
    -- -   For instance types with solid state drive (SSD) storage, specify
    --     @ssd@.
    --
    -- Default: @hdd@ and @ssd@
    InstanceRequirements -> Maybe [LocalStorageType]
localStorageTypes :: Prelude.Maybe [LocalStorageType],
    -- | The minimum and maximum amount of memory per vCPU, in GiB.
    --
    -- Default: No minimum or maximum limits
    InstanceRequirements -> Maybe MemoryGiBPerVCpu
memoryGiBPerVCpu :: Prelude.Maybe MemoryGiBPerVCpu,
    -- | The minimum and maximum amount of memory, in MiB.
    InstanceRequirements -> Maybe MemoryMiB
memoryMiB :: Prelude.Maybe MemoryMiB,
    -- | The minimum and maximum amount of network bandwidth, in gigabits per
    -- second (Gbps).
    --
    -- Default: No minimum or maximum limits
    InstanceRequirements -> Maybe NetworkBandwidthGbps
networkBandwidthGbps :: Prelude.Maybe NetworkBandwidthGbps,
    -- | The minimum and maximum number of network interfaces.
    --
    -- Default: No minimum or maximum limits
    InstanceRequirements -> Maybe NetworkInterfaceCount
networkInterfaceCount :: Prelude.Maybe NetworkInterfaceCount,
    -- | The price protection threshold for On-Demand Instances. This is the
    -- maximum you’ll pay for an On-Demand Instance, expressed as a percentage
    -- above the least expensive current generation M, C, or R instance type
    -- with your specified attributes. When Amazon EC2 selects instance types
    -- with your attributes, it excludes instance types priced above your
    -- threshold.
    --
    -- The parameter accepts an integer, which Amazon EC2 interprets as a
    -- percentage.
    --
    -- To turn off price protection, specify a high value, such as @999999@.
    --
    -- This parameter is not supported for
    -- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_GetSpotPlacementScores.html GetSpotPlacementScores>
    -- and
    -- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_GetInstanceTypesFromInstanceRequirements.html GetInstanceTypesFromInstanceRequirements>.
    --
    -- If you set @TargetCapacityUnitType@ to @vcpu@ or @memory-mib@, the price
    -- protection threshold is applied based on the per-vCPU or per-memory
    -- price instead of the per-instance price.
    --
    -- Default: @20@
    InstanceRequirements -> Maybe Int
onDemandMaxPricePercentageOverLowestPrice :: Prelude.Maybe Prelude.Int,
    -- | Indicates whether instance types must support hibernation for On-Demand
    -- Instances.
    --
    -- This parameter is not supported for
    -- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_GetSpotPlacementScores.html GetSpotPlacementScores>.
    --
    -- Default: @false@
    InstanceRequirements -> Maybe Bool
requireHibernateSupport :: Prelude.Maybe Prelude.Bool,
    -- | The price protection threshold for Spot Instances. This is the maximum
    -- you’ll pay for a Spot Instance, expressed as a percentage above the
    -- least expensive current generation M, C, or R instance type with your
    -- specified attributes. When Amazon EC2 selects instance types with your
    -- attributes, it excludes instance types priced above your threshold.
    --
    -- The parameter accepts an integer, which Amazon EC2 interprets as a
    -- percentage.
    --
    -- To turn off price protection, specify a high value, such as @999999@.
    --
    -- This parameter is not supported for
    -- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_GetSpotPlacementScores.html GetSpotPlacementScores>
    -- and
    -- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_GetInstanceTypesFromInstanceRequirements.html GetInstanceTypesFromInstanceRequirements>.
    --
    -- If you set @TargetCapacityUnitType@ to @vcpu@ or @memory-mib@, the price
    -- protection threshold is applied based on the per-vCPU or per-memory
    -- price instead of the per-instance price.
    --
    -- Default: @100@
    InstanceRequirements -> Maybe Int
spotMaxPricePercentageOverLowestPrice :: Prelude.Maybe Prelude.Int,
    -- | The minimum and maximum amount of total local storage, in GB.
    --
    -- Default: No minimum or maximum limits
    InstanceRequirements -> Maybe TotalLocalStorageGB
totalLocalStorageGB :: Prelude.Maybe TotalLocalStorageGB,
    -- | The minimum and maximum number of vCPUs.
    InstanceRequirements -> Maybe VCpuCountRange
vCpuCount :: Prelude.Maybe VCpuCountRange
  }
  deriving (InstanceRequirements -> InstanceRequirements -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InstanceRequirements -> InstanceRequirements -> Bool
$c/= :: InstanceRequirements -> InstanceRequirements -> Bool
== :: InstanceRequirements -> InstanceRequirements -> Bool
$c== :: InstanceRequirements -> InstanceRequirements -> Bool
Prelude.Eq, ReadPrec [InstanceRequirements]
ReadPrec InstanceRequirements
Int -> ReadS InstanceRequirements
ReadS [InstanceRequirements]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [InstanceRequirements]
$creadListPrec :: ReadPrec [InstanceRequirements]
readPrec :: ReadPrec InstanceRequirements
$creadPrec :: ReadPrec InstanceRequirements
readList :: ReadS [InstanceRequirements]
$creadList :: ReadS [InstanceRequirements]
readsPrec :: Int -> ReadS InstanceRequirements
$creadsPrec :: Int -> ReadS InstanceRequirements
Prelude.Read, Int -> InstanceRequirements -> ShowS
[InstanceRequirements] -> ShowS
InstanceRequirements -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InstanceRequirements] -> ShowS
$cshowList :: [InstanceRequirements] -> ShowS
show :: InstanceRequirements -> String
$cshow :: InstanceRequirements -> String
showsPrec :: Int -> InstanceRequirements -> ShowS
$cshowsPrec :: Int -> InstanceRequirements -> ShowS
Prelude.Show, forall x. Rep InstanceRequirements x -> InstanceRequirements
forall x. InstanceRequirements -> Rep InstanceRequirements x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InstanceRequirements x -> InstanceRequirements
$cfrom :: forall x. InstanceRequirements -> Rep InstanceRequirements x
Prelude.Generic)

-- |
-- Create a value of 'InstanceRequirements' 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:
--
-- 'acceleratorCount', 'instanceRequirements_acceleratorCount' - The minimum and maximum number of accelerators (GPUs, FPGAs, or Amazon
-- Web Services Inferentia chips) on an instance.
--
-- To exclude accelerator-enabled instance types, set @Max@ to @0@.
--
-- Default: No minimum or maximum limits
--
-- 'acceleratorManufacturers', 'instanceRequirements_acceleratorManufacturers' - Indicates whether instance types must have accelerators by specific
-- manufacturers.
--
-- -   For instance types with NVIDIA devices, specify @nvidia@.
--
-- -   For instance types with AMD devices, specify @amd@.
--
-- -   For instance types with Amazon Web Services devices, specify
--     @amazon-web-services@.
--
-- -   For instance types with Xilinx devices, specify @xilinx@.
--
-- Default: Any manufacturer
--
-- 'acceleratorNames', 'instanceRequirements_acceleratorNames' - The accelerators that must be on the instance type.
--
-- -   For instance types with NVIDIA A100 GPUs, specify @a100@.
--
-- -   For instance types with NVIDIA V100 GPUs, specify @v100@.
--
-- -   For instance types with NVIDIA K80 GPUs, specify @k80@.
--
-- -   For instance types with NVIDIA T4 GPUs, specify @t4@.
--
-- -   For instance types with NVIDIA M60 GPUs, specify @m60@.
--
-- -   For instance types with AMD Radeon Pro V520 GPUs, specify
--     @radeon-pro-v520@.
--
-- -   For instance types with Xilinx VU9P FPGAs, specify @vu9p@.
--
-- -   For instance types with Amazon Web Services Inferentia chips,
--     specify @inferentia@.
--
-- -   For instance types with NVIDIA GRID K520 GPUs, specify @k520@.
--
-- Default: Any accelerator
--
-- 'acceleratorTotalMemoryMiB', 'instanceRequirements_acceleratorTotalMemoryMiB' - The minimum and maximum amount of total accelerator memory, in MiB.
--
-- Default: No minimum or maximum limits
--
-- 'acceleratorTypes', 'instanceRequirements_acceleratorTypes' - The accelerator types that must be on the instance type.
--
-- -   For instance types with GPU accelerators, specify @gpu@.
--
-- -   For instance types with FPGA accelerators, specify @fpga@.
--
-- -   For instance types with inference accelerators, specify @inference@.
--
-- Default: Any accelerator type
--
-- 'allowedInstanceTypes', 'instanceRequirements_allowedInstanceTypes' - The instance types to apply your specified attributes against. All other
-- instance types are ignored, even if they match your specified
-- attributes.
--
-- You can use strings with one or more wild cards, represented by an
-- asterisk (@*@), to allow an instance type, size, or generation. The
-- following are examples: @m5.8xlarge@, @c5*.*@, @m5a.*@, @r*@, @*3*@.
--
-- For example, if you specify @c5*@,Amazon EC2 will allow the entire C5
-- instance family, which includes all C5a and C5n instance types. If you
-- specify @m5a.*@, Amazon EC2 will allow all the M5a instance types, but
-- not the M5n instance types.
--
-- If you specify @AllowedInstanceTypes@, you can\'t specify
-- @ExcludedInstanceTypes@.
--
-- Default: All instance types
--
-- 'bareMetal', 'instanceRequirements_bareMetal' - Indicates whether bare metal instance types must be included, excluded,
-- or required.
--
-- -   To include bare metal instance types, specify @included@.
--
-- -   To require only bare metal instance types, specify @required@.
--
-- -   To exclude bare metal instance types, specify @excluded@.
--
-- Default: @excluded@
--
-- 'baselineEbsBandwidthMbps', 'instanceRequirements_baselineEbsBandwidthMbps' - The minimum and maximum baseline bandwidth to Amazon EBS, in Mbps. For
-- more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/ebs-optimized.html Amazon EBS–optimized instances>
-- in the /Amazon EC2 User Guide/.
--
-- Default: No minimum or maximum limits
--
-- 'burstablePerformance', 'instanceRequirements_burstablePerformance' - Indicates whether burstable performance T instance types are included,
-- excluded, or required. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/burstable-performance-instances.html Burstable performance instances>.
--
-- -   To include burstable performance instance types, specify @included@.
--
-- -   To require only burstable performance instance types, specify
--     @required@.
--
-- -   To exclude burstable performance instance types, specify @excluded@.
--
-- Default: @excluded@
--
-- 'cpuManufacturers', 'instanceRequirements_cpuManufacturers' - The CPU manufacturers to include.
--
-- -   For instance types with Intel CPUs, specify @intel@.
--
-- -   For instance types with AMD CPUs, specify @amd@.
--
-- -   For instance types with Amazon Web Services CPUs, specify
--     @amazon-web-services@.
--
-- Don\'t confuse the CPU manufacturer with the CPU architecture. Instances
-- will be launched with a compatible CPU architecture based on the Amazon
-- Machine Image (AMI) that you specify in your launch template.
--
-- Default: Any manufacturer
--
-- 'excludedInstanceTypes', 'instanceRequirements_excludedInstanceTypes' - The instance types to exclude.
--
-- You can use strings with one or more wild cards, represented by an
-- asterisk (@*@), to exclude an instance type, size, or generation. The
-- following are examples: @m5.8xlarge@, @c5*.*@, @m5a.*@, @r*@, @*3*@.
--
-- For example, if you specify @c5*@,Amazon EC2 will exclude the entire C5
-- instance family, which includes all C5a and C5n instance types. If you
-- specify @m5a.*@, Amazon EC2 will exclude all the M5a instance types, but
-- not the M5n instance types.
--
-- If you specify @ExcludedInstanceTypes@, you can\'t specify
-- @AllowedInstanceTypes@.
--
-- Default: No excluded instance types
--
-- 'instanceGenerations', 'instanceRequirements_instanceGenerations' - Indicates whether current or previous generation instance types are
-- included. The current generation instance types are recommended for use.
-- Current generation instance types are typically the latest two to three
-- generations in each instance family. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/instance-types.html Instance types>
-- in the /Amazon EC2 User Guide/.
--
-- For current generation instance types, specify @current@.
--
-- For previous generation instance types, specify @previous@.
--
-- Default: Current and previous generation instance types
--
-- 'localStorage', 'instanceRequirements_localStorage' - Indicates whether instance types with instance store volumes are
-- included, excluded, or required. For more information,
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/InstanceStorage.html Amazon EC2 instance store>
-- in the /Amazon EC2 User Guide/.
--
-- -   To include instance types with instance store volumes, specify
--     @included@.
--
-- -   To require only instance types with instance store volumes, specify
--     @required@.
--
-- -   To exclude instance types with instance store volumes, specify
--     @excluded@.
--
-- Default: @included@
--
-- 'localStorageTypes', 'instanceRequirements_localStorageTypes' - The type of local storage that is required.
--
-- -   For instance types with hard disk drive (HDD) storage, specify
--     @hdd@.
--
-- -   For instance types with solid state drive (SSD) storage, specify
--     @ssd@.
--
-- Default: @hdd@ and @ssd@
--
-- 'memoryGiBPerVCpu', 'instanceRequirements_memoryGiBPerVCpu' - The minimum and maximum amount of memory per vCPU, in GiB.
--
-- Default: No minimum or maximum limits
--
-- 'memoryMiB', 'instanceRequirements_memoryMiB' - The minimum and maximum amount of memory, in MiB.
--
-- 'networkBandwidthGbps', 'instanceRequirements_networkBandwidthGbps' - The minimum and maximum amount of network bandwidth, in gigabits per
-- second (Gbps).
--
-- Default: No minimum or maximum limits
--
-- 'networkInterfaceCount', 'instanceRequirements_networkInterfaceCount' - The minimum and maximum number of network interfaces.
--
-- Default: No minimum or maximum limits
--
-- 'onDemandMaxPricePercentageOverLowestPrice', 'instanceRequirements_onDemandMaxPricePercentageOverLowestPrice' - The price protection threshold for On-Demand Instances. This is the
-- maximum you’ll pay for an On-Demand Instance, expressed as a percentage
-- above the least expensive current generation M, C, or R instance type
-- with your specified attributes. When Amazon EC2 selects instance types
-- with your attributes, it excludes instance types priced above your
-- threshold.
--
-- The parameter accepts an integer, which Amazon EC2 interprets as a
-- percentage.
--
-- To turn off price protection, specify a high value, such as @999999@.
--
-- This parameter is not supported for
-- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_GetSpotPlacementScores.html GetSpotPlacementScores>
-- and
-- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_GetInstanceTypesFromInstanceRequirements.html GetInstanceTypesFromInstanceRequirements>.
--
-- If you set @TargetCapacityUnitType@ to @vcpu@ or @memory-mib@, the price
-- protection threshold is applied based on the per-vCPU or per-memory
-- price instead of the per-instance price.
--
-- Default: @20@
--
-- 'requireHibernateSupport', 'instanceRequirements_requireHibernateSupport' - Indicates whether instance types must support hibernation for On-Demand
-- Instances.
--
-- This parameter is not supported for
-- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_GetSpotPlacementScores.html GetSpotPlacementScores>.
--
-- Default: @false@
--
-- 'spotMaxPricePercentageOverLowestPrice', 'instanceRequirements_spotMaxPricePercentageOverLowestPrice' - The price protection threshold for Spot Instances. This is the maximum
-- you’ll pay for a Spot Instance, expressed as a percentage above the
-- least expensive current generation M, C, or R instance type with your
-- specified attributes. When Amazon EC2 selects instance types with your
-- attributes, it excludes instance types priced above your threshold.
--
-- The parameter accepts an integer, which Amazon EC2 interprets as a
-- percentage.
--
-- To turn off price protection, specify a high value, such as @999999@.
--
-- This parameter is not supported for
-- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_GetSpotPlacementScores.html GetSpotPlacementScores>
-- and
-- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_GetInstanceTypesFromInstanceRequirements.html GetInstanceTypesFromInstanceRequirements>.
--
-- If you set @TargetCapacityUnitType@ to @vcpu@ or @memory-mib@, the price
-- protection threshold is applied based on the per-vCPU or per-memory
-- price instead of the per-instance price.
--
-- Default: @100@
--
-- 'totalLocalStorageGB', 'instanceRequirements_totalLocalStorageGB' - The minimum and maximum amount of total local storage, in GB.
--
-- Default: No minimum or maximum limits
--
-- 'vCpuCount', 'instanceRequirements_vCpuCount' - The minimum and maximum number of vCPUs.
newInstanceRequirements ::
  InstanceRequirements
newInstanceRequirements :: InstanceRequirements
newInstanceRequirements =
  InstanceRequirements'
    { $sel:acceleratorCount:InstanceRequirements' :: Maybe AcceleratorCount
acceleratorCount =
        forall a. Maybe a
Prelude.Nothing,
      $sel:acceleratorManufacturers:InstanceRequirements' :: Maybe [AcceleratorManufacturer]
acceleratorManufacturers = forall a. Maybe a
Prelude.Nothing,
      $sel:acceleratorNames:InstanceRequirements' :: Maybe [AcceleratorName]
acceleratorNames = forall a. Maybe a
Prelude.Nothing,
      $sel:acceleratorTotalMemoryMiB:InstanceRequirements' :: Maybe AcceleratorTotalMemoryMiB
acceleratorTotalMemoryMiB = forall a. Maybe a
Prelude.Nothing,
      $sel:acceleratorTypes:InstanceRequirements' :: Maybe [AcceleratorType]
acceleratorTypes = forall a. Maybe a
Prelude.Nothing,
      $sel:allowedInstanceTypes:InstanceRequirements' :: Maybe [Text]
allowedInstanceTypes = forall a. Maybe a
Prelude.Nothing,
      $sel:bareMetal:InstanceRequirements' :: Maybe BareMetal
bareMetal = forall a. Maybe a
Prelude.Nothing,
      $sel:baselineEbsBandwidthMbps:InstanceRequirements' :: Maybe BaselineEbsBandwidthMbps
baselineEbsBandwidthMbps = forall a. Maybe a
Prelude.Nothing,
      $sel:burstablePerformance:InstanceRequirements' :: Maybe BurstablePerformance
burstablePerformance = forall a. Maybe a
Prelude.Nothing,
      $sel:cpuManufacturers:InstanceRequirements' :: Maybe [CpuManufacturer]
cpuManufacturers = forall a. Maybe a
Prelude.Nothing,
      $sel:excludedInstanceTypes:InstanceRequirements' :: Maybe [Text]
excludedInstanceTypes = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceGenerations:InstanceRequirements' :: Maybe [InstanceGeneration]
instanceGenerations = forall a. Maybe a
Prelude.Nothing,
      $sel:localStorage:InstanceRequirements' :: Maybe LocalStorage
localStorage = forall a. Maybe a
Prelude.Nothing,
      $sel:localStorageTypes:InstanceRequirements' :: Maybe [LocalStorageType]
localStorageTypes = forall a. Maybe a
Prelude.Nothing,
      $sel:memoryGiBPerVCpu:InstanceRequirements' :: Maybe MemoryGiBPerVCpu
memoryGiBPerVCpu = forall a. Maybe a
Prelude.Nothing,
      $sel:memoryMiB:InstanceRequirements' :: Maybe MemoryMiB
memoryMiB = forall a. Maybe a
Prelude.Nothing,
      $sel:networkBandwidthGbps:InstanceRequirements' :: Maybe NetworkBandwidthGbps
networkBandwidthGbps = forall a. Maybe a
Prelude.Nothing,
      $sel:networkInterfaceCount:InstanceRequirements' :: Maybe NetworkInterfaceCount
networkInterfaceCount = forall a. Maybe a
Prelude.Nothing,
      $sel:onDemandMaxPricePercentageOverLowestPrice:InstanceRequirements' :: Maybe Int
onDemandMaxPricePercentageOverLowestPrice =
        forall a. Maybe a
Prelude.Nothing,
      $sel:requireHibernateSupport:InstanceRequirements' :: Maybe Bool
requireHibernateSupport = forall a. Maybe a
Prelude.Nothing,
      $sel:spotMaxPricePercentageOverLowestPrice:InstanceRequirements' :: Maybe Int
spotMaxPricePercentageOverLowestPrice =
        forall a. Maybe a
Prelude.Nothing,
      $sel:totalLocalStorageGB:InstanceRequirements' :: Maybe TotalLocalStorageGB
totalLocalStorageGB = forall a. Maybe a
Prelude.Nothing,
      $sel:vCpuCount:InstanceRequirements' :: Maybe VCpuCountRange
vCpuCount = forall a. Maybe a
Prelude.Nothing
    }

-- | The minimum and maximum number of accelerators (GPUs, FPGAs, or Amazon
-- Web Services Inferentia chips) on an instance.
--
-- To exclude accelerator-enabled instance types, set @Max@ to @0@.
--
-- Default: No minimum or maximum limits
instanceRequirements_acceleratorCount :: Lens.Lens' InstanceRequirements (Prelude.Maybe AcceleratorCount)
instanceRequirements_acceleratorCount :: Lens' InstanceRequirements (Maybe AcceleratorCount)
instanceRequirements_acceleratorCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceRequirements' {Maybe AcceleratorCount
acceleratorCount :: Maybe AcceleratorCount
$sel:acceleratorCount:InstanceRequirements' :: InstanceRequirements -> Maybe AcceleratorCount
acceleratorCount} -> Maybe AcceleratorCount
acceleratorCount) (\s :: InstanceRequirements
s@InstanceRequirements' {} Maybe AcceleratorCount
a -> InstanceRequirements
s {$sel:acceleratorCount:InstanceRequirements' :: Maybe AcceleratorCount
acceleratorCount = Maybe AcceleratorCount
a} :: InstanceRequirements)

-- | Indicates whether instance types must have accelerators by specific
-- manufacturers.
--
-- -   For instance types with NVIDIA devices, specify @nvidia@.
--
-- -   For instance types with AMD devices, specify @amd@.
--
-- -   For instance types with Amazon Web Services devices, specify
--     @amazon-web-services@.
--
-- -   For instance types with Xilinx devices, specify @xilinx@.
--
-- Default: Any manufacturer
instanceRequirements_acceleratorManufacturers :: Lens.Lens' InstanceRequirements (Prelude.Maybe [AcceleratorManufacturer])
instanceRequirements_acceleratorManufacturers :: Lens' InstanceRequirements (Maybe [AcceleratorManufacturer])
instanceRequirements_acceleratorManufacturers = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceRequirements' {Maybe [AcceleratorManufacturer]
acceleratorManufacturers :: Maybe [AcceleratorManufacturer]
$sel:acceleratorManufacturers:InstanceRequirements' :: InstanceRequirements -> Maybe [AcceleratorManufacturer]
acceleratorManufacturers} -> Maybe [AcceleratorManufacturer]
acceleratorManufacturers) (\s :: InstanceRequirements
s@InstanceRequirements' {} Maybe [AcceleratorManufacturer]
a -> InstanceRequirements
s {$sel:acceleratorManufacturers:InstanceRequirements' :: Maybe [AcceleratorManufacturer]
acceleratorManufacturers = Maybe [AcceleratorManufacturer]
a} :: InstanceRequirements) 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 accelerators that must be on the instance type.
--
-- -   For instance types with NVIDIA A100 GPUs, specify @a100@.
--
-- -   For instance types with NVIDIA V100 GPUs, specify @v100@.
--
-- -   For instance types with NVIDIA K80 GPUs, specify @k80@.
--
-- -   For instance types with NVIDIA T4 GPUs, specify @t4@.
--
-- -   For instance types with NVIDIA M60 GPUs, specify @m60@.
--
-- -   For instance types with AMD Radeon Pro V520 GPUs, specify
--     @radeon-pro-v520@.
--
-- -   For instance types with Xilinx VU9P FPGAs, specify @vu9p@.
--
-- -   For instance types with Amazon Web Services Inferentia chips,
--     specify @inferentia@.
--
-- -   For instance types with NVIDIA GRID K520 GPUs, specify @k520@.
--
-- Default: Any accelerator
instanceRequirements_acceleratorNames :: Lens.Lens' InstanceRequirements (Prelude.Maybe [AcceleratorName])
instanceRequirements_acceleratorNames :: Lens' InstanceRequirements (Maybe [AcceleratorName])
instanceRequirements_acceleratorNames = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceRequirements' {Maybe [AcceleratorName]
acceleratorNames :: Maybe [AcceleratorName]
$sel:acceleratorNames:InstanceRequirements' :: InstanceRequirements -> Maybe [AcceleratorName]
acceleratorNames} -> Maybe [AcceleratorName]
acceleratorNames) (\s :: InstanceRequirements
s@InstanceRequirements' {} Maybe [AcceleratorName]
a -> InstanceRequirements
s {$sel:acceleratorNames:InstanceRequirements' :: Maybe [AcceleratorName]
acceleratorNames = Maybe [AcceleratorName]
a} :: InstanceRequirements) 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 minimum and maximum amount of total accelerator memory, in MiB.
--
-- Default: No minimum or maximum limits
instanceRequirements_acceleratorTotalMemoryMiB :: Lens.Lens' InstanceRequirements (Prelude.Maybe AcceleratorTotalMemoryMiB)
instanceRequirements_acceleratorTotalMemoryMiB :: Lens' InstanceRequirements (Maybe AcceleratorTotalMemoryMiB)
instanceRequirements_acceleratorTotalMemoryMiB = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceRequirements' {Maybe AcceleratorTotalMemoryMiB
acceleratorTotalMemoryMiB :: Maybe AcceleratorTotalMemoryMiB
$sel:acceleratorTotalMemoryMiB:InstanceRequirements' :: InstanceRequirements -> Maybe AcceleratorTotalMemoryMiB
acceleratorTotalMemoryMiB} -> Maybe AcceleratorTotalMemoryMiB
acceleratorTotalMemoryMiB) (\s :: InstanceRequirements
s@InstanceRequirements' {} Maybe AcceleratorTotalMemoryMiB
a -> InstanceRequirements
s {$sel:acceleratorTotalMemoryMiB:InstanceRequirements' :: Maybe AcceleratorTotalMemoryMiB
acceleratorTotalMemoryMiB = Maybe AcceleratorTotalMemoryMiB
a} :: InstanceRequirements)

-- | The accelerator types that must be on the instance type.
--
-- -   For instance types with GPU accelerators, specify @gpu@.
--
-- -   For instance types with FPGA accelerators, specify @fpga@.
--
-- -   For instance types with inference accelerators, specify @inference@.
--
-- Default: Any accelerator type
instanceRequirements_acceleratorTypes :: Lens.Lens' InstanceRequirements (Prelude.Maybe [AcceleratorType])
instanceRequirements_acceleratorTypes :: Lens' InstanceRequirements (Maybe [AcceleratorType])
instanceRequirements_acceleratorTypes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceRequirements' {Maybe [AcceleratorType]
acceleratorTypes :: Maybe [AcceleratorType]
$sel:acceleratorTypes:InstanceRequirements' :: InstanceRequirements -> Maybe [AcceleratorType]
acceleratorTypes} -> Maybe [AcceleratorType]
acceleratorTypes) (\s :: InstanceRequirements
s@InstanceRequirements' {} Maybe [AcceleratorType]
a -> InstanceRequirements
s {$sel:acceleratorTypes:InstanceRequirements' :: Maybe [AcceleratorType]
acceleratorTypes = Maybe [AcceleratorType]
a} :: InstanceRequirements) 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 instance types to apply your specified attributes against. All other
-- instance types are ignored, even if they match your specified
-- attributes.
--
-- You can use strings with one or more wild cards, represented by an
-- asterisk (@*@), to allow an instance type, size, or generation. The
-- following are examples: @m5.8xlarge@, @c5*.*@, @m5a.*@, @r*@, @*3*@.
--
-- For example, if you specify @c5*@,Amazon EC2 will allow the entire C5
-- instance family, which includes all C5a and C5n instance types. If you
-- specify @m5a.*@, Amazon EC2 will allow all the M5a instance types, but
-- not the M5n instance types.
--
-- If you specify @AllowedInstanceTypes@, you can\'t specify
-- @ExcludedInstanceTypes@.
--
-- Default: All instance types
instanceRequirements_allowedInstanceTypes :: Lens.Lens' InstanceRequirements (Prelude.Maybe [Prelude.Text])
instanceRequirements_allowedInstanceTypes :: Lens' InstanceRequirements (Maybe [Text])
instanceRequirements_allowedInstanceTypes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceRequirements' {Maybe [Text]
allowedInstanceTypes :: Maybe [Text]
$sel:allowedInstanceTypes:InstanceRequirements' :: InstanceRequirements -> Maybe [Text]
allowedInstanceTypes} -> Maybe [Text]
allowedInstanceTypes) (\s :: InstanceRequirements
s@InstanceRequirements' {} Maybe [Text]
a -> InstanceRequirements
s {$sel:allowedInstanceTypes:InstanceRequirements' :: Maybe [Text]
allowedInstanceTypes = Maybe [Text]
a} :: InstanceRequirements) 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 bare metal instance types must be included, excluded,
-- or required.
--
-- -   To include bare metal instance types, specify @included@.
--
-- -   To require only bare metal instance types, specify @required@.
--
-- -   To exclude bare metal instance types, specify @excluded@.
--
-- Default: @excluded@
instanceRequirements_bareMetal :: Lens.Lens' InstanceRequirements (Prelude.Maybe BareMetal)
instanceRequirements_bareMetal :: Lens' InstanceRequirements (Maybe BareMetal)
instanceRequirements_bareMetal = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceRequirements' {Maybe BareMetal
bareMetal :: Maybe BareMetal
$sel:bareMetal:InstanceRequirements' :: InstanceRequirements -> Maybe BareMetal
bareMetal} -> Maybe BareMetal
bareMetal) (\s :: InstanceRequirements
s@InstanceRequirements' {} Maybe BareMetal
a -> InstanceRequirements
s {$sel:bareMetal:InstanceRequirements' :: Maybe BareMetal
bareMetal = Maybe BareMetal
a} :: InstanceRequirements)

-- | The minimum and maximum baseline bandwidth to Amazon EBS, in Mbps. For
-- more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/ebs-optimized.html Amazon EBS–optimized instances>
-- in the /Amazon EC2 User Guide/.
--
-- Default: No minimum or maximum limits
instanceRequirements_baselineEbsBandwidthMbps :: Lens.Lens' InstanceRequirements (Prelude.Maybe BaselineEbsBandwidthMbps)
instanceRequirements_baselineEbsBandwidthMbps :: Lens' InstanceRequirements (Maybe BaselineEbsBandwidthMbps)
instanceRequirements_baselineEbsBandwidthMbps = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceRequirements' {Maybe BaselineEbsBandwidthMbps
baselineEbsBandwidthMbps :: Maybe BaselineEbsBandwidthMbps
$sel:baselineEbsBandwidthMbps:InstanceRequirements' :: InstanceRequirements -> Maybe BaselineEbsBandwidthMbps
baselineEbsBandwidthMbps} -> Maybe BaselineEbsBandwidthMbps
baselineEbsBandwidthMbps) (\s :: InstanceRequirements
s@InstanceRequirements' {} Maybe BaselineEbsBandwidthMbps
a -> InstanceRequirements
s {$sel:baselineEbsBandwidthMbps:InstanceRequirements' :: Maybe BaselineEbsBandwidthMbps
baselineEbsBandwidthMbps = Maybe BaselineEbsBandwidthMbps
a} :: InstanceRequirements)

-- | Indicates whether burstable performance T instance types are included,
-- excluded, or required. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/burstable-performance-instances.html Burstable performance instances>.
--
-- -   To include burstable performance instance types, specify @included@.
--
-- -   To require only burstable performance instance types, specify
--     @required@.
--
-- -   To exclude burstable performance instance types, specify @excluded@.
--
-- Default: @excluded@
instanceRequirements_burstablePerformance :: Lens.Lens' InstanceRequirements (Prelude.Maybe BurstablePerformance)
instanceRequirements_burstablePerformance :: Lens' InstanceRequirements (Maybe BurstablePerformance)
instanceRequirements_burstablePerformance = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceRequirements' {Maybe BurstablePerformance
burstablePerformance :: Maybe BurstablePerformance
$sel:burstablePerformance:InstanceRequirements' :: InstanceRequirements -> Maybe BurstablePerformance
burstablePerformance} -> Maybe BurstablePerformance
burstablePerformance) (\s :: InstanceRequirements
s@InstanceRequirements' {} Maybe BurstablePerformance
a -> InstanceRequirements
s {$sel:burstablePerformance:InstanceRequirements' :: Maybe BurstablePerformance
burstablePerformance = Maybe BurstablePerformance
a} :: InstanceRequirements)

-- | The CPU manufacturers to include.
--
-- -   For instance types with Intel CPUs, specify @intel@.
--
-- -   For instance types with AMD CPUs, specify @amd@.
--
-- -   For instance types with Amazon Web Services CPUs, specify
--     @amazon-web-services@.
--
-- Don\'t confuse the CPU manufacturer with the CPU architecture. Instances
-- will be launched with a compatible CPU architecture based on the Amazon
-- Machine Image (AMI) that you specify in your launch template.
--
-- Default: Any manufacturer
instanceRequirements_cpuManufacturers :: Lens.Lens' InstanceRequirements (Prelude.Maybe [CpuManufacturer])
instanceRequirements_cpuManufacturers :: Lens' InstanceRequirements (Maybe [CpuManufacturer])
instanceRequirements_cpuManufacturers = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceRequirements' {Maybe [CpuManufacturer]
cpuManufacturers :: Maybe [CpuManufacturer]
$sel:cpuManufacturers:InstanceRequirements' :: InstanceRequirements -> Maybe [CpuManufacturer]
cpuManufacturers} -> Maybe [CpuManufacturer]
cpuManufacturers) (\s :: InstanceRequirements
s@InstanceRequirements' {} Maybe [CpuManufacturer]
a -> InstanceRequirements
s {$sel:cpuManufacturers:InstanceRequirements' :: Maybe [CpuManufacturer]
cpuManufacturers = Maybe [CpuManufacturer]
a} :: InstanceRequirements) 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 instance types to exclude.
--
-- You can use strings with one or more wild cards, represented by an
-- asterisk (@*@), to exclude an instance type, size, or generation. The
-- following are examples: @m5.8xlarge@, @c5*.*@, @m5a.*@, @r*@, @*3*@.
--
-- For example, if you specify @c5*@,Amazon EC2 will exclude the entire C5
-- instance family, which includes all C5a and C5n instance types. If you
-- specify @m5a.*@, Amazon EC2 will exclude all the M5a instance types, but
-- not the M5n instance types.
--
-- If you specify @ExcludedInstanceTypes@, you can\'t specify
-- @AllowedInstanceTypes@.
--
-- Default: No excluded instance types
instanceRequirements_excludedInstanceTypes :: Lens.Lens' InstanceRequirements (Prelude.Maybe [Prelude.Text])
instanceRequirements_excludedInstanceTypes :: Lens' InstanceRequirements (Maybe [Text])
instanceRequirements_excludedInstanceTypes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceRequirements' {Maybe [Text]
excludedInstanceTypes :: Maybe [Text]
$sel:excludedInstanceTypes:InstanceRequirements' :: InstanceRequirements -> Maybe [Text]
excludedInstanceTypes} -> Maybe [Text]
excludedInstanceTypes) (\s :: InstanceRequirements
s@InstanceRequirements' {} Maybe [Text]
a -> InstanceRequirements
s {$sel:excludedInstanceTypes:InstanceRequirements' :: Maybe [Text]
excludedInstanceTypes = Maybe [Text]
a} :: InstanceRequirements) 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 current or previous generation instance types are
-- included. The current generation instance types are recommended for use.
-- Current generation instance types are typically the latest two to three
-- generations in each instance family. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/instance-types.html Instance types>
-- in the /Amazon EC2 User Guide/.
--
-- For current generation instance types, specify @current@.
--
-- For previous generation instance types, specify @previous@.
--
-- Default: Current and previous generation instance types
instanceRequirements_instanceGenerations :: Lens.Lens' InstanceRequirements (Prelude.Maybe [InstanceGeneration])
instanceRequirements_instanceGenerations :: Lens' InstanceRequirements (Maybe [InstanceGeneration])
instanceRequirements_instanceGenerations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceRequirements' {Maybe [InstanceGeneration]
instanceGenerations :: Maybe [InstanceGeneration]
$sel:instanceGenerations:InstanceRequirements' :: InstanceRequirements -> Maybe [InstanceGeneration]
instanceGenerations} -> Maybe [InstanceGeneration]
instanceGenerations) (\s :: InstanceRequirements
s@InstanceRequirements' {} Maybe [InstanceGeneration]
a -> InstanceRequirements
s {$sel:instanceGenerations:InstanceRequirements' :: Maybe [InstanceGeneration]
instanceGenerations = Maybe [InstanceGeneration]
a} :: InstanceRequirements) 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 instance types with instance store volumes are
-- included, excluded, or required. For more information,
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/InstanceStorage.html Amazon EC2 instance store>
-- in the /Amazon EC2 User Guide/.
--
-- -   To include instance types with instance store volumes, specify
--     @included@.
--
-- -   To require only instance types with instance store volumes, specify
--     @required@.
--
-- -   To exclude instance types with instance store volumes, specify
--     @excluded@.
--
-- Default: @included@
instanceRequirements_localStorage :: Lens.Lens' InstanceRequirements (Prelude.Maybe LocalStorage)
instanceRequirements_localStorage :: Lens' InstanceRequirements (Maybe LocalStorage)
instanceRequirements_localStorage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceRequirements' {Maybe LocalStorage
localStorage :: Maybe LocalStorage
$sel:localStorage:InstanceRequirements' :: InstanceRequirements -> Maybe LocalStorage
localStorage} -> Maybe LocalStorage
localStorage) (\s :: InstanceRequirements
s@InstanceRequirements' {} Maybe LocalStorage
a -> InstanceRequirements
s {$sel:localStorage:InstanceRequirements' :: Maybe LocalStorage
localStorage = Maybe LocalStorage
a} :: InstanceRequirements)

-- | The type of local storage that is required.
--
-- -   For instance types with hard disk drive (HDD) storage, specify
--     @hdd@.
--
-- -   For instance types with solid state drive (SSD) storage, specify
--     @ssd@.
--
-- Default: @hdd@ and @ssd@
instanceRequirements_localStorageTypes :: Lens.Lens' InstanceRequirements (Prelude.Maybe [LocalStorageType])
instanceRequirements_localStorageTypes :: Lens' InstanceRequirements (Maybe [LocalStorageType])
instanceRequirements_localStorageTypes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceRequirements' {Maybe [LocalStorageType]
localStorageTypes :: Maybe [LocalStorageType]
$sel:localStorageTypes:InstanceRequirements' :: InstanceRequirements -> Maybe [LocalStorageType]
localStorageTypes} -> Maybe [LocalStorageType]
localStorageTypes) (\s :: InstanceRequirements
s@InstanceRequirements' {} Maybe [LocalStorageType]
a -> InstanceRequirements
s {$sel:localStorageTypes:InstanceRequirements' :: Maybe [LocalStorageType]
localStorageTypes = Maybe [LocalStorageType]
a} :: InstanceRequirements) 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 minimum and maximum amount of memory per vCPU, in GiB.
--
-- Default: No minimum or maximum limits
instanceRequirements_memoryGiBPerVCpu :: Lens.Lens' InstanceRequirements (Prelude.Maybe MemoryGiBPerVCpu)
instanceRequirements_memoryGiBPerVCpu :: Lens' InstanceRequirements (Maybe MemoryGiBPerVCpu)
instanceRequirements_memoryGiBPerVCpu = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceRequirements' {Maybe MemoryGiBPerVCpu
memoryGiBPerVCpu :: Maybe MemoryGiBPerVCpu
$sel:memoryGiBPerVCpu:InstanceRequirements' :: InstanceRequirements -> Maybe MemoryGiBPerVCpu
memoryGiBPerVCpu} -> Maybe MemoryGiBPerVCpu
memoryGiBPerVCpu) (\s :: InstanceRequirements
s@InstanceRequirements' {} Maybe MemoryGiBPerVCpu
a -> InstanceRequirements
s {$sel:memoryGiBPerVCpu:InstanceRequirements' :: Maybe MemoryGiBPerVCpu
memoryGiBPerVCpu = Maybe MemoryGiBPerVCpu
a} :: InstanceRequirements)

-- | The minimum and maximum amount of memory, in MiB.
instanceRequirements_memoryMiB :: Lens.Lens' InstanceRequirements (Prelude.Maybe MemoryMiB)
instanceRequirements_memoryMiB :: Lens' InstanceRequirements (Maybe MemoryMiB)
instanceRequirements_memoryMiB = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceRequirements' {Maybe MemoryMiB
memoryMiB :: Maybe MemoryMiB
$sel:memoryMiB:InstanceRequirements' :: InstanceRequirements -> Maybe MemoryMiB
memoryMiB} -> Maybe MemoryMiB
memoryMiB) (\s :: InstanceRequirements
s@InstanceRequirements' {} Maybe MemoryMiB
a -> InstanceRequirements
s {$sel:memoryMiB:InstanceRequirements' :: Maybe MemoryMiB
memoryMiB = Maybe MemoryMiB
a} :: InstanceRequirements)

-- | The minimum and maximum amount of network bandwidth, in gigabits per
-- second (Gbps).
--
-- Default: No minimum or maximum limits
instanceRequirements_networkBandwidthGbps :: Lens.Lens' InstanceRequirements (Prelude.Maybe NetworkBandwidthGbps)
instanceRequirements_networkBandwidthGbps :: Lens' InstanceRequirements (Maybe NetworkBandwidthGbps)
instanceRequirements_networkBandwidthGbps = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceRequirements' {Maybe NetworkBandwidthGbps
networkBandwidthGbps :: Maybe NetworkBandwidthGbps
$sel:networkBandwidthGbps:InstanceRequirements' :: InstanceRequirements -> Maybe NetworkBandwidthGbps
networkBandwidthGbps} -> Maybe NetworkBandwidthGbps
networkBandwidthGbps) (\s :: InstanceRequirements
s@InstanceRequirements' {} Maybe NetworkBandwidthGbps
a -> InstanceRequirements
s {$sel:networkBandwidthGbps:InstanceRequirements' :: Maybe NetworkBandwidthGbps
networkBandwidthGbps = Maybe NetworkBandwidthGbps
a} :: InstanceRequirements)

-- | The minimum and maximum number of network interfaces.
--
-- Default: No minimum or maximum limits
instanceRequirements_networkInterfaceCount :: Lens.Lens' InstanceRequirements (Prelude.Maybe NetworkInterfaceCount)
instanceRequirements_networkInterfaceCount :: Lens' InstanceRequirements (Maybe NetworkInterfaceCount)
instanceRequirements_networkInterfaceCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceRequirements' {Maybe NetworkInterfaceCount
networkInterfaceCount :: Maybe NetworkInterfaceCount
$sel:networkInterfaceCount:InstanceRequirements' :: InstanceRequirements -> Maybe NetworkInterfaceCount
networkInterfaceCount} -> Maybe NetworkInterfaceCount
networkInterfaceCount) (\s :: InstanceRequirements
s@InstanceRequirements' {} Maybe NetworkInterfaceCount
a -> InstanceRequirements
s {$sel:networkInterfaceCount:InstanceRequirements' :: Maybe NetworkInterfaceCount
networkInterfaceCount = Maybe NetworkInterfaceCount
a} :: InstanceRequirements)

-- | The price protection threshold for On-Demand Instances. This is the
-- maximum you’ll pay for an On-Demand Instance, expressed as a percentage
-- above the least expensive current generation M, C, or R instance type
-- with your specified attributes. When Amazon EC2 selects instance types
-- with your attributes, it excludes instance types priced above your
-- threshold.
--
-- The parameter accepts an integer, which Amazon EC2 interprets as a
-- percentage.
--
-- To turn off price protection, specify a high value, such as @999999@.
--
-- This parameter is not supported for
-- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_GetSpotPlacementScores.html GetSpotPlacementScores>
-- and
-- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_GetInstanceTypesFromInstanceRequirements.html GetInstanceTypesFromInstanceRequirements>.
--
-- If you set @TargetCapacityUnitType@ to @vcpu@ or @memory-mib@, the price
-- protection threshold is applied based on the per-vCPU or per-memory
-- price instead of the per-instance price.
--
-- Default: @20@
instanceRequirements_onDemandMaxPricePercentageOverLowestPrice :: Lens.Lens' InstanceRequirements (Prelude.Maybe Prelude.Int)
instanceRequirements_onDemandMaxPricePercentageOverLowestPrice :: Lens' InstanceRequirements (Maybe Int)
instanceRequirements_onDemandMaxPricePercentageOverLowestPrice = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceRequirements' {Maybe Int
onDemandMaxPricePercentageOverLowestPrice :: Maybe Int
$sel:onDemandMaxPricePercentageOverLowestPrice:InstanceRequirements' :: InstanceRequirements -> Maybe Int
onDemandMaxPricePercentageOverLowestPrice} -> Maybe Int
onDemandMaxPricePercentageOverLowestPrice) (\s :: InstanceRequirements
s@InstanceRequirements' {} Maybe Int
a -> InstanceRequirements
s {$sel:onDemandMaxPricePercentageOverLowestPrice:InstanceRequirements' :: Maybe Int
onDemandMaxPricePercentageOverLowestPrice = Maybe Int
a} :: InstanceRequirements)

-- | Indicates whether instance types must support hibernation for On-Demand
-- Instances.
--
-- This parameter is not supported for
-- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_GetSpotPlacementScores.html GetSpotPlacementScores>.
--
-- Default: @false@
instanceRequirements_requireHibernateSupport :: Lens.Lens' InstanceRequirements (Prelude.Maybe Prelude.Bool)
instanceRequirements_requireHibernateSupport :: Lens' InstanceRequirements (Maybe Bool)
instanceRequirements_requireHibernateSupport = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceRequirements' {Maybe Bool
requireHibernateSupport :: Maybe Bool
$sel:requireHibernateSupport:InstanceRequirements' :: InstanceRequirements -> Maybe Bool
requireHibernateSupport} -> Maybe Bool
requireHibernateSupport) (\s :: InstanceRequirements
s@InstanceRequirements' {} Maybe Bool
a -> InstanceRequirements
s {$sel:requireHibernateSupport:InstanceRequirements' :: Maybe Bool
requireHibernateSupport = Maybe Bool
a} :: InstanceRequirements)

-- | The price protection threshold for Spot Instances. This is the maximum
-- you’ll pay for a Spot Instance, expressed as a percentage above the
-- least expensive current generation M, C, or R instance type with your
-- specified attributes. When Amazon EC2 selects instance types with your
-- attributes, it excludes instance types priced above your threshold.
--
-- The parameter accepts an integer, which Amazon EC2 interprets as a
-- percentage.
--
-- To turn off price protection, specify a high value, such as @999999@.
--
-- This parameter is not supported for
-- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_GetSpotPlacementScores.html GetSpotPlacementScores>
-- and
-- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_GetInstanceTypesFromInstanceRequirements.html GetInstanceTypesFromInstanceRequirements>.
--
-- If you set @TargetCapacityUnitType@ to @vcpu@ or @memory-mib@, the price
-- protection threshold is applied based on the per-vCPU or per-memory
-- price instead of the per-instance price.
--
-- Default: @100@
instanceRequirements_spotMaxPricePercentageOverLowestPrice :: Lens.Lens' InstanceRequirements (Prelude.Maybe Prelude.Int)
instanceRequirements_spotMaxPricePercentageOverLowestPrice :: Lens' InstanceRequirements (Maybe Int)
instanceRequirements_spotMaxPricePercentageOverLowestPrice = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceRequirements' {Maybe Int
spotMaxPricePercentageOverLowestPrice :: Maybe Int
$sel:spotMaxPricePercentageOverLowestPrice:InstanceRequirements' :: InstanceRequirements -> Maybe Int
spotMaxPricePercentageOverLowestPrice} -> Maybe Int
spotMaxPricePercentageOverLowestPrice) (\s :: InstanceRequirements
s@InstanceRequirements' {} Maybe Int
a -> InstanceRequirements
s {$sel:spotMaxPricePercentageOverLowestPrice:InstanceRequirements' :: Maybe Int
spotMaxPricePercentageOverLowestPrice = Maybe Int
a} :: InstanceRequirements)

-- | The minimum and maximum amount of total local storage, in GB.
--
-- Default: No minimum or maximum limits
instanceRequirements_totalLocalStorageGB :: Lens.Lens' InstanceRequirements (Prelude.Maybe TotalLocalStorageGB)
instanceRequirements_totalLocalStorageGB :: Lens' InstanceRequirements (Maybe TotalLocalStorageGB)
instanceRequirements_totalLocalStorageGB = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceRequirements' {Maybe TotalLocalStorageGB
totalLocalStorageGB :: Maybe TotalLocalStorageGB
$sel:totalLocalStorageGB:InstanceRequirements' :: InstanceRequirements -> Maybe TotalLocalStorageGB
totalLocalStorageGB} -> Maybe TotalLocalStorageGB
totalLocalStorageGB) (\s :: InstanceRequirements
s@InstanceRequirements' {} Maybe TotalLocalStorageGB
a -> InstanceRequirements
s {$sel:totalLocalStorageGB:InstanceRequirements' :: Maybe TotalLocalStorageGB
totalLocalStorageGB = Maybe TotalLocalStorageGB
a} :: InstanceRequirements)

-- | The minimum and maximum number of vCPUs.
instanceRequirements_vCpuCount :: Lens.Lens' InstanceRequirements (Prelude.Maybe VCpuCountRange)
instanceRequirements_vCpuCount :: Lens' InstanceRequirements (Maybe VCpuCountRange)
instanceRequirements_vCpuCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceRequirements' {Maybe VCpuCountRange
vCpuCount :: Maybe VCpuCountRange
$sel:vCpuCount:InstanceRequirements' :: InstanceRequirements -> Maybe VCpuCountRange
vCpuCount} -> Maybe VCpuCountRange
vCpuCount) (\s :: InstanceRequirements
s@InstanceRequirements' {} Maybe VCpuCountRange
a -> InstanceRequirements
s {$sel:vCpuCount:InstanceRequirements' :: Maybe VCpuCountRange
vCpuCount = Maybe VCpuCountRange
a} :: InstanceRequirements)

instance Data.FromXML InstanceRequirements where
  parseXML :: [Node] -> Either String InstanceRequirements
parseXML [Node]
x =
    Maybe AcceleratorCount
-> Maybe [AcceleratorManufacturer]
-> Maybe [AcceleratorName]
-> Maybe AcceleratorTotalMemoryMiB
-> Maybe [AcceleratorType]
-> Maybe [Text]
-> Maybe BareMetal
-> Maybe BaselineEbsBandwidthMbps
-> Maybe BurstablePerformance
-> Maybe [CpuManufacturer]
-> Maybe [Text]
-> Maybe [InstanceGeneration]
-> Maybe LocalStorage
-> Maybe [LocalStorageType]
-> Maybe MemoryGiBPerVCpu
-> Maybe MemoryMiB
-> Maybe NetworkBandwidthGbps
-> Maybe NetworkInterfaceCount
-> Maybe Int
-> Maybe Bool
-> Maybe Int
-> Maybe TotalLocalStorageGB
-> Maybe VCpuCountRange
-> InstanceRequirements
InstanceRequirements'
      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
"acceleratorCount")
      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
"acceleratorManufacturerSet"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"item")
                  )
      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
"acceleratorNameSet"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"item")
                  )
      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
"acceleratorTotalMemoryMiB")
      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
"acceleratorTypeSet"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"item")
                  )
      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
"allowedInstanceTypeSet"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"item")
                  )
      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
"bareMetal")
      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
"baselineEbsBandwidthMbps")
      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
"burstablePerformance")
      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
"cpuManufacturerSet"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"item")
                  )
      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
"excludedInstanceTypeSet"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"item")
                  )
      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
"instanceGenerationSet"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"item")
                  )
      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
"localStorage")
      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
"localStorageTypeSet"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"item")
                  )
      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
"memoryGiBPerVCpu")
      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
"memoryMiB")
      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
"networkBandwidthGbps")
      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
"networkInterfaceCount")
      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
"onDemandMaxPricePercentageOverLowestPrice"
                  )
      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
"requireHibernateSupport")
      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
"spotMaxPricePercentageOverLowestPrice")
      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
"totalLocalStorageGB")
      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
"vCpuCount")

instance Prelude.Hashable InstanceRequirements where
  hashWithSalt :: Int -> InstanceRequirements -> Int
hashWithSalt Int
_salt InstanceRequirements' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe [AcceleratorManufacturer]
Maybe [AcceleratorName]
Maybe [AcceleratorType]
Maybe [CpuManufacturer]
Maybe [InstanceGeneration]
Maybe [LocalStorageType]
Maybe AcceleratorCount
Maybe AcceleratorTotalMemoryMiB
Maybe BareMetal
Maybe BaselineEbsBandwidthMbps
Maybe BurstablePerformance
Maybe LocalStorage
Maybe MemoryGiBPerVCpu
Maybe MemoryMiB
Maybe NetworkBandwidthGbps
Maybe NetworkInterfaceCount
Maybe TotalLocalStorageGB
Maybe VCpuCountRange
vCpuCount :: Maybe VCpuCountRange
totalLocalStorageGB :: Maybe TotalLocalStorageGB
spotMaxPricePercentageOverLowestPrice :: Maybe Int
requireHibernateSupport :: Maybe Bool
onDemandMaxPricePercentageOverLowestPrice :: Maybe Int
networkInterfaceCount :: Maybe NetworkInterfaceCount
networkBandwidthGbps :: Maybe NetworkBandwidthGbps
memoryMiB :: Maybe MemoryMiB
memoryGiBPerVCpu :: Maybe MemoryGiBPerVCpu
localStorageTypes :: Maybe [LocalStorageType]
localStorage :: Maybe LocalStorage
instanceGenerations :: Maybe [InstanceGeneration]
excludedInstanceTypes :: Maybe [Text]
cpuManufacturers :: Maybe [CpuManufacturer]
burstablePerformance :: Maybe BurstablePerformance
baselineEbsBandwidthMbps :: Maybe BaselineEbsBandwidthMbps
bareMetal :: Maybe BareMetal
allowedInstanceTypes :: Maybe [Text]
acceleratorTypes :: Maybe [AcceleratorType]
acceleratorTotalMemoryMiB :: Maybe AcceleratorTotalMemoryMiB
acceleratorNames :: Maybe [AcceleratorName]
acceleratorManufacturers :: Maybe [AcceleratorManufacturer]
acceleratorCount :: Maybe AcceleratorCount
$sel:vCpuCount:InstanceRequirements' :: InstanceRequirements -> Maybe VCpuCountRange
$sel:totalLocalStorageGB:InstanceRequirements' :: InstanceRequirements -> Maybe TotalLocalStorageGB
$sel:spotMaxPricePercentageOverLowestPrice:InstanceRequirements' :: InstanceRequirements -> Maybe Int
$sel:requireHibernateSupport:InstanceRequirements' :: InstanceRequirements -> Maybe Bool
$sel:onDemandMaxPricePercentageOverLowestPrice:InstanceRequirements' :: InstanceRequirements -> Maybe Int
$sel:networkInterfaceCount:InstanceRequirements' :: InstanceRequirements -> Maybe NetworkInterfaceCount
$sel:networkBandwidthGbps:InstanceRequirements' :: InstanceRequirements -> Maybe NetworkBandwidthGbps
$sel:memoryMiB:InstanceRequirements' :: InstanceRequirements -> Maybe MemoryMiB
$sel:memoryGiBPerVCpu:InstanceRequirements' :: InstanceRequirements -> Maybe MemoryGiBPerVCpu
$sel:localStorageTypes:InstanceRequirements' :: InstanceRequirements -> Maybe [LocalStorageType]
$sel:localStorage:InstanceRequirements' :: InstanceRequirements -> Maybe LocalStorage
$sel:instanceGenerations:InstanceRequirements' :: InstanceRequirements -> Maybe [InstanceGeneration]
$sel:excludedInstanceTypes:InstanceRequirements' :: InstanceRequirements -> Maybe [Text]
$sel:cpuManufacturers:InstanceRequirements' :: InstanceRequirements -> Maybe [CpuManufacturer]
$sel:burstablePerformance:InstanceRequirements' :: InstanceRequirements -> Maybe BurstablePerformance
$sel:baselineEbsBandwidthMbps:InstanceRequirements' :: InstanceRequirements -> Maybe BaselineEbsBandwidthMbps
$sel:bareMetal:InstanceRequirements' :: InstanceRequirements -> Maybe BareMetal
$sel:allowedInstanceTypes:InstanceRequirements' :: InstanceRequirements -> Maybe [Text]
$sel:acceleratorTypes:InstanceRequirements' :: InstanceRequirements -> Maybe [AcceleratorType]
$sel:acceleratorTotalMemoryMiB:InstanceRequirements' :: InstanceRequirements -> Maybe AcceleratorTotalMemoryMiB
$sel:acceleratorNames:InstanceRequirements' :: InstanceRequirements -> Maybe [AcceleratorName]
$sel:acceleratorManufacturers:InstanceRequirements' :: InstanceRequirements -> Maybe [AcceleratorManufacturer]
$sel:acceleratorCount:InstanceRequirements' :: InstanceRequirements -> Maybe AcceleratorCount
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AcceleratorCount
acceleratorCount
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [AcceleratorManufacturer]
acceleratorManufacturers
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [AcceleratorName]
acceleratorNames
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AcceleratorTotalMemoryMiB
acceleratorTotalMemoryMiB
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [AcceleratorType]
acceleratorTypes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
allowedInstanceTypes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe BareMetal
bareMetal
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe BaselineEbsBandwidthMbps
baselineEbsBandwidthMbps
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe BurstablePerformance
burstablePerformance
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [CpuManufacturer]
cpuManufacturers
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
excludedInstanceTypes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [InstanceGeneration]
instanceGenerations
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LocalStorage
localStorage
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [LocalStorageType]
localStorageTypes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MemoryGiBPerVCpu
memoryGiBPerVCpu
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MemoryMiB
memoryMiB
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe NetworkBandwidthGbps
networkBandwidthGbps
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe NetworkInterfaceCount
networkInterfaceCount
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
onDemandMaxPricePercentageOverLowestPrice
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
requireHibernateSupport
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
spotMaxPricePercentageOverLowestPrice
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TotalLocalStorageGB
totalLocalStorageGB
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe VCpuCountRange
vCpuCount

instance Prelude.NFData InstanceRequirements where
  rnf :: InstanceRequirements -> ()
rnf InstanceRequirements' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe [AcceleratorManufacturer]
Maybe [AcceleratorName]
Maybe [AcceleratorType]
Maybe [CpuManufacturer]
Maybe [InstanceGeneration]
Maybe [LocalStorageType]
Maybe AcceleratorCount
Maybe AcceleratorTotalMemoryMiB
Maybe BareMetal
Maybe BaselineEbsBandwidthMbps
Maybe BurstablePerformance
Maybe LocalStorage
Maybe MemoryGiBPerVCpu
Maybe MemoryMiB
Maybe NetworkBandwidthGbps
Maybe NetworkInterfaceCount
Maybe TotalLocalStorageGB
Maybe VCpuCountRange
vCpuCount :: Maybe VCpuCountRange
totalLocalStorageGB :: Maybe TotalLocalStorageGB
spotMaxPricePercentageOverLowestPrice :: Maybe Int
requireHibernateSupport :: Maybe Bool
onDemandMaxPricePercentageOverLowestPrice :: Maybe Int
networkInterfaceCount :: Maybe NetworkInterfaceCount
networkBandwidthGbps :: Maybe NetworkBandwidthGbps
memoryMiB :: Maybe MemoryMiB
memoryGiBPerVCpu :: Maybe MemoryGiBPerVCpu
localStorageTypes :: Maybe [LocalStorageType]
localStorage :: Maybe LocalStorage
instanceGenerations :: Maybe [InstanceGeneration]
excludedInstanceTypes :: Maybe [Text]
cpuManufacturers :: Maybe [CpuManufacturer]
burstablePerformance :: Maybe BurstablePerformance
baselineEbsBandwidthMbps :: Maybe BaselineEbsBandwidthMbps
bareMetal :: Maybe BareMetal
allowedInstanceTypes :: Maybe [Text]
acceleratorTypes :: Maybe [AcceleratorType]
acceleratorTotalMemoryMiB :: Maybe AcceleratorTotalMemoryMiB
acceleratorNames :: Maybe [AcceleratorName]
acceleratorManufacturers :: Maybe [AcceleratorManufacturer]
acceleratorCount :: Maybe AcceleratorCount
$sel:vCpuCount:InstanceRequirements' :: InstanceRequirements -> Maybe VCpuCountRange
$sel:totalLocalStorageGB:InstanceRequirements' :: InstanceRequirements -> Maybe TotalLocalStorageGB
$sel:spotMaxPricePercentageOverLowestPrice:InstanceRequirements' :: InstanceRequirements -> Maybe Int
$sel:requireHibernateSupport:InstanceRequirements' :: InstanceRequirements -> Maybe Bool
$sel:onDemandMaxPricePercentageOverLowestPrice:InstanceRequirements' :: InstanceRequirements -> Maybe Int
$sel:networkInterfaceCount:InstanceRequirements' :: InstanceRequirements -> Maybe NetworkInterfaceCount
$sel:networkBandwidthGbps:InstanceRequirements' :: InstanceRequirements -> Maybe NetworkBandwidthGbps
$sel:memoryMiB:InstanceRequirements' :: InstanceRequirements -> Maybe MemoryMiB
$sel:memoryGiBPerVCpu:InstanceRequirements' :: InstanceRequirements -> Maybe MemoryGiBPerVCpu
$sel:localStorageTypes:InstanceRequirements' :: InstanceRequirements -> Maybe [LocalStorageType]
$sel:localStorage:InstanceRequirements' :: InstanceRequirements -> Maybe LocalStorage
$sel:instanceGenerations:InstanceRequirements' :: InstanceRequirements -> Maybe [InstanceGeneration]
$sel:excludedInstanceTypes:InstanceRequirements' :: InstanceRequirements -> Maybe [Text]
$sel:cpuManufacturers:InstanceRequirements' :: InstanceRequirements -> Maybe [CpuManufacturer]
$sel:burstablePerformance:InstanceRequirements' :: InstanceRequirements -> Maybe BurstablePerformance
$sel:baselineEbsBandwidthMbps:InstanceRequirements' :: InstanceRequirements -> Maybe BaselineEbsBandwidthMbps
$sel:bareMetal:InstanceRequirements' :: InstanceRequirements -> Maybe BareMetal
$sel:allowedInstanceTypes:InstanceRequirements' :: InstanceRequirements -> Maybe [Text]
$sel:acceleratorTypes:InstanceRequirements' :: InstanceRequirements -> Maybe [AcceleratorType]
$sel:acceleratorTotalMemoryMiB:InstanceRequirements' :: InstanceRequirements -> Maybe AcceleratorTotalMemoryMiB
$sel:acceleratorNames:InstanceRequirements' :: InstanceRequirements -> Maybe [AcceleratorName]
$sel:acceleratorManufacturers:InstanceRequirements' :: InstanceRequirements -> Maybe [AcceleratorManufacturer]
$sel:acceleratorCount:InstanceRequirements' :: InstanceRequirements -> Maybe AcceleratorCount
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AcceleratorCount
acceleratorCount
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [AcceleratorManufacturer]
acceleratorManufacturers
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [AcceleratorName]
acceleratorNames
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AcceleratorTotalMemoryMiB
acceleratorTotalMemoryMiB
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [AcceleratorType]
acceleratorTypes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
allowedInstanceTypes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe BareMetal
bareMetal
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe BaselineEbsBandwidthMbps
baselineEbsBandwidthMbps
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe BurstablePerformance
burstablePerformance
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [CpuManufacturer]
cpuManufacturers
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
excludedInstanceTypes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [InstanceGeneration]
instanceGenerations
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LocalStorage
localStorage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [LocalStorageType]
localStorageTypes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MemoryGiBPerVCpu
memoryGiBPerVCpu
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MemoryMiB
memoryMiB
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe NetworkBandwidthGbps
networkBandwidthGbps
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe NetworkInterfaceCount
networkInterfaceCount
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Int
onDemandMaxPricePercentageOverLowestPrice
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Bool
requireHibernateSupport
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Int
spotMaxPricePercentageOverLowestPrice
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe TotalLocalStorageGB
totalLocalStorageGB
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe VCpuCountRange
vCpuCount

instance Data.ToQuery InstanceRequirements where
  toQuery :: InstanceRequirements -> QueryString
toQuery InstanceRequirements' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe [AcceleratorManufacturer]
Maybe [AcceleratorName]
Maybe [AcceleratorType]
Maybe [CpuManufacturer]
Maybe [InstanceGeneration]
Maybe [LocalStorageType]
Maybe AcceleratorCount
Maybe AcceleratorTotalMemoryMiB
Maybe BareMetal
Maybe BaselineEbsBandwidthMbps
Maybe BurstablePerformance
Maybe LocalStorage
Maybe MemoryGiBPerVCpu
Maybe MemoryMiB
Maybe NetworkBandwidthGbps
Maybe NetworkInterfaceCount
Maybe TotalLocalStorageGB
Maybe VCpuCountRange
vCpuCount :: Maybe VCpuCountRange
totalLocalStorageGB :: Maybe TotalLocalStorageGB
spotMaxPricePercentageOverLowestPrice :: Maybe Int
requireHibernateSupport :: Maybe Bool
onDemandMaxPricePercentageOverLowestPrice :: Maybe Int
networkInterfaceCount :: Maybe NetworkInterfaceCount
networkBandwidthGbps :: Maybe NetworkBandwidthGbps
memoryMiB :: Maybe MemoryMiB
memoryGiBPerVCpu :: Maybe MemoryGiBPerVCpu
localStorageTypes :: Maybe [LocalStorageType]
localStorage :: Maybe LocalStorage
instanceGenerations :: Maybe [InstanceGeneration]
excludedInstanceTypes :: Maybe [Text]
cpuManufacturers :: Maybe [CpuManufacturer]
burstablePerformance :: Maybe BurstablePerformance
baselineEbsBandwidthMbps :: Maybe BaselineEbsBandwidthMbps
bareMetal :: Maybe BareMetal
allowedInstanceTypes :: Maybe [Text]
acceleratorTypes :: Maybe [AcceleratorType]
acceleratorTotalMemoryMiB :: Maybe AcceleratorTotalMemoryMiB
acceleratorNames :: Maybe [AcceleratorName]
acceleratorManufacturers :: Maybe [AcceleratorManufacturer]
acceleratorCount :: Maybe AcceleratorCount
$sel:vCpuCount:InstanceRequirements' :: InstanceRequirements -> Maybe VCpuCountRange
$sel:totalLocalStorageGB:InstanceRequirements' :: InstanceRequirements -> Maybe TotalLocalStorageGB
$sel:spotMaxPricePercentageOverLowestPrice:InstanceRequirements' :: InstanceRequirements -> Maybe Int
$sel:requireHibernateSupport:InstanceRequirements' :: InstanceRequirements -> Maybe Bool
$sel:onDemandMaxPricePercentageOverLowestPrice:InstanceRequirements' :: InstanceRequirements -> Maybe Int
$sel:networkInterfaceCount:InstanceRequirements' :: InstanceRequirements -> Maybe NetworkInterfaceCount
$sel:networkBandwidthGbps:InstanceRequirements' :: InstanceRequirements -> Maybe NetworkBandwidthGbps
$sel:memoryMiB:InstanceRequirements' :: InstanceRequirements -> Maybe MemoryMiB
$sel:memoryGiBPerVCpu:InstanceRequirements' :: InstanceRequirements -> Maybe MemoryGiBPerVCpu
$sel:localStorageTypes:InstanceRequirements' :: InstanceRequirements -> Maybe [LocalStorageType]
$sel:localStorage:InstanceRequirements' :: InstanceRequirements -> Maybe LocalStorage
$sel:instanceGenerations:InstanceRequirements' :: InstanceRequirements -> Maybe [InstanceGeneration]
$sel:excludedInstanceTypes:InstanceRequirements' :: InstanceRequirements -> Maybe [Text]
$sel:cpuManufacturers:InstanceRequirements' :: InstanceRequirements -> Maybe [CpuManufacturer]
$sel:burstablePerformance:InstanceRequirements' :: InstanceRequirements -> Maybe BurstablePerformance
$sel:baselineEbsBandwidthMbps:InstanceRequirements' :: InstanceRequirements -> Maybe BaselineEbsBandwidthMbps
$sel:bareMetal:InstanceRequirements' :: InstanceRequirements -> Maybe BareMetal
$sel:allowedInstanceTypes:InstanceRequirements' :: InstanceRequirements -> Maybe [Text]
$sel:acceleratorTypes:InstanceRequirements' :: InstanceRequirements -> Maybe [AcceleratorType]
$sel:acceleratorTotalMemoryMiB:InstanceRequirements' :: InstanceRequirements -> Maybe AcceleratorTotalMemoryMiB
$sel:acceleratorNames:InstanceRequirements' :: InstanceRequirements -> Maybe [AcceleratorName]
$sel:acceleratorManufacturers:InstanceRequirements' :: InstanceRequirements -> Maybe [AcceleratorManufacturer]
$sel:acceleratorCount:InstanceRequirements' :: InstanceRequirements -> Maybe AcceleratorCount
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"AcceleratorCount" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe AcceleratorCount
acceleratorCount,
        forall a. ToQuery a => a -> QueryString
Data.toQuery
          ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"AcceleratorManufacturerSet"
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [AcceleratorManufacturer]
acceleratorManufacturers
          ),
        forall a. ToQuery a => a -> QueryString
Data.toQuery
          ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"AcceleratorNameSet"
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [AcceleratorName]
acceleratorNames
          ),
        ByteString
"AcceleratorTotalMemoryMiB"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe AcceleratorTotalMemoryMiB
acceleratorTotalMemoryMiB,
        forall a. ToQuery a => a -> QueryString
Data.toQuery
          ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"AcceleratorTypeSet"
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [AcceleratorType]
acceleratorTypes
          ),
        forall a. ToQuery a => a -> QueryString
Data.toQuery
          ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"AllowedInstanceTypeSet"
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
allowedInstanceTypes
          ),
        ByteString
"BareMetal" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe BareMetal
bareMetal,
        ByteString
"BaselineEbsBandwidthMbps"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe BaselineEbsBandwidthMbps
baselineEbsBandwidthMbps,
        ByteString
"BurstablePerformance" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe BurstablePerformance
burstablePerformance,
        forall a. ToQuery a => a -> QueryString
Data.toQuery
          ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"CpuManufacturerSet"
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [CpuManufacturer]
cpuManufacturers
          ),
        forall a. ToQuery a => a -> QueryString
Data.toQuery
          ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"ExcludedInstanceTypeSet"
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
excludedInstanceTypes
          ),
        forall a. ToQuery a => a -> QueryString
Data.toQuery
          ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"InstanceGenerationSet"
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [InstanceGeneration]
instanceGenerations
          ),
        ByteString
"LocalStorage" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe LocalStorage
localStorage,
        forall a. ToQuery a => a -> QueryString
Data.toQuery
          ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"LocalStorageTypeSet"
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [LocalStorageType]
localStorageTypes
          ),
        ByteString
"MemoryGiBPerVCpu" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe MemoryGiBPerVCpu
memoryGiBPerVCpu,
        ByteString
"MemoryMiB" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe MemoryMiB
memoryMiB,
        ByteString
"NetworkBandwidthGbps" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe NetworkBandwidthGbps
networkBandwidthGbps,
        ByteString
"NetworkInterfaceCount"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe NetworkInterfaceCount
networkInterfaceCount,
        ByteString
"OnDemandMaxPricePercentageOverLowestPrice"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
onDemandMaxPricePercentageOverLowestPrice,
        ByteString
"RequireHibernateSupport"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
requireHibernateSupport,
        ByteString
"SpotMaxPricePercentageOverLowestPrice"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
spotMaxPricePercentageOverLowestPrice,
        ByteString
"TotalLocalStorageGB" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe TotalLocalStorageGB
totalLocalStorageGB,
        ByteString
"VCpuCount" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe VCpuCountRange
vCpuCount
      ]