module Stratosphere.EC2.Instance (
        module Exports, Instance(..), mkInstance
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.EC2.Instance.BlockDeviceMappingProperty as Exports
import {-# SOURCE #-} Stratosphere.EC2.Instance.CpuOptionsProperty as Exports
import {-# SOURCE #-} Stratosphere.EC2.Instance.CreditSpecificationProperty as Exports
import {-# SOURCE #-} Stratosphere.EC2.Instance.ElasticGpuSpecificationProperty as Exports
import {-# SOURCE #-} Stratosphere.EC2.Instance.ElasticInferenceAcceleratorProperty as Exports
import {-# SOURCE #-} Stratosphere.EC2.Instance.EnclaveOptionsProperty as Exports
import {-# SOURCE #-} Stratosphere.EC2.Instance.HibernationOptionsProperty as Exports
import {-# SOURCE #-} Stratosphere.EC2.Instance.InstanceIpv6AddressProperty as Exports
import {-# SOURCE #-} Stratosphere.EC2.Instance.LaunchTemplateSpecificationProperty as Exports
import {-# SOURCE #-} Stratosphere.EC2.Instance.LicenseSpecificationProperty as Exports
import {-# SOURCE #-} Stratosphere.EC2.Instance.MetadataOptionsProperty as Exports
import {-# SOURCE #-} Stratosphere.EC2.Instance.NetworkInterfaceProperty as Exports
import {-# SOURCE #-} Stratosphere.EC2.Instance.PrivateDnsNameOptionsProperty as Exports
import {-# SOURCE #-} Stratosphere.EC2.Instance.SsmAssociationProperty as Exports
import {-# SOURCE #-} Stratosphere.EC2.Instance.VolumeProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Tag
import Stratosphere.Value
data Instance
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html>
    Instance {Instance -> ()
haddock_workaround_ :: (),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-additionalinfo>
              Instance -> Maybe (Value Text)
additionalInfo :: (Prelude.Maybe (Value Prelude.Text)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-affinity>
              Instance -> Maybe (Value Text)
affinity :: (Prelude.Maybe (Value Prelude.Text)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-availabilityzone>
              Instance -> Maybe (Value Text)
availabilityZone :: (Prelude.Maybe (Value Prelude.Text)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-blockdevicemappings>
              Instance -> Maybe [BlockDeviceMappingProperty]
blockDeviceMappings :: (Prelude.Maybe [BlockDeviceMappingProperty]),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-cpuoptions>
              Instance -> Maybe CpuOptionsProperty
cpuOptions :: (Prelude.Maybe CpuOptionsProperty),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-creditspecification>
              Instance -> Maybe CreditSpecificationProperty
creditSpecification :: (Prelude.Maybe CreditSpecificationProperty),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-disableapitermination>
              Instance -> Maybe (Value Bool)
disableApiTermination :: (Prelude.Maybe (Value Prelude.Bool)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-ebsoptimized>
              Instance -> Maybe (Value Bool)
ebsOptimized :: (Prelude.Maybe (Value Prelude.Bool)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-elasticgpuspecifications>
              Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticGpuSpecifications :: (Prelude.Maybe [ElasticGpuSpecificationProperty]),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-elasticinferenceaccelerators>
              Instance -> Maybe [ElasticInferenceAcceleratorProperty]
elasticInferenceAccelerators :: (Prelude.Maybe [ElasticInferenceAcceleratorProperty]),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-enclaveoptions>
              Instance -> Maybe EnclaveOptionsProperty
enclaveOptions :: (Prelude.Maybe EnclaveOptionsProperty),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-hibernationoptions>
              Instance -> Maybe HibernationOptionsProperty
hibernationOptions :: (Prelude.Maybe HibernationOptionsProperty),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-hostid>
              Instance -> Maybe (Value Text)
hostId :: (Prelude.Maybe (Value Prelude.Text)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-hostresourcegrouparn>
              Instance -> Maybe (Value Text)
hostResourceGroupArn :: (Prelude.Maybe (Value Prelude.Text)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-iaminstanceprofile>
              Instance -> Maybe (Value Text)
iamInstanceProfile :: (Prelude.Maybe (Value Prelude.Text)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-imageid>
              Instance -> Maybe (Value Text)
imageId :: (Prelude.Maybe (Value Prelude.Text)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-instanceinitiatedshutdownbehavior>
              Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: (Prelude.Maybe (Value Prelude.Text)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-instancetype>
              Instance -> Maybe (Value Text)
instanceType :: (Prelude.Maybe (Value Prelude.Text)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-ipv6addresscount>
              Instance -> Maybe (Value Integer)
ipv6AddressCount :: (Prelude.Maybe (Value Prelude.Integer)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-ipv6addresses>
              Instance -> Maybe [InstanceIpv6AddressProperty]
ipv6Addresses :: (Prelude.Maybe [InstanceIpv6AddressProperty]),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-kernelid>
              Instance -> Maybe (Value Text)
kernelId :: (Prelude.Maybe (Value Prelude.Text)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-keyname>
              Instance -> Maybe (Value Text)
keyName :: (Prelude.Maybe (Value Prelude.Text)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-launchtemplate>
              Instance -> Maybe LaunchTemplateSpecificationProperty
launchTemplate :: (Prelude.Maybe LaunchTemplateSpecificationProperty),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-licensespecifications>
              Instance -> Maybe [LicenseSpecificationProperty]
licenseSpecifications :: (Prelude.Maybe [LicenseSpecificationProperty]),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-metadataoptions>
              Instance -> Maybe MetadataOptionsProperty
metadataOptions :: (Prelude.Maybe MetadataOptionsProperty),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-monitoring>
              Instance -> Maybe (Value Bool)
monitoring :: (Prelude.Maybe (Value Prelude.Bool)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-networkinterfaces>
              Instance -> Maybe [NetworkInterfaceProperty]
networkInterfaces :: (Prelude.Maybe [NetworkInterfaceProperty]),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-placementgroupname>
              Instance -> Maybe (Value Text)
placementGroupName :: (Prelude.Maybe (Value Prelude.Text)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-privatednsnameoptions>
              Instance -> Maybe PrivateDnsNameOptionsProperty
privateDnsNameOptions :: (Prelude.Maybe PrivateDnsNameOptionsProperty),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-privateipaddress>
              Instance -> Maybe (Value Text)
privateIpAddress :: (Prelude.Maybe (Value Prelude.Text)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-propagatetagstovolumeoncreation>
              Instance -> Maybe (Value Bool)
propagateTagsToVolumeOnCreation :: (Prelude.Maybe (Value Prelude.Bool)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-ramdiskid>
              Instance -> Maybe (Value Text)
ramdiskId :: (Prelude.Maybe (Value Prelude.Text)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-securitygroupids>
              Instance -> Maybe (ValueList Text)
securityGroupIds :: (Prelude.Maybe (ValueList Prelude.Text)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-securitygroups>
              Instance -> Maybe (ValueList Text)
securityGroups :: (Prelude.Maybe (ValueList Prelude.Text)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-sourcedestcheck>
              Instance -> Maybe (Value Bool)
sourceDestCheck :: (Prelude.Maybe (Value Prelude.Bool)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-ssmassociations>
              Instance -> Maybe [SsmAssociationProperty]
ssmAssociations :: (Prelude.Maybe [SsmAssociationProperty]),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-subnetid>
              Instance -> Maybe (Value Text)
subnetId :: (Prelude.Maybe (Value Prelude.Text)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-tags>
              Instance -> Maybe [Tag]
tags :: (Prelude.Maybe [Tag]),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-tenancy>
              Instance -> Maybe (Value Text)
tenancy :: (Prelude.Maybe (Value Prelude.Text)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-userdata>
              Instance -> Maybe (Value Text)
userData :: (Prelude.Maybe (Value Prelude.Text)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-instance.html#cfn-ec2-instance-volumes>
              Instance -> Maybe [VolumeProperty]
volumes :: (Prelude.Maybe [VolumeProperty])}
  deriving stock (Instance -> Instance -> Bool
(Instance -> Instance -> Bool)
-> (Instance -> Instance -> Bool) -> Eq Instance
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Instance -> Instance -> Bool
== :: Instance -> Instance -> Bool
$c/= :: Instance -> Instance -> Bool
/= :: Instance -> Instance -> Bool
Prelude.Eq, Int -> Instance -> ShowS
[Instance] -> ShowS
Instance -> String
(Int -> Instance -> ShowS)
-> (Instance -> String) -> ([Instance] -> ShowS) -> Show Instance
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Instance -> ShowS
showsPrec :: Int -> Instance -> ShowS
$cshow :: Instance -> String
show :: Instance -> String
$cshowList :: [Instance] -> ShowS
showList :: [Instance] -> ShowS
Prelude.Show)
mkInstance :: Instance
mkInstance :: Instance
mkInstance
  = Instance
      {haddock_workaround_ :: ()
haddock_workaround_ = (), additionalInfo :: Maybe (Value Text)
additionalInfo = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       affinity :: Maybe (Value Text)
affinity = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, availabilityZone :: Maybe (Value Text)
availabilityZone = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
blockDeviceMappings = Maybe [BlockDeviceMappingProperty]
forall a. Maybe a
Prelude.Nothing,
       cpuOptions :: Maybe CpuOptionsProperty
cpuOptions = Maybe CpuOptionsProperty
forall a. Maybe a
Prelude.Nothing,
       creditSpecification :: Maybe CreditSpecificationProperty
creditSpecification = Maybe CreditSpecificationProperty
forall a. Maybe a
Prelude.Nothing,
       disableApiTermination :: Maybe (Value Bool)
disableApiTermination = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing,
       ebsOptimized :: Maybe (Value Bool)
ebsOptimized = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing,
       elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticGpuSpecifications = Maybe [ElasticGpuSpecificationProperty]
forall a. Maybe a
Prelude.Nothing,
       elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
elasticInferenceAccelerators = Maybe [ElasticInferenceAcceleratorProperty]
forall a. Maybe a
Prelude.Nothing,
       enclaveOptions :: Maybe EnclaveOptionsProperty
enclaveOptions = Maybe EnclaveOptionsProperty
forall a. Maybe a
Prelude.Nothing,
       hibernationOptions :: Maybe HibernationOptionsProperty
hibernationOptions = Maybe HibernationOptionsProperty
forall a. Maybe a
Prelude.Nothing, hostId :: Maybe (Value Text)
hostId = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       hostResourceGroupArn :: Maybe (Value Text)
hostResourceGroupArn = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       iamInstanceProfile :: Maybe (Value Text)
iamInstanceProfile = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, imageId :: Maybe (Value Text)
imageId = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceInitiatedShutdownBehavior = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       instanceType :: Maybe (Value Text)
instanceType = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, ipv6AddressCount :: Maybe (Value Integer)
ipv6AddressCount = Maybe (Value Integer)
forall a. Maybe a
Prelude.Nothing,
       ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
ipv6Addresses = Maybe [InstanceIpv6AddressProperty]
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, launchTemplate :: Maybe LaunchTemplateSpecificationProperty
launchTemplate = Maybe LaunchTemplateSpecificationProperty
forall a. Maybe a
Prelude.Nothing,
       licenseSpecifications :: Maybe [LicenseSpecificationProperty]
licenseSpecifications = Maybe [LicenseSpecificationProperty]
forall a. Maybe a
Prelude.Nothing,
       metadataOptions :: Maybe MetadataOptionsProperty
metadataOptions = Maybe MetadataOptionsProperty
forall a. Maybe a
Prelude.Nothing, monitoring :: Maybe (Value Bool)
monitoring = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing,
       networkInterfaces :: Maybe [NetworkInterfaceProperty]
networkInterfaces = Maybe [NetworkInterfaceProperty]
forall a. Maybe a
Prelude.Nothing,
       placementGroupName :: Maybe (Value Text)
placementGroupName = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateDnsNameOptions = Maybe PrivateDnsNameOptionsProperty
forall a. Maybe a
Prelude.Nothing,
       privateIpAddress :: Maybe (Value Text)
privateIpAddress = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
propagateTagsToVolumeOnCreation = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing,
       ramdiskId :: Maybe (Value Text)
ramdiskId = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, securityGroupIds :: Maybe (ValueList Text)
securityGroupIds = Maybe (ValueList Text)
forall a. Maybe a
Prelude.Nothing,
       securityGroups :: Maybe (ValueList Text)
securityGroups = Maybe (ValueList Text)
forall a. Maybe a
Prelude.Nothing,
       sourceDestCheck :: Maybe (Value Bool)
sourceDestCheck = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing,
       ssmAssociations :: Maybe [SsmAssociationProperty]
ssmAssociations = Maybe [SsmAssociationProperty]
forall a. Maybe a
Prelude.Nothing, subnetId :: Maybe (Value Text)
subnetId = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       tags :: Maybe [Tag]
tags = Maybe [Tag]
forall a. Maybe a
Prelude.Nothing, tenancy :: Maybe (Value Text)
tenancy = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       userData :: Maybe (Value Text)
userData = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, volumes :: Maybe [VolumeProperty]
volumes = Maybe [VolumeProperty]
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties Instance where
  toResourceProperties :: Instance -> ResourceProperties
toResourceProperties Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::EC2::Instance", supportsTags :: Bool
supportsTags = Bool
Prelude.True,
         properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
                        ([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
                           [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
"AdditionalInfo" (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)
additionalInfo,
                            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
"Affinity" (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)
affinity,
                            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
"AvailabilityZone" (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)
availabilityZone,
                            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 -> CpuOptionsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CpuOptions" (CpuOptionsProperty -> (Key, Value))
-> Maybe CpuOptionsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe CpuOptionsProperty
cpuOptions,
                            Key -> CreditSpecificationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CreditSpecification" (CreditSpecificationProperty -> (Key, Value))
-> Maybe CreditSpecificationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe CreditSpecificationProperty
creditSpecification,
                            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
"DisableApiTermination"
                              (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)
disableApiTermination,
                            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 -> [ElasticGpuSpecificationProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ElasticGpuSpecifications"
                              ([ElasticGpuSpecificationProperty] -> (Key, Value))
-> Maybe [ElasticGpuSpecificationProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [ElasticGpuSpecificationProperty]
elasticGpuSpecifications,
                            Key -> [ElasticInferenceAcceleratorProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ElasticInferenceAccelerators"
                              ([ElasticInferenceAcceleratorProperty] -> (Key, Value))
-> Maybe [ElasticInferenceAcceleratorProperty]
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [ElasticInferenceAcceleratorProperty]
elasticInferenceAccelerators,
                            Key -> EnclaveOptionsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"EnclaveOptions" (EnclaveOptionsProperty -> (Key, Value))
-> Maybe EnclaveOptionsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe EnclaveOptionsProperty
enclaveOptions,
                            Key -> HibernationOptionsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"HibernationOptions" (HibernationOptionsProperty -> (Key, Value))
-> Maybe HibernationOptionsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe HibernationOptionsProperty
hibernationOptions,
                            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
"HostId" (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)
hostId,
                            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
"HostResourceGroupArn" (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)
hostResourceGroupArn,
                            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
"ImageId" (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)
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..=) Key
"InstanceInitiatedShutdownBehavior"
                              (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)
instanceInitiatedShutdownBehavior,
                            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
"InstanceType" (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)
instanceType,
                            Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Ipv6AddressCount" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
ipv6AddressCount,
                            Key -> [InstanceIpv6AddressProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Ipv6Addresses" ([InstanceIpv6AddressProperty] -> (Key, Value))
-> Maybe [InstanceIpv6AddressProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [InstanceIpv6AddressProperty]
ipv6Addresses,
                            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 -> LaunchTemplateSpecificationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"LaunchTemplate" (LaunchTemplateSpecificationProperty -> (Key, Value))
-> Maybe LaunchTemplateSpecificationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe LaunchTemplateSpecificationProperty
launchTemplate,
                            Key -> [LicenseSpecificationProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"LicenseSpecifications"
                              ([LicenseSpecificationProperty] -> (Key, Value))
-> Maybe [LicenseSpecificationProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [LicenseSpecificationProperty]
licenseSpecifications,
                            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 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
"Monitoring" (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)
monitoring,
                            Key -> [NetworkInterfaceProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"NetworkInterfaces" ([NetworkInterfaceProperty] -> (Key, Value))
-> Maybe [NetworkInterfaceProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [NetworkInterfaceProperty]
networkInterfaces,
                            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
"PlacementGroupName" (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)
placementGroupName,
                            Key -> PrivateDnsNameOptionsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"PrivateDnsNameOptions"
                              (PrivateDnsNameOptionsProperty -> (Key, Value))
-> Maybe PrivateDnsNameOptionsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe PrivateDnsNameOptionsProperty
privateDnsNameOptions,
                            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
"PrivateIpAddress" (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)
privateIpAddress,
                            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
"PropagateTagsToVolumeOnCreation"
                              (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)
propagateTagsToVolumeOnCreation,
                            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
"SecurityGroupIds" (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)
securityGroupIds,
                            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 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
"SourceDestCheck" (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)
sourceDestCheck,
                            Key -> [SsmAssociationProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SsmAssociations" ([SsmAssociationProperty] -> (Key, Value))
-> Maybe [SsmAssociationProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [SsmAssociationProperty]
ssmAssociations,
                            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
"SubnetId" (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)
subnetId,
                            Key -> [Tag] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Tags" ([Tag] -> (Key, Value)) -> Maybe [Tag] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags,
                            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
"Tenancy" (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)
tenancy,
                            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,
                            Key -> [VolumeProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Volumes" ([VolumeProperty] -> (Key, Value))
-> Maybe [VolumeProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [VolumeProperty]
volumes])}
instance JSON.ToJSON Instance where
  toJSON :: Instance -> Value
toJSON Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = [(Key, Value)] -> Value
JSON.object
        ([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
           ([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
              [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
"AdditionalInfo" (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)
additionalInfo,
               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
"Affinity" (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)
affinity,
               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
"AvailabilityZone" (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)
availabilityZone,
               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 -> CpuOptionsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CpuOptions" (CpuOptionsProperty -> (Key, Value))
-> Maybe CpuOptionsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe CpuOptionsProperty
cpuOptions,
               Key -> CreditSpecificationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CreditSpecification" (CreditSpecificationProperty -> (Key, Value))
-> Maybe CreditSpecificationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe CreditSpecificationProperty
creditSpecification,
               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
"DisableApiTermination"
                 (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)
disableApiTermination,
               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 -> [ElasticGpuSpecificationProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ElasticGpuSpecifications"
                 ([ElasticGpuSpecificationProperty] -> (Key, Value))
-> Maybe [ElasticGpuSpecificationProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [ElasticGpuSpecificationProperty]
elasticGpuSpecifications,
               Key -> [ElasticInferenceAcceleratorProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ElasticInferenceAccelerators"
                 ([ElasticInferenceAcceleratorProperty] -> (Key, Value))
-> Maybe [ElasticInferenceAcceleratorProperty]
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [ElasticInferenceAcceleratorProperty]
elasticInferenceAccelerators,
               Key -> EnclaveOptionsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"EnclaveOptions" (EnclaveOptionsProperty -> (Key, Value))
-> Maybe EnclaveOptionsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe EnclaveOptionsProperty
enclaveOptions,
               Key -> HibernationOptionsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"HibernationOptions" (HibernationOptionsProperty -> (Key, Value))
-> Maybe HibernationOptionsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe HibernationOptionsProperty
hibernationOptions,
               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
"HostId" (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)
hostId,
               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
"HostResourceGroupArn" (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)
hostResourceGroupArn,
               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
"ImageId" (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)
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..=) Key
"InstanceInitiatedShutdownBehavior"
                 (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)
instanceInitiatedShutdownBehavior,
               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
"InstanceType" (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)
instanceType,
               Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Ipv6AddressCount" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
ipv6AddressCount,
               Key -> [InstanceIpv6AddressProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Ipv6Addresses" ([InstanceIpv6AddressProperty] -> (Key, Value))
-> Maybe [InstanceIpv6AddressProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [InstanceIpv6AddressProperty]
ipv6Addresses,
               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 -> LaunchTemplateSpecificationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"LaunchTemplate" (LaunchTemplateSpecificationProperty -> (Key, Value))
-> Maybe LaunchTemplateSpecificationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe LaunchTemplateSpecificationProperty
launchTemplate,
               Key -> [LicenseSpecificationProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"LicenseSpecifications"
                 ([LicenseSpecificationProperty] -> (Key, Value))
-> Maybe [LicenseSpecificationProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [LicenseSpecificationProperty]
licenseSpecifications,
               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 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
"Monitoring" (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)
monitoring,
               Key -> [NetworkInterfaceProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"NetworkInterfaces" ([NetworkInterfaceProperty] -> (Key, Value))
-> Maybe [NetworkInterfaceProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [NetworkInterfaceProperty]
networkInterfaces,
               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
"PlacementGroupName" (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)
placementGroupName,
               Key -> PrivateDnsNameOptionsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"PrivateDnsNameOptions"
                 (PrivateDnsNameOptionsProperty -> (Key, Value))
-> Maybe PrivateDnsNameOptionsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe PrivateDnsNameOptionsProperty
privateDnsNameOptions,
               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
"PrivateIpAddress" (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)
privateIpAddress,
               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
"PropagateTagsToVolumeOnCreation"
                 (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)
propagateTagsToVolumeOnCreation,
               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
"SecurityGroupIds" (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)
securityGroupIds,
               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 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
"SourceDestCheck" (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)
sourceDestCheck,
               Key -> [SsmAssociationProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SsmAssociations" ([SsmAssociationProperty] -> (Key, Value))
-> Maybe [SsmAssociationProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [SsmAssociationProperty]
ssmAssociations,
               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
"SubnetId" (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)
subnetId,
               Key -> [Tag] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Tags" ([Tag] -> (Key, Value)) -> Maybe [Tag] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags,
               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
"Tenancy" (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)
tenancy,
               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,
               Key -> [VolumeProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Volumes" ([VolumeProperty] -> (Key, Value))
-> Maybe [VolumeProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [VolumeProperty]
volumes]))
instance Property "AdditionalInfo" Instance where
  type PropertyType "AdditionalInfo" Instance = Value Prelude.Text
  set :: PropertyType "AdditionalInfo" Instance -> Instance -> Instance
set PropertyType "AdditionalInfo" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {additionalInfo :: Maybe (Value Text)
additionalInfo = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "AdditionalInfo" Instance
Value Text
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "Affinity" Instance where
  type PropertyType "Affinity" Instance = Value Prelude.Text
  set :: PropertyType "Affinity" Instance -> Instance -> Instance
set PropertyType "Affinity" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {affinity :: Maybe (Value Text)
affinity = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Affinity" Instance
Value Text
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "AvailabilityZone" Instance where
  type PropertyType "AvailabilityZone" Instance = Value Prelude.Text
  set :: PropertyType "AvailabilityZone" Instance -> Instance -> Instance
set PropertyType "AvailabilityZone" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {availabilityZone :: Maybe (Value Text)
availabilityZone = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "AvailabilityZone" Instance
Value Text
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "BlockDeviceMappings" Instance where
  type PropertyType "BlockDeviceMappings" Instance = [BlockDeviceMappingProperty]
  set :: PropertyType "BlockDeviceMappings" Instance -> Instance -> Instance
set PropertyType "BlockDeviceMappings" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {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" Instance
newValue, Maybe [Tag]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "CpuOptions" Instance where
  type PropertyType "CpuOptions" Instance = CpuOptionsProperty
  set :: PropertyType "CpuOptions" Instance -> Instance -> Instance
set PropertyType "CpuOptions" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {cpuOptions :: Maybe CpuOptionsProperty
cpuOptions = CpuOptionsProperty -> Maybe CpuOptionsProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "CpuOptions" Instance
CpuOptionsProperty
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "CreditSpecification" Instance where
  type PropertyType "CreditSpecification" Instance = CreditSpecificationProperty
  set :: PropertyType "CreditSpecification" Instance -> Instance -> Instance
set PropertyType "CreditSpecification" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {creditSpecification :: Maybe CreditSpecificationProperty
creditSpecification = CreditSpecificationProperty -> Maybe CreditSpecificationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "CreditSpecification" Instance
CreditSpecificationProperty
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "DisableApiTermination" Instance where
  type PropertyType "DisableApiTermination" Instance = Value Prelude.Bool
  set :: PropertyType "DisableApiTermination" Instance
-> Instance -> Instance
set PropertyType "DisableApiTermination" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {disableApiTermination :: Maybe (Value Bool)
disableApiTermination = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "DisableApiTermination" Instance
Value Bool
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "EbsOptimized" Instance where
  type PropertyType "EbsOptimized" Instance = Value Prelude.Bool
  set :: PropertyType "EbsOptimized" Instance -> Instance -> Instance
set PropertyType "EbsOptimized" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {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" Instance
Value Bool
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "ElasticGpuSpecifications" Instance where
  type PropertyType "ElasticGpuSpecifications" Instance = [ElasticGpuSpecificationProperty]
  set :: PropertyType "ElasticGpuSpecifications" Instance
-> Instance -> Instance
set PropertyType "ElasticGpuSpecifications" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticGpuSpecifications = [ElasticGpuSpecificationProperty]
-> Maybe [ElasticGpuSpecificationProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [ElasticGpuSpecificationProperty]
PropertyType "ElasticGpuSpecifications" Instance
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "ElasticInferenceAccelerators" Instance where
  type PropertyType "ElasticInferenceAccelerators" Instance = [ElasticInferenceAcceleratorProperty]
  set :: PropertyType "ElasticInferenceAccelerators" Instance
-> Instance -> Instance
set PropertyType "ElasticInferenceAccelerators" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance
        {elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
elasticInferenceAccelerators = [ElasticInferenceAcceleratorProperty]
-> Maybe [ElasticInferenceAcceleratorProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [ElasticInferenceAcceleratorProperty]
PropertyType "ElasticInferenceAccelerators" Instance
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "EnclaveOptions" Instance where
  type PropertyType "EnclaveOptions" Instance = EnclaveOptionsProperty
  set :: PropertyType "EnclaveOptions" Instance -> Instance -> Instance
set PropertyType "EnclaveOptions" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {enclaveOptions :: Maybe EnclaveOptionsProperty
enclaveOptions = EnclaveOptionsProperty -> Maybe EnclaveOptionsProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "EnclaveOptions" Instance
EnclaveOptionsProperty
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "HibernationOptions" Instance where
  type PropertyType "HibernationOptions" Instance = HibernationOptionsProperty
  set :: PropertyType "HibernationOptions" Instance -> Instance -> Instance
set PropertyType "HibernationOptions" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {hibernationOptions :: Maybe HibernationOptionsProperty
hibernationOptions = HibernationOptionsProperty -> Maybe HibernationOptionsProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "HibernationOptions" Instance
HibernationOptionsProperty
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "HostId" Instance where
  type PropertyType "HostId" Instance = Value Prelude.Text
  set :: PropertyType "HostId" Instance -> Instance -> Instance
set PropertyType "HostId" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {hostId :: Maybe (Value Text)
hostId = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "HostId" Instance
Value Text
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "HostResourceGroupArn" Instance where
  type PropertyType "HostResourceGroupArn" Instance = Value Prelude.Text
  set :: PropertyType "HostResourceGroupArn" Instance
-> Instance -> Instance
set PropertyType "HostResourceGroupArn" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {hostResourceGroupArn :: Maybe (Value Text)
hostResourceGroupArn = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "HostResourceGroupArn" Instance
Value Text
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "IamInstanceProfile" Instance where
  type PropertyType "IamInstanceProfile" Instance = Value Prelude.Text
  set :: PropertyType "IamInstanceProfile" Instance -> Instance -> Instance
set PropertyType "IamInstanceProfile" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {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" Instance
Value Text
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "ImageId" Instance where
  type PropertyType "ImageId" Instance = Value Prelude.Text
  set :: PropertyType "ImageId" Instance -> Instance -> Instance
set PropertyType "ImageId" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {imageId :: Maybe (Value Text)
imageId = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ImageId" Instance
Value Text
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "InstanceInitiatedShutdownBehavior" Instance where
  type PropertyType "InstanceInitiatedShutdownBehavior" Instance = Value Prelude.Text
  set :: PropertyType "InstanceInitiatedShutdownBehavior" Instance
-> Instance -> Instance
set PropertyType "InstanceInitiatedShutdownBehavior" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance
        {instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceInitiatedShutdownBehavior = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "InstanceInitiatedShutdownBehavior" Instance
Value Text
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "InstanceType" Instance where
  type PropertyType "InstanceType" Instance = Value Prelude.Text
  set :: PropertyType "InstanceType" Instance -> Instance -> Instance
set PropertyType "InstanceType" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {instanceType :: Maybe (Value Text)
instanceType = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "InstanceType" Instance
Value Text
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "Ipv6AddressCount" Instance where
  type PropertyType "Ipv6AddressCount" Instance = Value Prelude.Integer
  set :: PropertyType "Ipv6AddressCount" Instance -> Instance -> Instance
set PropertyType "Ipv6AddressCount" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {ipv6AddressCount :: Maybe (Value Integer)
ipv6AddressCount = Value Integer -> Maybe (Value Integer)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Ipv6AddressCount" Instance
Value Integer
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "Ipv6Addresses" Instance where
  type PropertyType "Ipv6Addresses" Instance = [InstanceIpv6AddressProperty]
  set :: PropertyType "Ipv6Addresses" Instance -> Instance -> Instance
set PropertyType "Ipv6Addresses" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
ipv6Addresses = [InstanceIpv6AddressProperty]
-> Maybe [InstanceIpv6AddressProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [InstanceIpv6AddressProperty]
PropertyType "Ipv6Addresses" Instance
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "KernelId" Instance where
  type PropertyType "KernelId" Instance = Value Prelude.Text
  set :: PropertyType "KernelId" Instance -> Instance -> Instance
set PropertyType "KernelId" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {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" Instance
Value Text
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "KeyName" Instance where
  type PropertyType "KeyName" Instance = Value Prelude.Text
  set :: PropertyType "KeyName" Instance -> Instance -> Instance
set PropertyType "KeyName" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {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" Instance
Value Text
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "LaunchTemplate" Instance where
  type PropertyType "LaunchTemplate" Instance = LaunchTemplateSpecificationProperty
  set :: PropertyType "LaunchTemplate" Instance -> Instance -> Instance
set PropertyType "LaunchTemplate" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {launchTemplate :: Maybe LaunchTemplateSpecificationProperty
launchTemplate = LaunchTemplateSpecificationProperty
-> Maybe LaunchTemplateSpecificationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "LaunchTemplate" Instance
LaunchTemplateSpecificationProperty
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "LicenseSpecifications" Instance where
  type PropertyType "LicenseSpecifications" Instance = [LicenseSpecificationProperty]
  set :: PropertyType "LicenseSpecifications" Instance
-> Instance -> Instance
set PropertyType "LicenseSpecifications" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {licenseSpecifications :: Maybe [LicenseSpecificationProperty]
licenseSpecifications = [LicenseSpecificationProperty]
-> Maybe [LicenseSpecificationProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [LicenseSpecificationProperty]
PropertyType "LicenseSpecifications" Instance
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "MetadataOptions" Instance where
  type PropertyType "MetadataOptions" Instance = MetadataOptionsProperty
  set :: PropertyType "MetadataOptions" Instance -> Instance -> Instance
set PropertyType "MetadataOptions" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {metadataOptions :: Maybe MetadataOptionsProperty
metadataOptions = MetadataOptionsProperty -> Maybe MetadataOptionsProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "MetadataOptions" Instance
MetadataOptionsProperty
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "Monitoring" Instance where
  type PropertyType "Monitoring" Instance = Value Prelude.Bool
  set :: PropertyType "Monitoring" Instance -> Instance -> Instance
set PropertyType "Monitoring" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {monitoring :: Maybe (Value Bool)
monitoring = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Monitoring" Instance
Value Bool
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "NetworkInterfaces" Instance where
  type PropertyType "NetworkInterfaces" Instance = [NetworkInterfaceProperty]
  set :: PropertyType "NetworkInterfaces" Instance -> Instance -> Instance
set PropertyType "NetworkInterfaces" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {networkInterfaces :: Maybe [NetworkInterfaceProperty]
networkInterfaces = [NetworkInterfaceProperty] -> Maybe [NetworkInterfaceProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [NetworkInterfaceProperty]
PropertyType "NetworkInterfaces" Instance
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "PlacementGroupName" Instance where
  type PropertyType "PlacementGroupName" Instance = Value Prelude.Text
  set :: PropertyType "PlacementGroupName" Instance -> Instance -> Instance
set PropertyType "PlacementGroupName" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {placementGroupName :: Maybe (Value Text)
placementGroupName = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "PlacementGroupName" Instance
Value Text
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "PrivateDnsNameOptions" Instance where
  type PropertyType "PrivateDnsNameOptions" Instance = PrivateDnsNameOptionsProperty
  set :: PropertyType "PrivateDnsNameOptions" Instance
-> Instance -> Instance
set PropertyType "PrivateDnsNameOptions" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateDnsNameOptions = PrivateDnsNameOptionsProperty
-> Maybe PrivateDnsNameOptionsProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "PrivateDnsNameOptions" Instance
PrivateDnsNameOptionsProperty
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "PrivateIpAddress" Instance where
  type PropertyType "PrivateIpAddress" Instance = Value Prelude.Text
  set :: PropertyType "PrivateIpAddress" Instance -> Instance -> Instance
set PropertyType "PrivateIpAddress" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {privateIpAddress :: Maybe (Value Text)
privateIpAddress = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "PrivateIpAddress" Instance
Value Text
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "PropagateTagsToVolumeOnCreation" Instance where
  type PropertyType "PropagateTagsToVolumeOnCreation" Instance = Value Prelude.Bool
  set :: PropertyType "PropagateTagsToVolumeOnCreation" Instance
-> Instance -> Instance
set PropertyType "PropagateTagsToVolumeOnCreation" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance
        {propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
propagateTagsToVolumeOnCreation = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "PropagateTagsToVolumeOnCreation" Instance
Value Bool
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "RamdiskId" Instance where
  type PropertyType "RamdiskId" Instance = Value Prelude.Text
  set :: PropertyType "RamdiskId" Instance -> Instance -> Instance
set PropertyType "RamdiskId" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {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" Instance
Value Text
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "SecurityGroupIds" Instance where
  type PropertyType "SecurityGroupIds" Instance = ValueList Prelude.Text
  set :: PropertyType "SecurityGroupIds" Instance -> Instance -> Instance
set PropertyType "SecurityGroupIds" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {securityGroupIds :: Maybe (ValueList Text)
securityGroupIds = ValueList Text -> Maybe (ValueList Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "SecurityGroupIds" Instance
ValueList Text
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "SecurityGroups" Instance where
  type PropertyType "SecurityGroups" Instance = ValueList Prelude.Text
  set :: PropertyType "SecurityGroups" Instance -> Instance -> Instance
set PropertyType "SecurityGroups" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {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" Instance
ValueList Text
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "SourceDestCheck" Instance where
  type PropertyType "SourceDestCheck" Instance = Value Prelude.Bool
  set :: PropertyType "SourceDestCheck" Instance -> Instance -> Instance
set PropertyType "SourceDestCheck" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {sourceDestCheck :: Maybe (Value Bool)
sourceDestCheck = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "SourceDestCheck" Instance
Value Bool
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "SsmAssociations" Instance where
  type PropertyType "SsmAssociations" Instance = [SsmAssociationProperty]
  set :: PropertyType "SsmAssociations" Instance -> Instance -> Instance
set PropertyType "SsmAssociations" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {ssmAssociations :: Maybe [SsmAssociationProperty]
ssmAssociations = [SsmAssociationProperty] -> Maybe [SsmAssociationProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [SsmAssociationProperty]
PropertyType "SsmAssociations" Instance
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "SubnetId" Instance where
  type PropertyType "SubnetId" Instance = Value Prelude.Text
  set :: PropertyType "SubnetId" Instance -> Instance -> Instance
set PropertyType "SubnetId" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {subnetId :: Maybe (Value Text)
subnetId = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "SubnetId" Instance
Value Text
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "Tags" Instance where
  type PropertyType "Tags" Instance = [Tag]
  set :: PropertyType "Tags" Instance -> Instance -> Instance
set PropertyType "Tags" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {tags :: Maybe [Tag]
tags = [Tag] -> Maybe [Tag]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [Tag]
PropertyType "Tags" Instance
newValue, Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "Tenancy" Instance where
  type PropertyType "Tenancy" Instance = Value Prelude.Text
  set :: PropertyType "Tenancy" Instance -> Instance -> Instance
set PropertyType "Tenancy" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {tenancy :: Maybe (Value Text)
tenancy = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Tenancy" Instance
Value Text
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "UserData" Instance where
  type PropertyType "UserData" Instance = Value Prelude.Text
  set :: PropertyType "UserData" Instance -> Instance -> Instance
set PropertyType "UserData" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {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" Instance
Value Text
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "Volumes" Instance where
  type PropertyType "Volumes" Instance = [VolumeProperty]
  set :: PropertyType "Volumes" Instance -> Instance -> Instance
set PropertyType "Volumes" Instance
newValue Instance {Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: Instance -> ()
additionalInfo :: Instance -> Maybe (Value Text)
affinity :: Instance -> Maybe (Value Text)
availabilityZone :: Instance -> Maybe (Value Text)
blockDeviceMappings :: Instance -> Maybe [BlockDeviceMappingProperty]
cpuOptions :: Instance -> Maybe CpuOptionsProperty
creditSpecification :: Instance -> Maybe CreditSpecificationProperty
disableApiTermination :: Instance -> Maybe (Value Bool)
ebsOptimized :: Instance -> Maybe (Value Bool)
elasticGpuSpecifications :: Instance -> Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Instance -> Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Instance -> Maybe EnclaveOptionsProperty
hibernationOptions :: Instance -> Maybe HibernationOptionsProperty
hostId :: Instance -> Maybe (Value Text)
hostResourceGroupArn :: Instance -> Maybe (Value Text)
iamInstanceProfile :: Instance -> Maybe (Value Text)
imageId :: Instance -> Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Instance -> Maybe (Value Text)
instanceType :: Instance -> Maybe (Value Text)
ipv6AddressCount :: Instance -> Maybe (Value Integer)
ipv6Addresses :: Instance -> Maybe [InstanceIpv6AddressProperty]
kernelId :: Instance -> Maybe (Value Text)
keyName :: Instance -> Maybe (Value Text)
launchTemplate :: Instance -> Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Instance -> Maybe [LicenseSpecificationProperty]
metadataOptions :: Instance -> Maybe MetadataOptionsProperty
monitoring :: Instance -> Maybe (Value Bool)
networkInterfaces :: Instance -> Maybe [NetworkInterfaceProperty]
placementGroupName :: Instance -> Maybe (Value Text)
privateDnsNameOptions :: Instance -> Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Instance -> Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Instance -> Maybe (Value Bool)
ramdiskId :: Instance -> Maybe (Value Text)
securityGroupIds :: Instance -> Maybe (ValueList Text)
securityGroups :: Instance -> Maybe (ValueList Text)
sourceDestCheck :: Instance -> Maybe (Value Bool)
ssmAssociations :: Instance -> Maybe [SsmAssociationProperty]
subnetId :: Instance -> Maybe (Value Text)
tags :: Instance -> Maybe [Tag]
tenancy :: Instance -> Maybe (Value Text)
userData :: Instance -> Maybe (Value Text)
volumes :: Instance -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = Instance {volumes :: Maybe [VolumeProperty]
volumes = [VolumeProperty] -> Maybe [VolumeProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [VolumeProperty]
PropertyType "Volumes" Instance
newValue, Maybe [Tag]
Maybe [BlockDeviceMappingProperty]
Maybe [ElasticGpuSpecificationProperty]
Maybe [ElasticInferenceAcceleratorProperty]
Maybe [InstanceIpv6AddressProperty]
Maybe [LicenseSpecificationProperty]
Maybe [NetworkInterfaceProperty]
Maybe [SsmAssociationProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe CpuOptionsProperty
Maybe CreditSpecificationProperty
Maybe EnclaveOptionsProperty
Maybe HibernationOptionsProperty
Maybe LaunchTemplateSpecificationProperty
Maybe MetadataOptionsProperty
Maybe PrivateDnsNameOptionsProperty
()
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
haddock_workaround_ :: ()
additionalInfo :: Maybe (Value Text)
affinity :: Maybe (Value Text)
availabilityZone :: Maybe (Value Text)
blockDeviceMappings :: Maybe [BlockDeviceMappingProperty]
cpuOptions :: Maybe CpuOptionsProperty
creditSpecification :: Maybe CreditSpecificationProperty
disableApiTermination :: Maybe (Value Bool)
ebsOptimized :: Maybe (Value Bool)
elasticGpuSpecifications :: Maybe [ElasticGpuSpecificationProperty]
elasticInferenceAccelerators :: Maybe [ElasticInferenceAcceleratorProperty]
enclaveOptions :: Maybe EnclaveOptionsProperty
hibernationOptions :: Maybe HibernationOptionsProperty
hostId :: Maybe (Value Text)
hostResourceGroupArn :: Maybe (Value Text)
iamInstanceProfile :: Maybe (Value Text)
imageId :: Maybe (Value Text)
instanceInitiatedShutdownBehavior :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
ipv6AddressCount :: Maybe (Value Integer)
ipv6Addresses :: Maybe [InstanceIpv6AddressProperty]
kernelId :: Maybe (Value Text)
keyName :: Maybe (Value Text)
launchTemplate :: Maybe LaunchTemplateSpecificationProperty
licenseSpecifications :: Maybe [LicenseSpecificationProperty]
metadataOptions :: Maybe MetadataOptionsProperty
monitoring :: Maybe (Value Bool)
networkInterfaces :: Maybe [NetworkInterfaceProperty]
placementGroupName :: Maybe (Value Text)
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsProperty
privateIpAddress :: Maybe (Value Text)
propagateTagsToVolumeOnCreation :: Maybe (Value Bool)
ramdiskId :: Maybe (Value Text)
securityGroupIds :: Maybe (ValueList Text)
securityGroups :: Maybe (ValueList Text)
sourceDestCheck :: Maybe (Value Bool)
ssmAssociations :: Maybe [SsmAssociationProperty]
subnetId :: Maybe (Value Text)
tags :: Maybe [Tag]
tenancy :: Maybe (Value Text)
userData :: Maybe (Value Text)
..}