{-# 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 #-}
module Amazonka.EC2.Types.SpotFleetLaunchSpecification 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.BlockDeviceMapping
import Amazonka.EC2.Types.GroupIdentifier
import Amazonka.EC2.Types.IamInstanceProfileSpecification
import Amazonka.EC2.Types.InstanceNetworkInterfaceSpecification
import Amazonka.EC2.Types.InstanceRequirements
import Amazonka.EC2.Types.InstanceType
import Amazonka.EC2.Types.SpotFleetMonitoring
import Amazonka.EC2.Types.SpotFleetTagSpecification
import Amazonka.EC2.Types.SpotPlacement
import qualified Amazonka.Prelude as Prelude
data SpotFleetLaunchSpecification = SpotFleetLaunchSpecification'
{
SpotFleetLaunchSpecification -> Maybe Text
addressingType :: Prelude.Maybe Prelude.Text,
SpotFleetLaunchSpecification -> Maybe [BlockDeviceMapping]
blockDeviceMappings :: Prelude.Maybe [BlockDeviceMapping],
SpotFleetLaunchSpecification -> Maybe Bool
ebsOptimized :: Prelude.Maybe Prelude.Bool,
SpotFleetLaunchSpecification
-> Maybe IamInstanceProfileSpecification
iamInstanceProfile :: Prelude.Maybe IamInstanceProfileSpecification,
SpotFleetLaunchSpecification -> Maybe Text
imageId :: Prelude.Maybe Prelude.Text,
SpotFleetLaunchSpecification -> Maybe InstanceRequirements
instanceRequirements :: Prelude.Maybe InstanceRequirements,
SpotFleetLaunchSpecification -> Maybe InstanceType
instanceType :: Prelude.Maybe InstanceType,
SpotFleetLaunchSpecification -> Maybe Text
kernelId :: Prelude.Maybe Prelude.Text,
SpotFleetLaunchSpecification -> Maybe Text
keyName :: Prelude.Maybe Prelude.Text,
SpotFleetLaunchSpecification -> Maybe SpotFleetMonitoring
monitoring :: Prelude.Maybe SpotFleetMonitoring,
SpotFleetLaunchSpecification
-> Maybe [InstanceNetworkInterfaceSpecification]
networkInterfaces :: Prelude.Maybe [InstanceNetworkInterfaceSpecification],
SpotFleetLaunchSpecification -> Maybe SpotPlacement
placement :: Prelude.Maybe SpotPlacement,
SpotFleetLaunchSpecification -> Maybe Text
ramdiskId :: Prelude.Maybe Prelude.Text,
SpotFleetLaunchSpecification -> Maybe [GroupIdentifier]
securityGroups :: Prelude.Maybe [GroupIdentifier],
SpotFleetLaunchSpecification -> Maybe Text
spotPrice :: Prelude.Maybe Prelude.Text,
SpotFleetLaunchSpecification -> Maybe Text
subnetId :: Prelude.Maybe Prelude.Text,
SpotFleetLaunchSpecification -> Maybe [SpotFleetTagSpecification]
tagSpecifications :: Prelude.Maybe [SpotFleetTagSpecification],
SpotFleetLaunchSpecification -> Maybe Text
userData :: Prelude.Maybe Prelude.Text,
SpotFleetLaunchSpecification -> Maybe Double
weightedCapacity :: Prelude.Maybe Prelude.Double
}
deriving (SpotFleetLaunchSpecification
-> SpotFleetLaunchSpecification -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SpotFleetLaunchSpecification
-> SpotFleetLaunchSpecification -> Bool
$c/= :: SpotFleetLaunchSpecification
-> SpotFleetLaunchSpecification -> Bool
== :: SpotFleetLaunchSpecification
-> SpotFleetLaunchSpecification -> Bool
$c== :: SpotFleetLaunchSpecification
-> SpotFleetLaunchSpecification -> Bool
Prelude.Eq, ReadPrec [SpotFleetLaunchSpecification]
ReadPrec SpotFleetLaunchSpecification
Int -> ReadS SpotFleetLaunchSpecification
ReadS [SpotFleetLaunchSpecification]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SpotFleetLaunchSpecification]
$creadListPrec :: ReadPrec [SpotFleetLaunchSpecification]
readPrec :: ReadPrec SpotFleetLaunchSpecification
$creadPrec :: ReadPrec SpotFleetLaunchSpecification
readList :: ReadS [SpotFleetLaunchSpecification]
$creadList :: ReadS [SpotFleetLaunchSpecification]
readsPrec :: Int -> ReadS SpotFleetLaunchSpecification
$creadsPrec :: Int -> ReadS SpotFleetLaunchSpecification
Prelude.Read, Int -> SpotFleetLaunchSpecification -> ShowS
[SpotFleetLaunchSpecification] -> ShowS
SpotFleetLaunchSpecification -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SpotFleetLaunchSpecification] -> ShowS
$cshowList :: [SpotFleetLaunchSpecification] -> ShowS
show :: SpotFleetLaunchSpecification -> String
$cshow :: SpotFleetLaunchSpecification -> String
showsPrec :: Int -> SpotFleetLaunchSpecification -> ShowS
$cshowsPrec :: Int -> SpotFleetLaunchSpecification -> ShowS
Prelude.Show, forall x.
Rep SpotFleetLaunchSpecification x -> SpotFleetLaunchSpecification
forall x.
SpotFleetLaunchSpecification -> Rep SpotFleetLaunchSpecification x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SpotFleetLaunchSpecification x -> SpotFleetLaunchSpecification
$cfrom :: forall x.
SpotFleetLaunchSpecification -> Rep SpotFleetLaunchSpecification x
Prelude.Generic)
newSpotFleetLaunchSpecification ::
SpotFleetLaunchSpecification
newSpotFleetLaunchSpecification :: SpotFleetLaunchSpecification
newSpotFleetLaunchSpecification =
SpotFleetLaunchSpecification'
{ $sel:addressingType:SpotFleetLaunchSpecification' :: Maybe Text
addressingType =
forall a. Maybe a
Prelude.Nothing,
$sel:blockDeviceMappings:SpotFleetLaunchSpecification' :: Maybe [BlockDeviceMapping]
blockDeviceMappings = forall a. Maybe a
Prelude.Nothing,
$sel:ebsOptimized:SpotFleetLaunchSpecification' :: Maybe Bool
ebsOptimized = forall a. Maybe a
Prelude.Nothing,
$sel:iamInstanceProfile:SpotFleetLaunchSpecification' :: Maybe IamInstanceProfileSpecification
iamInstanceProfile = forall a. Maybe a
Prelude.Nothing,
$sel:imageId:SpotFleetLaunchSpecification' :: Maybe Text
imageId = forall a. Maybe a
Prelude.Nothing,
$sel:instanceRequirements:SpotFleetLaunchSpecification' :: Maybe InstanceRequirements
instanceRequirements = forall a. Maybe a
Prelude.Nothing,
$sel:instanceType:SpotFleetLaunchSpecification' :: Maybe InstanceType
instanceType = forall a. Maybe a
Prelude.Nothing,
$sel:kernelId:SpotFleetLaunchSpecification' :: Maybe Text
kernelId = forall a. Maybe a
Prelude.Nothing,
$sel:keyName:SpotFleetLaunchSpecification' :: Maybe Text
keyName = forall a. Maybe a
Prelude.Nothing,
$sel:monitoring:SpotFleetLaunchSpecification' :: Maybe SpotFleetMonitoring
monitoring = forall a. Maybe a
Prelude.Nothing,
$sel:networkInterfaces:SpotFleetLaunchSpecification' :: Maybe [InstanceNetworkInterfaceSpecification]
networkInterfaces = forall a. Maybe a
Prelude.Nothing,
$sel:placement:SpotFleetLaunchSpecification' :: Maybe SpotPlacement
placement = forall a. Maybe a
Prelude.Nothing,
$sel:ramdiskId:SpotFleetLaunchSpecification' :: Maybe Text
ramdiskId = forall a. Maybe a
Prelude.Nothing,
$sel:securityGroups:SpotFleetLaunchSpecification' :: Maybe [GroupIdentifier]
securityGroups = forall a. Maybe a
Prelude.Nothing,
$sel:spotPrice:SpotFleetLaunchSpecification' :: Maybe Text
spotPrice = forall a. Maybe a
Prelude.Nothing,
$sel:subnetId:SpotFleetLaunchSpecification' :: Maybe Text
subnetId = forall a. Maybe a
Prelude.Nothing,
$sel:tagSpecifications:SpotFleetLaunchSpecification' :: Maybe [SpotFleetTagSpecification]
tagSpecifications = forall a. Maybe a
Prelude.Nothing,
$sel:userData:SpotFleetLaunchSpecification' :: Maybe Text
userData = forall a. Maybe a
Prelude.Nothing,
$sel:weightedCapacity:SpotFleetLaunchSpecification' :: Maybe Double
weightedCapacity = forall a. Maybe a
Prelude.Nothing
}
spotFleetLaunchSpecification_addressingType :: Lens.Lens' SpotFleetLaunchSpecification (Prelude.Maybe Prelude.Text)
spotFleetLaunchSpecification_addressingType :: Lens' SpotFleetLaunchSpecification (Maybe Text)
spotFleetLaunchSpecification_addressingType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SpotFleetLaunchSpecification' {Maybe Text
addressingType :: Maybe Text
$sel:addressingType:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Text
addressingType} -> Maybe Text
addressingType) (\s :: SpotFleetLaunchSpecification
s@SpotFleetLaunchSpecification' {} Maybe Text
a -> SpotFleetLaunchSpecification
s {$sel:addressingType:SpotFleetLaunchSpecification' :: Maybe Text
addressingType = Maybe Text
a} :: SpotFleetLaunchSpecification)
spotFleetLaunchSpecification_blockDeviceMappings :: Lens.Lens' SpotFleetLaunchSpecification (Prelude.Maybe [BlockDeviceMapping])
spotFleetLaunchSpecification_blockDeviceMappings :: Lens' SpotFleetLaunchSpecification (Maybe [BlockDeviceMapping])
spotFleetLaunchSpecification_blockDeviceMappings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SpotFleetLaunchSpecification' {Maybe [BlockDeviceMapping]
blockDeviceMappings :: Maybe [BlockDeviceMapping]
$sel:blockDeviceMappings:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe [BlockDeviceMapping]
blockDeviceMappings} -> Maybe [BlockDeviceMapping]
blockDeviceMappings) (\s :: SpotFleetLaunchSpecification
s@SpotFleetLaunchSpecification' {} Maybe [BlockDeviceMapping]
a -> SpotFleetLaunchSpecification
s {$sel:blockDeviceMappings:SpotFleetLaunchSpecification' :: Maybe [BlockDeviceMapping]
blockDeviceMappings = Maybe [BlockDeviceMapping]
a} :: SpotFleetLaunchSpecification) 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
spotFleetLaunchSpecification_ebsOptimized :: Lens.Lens' SpotFleetLaunchSpecification (Prelude.Maybe Prelude.Bool)
spotFleetLaunchSpecification_ebsOptimized :: Lens' SpotFleetLaunchSpecification (Maybe Bool)
spotFleetLaunchSpecification_ebsOptimized = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SpotFleetLaunchSpecification' {Maybe Bool
ebsOptimized :: Maybe Bool
$sel:ebsOptimized:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Bool
ebsOptimized} -> Maybe Bool
ebsOptimized) (\s :: SpotFleetLaunchSpecification
s@SpotFleetLaunchSpecification' {} Maybe Bool
a -> SpotFleetLaunchSpecification
s {$sel:ebsOptimized:SpotFleetLaunchSpecification' :: Maybe Bool
ebsOptimized = Maybe Bool
a} :: SpotFleetLaunchSpecification)
spotFleetLaunchSpecification_iamInstanceProfile :: Lens.Lens' SpotFleetLaunchSpecification (Prelude.Maybe IamInstanceProfileSpecification)
spotFleetLaunchSpecification_iamInstanceProfile :: Lens'
SpotFleetLaunchSpecification
(Maybe IamInstanceProfileSpecification)
spotFleetLaunchSpecification_iamInstanceProfile = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SpotFleetLaunchSpecification' {Maybe IamInstanceProfileSpecification
iamInstanceProfile :: Maybe IamInstanceProfileSpecification
$sel:iamInstanceProfile:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification
-> Maybe IamInstanceProfileSpecification
iamInstanceProfile} -> Maybe IamInstanceProfileSpecification
iamInstanceProfile) (\s :: SpotFleetLaunchSpecification
s@SpotFleetLaunchSpecification' {} Maybe IamInstanceProfileSpecification
a -> SpotFleetLaunchSpecification
s {$sel:iamInstanceProfile:SpotFleetLaunchSpecification' :: Maybe IamInstanceProfileSpecification
iamInstanceProfile = Maybe IamInstanceProfileSpecification
a} :: SpotFleetLaunchSpecification)
spotFleetLaunchSpecification_imageId :: Lens.Lens' SpotFleetLaunchSpecification (Prelude.Maybe Prelude.Text)
spotFleetLaunchSpecification_imageId :: Lens' SpotFleetLaunchSpecification (Maybe Text)
spotFleetLaunchSpecification_imageId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SpotFleetLaunchSpecification' {Maybe Text
imageId :: Maybe Text
$sel:imageId:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Text
imageId} -> Maybe Text
imageId) (\s :: SpotFleetLaunchSpecification
s@SpotFleetLaunchSpecification' {} Maybe Text
a -> SpotFleetLaunchSpecification
s {$sel:imageId:SpotFleetLaunchSpecification' :: Maybe Text
imageId = Maybe Text
a} :: SpotFleetLaunchSpecification)
spotFleetLaunchSpecification_instanceRequirements :: Lens.Lens' SpotFleetLaunchSpecification (Prelude.Maybe InstanceRequirements)
spotFleetLaunchSpecification_instanceRequirements :: Lens' SpotFleetLaunchSpecification (Maybe InstanceRequirements)
spotFleetLaunchSpecification_instanceRequirements = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SpotFleetLaunchSpecification' {Maybe InstanceRequirements
instanceRequirements :: Maybe InstanceRequirements
$sel:instanceRequirements:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe InstanceRequirements
instanceRequirements} -> Maybe InstanceRequirements
instanceRequirements) (\s :: SpotFleetLaunchSpecification
s@SpotFleetLaunchSpecification' {} Maybe InstanceRequirements
a -> SpotFleetLaunchSpecification
s {$sel:instanceRequirements:SpotFleetLaunchSpecification' :: Maybe InstanceRequirements
instanceRequirements = Maybe InstanceRequirements
a} :: SpotFleetLaunchSpecification)
spotFleetLaunchSpecification_instanceType :: Lens.Lens' SpotFleetLaunchSpecification (Prelude.Maybe InstanceType)
spotFleetLaunchSpecification_instanceType :: Lens' SpotFleetLaunchSpecification (Maybe InstanceType)
spotFleetLaunchSpecification_instanceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SpotFleetLaunchSpecification' {Maybe InstanceType
instanceType :: Maybe InstanceType
$sel:instanceType:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe InstanceType
instanceType} -> Maybe InstanceType
instanceType) (\s :: SpotFleetLaunchSpecification
s@SpotFleetLaunchSpecification' {} Maybe InstanceType
a -> SpotFleetLaunchSpecification
s {$sel:instanceType:SpotFleetLaunchSpecification' :: Maybe InstanceType
instanceType = Maybe InstanceType
a} :: SpotFleetLaunchSpecification)
spotFleetLaunchSpecification_kernelId :: Lens.Lens' SpotFleetLaunchSpecification (Prelude.Maybe Prelude.Text)
spotFleetLaunchSpecification_kernelId :: Lens' SpotFleetLaunchSpecification (Maybe Text)
spotFleetLaunchSpecification_kernelId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SpotFleetLaunchSpecification' {Maybe Text
kernelId :: Maybe Text
$sel:kernelId:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Text
kernelId} -> Maybe Text
kernelId) (\s :: SpotFleetLaunchSpecification
s@SpotFleetLaunchSpecification' {} Maybe Text
a -> SpotFleetLaunchSpecification
s {$sel:kernelId:SpotFleetLaunchSpecification' :: Maybe Text
kernelId = Maybe Text
a} :: SpotFleetLaunchSpecification)
spotFleetLaunchSpecification_keyName :: Lens.Lens' SpotFleetLaunchSpecification (Prelude.Maybe Prelude.Text)
spotFleetLaunchSpecification_keyName :: Lens' SpotFleetLaunchSpecification (Maybe Text)
spotFleetLaunchSpecification_keyName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SpotFleetLaunchSpecification' {Maybe Text
keyName :: Maybe Text
$sel:keyName:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Text
keyName} -> Maybe Text
keyName) (\s :: SpotFleetLaunchSpecification
s@SpotFleetLaunchSpecification' {} Maybe Text
a -> SpotFleetLaunchSpecification
s {$sel:keyName:SpotFleetLaunchSpecification' :: Maybe Text
keyName = Maybe Text
a} :: SpotFleetLaunchSpecification)
spotFleetLaunchSpecification_monitoring :: Lens.Lens' SpotFleetLaunchSpecification (Prelude.Maybe SpotFleetMonitoring)
spotFleetLaunchSpecification_monitoring :: Lens' SpotFleetLaunchSpecification (Maybe SpotFleetMonitoring)
spotFleetLaunchSpecification_monitoring = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SpotFleetLaunchSpecification' {Maybe SpotFleetMonitoring
monitoring :: Maybe SpotFleetMonitoring
$sel:monitoring:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe SpotFleetMonitoring
monitoring} -> Maybe SpotFleetMonitoring
monitoring) (\s :: SpotFleetLaunchSpecification
s@SpotFleetLaunchSpecification' {} Maybe SpotFleetMonitoring
a -> SpotFleetLaunchSpecification
s {$sel:monitoring:SpotFleetLaunchSpecification' :: Maybe SpotFleetMonitoring
monitoring = Maybe SpotFleetMonitoring
a} :: SpotFleetLaunchSpecification)
spotFleetLaunchSpecification_networkInterfaces :: Lens.Lens' SpotFleetLaunchSpecification (Prelude.Maybe [InstanceNetworkInterfaceSpecification])
spotFleetLaunchSpecification_networkInterfaces :: Lens'
SpotFleetLaunchSpecification
(Maybe [InstanceNetworkInterfaceSpecification])
spotFleetLaunchSpecification_networkInterfaces = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SpotFleetLaunchSpecification' {Maybe [InstanceNetworkInterfaceSpecification]
networkInterfaces :: Maybe [InstanceNetworkInterfaceSpecification]
$sel:networkInterfaces:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification
-> Maybe [InstanceNetworkInterfaceSpecification]
networkInterfaces} -> Maybe [InstanceNetworkInterfaceSpecification]
networkInterfaces) (\s :: SpotFleetLaunchSpecification
s@SpotFleetLaunchSpecification' {} Maybe [InstanceNetworkInterfaceSpecification]
a -> SpotFleetLaunchSpecification
s {$sel:networkInterfaces:SpotFleetLaunchSpecification' :: Maybe [InstanceNetworkInterfaceSpecification]
networkInterfaces = Maybe [InstanceNetworkInterfaceSpecification]
a} :: SpotFleetLaunchSpecification) 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
spotFleetLaunchSpecification_placement :: Lens.Lens' SpotFleetLaunchSpecification (Prelude.Maybe SpotPlacement)
spotFleetLaunchSpecification_placement :: Lens' SpotFleetLaunchSpecification (Maybe SpotPlacement)
spotFleetLaunchSpecification_placement = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SpotFleetLaunchSpecification' {Maybe SpotPlacement
placement :: Maybe SpotPlacement
$sel:placement:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe SpotPlacement
placement} -> Maybe SpotPlacement
placement) (\s :: SpotFleetLaunchSpecification
s@SpotFleetLaunchSpecification' {} Maybe SpotPlacement
a -> SpotFleetLaunchSpecification
s {$sel:placement:SpotFleetLaunchSpecification' :: Maybe SpotPlacement
placement = Maybe SpotPlacement
a} :: SpotFleetLaunchSpecification)
spotFleetLaunchSpecification_ramdiskId :: Lens.Lens' SpotFleetLaunchSpecification (Prelude.Maybe Prelude.Text)
spotFleetLaunchSpecification_ramdiskId :: Lens' SpotFleetLaunchSpecification (Maybe Text)
spotFleetLaunchSpecification_ramdiskId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SpotFleetLaunchSpecification' {Maybe Text
ramdiskId :: Maybe Text
$sel:ramdiskId:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Text
ramdiskId} -> Maybe Text
ramdiskId) (\s :: SpotFleetLaunchSpecification
s@SpotFleetLaunchSpecification' {} Maybe Text
a -> SpotFleetLaunchSpecification
s {$sel:ramdiskId:SpotFleetLaunchSpecification' :: Maybe Text
ramdiskId = Maybe Text
a} :: SpotFleetLaunchSpecification)
spotFleetLaunchSpecification_securityGroups :: Lens.Lens' SpotFleetLaunchSpecification (Prelude.Maybe [GroupIdentifier])
spotFleetLaunchSpecification_securityGroups :: Lens' SpotFleetLaunchSpecification (Maybe [GroupIdentifier])
spotFleetLaunchSpecification_securityGroups = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SpotFleetLaunchSpecification' {Maybe [GroupIdentifier]
securityGroups :: Maybe [GroupIdentifier]
$sel:securityGroups:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe [GroupIdentifier]
securityGroups} -> Maybe [GroupIdentifier]
securityGroups) (\s :: SpotFleetLaunchSpecification
s@SpotFleetLaunchSpecification' {} Maybe [GroupIdentifier]
a -> SpotFleetLaunchSpecification
s {$sel:securityGroups:SpotFleetLaunchSpecification' :: Maybe [GroupIdentifier]
securityGroups = Maybe [GroupIdentifier]
a} :: SpotFleetLaunchSpecification) 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
spotFleetLaunchSpecification_spotPrice :: Lens.Lens' SpotFleetLaunchSpecification (Prelude.Maybe Prelude.Text)
spotFleetLaunchSpecification_spotPrice :: Lens' SpotFleetLaunchSpecification (Maybe Text)
spotFleetLaunchSpecification_spotPrice = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SpotFleetLaunchSpecification' {Maybe Text
spotPrice :: Maybe Text
$sel:spotPrice:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Text
spotPrice} -> Maybe Text
spotPrice) (\s :: SpotFleetLaunchSpecification
s@SpotFleetLaunchSpecification' {} Maybe Text
a -> SpotFleetLaunchSpecification
s {$sel:spotPrice:SpotFleetLaunchSpecification' :: Maybe Text
spotPrice = Maybe Text
a} :: SpotFleetLaunchSpecification)
spotFleetLaunchSpecification_subnetId :: Lens.Lens' SpotFleetLaunchSpecification (Prelude.Maybe Prelude.Text)
spotFleetLaunchSpecification_subnetId :: Lens' SpotFleetLaunchSpecification (Maybe Text)
spotFleetLaunchSpecification_subnetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SpotFleetLaunchSpecification' {Maybe Text
subnetId :: Maybe Text
$sel:subnetId:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Text
subnetId} -> Maybe Text
subnetId) (\s :: SpotFleetLaunchSpecification
s@SpotFleetLaunchSpecification' {} Maybe Text
a -> SpotFleetLaunchSpecification
s {$sel:subnetId:SpotFleetLaunchSpecification' :: Maybe Text
subnetId = Maybe Text
a} :: SpotFleetLaunchSpecification)
spotFleetLaunchSpecification_tagSpecifications :: Lens.Lens' SpotFleetLaunchSpecification (Prelude.Maybe [SpotFleetTagSpecification])
spotFleetLaunchSpecification_tagSpecifications :: Lens'
SpotFleetLaunchSpecification (Maybe [SpotFleetTagSpecification])
spotFleetLaunchSpecification_tagSpecifications = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SpotFleetLaunchSpecification' {Maybe [SpotFleetTagSpecification]
tagSpecifications :: Maybe [SpotFleetTagSpecification]
$sel:tagSpecifications:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe [SpotFleetTagSpecification]
tagSpecifications} -> Maybe [SpotFleetTagSpecification]
tagSpecifications) (\s :: SpotFleetLaunchSpecification
s@SpotFleetLaunchSpecification' {} Maybe [SpotFleetTagSpecification]
a -> SpotFleetLaunchSpecification
s {$sel:tagSpecifications:SpotFleetLaunchSpecification' :: Maybe [SpotFleetTagSpecification]
tagSpecifications = Maybe [SpotFleetTagSpecification]
a} :: SpotFleetLaunchSpecification) 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
spotFleetLaunchSpecification_userData :: Lens.Lens' SpotFleetLaunchSpecification (Prelude.Maybe Prelude.Text)
spotFleetLaunchSpecification_userData :: Lens' SpotFleetLaunchSpecification (Maybe Text)
spotFleetLaunchSpecification_userData = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SpotFleetLaunchSpecification' {Maybe Text
userData :: Maybe Text
$sel:userData:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Text
userData} -> Maybe Text
userData) (\s :: SpotFleetLaunchSpecification
s@SpotFleetLaunchSpecification' {} Maybe Text
a -> SpotFleetLaunchSpecification
s {$sel:userData:SpotFleetLaunchSpecification' :: Maybe Text
userData = Maybe Text
a} :: SpotFleetLaunchSpecification)
spotFleetLaunchSpecification_weightedCapacity :: Lens.Lens' SpotFleetLaunchSpecification (Prelude.Maybe Prelude.Double)
spotFleetLaunchSpecification_weightedCapacity :: Lens' SpotFleetLaunchSpecification (Maybe Double)
spotFleetLaunchSpecification_weightedCapacity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SpotFleetLaunchSpecification' {Maybe Double
weightedCapacity :: Maybe Double
$sel:weightedCapacity:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Double
weightedCapacity} -> Maybe Double
weightedCapacity) (\s :: SpotFleetLaunchSpecification
s@SpotFleetLaunchSpecification' {} Maybe Double
a -> SpotFleetLaunchSpecification
s {$sel:weightedCapacity:SpotFleetLaunchSpecification' :: Maybe Double
weightedCapacity = Maybe Double
a} :: SpotFleetLaunchSpecification)
instance Data.FromXML SpotFleetLaunchSpecification where
parseXML :: [Node] -> Either String SpotFleetLaunchSpecification
parseXML [Node]
x =
Maybe Text
-> Maybe [BlockDeviceMapping]
-> Maybe Bool
-> Maybe IamInstanceProfileSpecification
-> Maybe Text
-> Maybe InstanceRequirements
-> Maybe InstanceType
-> Maybe Text
-> Maybe Text
-> Maybe SpotFleetMonitoring
-> Maybe [InstanceNetworkInterfaceSpecification]
-> Maybe SpotPlacement
-> Maybe Text
-> Maybe [GroupIdentifier]
-> Maybe Text
-> Maybe Text
-> Maybe [SpotFleetTagSpecification]
-> Maybe Text
-> Maybe Double
-> SpotFleetLaunchSpecification
SpotFleetLaunchSpecification'
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
"addressingType")
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
"blockDeviceMapping"
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
"ebsOptimized")
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
"iamInstanceProfile")
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
"imageId")
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
"instanceRequirements")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"instanceType")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"kernelId")
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
"keyName")
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
"monitoring")
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
"networkInterfaceSet"
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
"placement")
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
"ramdiskId")
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
"groupSet"
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
"spotPrice")
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
"subnetId")
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
"tagSpecificationSet"
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
"userData")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"weightedCapacity")
instance
Prelude.Hashable
SpotFleetLaunchSpecification
where
hashWithSalt :: Int -> SpotFleetLaunchSpecification -> Int
hashWithSalt Int
_salt SpotFleetLaunchSpecification' {Maybe Bool
Maybe Double
Maybe [GroupIdentifier]
Maybe [InstanceNetworkInterfaceSpecification]
Maybe [SpotFleetTagSpecification]
Maybe [BlockDeviceMapping]
Maybe Text
Maybe IamInstanceProfileSpecification
Maybe InstanceType
Maybe SpotFleetMonitoring
Maybe SpotPlacement
Maybe InstanceRequirements
weightedCapacity :: Maybe Double
userData :: Maybe Text
tagSpecifications :: Maybe [SpotFleetTagSpecification]
subnetId :: Maybe Text
spotPrice :: Maybe Text
securityGroups :: Maybe [GroupIdentifier]
ramdiskId :: Maybe Text
placement :: Maybe SpotPlacement
networkInterfaces :: Maybe [InstanceNetworkInterfaceSpecification]
monitoring :: Maybe SpotFleetMonitoring
keyName :: Maybe Text
kernelId :: Maybe Text
instanceType :: Maybe InstanceType
instanceRequirements :: Maybe InstanceRequirements
imageId :: Maybe Text
iamInstanceProfile :: Maybe IamInstanceProfileSpecification
ebsOptimized :: Maybe Bool
blockDeviceMappings :: Maybe [BlockDeviceMapping]
addressingType :: Maybe Text
$sel:weightedCapacity:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Double
$sel:userData:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Text
$sel:tagSpecifications:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe [SpotFleetTagSpecification]
$sel:subnetId:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Text
$sel:spotPrice:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Text
$sel:securityGroups:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe [GroupIdentifier]
$sel:ramdiskId:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Text
$sel:placement:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe SpotPlacement
$sel:networkInterfaces:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification
-> Maybe [InstanceNetworkInterfaceSpecification]
$sel:monitoring:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe SpotFleetMonitoring
$sel:keyName:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Text
$sel:kernelId:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Text
$sel:instanceType:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe InstanceType
$sel:instanceRequirements:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe InstanceRequirements
$sel:imageId:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Text
$sel:iamInstanceProfile:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification
-> Maybe IamInstanceProfileSpecification
$sel:ebsOptimized:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Bool
$sel:blockDeviceMappings:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe [BlockDeviceMapping]
$sel:addressingType:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Text
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
addressingType
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [BlockDeviceMapping]
blockDeviceMappings
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
ebsOptimized
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe IamInstanceProfileSpecification
iamInstanceProfile
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
imageId
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe InstanceRequirements
instanceRequirements
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe InstanceType
instanceType
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
kernelId
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
keyName
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SpotFleetMonitoring
monitoring
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [InstanceNetworkInterfaceSpecification]
networkInterfaces
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SpotPlacement
placement
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
ramdiskId
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [GroupIdentifier]
securityGroups
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
spotPrice
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
subnetId
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [SpotFleetTagSpecification]
tagSpecifications
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
userData
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Double
weightedCapacity
instance Prelude.NFData SpotFleetLaunchSpecification where
rnf :: SpotFleetLaunchSpecification -> ()
rnf SpotFleetLaunchSpecification' {Maybe Bool
Maybe Double
Maybe [GroupIdentifier]
Maybe [InstanceNetworkInterfaceSpecification]
Maybe [SpotFleetTagSpecification]
Maybe [BlockDeviceMapping]
Maybe Text
Maybe IamInstanceProfileSpecification
Maybe InstanceType
Maybe SpotFleetMonitoring
Maybe SpotPlacement
Maybe InstanceRequirements
weightedCapacity :: Maybe Double
userData :: Maybe Text
tagSpecifications :: Maybe [SpotFleetTagSpecification]
subnetId :: Maybe Text
spotPrice :: Maybe Text
securityGroups :: Maybe [GroupIdentifier]
ramdiskId :: Maybe Text
placement :: Maybe SpotPlacement
networkInterfaces :: Maybe [InstanceNetworkInterfaceSpecification]
monitoring :: Maybe SpotFleetMonitoring
keyName :: Maybe Text
kernelId :: Maybe Text
instanceType :: Maybe InstanceType
instanceRequirements :: Maybe InstanceRequirements
imageId :: Maybe Text
iamInstanceProfile :: Maybe IamInstanceProfileSpecification
ebsOptimized :: Maybe Bool
blockDeviceMappings :: Maybe [BlockDeviceMapping]
addressingType :: Maybe Text
$sel:weightedCapacity:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Double
$sel:userData:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Text
$sel:tagSpecifications:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe [SpotFleetTagSpecification]
$sel:subnetId:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Text
$sel:spotPrice:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Text
$sel:securityGroups:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe [GroupIdentifier]
$sel:ramdiskId:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Text
$sel:placement:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe SpotPlacement
$sel:networkInterfaces:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification
-> Maybe [InstanceNetworkInterfaceSpecification]
$sel:monitoring:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe SpotFleetMonitoring
$sel:keyName:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Text
$sel:kernelId:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Text
$sel:instanceType:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe InstanceType
$sel:instanceRequirements:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe InstanceRequirements
$sel:imageId:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Text
$sel:iamInstanceProfile:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification
-> Maybe IamInstanceProfileSpecification
$sel:ebsOptimized:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Bool
$sel:blockDeviceMappings:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe [BlockDeviceMapping]
$sel:addressingType:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
addressingType
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [BlockDeviceMapping]
blockDeviceMappings
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
ebsOptimized
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe IamInstanceProfileSpecification
iamInstanceProfile
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
imageId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe InstanceRequirements
instanceRequirements
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe InstanceType
instanceType
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
kernelId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
keyName
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SpotFleetMonitoring
monitoring
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [InstanceNetworkInterfaceSpecification]
networkInterfaces
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SpotPlacement
placement
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
ramdiskId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [GroupIdentifier]
securityGroups
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
spotPrice
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
subnetId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [SpotFleetTagSpecification]
tagSpecifications
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
userData
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Double
weightedCapacity
instance Data.ToQuery SpotFleetLaunchSpecification where
toQuery :: SpotFleetLaunchSpecification -> QueryString
toQuery SpotFleetLaunchSpecification' {Maybe Bool
Maybe Double
Maybe [GroupIdentifier]
Maybe [InstanceNetworkInterfaceSpecification]
Maybe [SpotFleetTagSpecification]
Maybe [BlockDeviceMapping]
Maybe Text
Maybe IamInstanceProfileSpecification
Maybe InstanceType
Maybe SpotFleetMonitoring
Maybe SpotPlacement
Maybe InstanceRequirements
weightedCapacity :: Maybe Double
userData :: Maybe Text
tagSpecifications :: Maybe [SpotFleetTagSpecification]
subnetId :: Maybe Text
spotPrice :: Maybe Text
securityGroups :: Maybe [GroupIdentifier]
ramdiskId :: Maybe Text
placement :: Maybe SpotPlacement
networkInterfaces :: Maybe [InstanceNetworkInterfaceSpecification]
monitoring :: Maybe SpotFleetMonitoring
keyName :: Maybe Text
kernelId :: Maybe Text
instanceType :: Maybe InstanceType
instanceRequirements :: Maybe InstanceRequirements
imageId :: Maybe Text
iamInstanceProfile :: Maybe IamInstanceProfileSpecification
ebsOptimized :: Maybe Bool
blockDeviceMappings :: Maybe [BlockDeviceMapping]
addressingType :: Maybe Text
$sel:weightedCapacity:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Double
$sel:userData:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Text
$sel:tagSpecifications:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe [SpotFleetTagSpecification]
$sel:subnetId:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Text
$sel:spotPrice:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Text
$sel:securityGroups:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe [GroupIdentifier]
$sel:ramdiskId:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Text
$sel:placement:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe SpotPlacement
$sel:networkInterfaces:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification
-> Maybe [InstanceNetworkInterfaceSpecification]
$sel:monitoring:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe SpotFleetMonitoring
$sel:keyName:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Text
$sel:kernelId:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Text
$sel:instanceType:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe InstanceType
$sel:instanceRequirements:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe InstanceRequirements
$sel:imageId:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Text
$sel:iamInstanceProfile:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification
-> Maybe IamInstanceProfileSpecification
$sel:ebsOptimized:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Bool
$sel:blockDeviceMappings:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe [BlockDeviceMapping]
$sel:addressingType:SpotFleetLaunchSpecification' :: SpotFleetLaunchSpecification -> Maybe Text
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ ByteString
"AddressingType" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
addressingType,
forall a. ToQuery a => a -> QueryString
Data.toQuery
( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"BlockDeviceMapping"
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [BlockDeviceMapping]
blockDeviceMappings
),
ByteString
"EbsOptimized" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
ebsOptimized,
ByteString
"IamInstanceProfile" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe IamInstanceProfileSpecification
iamInstanceProfile,
ByteString
"ImageId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
imageId,
ByteString
"InstanceRequirements" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe InstanceRequirements
instanceRequirements,
ByteString
"InstanceType" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe InstanceType
instanceType,
ByteString
"KernelId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
kernelId,
ByteString
"KeyName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
keyName,
ByteString
"Monitoring" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe SpotFleetMonitoring
monitoring,
forall a. ToQuery a => a -> QueryString
Data.toQuery
( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"NetworkInterfaceSet"
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [InstanceNetworkInterfaceSpecification]
networkInterfaces
),
ByteString
"Placement" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe SpotPlacement
placement,
ByteString
"RamdiskId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
ramdiskId,
forall a. ToQuery a => a -> QueryString
Data.toQuery
( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"GroupSet"
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [GroupIdentifier]
securityGroups
),
ByteString
"SpotPrice" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
spotPrice,
ByteString
"SubnetId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
subnetId,
forall a. ToQuery a => a -> QueryString
Data.toQuery
( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"TagSpecificationSet"
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [SpotFleetTagSpecification]
tagSpecifications
),
ByteString
"UserData" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
userData,
ByteString
"WeightedCapacity" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Double
weightedCapacity
]