module Stratosphere.AutoScaling.LaunchConfiguration (
module Exports, LaunchConfiguration(..), mkLaunchConfiguration
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.AutoScaling.LaunchConfiguration.BlockDeviceMappingProperty as Exports
import {-# SOURCE #-} Stratosphere.AutoScaling.LaunchConfiguration.MetadataOptionsProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data LaunchConfiguration
=
LaunchConfiguration {LaunchConfiguration -> ()
haddock_workaround_ :: (),
LaunchConfiguration -> Maybe (Value Bool)
associatePublicIpAddress :: (Prelude.Maybe (Value Prelude.Bool)),
LaunchConfiguration -> Maybe [BlockDeviceMappingProperty]
blockDeviceMappings :: (Prelude.Maybe [BlockDeviceMappingProperty]),
LaunchConfiguration -> Maybe (Value Text)
classicLinkVPCId :: (Prelude.Maybe (Value Prelude.Text)),
LaunchConfiguration -> Maybe (ValueList Text)
classicLinkVPCSecurityGroups :: (Prelude.Maybe (ValueList Prelude.Text)),
LaunchConfiguration -> Maybe (Value Bool)
ebsOptimized :: (Prelude.Maybe (Value Prelude.Bool)),
LaunchConfiguration -> Maybe (Value Text)
iamInstanceProfile :: (Prelude.Maybe (Value Prelude.Text)),
LaunchConfiguration -> Value Text
imageId :: (Value Prelude.Text),
LaunchConfiguration -> Maybe (Value Text)
instanceId :: (Prelude.Maybe (Value Prelude.Text)),
LaunchConfiguration -> Maybe (Value Bool)
instanceMonitoring :: (Prelude.Maybe (Value Prelude.Bool)),
LaunchConfiguration -> Value Text
instanceType :: (Value Prelude.Text),
LaunchConfiguration -> Maybe (Value Text)
kernelId :: (Prelude.Maybe (Value Prelude.Text)),
LaunchConfiguration -> Maybe (Value Text)
keyName :: (Prelude.Maybe (Value Prelude.Text)),
LaunchConfiguration -> Maybe (Value Text)
launchConfigurationName :: (Prelude.Maybe (Value Prelude.Text)),
LaunchConfiguration -> Maybe MetadataOptionsProperty
metadataOptions :: (Prelude.Maybe MetadataOptionsProperty),
LaunchConfiguration -> Maybe (Value Text)
placementTenancy :: (Prelude.Maybe (Value Prelude.Text)),
LaunchConfiguration -> Maybe (Value Text)
ramDiskId :: (Prelude.Maybe (Value Prelude.Text)),
LaunchConfiguration -> Maybe (ValueList Text)
securityGroups :: (Prelude.Maybe (ValueList Prelude.Text)),
LaunchConfiguration -> Maybe (Value Text)
spotPrice :: (Prelude.Maybe (Value Prelude.Text)),
LaunchConfiguration -> Maybe (Value Text)
userData :: (Prelude.Maybe (Value Prelude.Text))}
deriving stock (LaunchConfiguration -> LaunchConfiguration -> Bool
(LaunchConfiguration -> LaunchConfiguration -> Bool)
-> (LaunchConfiguration -> LaunchConfiguration -> Bool)
-> Eq LaunchConfiguration
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LaunchConfiguration -> LaunchConfiguration -> Bool
== :: LaunchConfiguration -> LaunchConfiguration -> Bool
$c/= :: LaunchConfiguration -> LaunchConfiguration -> Bool
/= :: LaunchConfiguration -> LaunchConfiguration -> Bool
Prelude.Eq, Int -> LaunchConfiguration -> ShowS
[LaunchConfiguration] -> ShowS
LaunchConfiguration -> String
(Int -> LaunchConfiguration -> ShowS)
-> (LaunchConfiguration -> String)
-> ([LaunchConfiguration] -> ShowS)
-> Show LaunchConfiguration
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LaunchConfiguration -> ShowS
showsPrec :: Int -> LaunchConfiguration -> ShowS
$cshow :: LaunchConfiguration -> String
show :: LaunchConfiguration -> String
$cshowList :: [LaunchConfiguration] -> ShowS
showList :: [LaunchConfiguration] -> ShowS
Prelude.Show)
mkLaunchConfiguration ::
Value Prelude.Text -> Value Prelude.Text -> LaunchConfiguration
mkLaunchConfiguration :: Value Text -> Value Text -> LaunchConfiguration
mkLaunchConfiguration Value Text
imageId Value Text
instanceType
= LaunchConfiguration
{haddock_workaround_ :: ()
haddock_workaround_ = (), imageId :: Value Text
imageId = Value Text
imageId,
instanceType :: Value Text
instanceType = Value Text
instanceType,
associatePublicIpAddress :: Maybe (Value Bool)
associatePublicIpAddress = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing,
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
blockDeviceMappings = Maybe [BlockDeviceMappingProperty]
forall a. Maybe a
Prelude.Nothing,
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCId = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
classicLinkVPCSecurityGroups = Maybe (ValueList Text)
forall a. Maybe a
Prelude.Nothing,
ebsOptimized :: Maybe (Value Bool)
ebsOptimized = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing,
iamInstanceProfile :: Maybe (Value Text)
iamInstanceProfile = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, instanceId :: Maybe (Value Text)
instanceId = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
instanceMonitoring :: Maybe (Value Bool)
instanceMonitoring = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing, kernelId :: Maybe (Value Text)
kernelId = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
keyName :: Maybe (Value Text)
keyName = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
launchConfigurationName :: Maybe (Value Text)
launchConfigurationName = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
metadataOptions :: Maybe MetadataOptionsProperty
metadataOptions = Maybe MetadataOptionsProperty
forall a. Maybe a
Prelude.Nothing,
placementTenancy :: Maybe (Value Text)
placementTenancy = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, ramDiskId :: Maybe (Value Text)
ramDiskId = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
securityGroups :: Maybe (ValueList Text)
securityGroups = Maybe (ValueList Text)
forall a. Maybe a
Prelude.Nothing, spotPrice :: Maybe (Value Text)
spotPrice = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
userData :: Maybe (Value Text)
userData = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties LaunchConfiguration where
toResourceProperties :: LaunchConfiguration -> ResourceProperties
toResourceProperties LaunchConfiguration {Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: LaunchConfiguration -> ()
associatePublicIpAddress :: LaunchConfiguration -> Maybe (Value Bool)
blockDeviceMappings :: LaunchConfiguration -> Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: LaunchConfiguration -> Maybe (Value Text)
classicLinkVPCSecurityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
ebsOptimized :: LaunchConfiguration -> Maybe (Value Bool)
iamInstanceProfile :: LaunchConfiguration -> Maybe (Value Text)
imageId :: LaunchConfiguration -> Value Text
instanceId :: LaunchConfiguration -> Maybe (Value Text)
instanceMonitoring :: LaunchConfiguration -> Maybe (Value Bool)
instanceType :: LaunchConfiguration -> Value Text
kernelId :: LaunchConfiguration -> Maybe (Value Text)
keyName :: LaunchConfiguration -> Maybe (Value Text)
launchConfigurationName :: LaunchConfiguration -> Maybe (Value Text)
metadataOptions :: LaunchConfiguration -> Maybe MetadataOptionsProperty
placementTenancy :: LaunchConfiguration -> Maybe (Value Text)
ramDiskId :: LaunchConfiguration -> Maybe (Value Text)
securityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
spotPrice :: LaunchConfiguration -> Maybe (Value Text)
userData :: LaunchConfiguration -> Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::AutoScaling::LaunchConfiguration",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
[Key
"ImageId" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
imageId, Key
"InstanceType" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
instanceType]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"AssociatePublicIpAddress"
(Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
associatePublicIpAddress,
Key -> [BlockDeviceMappingProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"BlockDeviceMappings" ([BlockDeviceMappingProperty] -> (Key, Value))
-> Maybe [BlockDeviceMappingProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [BlockDeviceMappingProperty]
blockDeviceMappings,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ClassicLinkVPCId" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
classicLinkVPCId,
Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ClassicLinkVPCSecurityGroups"
(ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
classicLinkVPCSecurityGroups,
Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"EbsOptimized" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
ebsOptimized,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"IamInstanceProfile" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
iamInstanceProfile,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"InstanceId" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
instanceId,
Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"InstanceMonitoring" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
instanceMonitoring,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"KernelId" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
kernelId,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"KeyName" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
keyName,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"LaunchConfigurationName"
(Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
launchConfigurationName,
Key -> MetadataOptionsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"MetadataOptions" (MetadataOptionsProperty -> (Key, Value))
-> Maybe MetadataOptionsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe MetadataOptionsProperty
metadataOptions,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"PlacementTenancy" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
placementTenancy,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RamDiskId" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
ramDiskId,
Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SecurityGroups" (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
securityGroups,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SpotPrice" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
spotPrice,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"UserData" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
userData]))}
instance JSON.ToJSON LaunchConfiguration where
toJSON :: LaunchConfiguration -> Value
toJSON LaunchConfiguration {Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: LaunchConfiguration -> ()
associatePublicIpAddress :: LaunchConfiguration -> Maybe (Value Bool)
blockDeviceMappings :: LaunchConfiguration -> Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: LaunchConfiguration -> Maybe (Value Text)
classicLinkVPCSecurityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
ebsOptimized :: LaunchConfiguration -> Maybe (Value Bool)
iamInstanceProfile :: LaunchConfiguration -> Maybe (Value Text)
imageId :: LaunchConfiguration -> Value Text
instanceId :: LaunchConfiguration -> Maybe (Value Text)
instanceMonitoring :: LaunchConfiguration -> Maybe (Value Bool)
instanceType :: LaunchConfiguration -> Value Text
kernelId :: LaunchConfiguration -> Maybe (Value Text)
keyName :: LaunchConfiguration -> Maybe (Value Text)
launchConfigurationName :: LaunchConfiguration -> Maybe (Value Text)
metadataOptions :: LaunchConfiguration -> Maybe MetadataOptionsProperty
placementTenancy :: LaunchConfiguration -> Maybe (Value Text)
ramDiskId :: LaunchConfiguration -> Maybe (Value Text)
securityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
spotPrice :: LaunchConfiguration -> Maybe (Value Text)
userData :: LaunchConfiguration -> Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
= [(Key, Value)] -> Value
JSON.object
([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
[Key
"ImageId" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
imageId, Key
"InstanceType" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
instanceType]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"AssociatePublicIpAddress"
(Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
associatePublicIpAddress,
Key -> [BlockDeviceMappingProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"BlockDeviceMappings" ([BlockDeviceMappingProperty] -> (Key, Value))
-> Maybe [BlockDeviceMappingProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [BlockDeviceMappingProperty]
blockDeviceMappings,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ClassicLinkVPCId" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
classicLinkVPCId,
Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ClassicLinkVPCSecurityGroups"
(ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
classicLinkVPCSecurityGroups,
Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"EbsOptimized" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
ebsOptimized,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"IamInstanceProfile" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
iamInstanceProfile,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"InstanceId" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
instanceId,
Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"InstanceMonitoring" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
instanceMonitoring,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"KernelId" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
kernelId,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"KeyName" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
keyName,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"LaunchConfigurationName"
(Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
launchConfigurationName,
Key -> MetadataOptionsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"MetadataOptions" (MetadataOptionsProperty -> (Key, Value))
-> Maybe MetadataOptionsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe MetadataOptionsProperty
metadataOptions,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"PlacementTenancy" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
placementTenancy,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RamDiskId" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
ramDiskId,
Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SecurityGroups" (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
securityGroups,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SpotPrice" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
spotPrice,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"UserData" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
userData])))
instance Property "AssociatePublicIpAddress" LaunchConfiguration where
type PropertyType "AssociatePublicIpAddress" LaunchConfiguration = Value Prelude.Bool
set :: PropertyType "AssociatePublicIpAddress" LaunchConfiguration
-> LaunchConfiguration -> LaunchConfiguration
set PropertyType "AssociatePublicIpAddress" LaunchConfiguration
newValue LaunchConfiguration {Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: LaunchConfiguration -> ()
associatePublicIpAddress :: LaunchConfiguration -> Maybe (Value Bool)
blockDeviceMappings :: LaunchConfiguration -> Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: LaunchConfiguration -> Maybe (Value Text)
classicLinkVPCSecurityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
ebsOptimized :: LaunchConfiguration -> Maybe (Value Bool)
iamInstanceProfile :: LaunchConfiguration -> Maybe (Value Text)
imageId :: LaunchConfiguration -> Value Text
instanceId :: LaunchConfiguration -> Maybe (Value Text)
instanceMonitoring :: LaunchConfiguration -> Maybe (Value Bool)
instanceType :: LaunchConfiguration -> Value Text
kernelId :: LaunchConfiguration -> Maybe (Value Text)
keyName :: LaunchConfiguration -> Maybe (Value Text)
launchConfigurationName :: LaunchConfiguration -> Maybe (Value Text)
metadataOptions :: LaunchConfiguration -> Maybe MetadataOptionsProperty
placementTenancy :: LaunchConfiguration -> Maybe (Value Text)
ramDiskId :: LaunchConfiguration -> Maybe (Value Text)
securityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
spotPrice :: LaunchConfiguration -> Maybe (Value Text)
userData :: LaunchConfiguration -> Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
= LaunchConfiguration
{associatePublicIpAddress :: Maybe (Value Bool)
associatePublicIpAddress = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "AssociatePublicIpAddress" LaunchConfiguration
Value Bool
newValue, Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: ()
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
haddock_workaround_ :: ()
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
instance Property "BlockDeviceMappings" LaunchConfiguration where
type PropertyType "BlockDeviceMappings" LaunchConfiguration = [BlockDeviceMappingProperty]
set :: PropertyType "BlockDeviceMappings" LaunchConfiguration
-> LaunchConfiguration -> LaunchConfiguration
set PropertyType "BlockDeviceMappings" LaunchConfiguration
newValue LaunchConfiguration {Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: LaunchConfiguration -> ()
associatePublicIpAddress :: LaunchConfiguration -> Maybe (Value Bool)
blockDeviceMappings :: LaunchConfiguration -> Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: LaunchConfiguration -> Maybe (Value Text)
classicLinkVPCSecurityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
ebsOptimized :: LaunchConfiguration -> Maybe (Value Bool)
iamInstanceProfile :: LaunchConfiguration -> Maybe (Value Text)
imageId :: LaunchConfiguration -> Value Text
instanceId :: LaunchConfiguration -> Maybe (Value Text)
instanceMonitoring :: LaunchConfiguration -> Maybe (Value Bool)
instanceType :: LaunchConfiguration -> Value Text
kernelId :: LaunchConfiguration -> Maybe (Value Text)
keyName :: LaunchConfiguration -> Maybe (Value Text)
launchConfigurationName :: LaunchConfiguration -> Maybe (Value Text)
metadataOptions :: LaunchConfiguration -> Maybe MetadataOptionsProperty
placementTenancy :: LaunchConfiguration -> Maybe (Value Text)
ramDiskId :: LaunchConfiguration -> Maybe (Value Text)
securityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
spotPrice :: LaunchConfiguration -> Maybe (Value Text)
userData :: LaunchConfiguration -> Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
= LaunchConfiguration
{blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
blockDeviceMappings = [BlockDeviceMappingProperty] -> Maybe [BlockDeviceMappingProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [BlockDeviceMappingProperty]
PropertyType "BlockDeviceMappings" LaunchConfiguration
newValue, Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
instance Property "ClassicLinkVPCId" LaunchConfiguration where
type PropertyType "ClassicLinkVPCId" LaunchConfiguration = Value Prelude.Text
set :: PropertyType "ClassicLinkVPCId" LaunchConfiguration
-> LaunchConfiguration -> LaunchConfiguration
set PropertyType "ClassicLinkVPCId" LaunchConfiguration
newValue LaunchConfiguration {Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: LaunchConfiguration -> ()
associatePublicIpAddress :: LaunchConfiguration -> Maybe (Value Bool)
blockDeviceMappings :: LaunchConfiguration -> Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: LaunchConfiguration -> Maybe (Value Text)
classicLinkVPCSecurityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
ebsOptimized :: LaunchConfiguration -> Maybe (Value Bool)
iamInstanceProfile :: LaunchConfiguration -> Maybe (Value Text)
imageId :: LaunchConfiguration -> Value Text
instanceId :: LaunchConfiguration -> Maybe (Value Text)
instanceMonitoring :: LaunchConfiguration -> Maybe (Value Bool)
instanceType :: LaunchConfiguration -> Value Text
kernelId :: LaunchConfiguration -> Maybe (Value Text)
keyName :: LaunchConfiguration -> Maybe (Value Text)
launchConfigurationName :: LaunchConfiguration -> Maybe (Value Text)
metadataOptions :: LaunchConfiguration -> Maybe MetadataOptionsProperty
placementTenancy :: LaunchConfiguration -> Maybe (Value Text)
ramDiskId :: LaunchConfiguration -> Maybe (Value Text)
securityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
spotPrice :: LaunchConfiguration -> Maybe (Value Text)
userData :: LaunchConfiguration -> Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
= LaunchConfiguration
{classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCId = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ClassicLinkVPCId" LaunchConfiguration
Value Text
newValue, Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
instance Property "ClassicLinkVPCSecurityGroups" LaunchConfiguration where
type PropertyType "ClassicLinkVPCSecurityGroups" LaunchConfiguration = ValueList Prelude.Text
set :: PropertyType "ClassicLinkVPCSecurityGroups" LaunchConfiguration
-> LaunchConfiguration -> LaunchConfiguration
set PropertyType "ClassicLinkVPCSecurityGroups" LaunchConfiguration
newValue LaunchConfiguration {Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: LaunchConfiguration -> ()
associatePublicIpAddress :: LaunchConfiguration -> Maybe (Value Bool)
blockDeviceMappings :: LaunchConfiguration -> Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: LaunchConfiguration -> Maybe (Value Text)
classicLinkVPCSecurityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
ebsOptimized :: LaunchConfiguration -> Maybe (Value Bool)
iamInstanceProfile :: LaunchConfiguration -> Maybe (Value Text)
imageId :: LaunchConfiguration -> Value Text
instanceId :: LaunchConfiguration -> Maybe (Value Text)
instanceMonitoring :: LaunchConfiguration -> Maybe (Value Bool)
instanceType :: LaunchConfiguration -> Value Text
kernelId :: LaunchConfiguration -> Maybe (Value Text)
keyName :: LaunchConfiguration -> Maybe (Value Text)
launchConfigurationName :: LaunchConfiguration -> Maybe (Value Text)
metadataOptions :: LaunchConfiguration -> Maybe MetadataOptionsProperty
placementTenancy :: LaunchConfiguration -> Maybe (Value Text)
ramDiskId :: LaunchConfiguration -> Maybe (Value Text)
securityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
spotPrice :: LaunchConfiguration -> Maybe (Value Text)
userData :: LaunchConfiguration -> Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
= LaunchConfiguration
{classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
classicLinkVPCSecurityGroups = ValueList Text -> Maybe (ValueList Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ClassicLinkVPCSecurityGroups" LaunchConfiguration
ValueList Text
newValue, Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
instance Property "EbsOptimized" LaunchConfiguration where
type PropertyType "EbsOptimized" LaunchConfiguration = Value Prelude.Bool
set :: PropertyType "EbsOptimized" LaunchConfiguration
-> LaunchConfiguration -> LaunchConfiguration
set PropertyType "EbsOptimized" LaunchConfiguration
newValue LaunchConfiguration {Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: LaunchConfiguration -> ()
associatePublicIpAddress :: LaunchConfiguration -> Maybe (Value Bool)
blockDeviceMappings :: LaunchConfiguration -> Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: LaunchConfiguration -> Maybe (Value Text)
classicLinkVPCSecurityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
ebsOptimized :: LaunchConfiguration -> Maybe (Value Bool)
iamInstanceProfile :: LaunchConfiguration -> Maybe (Value Text)
imageId :: LaunchConfiguration -> Value Text
instanceId :: LaunchConfiguration -> Maybe (Value Text)
instanceMonitoring :: LaunchConfiguration -> Maybe (Value Bool)
instanceType :: LaunchConfiguration -> Value Text
kernelId :: LaunchConfiguration -> Maybe (Value Text)
keyName :: LaunchConfiguration -> Maybe (Value Text)
launchConfigurationName :: LaunchConfiguration -> Maybe (Value Text)
metadataOptions :: LaunchConfiguration -> Maybe MetadataOptionsProperty
placementTenancy :: LaunchConfiguration -> Maybe (Value Text)
ramDiskId :: LaunchConfiguration -> Maybe (Value Text)
securityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
spotPrice :: LaunchConfiguration -> Maybe (Value Text)
userData :: LaunchConfiguration -> Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
= LaunchConfiguration {ebsOptimized :: Maybe (Value Bool)
ebsOptimized = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "EbsOptimized" LaunchConfiguration
Value Bool
newValue, Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
instance Property "IamInstanceProfile" LaunchConfiguration where
type PropertyType "IamInstanceProfile" LaunchConfiguration = Value Prelude.Text
set :: PropertyType "IamInstanceProfile" LaunchConfiguration
-> LaunchConfiguration -> LaunchConfiguration
set PropertyType "IamInstanceProfile" LaunchConfiguration
newValue LaunchConfiguration {Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: LaunchConfiguration -> ()
associatePublicIpAddress :: LaunchConfiguration -> Maybe (Value Bool)
blockDeviceMappings :: LaunchConfiguration -> Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: LaunchConfiguration -> Maybe (Value Text)
classicLinkVPCSecurityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
ebsOptimized :: LaunchConfiguration -> Maybe (Value Bool)
iamInstanceProfile :: LaunchConfiguration -> Maybe (Value Text)
imageId :: LaunchConfiguration -> Value Text
instanceId :: LaunchConfiguration -> Maybe (Value Text)
instanceMonitoring :: LaunchConfiguration -> Maybe (Value Bool)
instanceType :: LaunchConfiguration -> Value Text
kernelId :: LaunchConfiguration -> Maybe (Value Text)
keyName :: LaunchConfiguration -> Maybe (Value Text)
launchConfigurationName :: LaunchConfiguration -> Maybe (Value Text)
metadataOptions :: LaunchConfiguration -> Maybe MetadataOptionsProperty
placementTenancy :: LaunchConfiguration -> Maybe (Value Text)
ramDiskId :: LaunchConfiguration -> Maybe (Value Text)
securityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
spotPrice :: LaunchConfiguration -> Maybe (Value Text)
userData :: LaunchConfiguration -> Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
= LaunchConfiguration
{iamInstanceProfile :: Maybe (Value Text)
iamInstanceProfile = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "IamInstanceProfile" LaunchConfiguration
Value Text
newValue, Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
instance Property "ImageId" LaunchConfiguration where
type PropertyType "ImageId" LaunchConfiguration = Value Prelude.Text
set :: PropertyType "ImageId" LaunchConfiguration
-> LaunchConfiguration -> LaunchConfiguration
set PropertyType "ImageId" LaunchConfiguration
newValue LaunchConfiguration {Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: LaunchConfiguration -> ()
associatePublicIpAddress :: LaunchConfiguration -> Maybe (Value Bool)
blockDeviceMappings :: LaunchConfiguration -> Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: LaunchConfiguration -> Maybe (Value Text)
classicLinkVPCSecurityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
ebsOptimized :: LaunchConfiguration -> Maybe (Value Bool)
iamInstanceProfile :: LaunchConfiguration -> Maybe (Value Text)
imageId :: LaunchConfiguration -> Value Text
instanceId :: LaunchConfiguration -> Maybe (Value Text)
instanceMonitoring :: LaunchConfiguration -> Maybe (Value Bool)
instanceType :: LaunchConfiguration -> Value Text
kernelId :: LaunchConfiguration -> Maybe (Value Text)
keyName :: LaunchConfiguration -> Maybe (Value Text)
launchConfigurationName :: LaunchConfiguration -> Maybe (Value Text)
metadataOptions :: LaunchConfiguration -> Maybe MetadataOptionsProperty
placementTenancy :: LaunchConfiguration -> Maybe (Value Text)
ramDiskId :: LaunchConfiguration -> Maybe (Value Text)
securityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
spotPrice :: LaunchConfiguration -> Maybe (Value Text)
userData :: LaunchConfiguration -> Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
= LaunchConfiguration {imageId :: Value Text
imageId = PropertyType "ImageId" LaunchConfiguration
Value Text
newValue, Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
instance Property "InstanceId" LaunchConfiguration where
type PropertyType "InstanceId" LaunchConfiguration = Value Prelude.Text
set :: PropertyType "InstanceId" LaunchConfiguration
-> LaunchConfiguration -> LaunchConfiguration
set PropertyType "InstanceId" LaunchConfiguration
newValue LaunchConfiguration {Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: LaunchConfiguration -> ()
associatePublicIpAddress :: LaunchConfiguration -> Maybe (Value Bool)
blockDeviceMappings :: LaunchConfiguration -> Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: LaunchConfiguration -> Maybe (Value Text)
classicLinkVPCSecurityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
ebsOptimized :: LaunchConfiguration -> Maybe (Value Bool)
iamInstanceProfile :: LaunchConfiguration -> Maybe (Value Text)
imageId :: LaunchConfiguration -> Value Text
instanceId :: LaunchConfiguration -> Maybe (Value Text)
instanceMonitoring :: LaunchConfiguration -> Maybe (Value Bool)
instanceType :: LaunchConfiguration -> Value Text
kernelId :: LaunchConfiguration -> Maybe (Value Text)
keyName :: LaunchConfiguration -> Maybe (Value Text)
launchConfigurationName :: LaunchConfiguration -> Maybe (Value Text)
metadataOptions :: LaunchConfiguration -> Maybe MetadataOptionsProperty
placementTenancy :: LaunchConfiguration -> Maybe (Value Text)
ramDiskId :: LaunchConfiguration -> Maybe (Value Text)
securityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
spotPrice :: LaunchConfiguration -> Maybe (Value Text)
userData :: LaunchConfiguration -> Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
= LaunchConfiguration {instanceId :: Maybe (Value Text)
instanceId = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "InstanceId" LaunchConfiguration
Value Text
newValue, Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
instance Property "InstanceMonitoring" LaunchConfiguration where
type PropertyType "InstanceMonitoring" LaunchConfiguration = Value Prelude.Bool
set :: PropertyType "InstanceMonitoring" LaunchConfiguration
-> LaunchConfiguration -> LaunchConfiguration
set PropertyType "InstanceMonitoring" LaunchConfiguration
newValue LaunchConfiguration {Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: LaunchConfiguration -> ()
associatePublicIpAddress :: LaunchConfiguration -> Maybe (Value Bool)
blockDeviceMappings :: LaunchConfiguration -> Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: LaunchConfiguration -> Maybe (Value Text)
classicLinkVPCSecurityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
ebsOptimized :: LaunchConfiguration -> Maybe (Value Bool)
iamInstanceProfile :: LaunchConfiguration -> Maybe (Value Text)
imageId :: LaunchConfiguration -> Value Text
instanceId :: LaunchConfiguration -> Maybe (Value Text)
instanceMonitoring :: LaunchConfiguration -> Maybe (Value Bool)
instanceType :: LaunchConfiguration -> Value Text
kernelId :: LaunchConfiguration -> Maybe (Value Text)
keyName :: LaunchConfiguration -> Maybe (Value Text)
launchConfigurationName :: LaunchConfiguration -> Maybe (Value Text)
metadataOptions :: LaunchConfiguration -> Maybe MetadataOptionsProperty
placementTenancy :: LaunchConfiguration -> Maybe (Value Text)
ramDiskId :: LaunchConfiguration -> Maybe (Value Text)
securityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
spotPrice :: LaunchConfiguration -> Maybe (Value Text)
userData :: LaunchConfiguration -> Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
= LaunchConfiguration
{instanceMonitoring :: Maybe (Value Bool)
instanceMonitoring = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "InstanceMonitoring" LaunchConfiguration
Value Bool
newValue, Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
instance Property "InstanceType" LaunchConfiguration where
type PropertyType "InstanceType" LaunchConfiguration = Value Prelude.Text
set :: PropertyType "InstanceType" LaunchConfiguration
-> LaunchConfiguration -> LaunchConfiguration
set PropertyType "InstanceType" LaunchConfiguration
newValue LaunchConfiguration {Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: LaunchConfiguration -> ()
associatePublicIpAddress :: LaunchConfiguration -> Maybe (Value Bool)
blockDeviceMappings :: LaunchConfiguration -> Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: LaunchConfiguration -> Maybe (Value Text)
classicLinkVPCSecurityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
ebsOptimized :: LaunchConfiguration -> Maybe (Value Bool)
iamInstanceProfile :: LaunchConfiguration -> Maybe (Value Text)
imageId :: LaunchConfiguration -> Value Text
instanceId :: LaunchConfiguration -> Maybe (Value Text)
instanceMonitoring :: LaunchConfiguration -> Maybe (Value Bool)
instanceType :: LaunchConfiguration -> Value Text
kernelId :: LaunchConfiguration -> Maybe (Value Text)
keyName :: LaunchConfiguration -> Maybe (Value Text)
launchConfigurationName :: LaunchConfiguration -> Maybe (Value Text)
metadataOptions :: LaunchConfiguration -> Maybe MetadataOptionsProperty
placementTenancy :: LaunchConfiguration -> Maybe (Value Text)
ramDiskId :: LaunchConfiguration -> Maybe (Value Text)
securityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
spotPrice :: LaunchConfiguration -> Maybe (Value Text)
userData :: LaunchConfiguration -> Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
= LaunchConfiguration {instanceType :: Value Text
instanceType = PropertyType "InstanceType" LaunchConfiguration
Value Text
newValue, Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
instance Property "KernelId" LaunchConfiguration where
type PropertyType "KernelId" LaunchConfiguration = Value Prelude.Text
set :: PropertyType "KernelId" LaunchConfiguration
-> LaunchConfiguration -> LaunchConfiguration
set PropertyType "KernelId" LaunchConfiguration
newValue LaunchConfiguration {Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: LaunchConfiguration -> ()
associatePublicIpAddress :: LaunchConfiguration -> Maybe (Value Bool)
blockDeviceMappings :: LaunchConfiguration -> Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: LaunchConfiguration -> Maybe (Value Text)
classicLinkVPCSecurityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
ebsOptimized :: LaunchConfiguration -> Maybe (Value Bool)
iamInstanceProfile :: LaunchConfiguration -> Maybe (Value Text)
imageId :: LaunchConfiguration -> Value Text
instanceId :: LaunchConfiguration -> Maybe (Value Text)
instanceMonitoring :: LaunchConfiguration -> Maybe (Value Bool)
instanceType :: LaunchConfiguration -> Value Text
kernelId :: LaunchConfiguration -> Maybe (Value Text)
keyName :: LaunchConfiguration -> Maybe (Value Text)
launchConfigurationName :: LaunchConfiguration -> Maybe (Value Text)
metadataOptions :: LaunchConfiguration -> Maybe MetadataOptionsProperty
placementTenancy :: LaunchConfiguration -> Maybe (Value Text)
ramDiskId :: LaunchConfiguration -> Maybe (Value Text)
securityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
spotPrice :: LaunchConfiguration -> Maybe (Value Text)
userData :: LaunchConfiguration -> Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
= LaunchConfiguration {kernelId :: Maybe (Value Text)
kernelId = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "KernelId" LaunchConfiguration
Value Text
newValue, Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
instance Property "KeyName" LaunchConfiguration where
type PropertyType "KeyName" LaunchConfiguration = Value Prelude.Text
set :: PropertyType "KeyName" LaunchConfiguration
-> LaunchConfiguration -> LaunchConfiguration
set PropertyType "KeyName" LaunchConfiguration
newValue LaunchConfiguration {Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: LaunchConfiguration -> ()
associatePublicIpAddress :: LaunchConfiguration -> Maybe (Value Bool)
blockDeviceMappings :: LaunchConfiguration -> Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: LaunchConfiguration -> Maybe (Value Text)
classicLinkVPCSecurityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
ebsOptimized :: LaunchConfiguration -> Maybe (Value Bool)
iamInstanceProfile :: LaunchConfiguration -> Maybe (Value Text)
imageId :: LaunchConfiguration -> Value Text
instanceId :: LaunchConfiguration -> Maybe (Value Text)
instanceMonitoring :: LaunchConfiguration -> Maybe (Value Bool)
instanceType :: LaunchConfiguration -> Value Text
kernelId :: LaunchConfiguration -> Maybe (Value Text)
keyName :: LaunchConfiguration -> Maybe (Value Text)
launchConfigurationName :: LaunchConfiguration -> Maybe (Value Text)
metadataOptions :: LaunchConfiguration -> Maybe MetadataOptionsProperty
placementTenancy :: LaunchConfiguration -> Maybe (Value Text)
ramDiskId :: LaunchConfiguration -> Maybe (Value Text)
securityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
spotPrice :: LaunchConfiguration -> Maybe (Value Text)
userData :: LaunchConfiguration -> Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
= LaunchConfiguration {keyName :: Maybe (Value Text)
keyName = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "KeyName" LaunchConfiguration
Value Text
newValue, Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
instance Property "LaunchConfigurationName" LaunchConfiguration where
type PropertyType "LaunchConfigurationName" LaunchConfiguration = Value Prelude.Text
set :: PropertyType "LaunchConfigurationName" LaunchConfiguration
-> LaunchConfiguration -> LaunchConfiguration
set PropertyType "LaunchConfigurationName" LaunchConfiguration
newValue LaunchConfiguration {Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: LaunchConfiguration -> ()
associatePublicIpAddress :: LaunchConfiguration -> Maybe (Value Bool)
blockDeviceMappings :: LaunchConfiguration -> Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: LaunchConfiguration -> Maybe (Value Text)
classicLinkVPCSecurityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
ebsOptimized :: LaunchConfiguration -> Maybe (Value Bool)
iamInstanceProfile :: LaunchConfiguration -> Maybe (Value Text)
imageId :: LaunchConfiguration -> Value Text
instanceId :: LaunchConfiguration -> Maybe (Value Text)
instanceMonitoring :: LaunchConfiguration -> Maybe (Value Bool)
instanceType :: LaunchConfiguration -> Value Text
kernelId :: LaunchConfiguration -> Maybe (Value Text)
keyName :: LaunchConfiguration -> Maybe (Value Text)
launchConfigurationName :: LaunchConfiguration -> Maybe (Value Text)
metadataOptions :: LaunchConfiguration -> Maybe MetadataOptionsProperty
placementTenancy :: LaunchConfiguration -> Maybe (Value Text)
ramDiskId :: LaunchConfiguration -> Maybe (Value Text)
securityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
spotPrice :: LaunchConfiguration -> Maybe (Value Text)
userData :: LaunchConfiguration -> Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
= LaunchConfiguration
{launchConfigurationName :: Maybe (Value Text)
launchConfigurationName = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "LaunchConfigurationName" LaunchConfiguration
Value Text
newValue, Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
instance Property "MetadataOptions" LaunchConfiguration where
type PropertyType "MetadataOptions" LaunchConfiguration = MetadataOptionsProperty
set :: PropertyType "MetadataOptions" LaunchConfiguration
-> LaunchConfiguration -> LaunchConfiguration
set PropertyType "MetadataOptions" LaunchConfiguration
newValue LaunchConfiguration {Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: LaunchConfiguration -> ()
associatePublicIpAddress :: LaunchConfiguration -> Maybe (Value Bool)
blockDeviceMappings :: LaunchConfiguration -> Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: LaunchConfiguration -> Maybe (Value Text)
classicLinkVPCSecurityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
ebsOptimized :: LaunchConfiguration -> Maybe (Value Bool)
iamInstanceProfile :: LaunchConfiguration -> Maybe (Value Text)
imageId :: LaunchConfiguration -> Value Text
instanceId :: LaunchConfiguration -> Maybe (Value Text)
instanceMonitoring :: LaunchConfiguration -> Maybe (Value Bool)
instanceType :: LaunchConfiguration -> Value Text
kernelId :: LaunchConfiguration -> Maybe (Value Text)
keyName :: LaunchConfiguration -> Maybe (Value Text)
launchConfigurationName :: LaunchConfiguration -> Maybe (Value Text)
metadataOptions :: LaunchConfiguration -> Maybe MetadataOptionsProperty
placementTenancy :: LaunchConfiguration -> Maybe (Value Text)
ramDiskId :: LaunchConfiguration -> Maybe (Value Text)
securityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
spotPrice :: LaunchConfiguration -> Maybe (Value Text)
userData :: LaunchConfiguration -> Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
= LaunchConfiguration {metadataOptions :: Maybe MetadataOptionsProperty
metadataOptions = MetadataOptionsProperty -> Maybe MetadataOptionsProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "MetadataOptions" LaunchConfiguration
MetadataOptionsProperty
newValue, Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
instance Property "PlacementTenancy" LaunchConfiguration where
type PropertyType "PlacementTenancy" LaunchConfiguration = Value Prelude.Text
set :: PropertyType "PlacementTenancy" LaunchConfiguration
-> LaunchConfiguration -> LaunchConfiguration
set PropertyType "PlacementTenancy" LaunchConfiguration
newValue LaunchConfiguration {Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: LaunchConfiguration -> ()
associatePublicIpAddress :: LaunchConfiguration -> Maybe (Value Bool)
blockDeviceMappings :: LaunchConfiguration -> Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: LaunchConfiguration -> Maybe (Value Text)
classicLinkVPCSecurityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
ebsOptimized :: LaunchConfiguration -> Maybe (Value Bool)
iamInstanceProfile :: LaunchConfiguration -> Maybe (Value Text)
imageId :: LaunchConfiguration -> Value Text
instanceId :: LaunchConfiguration -> Maybe (Value Text)
instanceMonitoring :: LaunchConfiguration -> Maybe (Value Bool)
instanceType :: LaunchConfiguration -> Value Text
kernelId :: LaunchConfiguration -> Maybe (Value Text)
keyName :: LaunchConfiguration -> Maybe (Value Text)
launchConfigurationName :: LaunchConfiguration -> Maybe (Value Text)
metadataOptions :: LaunchConfiguration -> Maybe MetadataOptionsProperty
placementTenancy :: LaunchConfiguration -> Maybe (Value Text)
ramDiskId :: LaunchConfiguration -> Maybe (Value Text)
securityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
spotPrice :: LaunchConfiguration -> Maybe (Value Text)
userData :: LaunchConfiguration -> Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
= LaunchConfiguration
{placementTenancy :: Maybe (Value Text)
placementTenancy = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "PlacementTenancy" LaunchConfiguration
Value Text
newValue, Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
instance Property "RamDiskId" LaunchConfiguration where
type PropertyType "RamDiskId" LaunchConfiguration = Value Prelude.Text
set :: PropertyType "RamDiskId" LaunchConfiguration
-> LaunchConfiguration -> LaunchConfiguration
set PropertyType "RamDiskId" LaunchConfiguration
newValue LaunchConfiguration {Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: LaunchConfiguration -> ()
associatePublicIpAddress :: LaunchConfiguration -> Maybe (Value Bool)
blockDeviceMappings :: LaunchConfiguration -> Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: LaunchConfiguration -> Maybe (Value Text)
classicLinkVPCSecurityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
ebsOptimized :: LaunchConfiguration -> Maybe (Value Bool)
iamInstanceProfile :: LaunchConfiguration -> Maybe (Value Text)
imageId :: LaunchConfiguration -> Value Text
instanceId :: LaunchConfiguration -> Maybe (Value Text)
instanceMonitoring :: LaunchConfiguration -> Maybe (Value Bool)
instanceType :: LaunchConfiguration -> Value Text
kernelId :: LaunchConfiguration -> Maybe (Value Text)
keyName :: LaunchConfiguration -> Maybe (Value Text)
launchConfigurationName :: LaunchConfiguration -> Maybe (Value Text)
metadataOptions :: LaunchConfiguration -> Maybe MetadataOptionsProperty
placementTenancy :: LaunchConfiguration -> Maybe (Value Text)
ramDiskId :: LaunchConfiguration -> Maybe (Value Text)
securityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
spotPrice :: LaunchConfiguration -> Maybe (Value Text)
userData :: LaunchConfiguration -> Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
= LaunchConfiguration {ramDiskId :: Maybe (Value Text)
ramDiskId = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "RamDiskId" LaunchConfiguration
Value Text
newValue, Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
instance Property "SecurityGroups" LaunchConfiguration where
type PropertyType "SecurityGroups" LaunchConfiguration = ValueList Prelude.Text
set :: PropertyType "SecurityGroups" LaunchConfiguration
-> LaunchConfiguration -> LaunchConfiguration
set PropertyType "SecurityGroups" LaunchConfiguration
newValue LaunchConfiguration {Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: LaunchConfiguration -> ()
associatePublicIpAddress :: LaunchConfiguration -> Maybe (Value Bool)
blockDeviceMappings :: LaunchConfiguration -> Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: LaunchConfiguration -> Maybe (Value Text)
classicLinkVPCSecurityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
ebsOptimized :: LaunchConfiguration -> Maybe (Value Bool)
iamInstanceProfile :: LaunchConfiguration -> Maybe (Value Text)
imageId :: LaunchConfiguration -> Value Text
instanceId :: LaunchConfiguration -> Maybe (Value Text)
instanceMonitoring :: LaunchConfiguration -> Maybe (Value Bool)
instanceType :: LaunchConfiguration -> Value Text
kernelId :: LaunchConfiguration -> Maybe (Value Text)
keyName :: LaunchConfiguration -> Maybe (Value Text)
launchConfigurationName :: LaunchConfiguration -> Maybe (Value Text)
metadataOptions :: LaunchConfiguration -> Maybe MetadataOptionsProperty
placementTenancy :: LaunchConfiguration -> Maybe (Value Text)
ramDiskId :: LaunchConfiguration -> Maybe (Value Text)
securityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
spotPrice :: LaunchConfiguration -> Maybe (Value Text)
userData :: LaunchConfiguration -> Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
= LaunchConfiguration {securityGroups :: Maybe (ValueList Text)
securityGroups = ValueList Text -> Maybe (ValueList Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "SecurityGroups" LaunchConfiguration
ValueList Text
newValue, Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
instance Property "SpotPrice" LaunchConfiguration where
type PropertyType "SpotPrice" LaunchConfiguration = Value Prelude.Text
set :: PropertyType "SpotPrice" LaunchConfiguration
-> LaunchConfiguration -> LaunchConfiguration
set PropertyType "SpotPrice" LaunchConfiguration
newValue LaunchConfiguration {Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: LaunchConfiguration -> ()
associatePublicIpAddress :: LaunchConfiguration -> Maybe (Value Bool)
blockDeviceMappings :: LaunchConfiguration -> Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: LaunchConfiguration -> Maybe (Value Text)
classicLinkVPCSecurityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
ebsOptimized :: LaunchConfiguration -> Maybe (Value Bool)
iamInstanceProfile :: LaunchConfiguration -> Maybe (Value Text)
imageId :: LaunchConfiguration -> Value Text
instanceId :: LaunchConfiguration -> Maybe (Value Text)
instanceMonitoring :: LaunchConfiguration -> Maybe (Value Bool)
instanceType :: LaunchConfiguration -> Value Text
kernelId :: LaunchConfiguration -> Maybe (Value Text)
keyName :: LaunchConfiguration -> Maybe (Value Text)
launchConfigurationName :: LaunchConfiguration -> Maybe (Value Text)
metadataOptions :: LaunchConfiguration -> Maybe MetadataOptionsProperty
placementTenancy :: LaunchConfiguration -> Maybe (Value Text)
ramDiskId :: LaunchConfiguration -> Maybe (Value Text)
securityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
spotPrice :: LaunchConfiguration -> Maybe (Value Text)
userData :: LaunchConfiguration -> Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
= LaunchConfiguration {spotPrice :: Maybe (Value Text)
spotPrice = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "SpotPrice" LaunchConfiguration
Value Text
newValue, Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
userData :: Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
userData :: Maybe (Value Text)
..}
instance Property "UserData" LaunchConfiguration where
type PropertyType "UserData" LaunchConfiguration = Value Prelude.Text
set :: PropertyType "UserData" LaunchConfiguration
-> LaunchConfiguration -> LaunchConfiguration
set PropertyType "UserData" LaunchConfiguration
newValue LaunchConfiguration {Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: LaunchConfiguration -> ()
associatePublicIpAddress :: LaunchConfiguration -> Maybe (Value Bool)
blockDeviceMappings :: LaunchConfiguration -> Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: LaunchConfiguration -> Maybe (Value Text)
classicLinkVPCSecurityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
ebsOptimized :: LaunchConfiguration -> Maybe (Value Bool)
iamInstanceProfile :: LaunchConfiguration -> Maybe (Value Text)
imageId :: LaunchConfiguration -> Value Text
instanceId :: LaunchConfiguration -> Maybe (Value Text)
instanceMonitoring :: LaunchConfiguration -> Maybe (Value Bool)
instanceType :: LaunchConfiguration -> Value Text
kernelId :: LaunchConfiguration -> Maybe (Value Text)
keyName :: LaunchConfiguration -> Maybe (Value Text)
launchConfigurationName :: LaunchConfiguration -> Maybe (Value Text)
metadataOptions :: LaunchConfiguration -> Maybe MetadataOptionsProperty
placementTenancy :: LaunchConfiguration -> Maybe (Value Text)
ramDiskId :: LaunchConfiguration -> Maybe (Value Text)
securityGroups :: LaunchConfiguration -> Maybe (ValueList Text)
spotPrice :: LaunchConfiguration -> Maybe (Value Text)
userData :: LaunchConfiguration -> Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}
= LaunchConfiguration {userData :: Maybe (Value Text)
userData = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "UserData" LaunchConfiguration
Value Text
newValue, Maybe [BlockDeviceMappingProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe MetadataOptionsProperty
()
Value Text
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
haddock_workaround_ :: ()
associatePublicIpAddress :: Maybe (Value Bool)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
classicLinkVPCId :: Maybe (Value Text)
classicLinkVPCSecurityGroups :: Maybe (ValueList Text)
ebsOptimized :: Maybe (Value Bool)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Value Text
instanceId :: Maybe (Value Text)
instanceMonitoring :: Maybe (Value Bool)
instanceType :: Value Text
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchConfigurationName :: Maybe (Value Text)
metadataOptions :: Maybe MetadataOptionsProperty
placementTenancy :: Maybe (Value Text)
ramDiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
spotPrice :: Maybe (Value Text)
..}