{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module Network.AWS.EC2.Types.Product where
import Network.AWS.EC2.Internal
import Network.AWS.EC2.Types.Sum
import Network.AWS.Lens
import Network.AWS.Prelude
data AccountAttribute = AccountAttribute'
{ _aaAttributeValues :: !(Maybe [AccountAttributeValue])
, _aaAttributeName :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
accountAttribute
:: AccountAttribute
accountAttribute =
AccountAttribute' {_aaAttributeValues = Nothing, _aaAttributeName = Nothing}
aaAttributeValues :: Lens' AccountAttribute [AccountAttributeValue]
aaAttributeValues = lens _aaAttributeValues (\ s a -> s{_aaAttributeValues = a}) . _Default . _Coerce
aaAttributeName :: Lens' AccountAttribute (Maybe Text)
aaAttributeName = lens _aaAttributeName (\ s a -> s{_aaAttributeName = a})
instance FromXML AccountAttribute where
parseXML x
= AccountAttribute' <$>
(x .@? "attributeValueSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "attributeName")
instance Hashable AccountAttribute where
instance NFData AccountAttribute where
newtype AccountAttributeValue = AccountAttributeValue'
{ _aavAttributeValue :: Maybe Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
accountAttributeValue
:: AccountAttributeValue
accountAttributeValue = AccountAttributeValue' {_aavAttributeValue = Nothing}
aavAttributeValue :: Lens' AccountAttributeValue (Maybe Text)
aavAttributeValue = lens _aavAttributeValue (\ s a -> s{_aavAttributeValue = a})
instance FromXML AccountAttributeValue where
parseXML x
= AccountAttributeValue' <$> (x .@? "attributeValue")
instance Hashable AccountAttributeValue where
instance NFData AccountAttributeValue where
data ActiveInstance = ActiveInstance'
{ _aiInstanceId :: !(Maybe Text)
, _aiInstanceHealth :: !(Maybe InstanceHealthStatus)
, _aiInstanceType :: !(Maybe Text)
, _aiSpotInstanceRequestId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
activeInstance
:: ActiveInstance
activeInstance =
ActiveInstance'
{ _aiInstanceId = Nothing
, _aiInstanceHealth = Nothing
, _aiInstanceType = Nothing
, _aiSpotInstanceRequestId = Nothing
}
aiInstanceId :: Lens' ActiveInstance (Maybe Text)
aiInstanceId = lens _aiInstanceId (\ s a -> s{_aiInstanceId = a})
aiInstanceHealth :: Lens' ActiveInstance (Maybe InstanceHealthStatus)
aiInstanceHealth = lens _aiInstanceHealth (\ s a -> s{_aiInstanceHealth = a})
aiInstanceType :: Lens' ActiveInstance (Maybe Text)
aiInstanceType = lens _aiInstanceType (\ s a -> s{_aiInstanceType = a})
aiSpotInstanceRequestId :: Lens' ActiveInstance (Maybe Text)
aiSpotInstanceRequestId = lens _aiSpotInstanceRequestId (\ s a -> s{_aiSpotInstanceRequestId = a})
instance FromXML ActiveInstance where
parseXML x
= ActiveInstance' <$>
(x .@? "instanceId") <*> (x .@? "instanceHealth") <*>
(x .@? "instanceType")
<*> (x .@? "spotInstanceRequestId")
instance Hashable ActiveInstance where
instance NFData ActiveInstance where
data Address = Address'
{ _aAssociationId :: !(Maybe Text)
, _aInstanceId :: !(Maybe Text)
, _aNetworkInterfaceOwnerId :: !(Maybe Text)
, _aAllocationId :: !(Maybe Text)
, _aDomain :: !(Maybe DomainType)
, _aNetworkInterfaceId :: !(Maybe Text)
, _aPrivateIPAddress :: !(Maybe Text)
, _aPublicIP :: !(Maybe Text)
, _aTags :: !(Maybe [Tag])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
address
:: Address
address =
Address'
{ _aAssociationId = Nothing
, _aInstanceId = Nothing
, _aNetworkInterfaceOwnerId = Nothing
, _aAllocationId = Nothing
, _aDomain = Nothing
, _aNetworkInterfaceId = Nothing
, _aPrivateIPAddress = Nothing
, _aPublicIP = Nothing
, _aTags = Nothing
}
aAssociationId :: Lens' Address (Maybe Text)
aAssociationId = lens _aAssociationId (\ s a -> s{_aAssociationId = a})
aInstanceId :: Lens' Address (Maybe Text)
aInstanceId = lens _aInstanceId (\ s a -> s{_aInstanceId = a})
aNetworkInterfaceOwnerId :: Lens' Address (Maybe Text)
aNetworkInterfaceOwnerId = lens _aNetworkInterfaceOwnerId (\ s a -> s{_aNetworkInterfaceOwnerId = a})
aAllocationId :: Lens' Address (Maybe Text)
aAllocationId = lens _aAllocationId (\ s a -> s{_aAllocationId = a})
aDomain :: Lens' Address (Maybe DomainType)
aDomain = lens _aDomain (\ s a -> s{_aDomain = a})
aNetworkInterfaceId :: Lens' Address (Maybe Text)
aNetworkInterfaceId = lens _aNetworkInterfaceId (\ s a -> s{_aNetworkInterfaceId = a})
aPrivateIPAddress :: Lens' Address (Maybe Text)
aPrivateIPAddress = lens _aPrivateIPAddress (\ s a -> s{_aPrivateIPAddress = a})
aPublicIP :: Lens' Address (Maybe Text)
aPublicIP = lens _aPublicIP (\ s a -> s{_aPublicIP = a})
aTags :: Lens' Address [Tag]
aTags = lens _aTags (\ s a -> s{_aTags = a}) . _Default . _Coerce
instance FromXML Address where
parseXML x
= Address' <$>
(x .@? "associationId") <*> (x .@? "instanceId") <*>
(x .@? "networkInterfaceOwnerId")
<*> (x .@? "allocationId")
<*> (x .@? "domain")
<*> (x .@? "networkInterfaceId")
<*> (x .@? "privateIpAddress")
<*> (x .@? "publicIp")
<*>
(x .@? "tagSet" .!@ mempty >>=
may (parseXMLList "item"))
instance Hashable Address where
instance NFData Address where
data AllowedPrincipal = AllowedPrincipal'
{ _apPrincipalType :: !(Maybe PrincipalType)
, _apPrincipal :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
allowedPrincipal
:: AllowedPrincipal
allowedPrincipal =
AllowedPrincipal' {_apPrincipalType = Nothing, _apPrincipal = Nothing}
apPrincipalType :: Lens' AllowedPrincipal (Maybe PrincipalType)
apPrincipalType = lens _apPrincipalType (\ s a -> s{_apPrincipalType = a})
apPrincipal :: Lens' AllowedPrincipal (Maybe Text)
apPrincipal = lens _apPrincipal (\ s a -> s{_apPrincipal = a})
instance FromXML AllowedPrincipal where
parseXML x
= AllowedPrincipal' <$>
(x .@? "principalType") <*> (x .@? "principal")
instance Hashable AllowedPrincipal where
instance NFData AllowedPrincipal where
newtype AttributeBooleanValue = AttributeBooleanValue'
{ _abvValue :: Maybe Bool
} deriving (Eq, Read, Show, Data, Typeable, Generic)
attributeBooleanValue
:: AttributeBooleanValue
attributeBooleanValue = AttributeBooleanValue' {_abvValue = Nothing}
abvValue :: Lens' AttributeBooleanValue (Maybe Bool)
abvValue = lens _abvValue (\ s a -> s{_abvValue = a})
instance FromXML AttributeBooleanValue where
parseXML x
= AttributeBooleanValue' <$> (x .@? "value")
instance Hashable AttributeBooleanValue where
instance NFData AttributeBooleanValue where
instance ToQuery AttributeBooleanValue where
toQuery AttributeBooleanValue'{..}
= mconcat ["Value" =: _abvValue]
newtype AttributeValue = AttributeValue'
{ _avValue :: Maybe Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
attributeValue
:: AttributeValue
attributeValue = AttributeValue' {_avValue = Nothing}
avValue :: Lens' AttributeValue (Maybe Text)
avValue = lens _avValue (\ s a -> s{_avValue = a})
instance FromXML AttributeValue where
parseXML x = AttributeValue' <$> (x .@? "value")
instance Hashable AttributeValue where
instance NFData AttributeValue where
instance ToQuery AttributeValue where
toQuery AttributeValue'{..}
= mconcat ["Value" =: _avValue]
data AvailabilityZone = AvailabilityZone'
{ _azState :: !(Maybe AvailabilityZoneState)
, _azRegionName :: !(Maybe Text)
, _azZoneName :: !(Maybe Text)
, _azMessages :: !(Maybe [AvailabilityZoneMessage])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
availabilityZone
:: AvailabilityZone
availabilityZone =
AvailabilityZone'
{ _azState = Nothing
, _azRegionName = Nothing
, _azZoneName = Nothing
, _azMessages = Nothing
}
azState :: Lens' AvailabilityZone (Maybe AvailabilityZoneState)
azState = lens _azState (\ s a -> s{_azState = a})
azRegionName :: Lens' AvailabilityZone (Maybe Text)
azRegionName = lens _azRegionName (\ s a -> s{_azRegionName = a})
azZoneName :: Lens' AvailabilityZone (Maybe Text)
azZoneName = lens _azZoneName (\ s a -> s{_azZoneName = a})
azMessages :: Lens' AvailabilityZone [AvailabilityZoneMessage]
azMessages = lens _azMessages (\ s a -> s{_azMessages = a}) . _Default . _Coerce
instance FromXML AvailabilityZone where
parseXML x
= AvailabilityZone' <$>
(x .@? "zoneState") <*> (x .@? "regionName") <*>
(x .@? "zoneName")
<*>
(x .@? "messageSet" .!@ mempty >>=
may (parseXMLList "item"))
instance Hashable AvailabilityZone where
instance NFData AvailabilityZone where
newtype AvailabilityZoneMessage = AvailabilityZoneMessage'
{ _azmMessage :: Maybe Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
availabilityZoneMessage
:: AvailabilityZoneMessage
availabilityZoneMessage = AvailabilityZoneMessage' {_azmMessage = Nothing}
azmMessage :: Lens' AvailabilityZoneMessage (Maybe Text)
azmMessage = lens _azmMessage (\ s a -> s{_azmMessage = a})
instance FromXML AvailabilityZoneMessage where
parseXML x
= AvailabilityZoneMessage' <$> (x .@? "message")
instance Hashable AvailabilityZoneMessage where
instance NFData AvailabilityZoneMessage where
data AvailableCapacity = AvailableCapacity'
{ _acAvailableInstanceCapacity :: !(Maybe [InstanceCapacity])
, _acAvailableVCPUs :: !(Maybe Int)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
availableCapacity
:: AvailableCapacity
availableCapacity =
AvailableCapacity'
{_acAvailableInstanceCapacity = Nothing, _acAvailableVCPUs = Nothing}
acAvailableInstanceCapacity :: Lens' AvailableCapacity [InstanceCapacity]
acAvailableInstanceCapacity = lens _acAvailableInstanceCapacity (\ s a -> s{_acAvailableInstanceCapacity = a}) . _Default . _Coerce
acAvailableVCPUs :: Lens' AvailableCapacity (Maybe Int)
acAvailableVCPUs = lens _acAvailableVCPUs (\ s a -> s{_acAvailableVCPUs = a})
instance FromXML AvailableCapacity where
parseXML x
= AvailableCapacity' <$>
(x .@? "availableInstanceCapacity" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "availableVCpus")
instance Hashable AvailableCapacity where
instance NFData AvailableCapacity where
newtype BlobAttributeValue = BlobAttributeValue'
{ _bavValue :: Maybe Base64
} deriving (Eq, Read, Show, Data, Typeable, Generic)
blobAttributeValue
:: BlobAttributeValue
blobAttributeValue = BlobAttributeValue' {_bavValue = Nothing}
bavValue :: Lens' BlobAttributeValue (Maybe ByteString)
bavValue = lens _bavValue (\ s a -> s{_bavValue = a}) . mapping _Base64
instance Hashable BlobAttributeValue where
instance NFData BlobAttributeValue where
instance ToQuery BlobAttributeValue where
toQuery BlobAttributeValue'{..}
= mconcat ["Value" =: _bavValue]
data BlockDeviceMapping = BlockDeviceMapping'
{ _bdmVirtualName :: !(Maybe Text)
, _bdmNoDevice :: !(Maybe Text)
, _bdmEBS :: !(Maybe EBSBlockDevice)
, _bdmDeviceName :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
blockDeviceMapping
:: Text
-> BlockDeviceMapping
blockDeviceMapping pDeviceName_ =
BlockDeviceMapping'
{ _bdmVirtualName = Nothing
, _bdmNoDevice = Nothing
, _bdmEBS = Nothing
, _bdmDeviceName = pDeviceName_
}
bdmVirtualName :: Lens' BlockDeviceMapping (Maybe Text)
bdmVirtualName = lens _bdmVirtualName (\ s a -> s{_bdmVirtualName = a})
bdmNoDevice :: Lens' BlockDeviceMapping (Maybe Text)
bdmNoDevice = lens _bdmNoDevice (\ s a -> s{_bdmNoDevice = a})
bdmEBS :: Lens' BlockDeviceMapping (Maybe EBSBlockDevice)
bdmEBS = lens _bdmEBS (\ s a -> s{_bdmEBS = a})
bdmDeviceName :: Lens' BlockDeviceMapping Text
bdmDeviceName = lens _bdmDeviceName (\ s a -> s{_bdmDeviceName = a})
instance FromXML BlockDeviceMapping where
parseXML x
= BlockDeviceMapping' <$>
(x .@? "virtualName") <*> (x .@? "noDevice") <*>
(x .@? "ebs")
<*> (x .@ "deviceName")
instance Hashable BlockDeviceMapping where
instance NFData BlockDeviceMapping where
instance ToQuery BlockDeviceMapping where
toQuery BlockDeviceMapping'{..}
= mconcat
["VirtualName" =: _bdmVirtualName,
"NoDevice" =: _bdmNoDevice, "Ebs" =: _bdmEBS,
"DeviceName" =: _bdmDeviceName]
data BundleTask = BundleTask'
{ _btBundleTaskError :: !(Maybe BundleTaskError)
, _btBundleId :: !Text
, _btInstanceId :: !Text
, _btProgress :: !Text
, _btStartTime :: !ISO8601
, _btState :: !BundleTaskState
, _btStorage :: !Storage
, _btUpdateTime :: !ISO8601
} deriving (Eq, Read, Show, Data, Typeable, Generic)
bundleTask
:: Text
-> Text
-> Text
-> UTCTime
-> BundleTaskState
-> Storage
-> UTCTime
-> BundleTask
bundleTask pBundleId_ pInstanceId_ pProgress_ pStartTime_ pState_ pStorage_ pUpdateTime_ =
BundleTask'
{ _btBundleTaskError = Nothing
, _btBundleId = pBundleId_
, _btInstanceId = pInstanceId_
, _btProgress = pProgress_
, _btStartTime = _Time # pStartTime_
, _btState = pState_
, _btStorage = pStorage_
, _btUpdateTime = _Time # pUpdateTime_
}
btBundleTaskError :: Lens' BundleTask (Maybe BundleTaskError)
btBundleTaskError = lens _btBundleTaskError (\ s a -> s{_btBundleTaskError = a})
btBundleId :: Lens' BundleTask Text
btBundleId = lens _btBundleId (\ s a -> s{_btBundleId = a})
btInstanceId :: Lens' BundleTask Text
btInstanceId = lens _btInstanceId (\ s a -> s{_btInstanceId = a})
btProgress :: Lens' BundleTask Text
btProgress = lens _btProgress (\ s a -> s{_btProgress = a})
btStartTime :: Lens' BundleTask UTCTime
btStartTime = lens _btStartTime (\ s a -> s{_btStartTime = a}) . _Time
btState :: Lens' BundleTask BundleTaskState
btState = lens _btState (\ s a -> s{_btState = a})
btStorage :: Lens' BundleTask Storage
btStorage = lens _btStorage (\ s a -> s{_btStorage = a})
btUpdateTime :: Lens' BundleTask UTCTime
btUpdateTime = lens _btUpdateTime (\ s a -> s{_btUpdateTime = a}) . _Time
instance FromXML BundleTask where
parseXML x
= BundleTask' <$>
(x .@? "error") <*> (x .@ "bundleId") <*>
(x .@ "instanceId")
<*> (x .@ "progress")
<*> (x .@ "startTime")
<*> (x .@ "state")
<*> (x .@ "storage")
<*> (x .@ "updateTime")
instance Hashable BundleTask where
instance NFData BundleTask where
data BundleTaskError = BundleTaskError'
{ _bteCode :: !(Maybe Text)
, _bteMessage :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
bundleTaskError
:: BundleTaskError
bundleTaskError = BundleTaskError' {_bteCode = Nothing, _bteMessage = Nothing}
bteCode :: Lens' BundleTaskError (Maybe Text)
bteCode = lens _bteCode (\ s a -> s{_bteCode = a})
bteMessage :: Lens' BundleTaskError (Maybe Text)
bteMessage = lens _bteMessage (\ s a -> s{_bteMessage = a})
instance FromXML BundleTaskError where
parseXML x
= BundleTaskError' <$>
(x .@? "code") <*> (x .@? "message")
instance Hashable BundleTaskError where
instance NFData BundleTaskError where
data CPUOptions = CPUOptions'
{ _coCoreCount :: !(Maybe Int)
, _coThreadsPerCore :: !(Maybe Int)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
cpuOptions
:: CPUOptions
cpuOptions = CPUOptions' {_coCoreCount = Nothing, _coThreadsPerCore = Nothing}
coCoreCount :: Lens' CPUOptions (Maybe Int)
coCoreCount = lens _coCoreCount (\ s a -> s{_coCoreCount = a})
coThreadsPerCore :: Lens' CPUOptions (Maybe Int)
coThreadsPerCore = lens _coThreadsPerCore (\ s a -> s{_coThreadsPerCore = a})
instance FromXML CPUOptions where
parseXML x
= CPUOptions' <$>
(x .@? "coreCount") <*> (x .@? "threadsPerCore")
instance Hashable CPUOptions where
instance NFData CPUOptions where
data CPUOptionsRequest = CPUOptionsRequest'
{ _corCoreCount :: !(Maybe Int)
, _corThreadsPerCore :: !(Maybe Int)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
cpuOptionsRequest
:: CPUOptionsRequest
cpuOptionsRequest =
CPUOptionsRequest' {_corCoreCount = Nothing, _corThreadsPerCore = Nothing}
corCoreCount :: Lens' CPUOptionsRequest (Maybe Int)
corCoreCount = lens _corCoreCount (\ s a -> s{_corCoreCount = a})
corThreadsPerCore :: Lens' CPUOptionsRequest (Maybe Int)
corThreadsPerCore = lens _corThreadsPerCore (\ s a -> s{_corThreadsPerCore = a})
instance Hashable CPUOptionsRequest where
instance NFData CPUOptionsRequest where
instance ToQuery CPUOptionsRequest where
toQuery CPUOptionsRequest'{..}
= mconcat
["CoreCount" =: _corCoreCount,
"ThreadsPerCore" =: _corThreadsPerCore]
data CancelSpotFleetRequestsError = CancelSpotFleetRequestsError'
{ _csfreCode :: !CancelBatchErrorCode
, _csfreMessage :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
cancelSpotFleetRequestsError
:: CancelBatchErrorCode
-> Text
-> CancelSpotFleetRequestsError
cancelSpotFleetRequestsError pCode_ pMessage_ =
CancelSpotFleetRequestsError' {_csfreCode = pCode_, _csfreMessage = pMessage_}
csfreCode :: Lens' CancelSpotFleetRequestsError CancelBatchErrorCode
csfreCode = lens _csfreCode (\ s a -> s{_csfreCode = a})
csfreMessage :: Lens' CancelSpotFleetRequestsError Text
csfreMessage = lens _csfreMessage (\ s a -> s{_csfreMessage = a})
instance FromXML CancelSpotFleetRequestsError where
parseXML x
= CancelSpotFleetRequestsError' <$>
(x .@ "code") <*> (x .@ "message")
instance Hashable CancelSpotFleetRequestsError where
instance NFData CancelSpotFleetRequestsError where
data CancelSpotFleetRequestsErrorItem = CancelSpotFleetRequestsErrorItem'
{ _csfreiError :: !CancelSpotFleetRequestsError
, _csfreiSpotFleetRequestId :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
cancelSpotFleetRequestsErrorItem
:: CancelSpotFleetRequestsError
-> Text
-> CancelSpotFleetRequestsErrorItem
cancelSpotFleetRequestsErrorItem pError_ pSpotFleetRequestId_ =
CancelSpotFleetRequestsErrorItem'
{_csfreiError = pError_, _csfreiSpotFleetRequestId = pSpotFleetRequestId_}
csfreiError :: Lens' CancelSpotFleetRequestsErrorItem CancelSpotFleetRequestsError
csfreiError = lens _csfreiError (\ s a -> s{_csfreiError = a})
csfreiSpotFleetRequestId :: Lens' CancelSpotFleetRequestsErrorItem Text
csfreiSpotFleetRequestId = lens _csfreiSpotFleetRequestId (\ s a -> s{_csfreiSpotFleetRequestId = a})
instance FromXML CancelSpotFleetRequestsErrorItem
where
parseXML x
= CancelSpotFleetRequestsErrorItem' <$>
(x .@ "error") <*> (x .@ "spotFleetRequestId")
instance Hashable CancelSpotFleetRequestsErrorItem
where
instance NFData CancelSpotFleetRequestsErrorItem
where
data CancelSpotFleetRequestsSuccessItem = CancelSpotFleetRequestsSuccessItem'
{ _csfrsiCurrentSpotFleetRequestState :: !BatchState
, _csfrsiPreviousSpotFleetRequestState :: !BatchState
, _csfrsiSpotFleetRequestId :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
cancelSpotFleetRequestsSuccessItem
:: BatchState
-> BatchState
-> Text
-> CancelSpotFleetRequestsSuccessItem
cancelSpotFleetRequestsSuccessItem pCurrentSpotFleetRequestState_ pPreviousSpotFleetRequestState_ pSpotFleetRequestId_ =
CancelSpotFleetRequestsSuccessItem'
{ _csfrsiCurrentSpotFleetRequestState = pCurrentSpotFleetRequestState_
, _csfrsiPreviousSpotFleetRequestState = pPreviousSpotFleetRequestState_
, _csfrsiSpotFleetRequestId = pSpotFleetRequestId_
}
csfrsiCurrentSpotFleetRequestState :: Lens' CancelSpotFleetRequestsSuccessItem BatchState
csfrsiCurrentSpotFleetRequestState = lens _csfrsiCurrentSpotFleetRequestState (\ s a -> s{_csfrsiCurrentSpotFleetRequestState = a})
csfrsiPreviousSpotFleetRequestState :: Lens' CancelSpotFleetRequestsSuccessItem BatchState
csfrsiPreviousSpotFleetRequestState = lens _csfrsiPreviousSpotFleetRequestState (\ s a -> s{_csfrsiPreviousSpotFleetRequestState = a})
csfrsiSpotFleetRequestId :: Lens' CancelSpotFleetRequestsSuccessItem Text
csfrsiSpotFleetRequestId = lens _csfrsiSpotFleetRequestId (\ s a -> s{_csfrsiSpotFleetRequestId = a})
instance FromXML CancelSpotFleetRequestsSuccessItem
where
parseXML x
= CancelSpotFleetRequestsSuccessItem' <$>
(x .@ "currentSpotFleetRequestState") <*>
(x .@ "previousSpotFleetRequestState")
<*> (x .@ "spotFleetRequestId")
instance Hashable CancelSpotFleetRequestsSuccessItem
where
instance NFData CancelSpotFleetRequestsSuccessItem
where
data CancelledSpotInstanceRequest = CancelledSpotInstanceRequest'
{ _csirState :: !(Maybe CancelSpotInstanceRequestState)
, _csirSpotInstanceRequestId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
cancelledSpotInstanceRequest
:: CancelledSpotInstanceRequest
cancelledSpotInstanceRequest =
CancelledSpotInstanceRequest'
{_csirState = Nothing, _csirSpotInstanceRequestId = Nothing}
csirState :: Lens' CancelledSpotInstanceRequest (Maybe CancelSpotInstanceRequestState)
csirState = lens _csirState (\ s a -> s{_csirState = a})
csirSpotInstanceRequestId :: Lens' CancelledSpotInstanceRequest (Maybe Text)
csirSpotInstanceRequestId = lens _csirSpotInstanceRequestId (\ s a -> s{_csirSpotInstanceRequestId = a})
instance FromXML CancelledSpotInstanceRequest where
parseXML x
= CancelledSpotInstanceRequest' <$>
(x .@? "state") <*> (x .@? "spotInstanceRequestId")
instance Hashable CancelledSpotInstanceRequest where
instance NFData CancelledSpotInstanceRequest where
newtype CidrBlock = CidrBlock'
{ _cbCidrBlock :: Maybe Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
cidrBlock
:: CidrBlock
cidrBlock = CidrBlock' {_cbCidrBlock = Nothing}
cbCidrBlock :: Lens' CidrBlock (Maybe Text)
cbCidrBlock = lens _cbCidrBlock (\ s a -> s{_cbCidrBlock = a})
instance FromXML CidrBlock where
parseXML x = CidrBlock' <$> (x .@? "cidrBlock")
instance Hashable CidrBlock where
instance NFData CidrBlock where
data ClassicLinkDNSSupport = ClassicLinkDNSSupport'
{ _cldsVPCId :: !(Maybe Text)
, _cldsClassicLinkDNSSupported :: !(Maybe Bool)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
classicLinkDNSSupport
:: ClassicLinkDNSSupport
classicLinkDNSSupport =
ClassicLinkDNSSupport'
{_cldsVPCId = Nothing, _cldsClassicLinkDNSSupported = Nothing}
cldsVPCId :: Lens' ClassicLinkDNSSupport (Maybe Text)
cldsVPCId = lens _cldsVPCId (\ s a -> s{_cldsVPCId = a})
cldsClassicLinkDNSSupported :: Lens' ClassicLinkDNSSupport (Maybe Bool)
cldsClassicLinkDNSSupported = lens _cldsClassicLinkDNSSupported (\ s a -> s{_cldsClassicLinkDNSSupported = a})
instance FromXML ClassicLinkDNSSupport where
parseXML x
= ClassicLinkDNSSupport' <$>
(x .@? "vpcId") <*> (x .@? "classicLinkDnsSupported")
instance Hashable ClassicLinkDNSSupport where
instance NFData ClassicLinkDNSSupport where
data ClassicLinkInstance = ClassicLinkInstance'
{ _cliInstanceId :: !(Maybe Text)
, _cliGroups :: !(Maybe [GroupIdentifier])
, _cliVPCId :: !(Maybe Text)
, _cliTags :: !(Maybe [Tag])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
classicLinkInstance
:: ClassicLinkInstance
classicLinkInstance =
ClassicLinkInstance'
{ _cliInstanceId = Nothing
, _cliGroups = Nothing
, _cliVPCId = Nothing
, _cliTags = Nothing
}
cliInstanceId :: Lens' ClassicLinkInstance (Maybe Text)
cliInstanceId = lens _cliInstanceId (\ s a -> s{_cliInstanceId = a})
cliGroups :: Lens' ClassicLinkInstance [GroupIdentifier]
cliGroups = lens _cliGroups (\ s a -> s{_cliGroups = a}) . _Default . _Coerce
cliVPCId :: Lens' ClassicLinkInstance (Maybe Text)
cliVPCId = lens _cliVPCId (\ s a -> s{_cliVPCId = a})
cliTags :: Lens' ClassicLinkInstance [Tag]
cliTags = lens _cliTags (\ s a -> s{_cliTags = a}) . _Default . _Coerce
instance FromXML ClassicLinkInstance where
parseXML x
= ClassicLinkInstance' <$>
(x .@? "instanceId") <*>
(x .@? "groupSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "vpcId")
<*>
(x .@? "tagSet" .!@ mempty >>=
may (parseXMLList "item"))
instance Hashable ClassicLinkInstance where
instance NFData ClassicLinkInstance where
newtype ClassicLoadBalancer = ClassicLoadBalancer'
{ _clbName :: Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
classicLoadBalancer
:: Text
-> ClassicLoadBalancer
classicLoadBalancer pName_ = ClassicLoadBalancer' {_clbName = pName_}
clbName :: Lens' ClassicLoadBalancer Text
clbName = lens _clbName (\ s a -> s{_clbName = a})
instance FromXML ClassicLoadBalancer where
parseXML x = ClassicLoadBalancer' <$> (x .@ "name")
instance Hashable ClassicLoadBalancer where
instance NFData ClassicLoadBalancer where
instance ToQuery ClassicLoadBalancer where
toQuery ClassicLoadBalancer'{..}
= mconcat ["Name" =: _clbName]
newtype ClassicLoadBalancersConfig = ClassicLoadBalancersConfig'
{ _clbcClassicLoadBalancers :: List1 ClassicLoadBalancer
} deriving (Eq, Read, Show, Data, Typeable, Generic)
classicLoadBalancersConfig
:: NonEmpty ClassicLoadBalancer
-> ClassicLoadBalancersConfig
classicLoadBalancersConfig pClassicLoadBalancers_ =
ClassicLoadBalancersConfig'
{_clbcClassicLoadBalancers = _List1 # pClassicLoadBalancers_}
clbcClassicLoadBalancers :: Lens' ClassicLoadBalancersConfig (NonEmpty ClassicLoadBalancer)
clbcClassicLoadBalancers = lens _clbcClassicLoadBalancers (\ s a -> s{_clbcClassicLoadBalancers = a}) . _List1
instance FromXML ClassicLoadBalancersConfig where
parseXML x
= ClassicLoadBalancersConfig' <$>
(x .@? "classicLoadBalancers" .!@ mempty >>=
parseXMLList1 "item")
instance Hashable ClassicLoadBalancersConfig where
instance NFData ClassicLoadBalancersConfig where
instance ToQuery ClassicLoadBalancersConfig where
toQuery ClassicLoadBalancersConfig'{..}
= mconcat
[toQueryList "ClassicLoadBalancers"
_clbcClassicLoadBalancers]
data ClientData = ClientData'
{ _cdUploadStart :: !(Maybe ISO8601)
, _cdUploadSize :: !(Maybe Double)
, _cdUploadEnd :: !(Maybe ISO8601)
, _cdComment :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
clientData
:: ClientData
clientData =
ClientData'
{ _cdUploadStart = Nothing
, _cdUploadSize = Nothing
, _cdUploadEnd = Nothing
, _cdComment = Nothing
}
cdUploadStart :: Lens' ClientData (Maybe UTCTime)
cdUploadStart = lens _cdUploadStart (\ s a -> s{_cdUploadStart = a}) . mapping _Time
cdUploadSize :: Lens' ClientData (Maybe Double)
cdUploadSize = lens _cdUploadSize (\ s a -> s{_cdUploadSize = a})
cdUploadEnd :: Lens' ClientData (Maybe UTCTime)
cdUploadEnd = lens _cdUploadEnd (\ s a -> s{_cdUploadEnd = a}) . mapping _Time
cdComment :: Lens' ClientData (Maybe Text)
cdComment = lens _cdComment (\ s a -> s{_cdComment = a})
instance Hashable ClientData where
instance NFData ClientData where
instance ToQuery ClientData where
toQuery ClientData'{..}
= mconcat
["UploadStart" =: _cdUploadStart,
"UploadSize" =: _cdUploadSize,
"UploadEnd" =: _cdUploadEnd, "Comment" =: _cdComment]
data ConnectionNotification = ConnectionNotification'
{ _cnConnectionNotificationState :: !(Maybe ConnectionNotificationState)
, _cnConnectionNotificationType :: !(Maybe ConnectionNotificationType)
, _cnConnectionEvents :: !(Maybe [Text])
, _cnServiceId :: !(Maybe Text)
, _cnVPCEndpointId :: !(Maybe Text)
, _cnConnectionNotificationId :: !(Maybe Text)
, _cnConnectionNotificationARN :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
connectionNotification
:: ConnectionNotification
connectionNotification =
ConnectionNotification'
{ _cnConnectionNotificationState = Nothing
, _cnConnectionNotificationType = Nothing
, _cnConnectionEvents = Nothing
, _cnServiceId = Nothing
, _cnVPCEndpointId = Nothing
, _cnConnectionNotificationId = Nothing
, _cnConnectionNotificationARN = Nothing
}
cnConnectionNotificationState :: Lens' ConnectionNotification (Maybe ConnectionNotificationState)
cnConnectionNotificationState = lens _cnConnectionNotificationState (\ s a -> s{_cnConnectionNotificationState = a})
cnConnectionNotificationType :: Lens' ConnectionNotification (Maybe ConnectionNotificationType)
cnConnectionNotificationType = lens _cnConnectionNotificationType (\ s a -> s{_cnConnectionNotificationType = a})
cnConnectionEvents :: Lens' ConnectionNotification [Text]
cnConnectionEvents = lens _cnConnectionEvents (\ s a -> s{_cnConnectionEvents = a}) . _Default . _Coerce
cnServiceId :: Lens' ConnectionNotification (Maybe Text)
cnServiceId = lens _cnServiceId (\ s a -> s{_cnServiceId = a})
cnVPCEndpointId :: Lens' ConnectionNotification (Maybe Text)
cnVPCEndpointId = lens _cnVPCEndpointId (\ s a -> s{_cnVPCEndpointId = a})
cnConnectionNotificationId :: Lens' ConnectionNotification (Maybe Text)
cnConnectionNotificationId = lens _cnConnectionNotificationId (\ s a -> s{_cnConnectionNotificationId = a})
cnConnectionNotificationARN :: Lens' ConnectionNotification (Maybe Text)
cnConnectionNotificationARN = lens _cnConnectionNotificationARN (\ s a -> s{_cnConnectionNotificationARN = a})
instance FromXML ConnectionNotification where
parseXML x
= ConnectionNotification' <$>
(x .@? "connectionNotificationState") <*>
(x .@? "connectionNotificationType")
<*>
(x .@? "connectionEvents" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "serviceId")
<*> (x .@? "vpcEndpointId")
<*> (x .@? "connectionNotificationId")
<*> (x .@? "connectionNotificationArn")
instance Hashable ConnectionNotification where
instance NFData ConnectionNotification where
data ConversionTask = ConversionTask'
{ _ctImportInstance :: !(Maybe ImportInstanceTaskDetails)
, _ctState :: !(Maybe ConversionTaskState)
, _ctStatusMessage :: !(Maybe Text)
, _ctImportVolume :: !(Maybe ImportVolumeTaskDetails)
, _ctConversionTaskId :: !(Maybe Text)
, _ctExpirationTime :: !(Maybe Text)
, _ctTags :: !(Maybe [Tag])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
conversionTask
:: ConversionTask
conversionTask =
ConversionTask'
{ _ctImportInstance = Nothing
, _ctState = Nothing
, _ctStatusMessage = Nothing
, _ctImportVolume = Nothing
, _ctConversionTaskId = Nothing
, _ctExpirationTime = Nothing
, _ctTags = Nothing
}
ctImportInstance :: Lens' ConversionTask (Maybe ImportInstanceTaskDetails)
ctImportInstance = lens _ctImportInstance (\ s a -> s{_ctImportInstance = a})
ctState :: Lens' ConversionTask (Maybe ConversionTaskState)
ctState = lens _ctState (\ s a -> s{_ctState = a})
ctStatusMessage :: Lens' ConversionTask (Maybe Text)
ctStatusMessage = lens _ctStatusMessage (\ s a -> s{_ctStatusMessage = a})
ctImportVolume :: Lens' ConversionTask (Maybe ImportVolumeTaskDetails)
ctImportVolume = lens _ctImportVolume (\ s a -> s{_ctImportVolume = a})
ctConversionTaskId :: Lens' ConversionTask (Maybe Text)
ctConversionTaskId = lens _ctConversionTaskId (\ s a -> s{_ctConversionTaskId = a})
ctExpirationTime :: Lens' ConversionTask (Maybe Text)
ctExpirationTime = lens _ctExpirationTime (\ s a -> s{_ctExpirationTime = a})
ctTags :: Lens' ConversionTask [Tag]
ctTags = lens _ctTags (\ s a -> s{_ctTags = a}) . _Default . _Coerce
instance FromXML ConversionTask where
parseXML x
= ConversionTask' <$>
(x .@? "importInstance") <*> (x .@? "state") <*>
(x .@? "statusMessage")
<*> (x .@? "importVolume")
<*> (x .@? "conversionTaskId")
<*> (x .@? "expirationTime")
<*>
(x .@? "tagSet" .!@ mempty >>=
may (parseXMLList "item"))
instance Hashable ConversionTask where
instance NFData ConversionTask where
data CreateVolumePermission = CreateVolumePermission'
{ _cvpGroup :: !(Maybe PermissionGroup)
, _cvpUserId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
createVolumePermission
:: CreateVolumePermission
createVolumePermission =
CreateVolumePermission' {_cvpGroup = Nothing, _cvpUserId = Nothing}
cvpGroup :: Lens' CreateVolumePermission (Maybe PermissionGroup)
cvpGroup = lens _cvpGroup (\ s a -> s{_cvpGroup = a})
cvpUserId :: Lens' CreateVolumePermission (Maybe Text)
cvpUserId = lens _cvpUserId (\ s a -> s{_cvpUserId = a})
instance FromXML CreateVolumePermission where
parseXML x
= CreateVolumePermission' <$>
(x .@? "group") <*> (x .@? "userId")
instance Hashable CreateVolumePermission where
instance NFData CreateVolumePermission where
instance ToQuery CreateVolumePermission where
toQuery CreateVolumePermission'{..}
= mconcat
["Group" =: _cvpGroup, "UserId" =: _cvpUserId]
data CreateVolumePermissionModifications = CreateVolumePermissionModifications'
{ _cvpmRemove :: !(Maybe [CreateVolumePermission])
, _cvpmAdd :: !(Maybe [CreateVolumePermission])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
createVolumePermissionModifications
:: CreateVolumePermissionModifications
createVolumePermissionModifications =
CreateVolumePermissionModifications'
{_cvpmRemove = Nothing, _cvpmAdd = Nothing}
cvpmRemove :: Lens' CreateVolumePermissionModifications [CreateVolumePermission]
cvpmRemove = lens _cvpmRemove (\ s a -> s{_cvpmRemove = a}) . _Default . _Coerce
cvpmAdd :: Lens' CreateVolumePermissionModifications [CreateVolumePermission]
cvpmAdd = lens _cvpmAdd (\ s a -> s{_cvpmAdd = a}) . _Default . _Coerce
instance Hashable CreateVolumePermissionModifications
where
instance NFData CreateVolumePermissionModifications
where
instance ToQuery CreateVolumePermissionModifications
where
toQuery CreateVolumePermissionModifications'{..}
= mconcat
[toQuery (toQueryList "Remove" <$> _cvpmRemove),
toQuery (toQueryList "Add" <$> _cvpmAdd)]
newtype CreditSpecification = CreditSpecification'
{ _csCPUCredits :: Maybe Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
creditSpecification
:: CreditSpecification
creditSpecification = CreditSpecification' {_csCPUCredits = Nothing}
csCPUCredits :: Lens' CreditSpecification (Maybe Text)
csCPUCredits = lens _csCPUCredits (\ s a -> s{_csCPUCredits = a})
instance FromXML CreditSpecification where
parseXML x
= CreditSpecification' <$> (x .@? "cpuCredits")
instance Hashable CreditSpecification where
instance NFData CreditSpecification where
newtype CreditSpecificationRequest = CreditSpecificationRequest'
{ _csrCPUCredits :: Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
creditSpecificationRequest
:: Text
-> CreditSpecificationRequest
creditSpecificationRequest pCPUCredits_ =
CreditSpecificationRequest' {_csrCPUCredits = pCPUCredits_}
csrCPUCredits :: Lens' CreditSpecificationRequest Text
csrCPUCredits = lens _csrCPUCredits (\ s a -> s{_csrCPUCredits = a})
instance Hashable CreditSpecificationRequest where
instance NFData CreditSpecificationRequest where
instance ToQuery CreditSpecificationRequest where
toQuery CreditSpecificationRequest'{..}
= mconcat ["CpuCredits" =: _csrCPUCredits]
data CustomerGateway = CustomerGateway'
{ _cgTags :: !(Maybe [Tag])
, _cgBGPASN :: !Text
, _cgCustomerGatewayId :: !Text
, _cgIPAddress :: !Text
, _cgState :: !Text
, _cgType :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
customerGateway
:: Text
-> Text
-> Text
-> Text
-> Text
-> CustomerGateway
customerGateway pBGPASN_ pCustomerGatewayId_ pIPAddress_ pState_ pType_ =
CustomerGateway'
{ _cgTags = Nothing
, _cgBGPASN = pBGPASN_
, _cgCustomerGatewayId = pCustomerGatewayId_
, _cgIPAddress = pIPAddress_
, _cgState = pState_
, _cgType = pType_
}
cgTags :: Lens' CustomerGateway [Tag]
cgTags = lens _cgTags (\ s a -> s{_cgTags = a}) . _Default . _Coerce
cgBGPASN :: Lens' CustomerGateway Text
cgBGPASN = lens _cgBGPASN (\ s a -> s{_cgBGPASN = a})
cgCustomerGatewayId :: Lens' CustomerGateway Text
cgCustomerGatewayId = lens _cgCustomerGatewayId (\ s a -> s{_cgCustomerGatewayId = a})
cgIPAddress :: Lens' CustomerGateway Text
cgIPAddress = lens _cgIPAddress (\ s a -> s{_cgIPAddress = a})
cgState :: Lens' CustomerGateway Text
cgState = lens _cgState (\ s a -> s{_cgState = a})
cgType :: Lens' CustomerGateway Text
cgType = lens _cgType (\ s a -> s{_cgType = a})
instance FromXML CustomerGateway where
parseXML x
= CustomerGateway' <$>
(x .@? "tagSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@ "bgpAsn")
<*> (x .@ "customerGatewayId")
<*> (x .@ "ipAddress")
<*> (x .@ "state")
<*> (x .@ "type")
instance Hashable CustomerGateway where
instance NFData CustomerGateway where
data DHCPConfiguration = DHCPConfiguration'
{ _dcValues :: !(Maybe [AttributeValue])
, _dcKey :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
dhcpConfiguration
:: DHCPConfiguration
dhcpConfiguration = DHCPConfiguration' {_dcValues = Nothing, _dcKey = Nothing}
dcValues :: Lens' DHCPConfiguration [AttributeValue]
dcValues = lens _dcValues (\ s a -> s{_dcValues = a}) . _Default . _Coerce
dcKey :: Lens' DHCPConfiguration (Maybe Text)
dcKey = lens _dcKey (\ s a -> s{_dcKey = a})
instance FromXML DHCPConfiguration where
parseXML x
= DHCPConfiguration' <$>
(x .@? "valueSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "key")
instance Hashable DHCPConfiguration where
instance NFData DHCPConfiguration where
data DHCPOptions = DHCPOptions'
{ _doDHCPConfigurations :: !(Maybe [DHCPConfiguration])
, _doDHCPOptionsId :: !(Maybe Text)
, _doTags :: !(Maybe [Tag])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
dhcpOptions
:: DHCPOptions
dhcpOptions =
DHCPOptions'
{ _doDHCPConfigurations = Nothing
, _doDHCPOptionsId = Nothing
, _doTags = Nothing
}
doDHCPConfigurations :: Lens' DHCPOptions [DHCPConfiguration]
doDHCPConfigurations = lens _doDHCPConfigurations (\ s a -> s{_doDHCPConfigurations = a}) . _Default . _Coerce
doDHCPOptionsId :: Lens' DHCPOptions (Maybe Text)
doDHCPOptionsId = lens _doDHCPOptionsId (\ s a -> s{_doDHCPOptionsId = a})
doTags :: Lens' DHCPOptions [Tag]
doTags = lens _doTags (\ s a -> s{_doTags = a}) . _Default . _Coerce
instance FromXML DHCPOptions where
parseXML x
= DHCPOptions' <$>
(x .@? "dhcpConfigurationSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "dhcpOptionsId")
<*>
(x .@? "tagSet" .!@ mempty >>=
may (parseXMLList "item"))
instance Hashable DHCPOptions where
instance NFData DHCPOptions where
data DNSEntry = DNSEntry'
{ _deHostedZoneId :: !(Maybe Text)
, _deDNSName :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
dnsEntry
:: DNSEntry
dnsEntry = DNSEntry' {_deHostedZoneId = Nothing, _deDNSName = Nothing}
deHostedZoneId :: Lens' DNSEntry (Maybe Text)
deHostedZoneId = lens _deHostedZoneId (\ s a -> s{_deHostedZoneId = a})
deDNSName :: Lens' DNSEntry (Maybe Text)
deDNSName = lens _deDNSName (\ s a -> s{_deDNSName = a})
instance FromXML DNSEntry where
parseXML x
= DNSEntry' <$>
(x .@? "hostedZoneId") <*> (x .@? "dnsName")
instance Hashable DNSEntry where
instance NFData DNSEntry where
data DeleteFleetError = DeleteFleetError'
{ _dfeCode :: !(Maybe DeleteFleetErrorCode)
, _dfeMessage :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
deleteFleetError
:: DeleteFleetError
deleteFleetError = DeleteFleetError' {_dfeCode = Nothing, _dfeMessage = Nothing}
dfeCode :: Lens' DeleteFleetError (Maybe DeleteFleetErrorCode)
dfeCode = lens _dfeCode (\ s a -> s{_dfeCode = a})
dfeMessage :: Lens' DeleteFleetError (Maybe Text)
dfeMessage = lens _dfeMessage (\ s a -> s{_dfeMessage = a})
instance FromXML DeleteFleetError where
parseXML x
= DeleteFleetError' <$>
(x .@? "code") <*> (x .@? "message")
instance Hashable DeleteFleetError where
instance NFData DeleteFleetError where
data DeleteFleetErrorItem = DeleteFleetErrorItem'
{ _dfeiError :: !(Maybe DeleteFleetError)
, _dfeiFleetId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
deleteFleetErrorItem
:: DeleteFleetErrorItem
deleteFleetErrorItem =
DeleteFleetErrorItem' {_dfeiError = Nothing, _dfeiFleetId = Nothing}
dfeiError :: Lens' DeleteFleetErrorItem (Maybe DeleteFleetError)
dfeiError = lens _dfeiError (\ s a -> s{_dfeiError = a})
dfeiFleetId :: Lens' DeleteFleetErrorItem (Maybe Text)
dfeiFleetId = lens _dfeiFleetId (\ s a -> s{_dfeiFleetId = a})
instance FromXML DeleteFleetErrorItem where
parseXML x
= DeleteFleetErrorItem' <$>
(x .@? "error") <*> (x .@? "fleetId")
instance Hashable DeleteFleetErrorItem where
instance NFData DeleteFleetErrorItem where
data DeleteFleetSuccessItem = DeleteFleetSuccessItem'
{ _dfsiCurrentFleetState :: !(Maybe FleetStateCode)
, _dfsiPreviousFleetState :: !(Maybe FleetStateCode)
, _dfsiFleetId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
deleteFleetSuccessItem
:: DeleteFleetSuccessItem
deleteFleetSuccessItem =
DeleteFleetSuccessItem'
{ _dfsiCurrentFleetState = Nothing
, _dfsiPreviousFleetState = Nothing
, _dfsiFleetId = Nothing
}
dfsiCurrentFleetState :: Lens' DeleteFleetSuccessItem (Maybe FleetStateCode)
dfsiCurrentFleetState = lens _dfsiCurrentFleetState (\ s a -> s{_dfsiCurrentFleetState = a})
dfsiPreviousFleetState :: Lens' DeleteFleetSuccessItem (Maybe FleetStateCode)
dfsiPreviousFleetState = lens _dfsiPreviousFleetState (\ s a -> s{_dfsiPreviousFleetState = a})
dfsiFleetId :: Lens' DeleteFleetSuccessItem (Maybe Text)
dfsiFleetId = lens _dfsiFleetId (\ s a -> s{_dfsiFleetId = a})
instance FromXML DeleteFleetSuccessItem where
parseXML x
= DeleteFleetSuccessItem' <$>
(x .@? "currentFleetState") <*>
(x .@? "previousFleetState")
<*> (x .@? "fleetId")
instance Hashable DeleteFleetSuccessItem where
instance NFData DeleteFleetSuccessItem where
data DeleteLaunchTemplateVersionsResponseErrorItem = DeleteLaunchTemplateVersionsResponseErrorItem'
{ _dltvreiLaunchTemplateName :: !(Maybe Text)
, _dltvreiLaunchTemplateId :: !(Maybe Text)
, _dltvreiVersionNumber :: !(Maybe Integer)
, _dltvreiResponseError :: !(Maybe ResponseError)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
deleteLaunchTemplateVersionsResponseErrorItem
:: DeleteLaunchTemplateVersionsResponseErrorItem
deleteLaunchTemplateVersionsResponseErrorItem =
DeleteLaunchTemplateVersionsResponseErrorItem'
{ _dltvreiLaunchTemplateName = Nothing
, _dltvreiLaunchTemplateId = Nothing
, _dltvreiVersionNumber = Nothing
, _dltvreiResponseError = Nothing
}
dltvreiLaunchTemplateName :: Lens' DeleteLaunchTemplateVersionsResponseErrorItem (Maybe Text)
dltvreiLaunchTemplateName = lens _dltvreiLaunchTemplateName (\ s a -> s{_dltvreiLaunchTemplateName = a})
dltvreiLaunchTemplateId :: Lens' DeleteLaunchTemplateVersionsResponseErrorItem (Maybe Text)
dltvreiLaunchTemplateId = lens _dltvreiLaunchTemplateId (\ s a -> s{_dltvreiLaunchTemplateId = a})
dltvreiVersionNumber :: Lens' DeleteLaunchTemplateVersionsResponseErrorItem (Maybe Integer)
dltvreiVersionNumber = lens _dltvreiVersionNumber (\ s a -> s{_dltvreiVersionNumber = a})
dltvreiResponseError :: Lens' DeleteLaunchTemplateVersionsResponseErrorItem (Maybe ResponseError)
dltvreiResponseError = lens _dltvreiResponseError (\ s a -> s{_dltvreiResponseError = a})
instance FromXML
DeleteLaunchTemplateVersionsResponseErrorItem
where
parseXML x
= DeleteLaunchTemplateVersionsResponseErrorItem' <$>
(x .@? "launchTemplateName") <*>
(x .@? "launchTemplateId")
<*> (x .@? "versionNumber")
<*> (x .@? "responseError")
instance Hashable
DeleteLaunchTemplateVersionsResponseErrorItem
where
instance NFData
DeleteLaunchTemplateVersionsResponseErrorItem
where
data DeleteLaunchTemplateVersionsResponseSuccessItem = DeleteLaunchTemplateVersionsResponseSuccessItem'
{ _dltvrsiLaunchTemplateName :: !(Maybe Text)
, _dltvrsiLaunchTemplateId :: !(Maybe Text)
, _dltvrsiVersionNumber :: !(Maybe Integer)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
deleteLaunchTemplateVersionsResponseSuccessItem
:: DeleteLaunchTemplateVersionsResponseSuccessItem
deleteLaunchTemplateVersionsResponseSuccessItem =
DeleteLaunchTemplateVersionsResponseSuccessItem'
{ _dltvrsiLaunchTemplateName = Nothing
, _dltvrsiLaunchTemplateId = Nothing
, _dltvrsiVersionNumber = Nothing
}
dltvrsiLaunchTemplateName :: Lens' DeleteLaunchTemplateVersionsResponseSuccessItem (Maybe Text)
dltvrsiLaunchTemplateName = lens _dltvrsiLaunchTemplateName (\ s a -> s{_dltvrsiLaunchTemplateName = a})
dltvrsiLaunchTemplateId :: Lens' DeleteLaunchTemplateVersionsResponseSuccessItem (Maybe Text)
dltvrsiLaunchTemplateId = lens _dltvrsiLaunchTemplateId (\ s a -> s{_dltvrsiLaunchTemplateId = a})
dltvrsiVersionNumber :: Lens' DeleteLaunchTemplateVersionsResponseSuccessItem (Maybe Integer)
dltvrsiVersionNumber = lens _dltvrsiVersionNumber (\ s a -> s{_dltvrsiVersionNumber = a})
instance FromXML
DeleteLaunchTemplateVersionsResponseSuccessItem
where
parseXML x
= DeleteLaunchTemplateVersionsResponseSuccessItem'
<$>
(x .@? "launchTemplateName") <*>
(x .@? "launchTemplateId")
<*> (x .@? "versionNumber")
instance Hashable
DeleteLaunchTemplateVersionsResponseSuccessItem
where
instance NFData
DeleteLaunchTemplateVersionsResponseSuccessItem
where
data DiskImage = DiskImage'
{ _diImage :: !(Maybe DiskImageDetail)
, _diVolume :: !(Maybe VolumeDetail)
, _diDescription :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
diskImage
:: DiskImage
diskImage =
DiskImage' {_diImage = Nothing, _diVolume = Nothing, _diDescription = Nothing}
diImage :: Lens' DiskImage (Maybe DiskImageDetail)
diImage = lens _diImage (\ s a -> s{_diImage = a})
diVolume :: Lens' DiskImage (Maybe VolumeDetail)
diVolume = lens _diVolume (\ s a -> s{_diVolume = a})
diDescription :: Lens' DiskImage (Maybe Text)
diDescription = lens _diDescription (\ s a -> s{_diDescription = a})
instance Hashable DiskImage where
instance NFData DiskImage where
instance ToQuery DiskImage where
toQuery DiskImage'{..}
= mconcat
["Image" =: _diImage, "Volume" =: _diVolume,
"Description" =: _diDescription]
data DiskImageDescription = DiskImageDescription'
{ _dSize :: !(Maybe Integer)
, _dChecksum :: !(Maybe Text)
, _dFormat :: !(Maybe DiskImageFormat)
, _dImportManifestURL :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
diskImageDescription
:: DiskImageDescription
diskImageDescription =
DiskImageDescription'
{ _dSize = Nothing
, _dChecksum = Nothing
, _dFormat = Nothing
, _dImportManifestURL = Nothing
}
dSize :: Lens' DiskImageDescription (Maybe Integer)
dSize = lens _dSize (\ s a -> s{_dSize = a})
dChecksum :: Lens' DiskImageDescription (Maybe Text)
dChecksum = lens _dChecksum (\ s a -> s{_dChecksum = a})
dFormat :: Lens' DiskImageDescription (Maybe DiskImageFormat)
dFormat = lens _dFormat (\ s a -> s{_dFormat = a})
dImportManifestURL :: Lens' DiskImageDescription (Maybe Text)
dImportManifestURL = lens _dImportManifestURL (\ s a -> s{_dImportManifestURL = a})
instance FromXML DiskImageDescription where
parseXML x
= DiskImageDescription' <$>
(x .@? "size") <*> (x .@? "checksum") <*>
(x .@? "format")
<*> (x .@? "importManifestUrl")
instance Hashable DiskImageDescription where
instance NFData DiskImageDescription where
data DiskImageDetail = DiskImageDetail'
{ _didBytes :: !Integer
, _didFormat :: !DiskImageFormat
, _didImportManifestURL :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
diskImageDetail
:: Integer
-> DiskImageFormat
-> Text
-> DiskImageDetail
diskImageDetail pBytes_ pFormat_ pImportManifestURL_ =
DiskImageDetail'
{ _didBytes = pBytes_
, _didFormat = pFormat_
, _didImportManifestURL = pImportManifestURL_
}
didBytes :: Lens' DiskImageDetail Integer
didBytes = lens _didBytes (\ s a -> s{_didBytes = a})
didFormat :: Lens' DiskImageDetail DiskImageFormat
didFormat = lens _didFormat (\ s a -> s{_didFormat = a})
didImportManifestURL :: Lens' DiskImageDetail Text
didImportManifestURL = lens _didImportManifestURL (\ s a -> s{_didImportManifestURL = a})
instance Hashable DiskImageDetail where
instance NFData DiskImageDetail where
instance ToQuery DiskImageDetail where
toQuery DiskImageDetail'{..}
= mconcat
["Bytes" =: _didBytes, "Format" =: _didFormat,
"ImportManifestUrl" =: _didImportManifestURL]
data DiskImageVolumeDescription = DiskImageVolumeDescription'
{ _divdSize :: !(Maybe Integer)
, _divdId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
diskImageVolumeDescription
:: DiskImageVolumeDescription
diskImageVolumeDescription =
DiskImageVolumeDescription' {_divdSize = Nothing, _divdId = Nothing}
divdSize :: Lens' DiskImageVolumeDescription (Maybe Integer)
divdSize = lens _divdSize (\ s a -> s{_divdSize = a})
divdId :: Lens' DiskImageVolumeDescription (Maybe Text)
divdId = lens _divdId (\ s a -> s{_divdId = a})
instance FromXML DiskImageVolumeDescription where
parseXML x
= DiskImageVolumeDescription' <$>
(x .@? "size") <*> (x .@? "id")
instance Hashable DiskImageVolumeDescription where
instance NFData DiskImageVolumeDescription where
data EBSBlockDevice = EBSBlockDevice'
{ _ebdDeleteOnTermination :: !(Maybe Bool)
, _ebdVolumeSize :: !(Maybe Int)
, _ebdIOPS :: !(Maybe Int)
, _ebdEncrypted :: !(Maybe Bool)
, _ebdKMSKeyId :: !(Maybe Text)
, _ebdVolumeType :: !(Maybe VolumeType)
, _ebdSnapshotId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
ebsBlockDevice
:: EBSBlockDevice
ebsBlockDevice =
EBSBlockDevice'
{ _ebdDeleteOnTermination = Nothing
, _ebdVolumeSize = Nothing
, _ebdIOPS = Nothing
, _ebdEncrypted = Nothing
, _ebdKMSKeyId = Nothing
, _ebdVolumeType = Nothing
, _ebdSnapshotId = Nothing
}
ebdDeleteOnTermination :: Lens' EBSBlockDevice (Maybe Bool)
ebdDeleteOnTermination = lens _ebdDeleteOnTermination (\ s a -> s{_ebdDeleteOnTermination = a})
ebdVolumeSize :: Lens' EBSBlockDevice (Maybe Int)
ebdVolumeSize = lens _ebdVolumeSize (\ s a -> s{_ebdVolumeSize = a})
ebdIOPS :: Lens' EBSBlockDevice (Maybe Int)
ebdIOPS = lens _ebdIOPS (\ s a -> s{_ebdIOPS = a})
ebdEncrypted :: Lens' EBSBlockDevice (Maybe Bool)
ebdEncrypted = lens _ebdEncrypted (\ s a -> s{_ebdEncrypted = a})
ebdKMSKeyId :: Lens' EBSBlockDevice (Maybe Text)
ebdKMSKeyId = lens _ebdKMSKeyId (\ s a -> s{_ebdKMSKeyId = a})
ebdVolumeType :: Lens' EBSBlockDevice (Maybe VolumeType)
ebdVolumeType = lens _ebdVolumeType (\ s a -> s{_ebdVolumeType = a})
ebdSnapshotId :: Lens' EBSBlockDevice (Maybe Text)
ebdSnapshotId = lens _ebdSnapshotId (\ s a -> s{_ebdSnapshotId = a})
instance FromXML EBSBlockDevice where
parseXML x
= EBSBlockDevice' <$>
(x .@? "deleteOnTermination") <*>
(x .@? "volumeSize")
<*> (x .@? "iops")
<*> (x .@? "encrypted")
<*> (x .@? "KmsKeyId")
<*> (x .@? "volumeType")
<*> (x .@? "snapshotId")
instance Hashable EBSBlockDevice where
instance NFData EBSBlockDevice where
instance ToQuery EBSBlockDevice where
toQuery EBSBlockDevice'{..}
= mconcat
["DeleteOnTermination" =: _ebdDeleteOnTermination,
"VolumeSize" =: _ebdVolumeSize, "Iops" =: _ebdIOPS,
"Encrypted" =: _ebdEncrypted,
"KmsKeyId" =: _ebdKMSKeyId,
"VolumeType" =: _ebdVolumeType,
"SnapshotId" =: _ebdSnapshotId]
data EBSInstanceBlockDevice = EBSInstanceBlockDevice'
{ _eibdStatus :: !(Maybe AttachmentStatus)
, _eibdDeleteOnTermination :: !(Maybe Bool)
, _eibdVolumeId :: !(Maybe Text)
, _eibdAttachTime :: !(Maybe ISO8601)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
ebsInstanceBlockDevice
:: EBSInstanceBlockDevice
ebsInstanceBlockDevice =
EBSInstanceBlockDevice'
{ _eibdStatus = Nothing
, _eibdDeleteOnTermination = Nothing
, _eibdVolumeId = Nothing
, _eibdAttachTime = Nothing
}
eibdStatus :: Lens' EBSInstanceBlockDevice (Maybe AttachmentStatus)
eibdStatus = lens _eibdStatus (\ s a -> s{_eibdStatus = a})
eibdDeleteOnTermination :: Lens' EBSInstanceBlockDevice (Maybe Bool)
eibdDeleteOnTermination = lens _eibdDeleteOnTermination (\ s a -> s{_eibdDeleteOnTermination = a})
eibdVolumeId :: Lens' EBSInstanceBlockDevice (Maybe Text)
eibdVolumeId = lens _eibdVolumeId (\ s a -> s{_eibdVolumeId = a})
eibdAttachTime :: Lens' EBSInstanceBlockDevice (Maybe UTCTime)
eibdAttachTime = lens _eibdAttachTime (\ s a -> s{_eibdAttachTime = a}) . mapping _Time
instance FromXML EBSInstanceBlockDevice where
parseXML x
= EBSInstanceBlockDevice' <$>
(x .@? "status") <*> (x .@? "deleteOnTermination")
<*> (x .@? "volumeId")
<*> (x .@? "attachTime")
instance Hashable EBSInstanceBlockDevice where
instance NFData EBSInstanceBlockDevice where
data EBSInstanceBlockDeviceSpecification = EBSInstanceBlockDeviceSpecification'
{ _eibdsDeleteOnTermination :: !(Maybe Bool)
, _eibdsVolumeId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
ebsInstanceBlockDeviceSpecification
:: EBSInstanceBlockDeviceSpecification
ebsInstanceBlockDeviceSpecification =
EBSInstanceBlockDeviceSpecification'
{_eibdsDeleteOnTermination = Nothing, _eibdsVolumeId = Nothing}
eibdsDeleteOnTermination :: Lens' EBSInstanceBlockDeviceSpecification (Maybe Bool)
eibdsDeleteOnTermination = lens _eibdsDeleteOnTermination (\ s a -> s{_eibdsDeleteOnTermination = a})
eibdsVolumeId :: Lens' EBSInstanceBlockDeviceSpecification (Maybe Text)
eibdsVolumeId = lens _eibdsVolumeId (\ s a -> s{_eibdsVolumeId = a})
instance Hashable EBSInstanceBlockDeviceSpecification
where
instance NFData EBSInstanceBlockDeviceSpecification
where
instance ToQuery EBSInstanceBlockDeviceSpecification
where
toQuery EBSInstanceBlockDeviceSpecification'{..}
= mconcat
["DeleteOnTermination" =: _eibdsDeleteOnTermination,
"VolumeId" =: _eibdsVolumeId]
data EgressOnlyInternetGateway = EgressOnlyInternetGateway'
{ _eoigEgressOnlyInternetGatewayId :: !(Maybe Text)
, _eoigAttachments :: !(Maybe [InternetGatewayAttachment])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
egressOnlyInternetGateway
:: EgressOnlyInternetGateway
egressOnlyInternetGateway =
EgressOnlyInternetGateway'
{_eoigEgressOnlyInternetGatewayId = Nothing, _eoigAttachments = Nothing}
eoigEgressOnlyInternetGatewayId :: Lens' EgressOnlyInternetGateway (Maybe Text)
eoigEgressOnlyInternetGatewayId = lens _eoigEgressOnlyInternetGatewayId (\ s a -> s{_eoigEgressOnlyInternetGatewayId = a})
eoigAttachments :: Lens' EgressOnlyInternetGateway [InternetGatewayAttachment]
eoigAttachments = lens _eoigAttachments (\ s a -> s{_eoigAttachments = a}) . _Default . _Coerce
instance FromXML EgressOnlyInternetGateway where
parseXML x
= EgressOnlyInternetGateway' <$>
(x .@? "egressOnlyInternetGatewayId") <*>
(x .@? "attachmentSet" .!@ mempty >>=
may (parseXMLList "item"))
instance Hashable EgressOnlyInternetGateway where
instance NFData EgressOnlyInternetGateway where
data ElasticGpuAssociation = ElasticGpuAssociation'
{ _egaElasticGpuId :: !(Maybe Text)
, _egaElasticGpuAssociationId :: !(Maybe Text)
, _egaElasticGpuAssociationTime :: !(Maybe Text)
, _egaElasticGpuAssociationState :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
elasticGpuAssociation
:: ElasticGpuAssociation
elasticGpuAssociation =
ElasticGpuAssociation'
{ _egaElasticGpuId = Nothing
, _egaElasticGpuAssociationId = Nothing
, _egaElasticGpuAssociationTime = Nothing
, _egaElasticGpuAssociationState = Nothing
}
egaElasticGpuId :: Lens' ElasticGpuAssociation (Maybe Text)
egaElasticGpuId = lens _egaElasticGpuId (\ s a -> s{_egaElasticGpuId = a})
egaElasticGpuAssociationId :: Lens' ElasticGpuAssociation (Maybe Text)
egaElasticGpuAssociationId = lens _egaElasticGpuAssociationId (\ s a -> s{_egaElasticGpuAssociationId = a})
egaElasticGpuAssociationTime :: Lens' ElasticGpuAssociation (Maybe Text)
egaElasticGpuAssociationTime = lens _egaElasticGpuAssociationTime (\ s a -> s{_egaElasticGpuAssociationTime = a})
egaElasticGpuAssociationState :: Lens' ElasticGpuAssociation (Maybe Text)
egaElasticGpuAssociationState = lens _egaElasticGpuAssociationState (\ s a -> s{_egaElasticGpuAssociationState = a})
instance FromXML ElasticGpuAssociation where
parseXML x
= ElasticGpuAssociation' <$>
(x .@? "elasticGpuId") <*>
(x .@? "elasticGpuAssociationId")
<*> (x .@? "elasticGpuAssociationTime")
<*> (x .@? "elasticGpuAssociationState")
instance Hashable ElasticGpuAssociation where
instance NFData ElasticGpuAssociation where
newtype ElasticGpuHealth = ElasticGpuHealth'
{ _eghStatus :: Maybe ElasticGpuStatus
} deriving (Eq, Read, Show, Data, Typeable, Generic)
elasticGpuHealth
:: ElasticGpuHealth
elasticGpuHealth = ElasticGpuHealth' {_eghStatus = Nothing}
eghStatus :: Lens' ElasticGpuHealth (Maybe ElasticGpuStatus)
eghStatus = lens _eghStatus (\ s a -> s{_eghStatus = a})
instance FromXML ElasticGpuHealth where
parseXML x = ElasticGpuHealth' <$> (x .@? "status")
instance Hashable ElasticGpuHealth where
instance NFData ElasticGpuHealth where
newtype ElasticGpuSpecification = ElasticGpuSpecification'
{ _egsType :: Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
elasticGpuSpecification
:: Text
-> ElasticGpuSpecification
elasticGpuSpecification pType_ = ElasticGpuSpecification' {_egsType = pType_}
egsType :: Lens' ElasticGpuSpecification Text
egsType = lens _egsType (\ s a -> s{_egsType = a})
instance Hashable ElasticGpuSpecification where
instance NFData ElasticGpuSpecification where
instance ToQuery ElasticGpuSpecification where
toQuery ElasticGpuSpecification'{..}
= mconcat ["Type" =: _egsType]
newtype ElasticGpuSpecificationResponse = ElasticGpuSpecificationResponse'
{ _eType :: Maybe Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
elasticGpuSpecificationResponse
:: ElasticGpuSpecificationResponse
elasticGpuSpecificationResponse =
ElasticGpuSpecificationResponse' {_eType = Nothing}
eType :: Lens' ElasticGpuSpecificationResponse (Maybe Text)
eType = lens _eType (\ s a -> s{_eType = a})
instance FromXML ElasticGpuSpecificationResponse
where
parseXML x
= ElasticGpuSpecificationResponse' <$> (x .@? "type")
instance Hashable ElasticGpuSpecificationResponse
where
instance NFData ElasticGpuSpecificationResponse where
data ElasticGpus = ElasticGpus'
{ _egInstanceId :: !(Maybe Text)
, _egElasticGpuType :: !(Maybe Text)
, _egElasticGpuId :: !(Maybe Text)
, _egElasticGpuState :: !(Maybe ElasticGpuState)
, _egElasticGpuHealth :: !(Maybe ElasticGpuHealth)
, _egAvailabilityZone :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
elasticGpus
:: ElasticGpus
elasticGpus =
ElasticGpus'
{ _egInstanceId = Nothing
, _egElasticGpuType = Nothing
, _egElasticGpuId = Nothing
, _egElasticGpuState = Nothing
, _egElasticGpuHealth = Nothing
, _egAvailabilityZone = Nothing
}
egInstanceId :: Lens' ElasticGpus (Maybe Text)
egInstanceId = lens _egInstanceId (\ s a -> s{_egInstanceId = a})
egElasticGpuType :: Lens' ElasticGpus (Maybe Text)
egElasticGpuType = lens _egElasticGpuType (\ s a -> s{_egElasticGpuType = a})
egElasticGpuId :: Lens' ElasticGpus (Maybe Text)
egElasticGpuId = lens _egElasticGpuId (\ s a -> s{_egElasticGpuId = a})
egElasticGpuState :: Lens' ElasticGpus (Maybe ElasticGpuState)
egElasticGpuState = lens _egElasticGpuState (\ s a -> s{_egElasticGpuState = a})
egElasticGpuHealth :: Lens' ElasticGpus (Maybe ElasticGpuHealth)
egElasticGpuHealth = lens _egElasticGpuHealth (\ s a -> s{_egElasticGpuHealth = a})
egAvailabilityZone :: Lens' ElasticGpus (Maybe Text)
egAvailabilityZone = lens _egAvailabilityZone (\ s a -> s{_egAvailabilityZone = a})
instance FromXML ElasticGpus where
parseXML x
= ElasticGpus' <$>
(x .@? "instanceId") <*> (x .@? "elasticGpuType") <*>
(x .@? "elasticGpuId")
<*> (x .@? "elasticGpuState")
<*> (x .@? "elasticGpuHealth")
<*> (x .@? "availabilityZone")
instance Hashable ElasticGpus where
instance NFData ElasticGpus where
data EventInformation = EventInformation'
{ _eiInstanceId :: !(Maybe Text)
, _eiEventDescription :: !(Maybe Text)
, _eiEventSubType :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
eventInformation
:: EventInformation
eventInformation =
EventInformation'
{ _eiInstanceId = Nothing
, _eiEventDescription = Nothing
, _eiEventSubType = Nothing
}
eiInstanceId :: Lens' EventInformation (Maybe Text)
eiInstanceId = lens _eiInstanceId (\ s a -> s{_eiInstanceId = a})
eiEventDescription :: Lens' EventInformation (Maybe Text)
eiEventDescription = lens _eiEventDescription (\ s a -> s{_eiEventDescription = a})
eiEventSubType :: Lens' EventInformation (Maybe Text)
eiEventSubType = lens _eiEventSubType (\ s a -> s{_eiEventSubType = a})
instance FromXML EventInformation where
parseXML x
= EventInformation' <$>
(x .@? "instanceId") <*> (x .@? "eventDescription")
<*> (x .@? "eventSubType")
instance Hashable EventInformation where
instance NFData EventInformation where
data ExportTask = ExportTask'
{ _etDescription :: !Text
, _etExportTaskId :: !Text
, _etExportToS3Task :: !ExportToS3Task
, _etInstanceExportDetails :: !InstanceExportDetails
, _etState :: !ExportTaskState
, _etStatusMessage :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
exportTask
:: Text
-> Text
-> ExportToS3Task
-> InstanceExportDetails
-> ExportTaskState
-> Text
-> ExportTask
exportTask pDescription_ pExportTaskId_ pExportToS3Task_ pInstanceExportDetails_ pState_ pStatusMessage_ =
ExportTask'
{ _etDescription = pDescription_
, _etExportTaskId = pExportTaskId_
, _etExportToS3Task = pExportToS3Task_
, _etInstanceExportDetails = pInstanceExportDetails_
, _etState = pState_
, _etStatusMessage = pStatusMessage_
}
etDescription :: Lens' ExportTask Text
etDescription = lens _etDescription (\ s a -> s{_etDescription = a})
etExportTaskId :: Lens' ExportTask Text
etExportTaskId = lens _etExportTaskId (\ s a -> s{_etExportTaskId = a})
etExportToS3Task :: Lens' ExportTask ExportToS3Task
etExportToS3Task = lens _etExportToS3Task (\ s a -> s{_etExportToS3Task = a})
etInstanceExportDetails :: Lens' ExportTask InstanceExportDetails
etInstanceExportDetails = lens _etInstanceExportDetails (\ s a -> s{_etInstanceExportDetails = a})
etState :: Lens' ExportTask ExportTaskState
etState = lens _etState (\ s a -> s{_etState = a})
etStatusMessage :: Lens' ExportTask Text
etStatusMessage = lens _etStatusMessage (\ s a -> s{_etStatusMessage = a})
instance FromXML ExportTask where
parseXML x
= ExportTask' <$>
(x .@ "description") <*> (x .@ "exportTaskId") <*>
(x .@ "exportToS3")
<*> (x .@ "instanceExport")
<*> (x .@ "state")
<*> (x .@ "statusMessage")
instance Hashable ExportTask where
instance NFData ExportTask where
data ExportToS3Task = ExportToS3Task'
{ _etstS3Key :: !(Maybe Text)
, _etstContainerFormat :: !(Maybe ContainerFormat)
, _etstS3Bucket :: !(Maybe Text)
, _etstDiskImageFormat :: !(Maybe DiskImageFormat)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
exportToS3Task
:: ExportToS3Task
exportToS3Task =
ExportToS3Task'
{ _etstS3Key = Nothing
, _etstContainerFormat = Nothing
, _etstS3Bucket = Nothing
, _etstDiskImageFormat = Nothing
}
etstS3Key :: Lens' ExportToS3Task (Maybe Text)
etstS3Key = lens _etstS3Key (\ s a -> s{_etstS3Key = a})
etstContainerFormat :: Lens' ExportToS3Task (Maybe ContainerFormat)
etstContainerFormat = lens _etstContainerFormat (\ s a -> s{_etstContainerFormat = a})
etstS3Bucket :: Lens' ExportToS3Task (Maybe Text)
etstS3Bucket = lens _etstS3Bucket (\ s a -> s{_etstS3Bucket = a})
etstDiskImageFormat :: Lens' ExportToS3Task (Maybe DiskImageFormat)
etstDiskImageFormat = lens _etstDiskImageFormat (\ s a -> s{_etstDiskImageFormat = a})
instance FromXML ExportToS3Task where
parseXML x
= ExportToS3Task' <$>
(x .@? "s3Key") <*> (x .@? "containerFormat") <*>
(x .@? "s3Bucket")
<*> (x .@? "diskImageFormat")
instance Hashable ExportToS3Task where
instance NFData ExportToS3Task where
data ExportToS3TaskSpecification = ExportToS3TaskSpecification'
{ _etstsContainerFormat :: !(Maybe ContainerFormat)
, _etstsS3Prefix :: !(Maybe Text)
, _etstsS3Bucket :: !(Maybe Text)
, _etstsDiskImageFormat :: !(Maybe DiskImageFormat)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
exportToS3TaskSpecification
:: ExportToS3TaskSpecification
exportToS3TaskSpecification =
ExportToS3TaskSpecification'
{ _etstsContainerFormat = Nothing
, _etstsS3Prefix = Nothing
, _etstsS3Bucket = Nothing
, _etstsDiskImageFormat = Nothing
}
etstsContainerFormat :: Lens' ExportToS3TaskSpecification (Maybe ContainerFormat)
etstsContainerFormat = lens _etstsContainerFormat (\ s a -> s{_etstsContainerFormat = a})
etstsS3Prefix :: Lens' ExportToS3TaskSpecification (Maybe Text)
etstsS3Prefix = lens _etstsS3Prefix (\ s a -> s{_etstsS3Prefix = a})
etstsS3Bucket :: Lens' ExportToS3TaskSpecification (Maybe Text)
etstsS3Bucket = lens _etstsS3Bucket (\ s a -> s{_etstsS3Bucket = a})
etstsDiskImageFormat :: Lens' ExportToS3TaskSpecification (Maybe DiskImageFormat)
etstsDiskImageFormat = lens _etstsDiskImageFormat (\ s a -> s{_etstsDiskImageFormat = a})
instance Hashable ExportToS3TaskSpecification where
instance NFData ExportToS3TaskSpecification where
instance ToQuery ExportToS3TaskSpecification where
toQuery ExportToS3TaskSpecification'{..}
= mconcat
["ContainerFormat" =: _etstsContainerFormat,
"S3Prefix" =: _etstsS3Prefix,
"S3Bucket" =: _etstsS3Bucket,
"DiskImageFormat" =: _etstsDiskImageFormat]
data Filter = Filter'
{ _fValues :: !(Maybe [Text])
, _fName :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
filter'
:: Text
-> Filter
filter' pName_ = Filter' {_fValues = Nothing, _fName = pName_}
fValues :: Lens' Filter [Text]
fValues = lens _fValues (\ s a -> s{_fValues = a}) . _Default . _Coerce
fName :: Lens' Filter Text
fName = lens _fName (\ s a -> s{_fName = a})
instance Hashable Filter where
instance NFData Filter where
instance ToQuery Filter where
toQuery Filter'{..}
= mconcat
[toQuery (toQueryList "Value" <$> _fValues),
"Name" =: _fName]
data FleetData = FleetData'
{ _fdClientToken :: !(Maybe Text)
, _fdTargetCapacitySpecification :: !(Maybe TargetCapacitySpecification)
, _fdSpotOptions :: !(Maybe SpotOptions)
, _fdExcessCapacityTerminationPolicy :: !(Maybe FleetExcessCapacityTerminationPolicy)
, _fdFleetState :: !(Maybe FleetStateCode)
, _fdLaunchTemplateConfigs :: !(Maybe [FleetLaunchTemplateConfig])
, _fdValidUntil :: !(Maybe ISO8601)
, _fdTerminateInstancesWithExpiration :: !(Maybe Bool)
, _fdFulfilledCapacity :: !(Maybe Double)
, _fdType :: !(Maybe FleetType)
, _fdValidFrom :: !(Maybe ISO8601)
, _fdReplaceUnhealthyInstances :: !(Maybe Bool)
, _fdFulfilledOnDemandCapacity :: !(Maybe Double)
, _fdFleetId :: !(Maybe Text)
, _fdCreateTime :: !(Maybe ISO8601)
, _fdTags :: !(Maybe [Tag])
, _fdActivityStatus :: !(Maybe FleetActivityStatus)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
fleetData
:: FleetData
fleetData =
FleetData'
{ _fdClientToken = Nothing
, _fdTargetCapacitySpecification = Nothing
, _fdSpotOptions = Nothing
, _fdExcessCapacityTerminationPolicy = Nothing
, _fdFleetState = Nothing
, _fdLaunchTemplateConfigs = Nothing
, _fdValidUntil = Nothing
, _fdTerminateInstancesWithExpiration = Nothing
, _fdFulfilledCapacity = Nothing
, _fdType = Nothing
, _fdValidFrom = Nothing
, _fdReplaceUnhealthyInstances = Nothing
, _fdFulfilledOnDemandCapacity = Nothing
, _fdFleetId = Nothing
, _fdCreateTime = Nothing
, _fdTags = Nothing
, _fdActivityStatus = Nothing
}
fdClientToken :: Lens' FleetData (Maybe Text)
fdClientToken = lens _fdClientToken (\ s a -> s{_fdClientToken = a})
fdTargetCapacitySpecification :: Lens' FleetData (Maybe TargetCapacitySpecification)
fdTargetCapacitySpecification = lens _fdTargetCapacitySpecification (\ s a -> s{_fdTargetCapacitySpecification = a})
fdSpotOptions :: Lens' FleetData (Maybe SpotOptions)
fdSpotOptions = lens _fdSpotOptions (\ s a -> s{_fdSpotOptions = a})
fdExcessCapacityTerminationPolicy :: Lens' FleetData (Maybe FleetExcessCapacityTerminationPolicy)
fdExcessCapacityTerminationPolicy = lens _fdExcessCapacityTerminationPolicy (\ s a -> s{_fdExcessCapacityTerminationPolicy = a})
fdFleetState :: Lens' FleetData (Maybe FleetStateCode)
fdFleetState = lens _fdFleetState (\ s a -> s{_fdFleetState = a})
fdLaunchTemplateConfigs :: Lens' FleetData [FleetLaunchTemplateConfig]
fdLaunchTemplateConfigs = lens _fdLaunchTemplateConfigs (\ s a -> s{_fdLaunchTemplateConfigs = a}) . _Default . _Coerce
fdValidUntil :: Lens' FleetData (Maybe UTCTime)
fdValidUntil = lens _fdValidUntil (\ s a -> s{_fdValidUntil = a}) . mapping _Time
fdTerminateInstancesWithExpiration :: Lens' FleetData (Maybe Bool)
fdTerminateInstancesWithExpiration = lens _fdTerminateInstancesWithExpiration (\ s a -> s{_fdTerminateInstancesWithExpiration = a})
fdFulfilledCapacity :: Lens' FleetData (Maybe Double)
fdFulfilledCapacity = lens _fdFulfilledCapacity (\ s a -> s{_fdFulfilledCapacity = a})
fdType :: Lens' FleetData (Maybe FleetType)
fdType = lens _fdType (\ s a -> s{_fdType = a})
fdValidFrom :: Lens' FleetData (Maybe UTCTime)
fdValidFrom = lens _fdValidFrom (\ s a -> s{_fdValidFrom = a}) . mapping _Time
fdReplaceUnhealthyInstances :: Lens' FleetData (Maybe Bool)
fdReplaceUnhealthyInstances = lens _fdReplaceUnhealthyInstances (\ s a -> s{_fdReplaceUnhealthyInstances = a})
fdFulfilledOnDemandCapacity :: Lens' FleetData (Maybe Double)
fdFulfilledOnDemandCapacity = lens _fdFulfilledOnDemandCapacity (\ s a -> s{_fdFulfilledOnDemandCapacity = a})
fdFleetId :: Lens' FleetData (Maybe Text)
fdFleetId = lens _fdFleetId (\ s a -> s{_fdFleetId = a})
fdCreateTime :: Lens' FleetData (Maybe UTCTime)
fdCreateTime = lens _fdCreateTime (\ s a -> s{_fdCreateTime = a}) . mapping _Time
fdTags :: Lens' FleetData [Tag]
fdTags = lens _fdTags (\ s a -> s{_fdTags = a}) . _Default . _Coerce
fdActivityStatus :: Lens' FleetData (Maybe FleetActivityStatus)
fdActivityStatus = lens _fdActivityStatus (\ s a -> s{_fdActivityStatus = a})
instance FromXML FleetData where
parseXML x
= FleetData' <$>
(x .@? "clientToken") <*>
(x .@? "targetCapacitySpecification")
<*> (x .@? "spotOptions")
<*> (x .@? "excessCapacityTerminationPolicy")
<*> (x .@? "fleetState")
<*>
(x .@? "launchTemplateConfigs" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "validUntil")
<*> (x .@? "terminateInstancesWithExpiration")
<*> (x .@? "fulfilledCapacity")
<*> (x .@? "type")
<*> (x .@? "validFrom")
<*> (x .@? "replaceUnhealthyInstances")
<*> (x .@? "fulfilledOnDemandCapacity")
<*> (x .@? "fleetId")
<*> (x .@? "createTime")
<*>
(x .@? "tagSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "activityStatus")
instance Hashable FleetData where
instance NFData FleetData where
data FleetLaunchTemplateConfig = FleetLaunchTemplateConfig'
{ _fltcOverrides :: !(Maybe [FleetLaunchTemplateOverrides])
, _fltcLaunchTemplateSpecification :: !(Maybe FleetLaunchTemplateSpecification)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
fleetLaunchTemplateConfig
:: FleetLaunchTemplateConfig
fleetLaunchTemplateConfig =
FleetLaunchTemplateConfig'
{_fltcOverrides = Nothing, _fltcLaunchTemplateSpecification = Nothing}
fltcOverrides :: Lens' FleetLaunchTemplateConfig [FleetLaunchTemplateOverrides]
fltcOverrides = lens _fltcOverrides (\ s a -> s{_fltcOverrides = a}) . _Default . _Coerce
fltcLaunchTemplateSpecification :: Lens' FleetLaunchTemplateConfig (Maybe FleetLaunchTemplateSpecification)
fltcLaunchTemplateSpecification = lens _fltcLaunchTemplateSpecification (\ s a -> s{_fltcLaunchTemplateSpecification = a})
instance FromXML FleetLaunchTemplateConfig where
parseXML x
= FleetLaunchTemplateConfig' <$>
(x .@? "overrides" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "launchTemplateSpecification")
instance Hashable FleetLaunchTemplateConfig where
instance NFData FleetLaunchTemplateConfig where
data FleetLaunchTemplateConfigRequest = FleetLaunchTemplateConfigRequest'
{ _fltcrOverrides :: !(Maybe [FleetLaunchTemplateOverridesRequest])
, _fltcrLaunchTemplateSpecification :: !(Maybe FleetLaunchTemplateSpecificationRequest)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
fleetLaunchTemplateConfigRequest
:: FleetLaunchTemplateConfigRequest
fleetLaunchTemplateConfigRequest =
FleetLaunchTemplateConfigRequest'
{_fltcrOverrides = Nothing, _fltcrLaunchTemplateSpecification = Nothing}
fltcrOverrides :: Lens' FleetLaunchTemplateConfigRequest [FleetLaunchTemplateOverridesRequest]
fltcrOverrides = lens _fltcrOverrides (\ s a -> s{_fltcrOverrides = a}) . _Default . _Coerce
fltcrLaunchTemplateSpecification :: Lens' FleetLaunchTemplateConfigRequest (Maybe FleetLaunchTemplateSpecificationRequest)
fltcrLaunchTemplateSpecification = lens _fltcrLaunchTemplateSpecification (\ s a -> s{_fltcrLaunchTemplateSpecification = a})
instance Hashable FleetLaunchTemplateConfigRequest
where
instance NFData FleetLaunchTemplateConfigRequest
where
instance ToQuery FleetLaunchTemplateConfigRequest
where
toQuery FleetLaunchTemplateConfigRequest'{..}
= mconcat
[toQuery
(toQueryList "Overrides" <$> _fltcrOverrides),
"LaunchTemplateSpecification" =:
_fltcrLaunchTemplateSpecification]
data FleetLaunchTemplateOverrides = FleetLaunchTemplateOverrides'
{ _fltoWeightedCapacity :: !(Maybe Double)
, _fltoSubnetId :: !(Maybe Text)
, _fltoInstanceType :: !(Maybe InstanceType)
, _fltoAvailabilityZone :: !(Maybe Text)
, _fltoMaxPrice :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
fleetLaunchTemplateOverrides
:: FleetLaunchTemplateOverrides
fleetLaunchTemplateOverrides =
FleetLaunchTemplateOverrides'
{ _fltoWeightedCapacity = Nothing
, _fltoSubnetId = Nothing
, _fltoInstanceType = Nothing
, _fltoAvailabilityZone = Nothing
, _fltoMaxPrice = Nothing
}
fltoWeightedCapacity :: Lens' FleetLaunchTemplateOverrides (Maybe Double)
fltoWeightedCapacity = lens _fltoWeightedCapacity (\ s a -> s{_fltoWeightedCapacity = a})
fltoSubnetId :: Lens' FleetLaunchTemplateOverrides (Maybe Text)
fltoSubnetId = lens _fltoSubnetId (\ s a -> s{_fltoSubnetId = a})
fltoInstanceType :: Lens' FleetLaunchTemplateOverrides (Maybe InstanceType)
fltoInstanceType = lens _fltoInstanceType (\ s a -> s{_fltoInstanceType = a})
fltoAvailabilityZone :: Lens' FleetLaunchTemplateOverrides (Maybe Text)
fltoAvailabilityZone = lens _fltoAvailabilityZone (\ s a -> s{_fltoAvailabilityZone = a})
fltoMaxPrice :: Lens' FleetLaunchTemplateOverrides (Maybe Text)
fltoMaxPrice = lens _fltoMaxPrice (\ s a -> s{_fltoMaxPrice = a})
instance FromXML FleetLaunchTemplateOverrides where
parseXML x
= FleetLaunchTemplateOverrides' <$>
(x .@? "weightedCapacity") <*> (x .@? "subnetId") <*>
(x .@? "instanceType")
<*> (x .@? "availabilityZone")
<*> (x .@? "maxPrice")
instance Hashable FleetLaunchTemplateOverrides where
instance NFData FleetLaunchTemplateOverrides where
data FleetLaunchTemplateOverridesRequest = FleetLaunchTemplateOverridesRequest'
{ _fltorWeightedCapacity :: !(Maybe Double)
, _fltorSubnetId :: !(Maybe Text)
, _fltorInstanceType :: !(Maybe InstanceType)
, _fltorAvailabilityZone :: !(Maybe Text)
, _fltorMaxPrice :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
fleetLaunchTemplateOverridesRequest
:: FleetLaunchTemplateOverridesRequest
fleetLaunchTemplateOverridesRequest =
FleetLaunchTemplateOverridesRequest'
{ _fltorWeightedCapacity = Nothing
, _fltorSubnetId = Nothing
, _fltorInstanceType = Nothing
, _fltorAvailabilityZone = Nothing
, _fltorMaxPrice = Nothing
}
fltorWeightedCapacity :: Lens' FleetLaunchTemplateOverridesRequest (Maybe Double)
fltorWeightedCapacity = lens _fltorWeightedCapacity (\ s a -> s{_fltorWeightedCapacity = a})
fltorSubnetId :: Lens' FleetLaunchTemplateOverridesRequest (Maybe Text)
fltorSubnetId = lens _fltorSubnetId (\ s a -> s{_fltorSubnetId = a})
fltorInstanceType :: Lens' FleetLaunchTemplateOverridesRequest (Maybe InstanceType)
fltorInstanceType = lens _fltorInstanceType (\ s a -> s{_fltorInstanceType = a})
fltorAvailabilityZone :: Lens' FleetLaunchTemplateOverridesRequest (Maybe Text)
fltorAvailabilityZone = lens _fltorAvailabilityZone (\ s a -> s{_fltorAvailabilityZone = a})
fltorMaxPrice :: Lens' FleetLaunchTemplateOverridesRequest (Maybe Text)
fltorMaxPrice = lens _fltorMaxPrice (\ s a -> s{_fltorMaxPrice = a})
instance Hashable FleetLaunchTemplateOverridesRequest
where
instance NFData FleetLaunchTemplateOverridesRequest
where
instance ToQuery FleetLaunchTemplateOverridesRequest
where
toQuery FleetLaunchTemplateOverridesRequest'{..}
= mconcat
["WeightedCapacity" =: _fltorWeightedCapacity,
"SubnetId" =: _fltorSubnetId,
"InstanceType" =: _fltorInstanceType,
"AvailabilityZone" =: _fltorAvailabilityZone,
"MaxPrice" =: _fltorMaxPrice]
data FleetLaunchTemplateSpecification = FleetLaunchTemplateSpecification'
{ _fltsLaunchTemplateName :: !(Maybe Text)
, _fltsLaunchTemplateId :: !(Maybe Text)
, _fltsVersion :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
fleetLaunchTemplateSpecification
:: FleetLaunchTemplateSpecification
fleetLaunchTemplateSpecification =
FleetLaunchTemplateSpecification'
{ _fltsLaunchTemplateName = Nothing
, _fltsLaunchTemplateId = Nothing
, _fltsVersion = Nothing
}
fltsLaunchTemplateName :: Lens' FleetLaunchTemplateSpecification (Maybe Text)
fltsLaunchTemplateName = lens _fltsLaunchTemplateName (\ s a -> s{_fltsLaunchTemplateName = a})
fltsLaunchTemplateId :: Lens' FleetLaunchTemplateSpecification (Maybe Text)
fltsLaunchTemplateId = lens _fltsLaunchTemplateId (\ s a -> s{_fltsLaunchTemplateId = a})
fltsVersion :: Lens' FleetLaunchTemplateSpecification (Maybe Text)
fltsVersion = lens _fltsVersion (\ s a -> s{_fltsVersion = a})
instance FromXML FleetLaunchTemplateSpecification
where
parseXML x
= FleetLaunchTemplateSpecification' <$>
(x .@? "launchTemplateName") <*>
(x .@? "launchTemplateId")
<*> (x .@? "version")
instance Hashable FleetLaunchTemplateSpecification
where
instance NFData FleetLaunchTemplateSpecification
where
instance ToQuery FleetLaunchTemplateSpecification
where
toQuery FleetLaunchTemplateSpecification'{..}
= mconcat
["LaunchTemplateName" =: _fltsLaunchTemplateName,
"LaunchTemplateId" =: _fltsLaunchTemplateId,
"Version" =: _fltsVersion]
data FleetLaunchTemplateSpecificationRequest = FleetLaunchTemplateSpecificationRequest'
{ _fltsrLaunchTemplateName :: !(Maybe Text)
, _fltsrLaunchTemplateId :: !(Maybe Text)
, _fltsrVersion :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
fleetLaunchTemplateSpecificationRequest
:: FleetLaunchTemplateSpecificationRequest
fleetLaunchTemplateSpecificationRequest =
FleetLaunchTemplateSpecificationRequest'
{ _fltsrLaunchTemplateName = Nothing
, _fltsrLaunchTemplateId = Nothing
, _fltsrVersion = Nothing
}
fltsrLaunchTemplateName :: Lens' FleetLaunchTemplateSpecificationRequest (Maybe Text)
fltsrLaunchTemplateName = lens _fltsrLaunchTemplateName (\ s a -> s{_fltsrLaunchTemplateName = a})
fltsrLaunchTemplateId :: Lens' FleetLaunchTemplateSpecificationRequest (Maybe Text)
fltsrLaunchTemplateId = lens _fltsrLaunchTemplateId (\ s a -> s{_fltsrLaunchTemplateId = a})
fltsrVersion :: Lens' FleetLaunchTemplateSpecificationRequest (Maybe Text)
fltsrVersion = lens _fltsrVersion (\ s a -> s{_fltsrVersion = a})
instance Hashable
FleetLaunchTemplateSpecificationRequest
where
instance NFData
FleetLaunchTemplateSpecificationRequest
where
instance ToQuery
FleetLaunchTemplateSpecificationRequest
where
toQuery FleetLaunchTemplateSpecificationRequest'{..}
= mconcat
["LaunchTemplateName" =: _fltsrLaunchTemplateName,
"LaunchTemplateId" =: _fltsrLaunchTemplateId,
"Version" =: _fltsrVersion]
data FlowLog = FlowLog'
{ _flCreationTime :: !(Maybe ISO8601)
, _flResourceId :: !(Maybe Text)
, _flFlowLogStatus :: !(Maybe Text)
, _flTrafficType :: !(Maybe TrafficType)
, _flDeliverLogsStatus :: !(Maybe Text)
, _flDeliverLogsErrorMessage :: !(Maybe Text)
, _flLogGroupName :: !(Maybe Text)
, _flDeliverLogsPermissionARN :: !(Maybe Text)
, _flFlowLogId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
flowLog
:: FlowLog
flowLog =
FlowLog'
{ _flCreationTime = Nothing
, _flResourceId = Nothing
, _flFlowLogStatus = Nothing
, _flTrafficType = Nothing
, _flDeliverLogsStatus = Nothing
, _flDeliverLogsErrorMessage = Nothing
, _flLogGroupName = Nothing
, _flDeliverLogsPermissionARN = Nothing
, _flFlowLogId = Nothing
}
flCreationTime :: Lens' FlowLog (Maybe UTCTime)
flCreationTime = lens _flCreationTime (\ s a -> s{_flCreationTime = a}) . mapping _Time
flResourceId :: Lens' FlowLog (Maybe Text)
flResourceId = lens _flResourceId (\ s a -> s{_flResourceId = a})
flFlowLogStatus :: Lens' FlowLog (Maybe Text)
flFlowLogStatus = lens _flFlowLogStatus (\ s a -> s{_flFlowLogStatus = a})
flTrafficType :: Lens' FlowLog (Maybe TrafficType)
flTrafficType = lens _flTrafficType (\ s a -> s{_flTrafficType = a})
flDeliverLogsStatus :: Lens' FlowLog (Maybe Text)
flDeliverLogsStatus = lens _flDeliverLogsStatus (\ s a -> s{_flDeliverLogsStatus = a})
flDeliverLogsErrorMessage :: Lens' FlowLog (Maybe Text)
flDeliverLogsErrorMessage = lens _flDeliverLogsErrorMessage (\ s a -> s{_flDeliverLogsErrorMessage = a})
flLogGroupName :: Lens' FlowLog (Maybe Text)
flLogGroupName = lens _flLogGroupName (\ s a -> s{_flLogGroupName = a})
flDeliverLogsPermissionARN :: Lens' FlowLog (Maybe Text)
flDeliverLogsPermissionARN = lens _flDeliverLogsPermissionARN (\ s a -> s{_flDeliverLogsPermissionARN = a})
flFlowLogId :: Lens' FlowLog (Maybe Text)
flFlowLogId = lens _flFlowLogId (\ s a -> s{_flFlowLogId = a})
instance FromXML FlowLog where
parseXML x
= FlowLog' <$>
(x .@? "creationTime") <*> (x .@? "resourceId") <*>
(x .@? "flowLogStatus")
<*> (x .@? "trafficType")
<*> (x .@? "deliverLogsStatus")
<*> (x .@? "deliverLogsErrorMessage")
<*> (x .@? "logGroupName")
<*> (x .@? "deliverLogsPermissionArn")
<*> (x .@? "flowLogId")
instance Hashable FlowLog where
instance NFData FlowLog where
data FpgaImage = FpgaImage'
{ _fiShellVersion :: !(Maybe Text)
, _fiPciId :: !(Maybe PciId)
, _fiState :: !(Maybe FpgaImageState)
, _fiOwnerAlias :: !(Maybe Text)
, _fiFpgaImageId :: !(Maybe Text)
, _fiOwnerId :: !(Maybe Text)
, _fiUpdateTime :: !(Maybe ISO8601)
, _fiName :: !(Maybe Text)
, _fiProductCodes :: !(Maybe [ProductCode])
, _fiDescription :: !(Maybe Text)
, _fiCreateTime :: !(Maybe ISO8601)
, _fiTags :: !(Maybe [Tag])
, _fiPublic :: !(Maybe Bool)
, _fiFpgaImageGlobalId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
fpgaImage
:: FpgaImage
fpgaImage =
FpgaImage'
{ _fiShellVersion = Nothing
, _fiPciId = Nothing
, _fiState = Nothing
, _fiOwnerAlias = Nothing
, _fiFpgaImageId = Nothing
, _fiOwnerId = Nothing
, _fiUpdateTime = Nothing
, _fiName = Nothing
, _fiProductCodes = Nothing
, _fiDescription = Nothing
, _fiCreateTime = Nothing
, _fiTags = Nothing
, _fiPublic = Nothing
, _fiFpgaImageGlobalId = Nothing
}
fiShellVersion :: Lens' FpgaImage (Maybe Text)
fiShellVersion = lens _fiShellVersion (\ s a -> s{_fiShellVersion = a})
fiPciId :: Lens' FpgaImage (Maybe PciId)
fiPciId = lens _fiPciId (\ s a -> s{_fiPciId = a})
fiState :: Lens' FpgaImage (Maybe FpgaImageState)
fiState = lens _fiState (\ s a -> s{_fiState = a})
fiOwnerAlias :: Lens' FpgaImage (Maybe Text)
fiOwnerAlias = lens _fiOwnerAlias (\ s a -> s{_fiOwnerAlias = a})
fiFpgaImageId :: Lens' FpgaImage (Maybe Text)
fiFpgaImageId = lens _fiFpgaImageId (\ s a -> s{_fiFpgaImageId = a})
fiOwnerId :: Lens' FpgaImage (Maybe Text)
fiOwnerId = lens _fiOwnerId (\ s a -> s{_fiOwnerId = a})
fiUpdateTime :: Lens' FpgaImage (Maybe UTCTime)
fiUpdateTime = lens _fiUpdateTime (\ s a -> s{_fiUpdateTime = a}) . mapping _Time
fiName :: Lens' FpgaImage (Maybe Text)
fiName = lens _fiName (\ s a -> s{_fiName = a})
fiProductCodes :: Lens' FpgaImage [ProductCode]
fiProductCodes = lens _fiProductCodes (\ s a -> s{_fiProductCodes = a}) . _Default . _Coerce
fiDescription :: Lens' FpgaImage (Maybe Text)
fiDescription = lens _fiDescription (\ s a -> s{_fiDescription = a})
fiCreateTime :: Lens' FpgaImage (Maybe UTCTime)
fiCreateTime = lens _fiCreateTime (\ s a -> s{_fiCreateTime = a}) . mapping _Time
fiTags :: Lens' FpgaImage [Tag]
fiTags = lens _fiTags (\ s a -> s{_fiTags = a}) . _Default . _Coerce
fiPublic :: Lens' FpgaImage (Maybe Bool)
fiPublic = lens _fiPublic (\ s a -> s{_fiPublic = a})
fiFpgaImageGlobalId :: Lens' FpgaImage (Maybe Text)
fiFpgaImageGlobalId = lens _fiFpgaImageGlobalId (\ s a -> s{_fiFpgaImageGlobalId = a})
instance FromXML FpgaImage where
parseXML x
= FpgaImage' <$>
(x .@? "shellVersion") <*> (x .@? "pciId") <*>
(x .@? "state")
<*> (x .@? "ownerAlias")
<*> (x .@? "fpgaImageId")
<*> (x .@? "ownerId")
<*> (x .@? "updateTime")
<*> (x .@? "name")
<*>
(x .@? "productCodes" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "description")
<*> (x .@? "createTime")
<*>
(x .@? "tags" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "public")
<*> (x .@? "fpgaImageGlobalId")
instance Hashable FpgaImage where
instance NFData FpgaImage where
data FpgaImageAttribute = FpgaImageAttribute'
{ _fiaFpgaImageId :: !(Maybe Text)
, _fiaName :: !(Maybe Text)
, _fiaProductCodes :: !(Maybe [ProductCode])
, _fiaDescription :: !(Maybe Text)
, _fiaLoadPermissions :: !(Maybe [LoadPermission])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
fpgaImageAttribute
:: FpgaImageAttribute
fpgaImageAttribute =
FpgaImageAttribute'
{ _fiaFpgaImageId = Nothing
, _fiaName = Nothing
, _fiaProductCodes = Nothing
, _fiaDescription = Nothing
, _fiaLoadPermissions = Nothing
}
fiaFpgaImageId :: Lens' FpgaImageAttribute (Maybe Text)
fiaFpgaImageId = lens _fiaFpgaImageId (\ s a -> s{_fiaFpgaImageId = a})
fiaName :: Lens' FpgaImageAttribute (Maybe Text)
fiaName = lens _fiaName (\ s a -> s{_fiaName = a})
fiaProductCodes :: Lens' FpgaImageAttribute [ProductCode]
fiaProductCodes = lens _fiaProductCodes (\ s a -> s{_fiaProductCodes = a}) . _Default . _Coerce
fiaDescription :: Lens' FpgaImageAttribute (Maybe Text)
fiaDescription = lens _fiaDescription (\ s a -> s{_fiaDescription = a})
fiaLoadPermissions :: Lens' FpgaImageAttribute [LoadPermission]
fiaLoadPermissions = lens _fiaLoadPermissions (\ s a -> s{_fiaLoadPermissions = a}) . _Default . _Coerce
instance FromXML FpgaImageAttribute where
parseXML x
= FpgaImageAttribute' <$>
(x .@? "fpgaImageId") <*> (x .@? "name") <*>
(x .@? "productCodes" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "description")
<*>
(x .@? "loadPermissions" .!@ mempty >>=
may (parseXMLList "item"))
instance Hashable FpgaImageAttribute where
instance NFData FpgaImageAttribute where
data FpgaImageState = FpgaImageState'
{ _fisCode :: !(Maybe FpgaImageStateCode)
, _fisMessage :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
fpgaImageState
:: FpgaImageState
fpgaImageState = FpgaImageState' {_fisCode = Nothing, _fisMessage = Nothing}
fisCode :: Lens' FpgaImageState (Maybe FpgaImageStateCode)
fisCode = lens _fisCode (\ s a -> s{_fisCode = a})
fisMessage :: Lens' FpgaImageState (Maybe Text)
fisMessage = lens _fisMessage (\ s a -> s{_fisMessage = a})
instance FromXML FpgaImageState where
parseXML x
= FpgaImageState' <$>
(x .@? "code") <*> (x .@? "message")
instance Hashable FpgaImageState where
instance NFData FpgaImageState where
data GroupIdentifier = GroupIdentifier'
{ _giGroupId :: !(Maybe Text)
, _giGroupName :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
groupIdentifier
:: GroupIdentifier
groupIdentifier =
GroupIdentifier' {_giGroupId = Nothing, _giGroupName = Nothing}
giGroupId :: Lens' GroupIdentifier (Maybe Text)
giGroupId = lens _giGroupId (\ s a -> s{_giGroupId = a})
giGroupName :: Lens' GroupIdentifier (Maybe Text)
giGroupName = lens _giGroupName (\ s a -> s{_giGroupName = a})
instance FromXML GroupIdentifier where
parseXML x
= GroupIdentifier' <$>
(x .@? "groupId") <*> (x .@? "groupName")
instance Hashable GroupIdentifier where
instance NFData GroupIdentifier where
instance ToQuery GroupIdentifier where
toQuery GroupIdentifier'{..}
= mconcat
["GroupId" =: _giGroupId,
"GroupName" =: _giGroupName]
data HistoryRecord = HistoryRecord'
{ _hrEventInformation :: !EventInformation
, _hrEventType :: !EventType
, _hrTimestamp :: !ISO8601
} deriving (Eq, Read, Show, Data, Typeable, Generic)
historyRecord
:: EventInformation
-> EventType
-> UTCTime
-> HistoryRecord
historyRecord pEventInformation_ pEventType_ pTimestamp_ =
HistoryRecord'
{ _hrEventInformation = pEventInformation_
, _hrEventType = pEventType_
, _hrTimestamp = _Time # pTimestamp_
}
hrEventInformation :: Lens' HistoryRecord EventInformation
hrEventInformation = lens _hrEventInformation (\ s a -> s{_hrEventInformation = a})
hrEventType :: Lens' HistoryRecord EventType
hrEventType = lens _hrEventType (\ s a -> s{_hrEventType = a})
hrTimestamp :: Lens' HistoryRecord UTCTime
hrTimestamp = lens _hrTimestamp (\ s a -> s{_hrTimestamp = a}) . _Time
instance FromXML HistoryRecord where
parseXML x
= HistoryRecord' <$>
(x .@ "eventInformation") <*> (x .@ "eventType") <*>
(x .@ "timestamp")
instance Hashable HistoryRecord where
instance NFData HistoryRecord where
data HistoryRecordEntry = HistoryRecordEntry'
{ _hreEventType :: !(Maybe FleetEventType)
, _hreEventInformation :: !(Maybe EventInformation)
, _hreTimestamp :: !(Maybe ISO8601)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
historyRecordEntry
:: HistoryRecordEntry
historyRecordEntry =
HistoryRecordEntry'
{ _hreEventType = Nothing
, _hreEventInformation = Nothing
, _hreTimestamp = Nothing
}
hreEventType :: Lens' HistoryRecordEntry (Maybe FleetEventType)
hreEventType = lens _hreEventType (\ s a -> s{_hreEventType = a})
hreEventInformation :: Lens' HistoryRecordEntry (Maybe EventInformation)
hreEventInformation = lens _hreEventInformation (\ s a -> s{_hreEventInformation = a})
hreTimestamp :: Lens' HistoryRecordEntry (Maybe UTCTime)
hreTimestamp = lens _hreTimestamp (\ s a -> s{_hreTimestamp = a}) . mapping _Time
instance FromXML HistoryRecordEntry where
parseXML x
= HistoryRecordEntry' <$>
(x .@? "eventType") <*> (x .@? "eventInformation")
<*> (x .@? "timestamp")
instance Hashable HistoryRecordEntry where
instance NFData HistoryRecordEntry where
data Host = Host'
{ _hReleaseTime :: !(Maybe ISO8601)
, _hState :: !(Maybe AllocationState)
, _hClientToken :: !(Maybe Text)
, _hHostId :: !(Maybe Text)
, _hAvailableCapacity :: !(Maybe AvailableCapacity)
, _hHostReservationId :: !(Maybe Text)
, _hHostProperties :: !(Maybe HostProperties)
, _hAvailabilityZone :: !(Maybe Text)
, _hInstances :: !(Maybe [HostInstance])
, _hAllocationTime :: !(Maybe ISO8601)
, _hAutoPlacement :: !(Maybe AutoPlacement)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
host
:: Host
host =
Host'
{ _hReleaseTime = Nothing
, _hState = Nothing
, _hClientToken = Nothing
, _hHostId = Nothing
, _hAvailableCapacity = Nothing
, _hHostReservationId = Nothing
, _hHostProperties = Nothing
, _hAvailabilityZone = Nothing
, _hInstances = Nothing
, _hAllocationTime = Nothing
, _hAutoPlacement = Nothing
}
hReleaseTime :: Lens' Host (Maybe UTCTime)
hReleaseTime = lens _hReleaseTime (\ s a -> s{_hReleaseTime = a}) . mapping _Time
hState :: Lens' Host (Maybe AllocationState)
hState = lens _hState (\ s a -> s{_hState = a})
hClientToken :: Lens' Host (Maybe Text)
hClientToken = lens _hClientToken (\ s a -> s{_hClientToken = a})
hHostId :: Lens' Host (Maybe Text)
hHostId = lens _hHostId (\ s a -> s{_hHostId = a})
hAvailableCapacity :: Lens' Host (Maybe AvailableCapacity)
hAvailableCapacity = lens _hAvailableCapacity (\ s a -> s{_hAvailableCapacity = a})
hHostReservationId :: Lens' Host (Maybe Text)
hHostReservationId = lens _hHostReservationId (\ s a -> s{_hHostReservationId = a})
hHostProperties :: Lens' Host (Maybe HostProperties)
hHostProperties = lens _hHostProperties (\ s a -> s{_hHostProperties = a})
hAvailabilityZone :: Lens' Host (Maybe Text)
hAvailabilityZone = lens _hAvailabilityZone (\ s a -> s{_hAvailabilityZone = a})
hInstances :: Lens' Host [HostInstance]
hInstances = lens _hInstances (\ s a -> s{_hInstances = a}) . _Default . _Coerce
hAllocationTime :: Lens' Host (Maybe UTCTime)
hAllocationTime = lens _hAllocationTime (\ s a -> s{_hAllocationTime = a}) . mapping _Time
hAutoPlacement :: Lens' Host (Maybe AutoPlacement)
hAutoPlacement = lens _hAutoPlacement (\ s a -> s{_hAutoPlacement = a})
instance FromXML Host where
parseXML x
= Host' <$>
(x .@? "releaseTime") <*> (x .@? "state") <*>
(x .@? "clientToken")
<*> (x .@? "hostId")
<*> (x .@? "availableCapacity")
<*> (x .@? "hostReservationId")
<*> (x .@? "hostProperties")
<*> (x .@? "availabilityZone")
<*>
(x .@? "instances" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "allocationTime")
<*> (x .@? "autoPlacement")
instance Hashable Host where
instance NFData Host where
data HostInstance = HostInstance'
{ _hiInstanceId :: !(Maybe Text)
, _hiInstanceType :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
hostInstance
:: HostInstance
hostInstance =
HostInstance' {_hiInstanceId = Nothing, _hiInstanceType = Nothing}
hiInstanceId :: Lens' HostInstance (Maybe Text)
hiInstanceId = lens _hiInstanceId (\ s a -> s{_hiInstanceId = a})
hiInstanceType :: Lens' HostInstance (Maybe Text)
hiInstanceType = lens _hiInstanceType (\ s a -> s{_hiInstanceType = a})
instance FromXML HostInstance where
parseXML x
= HostInstance' <$>
(x .@? "instanceId") <*> (x .@? "instanceType")
instance Hashable HostInstance where
instance NFData HostInstance where
data HostOffering = HostOffering'
{ _hoInstanceFamily :: !(Maybe Text)
, _hoCurrencyCode :: !(Maybe CurrencyCodeValues)
, _hoHourlyPrice :: !(Maybe Text)
, _hoUpfrontPrice :: !(Maybe Text)
, _hoOfferingId :: !(Maybe Text)
, _hoDuration :: !(Maybe Int)
, _hoPaymentOption :: !(Maybe PaymentOption)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
hostOffering
:: HostOffering
hostOffering =
HostOffering'
{ _hoInstanceFamily = Nothing
, _hoCurrencyCode = Nothing
, _hoHourlyPrice = Nothing
, _hoUpfrontPrice = Nothing
, _hoOfferingId = Nothing
, _hoDuration = Nothing
, _hoPaymentOption = Nothing
}
hoInstanceFamily :: Lens' HostOffering (Maybe Text)
hoInstanceFamily = lens _hoInstanceFamily (\ s a -> s{_hoInstanceFamily = a})
hoCurrencyCode :: Lens' HostOffering (Maybe CurrencyCodeValues)
hoCurrencyCode = lens _hoCurrencyCode (\ s a -> s{_hoCurrencyCode = a})
hoHourlyPrice :: Lens' HostOffering (Maybe Text)
hoHourlyPrice = lens _hoHourlyPrice (\ s a -> s{_hoHourlyPrice = a})
hoUpfrontPrice :: Lens' HostOffering (Maybe Text)
hoUpfrontPrice = lens _hoUpfrontPrice (\ s a -> s{_hoUpfrontPrice = a})
hoOfferingId :: Lens' HostOffering (Maybe Text)
hoOfferingId = lens _hoOfferingId (\ s a -> s{_hoOfferingId = a})
hoDuration :: Lens' HostOffering (Maybe Int)
hoDuration = lens _hoDuration (\ s a -> s{_hoDuration = a})
hoPaymentOption :: Lens' HostOffering (Maybe PaymentOption)
hoPaymentOption = lens _hoPaymentOption (\ s a -> s{_hoPaymentOption = a})
instance FromXML HostOffering where
parseXML x
= HostOffering' <$>
(x .@? "instanceFamily") <*> (x .@? "currencyCode")
<*> (x .@? "hourlyPrice")
<*> (x .@? "upfrontPrice")
<*> (x .@? "offeringId")
<*> (x .@? "duration")
<*> (x .@? "paymentOption")
instance Hashable HostOffering where
instance NFData HostOffering where
data HostProperties = HostProperties'
{ _hpInstanceType :: !(Maybe Text)
, _hpTotalVCPUs :: !(Maybe Int)
, _hpCores :: !(Maybe Int)
, _hpSockets :: !(Maybe Int)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
hostProperties
:: HostProperties
hostProperties =
HostProperties'
{ _hpInstanceType = Nothing
, _hpTotalVCPUs = Nothing
, _hpCores = Nothing
, _hpSockets = Nothing
}
hpInstanceType :: Lens' HostProperties (Maybe Text)
hpInstanceType = lens _hpInstanceType (\ s a -> s{_hpInstanceType = a})
hpTotalVCPUs :: Lens' HostProperties (Maybe Int)
hpTotalVCPUs = lens _hpTotalVCPUs (\ s a -> s{_hpTotalVCPUs = a})
hpCores :: Lens' HostProperties (Maybe Int)
hpCores = lens _hpCores (\ s a -> s{_hpCores = a})
hpSockets :: Lens' HostProperties (Maybe Int)
hpSockets = lens _hpSockets (\ s a -> s{_hpSockets = a})
instance FromXML HostProperties where
parseXML x
= HostProperties' <$>
(x .@? "instanceType") <*> (x .@? "totalVCpus") <*>
(x .@? "cores")
<*> (x .@? "sockets")
instance Hashable HostProperties where
instance NFData HostProperties where
data HostReservation = HostReservation'
{ _hrState :: !(Maybe ReservationState)
, _hrInstanceFamily :: !(Maybe Text)
, _hrCurrencyCode :: !(Maybe CurrencyCodeValues)
, _hrHostReservationId :: !(Maybe Text)
, _hrStart :: !(Maybe ISO8601)
, _hrHourlyPrice :: !(Maybe Text)
, _hrCount :: !(Maybe Int)
, _hrUpfrontPrice :: !(Maybe Text)
, _hrEnd :: !(Maybe ISO8601)
, _hrHostIdSet :: !(Maybe [Text])
, _hrOfferingId :: !(Maybe Text)
, _hrDuration :: !(Maybe Int)
, _hrPaymentOption :: !(Maybe PaymentOption)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
hostReservation
:: HostReservation
hostReservation =
HostReservation'
{ _hrState = Nothing
, _hrInstanceFamily = Nothing
, _hrCurrencyCode = Nothing
, _hrHostReservationId = Nothing
, _hrStart = Nothing
, _hrHourlyPrice = Nothing
, _hrCount = Nothing
, _hrUpfrontPrice = Nothing
, _hrEnd = Nothing
, _hrHostIdSet = Nothing
, _hrOfferingId = Nothing
, _hrDuration = Nothing
, _hrPaymentOption = Nothing
}
hrState :: Lens' HostReservation (Maybe ReservationState)
hrState = lens _hrState (\ s a -> s{_hrState = a})
hrInstanceFamily :: Lens' HostReservation (Maybe Text)
hrInstanceFamily = lens _hrInstanceFamily (\ s a -> s{_hrInstanceFamily = a})
hrCurrencyCode :: Lens' HostReservation (Maybe CurrencyCodeValues)
hrCurrencyCode = lens _hrCurrencyCode (\ s a -> s{_hrCurrencyCode = a})
hrHostReservationId :: Lens' HostReservation (Maybe Text)
hrHostReservationId = lens _hrHostReservationId (\ s a -> s{_hrHostReservationId = a})
hrStart :: Lens' HostReservation (Maybe UTCTime)
hrStart = lens _hrStart (\ s a -> s{_hrStart = a}) . mapping _Time
hrHourlyPrice :: Lens' HostReservation (Maybe Text)
hrHourlyPrice = lens _hrHourlyPrice (\ s a -> s{_hrHourlyPrice = a})
hrCount :: Lens' HostReservation (Maybe Int)
hrCount = lens _hrCount (\ s a -> s{_hrCount = a})
hrUpfrontPrice :: Lens' HostReservation (Maybe Text)
hrUpfrontPrice = lens _hrUpfrontPrice (\ s a -> s{_hrUpfrontPrice = a})
hrEnd :: Lens' HostReservation (Maybe UTCTime)
hrEnd = lens _hrEnd (\ s a -> s{_hrEnd = a}) . mapping _Time
hrHostIdSet :: Lens' HostReservation [Text]
hrHostIdSet = lens _hrHostIdSet (\ s a -> s{_hrHostIdSet = a}) . _Default . _Coerce
hrOfferingId :: Lens' HostReservation (Maybe Text)
hrOfferingId = lens _hrOfferingId (\ s a -> s{_hrOfferingId = a})
hrDuration :: Lens' HostReservation (Maybe Int)
hrDuration = lens _hrDuration (\ s a -> s{_hrDuration = a})
hrPaymentOption :: Lens' HostReservation (Maybe PaymentOption)
hrPaymentOption = lens _hrPaymentOption (\ s a -> s{_hrPaymentOption = a})
instance FromXML HostReservation where
parseXML x
= HostReservation' <$>
(x .@? "state") <*> (x .@? "instanceFamily") <*>
(x .@? "currencyCode")
<*> (x .@? "hostReservationId")
<*> (x .@? "start")
<*> (x .@? "hourlyPrice")
<*> (x .@? "count")
<*> (x .@? "upfrontPrice")
<*> (x .@? "end")
<*>
(x .@? "hostIdSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "offeringId")
<*> (x .@? "duration")
<*> (x .@? "paymentOption")
instance Hashable HostReservation where
instance NFData HostReservation where
data IAMInstanceProfile = IAMInstanceProfile'
{ _iapARN :: !(Maybe Text)
, _iapId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
iamInstanceProfile
:: IAMInstanceProfile
iamInstanceProfile = IAMInstanceProfile' {_iapARN = Nothing, _iapId = Nothing}
iapARN :: Lens' IAMInstanceProfile (Maybe Text)
iapARN = lens _iapARN (\ s a -> s{_iapARN = a})
iapId :: Lens' IAMInstanceProfile (Maybe Text)
iapId = lens _iapId (\ s a -> s{_iapId = a})
instance FromXML IAMInstanceProfile where
parseXML x
= IAMInstanceProfile' <$>
(x .@? "arn") <*> (x .@? "id")
instance Hashable IAMInstanceProfile where
instance NFData IAMInstanceProfile where
data IAMInstanceProfileAssociation = IAMInstanceProfileAssociation'
{ _iapaAssociationId :: !(Maybe Text)
, _iapaInstanceId :: !(Maybe Text)
, _iapaState :: !(Maybe IAMInstanceProfileAssociationState)
, _iapaIAMInstanceProfile :: !(Maybe IAMInstanceProfile)
, _iapaTimestamp :: !(Maybe ISO8601)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
iamInstanceProfileAssociation
:: IAMInstanceProfileAssociation
iamInstanceProfileAssociation =
IAMInstanceProfileAssociation'
{ _iapaAssociationId = Nothing
, _iapaInstanceId = Nothing
, _iapaState = Nothing
, _iapaIAMInstanceProfile = Nothing
, _iapaTimestamp = Nothing
}
iapaAssociationId :: Lens' IAMInstanceProfileAssociation (Maybe Text)
iapaAssociationId = lens _iapaAssociationId (\ s a -> s{_iapaAssociationId = a})
iapaInstanceId :: Lens' IAMInstanceProfileAssociation (Maybe Text)
iapaInstanceId = lens _iapaInstanceId (\ s a -> s{_iapaInstanceId = a})
iapaState :: Lens' IAMInstanceProfileAssociation (Maybe IAMInstanceProfileAssociationState)
iapaState = lens _iapaState (\ s a -> s{_iapaState = a})
iapaIAMInstanceProfile :: Lens' IAMInstanceProfileAssociation (Maybe IAMInstanceProfile)
iapaIAMInstanceProfile = lens _iapaIAMInstanceProfile (\ s a -> s{_iapaIAMInstanceProfile = a})
iapaTimestamp :: Lens' IAMInstanceProfileAssociation (Maybe UTCTime)
iapaTimestamp = lens _iapaTimestamp (\ s a -> s{_iapaTimestamp = a}) . mapping _Time
instance FromXML IAMInstanceProfileAssociation where
parseXML x
= IAMInstanceProfileAssociation' <$>
(x .@? "associationId") <*> (x .@? "instanceId") <*>
(x .@? "state")
<*> (x .@? "iamInstanceProfile")
<*> (x .@? "timestamp")
instance Hashable IAMInstanceProfileAssociation where
instance NFData IAMInstanceProfileAssociation where
data IAMInstanceProfileSpecification = IAMInstanceProfileSpecification'
{ _iapsARN :: !(Maybe Text)
, _iapsName :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
iamInstanceProfileSpecification
:: IAMInstanceProfileSpecification
iamInstanceProfileSpecification =
IAMInstanceProfileSpecification' {_iapsARN = Nothing, _iapsName = Nothing}
iapsARN :: Lens' IAMInstanceProfileSpecification (Maybe Text)
iapsARN = lens _iapsARN (\ s a -> s{_iapsARN = a})
iapsName :: Lens' IAMInstanceProfileSpecification (Maybe Text)
iapsName = lens _iapsName (\ s a -> s{_iapsName = a})
instance FromXML IAMInstanceProfileSpecification
where
parseXML x
= IAMInstanceProfileSpecification' <$>
(x .@? "arn") <*> (x .@? "name")
instance Hashable IAMInstanceProfileSpecification
where
instance NFData IAMInstanceProfileSpecification where
instance ToQuery IAMInstanceProfileSpecification
where
toQuery IAMInstanceProfileSpecification'{..}
= mconcat ["Arn" =: _iapsARN, "Name" =: _iapsName]
data ICMPTypeCode = ICMPTypeCode'
{ _itcCode :: !(Maybe Int)
, _itcType :: !(Maybe Int)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
icmpTypeCode
:: ICMPTypeCode
icmpTypeCode = ICMPTypeCode' {_itcCode = Nothing, _itcType = Nothing}
itcCode :: Lens' ICMPTypeCode (Maybe Int)
itcCode = lens _itcCode (\ s a -> s{_itcCode = a})
itcType :: Lens' ICMPTypeCode (Maybe Int)
itcType = lens _itcType (\ s a -> s{_itcType = a})
instance FromXML ICMPTypeCode where
parseXML x
= ICMPTypeCode' <$> (x .@? "code") <*> (x .@? "type")
instance Hashable ICMPTypeCode where
instance NFData ICMPTypeCode where
instance ToQuery ICMPTypeCode where
toQuery ICMPTypeCode'{..}
= mconcat ["Code" =: _itcCode, "Type" =: _itcType]
data IPPermission = IPPermission'
{ _ipFromPort :: !(Maybe Int)
, _ipUserIdGroupPairs :: !(Maybe [UserIdGroupPair])
, _ipPrefixListIds :: !(Maybe [PrefixListId])
, _ipToPort :: !(Maybe Int)
, _ipIPv6Ranges :: !(Maybe [IPv6Range])
, _ipIPRanges :: !(Maybe [IPRange])
, _ipIPProtocol :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
ipPermission
:: Text
-> IPPermission
ipPermission pIPProtocol_ =
IPPermission'
{ _ipFromPort = Nothing
, _ipUserIdGroupPairs = Nothing
, _ipPrefixListIds = Nothing
, _ipToPort = Nothing
, _ipIPv6Ranges = Nothing
, _ipIPRanges = Nothing
, _ipIPProtocol = pIPProtocol_
}
ipFromPort :: Lens' IPPermission (Maybe Int)
ipFromPort = lens _ipFromPort (\ s a -> s{_ipFromPort = a})
ipUserIdGroupPairs :: Lens' IPPermission [UserIdGroupPair]
ipUserIdGroupPairs = lens _ipUserIdGroupPairs (\ s a -> s{_ipUserIdGroupPairs = a}) . _Default . _Coerce
ipPrefixListIds :: Lens' IPPermission [PrefixListId]
ipPrefixListIds = lens _ipPrefixListIds (\ s a -> s{_ipPrefixListIds = a}) . _Default . _Coerce
ipToPort :: Lens' IPPermission (Maybe Int)
ipToPort = lens _ipToPort (\ s a -> s{_ipToPort = a})
ipIPv6Ranges :: Lens' IPPermission [IPv6Range]
ipIPv6Ranges = lens _ipIPv6Ranges (\ s a -> s{_ipIPv6Ranges = a}) . _Default . _Coerce
ipIPRanges :: Lens' IPPermission [IPRange]
ipIPRanges = lens _ipIPRanges (\ s a -> s{_ipIPRanges = a}) . _Default . _Coerce
ipIPProtocol :: Lens' IPPermission Text
ipIPProtocol = lens _ipIPProtocol (\ s a -> s{_ipIPProtocol = a})
instance FromXML IPPermission where
parseXML x
= IPPermission' <$>
(x .@? "fromPort") <*>
(x .@? "groups" .!@ mempty >>=
may (parseXMLList "item"))
<*>
(x .@? "prefixListIds" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "toPort")
<*>
(x .@? "ipv6Ranges" .!@ mempty >>=
may (parseXMLList "item"))
<*>
(x .@? "ipRanges" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@ "ipProtocol")
instance Hashable IPPermission where
instance NFData IPPermission where
instance ToQuery IPPermission where
toQuery IPPermission'{..}
= mconcat
["FromPort" =: _ipFromPort,
toQuery
(toQueryList "Groups" <$> _ipUserIdGroupPairs),
toQuery
(toQueryList "PrefixListIds" <$> _ipPrefixListIds),
"ToPort" =: _ipToPort,
toQuery (toQueryList "Ipv6Ranges" <$> _ipIPv6Ranges),
toQuery (toQueryList "IpRanges" <$> _ipIPRanges),
"IpProtocol" =: _ipIPProtocol]
data IPRange = IPRange'
{ _iprDescription :: !(Maybe Text)
, _iprCidrIP :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
ipRange
:: Text
-> IPRange
ipRange pCidrIP_ = IPRange' {_iprDescription = Nothing, _iprCidrIP = pCidrIP_}
iprDescription :: Lens' IPRange (Maybe Text)
iprDescription = lens _iprDescription (\ s a -> s{_iprDescription = a})
iprCidrIP :: Lens' IPRange Text
iprCidrIP = lens _iprCidrIP (\ s a -> s{_iprCidrIP = a})
instance FromXML IPRange where
parseXML x
= IPRange' <$>
(x .@? "description") <*> (x .@ "cidrIp")
instance Hashable IPRange where
instance NFData IPRange where
instance ToQuery IPRange where
toQuery IPRange'{..}
= mconcat
["Description" =: _iprDescription,
"CidrIp" =: _iprCidrIP]
newtype IPv6CidrBlock = IPv6CidrBlock'
{ _icbIPv6CidrBlock :: Maybe Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
ipv6CidrBlock
:: IPv6CidrBlock
ipv6CidrBlock = IPv6CidrBlock' {_icbIPv6CidrBlock = Nothing}
icbIPv6CidrBlock :: Lens' IPv6CidrBlock (Maybe Text)
icbIPv6CidrBlock = lens _icbIPv6CidrBlock (\ s a -> s{_icbIPv6CidrBlock = a})
instance FromXML IPv6CidrBlock where
parseXML x
= IPv6CidrBlock' <$> (x .@? "ipv6CidrBlock")
instance Hashable IPv6CidrBlock where
instance NFData IPv6CidrBlock where
data IPv6Range = IPv6Range'
{ _irCidrIPv6 :: !(Maybe Text)
, _irDescription :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
ipv6Range
:: IPv6Range
ipv6Range = IPv6Range' {_irCidrIPv6 = Nothing, _irDescription = Nothing}
irCidrIPv6 :: Lens' IPv6Range (Maybe Text)
irCidrIPv6 = lens _irCidrIPv6 (\ s a -> s{_irCidrIPv6 = a})
irDescription :: Lens' IPv6Range (Maybe Text)
irDescription = lens _irDescription (\ s a -> s{_irDescription = a})
instance FromXML IPv6Range where
parseXML x
= IPv6Range' <$>
(x .@? "cidrIpv6") <*> (x .@? "description")
instance Hashable IPv6Range where
instance NFData IPv6Range where
instance ToQuery IPv6Range where
toQuery IPv6Range'{..}
= mconcat
["CidrIpv6" =: _irCidrIPv6,
"Description" =: _irDescription]
data IdFormat = IdFormat'
{ _ifUseLongIds :: !(Maybe Bool)
, _ifDeadline :: !(Maybe ISO8601)
, _ifResource :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
idFormat
:: IdFormat
idFormat =
IdFormat'
{_ifUseLongIds = Nothing, _ifDeadline = Nothing, _ifResource = Nothing}
ifUseLongIds :: Lens' IdFormat (Maybe Bool)
ifUseLongIds = lens _ifUseLongIds (\ s a -> s{_ifUseLongIds = a})
ifDeadline :: Lens' IdFormat (Maybe UTCTime)
ifDeadline = lens _ifDeadline (\ s a -> s{_ifDeadline = a}) . mapping _Time
ifResource :: Lens' IdFormat (Maybe Text)
ifResource = lens _ifResource (\ s a -> s{_ifResource = a})
instance FromXML IdFormat where
parseXML x
= IdFormat' <$>
(x .@? "useLongIds") <*> (x .@? "deadline") <*>
(x .@? "resource")
instance Hashable IdFormat where
instance NFData IdFormat where
data Image = Image'
{ _iPlatform :: !(Maybe PlatformValues)
, _iEnaSupport :: !(Maybe Bool)
, _iImageOwnerAlias :: !(Maybe Text)
, _iRAMDiskId :: !(Maybe Text)
, _iKernelId :: !(Maybe Text)
, _iRootDeviceName :: !(Maybe Text)
, _iSRIOVNetSupport :: !(Maybe Text)
, _iName :: !(Maybe Text)
, _iCreationDate :: !(Maybe Text)
, _iProductCodes :: !(Maybe [ProductCode])
, _iStateReason :: !(Maybe StateReason)
, _iDescription :: !(Maybe Text)
, _iBlockDeviceMappings :: !(Maybe [BlockDeviceMapping])
, _iTags :: !(Maybe [Tag])
, _iImageId :: !Text
, _iImageLocation :: !Text
, _iState :: !ImageState
, _iOwnerId :: !Text
, _iPublic :: !Bool
, _iArchitecture :: !ArchitectureValues
, _iImageType :: !ImageTypeValues
, _iRootDeviceType :: !DeviceType
, _iVirtualizationType :: !VirtualizationType
, _iHypervisor :: !HypervisorType
} deriving (Eq, Read, Show, Data, Typeable, Generic)
image
:: Text
-> Text
-> ImageState
-> Text
-> Bool
-> ArchitectureValues
-> ImageTypeValues
-> DeviceType
-> VirtualizationType
-> HypervisorType
-> Image
image pImageId_ pImageLocation_ pState_ pOwnerId_ pPublic_ pArchitecture_ pImageType_ pRootDeviceType_ pVirtualizationType_ pHypervisor_ =
Image'
{ _iPlatform = Nothing
, _iEnaSupport = Nothing
, _iImageOwnerAlias = Nothing
, _iRAMDiskId = Nothing
, _iKernelId = Nothing
, _iRootDeviceName = Nothing
, _iSRIOVNetSupport = Nothing
, _iName = Nothing
, _iCreationDate = Nothing
, _iProductCodes = Nothing
, _iStateReason = Nothing
, _iDescription = Nothing
, _iBlockDeviceMappings = Nothing
, _iTags = Nothing
, _iImageId = pImageId_
, _iImageLocation = pImageLocation_
, _iState = pState_
, _iOwnerId = pOwnerId_
, _iPublic = pPublic_
, _iArchitecture = pArchitecture_
, _iImageType = pImageType_
, _iRootDeviceType = pRootDeviceType_
, _iVirtualizationType = pVirtualizationType_
, _iHypervisor = pHypervisor_
}
iPlatform :: Lens' Image (Maybe PlatformValues)
iPlatform = lens _iPlatform (\ s a -> s{_iPlatform = a})
iEnaSupport :: Lens' Image (Maybe Bool)
iEnaSupport = lens _iEnaSupport (\ s a -> s{_iEnaSupport = a})
iImageOwnerAlias :: Lens' Image (Maybe Text)
iImageOwnerAlias = lens _iImageOwnerAlias (\ s a -> s{_iImageOwnerAlias = a})
iRAMDiskId :: Lens' Image (Maybe Text)
iRAMDiskId = lens _iRAMDiskId (\ s a -> s{_iRAMDiskId = a})
iKernelId :: Lens' Image (Maybe Text)
iKernelId = lens _iKernelId (\ s a -> s{_iKernelId = a})
iRootDeviceName :: Lens' Image (Maybe Text)
iRootDeviceName = lens _iRootDeviceName (\ s a -> s{_iRootDeviceName = a})
iSRIOVNetSupport :: Lens' Image (Maybe Text)
iSRIOVNetSupport = lens _iSRIOVNetSupport (\ s a -> s{_iSRIOVNetSupport = a})
iName :: Lens' Image (Maybe Text)
iName = lens _iName (\ s a -> s{_iName = a})
iCreationDate :: Lens' Image (Maybe Text)
iCreationDate = lens _iCreationDate (\ s a -> s{_iCreationDate = a})
iProductCodes :: Lens' Image [ProductCode]
iProductCodes = lens _iProductCodes (\ s a -> s{_iProductCodes = a}) . _Default . _Coerce
iStateReason :: Lens' Image (Maybe StateReason)
iStateReason = lens _iStateReason (\ s a -> s{_iStateReason = a})
iDescription :: Lens' Image (Maybe Text)
iDescription = lens _iDescription (\ s a -> s{_iDescription = a})
iBlockDeviceMappings :: Lens' Image [BlockDeviceMapping]
iBlockDeviceMappings = lens _iBlockDeviceMappings (\ s a -> s{_iBlockDeviceMappings = a}) . _Default . _Coerce
iTags :: Lens' Image [Tag]
iTags = lens _iTags (\ s a -> s{_iTags = a}) . _Default . _Coerce
iImageId :: Lens' Image Text
iImageId = lens _iImageId (\ s a -> s{_iImageId = a})
iImageLocation :: Lens' Image Text
iImageLocation = lens _iImageLocation (\ s a -> s{_iImageLocation = a})
iState :: Lens' Image ImageState
iState = lens _iState (\ s a -> s{_iState = a})
iOwnerId :: Lens' Image Text
iOwnerId = lens _iOwnerId (\ s a -> s{_iOwnerId = a})
iPublic :: Lens' Image Bool
iPublic = lens _iPublic (\ s a -> s{_iPublic = a})
iArchitecture :: Lens' Image ArchitectureValues
iArchitecture = lens _iArchitecture (\ s a -> s{_iArchitecture = a})
iImageType :: Lens' Image ImageTypeValues
iImageType = lens _iImageType (\ s a -> s{_iImageType = a})
iRootDeviceType :: Lens' Image DeviceType
iRootDeviceType = lens _iRootDeviceType (\ s a -> s{_iRootDeviceType = a})
iVirtualizationType :: Lens' Image VirtualizationType
iVirtualizationType = lens _iVirtualizationType (\ s a -> s{_iVirtualizationType = a})
iHypervisor :: Lens' Image HypervisorType
iHypervisor = lens _iHypervisor (\ s a -> s{_iHypervisor = a})
instance FromXML Image where
parseXML x
= Image' <$>
(x .@? "platform") <*> (x .@? "enaSupport") <*>
(x .@? "imageOwnerAlias")
<*> (x .@? "ramdiskId")
<*> (x .@? "kernelId")
<*> (x .@? "rootDeviceName")
<*> (x .@? "sriovNetSupport")
<*> (x .@? "name")
<*> (x .@? "creationDate")
<*>
(x .@? "productCodes" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "stateReason")
<*> (x .@? "description")
<*>
(x .@? "blockDeviceMapping" .!@ mempty >>=
may (parseXMLList "item"))
<*>
(x .@? "tagSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@ "imageId")
<*> (x .@ "imageLocation")
<*> (x .@ "imageState")
<*> (x .@ "imageOwnerId")
<*> (x .@ "isPublic")
<*> (x .@ "architecture")
<*> (x .@ "imageType")
<*> (x .@ "rootDeviceType")
<*> (x .@ "virtualizationType")
<*> (x .@ "hypervisor")
instance Hashable Image where
instance NFData Image where
data ImageDiskContainer = ImageDiskContainer'
{ _idcFormat :: !(Maybe Text)
, _idcURL :: !(Maybe Text)
, _idcDeviceName :: !(Maybe Text)
, _idcUserBucket :: !(Maybe UserBucket)
, _idcDescription :: !(Maybe Text)
, _idcSnapshotId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
imageDiskContainer
:: ImageDiskContainer
imageDiskContainer =
ImageDiskContainer'
{ _idcFormat = Nothing
, _idcURL = Nothing
, _idcDeviceName = Nothing
, _idcUserBucket = Nothing
, _idcDescription = Nothing
, _idcSnapshotId = Nothing
}
idcFormat :: Lens' ImageDiskContainer (Maybe Text)
idcFormat = lens _idcFormat (\ s a -> s{_idcFormat = a})
idcURL :: Lens' ImageDiskContainer (Maybe Text)
idcURL = lens _idcURL (\ s a -> s{_idcURL = a})
idcDeviceName :: Lens' ImageDiskContainer (Maybe Text)
idcDeviceName = lens _idcDeviceName (\ s a -> s{_idcDeviceName = a})
idcUserBucket :: Lens' ImageDiskContainer (Maybe UserBucket)
idcUserBucket = lens _idcUserBucket (\ s a -> s{_idcUserBucket = a})
idcDescription :: Lens' ImageDiskContainer (Maybe Text)
idcDescription = lens _idcDescription (\ s a -> s{_idcDescription = a})
idcSnapshotId :: Lens' ImageDiskContainer (Maybe Text)
idcSnapshotId = lens _idcSnapshotId (\ s a -> s{_idcSnapshotId = a})
instance Hashable ImageDiskContainer where
instance NFData ImageDiskContainer where
instance ToQuery ImageDiskContainer where
toQuery ImageDiskContainer'{..}
= mconcat
["Format" =: _idcFormat, "Url" =: _idcURL,
"DeviceName" =: _idcDeviceName,
"UserBucket" =: _idcUserBucket,
"Description" =: _idcDescription,
"SnapshotId" =: _idcSnapshotId]
data ImportImageTask = ImportImageTask'
{ _iitStatus :: !(Maybe Text)
, _iitHypervisor :: !(Maybe Text)
, _iitPlatform :: !(Maybe Text)
, _iitProgress :: !(Maybe Text)
, _iitLicenseType :: !(Maybe Text)
, _iitSnapshotDetails :: !(Maybe [SnapshotDetail])
, _iitStatusMessage :: !(Maybe Text)
, _iitImageId :: !(Maybe Text)
, _iitImportTaskId :: !(Maybe Text)
, _iitArchitecture :: !(Maybe Text)
, _iitDescription :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
importImageTask
:: ImportImageTask
importImageTask =
ImportImageTask'
{ _iitStatus = Nothing
, _iitHypervisor = Nothing
, _iitPlatform = Nothing
, _iitProgress = Nothing
, _iitLicenseType = Nothing
, _iitSnapshotDetails = Nothing
, _iitStatusMessage = Nothing
, _iitImageId = Nothing
, _iitImportTaskId = Nothing
, _iitArchitecture = Nothing
, _iitDescription = Nothing
}
iitStatus :: Lens' ImportImageTask (Maybe Text)
iitStatus = lens _iitStatus (\ s a -> s{_iitStatus = a})
iitHypervisor :: Lens' ImportImageTask (Maybe Text)
iitHypervisor = lens _iitHypervisor (\ s a -> s{_iitHypervisor = a})
iitPlatform :: Lens' ImportImageTask (Maybe Text)
iitPlatform = lens _iitPlatform (\ s a -> s{_iitPlatform = a})
iitProgress :: Lens' ImportImageTask (Maybe Text)
iitProgress = lens _iitProgress (\ s a -> s{_iitProgress = a})
iitLicenseType :: Lens' ImportImageTask (Maybe Text)
iitLicenseType = lens _iitLicenseType (\ s a -> s{_iitLicenseType = a})
iitSnapshotDetails :: Lens' ImportImageTask [SnapshotDetail]
iitSnapshotDetails = lens _iitSnapshotDetails (\ s a -> s{_iitSnapshotDetails = a}) . _Default . _Coerce
iitStatusMessage :: Lens' ImportImageTask (Maybe Text)
iitStatusMessage = lens _iitStatusMessage (\ s a -> s{_iitStatusMessage = a})
iitImageId :: Lens' ImportImageTask (Maybe Text)
iitImageId = lens _iitImageId (\ s a -> s{_iitImageId = a})
iitImportTaskId :: Lens' ImportImageTask (Maybe Text)
iitImportTaskId = lens _iitImportTaskId (\ s a -> s{_iitImportTaskId = a})
iitArchitecture :: Lens' ImportImageTask (Maybe Text)
iitArchitecture = lens _iitArchitecture (\ s a -> s{_iitArchitecture = a})
iitDescription :: Lens' ImportImageTask (Maybe Text)
iitDescription = lens _iitDescription (\ s a -> s{_iitDescription = a})
instance FromXML ImportImageTask where
parseXML x
= ImportImageTask' <$>
(x .@? "status") <*> (x .@? "hypervisor") <*>
(x .@? "platform")
<*> (x .@? "progress")
<*> (x .@? "licenseType")
<*>
(x .@? "snapshotDetailSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "statusMessage")
<*> (x .@? "imageId")
<*> (x .@? "importTaskId")
<*> (x .@? "architecture")
<*> (x .@? "description")
instance Hashable ImportImageTask where
instance NFData ImportImageTask where
data ImportInstanceLaunchSpecification = ImportInstanceLaunchSpecification'
{ _iilsAdditionalInfo :: !(Maybe Text)
, _iilsGroupNames :: !(Maybe [Text])
, _iilsSubnetId :: !(Maybe Text)
, _iilsInstanceType :: !(Maybe InstanceType)
, _iilsGroupIds :: !(Maybe [Text])
, _iilsUserData :: !(Maybe UserData)
, _iilsMonitoring :: !(Maybe Bool)
, _iilsPrivateIPAddress :: !(Maybe Text)
, _iilsInstanceInitiatedShutdownBehavior :: !(Maybe ShutdownBehavior)
, _iilsArchitecture :: !(Maybe ArchitectureValues)
, _iilsPlacement :: !(Maybe Placement)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
importInstanceLaunchSpecification
:: ImportInstanceLaunchSpecification
importInstanceLaunchSpecification =
ImportInstanceLaunchSpecification'
{ _iilsAdditionalInfo = Nothing
, _iilsGroupNames = Nothing
, _iilsSubnetId = Nothing
, _iilsInstanceType = Nothing
, _iilsGroupIds = Nothing
, _iilsUserData = Nothing
, _iilsMonitoring = Nothing
, _iilsPrivateIPAddress = Nothing
, _iilsInstanceInitiatedShutdownBehavior = Nothing
, _iilsArchitecture = Nothing
, _iilsPlacement = Nothing
}
iilsAdditionalInfo :: Lens' ImportInstanceLaunchSpecification (Maybe Text)
iilsAdditionalInfo = lens _iilsAdditionalInfo (\ s a -> s{_iilsAdditionalInfo = a})
iilsGroupNames :: Lens' ImportInstanceLaunchSpecification [Text]
iilsGroupNames = lens _iilsGroupNames (\ s a -> s{_iilsGroupNames = a}) . _Default . _Coerce
iilsSubnetId :: Lens' ImportInstanceLaunchSpecification (Maybe Text)
iilsSubnetId = lens _iilsSubnetId (\ s a -> s{_iilsSubnetId = a})
iilsInstanceType :: Lens' ImportInstanceLaunchSpecification (Maybe InstanceType)
iilsInstanceType = lens _iilsInstanceType (\ s a -> s{_iilsInstanceType = a})
iilsGroupIds :: Lens' ImportInstanceLaunchSpecification [Text]
iilsGroupIds = lens _iilsGroupIds (\ s a -> s{_iilsGroupIds = a}) . _Default . _Coerce
iilsUserData :: Lens' ImportInstanceLaunchSpecification (Maybe UserData)
iilsUserData = lens _iilsUserData (\ s a -> s{_iilsUserData = a})
iilsMonitoring :: Lens' ImportInstanceLaunchSpecification (Maybe Bool)
iilsMonitoring = lens _iilsMonitoring (\ s a -> s{_iilsMonitoring = a})
iilsPrivateIPAddress :: Lens' ImportInstanceLaunchSpecification (Maybe Text)
iilsPrivateIPAddress = lens _iilsPrivateIPAddress (\ s a -> s{_iilsPrivateIPAddress = a})
iilsInstanceInitiatedShutdownBehavior :: Lens' ImportInstanceLaunchSpecification (Maybe ShutdownBehavior)
iilsInstanceInitiatedShutdownBehavior = lens _iilsInstanceInitiatedShutdownBehavior (\ s a -> s{_iilsInstanceInitiatedShutdownBehavior = a})
iilsArchitecture :: Lens' ImportInstanceLaunchSpecification (Maybe ArchitectureValues)
iilsArchitecture = lens _iilsArchitecture (\ s a -> s{_iilsArchitecture = a})
iilsPlacement :: Lens' ImportInstanceLaunchSpecification (Maybe Placement)
iilsPlacement = lens _iilsPlacement (\ s a -> s{_iilsPlacement = a})
instance Hashable ImportInstanceLaunchSpecification
where
instance NFData ImportInstanceLaunchSpecification
where
instance ToQuery ImportInstanceLaunchSpecification
where
toQuery ImportInstanceLaunchSpecification'{..}
= mconcat
["AdditionalInfo" =: _iilsAdditionalInfo,
toQuery
(toQueryList "GroupName" <$> _iilsGroupNames),
"SubnetId" =: _iilsSubnetId,
"InstanceType" =: _iilsInstanceType,
toQuery (toQueryList "GroupId" <$> _iilsGroupIds),
"UserData" =: _iilsUserData,
"Monitoring" =: _iilsMonitoring,
"PrivateIpAddress" =: _iilsPrivateIPAddress,
"InstanceInitiatedShutdownBehavior" =:
_iilsInstanceInitiatedShutdownBehavior,
"Architecture" =: _iilsArchitecture,
"Placement" =: _iilsPlacement]
data ImportInstanceTaskDetails = ImportInstanceTaskDetails'
{ _iitdInstanceId :: !(Maybe Text)
, _iitdPlatform :: !(Maybe PlatformValues)
, _iitdVolumes :: !(Maybe [ImportInstanceVolumeDetailItem])
, _iitdDescription :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
importInstanceTaskDetails
:: ImportInstanceTaskDetails
importInstanceTaskDetails =
ImportInstanceTaskDetails'
{ _iitdInstanceId = Nothing
, _iitdPlatform = Nothing
, _iitdVolumes = Nothing
, _iitdDescription = Nothing
}
iitdInstanceId :: Lens' ImportInstanceTaskDetails (Maybe Text)
iitdInstanceId = lens _iitdInstanceId (\ s a -> s{_iitdInstanceId = a})
iitdPlatform :: Lens' ImportInstanceTaskDetails (Maybe PlatformValues)
iitdPlatform = lens _iitdPlatform (\ s a -> s{_iitdPlatform = a})
iitdVolumes :: Lens' ImportInstanceTaskDetails [ImportInstanceVolumeDetailItem]
iitdVolumes = lens _iitdVolumes (\ s a -> s{_iitdVolumes = a}) . _Default . _Coerce
iitdDescription :: Lens' ImportInstanceTaskDetails (Maybe Text)
iitdDescription = lens _iitdDescription (\ s a -> s{_iitdDescription = a})
instance FromXML ImportInstanceTaskDetails where
parseXML x
= ImportInstanceTaskDetails' <$>
(x .@? "instanceId") <*> (x .@? "platform") <*>
(x .@? "volumes" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "description")
instance Hashable ImportInstanceTaskDetails where
instance NFData ImportInstanceTaskDetails where
data ImportInstanceVolumeDetailItem = ImportInstanceVolumeDetailItem'
{ _iivdiStatusMessage :: !(Maybe Text)
, _iivdiDescription :: !(Maybe Text)
, _iivdiAvailabilityZone :: !Text
, _iivdiBytesConverted :: !Integer
, _iivdiImage :: !DiskImageDescription
, _iivdiStatus :: !Text
, _iivdiVolume :: !DiskImageVolumeDescription
} deriving (Eq, Read, Show, Data, Typeable, Generic)
importInstanceVolumeDetailItem
:: Text
-> Integer
-> DiskImageDescription
-> Text
-> DiskImageVolumeDescription
-> ImportInstanceVolumeDetailItem
importInstanceVolumeDetailItem pAvailabilityZone_ pBytesConverted_ pImage_ pStatus_ pVolume_ =
ImportInstanceVolumeDetailItem'
{ _iivdiStatusMessage = Nothing
, _iivdiDescription = Nothing
, _iivdiAvailabilityZone = pAvailabilityZone_
, _iivdiBytesConverted = pBytesConverted_
, _iivdiImage = pImage_
, _iivdiStatus = pStatus_
, _iivdiVolume = pVolume_
}
iivdiStatusMessage :: Lens' ImportInstanceVolumeDetailItem (Maybe Text)
iivdiStatusMessage = lens _iivdiStatusMessage (\ s a -> s{_iivdiStatusMessage = a})
iivdiDescription :: Lens' ImportInstanceVolumeDetailItem (Maybe Text)
iivdiDescription = lens _iivdiDescription (\ s a -> s{_iivdiDescription = a})
iivdiAvailabilityZone :: Lens' ImportInstanceVolumeDetailItem Text
iivdiAvailabilityZone = lens _iivdiAvailabilityZone (\ s a -> s{_iivdiAvailabilityZone = a})
iivdiBytesConverted :: Lens' ImportInstanceVolumeDetailItem Integer
iivdiBytesConverted = lens _iivdiBytesConverted (\ s a -> s{_iivdiBytesConverted = a})
iivdiImage :: Lens' ImportInstanceVolumeDetailItem DiskImageDescription
iivdiImage = lens _iivdiImage (\ s a -> s{_iivdiImage = a})
iivdiStatus :: Lens' ImportInstanceVolumeDetailItem Text
iivdiStatus = lens _iivdiStatus (\ s a -> s{_iivdiStatus = a})
iivdiVolume :: Lens' ImportInstanceVolumeDetailItem DiskImageVolumeDescription
iivdiVolume = lens _iivdiVolume (\ s a -> s{_iivdiVolume = a})
instance FromXML ImportInstanceVolumeDetailItem where
parseXML x
= ImportInstanceVolumeDetailItem' <$>
(x .@? "statusMessage") <*> (x .@? "description") <*>
(x .@ "availabilityZone")
<*> (x .@ "bytesConverted")
<*> (x .@ "image")
<*> (x .@ "status")
<*> (x .@ "volume")
instance Hashable ImportInstanceVolumeDetailItem
where
instance NFData ImportInstanceVolumeDetailItem where
data ImportSnapshotTask = ImportSnapshotTask'
{ _istSnapshotTaskDetail :: !(Maybe SnapshotTaskDetail)
, _istImportTaskId :: !(Maybe Text)
, _istDescription :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
importSnapshotTask
:: ImportSnapshotTask
importSnapshotTask =
ImportSnapshotTask'
{ _istSnapshotTaskDetail = Nothing
, _istImportTaskId = Nothing
, _istDescription = Nothing
}
istSnapshotTaskDetail :: Lens' ImportSnapshotTask (Maybe SnapshotTaskDetail)
istSnapshotTaskDetail = lens _istSnapshotTaskDetail (\ s a -> s{_istSnapshotTaskDetail = a})
istImportTaskId :: Lens' ImportSnapshotTask (Maybe Text)
istImportTaskId = lens _istImportTaskId (\ s a -> s{_istImportTaskId = a})
istDescription :: Lens' ImportSnapshotTask (Maybe Text)
istDescription = lens _istDescription (\ s a -> s{_istDescription = a})
instance FromXML ImportSnapshotTask where
parseXML x
= ImportSnapshotTask' <$>
(x .@? "snapshotTaskDetail") <*>
(x .@? "importTaskId")
<*> (x .@? "description")
instance Hashable ImportSnapshotTask where
instance NFData ImportSnapshotTask where
data ImportVolumeTaskDetails = ImportVolumeTaskDetails'
{ _ivtdBytesConverted :: !(Maybe Integer)
, _ivtdImage :: !(Maybe DiskImageDescription)
, _ivtdVolume :: !(Maybe DiskImageVolumeDescription)
, _ivtdAvailabilityZone :: !(Maybe Text)
, _ivtdDescription :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
importVolumeTaskDetails
:: ImportVolumeTaskDetails
importVolumeTaskDetails =
ImportVolumeTaskDetails'
{ _ivtdBytesConverted = Nothing
, _ivtdImage = Nothing
, _ivtdVolume = Nothing
, _ivtdAvailabilityZone = Nothing
, _ivtdDescription = Nothing
}
ivtdBytesConverted :: Lens' ImportVolumeTaskDetails (Maybe Integer)
ivtdBytesConverted = lens _ivtdBytesConverted (\ s a -> s{_ivtdBytesConverted = a})
ivtdImage :: Lens' ImportVolumeTaskDetails (Maybe DiskImageDescription)
ivtdImage = lens _ivtdImage (\ s a -> s{_ivtdImage = a})
ivtdVolume :: Lens' ImportVolumeTaskDetails (Maybe DiskImageVolumeDescription)
ivtdVolume = lens _ivtdVolume (\ s a -> s{_ivtdVolume = a})
ivtdAvailabilityZone :: Lens' ImportVolumeTaskDetails (Maybe Text)
ivtdAvailabilityZone = lens _ivtdAvailabilityZone (\ s a -> s{_ivtdAvailabilityZone = a})
ivtdDescription :: Lens' ImportVolumeTaskDetails (Maybe Text)
ivtdDescription = lens _ivtdDescription (\ s a -> s{_ivtdDescription = a})
instance FromXML ImportVolumeTaskDetails where
parseXML x
= ImportVolumeTaskDetails' <$>
(x .@? "bytesConverted") <*> (x .@? "image") <*>
(x .@? "volume")
<*> (x .@? "availabilityZone")
<*> (x .@? "description")
instance Hashable ImportVolumeTaskDetails where
instance NFData ImportVolumeTaskDetails where
data Instance = Instance'
{ _insPublicDNSName :: !(Maybe Text)
, _insPlatform :: !(Maybe PlatformValues)
, _insSecurityGroups :: !(Maybe [GroupIdentifier])
, _insClientToken :: !(Maybe Text)
, _insEnaSupport :: !(Maybe Bool)
, _insSourceDestCheck :: !(Maybe Bool)
, _insElasticGpuAssociations :: !(Maybe [ElasticGpuAssociation])
, _insVPCId :: !(Maybe Text)
, _insKeyName :: !(Maybe Text)
, _insNetworkInterfaces :: !(Maybe [InstanceNetworkInterface])
, _insRAMDiskId :: !(Maybe Text)
, _insCPUOptions :: !(Maybe CPUOptions)
, _insSubnetId :: !(Maybe Text)
, _insKernelId :: !(Maybe Text)
, _insRootDeviceName :: !(Maybe Text)
, _insSRIOVNetSupport :: !(Maybe Text)
, _insEBSOptimized :: !(Maybe Bool)
, _insStateTransitionReason :: !(Maybe Text)
, _insInstanceLifecycle :: !(Maybe InstanceLifecycleType)
, _insIAMInstanceProfile :: !(Maybe IAMInstanceProfile)
, _insPrivateIPAddress :: !(Maybe Text)
, _insProductCodes :: !(Maybe [ProductCode])
, _insSpotInstanceRequestId :: !(Maybe Text)
, _insPrivateDNSName :: !(Maybe Text)
, _insStateReason :: !(Maybe StateReason)
, _insBlockDeviceMappings :: !(Maybe [InstanceBlockDeviceMapping])
, _insPublicIPAddress :: !(Maybe Text)
, _insTags :: !(Maybe [Tag])
, _insInstanceId :: !Text
, _insImageId :: !Text
, _insAMILaunchIndex :: !Int
, _insInstanceType :: !InstanceType
, _insLaunchTime :: !ISO8601
, _insPlacement :: !Placement
, _insMonitoring :: !Monitoring
, _insArchitecture :: !ArchitectureValues
, _insRootDeviceType :: !DeviceType
, _insVirtualizationType :: !VirtualizationType
, _insHypervisor :: !HypervisorType
, _insState :: !InstanceState
} deriving (Eq, Read, Show, Data, Typeable, Generic)
instance'
:: Text
-> Text
-> Int
-> InstanceType
-> UTCTime
-> Placement
-> Monitoring
-> ArchitectureValues
-> DeviceType
-> VirtualizationType
-> HypervisorType
-> InstanceState
-> Instance
instance' pInstanceId_ pImageId_ pAMILaunchIndex_ pInstanceType_ pLaunchTime_ pPlacement_ pMonitoring_ pArchitecture_ pRootDeviceType_ pVirtualizationType_ pHypervisor_ pState_ =
Instance'
{ _insPublicDNSName = Nothing
, _insPlatform = Nothing
, _insSecurityGroups = Nothing
, _insClientToken = Nothing
, _insEnaSupport = Nothing
, _insSourceDestCheck = Nothing
, _insElasticGpuAssociations = Nothing
, _insVPCId = Nothing
, _insKeyName = Nothing
, _insNetworkInterfaces = Nothing
, _insRAMDiskId = Nothing
, _insCPUOptions = Nothing
, _insSubnetId = Nothing
, _insKernelId = Nothing
, _insRootDeviceName = Nothing
, _insSRIOVNetSupport = Nothing
, _insEBSOptimized = Nothing
, _insStateTransitionReason = Nothing
, _insInstanceLifecycle = Nothing
, _insIAMInstanceProfile = Nothing
, _insPrivateIPAddress = Nothing
, _insProductCodes = Nothing
, _insSpotInstanceRequestId = Nothing
, _insPrivateDNSName = Nothing
, _insStateReason = Nothing
, _insBlockDeviceMappings = Nothing
, _insPublicIPAddress = Nothing
, _insTags = Nothing
, _insInstanceId = pInstanceId_
, _insImageId = pImageId_
, _insAMILaunchIndex = pAMILaunchIndex_
, _insInstanceType = pInstanceType_
, _insLaunchTime = _Time # pLaunchTime_
, _insPlacement = pPlacement_
, _insMonitoring = pMonitoring_
, _insArchitecture = pArchitecture_
, _insRootDeviceType = pRootDeviceType_
, _insVirtualizationType = pVirtualizationType_
, _insHypervisor = pHypervisor_
, _insState = pState_
}
insPublicDNSName :: Lens' Instance (Maybe Text)
insPublicDNSName = lens _insPublicDNSName (\ s a -> s{_insPublicDNSName = a})
insPlatform :: Lens' Instance (Maybe PlatformValues)
insPlatform = lens _insPlatform (\ s a -> s{_insPlatform = a})
insSecurityGroups :: Lens' Instance [GroupIdentifier]
insSecurityGroups = lens _insSecurityGroups (\ s a -> s{_insSecurityGroups = a}) . _Default . _Coerce
insClientToken :: Lens' Instance (Maybe Text)
insClientToken = lens _insClientToken (\ s a -> s{_insClientToken = a})
insEnaSupport :: Lens' Instance (Maybe Bool)
insEnaSupport = lens _insEnaSupport (\ s a -> s{_insEnaSupport = a})
insSourceDestCheck :: Lens' Instance (Maybe Bool)
insSourceDestCheck = lens _insSourceDestCheck (\ s a -> s{_insSourceDestCheck = a})
insElasticGpuAssociations :: Lens' Instance [ElasticGpuAssociation]
insElasticGpuAssociations = lens _insElasticGpuAssociations (\ s a -> s{_insElasticGpuAssociations = a}) . _Default . _Coerce
insVPCId :: Lens' Instance (Maybe Text)
insVPCId = lens _insVPCId (\ s a -> s{_insVPCId = a})
insKeyName :: Lens' Instance (Maybe Text)
insKeyName = lens _insKeyName (\ s a -> s{_insKeyName = a})
insNetworkInterfaces :: Lens' Instance [InstanceNetworkInterface]
insNetworkInterfaces = lens _insNetworkInterfaces (\ s a -> s{_insNetworkInterfaces = a}) . _Default . _Coerce
insRAMDiskId :: Lens' Instance (Maybe Text)
insRAMDiskId = lens _insRAMDiskId (\ s a -> s{_insRAMDiskId = a})
insCPUOptions :: Lens' Instance (Maybe CPUOptions)
insCPUOptions = lens _insCPUOptions (\ s a -> s{_insCPUOptions = a})
insSubnetId :: Lens' Instance (Maybe Text)
insSubnetId = lens _insSubnetId (\ s a -> s{_insSubnetId = a})
insKernelId :: Lens' Instance (Maybe Text)
insKernelId = lens _insKernelId (\ s a -> s{_insKernelId = a})
insRootDeviceName :: Lens' Instance (Maybe Text)
insRootDeviceName = lens _insRootDeviceName (\ s a -> s{_insRootDeviceName = a})
insSRIOVNetSupport :: Lens' Instance (Maybe Text)
insSRIOVNetSupport = lens _insSRIOVNetSupport (\ s a -> s{_insSRIOVNetSupport = a})
insEBSOptimized :: Lens' Instance (Maybe Bool)
insEBSOptimized = lens _insEBSOptimized (\ s a -> s{_insEBSOptimized = a})
insStateTransitionReason :: Lens' Instance (Maybe Text)
insStateTransitionReason = lens _insStateTransitionReason (\ s a -> s{_insStateTransitionReason = a})
insInstanceLifecycle :: Lens' Instance (Maybe InstanceLifecycleType)
insInstanceLifecycle = lens _insInstanceLifecycle (\ s a -> s{_insInstanceLifecycle = a})
insIAMInstanceProfile :: Lens' Instance (Maybe IAMInstanceProfile)
insIAMInstanceProfile = lens _insIAMInstanceProfile (\ s a -> s{_insIAMInstanceProfile = a})
insPrivateIPAddress :: Lens' Instance (Maybe Text)
insPrivateIPAddress = lens _insPrivateIPAddress (\ s a -> s{_insPrivateIPAddress = a})
insProductCodes :: Lens' Instance [ProductCode]
insProductCodes = lens _insProductCodes (\ s a -> s{_insProductCodes = a}) . _Default . _Coerce
insSpotInstanceRequestId :: Lens' Instance (Maybe Text)
insSpotInstanceRequestId = lens _insSpotInstanceRequestId (\ s a -> s{_insSpotInstanceRequestId = a})
insPrivateDNSName :: Lens' Instance (Maybe Text)
insPrivateDNSName = lens _insPrivateDNSName (\ s a -> s{_insPrivateDNSName = a})
insStateReason :: Lens' Instance (Maybe StateReason)
insStateReason = lens _insStateReason (\ s a -> s{_insStateReason = a})
insBlockDeviceMappings :: Lens' Instance [InstanceBlockDeviceMapping]
insBlockDeviceMappings = lens _insBlockDeviceMappings (\ s a -> s{_insBlockDeviceMappings = a}) . _Default . _Coerce
insPublicIPAddress :: Lens' Instance (Maybe Text)
insPublicIPAddress = lens _insPublicIPAddress (\ s a -> s{_insPublicIPAddress = a})
insTags :: Lens' Instance [Tag]
insTags = lens _insTags (\ s a -> s{_insTags = a}) . _Default . _Coerce
insInstanceId :: Lens' Instance Text
insInstanceId = lens _insInstanceId (\ s a -> s{_insInstanceId = a})
insImageId :: Lens' Instance Text
insImageId = lens _insImageId (\ s a -> s{_insImageId = a})
insAMILaunchIndex :: Lens' Instance Int
insAMILaunchIndex = lens _insAMILaunchIndex (\ s a -> s{_insAMILaunchIndex = a})
insInstanceType :: Lens' Instance InstanceType
insInstanceType = lens _insInstanceType (\ s a -> s{_insInstanceType = a})
insLaunchTime :: Lens' Instance UTCTime
insLaunchTime = lens _insLaunchTime (\ s a -> s{_insLaunchTime = a}) . _Time
insPlacement :: Lens' Instance Placement
insPlacement = lens _insPlacement (\ s a -> s{_insPlacement = a})
insMonitoring :: Lens' Instance Monitoring
insMonitoring = lens _insMonitoring (\ s a -> s{_insMonitoring = a})
insArchitecture :: Lens' Instance ArchitectureValues
insArchitecture = lens _insArchitecture (\ s a -> s{_insArchitecture = a})
insRootDeviceType :: Lens' Instance DeviceType
insRootDeviceType = lens _insRootDeviceType (\ s a -> s{_insRootDeviceType = a})
insVirtualizationType :: Lens' Instance VirtualizationType
insVirtualizationType = lens _insVirtualizationType (\ s a -> s{_insVirtualizationType = a})
insHypervisor :: Lens' Instance HypervisorType
insHypervisor = lens _insHypervisor (\ s a -> s{_insHypervisor = a})
insState :: Lens' Instance InstanceState
insState = lens _insState (\ s a -> s{_insState = a})
instance FromXML Instance where
parseXML x
= Instance' <$>
(x .@? "dnsName") <*> (x .@? "platform") <*>
(x .@? "groupSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "clientToken")
<*> (x .@? "enaSupport")
<*> (x .@? "sourceDestCheck")
<*>
(x .@? "elasticGpuAssociationSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "vpcId")
<*> (x .@? "keyName")
<*>
(x .@? "networkInterfaceSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "ramdiskId")
<*> (x .@? "cpuOptions")
<*> (x .@? "subnetId")
<*> (x .@? "kernelId")
<*> (x .@? "rootDeviceName")
<*> (x .@? "sriovNetSupport")
<*> (x .@? "ebsOptimized")
<*> (x .@? "reason")
<*> (x .@? "instanceLifecycle")
<*> (x .@? "iamInstanceProfile")
<*> (x .@? "privateIpAddress")
<*>
(x .@? "productCodes" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "spotInstanceRequestId")
<*> (x .@? "privateDnsName")
<*> (x .@? "stateReason")
<*>
(x .@? "blockDeviceMapping" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "ipAddress")
<*>
(x .@? "tagSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@ "instanceId")
<*> (x .@ "imageId")
<*> (x .@ "amiLaunchIndex")
<*> (x .@ "instanceType")
<*> (x .@ "launchTime")
<*> (x .@ "placement")
<*> (x .@ "monitoring")
<*> (x .@ "architecture")
<*> (x .@ "rootDeviceType")
<*> (x .@ "virtualizationType")
<*> (x .@ "hypervisor")
<*> (x .@ "instanceState")
instance Hashable Instance where
instance NFData Instance where
data InstanceBlockDeviceMapping = InstanceBlockDeviceMapping'
{ _ibdmEBS :: !(Maybe EBSInstanceBlockDevice)
, _ibdmDeviceName :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
instanceBlockDeviceMapping
:: InstanceBlockDeviceMapping
instanceBlockDeviceMapping =
InstanceBlockDeviceMapping' {_ibdmEBS = Nothing, _ibdmDeviceName = Nothing}
ibdmEBS :: Lens' InstanceBlockDeviceMapping (Maybe EBSInstanceBlockDevice)
ibdmEBS = lens _ibdmEBS (\ s a -> s{_ibdmEBS = a})
ibdmDeviceName :: Lens' InstanceBlockDeviceMapping (Maybe Text)
ibdmDeviceName = lens _ibdmDeviceName (\ s a -> s{_ibdmDeviceName = a})
instance FromXML InstanceBlockDeviceMapping where
parseXML x
= InstanceBlockDeviceMapping' <$>
(x .@? "ebs") <*> (x .@? "deviceName")
instance Hashable InstanceBlockDeviceMapping where
instance NFData InstanceBlockDeviceMapping where
data InstanceBlockDeviceMappingSpecification = InstanceBlockDeviceMappingSpecification'
{ _ibdmsVirtualName :: !(Maybe Text)
, _ibdmsNoDevice :: !(Maybe Text)
, _ibdmsEBS :: !(Maybe EBSInstanceBlockDeviceSpecification)
, _ibdmsDeviceName :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
instanceBlockDeviceMappingSpecification
:: InstanceBlockDeviceMappingSpecification
instanceBlockDeviceMappingSpecification =
InstanceBlockDeviceMappingSpecification'
{ _ibdmsVirtualName = Nothing
, _ibdmsNoDevice = Nothing
, _ibdmsEBS = Nothing
, _ibdmsDeviceName = Nothing
}
ibdmsVirtualName :: Lens' InstanceBlockDeviceMappingSpecification (Maybe Text)
ibdmsVirtualName = lens _ibdmsVirtualName (\ s a -> s{_ibdmsVirtualName = a})
ibdmsNoDevice :: Lens' InstanceBlockDeviceMappingSpecification (Maybe Text)
ibdmsNoDevice = lens _ibdmsNoDevice (\ s a -> s{_ibdmsNoDevice = a})
ibdmsEBS :: Lens' InstanceBlockDeviceMappingSpecification (Maybe EBSInstanceBlockDeviceSpecification)
ibdmsEBS = lens _ibdmsEBS (\ s a -> s{_ibdmsEBS = a})
ibdmsDeviceName :: Lens' InstanceBlockDeviceMappingSpecification (Maybe Text)
ibdmsDeviceName = lens _ibdmsDeviceName (\ s a -> s{_ibdmsDeviceName = a})
instance Hashable
InstanceBlockDeviceMappingSpecification
where
instance NFData
InstanceBlockDeviceMappingSpecification
where
instance ToQuery
InstanceBlockDeviceMappingSpecification
where
toQuery InstanceBlockDeviceMappingSpecification'{..}
= mconcat
["VirtualName" =: _ibdmsVirtualName,
"NoDevice" =: _ibdmsNoDevice, "Ebs" =: _ibdmsEBS,
"DeviceName" =: _ibdmsDeviceName]
data InstanceCapacity = InstanceCapacity'
{ _icAvailableCapacity :: !(Maybe Int)
, _icInstanceType :: !(Maybe Text)
, _icTotalCapacity :: !(Maybe Int)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
instanceCapacity
:: InstanceCapacity
instanceCapacity =
InstanceCapacity'
{ _icAvailableCapacity = Nothing
, _icInstanceType = Nothing
, _icTotalCapacity = Nothing
}
icAvailableCapacity :: Lens' InstanceCapacity (Maybe Int)
icAvailableCapacity = lens _icAvailableCapacity (\ s a -> s{_icAvailableCapacity = a})
icInstanceType :: Lens' InstanceCapacity (Maybe Text)
icInstanceType = lens _icInstanceType (\ s a -> s{_icInstanceType = a})
icTotalCapacity :: Lens' InstanceCapacity (Maybe Int)
icTotalCapacity = lens _icTotalCapacity (\ s a -> s{_icTotalCapacity = a})
instance FromXML InstanceCapacity where
parseXML x
= InstanceCapacity' <$>
(x .@? "availableCapacity") <*>
(x .@? "instanceType")
<*> (x .@? "totalCapacity")
instance Hashable InstanceCapacity where
instance NFData InstanceCapacity where
data InstanceCount = InstanceCount'
{ _icState :: !(Maybe ListingState)
, _icInstanceCount :: !(Maybe Int)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
instanceCount
:: InstanceCount
instanceCount = InstanceCount' {_icState = Nothing, _icInstanceCount = Nothing}
icState :: Lens' InstanceCount (Maybe ListingState)
icState = lens _icState (\ s a -> s{_icState = a})
icInstanceCount :: Lens' InstanceCount (Maybe Int)
icInstanceCount = lens _icInstanceCount (\ s a -> s{_icInstanceCount = a})
instance FromXML InstanceCount where
parseXML x
= InstanceCount' <$>
(x .@? "state") <*> (x .@? "instanceCount")
instance Hashable InstanceCount where
instance NFData InstanceCount where
data InstanceCreditSpecification = InstanceCreditSpecification'
{ _icsInstanceId :: !(Maybe Text)
, _icsCPUCredits :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
instanceCreditSpecification
:: InstanceCreditSpecification
instanceCreditSpecification =
InstanceCreditSpecification'
{_icsInstanceId = Nothing, _icsCPUCredits = Nothing}
icsInstanceId :: Lens' InstanceCreditSpecification (Maybe Text)
icsInstanceId = lens _icsInstanceId (\ s a -> s{_icsInstanceId = a})
icsCPUCredits :: Lens' InstanceCreditSpecification (Maybe Text)
icsCPUCredits = lens _icsCPUCredits (\ s a -> s{_icsCPUCredits = a})
instance FromXML InstanceCreditSpecification where
parseXML x
= InstanceCreditSpecification' <$>
(x .@? "instanceId") <*> (x .@? "cpuCredits")
instance Hashable InstanceCreditSpecification where
instance NFData InstanceCreditSpecification where
data InstanceCreditSpecificationRequest = InstanceCreditSpecificationRequest'
{ _icsrInstanceId :: !(Maybe Text)
, _icsrCPUCredits :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
instanceCreditSpecificationRequest
:: InstanceCreditSpecificationRequest
instanceCreditSpecificationRequest =
InstanceCreditSpecificationRequest'
{_icsrInstanceId = Nothing, _icsrCPUCredits = Nothing}
icsrInstanceId :: Lens' InstanceCreditSpecificationRequest (Maybe Text)
icsrInstanceId = lens _icsrInstanceId (\ s a -> s{_icsrInstanceId = a})
icsrCPUCredits :: Lens' InstanceCreditSpecificationRequest (Maybe Text)
icsrCPUCredits = lens _icsrCPUCredits (\ s a -> s{_icsrCPUCredits = a})
instance Hashable InstanceCreditSpecificationRequest
where
instance NFData InstanceCreditSpecificationRequest
where
instance ToQuery InstanceCreditSpecificationRequest
where
toQuery InstanceCreditSpecificationRequest'{..}
= mconcat
["InstanceId" =: _icsrInstanceId,
"CpuCredits" =: _icsrCPUCredits]
data InstanceExportDetails = InstanceExportDetails'
{ _iedTargetEnvironment :: !(Maybe ExportEnvironment)
, _iedInstanceId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
instanceExportDetails
:: InstanceExportDetails
instanceExportDetails =
InstanceExportDetails'
{_iedTargetEnvironment = Nothing, _iedInstanceId = Nothing}
iedTargetEnvironment :: Lens' InstanceExportDetails (Maybe ExportEnvironment)
iedTargetEnvironment = lens _iedTargetEnvironment (\ s a -> s{_iedTargetEnvironment = a})
iedInstanceId :: Lens' InstanceExportDetails (Maybe Text)
iedInstanceId = lens _iedInstanceId (\ s a -> s{_iedInstanceId = a})
instance FromXML InstanceExportDetails where
parseXML x
= InstanceExportDetails' <$>
(x .@? "targetEnvironment") <*> (x .@? "instanceId")
instance Hashable InstanceExportDetails where
instance NFData InstanceExportDetails where
newtype InstanceIPv6Address = InstanceIPv6Address'
{ _iiaIPv6Address :: Maybe Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
instanceIPv6Address
:: InstanceIPv6Address
instanceIPv6Address = InstanceIPv6Address' {_iiaIPv6Address = Nothing}
iiaIPv6Address :: Lens' InstanceIPv6Address (Maybe Text)
iiaIPv6Address = lens _iiaIPv6Address (\ s a -> s{_iiaIPv6Address = a})
instance FromXML InstanceIPv6Address where
parseXML x
= InstanceIPv6Address' <$> (x .@? "ipv6Address")
instance Hashable InstanceIPv6Address where
instance NFData InstanceIPv6Address where
instance ToQuery InstanceIPv6Address where
toQuery InstanceIPv6Address'{..}
= mconcat ["Ipv6Address" =: _iiaIPv6Address]
newtype InstanceIPv6AddressRequest = InstanceIPv6AddressRequest'
{ _iiarIPv6Address :: Maybe Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
instanceIPv6AddressRequest
:: InstanceIPv6AddressRequest
instanceIPv6AddressRequest =
InstanceIPv6AddressRequest' {_iiarIPv6Address = Nothing}
iiarIPv6Address :: Lens' InstanceIPv6AddressRequest (Maybe Text)
iiarIPv6Address = lens _iiarIPv6Address (\ s a -> s{_iiarIPv6Address = a})
instance Hashable InstanceIPv6AddressRequest where
instance NFData InstanceIPv6AddressRequest where
instance ToQuery InstanceIPv6AddressRequest where
toQuery InstanceIPv6AddressRequest'{..}
= mconcat ["Ipv6Address" =: _iiarIPv6Address]
data InstanceMarketOptionsRequest = InstanceMarketOptionsRequest'
{ _imorMarketType :: !(Maybe MarketType)
, _imorSpotOptions :: !(Maybe SpotMarketOptions)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
instanceMarketOptionsRequest
:: InstanceMarketOptionsRequest
instanceMarketOptionsRequest =
InstanceMarketOptionsRequest'
{_imorMarketType = Nothing, _imorSpotOptions = Nothing}
imorMarketType :: Lens' InstanceMarketOptionsRequest (Maybe MarketType)
imorMarketType = lens _imorMarketType (\ s a -> s{_imorMarketType = a})
imorSpotOptions :: Lens' InstanceMarketOptionsRequest (Maybe SpotMarketOptions)
imorSpotOptions = lens _imorSpotOptions (\ s a -> s{_imorSpotOptions = a})
instance Hashable InstanceMarketOptionsRequest where
instance NFData InstanceMarketOptionsRequest where
instance ToQuery InstanceMarketOptionsRequest where
toQuery InstanceMarketOptionsRequest'{..}
= mconcat
["MarketType" =: _imorMarketType,
"SpotOptions" =: _imorSpotOptions]
data InstanceMonitoring = InstanceMonitoring'
{ _imInstanceId :: !(Maybe Text)
, _imMonitoring :: !(Maybe Monitoring)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
instanceMonitoring
:: InstanceMonitoring
instanceMonitoring =
InstanceMonitoring' {_imInstanceId = Nothing, _imMonitoring = Nothing}
imInstanceId :: Lens' InstanceMonitoring (Maybe Text)
imInstanceId = lens _imInstanceId (\ s a -> s{_imInstanceId = a})
imMonitoring :: Lens' InstanceMonitoring (Maybe Monitoring)
imMonitoring = lens _imMonitoring (\ s a -> s{_imMonitoring = a})
instance FromXML InstanceMonitoring where
parseXML x
= InstanceMonitoring' <$>
(x .@? "instanceId") <*> (x .@? "monitoring")
instance Hashable InstanceMonitoring where
instance NFData InstanceMonitoring where
data InstanceNetworkInterface = InstanceNetworkInterface'
{ _iniGroups :: !(Maybe [GroupIdentifier])
, _iniStatus :: !(Maybe NetworkInterfaceStatus)
, _iniPrivateIPAddresses :: !(Maybe [InstancePrivateIPAddress])
, _iniSourceDestCheck :: !(Maybe Bool)
, _iniVPCId :: !(Maybe Text)
, _iniNetworkInterfaceId :: !(Maybe Text)
, _iniSubnetId :: !(Maybe Text)
, _iniMACAddress :: !(Maybe Text)
, _iniAttachment :: !(Maybe InstanceNetworkInterfaceAttachment)
, _iniOwnerId :: !(Maybe Text)
, _iniPrivateIPAddress :: !(Maybe Text)
, _iniPrivateDNSName :: !(Maybe Text)
, _iniDescription :: !(Maybe Text)
, _iniAssociation :: !(Maybe InstanceNetworkInterfaceAssociation)
, _iniIPv6Addresses :: !(Maybe [InstanceIPv6Address])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
instanceNetworkInterface
:: InstanceNetworkInterface
instanceNetworkInterface =
InstanceNetworkInterface'
{ _iniGroups = Nothing
, _iniStatus = Nothing
, _iniPrivateIPAddresses = Nothing
, _iniSourceDestCheck = Nothing
, _iniVPCId = Nothing
, _iniNetworkInterfaceId = Nothing
, _iniSubnetId = Nothing
, _iniMACAddress = Nothing
, _iniAttachment = Nothing
, _iniOwnerId = Nothing
, _iniPrivateIPAddress = Nothing
, _iniPrivateDNSName = Nothing
, _iniDescription = Nothing
, _iniAssociation = Nothing
, _iniIPv6Addresses = Nothing
}
iniGroups :: Lens' InstanceNetworkInterface [GroupIdentifier]
iniGroups = lens _iniGroups (\ s a -> s{_iniGroups = a}) . _Default . _Coerce
iniStatus :: Lens' InstanceNetworkInterface (Maybe NetworkInterfaceStatus)
iniStatus = lens _iniStatus (\ s a -> s{_iniStatus = a})
iniPrivateIPAddresses :: Lens' InstanceNetworkInterface [InstancePrivateIPAddress]
iniPrivateIPAddresses = lens _iniPrivateIPAddresses (\ s a -> s{_iniPrivateIPAddresses = a}) . _Default . _Coerce
iniSourceDestCheck :: Lens' InstanceNetworkInterface (Maybe Bool)
iniSourceDestCheck = lens _iniSourceDestCheck (\ s a -> s{_iniSourceDestCheck = a})
iniVPCId :: Lens' InstanceNetworkInterface (Maybe Text)
iniVPCId = lens _iniVPCId (\ s a -> s{_iniVPCId = a})
iniNetworkInterfaceId :: Lens' InstanceNetworkInterface (Maybe Text)
iniNetworkInterfaceId = lens _iniNetworkInterfaceId (\ s a -> s{_iniNetworkInterfaceId = a})
iniSubnetId :: Lens' InstanceNetworkInterface (Maybe Text)
iniSubnetId = lens _iniSubnetId (\ s a -> s{_iniSubnetId = a})
iniMACAddress :: Lens' InstanceNetworkInterface (Maybe Text)
iniMACAddress = lens _iniMACAddress (\ s a -> s{_iniMACAddress = a})
iniAttachment :: Lens' InstanceNetworkInterface (Maybe InstanceNetworkInterfaceAttachment)
iniAttachment = lens _iniAttachment (\ s a -> s{_iniAttachment = a})
iniOwnerId :: Lens' InstanceNetworkInterface (Maybe Text)
iniOwnerId = lens _iniOwnerId (\ s a -> s{_iniOwnerId = a})
iniPrivateIPAddress :: Lens' InstanceNetworkInterface (Maybe Text)
iniPrivateIPAddress = lens _iniPrivateIPAddress (\ s a -> s{_iniPrivateIPAddress = a})
iniPrivateDNSName :: Lens' InstanceNetworkInterface (Maybe Text)
iniPrivateDNSName = lens _iniPrivateDNSName (\ s a -> s{_iniPrivateDNSName = a})
iniDescription :: Lens' InstanceNetworkInterface (Maybe Text)
iniDescription = lens _iniDescription (\ s a -> s{_iniDescription = a})
iniAssociation :: Lens' InstanceNetworkInterface (Maybe InstanceNetworkInterfaceAssociation)
iniAssociation = lens _iniAssociation (\ s a -> s{_iniAssociation = a})
iniIPv6Addresses :: Lens' InstanceNetworkInterface [InstanceIPv6Address]
iniIPv6Addresses = lens _iniIPv6Addresses (\ s a -> s{_iniIPv6Addresses = a}) . _Default . _Coerce
instance FromXML InstanceNetworkInterface where
parseXML x
= InstanceNetworkInterface' <$>
(x .@? "groupSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "status")
<*>
(x .@? "privateIpAddressesSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "sourceDestCheck")
<*> (x .@? "vpcId")
<*> (x .@? "networkInterfaceId")
<*> (x .@? "subnetId")
<*> (x .@? "macAddress")
<*> (x .@? "attachment")
<*> (x .@? "ownerId")
<*> (x .@? "privateIpAddress")
<*> (x .@? "privateDnsName")
<*> (x .@? "description")
<*> (x .@? "association")
<*>
(x .@? "ipv6AddressesSet" .!@ mempty >>=
may (parseXMLList "item"))
instance Hashable InstanceNetworkInterface where
instance NFData InstanceNetworkInterface where
data InstanceNetworkInterfaceAssociation = InstanceNetworkInterfaceAssociation'
{ _iniaPublicDNSName :: !(Maybe Text)
, _iniaIPOwnerId :: !(Maybe Text)
, _iniaPublicIP :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
instanceNetworkInterfaceAssociation
:: InstanceNetworkInterfaceAssociation
instanceNetworkInterfaceAssociation =
InstanceNetworkInterfaceAssociation'
{ _iniaPublicDNSName = Nothing
, _iniaIPOwnerId = Nothing
, _iniaPublicIP = Nothing
}
iniaPublicDNSName :: Lens' InstanceNetworkInterfaceAssociation (Maybe Text)
iniaPublicDNSName = lens _iniaPublicDNSName (\ s a -> s{_iniaPublicDNSName = a})
iniaIPOwnerId :: Lens' InstanceNetworkInterfaceAssociation (Maybe Text)
iniaIPOwnerId = lens _iniaIPOwnerId (\ s a -> s{_iniaIPOwnerId = a})
iniaPublicIP :: Lens' InstanceNetworkInterfaceAssociation (Maybe Text)
iniaPublicIP = lens _iniaPublicIP (\ s a -> s{_iniaPublicIP = a})
instance FromXML InstanceNetworkInterfaceAssociation
where
parseXML x
= InstanceNetworkInterfaceAssociation' <$>
(x .@? "publicDnsName") <*> (x .@? "ipOwnerId") <*>
(x .@? "publicIp")
instance Hashable InstanceNetworkInterfaceAssociation
where
instance NFData InstanceNetworkInterfaceAssociation
where
data InstanceNetworkInterfaceAttachment = InstanceNetworkInterfaceAttachment'
{ _iniaStatus :: !(Maybe AttachmentStatus)
, _iniaDeleteOnTermination :: !(Maybe Bool)
, _iniaAttachmentId :: !(Maybe Text)
, _iniaAttachTime :: !(Maybe ISO8601)
, _iniaDeviceIndex :: !(Maybe Int)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
instanceNetworkInterfaceAttachment
:: InstanceNetworkInterfaceAttachment
instanceNetworkInterfaceAttachment =
InstanceNetworkInterfaceAttachment'
{ _iniaStatus = Nothing
, _iniaDeleteOnTermination = Nothing
, _iniaAttachmentId = Nothing
, _iniaAttachTime = Nothing
, _iniaDeviceIndex = Nothing
}
iniaStatus :: Lens' InstanceNetworkInterfaceAttachment (Maybe AttachmentStatus)
iniaStatus = lens _iniaStatus (\ s a -> s{_iniaStatus = a})
iniaDeleteOnTermination :: Lens' InstanceNetworkInterfaceAttachment (Maybe Bool)
iniaDeleteOnTermination = lens _iniaDeleteOnTermination (\ s a -> s{_iniaDeleteOnTermination = a})
iniaAttachmentId :: Lens' InstanceNetworkInterfaceAttachment (Maybe Text)
iniaAttachmentId = lens _iniaAttachmentId (\ s a -> s{_iniaAttachmentId = a})
iniaAttachTime :: Lens' InstanceNetworkInterfaceAttachment (Maybe UTCTime)
iniaAttachTime = lens _iniaAttachTime (\ s a -> s{_iniaAttachTime = a}) . mapping _Time
iniaDeviceIndex :: Lens' InstanceNetworkInterfaceAttachment (Maybe Int)
iniaDeviceIndex = lens _iniaDeviceIndex (\ s a -> s{_iniaDeviceIndex = a})
instance FromXML InstanceNetworkInterfaceAttachment
where
parseXML x
= InstanceNetworkInterfaceAttachment' <$>
(x .@? "status") <*> (x .@? "deleteOnTermination")
<*> (x .@? "attachmentId")
<*> (x .@? "attachTime")
<*> (x .@? "deviceIndex")
instance Hashable InstanceNetworkInterfaceAttachment
where
instance NFData InstanceNetworkInterfaceAttachment
where
data InstanceNetworkInterfaceSpecification = InstanceNetworkInterfaceSpecification'
{ _inisGroups :: !(Maybe [Text])
, _inisPrivateIPAddresses :: !(Maybe [PrivateIPAddressSpecification])
, _inisDeleteOnTermination :: !(Maybe Bool)
, _inisAssociatePublicIPAddress :: !(Maybe Bool)
, _inisNetworkInterfaceId :: !(Maybe Text)
, _inisSubnetId :: !(Maybe Text)
, _inisIPv6AddressCount :: !(Maybe Int)
, _inisPrivateIPAddress :: !(Maybe Text)
, _inisSecondaryPrivateIPAddressCount :: !(Maybe Int)
, _inisDescription :: !(Maybe Text)
, _inisDeviceIndex :: !(Maybe Int)
, _inisIPv6Addresses :: !(Maybe [InstanceIPv6Address])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
instanceNetworkInterfaceSpecification
:: InstanceNetworkInterfaceSpecification
instanceNetworkInterfaceSpecification =
InstanceNetworkInterfaceSpecification'
{ _inisGroups = Nothing
, _inisPrivateIPAddresses = Nothing
, _inisDeleteOnTermination = Nothing
, _inisAssociatePublicIPAddress = Nothing
, _inisNetworkInterfaceId = Nothing
, _inisSubnetId = Nothing
, _inisIPv6AddressCount = Nothing
, _inisPrivateIPAddress = Nothing
, _inisSecondaryPrivateIPAddressCount = Nothing
, _inisDescription = Nothing
, _inisDeviceIndex = Nothing
, _inisIPv6Addresses = Nothing
}
inisGroups :: Lens' InstanceNetworkInterfaceSpecification [Text]
inisGroups = lens _inisGroups (\ s a -> s{_inisGroups = a}) . _Default . _Coerce
inisPrivateIPAddresses :: Lens' InstanceNetworkInterfaceSpecification [PrivateIPAddressSpecification]
inisPrivateIPAddresses = lens _inisPrivateIPAddresses (\ s a -> s{_inisPrivateIPAddresses = a}) . _Default . _Coerce
inisDeleteOnTermination :: Lens' InstanceNetworkInterfaceSpecification (Maybe Bool)
inisDeleteOnTermination = lens _inisDeleteOnTermination (\ s a -> s{_inisDeleteOnTermination = a})
inisAssociatePublicIPAddress :: Lens' InstanceNetworkInterfaceSpecification (Maybe Bool)
inisAssociatePublicIPAddress = lens _inisAssociatePublicIPAddress (\ s a -> s{_inisAssociatePublicIPAddress = a})
inisNetworkInterfaceId :: Lens' InstanceNetworkInterfaceSpecification (Maybe Text)
inisNetworkInterfaceId = lens _inisNetworkInterfaceId (\ s a -> s{_inisNetworkInterfaceId = a})
inisSubnetId :: Lens' InstanceNetworkInterfaceSpecification (Maybe Text)
inisSubnetId = lens _inisSubnetId (\ s a -> s{_inisSubnetId = a})
inisIPv6AddressCount :: Lens' InstanceNetworkInterfaceSpecification (Maybe Int)
inisIPv6AddressCount = lens _inisIPv6AddressCount (\ s a -> s{_inisIPv6AddressCount = a})
inisPrivateIPAddress :: Lens' InstanceNetworkInterfaceSpecification (Maybe Text)
inisPrivateIPAddress = lens _inisPrivateIPAddress (\ s a -> s{_inisPrivateIPAddress = a})
inisSecondaryPrivateIPAddressCount :: Lens' InstanceNetworkInterfaceSpecification (Maybe Int)
inisSecondaryPrivateIPAddressCount = lens _inisSecondaryPrivateIPAddressCount (\ s a -> s{_inisSecondaryPrivateIPAddressCount = a})
inisDescription :: Lens' InstanceNetworkInterfaceSpecification (Maybe Text)
inisDescription = lens _inisDescription (\ s a -> s{_inisDescription = a})
inisDeviceIndex :: Lens' InstanceNetworkInterfaceSpecification (Maybe Int)
inisDeviceIndex = lens _inisDeviceIndex (\ s a -> s{_inisDeviceIndex = a})
inisIPv6Addresses :: Lens' InstanceNetworkInterfaceSpecification [InstanceIPv6Address]
inisIPv6Addresses = lens _inisIPv6Addresses (\ s a -> s{_inisIPv6Addresses = a}) . _Default . _Coerce
instance FromXML
InstanceNetworkInterfaceSpecification
where
parseXML x
= InstanceNetworkInterfaceSpecification' <$>
(x .@? "SecurityGroupId" .!@ mempty >>=
may (parseXMLList "SecurityGroupId"))
<*>
(x .@? "privateIpAddressesSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "deleteOnTermination")
<*> (x .@? "associatePublicIpAddress")
<*> (x .@? "networkInterfaceId")
<*> (x .@? "subnetId")
<*> (x .@? "ipv6AddressCount")
<*> (x .@? "privateIpAddress")
<*> (x .@? "secondaryPrivateIpAddressCount")
<*> (x .@? "description")
<*> (x .@? "deviceIndex")
<*>
(x .@? "ipv6AddressesSet" .!@ mempty >>=
may (parseXMLList "item"))
instance Hashable
InstanceNetworkInterfaceSpecification
where
instance NFData InstanceNetworkInterfaceSpecification
where
instance ToQuery
InstanceNetworkInterfaceSpecification
where
toQuery InstanceNetworkInterfaceSpecification'{..}
= mconcat
[toQuery
(toQueryList "SecurityGroupId" <$> _inisGroups),
toQuery
(toQueryList "PrivateIpAddresses" <$>
_inisPrivateIPAddresses),
"DeleteOnTermination" =: _inisDeleteOnTermination,
"AssociatePublicIpAddress" =:
_inisAssociatePublicIPAddress,
"NetworkInterfaceId" =: _inisNetworkInterfaceId,
"SubnetId" =: _inisSubnetId,
"Ipv6AddressCount" =: _inisIPv6AddressCount,
"PrivateIpAddress" =: _inisPrivateIPAddress,
"SecondaryPrivateIpAddressCount" =:
_inisSecondaryPrivateIPAddressCount,
"Description" =: _inisDescription,
"DeviceIndex" =: _inisDeviceIndex,
toQuery
(toQueryList "Ipv6Addresses" <$> _inisIPv6Addresses)]
data InstancePrivateIPAddress = InstancePrivateIPAddress'
{ _ipiaPrimary :: !(Maybe Bool)
, _ipiaPrivateIPAddress :: !(Maybe Text)
, _ipiaPrivateDNSName :: !(Maybe Text)
, _ipiaAssociation :: !(Maybe InstanceNetworkInterfaceAssociation)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
instancePrivateIPAddress
:: InstancePrivateIPAddress
instancePrivateIPAddress =
InstancePrivateIPAddress'
{ _ipiaPrimary = Nothing
, _ipiaPrivateIPAddress = Nothing
, _ipiaPrivateDNSName = Nothing
, _ipiaAssociation = Nothing
}
ipiaPrimary :: Lens' InstancePrivateIPAddress (Maybe Bool)
ipiaPrimary = lens _ipiaPrimary (\ s a -> s{_ipiaPrimary = a})
ipiaPrivateIPAddress :: Lens' InstancePrivateIPAddress (Maybe Text)
ipiaPrivateIPAddress = lens _ipiaPrivateIPAddress (\ s a -> s{_ipiaPrivateIPAddress = a})
ipiaPrivateDNSName :: Lens' InstancePrivateIPAddress (Maybe Text)
ipiaPrivateDNSName = lens _ipiaPrivateDNSName (\ s a -> s{_ipiaPrivateDNSName = a})
ipiaAssociation :: Lens' InstancePrivateIPAddress (Maybe InstanceNetworkInterfaceAssociation)
ipiaAssociation = lens _ipiaAssociation (\ s a -> s{_ipiaAssociation = a})
instance FromXML InstancePrivateIPAddress where
parseXML x
= InstancePrivateIPAddress' <$>
(x .@? "primary") <*> (x .@? "privateIpAddress") <*>
(x .@? "privateDnsName")
<*> (x .@? "association")
instance Hashable InstancePrivateIPAddress where
instance NFData InstancePrivateIPAddress where
data InstanceState = InstanceState'
{ _isName :: !InstanceStateName
, _isCode :: !Int
} deriving (Eq, Read, Show, Data, Typeable, Generic)
instanceState
:: InstanceStateName
-> Int
-> InstanceState
instanceState pName_ pCode_ =
InstanceState' {_isName = pName_, _isCode = pCode_}
isName :: Lens' InstanceState InstanceStateName
isName = lens _isName (\ s a -> s{_isName = a})
isCode :: Lens' InstanceState Int
isCode = lens _isCode (\ s a -> s{_isCode = a})
instance FromXML InstanceState where
parseXML x
= InstanceState' <$> (x .@ "name") <*> (x .@ "code")
instance Hashable InstanceState where
instance NFData InstanceState where
data InstanceStateChange = InstanceStateChange'
{ _iscInstanceId :: !(Maybe Text)
, _iscCurrentState :: !(Maybe InstanceState)
, _iscPreviousState :: !(Maybe InstanceState)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
instanceStateChange
:: InstanceStateChange
instanceStateChange =
InstanceStateChange'
{ _iscInstanceId = Nothing
, _iscCurrentState = Nothing
, _iscPreviousState = Nothing
}
iscInstanceId :: Lens' InstanceStateChange (Maybe Text)
iscInstanceId = lens _iscInstanceId (\ s a -> s{_iscInstanceId = a})
iscCurrentState :: Lens' InstanceStateChange (Maybe InstanceState)
iscCurrentState = lens _iscCurrentState (\ s a -> s{_iscCurrentState = a})
iscPreviousState :: Lens' InstanceStateChange (Maybe InstanceState)
iscPreviousState = lens _iscPreviousState (\ s a -> s{_iscPreviousState = a})
instance FromXML InstanceStateChange where
parseXML x
= InstanceStateChange' <$>
(x .@? "instanceId") <*> (x .@? "currentState") <*>
(x .@? "previousState")
instance Hashable InstanceStateChange where
instance NFData InstanceStateChange where
data InstanceStatus = InstanceStatus'
{ _isInstanceId :: !(Maybe Text)
, _isSystemStatus :: !(Maybe InstanceStatusSummary)
, _isEvents :: !(Maybe [InstanceStatusEvent])
, _isAvailabilityZone :: !(Maybe Text)
, _isInstanceStatus :: !(Maybe InstanceStatusSummary)
, _isInstanceState :: !(Maybe InstanceState)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
instanceStatus
:: InstanceStatus
instanceStatus =
InstanceStatus'
{ _isInstanceId = Nothing
, _isSystemStatus = Nothing
, _isEvents = Nothing
, _isAvailabilityZone = Nothing
, _isInstanceStatus = Nothing
, _isInstanceState = Nothing
}
isInstanceId :: Lens' InstanceStatus (Maybe Text)
isInstanceId = lens _isInstanceId (\ s a -> s{_isInstanceId = a})
isSystemStatus :: Lens' InstanceStatus (Maybe InstanceStatusSummary)
isSystemStatus = lens _isSystemStatus (\ s a -> s{_isSystemStatus = a})
isEvents :: Lens' InstanceStatus [InstanceStatusEvent]
isEvents = lens _isEvents (\ s a -> s{_isEvents = a}) . _Default . _Coerce
isAvailabilityZone :: Lens' InstanceStatus (Maybe Text)
isAvailabilityZone = lens _isAvailabilityZone (\ s a -> s{_isAvailabilityZone = a})
isInstanceStatus :: Lens' InstanceStatus (Maybe InstanceStatusSummary)
isInstanceStatus = lens _isInstanceStatus (\ s a -> s{_isInstanceStatus = a})
isInstanceState :: Lens' InstanceStatus (Maybe InstanceState)
isInstanceState = lens _isInstanceState (\ s a -> s{_isInstanceState = a})
instance FromXML InstanceStatus where
parseXML x
= InstanceStatus' <$>
(x .@? "instanceId") <*> (x .@? "systemStatus") <*>
(x .@? "eventsSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "availabilityZone")
<*> (x .@? "instanceStatus")
<*> (x .@? "instanceState")
instance Hashable InstanceStatus where
instance NFData InstanceStatus where
data InstanceStatusDetails = InstanceStatusDetails'
{ _isdStatus :: !(Maybe StatusType)
, _isdImpairedSince :: !(Maybe ISO8601)
, _isdName :: !(Maybe StatusName)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
instanceStatusDetails
:: InstanceStatusDetails
instanceStatusDetails =
InstanceStatusDetails'
{_isdStatus = Nothing, _isdImpairedSince = Nothing, _isdName = Nothing}
isdStatus :: Lens' InstanceStatusDetails (Maybe StatusType)
isdStatus = lens _isdStatus (\ s a -> s{_isdStatus = a})
isdImpairedSince :: Lens' InstanceStatusDetails (Maybe UTCTime)
isdImpairedSince = lens _isdImpairedSince (\ s a -> s{_isdImpairedSince = a}) . mapping _Time
isdName :: Lens' InstanceStatusDetails (Maybe StatusName)
isdName = lens _isdName (\ s a -> s{_isdName = a})
instance FromXML InstanceStatusDetails where
parseXML x
= InstanceStatusDetails' <$>
(x .@? "status") <*> (x .@? "impairedSince") <*>
(x .@? "name")
instance Hashable InstanceStatusDetails where
instance NFData InstanceStatusDetails where
data InstanceStatusEvent = InstanceStatusEvent'
{ _iseNotBefore :: !(Maybe ISO8601)
, _iseCode :: !(Maybe EventCode)
, _iseDescription :: !(Maybe Text)
, _iseNotAfter :: !(Maybe ISO8601)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
instanceStatusEvent
:: InstanceStatusEvent
instanceStatusEvent =
InstanceStatusEvent'
{ _iseNotBefore = Nothing
, _iseCode = Nothing
, _iseDescription = Nothing
, _iseNotAfter = Nothing
}
iseNotBefore :: Lens' InstanceStatusEvent (Maybe UTCTime)
iseNotBefore = lens _iseNotBefore (\ s a -> s{_iseNotBefore = a}) . mapping _Time
iseCode :: Lens' InstanceStatusEvent (Maybe EventCode)
iseCode = lens _iseCode (\ s a -> s{_iseCode = a})
iseDescription :: Lens' InstanceStatusEvent (Maybe Text)
iseDescription = lens _iseDescription (\ s a -> s{_iseDescription = a})
iseNotAfter :: Lens' InstanceStatusEvent (Maybe UTCTime)
iseNotAfter = lens _iseNotAfter (\ s a -> s{_iseNotAfter = a}) . mapping _Time
instance FromXML InstanceStatusEvent where
parseXML x
= InstanceStatusEvent' <$>
(x .@? "notBefore") <*> (x .@? "code") <*>
(x .@? "description")
<*> (x .@? "notAfter")
instance Hashable InstanceStatusEvent where
instance NFData InstanceStatusEvent where
data InstanceStatusSummary = InstanceStatusSummary'
{ _issDetails :: !(Maybe [InstanceStatusDetails])
, _issStatus :: !SummaryStatus
} deriving (Eq, Read, Show, Data, Typeable, Generic)
instanceStatusSummary
:: SummaryStatus
-> InstanceStatusSummary
instanceStatusSummary pStatus_ =
InstanceStatusSummary' {_issDetails = Nothing, _issStatus = pStatus_}
issDetails :: Lens' InstanceStatusSummary [InstanceStatusDetails]
issDetails = lens _issDetails (\ s a -> s{_issDetails = a}) . _Default . _Coerce
issStatus :: Lens' InstanceStatusSummary SummaryStatus
issStatus = lens _issStatus (\ s a -> s{_issStatus = a})
instance FromXML InstanceStatusSummary where
parseXML x
= InstanceStatusSummary' <$>
(x .@? "details" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@ "status")
instance Hashable InstanceStatusSummary where
instance NFData InstanceStatusSummary where
data InternetGateway = InternetGateway'
{ _igAttachments :: !(Maybe [InternetGatewayAttachment])
, _igTags :: !(Maybe [Tag])
, _igInternetGatewayId :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
internetGateway
:: Text
-> InternetGateway
internetGateway pInternetGatewayId_ =
InternetGateway'
{ _igAttachments = Nothing
, _igTags = Nothing
, _igInternetGatewayId = pInternetGatewayId_
}
igAttachments :: Lens' InternetGateway [InternetGatewayAttachment]
igAttachments = lens _igAttachments (\ s a -> s{_igAttachments = a}) . _Default . _Coerce
igTags :: Lens' InternetGateway [Tag]
igTags = lens _igTags (\ s a -> s{_igTags = a}) . _Default . _Coerce
igInternetGatewayId :: Lens' InternetGateway Text
igInternetGatewayId = lens _igInternetGatewayId (\ s a -> s{_igInternetGatewayId = a})
instance FromXML InternetGateway where
parseXML x
= InternetGateway' <$>
(x .@? "attachmentSet" .!@ mempty >>=
may (parseXMLList "item"))
<*>
(x .@? "tagSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@ "internetGatewayId")
instance Hashable InternetGateway where
instance NFData InternetGateway where
data InternetGatewayAttachment = InternetGatewayAttachment'
{ _igaState :: !AttachmentStatus
, _igaVPCId :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
internetGatewayAttachment
:: AttachmentStatus
-> Text
-> InternetGatewayAttachment
internetGatewayAttachment pState_ pVPCId_ =
InternetGatewayAttachment' {_igaState = pState_, _igaVPCId = pVPCId_}
igaState :: Lens' InternetGatewayAttachment AttachmentStatus
igaState = lens _igaState (\ s a -> s{_igaState = a})
igaVPCId :: Lens' InternetGatewayAttachment Text
igaVPCId = lens _igaVPCId (\ s a -> s{_igaVPCId = a})
instance FromXML InternetGatewayAttachment where
parseXML x
= InternetGatewayAttachment' <$>
(x .@ "state") <*> (x .@ "vpcId")
instance Hashable InternetGatewayAttachment where
instance NFData InternetGatewayAttachment where
data KeyPairInfo = KeyPairInfo'
{ _kpiKeyFingerprint :: !(Maybe Text)
, _kpiKeyName :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
keyPairInfo
:: KeyPairInfo
keyPairInfo = KeyPairInfo' {_kpiKeyFingerprint = Nothing, _kpiKeyName = Nothing}
kpiKeyFingerprint :: Lens' KeyPairInfo (Maybe Text)
kpiKeyFingerprint = lens _kpiKeyFingerprint (\ s a -> s{_kpiKeyFingerprint = a})
kpiKeyName :: Lens' KeyPairInfo (Maybe Text)
kpiKeyName = lens _kpiKeyName (\ s a -> s{_kpiKeyName = a})
instance FromXML KeyPairInfo where
parseXML x
= KeyPairInfo' <$>
(x .@? "keyFingerprint") <*> (x .@? "keyName")
instance Hashable KeyPairInfo where
instance NFData KeyPairInfo where
data LaunchPermission = LaunchPermission'
{ _lGroup :: !(Maybe PermissionGroup)
, _lUserId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
launchPermission
:: LaunchPermission
launchPermission = LaunchPermission' {_lGroup = Nothing, _lUserId = Nothing}
lGroup :: Lens' LaunchPermission (Maybe PermissionGroup)
lGroup = lens _lGroup (\ s a -> s{_lGroup = a})
lUserId :: Lens' LaunchPermission (Maybe Text)
lUserId = lens _lUserId (\ s a -> s{_lUserId = a})
instance FromXML LaunchPermission where
parseXML x
= LaunchPermission' <$>
(x .@? "group") <*> (x .@? "userId")
instance Hashable LaunchPermission where
instance NFData LaunchPermission where
instance ToQuery LaunchPermission where
toQuery LaunchPermission'{..}
= mconcat ["Group" =: _lGroup, "UserId" =: _lUserId]
data LaunchPermissionModifications = LaunchPermissionModifications'
{ _lRemove :: !(Maybe [LaunchPermission])
, _lAdd :: !(Maybe [LaunchPermission])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
launchPermissionModifications
:: LaunchPermissionModifications
launchPermissionModifications =
LaunchPermissionModifications' {_lRemove = Nothing, _lAdd = Nothing}
lRemove :: Lens' LaunchPermissionModifications [LaunchPermission]
lRemove = lens _lRemove (\ s a -> s{_lRemove = a}) . _Default . _Coerce
lAdd :: Lens' LaunchPermissionModifications [LaunchPermission]
lAdd = lens _lAdd (\ s a -> s{_lAdd = a}) . _Default . _Coerce
instance Hashable LaunchPermissionModifications where
instance NFData LaunchPermissionModifications where
instance ToQuery LaunchPermissionModifications where
toQuery LaunchPermissionModifications'{..}
= mconcat
[toQuery (toQueryList "Remove" <$> _lRemove),
toQuery (toQueryList "Add" <$> _lAdd)]
data LaunchSpecification = LaunchSpecification'
{ _lsSecurityGroups :: !(Maybe [GroupIdentifier])
, _lsKeyName :: !(Maybe Text)
, _lsNetworkInterfaces :: !(Maybe [InstanceNetworkInterfaceSpecification])
, _lsRAMDiskId :: !(Maybe Text)
, _lsSubnetId :: !(Maybe Text)
, _lsKernelId :: !(Maybe Text)
, _lsInstanceType :: !(Maybe InstanceType)
, _lsEBSOptimized :: !(Maybe Bool)
, _lsUserData :: !(Maybe Text)
, _lsMonitoring :: !(Maybe RunInstancesMonitoringEnabled)
, _lsIAMInstanceProfile :: !(Maybe IAMInstanceProfileSpecification)
, _lsImageId :: !(Maybe Text)
, _lsAddressingType :: !(Maybe Text)
, _lsBlockDeviceMappings :: !(Maybe [BlockDeviceMapping])
, _lsPlacement :: !(Maybe SpotPlacement)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
launchSpecification
:: LaunchSpecification
launchSpecification =
LaunchSpecification'
{ _lsSecurityGroups = Nothing
, _lsKeyName = Nothing
, _lsNetworkInterfaces = Nothing
, _lsRAMDiskId = Nothing
, _lsSubnetId = Nothing
, _lsKernelId = Nothing
, _lsInstanceType = Nothing
, _lsEBSOptimized = Nothing
, _lsUserData = Nothing
, _lsMonitoring = Nothing
, _lsIAMInstanceProfile = Nothing
, _lsImageId = Nothing
, _lsAddressingType = Nothing
, _lsBlockDeviceMappings = Nothing
, _lsPlacement = Nothing
}
lsSecurityGroups :: Lens' LaunchSpecification [GroupIdentifier]
lsSecurityGroups = lens _lsSecurityGroups (\ s a -> s{_lsSecurityGroups = a}) . _Default . _Coerce
lsKeyName :: Lens' LaunchSpecification (Maybe Text)
lsKeyName = lens _lsKeyName (\ s a -> s{_lsKeyName = a})
lsNetworkInterfaces :: Lens' LaunchSpecification [InstanceNetworkInterfaceSpecification]
lsNetworkInterfaces = lens _lsNetworkInterfaces (\ s a -> s{_lsNetworkInterfaces = a}) . _Default . _Coerce
lsRAMDiskId :: Lens' LaunchSpecification (Maybe Text)
lsRAMDiskId = lens _lsRAMDiskId (\ s a -> s{_lsRAMDiskId = a})
lsSubnetId :: Lens' LaunchSpecification (Maybe Text)
lsSubnetId = lens _lsSubnetId (\ s a -> s{_lsSubnetId = a})
lsKernelId :: Lens' LaunchSpecification (Maybe Text)
lsKernelId = lens _lsKernelId (\ s a -> s{_lsKernelId = a})
lsInstanceType :: Lens' LaunchSpecification (Maybe InstanceType)
lsInstanceType = lens _lsInstanceType (\ s a -> s{_lsInstanceType = a})
lsEBSOptimized :: Lens' LaunchSpecification (Maybe Bool)
lsEBSOptimized = lens _lsEBSOptimized (\ s a -> s{_lsEBSOptimized = a})
lsUserData :: Lens' LaunchSpecification (Maybe Text)
lsUserData = lens _lsUserData (\ s a -> s{_lsUserData = a})
lsMonitoring :: Lens' LaunchSpecification (Maybe RunInstancesMonitoringEnabled)
lsMonitoring = lens _lsMonitoring (\ s a -> s{_lsMonitoring = a})
lsIAMInstanceProfile :: Lens' LaunchSpecification (Maybe IAMInstanceProfileSpecification)
lsIAMInstanceProfile = lens _lsIAMInstanceProfile (\ s a -> s{_lsIAMInstanceProfile = a})
lsImageId :: Lens' LaunchSpecification (Maybe Text)
lsImageId = lens _lsImageId (\ s a -> s{_lsImageId = a})
lsAddressingType :: Lens' LaunchSpecification (Maybe Text)
lsAddressingType = lens _lsAddressingType (\ s a -> s{_lsAddressingType = a})
lsBlockDeviceMappings :: Lens' LaunchSpecification [BlockDeviceMapping]
lsBlockDeviceMappings = lens _lsBlockDeviceMappings (\ s a -> s{_lsBlockDeviceMappings = a}) . _Default . _Coerce
lsPlacement :: Lens' LaunchSpecification (Maybe SpotPlacement)
lsPlacement = lens _lsPlacement (\ s a -> s{_lsPlacement = a})
instance FromXML LaunchSpecification where
parseXML x
= LaunchSpecification' <$>
(x .@? "groupSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "keyName")
<*>
(x .@? "networkInterfaceSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "ramdiskId")
<*> (x .@? "subnetId")
<*> (x .@? "kernelId")
<*> (x .@? "instanceType")
<*> (x .@? "ebsOptimized")
<*> (x .@? "userData")
<*> (x .@? "monitoring")
<*> (x .@? "iamInstanceProfile")
<*> (x .@? "imageId")
<*> (x .@? "addressingType")
<*>
(x .@? "blockDeviceMapping" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "placement")
instance Hashable LaunchSpecification where
instance NFData LaunchSpecification where
data LaunchTemplate = LaunchTemplate'
{ _ltLaunchTemplateName :: !(Maybe Text)
, _ltLatestVersionNumber :: !(Maybe Integer)
, _ltLaunchTemplateId :: !(Maybe Text)
, _ltCreatedBy :: !(Maybe Text)
, _ltDefaultVersionNumber :: !(Maybe Integer)
, _ltCreateTime :: !(Maybe ISO8601)
, _ltTags :: !(Maybe [Tag])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
launchTemplate
:: LaunchTemplate
launchTemplate =
LaunchTemplate'
{ _ltLaunchTemplateName = Nothing
, _ltLatestVersionNumber = Nothing
, _ltLaunchTemplateId = Nothing
, _ltCreatedBy = Nothing
, _ltDefaultVersionNumber = Nothing
, _ltCreateTime = Nothing
, _ltTags = Nothing
}
ltLaunchTemplateName :: Lens' LaunchTemplate (Maybe Text)
ltLaunchTemplateName = lens _ltLaunchTemplateName (\ s a -> s{_ltLaunchTemplateName = a})
ltLatestVersionNumber :: Lens' LaunchTemplate (Maybe Integer)
ltLatestVersionNumber = lens _ltLatestVersionNumber (\ s a -> s{_ltLatestVersionNumber = a})
ltLaunchTemplateId :: Lens' LaunchTemplate (Maybe Text)
ltLaunchTemplateId = lens _ltLaunchTemplateId (\ s a -> s{_ltLaunchTemplateId = a})
ltCreatedBy :: Lens' LaunchTemplate (Maybe Text)
ltCreatedBy = lens _ltCreatedBy (\ s a -> s{_ltCreatedBy = a})
ltDefaultVersionNumber :: Lens' LaunchTemplate (Maybe Integer)
ltDefaultVersionNumber = lens _ltDefaultVersionNumber (\ s a -> s{_ltDefaultVersionNumber = a})
ltCreateTime :: Lens' LaunchTemplate (Maybe UTCTime)
ltCreateTime = lens _ltCreateTime (\ s a -> s{_ltCreateTime = a}) . mapping _Time
ltTags :: Lens' LaunchTemplate [Tag]
ltTags = lens _ltTags (\ s a -> s{_ltTags = a}) . _Default . _Coerce
instance FromXML LaunchTemplate where
parseXML x
= LaunchTemplate' <$>
(x .@? "launchTemplateName") <*>
(x .@? "latestVersionNumber")
<*> (x .@? "launchTemplateId")
<*> (x .@? "createdBy")
<*> (x .@? "defaultVersionNumber")
<*> (x .@? "createTime")
<*>
(x .@? "tagSet" .!@ mempty >>=
may (parseXMLList "item"))
instance Hashable LaunchTemplate where
instance NFData LaunchTemplate where
data LaunchTemplateBlockDeviceMapping = LaunchTemplateBlockDeviceMapping'
{ _ltbdmVirtualName :: !(Maybe Text)
, _ltbdmNoDevice :: !(Maybe Text)
, _ltbdmEBS :: !(Maybe LaunchTemplateEBSBlockDevice)
, _ltbdmDeviceName :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
launchTemplateBlockDeviceMapping
:: LaunchTemplateBlockDeviceMapping
launchTemplateBlockDeviceMapping =
LaunchTemplateBlockDeviceMapping'
{ _ltbdmVirtualName = Nothing
, _ltbdmNoDevice = Nothing
, _ltbdmEBS = Nothing
, _ltbdmDeviceName = Nothing
}
ltbdmVirtualName :: Lens' LaunchTemplateBlockDeviceMapping (Maybe Text)
ltbdmVirtualName = lens _ltbdmVirtualName (\ s a -> s{_ltbdmVirtualName = a})
ltbdmNoDevice :: Lens' LaunchTemplateBlockDeviceMapping (Maybe Text)
ltbdmNoDevice = lens _ltbdmNoDevice (\ s a -> s{_ltbdmNoDevice = a})
ltbdmEBS :: Lens' LaunchTemplateBlockDeviceMapping (Maybe LaunchTemplateEBSBlockDevice)
ltbdmEBS = lens _ltbdmEBS (\ s a -> s{_ltbdmEBS = a})
ltbdmDeviceName :: Lens' LaunchTemplateBlockDeviceMapping (Maybe Text)
ltbdmDeviceName = lens _ltbdmDeviceName (\ s a -> s{_ltbdmDeviceName = a})
instance FromXML LaunchTemplateBlockDeviceMapping
where
parseXML x
= LaunchTemplateBlockDeviceMapping' <$>
(x .@? "virtualName") <*> (x .@? "noDevice") <*>
(x .@? "ebs")
<*> (x .@? "deviceName")
instance Hashable LaunchTemplateBlockDeviceMapping
where
instance NFData LaunchTemplateBlockDeviceMapping
where
data LaunchTemplateBlockDeviceMappingRequest = LaunchTemplateBlockDeviceMappingRequest'
{ _ltbdmrVirtualName :: !(Maybe Text)
, _ltbdmrNoDevice :: !(Maybe Text)
, _ltbdmrEBS :: !(Maybe LaunchTemplateEBSBlockDeviceRequest)
, _ltbdmrDeviceName :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
launchTemplateBlockDeviceMappingRequest
:: LaunchTemplateBlockDeviceMappingRequest
launchTemplateBlockDeviceMappingRequest =
LaunchTemplateBlockDeviceMappingRequest'
{ _ltbdmrVirtualName = Nothing
, _ltbdmrNoDevice = Nothing
, _ltbdmrEBS = Nothing
, _ltbdmrDeviceName = Nothing
}
ltbdmrVirtualName :: Lens' LaunchTemplateBlockDeviceMappingRequest (Maybe Text)
ltbdmrVirtualName = lens _ltbdmrVirtualName (\ s a -> s{_ltbdmrVirtualName = a})
ltbdmrNoDevice :: Lens' LaunchTemplateBlockDeviceMappingRequest (Maybe Text)
ltbdmrNoDevice = lens _ltbdmrNoDevice (\ s a -> s{_ltbdmrNoDevice = a})
ltbdmrEBS :: Lens' LaunchTemplateBlockDeviceMappingRequest (Maybe LaunchTemplateEBSBlockDeviceRequest)
ltbdmrEBS = lens _ltbdmrEBS (\ s a -> s{_ltbdmrEBS = a})
ltbdmrDeviceName :: Lens' LaunchTemplateBlockDeviceMappingRequest (Maybe Text)
ltbdmrDeviceName = lens _ltbdmrDeviceName (\ s a -> s{_ltbdmrDeviceName = a})
instance Hashable
LaunchTemplateBlockDeviceMappingRequest
where
instance NFData
LaunchTemplateBlockDeviceMappingRequest
where
instance ToQuery
LaunchTemplateBlockDeviceMappingRequest
where
toQuery LaunchTemplateBlockDeviceMappingRequest'{..}
= mconcat
["VirtualName" =: _ltbdmrVirtualName,
"NoDevice" =: _ltbdmrNoDevice, "Ebs" =: _ltbdmrEBS,
"DeviceName" =: _ltbdmrDeviceName]
data LaunchTemplateConfig = LaunchTemplateConfig'
{ _ltcOverrides :: !(Maybe [LaunchTemplateOverrides])
, _ltcLaunchTemplateSpecification :: !(Maybe FleetLaunchTemplateSpecification)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
launchTemplateConfig
:: LaunchTemplateConfig
launchTemplateConfig =
LaunchTemplateConfig'
{_ltcOverrides = Nothing, _ltcLaunchTemplateSpecification = Nothing}
ltcOverrides :: Lens' LaunchTemplateConfig [LaunchTemplateOverrides]
ltcOverrides = lens _ltcOverrides (\ s a -> s{_ltcOverrides = a}) . _Default . _Coerce
ltcLaunchTemplateSpecification :: Lens' LaunchTemplateConfig (Maybe FleetLaunchTemplateSpecification)
ltcLaunchTemplateSpecification = lens _ltcLaunchTemplateSpecification (\ s a -> s{_ltcLaunchTemplateSpecification = a})
instance FromXML LaunchTemplateConfig where
parseXML x
= LaunchTemplateConfig' <$>
(x .@? "overrides" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "launchTemplateSpecification")
instance Hashable LaunchTemplateConfig where
instance NFData LaunchTemplateConfig where
instance ToQuery LaunchTemplateConfig where
toQuery LaunchTemplateConfig'{..}
= mconcat
[toQuery (toQueryList "Overrides" <$> _ltcOverrides),
"LaunchTemplateSpecification" =:
_ltcLaunchTemplateSpecification]
data LaunchTemplateEBSBlockDevice = LaunchTemplateEBSBlockDevice'
{ _ltebdDeleteOnTermination :: !(Maybe Bool)
, _ltebdVolumeSize :: !(Maybe Int)
, _ltebdIOPS :: !(Maybe Int)
, _ltebdEncrypted :: !(Maybe Bool)
, _ltebdKMSKeyId :: !(Maybe Text)
, _ltebdVolumeType :: !(Maybe VolumeType)
, _ltebdSnapshotId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
launchTemplateEBSBlockDevice
:: LaunchTemplateEBSBlockDevice
launchTemplateEBSBlockDevice =
LaunchTemplateEBSBlockDevice'
{ _ltebdDeleteOnTermination = Nothing
, _ltebdVolumeSize = Nothing
, _ltebdIOPS = Nothing
, _ltebdEncrypted = Nothing
, _ltebdKMSKeyId = Nothing
, _ltebdVolumeType = Nothing
, _ltebdSnapshotId = Nothing
}
ltebdDeleteOnTermination :: Lens' LaunchTemplateEBSBlockDevice (Maybe Bool)
ltebdDeleteOnTermination = lens _ltebdDeleteOnTermination (\ s a -> s{_ltebdDeleteOnTermination = a})
ltebdVolumeSize :: Lens' LaunchTemplateEBSBlockDevice (Maybe Int)
ltebdVolumeSize = lens _ltebdVolumeSize (\ s a -> s{_ltebdVolumeSize = a})
ltebdIOPS :: Lens' LaunchTemplateEBSBlockDevice (Maybe Int)
ltebdIOPS = lens _ltebdIOPS (\ s a -> s{_ltebdIOPS = a})
ltebdEncrypted :: Lens' LaunchTemplateEBSBlockDevice (Maybe Bool)
ltebdEncrypted = lens _ltebdEncrypted (\ s a -> s{_ltebdEncrypted = a})
ltebdKMSKeyId :: Lens' LaunchTemplateEBSBlockDevice (Maybe Text)
ltebdKMSKeyId = lens _ltebdKMSKeyId (\ s a -> s{_ltebdKMSKeyId = a})
ltebdVolumeType :: Lens' LaunchTemplateEBSBlockDevice (Maybe VolumeType)
ltebdVolumeType = lens _ltebdVolumeType (\ s a -> s{_ltebdVolumeType = a})
ltebdSnapshotId :: Lens' LaunchTemplateEBSBlockDevice (Maybe Text)
ltebdSnapshotId = lens _ltebdSnapshotId (\ s a -> s{_ltebdSnapshotId = a})
instance FromXML LaunchTemplateEBSBlockDevice where
parseXML x
= LaunchTemplateEBSBlockDevice' <$>
(x .@? "deleteOnTermination") <*>
(x .@? "volumeSize")
<*> (x .@? "iops")
<*> (x .@? "encrypted")
<*> (x .@? "kmsKeyId")
<*> (x .@? "volumeType")
<*> (x .@? "snapshotId")
instance Hashable LaunchTemplateEBSBlockDevice where
instance NFData LaunchTemplateEBSBlockDevice where
data LaunchTemplateEBSBlockDeviceRequest = LaunchTemplateEBSBlockDeviceRequest'
{ _ltebdrDeleteOnTermination :: !(Maybe Bool)
, _ltebdrVolumeSize :: !(Maybe Int)
, _ltebdrIOPS :: !(Maybe Int)
, _ltebdrEncrypted :: !(Maybe Bool)
, _ltebdrKMSKeyId :: !(Maybe Text)
, _ltebdrVolumeType :: !(Maybe VolumeType)
, _ltebdrSnapshotId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
launchTemplateEBSBlockDeviceRequest
:: LaunchTemplateEBSBlockDeviceRequest
launchTemplateEBSBlockDeviceRequest =
LaunchTemplateEBSBlockDeviceRequest'
{ _ltebdrDeleteOnTermination = Nothing
, _ltebdrVolumeSize = Nothing
, _ltebdrIOPS = Nothing
, _ltebdrEncrypted = Nothing
, _ltebdrKMSKeyId = Nothing
, _ltebdrVolumeType = Nothing
, _ltebdrSnapshotId = Nothing
}
ltebdrDeleteOnTermination :: Lens' LaunchTemplateEBSBlockDeviceRequest (Maybe Bool)
ltebdrDeleteOnTermination = lens _ltebdrDeleteOnTermination (\ s a -> s{_ltebdrDeleteOnTermination = a})
ltebdrVolumeSize :: Lens' LaunchTemplateEBSBlockDeviceRequest (Maybe Int)
ltebdrVolumeSize = lens _ltebdrVolumeSize (\ s a -> s{_ltebdrVolumeSize = a})
ltebdrIOPS :: Lens' LaunchTemplateEBSBlockDeviceRequest (Maybe Int)
ltebdrIOPS = lens _ltebdrIOPS (\ s a -> s{_ltebdrIOPS = a})
ltebdrEncrypted :: Lens' LaunchTemplateEBSBlockDeviceRequest (Maybe Bool)
ltebdrEncrypted = lens _ltebdrEncrypted (\ s a -> s{_ltebdrEncrypted = a})
ltebdrKMSKeyId :: Lens' LaunchTemplateEBSBlockDeviceRequest (Maybe Text)
ltebdrKMSKeyId = lens _ltebdrKMSKeyId (\ s a -> s{_ltebdrKMSKeyId = a})
ltebdrVolumeType :: Lens' LaunchTemplateEBSBlockDeviceRequest (Maybe VolumeType)
ltebdrVolumeType = lens _ltebdrVolumeType (\ s a -> s{_ltebdrVolumeType = a})
ltebdrSnapshotId :: Lens' LaunchTemplateEBSBlockDeviceRequest (Maybe Text)
ltebdrSnapshotId = lens _ltebdrSnapshotId (\ s a -> s{_ltebdrSnapshotId = a})
instance Hashable LaunchTemplateEBSBlockDeviceRequest
where
instance NFData LaunchTemplateEBSBlockDeviceRequest
where
instance ToQuery LaunchTemplateEBSBlockDeviceRequest
where
toQuery LaunchTemplateEBSBlockDeviceRequest'{..}
= mconcat
["DeleteOnTermination" =: _ltebdrDeleteOnTermination,
"VolumeSize" =: _ltebdrVolumeSize,
"Iops" =: _ltebdrIOPS,
"Encrypted" =: _ltebdrEncrypted,
"KmsKeyId" =: _ltebdrKMSKeyId,
"VolumeType" =: _ltebdrVolumeType,
"SnapshotId" =: _ltebdrSnapshotId]
data LaunchTemplateIAMInstanceProfileSpecification = LaunchTemplateIAMInstanceProfileSpecification'
{ _ltiapsARN :: !(Maybe Text)
, _ltiapsName :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
launchTemplateIAMInstanceProfileSpecification
:: LaunchTemplateIAMInstanceProfileSpecification
launchTemplateIAMInstanceProfileSpecification =
LaunchTemplateIAMInstanceProfileSpecification'
{_ltiapsARN = Nothing, _ltiapsName = Nothing}
ltiapsARN :: Lens' LaunchTemplateIAMInstanceProfileSpecification (Maybe Text)
ltiapsARN = lens _ltiapsARN (\ s a -> s{_ltiapsARN = a})
ltiapsName :: Lens' LaunchTemplateIAMInstanceProfileSpecification (Maybe Text)
ltiapsName = lens _ltiapsName (\ s a -> s{_ltiapsName = a})
instance FromXML
LaunchTemplateIAMInstanceProfileSpecification
where
parseXML x
= LaunchTemplateIAMInstanceProfileSpecification' <$>
(x .@? "arn") <*> (x .@? "name")
instance Hashable
LaunchTemplateIAMInstanceProfileSpecification
where
instance NFData
LaunchTemplateIAMInstanceProfileSpecification
where
data LaunchTemplateIAMInstanceProfileSpecificationRequest = LaunchTemplateIAMInstanceProfileSpecificationRequest'
{ _ltiapsrARN :: !(Maybe Text)
, _ltiapsrName :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
launchTemplateIAMInstanceProfileSpecificationRequest
:: LaunchTemplateIAMInstanceProfileSpecificationRequest
launchTemplateIAMInstanceProfileSpecificationRequest =
LaunchTemplateIAMInstanceProfileSpecificationRequest'
{_ltiapsrARN = Nothing, _ltiapsrName = Nothing}
ltiapsrARN :: Lens' LaunchTemplateIAMInstanceProfileSpecificationRequest (Maybe Text)
ltiapsrARN = lens _ltiapsrARN (\ s a -> s{_ltiapsrARN = a})
ltiapsrName :: Lens' LaunchTemplateIAMInstanceProfileSpecificationRequest (Maybe Text)
ltiapsrName = lens _ltiapsrName (\ s a -> s{_ltiapsrName = a})
instance Hashable
LaunchTemplateIAMInstanceProfileSpecificationRequest
where
instance NFData
LaunchTemplateIAMInstanceProfileSpecificationRequest
where
instance ToQuery
LaunchTemplateIAMInstanceProfileSpecificationRequest
where
toQuery
LaunchTemplateIAMInstanceProfileSpecificationRequest'{..}
= mconcat
["Arn" =: _ltiapsrARN, "Name" =: _ltiapsrName]
data LaunchTemplateInstanceMarketOptions = LaunchTemplateInstanceMarketOptions'
{ _ltimoMarketType :: !(Maybe MarketType)
, _ltimoSpotOptions :: !(Maybe LaunchTemplateSpotMarketOptions)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
launchTemplateInstanceMarketOptions
:: LaunchTemplateInstanceMarketOptions
launchTemplateInstanceMarketOptions =
LaunchTemplateInstanceMarketOptions'
{_ltimoMarketType = Nothing, _ltimoSpotOptions = Nothing}
ltimoMarketType :: Lens' LaunchTemplateInstanceMarketOptions (Maybe MarketType)
ltimoMarketType = lens _ltimoMarketType (\ s a -> s{_ltimoMarketType = a})
ltimoSpotOptions :: Lens' LaunchTemplateInstanceMarketOptions (Maybe LaunchTemplateSpotMarketOptions)
ltimoSpotOptions = lens _ltimoSpotOptions (\ s a -> s{_ltimoSpotOptions = a})
instance FromXML LaunchTemplateInstanceMarketOptions
where
parseXML x
= LaunchTemplateInstanceMarketOptions' <$>
(x .@? "marketType") <*> (x .@? "spotOptions")
instance Hashable LaunchTemplateInstanceMarketOptions
where
instance NFData LaunchTemplateInstanceMarketOptions
where
data LaunchTemplateInstanceMarketOptionsRequest = LaunchTemplateInstanceMarketOptionsRequest'
{ _ltimorMarketType :: !(Maybe MarketType)
, _ltimorSpotOptions :: !(Maybe LaunchTemplateSpotMarketOptionsRequest)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
launchTemplateInstanceMarketOptionsRequest
:: LaunchTemplateInstanceMarketOptionsRequest
launchTemplateInstanceMarketOptionsRequest =
LaunchTemplateInstanceMarketOptionsRequest'
{_ltimorMarketType = Nothing, _ltimorSpotOptions = Nothing}
ltimorMarketType :: Lens' LaunchTemplateInstanceMarketOptionsRequest (Maybe MarketType)
ltimorMarketType = lens _ltimorMarketType (\ s a -> s{_ltimorMarketType = a})
ltimorSpotOptions :: Lens' LaunchTemplateInstanceMarketOptionsRequest (Maybe LaunchTemplateSpotMarketOptionsRequest)
ltimorSpotOptions = lens _ltimorSpotOptions (\ s a -> s{_ltimorSpotOptions = a})
instance Hashable
LaunchTemplateInstanceMarketOptionsRequest
where
instance NFData
LaunchTemplateInstanceMarketOptionsRequest
where
instance ToQuery
LaunchTemplateInstanceMarketOptionsRequest
where
toQuery
LaunchTemplateInstanceMarketOptionsRequest'{..}
= mconcat
["MarketType" =: _ltimorMarketType,
"SpotOptions" =: _ltimorSpotOptions]
data LaunchTemplateInstanceNetworkInterfaceSpecification = LaunchTemplateInstanceNetworkInterfaceSpecification'
{ _ltinisGroups :: !(Maybe [Text])
, _ltinisPrivateIPAddresses :: !(Maybe [PrivateIPAddressSpecification])
, _ltinisDeleteOnTermination :: !(Maybe Bool)
, _ltinisAssociatePublicIPAddress :: !(Maybe Bool)
, _ltinisNetworkInterfaceId :: !(Maybe Text)
, _ltinisSubnetId :: !(Maybe Text)
, _ltinisIPv6AddressCount :: !(Maybe Int)
, _ltinisPrivateIPAddress :: !(Maybe Text)
, _ltinisSecondaryPrivateIPAddressCount :: !(Maybe Int)
, _ltinisDescription :: !(Maybe Text)
, _ltinisDeviceIndex :: !(Maybe Int)
, _ltinisIPv6Addresses :: !(Maybe [InstanceIPv6Address])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
launchTemplateInstanceNetworkInterfaceSpecification
:: LaunchTemplateInstanceNetworkInterfaceSpecification
launchTemplateInstanceNetworkInterfaceSpecification =
LaunchTemplateInstanceNetworkInterfaceSpecification'
{ _ltinisGroups = Nothing
, _ltinisPrivateIPAddresses = Nothing
, _ltinisDeleteOnTermination = Nothing
, _ltinisAssociatePublicIPAddress = Nothing
, _ltinisNetworkInterfaceId = Nothing
, _ltinisSubnetId = Nothing
, _ltinisIPv6AddressCount = Nothing
, _ltinisPrivateIPAddress = Nothing
, _ltinisSecondaryPrivateIPAddressCount = Nothing
, _ltinisDescription = Nothing
, _ltinisDeviceIndex = Nothing
, _ltinisIPv6Addresses = Nothing
}
ltinisGroups :: Lens' LaunchTemplateInstanceNetworkInterfaceSpecification [Text]
ltinisGroups = lens _ltinisGroups (\ s a -> s{_ltinisGroups = a}) . _Default . _Coerce
ltinisPrivateIPAddresses :: Lens' LaunchTemplateInstanceNetworkInterfaceSpecification [PrivateIPAddressSpecification]
ltinisPrivateIPAddresses = lens _ltinisPrivateIPAddresses (\ s a -> s{_ltinisPrivateIPAddresses = a}) . _Default . _Coerce
ltinisDeleteOnTermination :: Lens' LaunchTemplateInstanceNetworkInterfaceSpecification (Maybe Bool)
ltinisDeleteOnTermination = lens _ltinisDeleteOnTermination (\ s a -> s{_ltinisDeleteOnTermination = a})
ltinisAssociatePublicIPAddress :: Lens' LaunchTemplateInstanceNetworkInterfaceSpecification (Maybe Bool)
ltinisAssociatePublicIPAddress = lens _ltinisAssociatePublicIPAddress (\ s a -> s{_ltinisAssociatePublicIPAddress = a})
ltinisNetworkInterfaceId :: Lens' LaunchTemplateInstanceNetworkInterfaceSpecification (Maybe Text)
ltinisNetworkInterfaceId = lens _ltinisNetworkInterfaceId (\ s a -> s{_ltinisNetworkInterfaceId = a})
ltinisSubnetId :: Lens' LaunchTemplateInstanceNetworkInterfaceSpecification (Maybe Text)
ltinisSubnetId = lens _ltinisSubnetId (\ s a -> s{_ltinisSubnetId = a})
ltinisIPv6AddressCount :: Lens' LaunchTemplateInstanceNetworkInterfaceSpecification (Maybe Int)
ltinisIPv6AddressCount = lens _ltinisIPv6AddressCount (\ s a -> s{_ltinisIPv6AddressCount = a})
ltinisPrivateIPAddress :: Lens' LaunchTemplateInstanceNetworkInterfaceSpecification (Maybe Text)
ltinisPrivateIPAddress = lens _ltinisPrivateIPAddress (\ s a -> s{_ltinisPrivateIPAddress = a})
ltinisSecondaryPrivateIPAddressCount :: Lens' LaunchTemplateInstanceNetworkInterfaceSpecification (Maybe Int)
ltinisSecondaryPrivateIPAddressCount = lens _ltinisSecondaryPrivateIPAddressCount (\ s a -> s{_ltinisSecondaryPrivateIPAddressCount = a})
ltinisDescription :: Lens' LaunchTemplateInstanceNetworkInterfaceSpecification (Maybe Text)
ltinisDescription = lens _ltinisDescription (\ s a -> s{_ltinisDescription = a})
ltinisDeviceIndex :: Lens' LaunchTemplateInstanceNetworkInterfaceSpecification (Maybe Int)
ltinisDeviceIndex = lens _ltinisDeviceIndex (\ s a -> s{_ltinisDeviceIndex = a})
ltinisIPv6Addresses :: Lens' LaunchTemplateInstanceNetworkInterfaceSpecification [InstanceIPv6Address]
ltinisIPv6Addresses = lens _ltinisIPv6Addresses (\ s a -> s{_ltinisIPv6Addresses = a}) . _Default . _Coerce
instance FromXML
LaunchTemplateInstanceNetworkInterfaceSpecification
where
parseXML x
= LaunchTemplateInstanceNetworkInterfaceSpecification'
<$>
(x .@? "groupSet" .!@ mempty >>=
may (parseXMLList "groupId"))
<*>
(x .@? "privateIpAddressesSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "deleteOnTermination")
<*> (x .@? "associatePublicIpAddress")
<*> (x .@? "networkInterfaceId")
<*> (x .@? "subnetId")
<*> (x .@? "ipv6AddressCount")
<*> (x .@? "privateIpAddress")
<*> (x .@? "secondaryPrivateIpAddressCount")
<*> (x .@? "description")
<*> (x .@? "deviceIndex")
<*>
(x .@? "ipv6AddressesSet" .!@ mempty >>=
may (parseXMLList "item"))
instance Hashable
LaunchTemplateInstanceNetworkInterfaceSpecification
where
instance NFData
LaunchTemplateInstanceNetworkInterfaceSpecification
where
data LaunchTemplateInstanceNetworkInterfaceSpecificationRequest = LaunchTemplateInstanceNetworkInterfaceSpecificationRequest'
{ _ltinisrGroups :: !(Maybe [Text])
, _ltinisrPrivateIPAddresses :: !(Maybe [PrivateIPAddressSpecification])
, _ltinisrDeleteOnTermination :: !(Maybe Bool)
, _ltinisrAssociatePublicIPAddress :: !(Maybe Bool)
, _ltinisrNetworkInterfaceId :: !(Maybe Text)
, _ltinisrSubnetId :: !(Maybe Text)
, _ltinisrIPv6AddressCount :: !(Maybe Int)
, _ltinisrPrivateIPAddress :: !(Maybe Text)
, _ltinisrSecondaryPrivateIPAddressCount :: !(Maybe Int)
, _ltinisrDescription :: !(Maybe Text)
, _ltinisrDeviceIndex :: !(Maybe Int)
, _ltinisrIPv6Addresses :: !(Maybe [InstanceIPv6AddressRequest])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
launchTemplateInstanceNetworkInterfaceSpecificationRequest
:: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
launchTemplateInstanceNetworkInterfaceSpecificationRequest =
LaunchTemplateInstanceNetworkInterfaceSpecificationRequest'
{ _ltinisrGroups = Nothing
, _ltinisrPrivateIPAddresses = Nothing
, _ltinisrDeleteOnTermination = Nothing
, _ltinisrAssociatePublicIPAddress = Nothing
, _ltinisrNetworkInterfaceId = Nothing
, _ltinisrSubnetId = Nothing
, _ltinisrIPv6AddressCount = Nothing
, _ltinisrPrivateIPAddress = Nothing
, _ltinisrSecondaryPrivateIPAddressCount = Nothing
, _ltinisrDescription = Nothing
, _ltinisrDeviceIndex = Nothing
, _ltinisrIPv6Addresses = Nothing
}
ltinisrGroups :: Lens' LaunchTemplateInstanceNetworkInterfaceSpecificationRequest [Text]
ltinisrGroups = lens _ltinisrGroups (\ s a -> s{_ltinisrGroups = a}) . _Default . _Coerce
ltinisrPrivateIPAddresses :: Lens' LaunchTemplateInstanceNetworkInterfaceSpecificationRequest [PrivateIPAddressSpecification]
ltinisrPrivateIPAddresses = lens _ltinisrPrivateIPAddresses (\ s a -> s{_ltinisrPrivateIPAddresses = a}) . _Default . _Coerce
ltinisrDeleteOnTermination :: Lens' LaunchTemplateInstanceNetworkInterfaceSpecificationRequest (Maybe Bool)
ltinisrDeleteOnTermination = lens _ltinisrDeleteOnTermination (\ s a -> s{_ltinisrDeleteOnTermination = a})
ltinisrAssociatePublicIPAddress :: Lens' LaunchTemplateInstanceNetworkInterfaceSpecificationRequest (Maybe Bool)
ltinisrAssociatePublicIPAddress = lens _ltinisrAssociatePublicIPAddress (\ s a -> s{_ltinisrAssociatePublicIPAddress = a})
ltinisrNetworkInterfaceId :: Lens' LaunchTemplateInstanceNetworkInterfaceSpecificationRequest (Maybe Text)
ltinisrNetworkInterfaceId = lens _ltinisrNetworkInterfaceId (\ s a -> s{_ltinisrNetworkInterfaceId = a})
ltinisrSubnetId :: Lens' LaunchTemplateInstanceNetworkInterfaceSpecificationRequest (Maybe Text)
ltinisrSubnetId = lens _ltinisrSubnetId (\ s a -> s{_ltinisrSubnetId = a})
ltinisrIPv6AddressCount :: Lens' LaunchTemplateInstanceNetworkInterfaceSpecificationRequest (Maybe Int)
ltinisrIPv6AddressCount = lens _ltinisrIPv6AddressCount (\ s a -> s{_ltinisrIPv6AddressCount = a})
ltinisrPrivateIPAddress :: Lens' LaunchTemplateInstanceNetworkInterfaceSpecificationRequest (Maybe Text)
ltinisrPrivateIPAddress = lens _ltinisrPrivateIPAddress (\ s a -> s{_ltinisrPrivateIPAddress = a})
ltinisrSecondaryPrivateIPAddressCount :: Lens' LaunchTemplateInstanceNetworkInterfaceSpecificationRequest (Maybe Int)
ltinisrSecondaryPrivateIPAddressCount = lens _ltinisrSecondaryPrivateIPAddressCount (\ s a -> s{_ltinisrSecondaryPrivateIPAddressCount = a})
ltinisrDescription :: Lens' LaunchTemplateInstanceNetworkInterfaceSpecificationRequest (Maybe Text)
ltinisrDescription = lens _ltinisrDescription (\ s a -> s{_ltinisrDescription = a})
ltinisrDeviceIndex :: Lens' LaunchTemplateInstanceNetworkInterfaceSpecificationRequest (Maybe Int)
ltinisrDeviceIndex = lens _ltinisrDeviceIndex (\ s a -> s{_ltinisrDeviceIndex = a})
ltinisrIPv6Addresses :: Lens' LaunchTemplateInstanceNetworkInterfaceSpecificationRequest [InstanceIPv6AddressRequest]
ltinisrIPv6Addresses = lens _ltinisrIPv6Addresses (\ s a -> s{_ltinisrIPv6Addresses = a}) . _Default . _Coerce
instance Hashable
LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
where
instance NFData
LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
where
instance ToQuery
LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
where
toQuery
LaunchTemplateInstanceNetworkInterfaceSpecificationRequest'{..}
= mconcat
[toQuery
(toQueryList "SecurityGroupId" <$> _ltinisrGroups),
toQuery
(toQueryList "PrivateIpAddresses" <$>
_ltinisrPrivateIPAddresses),
"DeleteOnTermination" =: _ltinisrDeleteOnTermination,
"AssociatePublicIpAddress" =:
_ltinisrAssociatePublicIPAddress,
"NetworkInterfaceId" =: _ltinisrNetworkInterfaceId,
"SubnetId" =: _ltinisrSubnetId,
"Ipv6AddressCount" =: _ltinisrIPv6AddressCount,
"PrivateIpAddress" =: _ltinisrPrivateIPAddress,
"SecondaryPrivateIpAddressCount" =:
_ltinisrSecondaryPrivateIPAddressCount,
"Description" =: _ltinisrDescription,
"DeviceIndex" =: _ltinisrDeviceIndex,
toQuery
(toQueryList "Ipv6Addresses" <$>
_ltinisrIPv6Addresses)]
data LaunchTemplateOverrides = LaunchTemplateOverrides'
{ _ltoSpotPrice :: !(Maybe Text)
, _ltoWeightedCapacity :: !(Maybe Double)
, _ltoSubnetId :: !(Maybe Text)
, _ltoInstanceType :: !(Maybe InstanceType)
, _ltoAvailabilityZone :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
launchTemplateOverrides
:: LaunchTemplateOverrides
launchTemplateOverrides =
LaunchTemplateOverrides'
{ _ltoSpotPrice = Nothing
, _ltoWeightedCapacity = Nothing
, _ltoSubnetId = Nothing
, _ltoInstanceType = Nothing
, _ltoAvailabilityZone = Nothing
}
ltoSpotPrice :: Lens' LaunchTemplateOverrides (Maybe Text)
ltoSpotPrice = lens _ltoSpotPrice (\ s a -> s{_ltoSpotPrice = a})
ltoWeightedCapacity :: Lens' LaunchTemplateOverrides (Maybe Double)
ltoWeightedCapacity = lens _ltoWeightedCapacity (\ s a -> s{_ltoWeightedCapacity = a})
ltoSubnetId :: Lens' LaunchTemplateOverrides (Maybe Text)
ltoSubnetId = lens _ltoSubnetId (\ s a -> s{_ltoSubnetId = a})
ltoInstanceType :: Lens' LaunchTemplateOverrides (Maybe InstanceType)
ltoInstanceType = lens _ltoInstanceType (\ s a -> s{_ltoInstanceType = a})
ltoAvailabilityZone :: Lens' LaunchTemplateOverrides (Maybe Text)
ltoAvailabilityZone = lens _ltoAvailabilityZone (\ s a -> s{_ltoAvailabilityZone = a})
instance FromXML LaunchTemplateOverrides where
parseXML x
= LaunchTemplateOverrides' <$>
(x .@? "spotPrice") <*> (x .@? "weightedCapacity")
<*> (x .@? "subnetId")
<*> (x .@? "instanceType")
<*> (x .@? "availabilityZone")
instance Hashable LaunchTemplateOverrides where
instance NFData LaunchTemplateOverrides where
instance ToQuery LaunchTemplateOverrides where
toQuery LaunchTemplateOverrides'{..}
= mconcat
["SpotPrice" =: _ltoSpotPrice,
"WeightedCapacity" =: _ltoWeightedCapacity,
"SubnetId" =: _ltoSubnetId,
"InstanceType" =: _ltoInstanceType,
"AvailabilityZone" =: _ltoAvailabilityZone]
data LaunchTemplatePlacement = LaunchTemplatePlacement'
{ _ltpAffinity :: !(Maybe Text)
, _ltpHostId :: !(Maybe Text)
, _ltpSpreadDomain :: !(Maybe Text)
, _ltpAvailabilityZone :: !(Maybe Text)
, _ltpTenancy :: !(Maybe Tenancy)
, _ltpGroupName :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
launchTemplatePlacement
:: LaunchTemplatePlacement
launchTemplatePlacement =
LaunchTemplatePlacement'
{ _ltpAffinity = Nothing
, _ltpHostId = Nothing
, _ltpSpreadDomain = Nothing
, _ltpAvailabilityZone = Nothing
, _ltpTenancy = Nothing
, _ltpGroupName = Nothing
}
ltpAffinity :: Lens' LaunchTemplatePlacement (Maybe Text)
ltpAffinity = lens _ltpAffinity (\ s a -> s{_ltpAffinity = a})
ltpHostId :: Lens' LaunchTemplatePlacement (Maybe Text)
ltpHostId = lens _ltpHostId (\ s a -> s{_ltpHostId = a})
ltpSpreadDomain :: Lens' LaunchTemplatePlacement (Maybe Text)
ltpSpreadDomain = lens _ltpSpreadDomain (\ s a -> s{_ltpSpreadDomain = a})
ltpAvailabilityZone :: Lens' LaunchTemplatePlacement (Maybe Text)
ltpAvailabilityZone = lens _ltpAvailabilityZone (\ s a -> s{_ltpAvailabilityZone = a})
ltpTenancy :: Lens' LaunchTemplatePlacement (Maybe Tenancy)
ltpTenancy = lens _ltpTenancy (\ s a -> s{_ltpTenancy = a})
ltpGroupName :: Lens' LaunchTemplatePlacement (Maybe Text)
ltpGroupName = lens _ltpGroupName (\ s a -> s{_ltpGroupName = a})
instance FromXML LaunchTemplatePlacement where
parseXML x
= LaunchTemplatePlacement' <$>
(x .@? "affinity") <*> (x .@? "hostId") <*>
(x .@? "spreadDomain")
<*> (x .@? "availabilityZone")
<*> (x .@? "tenancy")
<*> (x .@? "groupName")
instance Hashable LaunchTemplatePlacement where
instance NFData LaunchTemplatePlacement where
data LaunchTemplatePlacementRequest = LaunchTemplatePlacementRequest'
{ _ltprAffinity :: !(Maybe Text)
, _ltprHostId :: !(Maybe Text)
, _ltprSpreadDomain :: !(Maybe Text)
, _ltprAvailabilityZone :: !(Maybe Text)
, _ltprTenancy :: !(Maybe Tenancy)
, _ltprGroupName :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
launchTemplatePlacementRequest
:: LaunchTemplatePlacementRequest
launchTemplatePlacementRequest =
LaunchTemplatePlacementRequest'
{ _ltprAffinity = Nothing
, _ltprHostId = Nothing
, _ltprSpreadDomain = Nothing
, _ltprAvailabilityZone = Nothing
, _ltprTenancy = Nothing
, _ltprGroupName = Nothing
}
ltprAffinity :: Lens' LaunchTemplatePlacementRequest (Maybe Text)
ltprAffinity = lens _ltprAffinity (\ s a -> s{_ltprAffinity = a})
ltprHostId :: Lens' LaunchTemplatePlacementRequest (Maybe Text)
ltprHostId = lens _ltprHostId (\ s a -> s{_ltprHostId = a})
ltprSpreadDomain :: Lens' LaunchTemplatePlacementRequest (Maybe Text)
ltprSpreadDomain = lens _ltprSpreadDomain (\ s a -> s{_ltprSpreadDomain = a})
ltprAvailabilityZone :: Lens' LaunchTemplatePlacementRequest (Maybe Text)
ltprAvailabilityZone = lens _ltprAvailabilityZone (\ s a -> s{_ltprAvailabilityZone = a})
ltprTenancy :: Lens' LaunchTemplatePlacementRequest (Maybe Tenancy)
ltprTenancy = lens _ltprTenancy (\ s a -> s{_ltprTenancy = a})
ltprGroupName :: Lens' LaunchTemplatePlacementRequest (Maybe Text)
ltprGroupName = lens _ltprGroupName (\ s a -> s{_ltprGroupName = a})
instance Hashable LaunchTemplatePlacementRequest
where
instance NFData LaunchTemplatePlacementRequest where
instance ToQuery LaunchTemplatePlacementRequest where
toQuery LaunchTemplatePlacementRequest'{..}
= mconcat
["Affinity" =: _ltprAffinity,
"HostId" =: _ltprHostId,
"SpreadDomain" =: _ltprSpreadDomain,
"AvailabilityZone" =: _ltprAvailabilityZone,
"Tenancy" =: _ltprTenancy,
"GroupName" =: _ltprGroupName]
data LaunchTemplateSpecification = LaunchTemplateSpecification'
{ _ltsLaunchTemplateName :: !(Maybe Text)
, _ltsLaunchTemplateId :: !(Maybe Text)
, _ltsVersion :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
launchTemplateSpecification
:: LaunchTemplateSpecification
launchTemplateSpecification =
LaunchTemplateSpecification'
{ _ltsLaunchTemplateName = Nothing
, _ltsLaunchTemplateId = Nothing
, _ltsVersion = Nothing
}
ltsLaunchTemplateName :: Lens' LaunchTemplateSpecification (Maybe Text)
ltsLaunchTemplateName = lens _ltsLaunchTemplateName (\ s a -> s{_ltsLaunchTemplateName = a})
ltsLaunchTemplateId :: Lens' LaunchTemplateSpecification (Maybe Text)
ltsLaunchTemplateId = lens _ltsLaunchTemplateId (\ s a -> s{_ltsLaunchTemplateId = a})
ltsVersion :: Lens' LaunchTemplateSpecification (Maybe Text)
ltsVersion = lens _ltsVersion (\ s a -> s{_ltsVersion = a})
instance Hashable LaunchTemplateSpecification where
instance NFData LaunchTemplateSpecification where
instance ToQuery LaunchTemplateSpecification where
toQuery LaunchTemplateSpecification'{..}
= mconcat
["LaunchTemplateName" =: _ltsLaunchTemplateName,
"LaunchTemplateId" =: _ltsLaunchTemplateId,
"Version" =: _ltsVersion]
data LaunchTemplateSpotMarketOptions = LaunchTemplateSpotMarketOptions'
{ _ltsmoBlockDurationMinutes :: !(Maybe Int)
, _ltsmoInstanceInterruptionBehavior :: !(Maybe InstanceInterruptionBehavior)
, _ltsmoValidUntil :: !(Maybe ISO8601)
, _ltsmoSpotInstanceType :: !(Maybe SpotInstanceType)
, _ltsmoMaxPrice :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
launchTemplateSpotMarketOptions
:: LaunchTemplateSpotMarketOptions
launchTemplateSpotMarketOptions =
LaunchTemplateSpotMarketOptions'
{ _ltsmoBlockDurationMinutes = Nothing
, _ltsmoInstanceInterruptionBehavior = Nothing
, _ltsmoValidUntil = Nothing
, _ltsmoSpotInstanceType = Nothing
, _ltsmoMaxPrice = Nothing
}
ltsmoBlockDurationMinutes :: Lens' LaunchTemplateSpotMarketOptions (Maybe Int)
ltsmoBlockDurationMinutes = lens _ltsmoBlockDurationMinutes (\ s a -> s{_ltsmoBlockDurationMinutes = a})
ltsmoInstanceInterruptionBehavior :: Lens' LaunchTemplateSpotMarketOptions (Maybe InstanceInterruptionBehavior)
ltsmoInstanceInterruptionBehavior = lens _ltsmoInstanceInterruptionBehavior (\ s a -> s{_ltsmoInstanceInterruptionBehavior = a})
ltsmoValidUntil :: Lens' LaunchTemplateSpotMarketOptions (Maybe UTCTime)
ltsmoValidUntil = lens _ltsmoValidUntil (\ s a -> s{_ltsmoValidUntil = a}) . mapping _Time
ltsmoSpotInstanceType :: Lens' LaunchTemplateSpotMarketOptions (Maybe SpotInstanceType)
ltsmoSpotInstanceType = lens _ltsmoSpotInstanceType (\ s a -> s{_ltsmoSpotInstanceType = a})
ltsmoMaxPrice :: Lens' LaunchTemplateSpotMarketOptions (Maybe Text)
ltsmoMaxPrice = lens _ltsmoMaxPrice (\ s a -> s{_ltsmoMaxPrice = a})
instance FromXML LaunchTemplateSpotMarketOptions
where
parseXML x
= LaunchTemplateSpotMarketOptions' <$>
(x .@? "blockDurationMinutes") <*>
(x .@? "instanceInterruptionBehavior")
<*> (x .@? "validUntil")
<*> (x .@? "spotInstanceType")
<*> (x .@? "maxPrice")
instance Hashable LaunchTemplateSpotMarketOptions
where
instance NFData LaunchTemplateSpotMarketOptions where
data LaunchTemplateSpotMarketOptionsRequest = LaunchTemplateSpotMarketOptionsRequest'
{ _ltsmorBlockDurationMinutes :: !(Maybe Int)
, _ltsmorInstanceInterruptionBehavior :: !(Maybe InstanceInterruptionBehavior)
, _ltsmorValidUntil :: !(Maybe ISO8601)
, _ltsmorSpotInstanceType :: !(Maybe SpotInstanceType)
, _ltsmorMaxPrice :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
launchTemplateSpotMarketOptionsRequest
:: LaunchTemplateSpotMarketOptionsRequest
launchTemplateSpotMarketOptionsRequest =
LaunchTemplateSpotMarketOptionsRequest'
{ _ltsmorBlockDurationMinutes = Nothing
, _ltsmorInstanceInterruptionBehavior = Nothing
, _ltsmorValidUntil = Nothing
, _ltsmorSpotInstanceType = Nothing
, _ltsmorMaxPrice = Nothing
}
ltsmorBlockDurationMinutes :: Lens' LaunchTemplateSpotMarketOptionsRequest (Maybe Int)
ltsmorBlockDurationMinutes = lens _ltsmorBlockDurationMinutes (\ s a -> s{_ltsmorBlockDurationMinutes = a})
ltsmorInstanceInterruptionBehavior :: Lens' LaunchTemplateSpotMarketOptionsRequest (Maybe InstanceInterruptionBehavior)
ltsmorInstanceInterruptionBehavior = lens _ltsmorInstanceInterruptionBehavior (\ s a -> s{_ltsmorInstanceInterruptionBehavior = a})
ltsmorValidUntil :: Lens' LaunchTemplateSpotMarketOptionsRequest (Maybe UTCTime)
ltsmorValidUntil = lens _ltsmorValidUntil (\ s a -> s{_ltsmorValidUntil = a}) . mapping _Time
ltsmorSpotInstanceType :: Lens' LaunchTemplateSpotMarketOptionsRequest (Maybe SpotInstanceType)
ltsmorSpotInstanceType = lens _ltsmorSpotInstanceType (\ s a -> s{_ltsmorSpotInstanceType = a})
ltsmorMaxPrice :: Lens' LaunchTemplateSpotMarketOptionsRequest (Maybe Text)
ltsmorMaxPrice = lens _ltsmorMaxPrice (\ s a -> s{_ltsmorMaxPrice = a})
instance Hashable
LaunchTemplateSpotMarketOptionsRequest
where
instance NFData
LaunchTemplateSpotMarketOptionsRequest
where
instance ToQuery
LaunchTemplateSpotMarketOptionsRequest
where
toQuery LaunchTemplateSpotMarketOptionsRequest'{..}
= mconcat
["BlockDurationMinutes" =:
_ltsmorBlockDurationMinutes,
"InstanceInterruptionBehavior" =:
_ltsmorInstanceInterruptionBehavior,
"ValidUntil" =: _ltsmorValidUntil,
"SpotInstanceType" =: _ltsmorSpotInstanceType,
"MaxPrice" =: _ltsmorMaxPrice]
data LaunchTemplateTagSpecification = LaunchTemplateTagSpecification'
{ _lttsResourceType :: !(Maybe ResourceType)
, _lttsTags :: !(Maybe [Tag])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
launchTemplateTagSpecification
:: LaunchTemplateTagSpecification
launchTemplateTagSpecification =
LaunchTemplateTagSpecification'
{_lttsResourceType = Nothing, _lttsTags = Nothing}
lttsResourceType :: Lens' LaunchTemplateTagSpecification (Maybe ResourceType)
lttsResourceType = lens _lttsResourceType (\ s a -> s{_lttsResourceType = a})
lttsTags :: Lens' LaunchTemplateTagSpecification [Tag]
lttsTags = lens _lttsTags (\ s a -> s{_lttsTags = a}) . _Default . _Coerce
instance FromXML LaunchTemplateTagSpecification where
parseXML x
= LaunchTemplateTagSpecification' <$>
(x .@? "resourceType") <*>
(x .@? "tagSet" .!@ mempty >>=
may (parseXMLList "item"))
instance Hashable LaunchTemplateTagSpecification
where
instance NFData LaunchTemplateTagSpecification where
data LaunchTemplateTagSpecificationRequest = LaunchTemplateTagSpecificationRequest'
{ _lttsrResourceType :: !(Maybe ResourceType)
, _lttsrTags :: !(Maybe [Tag])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
launchTemplateTagSpecificationRequest
:: LaunchTemplateTagSpecificationRequest
launchTemplateTagSpecificationRequest =
LaunchTemplateTagSpecificationRequest'
{_lttsrResourceType = Nothing, _lttsrTags = Nothing}
lttsrResourceType :: Lens' LaunchTemplateTagSpecificationRequest (Maybe ResourceType)
lttsrResourceType = lens _lttsrResourceType (\ s a -> s{_lttsrResourceType = a})
lttsrTags :: Lens' LaunchTemplateTagSpecificationRequest [Tag]
lttsrTags = lens _lttsrTags (\ s a -> s{_lttsrTags = a}) . _Default . _Coerce
instance Hashable
LaunchTemplateTagSpecificationRequest
where
instance NFData LaunchTemplateTagSpecificationRequest
where
instance ToQuery
LaunchTemplateTagSpecificationRequest
where
toQuery LaunchTemplateTagSpecificationRequest'{..}
= mconcat
["ResourceType" =: _lttsrResourceType,
toQuery (toQueryList "Tag" <$> _lttsrTags)]
data LaunchTemplateVersion = LaunchTemplateVersion'
{ _ltvLaunchTemplateName :: !(Maybe Text)
, _ltvLaunchTemplateId :: !(Maybe Text)
, _ltvCreatedBy :: !(Maybe Text)
, _ltvDefaultVersion :: !(Maybe Bool)
, _ltvVersionNumber :: !(Maybe Integer)
, _ltvVersionDescription :: !(Maybe Text)
, _ltvLaunchTemplateData :: !(Maybe ResponseLaunchTemplateData)
, _ltvCreateTime :: !(Maybe ISO8601)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
launchTemplateVersion
:: LaunchTemplateVersion
launchTemplateVersion =
LaunchTemplateVersion'
{ _ltvLaunchTemplateName = Nothing
, _ltvLaunchTemplateId = Nothing
, _ltvCreatedBy = Nothing
, _ltvDefaultVersion = Nothing
, _ltvVersionNumber = Nothing
, _ltvVersionDescription = Nothing
, _ltvLaunchTemplateData = Nothing
, _ltvCreateTime = Nothing
}
ltvLaunchTemplateName :: Lens' LaunchTemplateVersion (Maybe Text)
ltvLaunchTemplateName = lens _ltvLaunchTemplateName (\ s a -> s{_ltvLaunchTemplateName = a})
ltvLaunchTemplateId :: Lens' LaunchTemplateVersion (Maybe Text)
ltvLaunchTemplateId = lens _ltvLaunchTemplateId (\ s a -> s{_ltvLaunchTemplateId = a})
ltvCreatedBy :: Lens' LaunchTemplateVersion (Maybe Text)
ltvCreatedBy = lens _ltvCreatedBy (\ s a -> s{_ltvCreatedBy = a})
ltvDefaultVersion :: Lens' LaunchTemplateVersion (Maybe Bool)
ltvDefaultVersion = lens _ltvDefaultVersion (\ s a -> s{_ltvDefaultVersion = a})
ltvVersionNumber :: Lens' LaunchTemplateVersion (Maybe Integer)
ltvVersionNumber = lens _ltvVersionNumber (\ s a -> s{_ltvVersionNumber = a})
ltvVersionDescription :: Lens' LaunchTemplateVersion (Maybe Text)
ltvVersionDescription = lens _ltvVersionDescription (\ s a -> s{_ltvVersionDescription = a})
ltvLaunchTemplateData :: Lens' LaunchTemplateVersion (Maybe ResponseLaunchTemplateData)
ltvLaunchTemplateData = lens _ltvLaunchTemplateData (\ s a -> s{_ltvLaunchTemplateData = a})
ltvCreateTime :: Lens' LaunchTemplateVersion (Maybe UTCTime)
ltvCreateTime = lens _ltvCreateTime (\ s a -> s{_ltvCreateTime = a}) . mapping _Time
instance FromXML LaunchTemplateVersion where
parseXML x
= LaunchTemplateVersion' <$>
(x .@? "launchTemplateName") <*>
(x .@? "launchTemplateId")
<*> (x .@? "createdBy")
<*> (x .@? "defaultVersion")
<*> (x .@? "versionNumber")
<*> (x .@? "versionDescription")
<*> (x .@? "launchTemplateData")
<*> (x .@? "createTime")
instance Hashable LaunchTemplateVersion where
instance NFData LaunchTemplateVersion where
newtype LaunchTemplatesMonitoring = LaunchTemplatesMonitoring'
{ _ltmEnabled :: Maybe Bool
} deriving (Eq, Read, Show, Data, Typeable, Generic)
launchTemplatesMonitoring
:: LaunchTemplatesMonitoring
launchTemplatesMonitoring = LaunchTemplatesMonitoring' {_ltmEnabled = Nothing}
ltmEnabled :: Lens' LaunchTemplatesMonitoring (Maybe Bool)
ltmEnabled = lens _ltmEnabled (\ s a -> s{_ltmEnabled = a})
instance FromXML LaunchTemplatesMonitoring where
parseXML x
= LaunchTemplatesMonitoring' <$> (x .@? "enabled")
instance Hashable LaunchTemplatesMonitoring where
instance NFData LaunchTemplatesMonitoring where
newtype LaunchTemplatesMonitoringRequest = LaunchTemplatesMonitoringRequest'
{ _ltmrEnabled :: Maybe Bool
} deriving (Eq, Read, Show, Data, Typeable, Generic)
launchTemplatesMonitoringRequest
:: LaunchTemplatesMonitoringRequest
launchTemplatesMonitoringRequest =
LaunchTemplatesMonitoringRequest' {_ltmrEnabled = Nothing}
ltmrEnabled :: Lens' LaunchTemplatesMonitoringRequest (Maybe Bool)
ltmrEnabled = lens _ltmrEnabled (\ s a -> s{_ltmrEnabled = a})
instance Hashable LaunchTemplatesMonitoringRequest
where
instance NFData LaunchTemplatesMonitoringRequest
where
instance ToQuery LaunchTemplatesMonitoringRequest
where
toQuery LaunchTemplatesMonitoringRequest'{..}
= mconcat ["Enabled" =: _ltmrEnabled]
data LoadBalancersConfig = LoadBalancersConfig'
{ _lbcClassicLoadBalancersConfig :: !(Maybe ClassicLoadBalancersConfig)
, _lbcTargetGroupsConfig :: !(Maybe TargetGroupsConfig)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
loadBalancersConfig
:: LoadBalancersConfig
loadBalancersConfig =
LoadBalancersConfig'
{_lbcClassicLoadBalancersConfig = Nothing, _lbcTargetGroupsConfig = Nothing}
lbcClassicLoadBalancersConfig :: Lens' LoadBalancersConfig (Maybe ClassicLoadBalancersConfig)
lbcClassicLoadBalancersConfig = lens _lbcClassicLoadBalancersConfig (\ s a -> s{_lbcClassicLoadBalancersConfig = a})
lbcTargetGroupsConfig :: Lens' LoadBalancersConfig (Maybe TargetGroupsConfig)
lbcTargetGroupsConfig = lens _lbcTargetGroupsConfig (\ s a -> s{_lbcTargetGroupsConfig = a})
instance FromXML LoadBalancersConfig where
parseXML x
= LoadBalancersConfig' <$>
(x .@? "classicLoadBalancersConfig") <*>
(x .@? "targetGroupsConfig")
instance Hashable LoadBalancersConfig where
instance NFData LoadBalancersConfig where
instance ToQuery LoadBalancersConfig where
toQuery LoadBalancersConfig'{..}
= mconcat
["ClassicLoadBalancersConfig" =:
_lbcClassicLoadBalancersConfig,
"TargetGroupsConfig" =: _lbcTargetGroupsConfig]
data LoadPermission = LoadPermission'
{ _lpGroup :: !(Maybe PermissionGroup)
, _lpUserId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
loadPermission
:: LoadPermission
loadPermission = LoadPermission' {_lpGroup = Nothing, _lpUserId = Nothing}
lpGroup :: Lens' LoadPermission (Maybe PermissionGroup)
lpGroup = lens _lpGroup (\ s a -> s{_lpGroup = a})
lpUserId :: Lens' LoadPermission (Maybe Text)
lpUserId = lens _lpUserId (\ s a -> s{_lpUserId = a})
instance FromXML LoadPermission where
parseXML x
= LoadPermission' <$>
(x .@? "group") <*> (x .@? "userId")
instance Hashable LoadPermission where
instance NFData LoadPermission where
data LoadPermissionModifications = LoadPermissionModifications'
{ _lpmRemove :: !(Maybe [LoadPermissionRequest])
, _lpmAdd :: !(Maybe [LoadPermissionRequest])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
loadPermissionModifications
:: LoadPermissionModifications
loadPermissionModifications =
LoadPermissionModifications' {_lpmRemove = Nothing, _lpmAdd = Nothing}
lpmRemove :: Lens' LoadPermissionModifications [LoadPermissionRequest]
lpmRemove = lens _lpmRemove (\ s a -> s{_lpmRemove = a}) . _Default . _Coerce
lpmAdd :: Lens' LoadPermissionModifications [LoadPermissionRequest]
lpmAdd = lens _lpmAdd (\ s a -> s{_lpmAdd = a}) . _Default . _Coerce
instance Hashable LoadPermissionModifications where
instance NFData LoadPermissionModifications where
instance ToQuery LoadPermissionModifications where
toQuery LoadPermissionModifications'{..}
= mconcat
[toQuery (toQueryList "Remove" <$> _lpmRemove),
toQuery (toQueryList "Add" <$> _lpmAdd)]
data LoadPermissionRequest = LoadPermissionRequest'
{ _lprGroup :: !(Maybe PermissionGroup)
, _lprUserId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
loadPermissionRequest
:: LoadPermissionRequest
loadPermissionRequest =
LoadPermissionRequest' {_lprGroup = Nothing, _lprUserId = Nothing}
lprGroup :: Lens' LoadPermissionRequest (Maybe PermissionGroup)
lprGroup = lens _lprGroup (\ s a -> s{_lprGroup = a})
lprUserId :: Lens' LoadPermissionRequest (Maybe Text)
lprUserId = lens _lprUserId (\ s a -> s{_lprUserId = a})
instance Hashable LoadPermissionRequest where
instance NFData LoadPermissionRequest where
instance ToQuery LoadPermissionRequest where
toQuery LoadPermissionRequest'{..}
= mconcat
["Group" =: _lprGroup, "UserId" =: _lprUserId]
newtype Monitoring = Monitoring'
{ _mState :: Maybe MonitoringState
} deriving (Eq, Read, Show, Data, Typeable, Generic)
monitoring
:: Monitoring
monitoring = Monitoring' {_mState = Nothing}
mState :: Lens' Monitoring (Maybe MonitoringState)
mState = lens _mState (\ s a -> s{_mState = a})
instance FromXML Monitoring where
parseXML x = Monitoring' <$> (x .@? "state")
instance Hashable Monitoring where
instance NFData Monitoring where
data MovingAddressStatus = MovingAddressStatus'
{ _masMoveStatus :: !(Maybe MoveStatus)
, _masPublicIP :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
movingAddressStatus
:: MovingAddressStatus
movingAddressStatus =
MovingAddressStatus' {_masMoveStatus = Nothing, _masPublicIP = Nothing}
masMoveStatus :: Lens' MovingAddressStatus (Maybe MoveStatus)
masMoveStatus = lens _masMoveStatus (\ s a -> s{_masMoveStatus = a})
masPublicIP :: Lens' MovingAddressStatus (Maybe Text)
masPublicIP = lens _masPublicIP (\ s a -> s{_masPublicIP = a})
instance FromXML MovingAddressStatus where
parseXML x
= MovingAddressStatus' <$>
(x .@? "moveStatus") <*> (x .@? "publicIp")
instance Hashable MovingAddressStatus where
instance NFData MovingAddressStatus where
data NatGateway = NatGateway'
{ _ngState :: !(Maybe NatGatewayState)
, _ngFailureCode :: !(Maybe Text)
, _ngVPCId :: !(Maybe Text)
, _ngFailureMessage :: !(Maybe Text)
, _ngNatGatewayId :: !(Maybe Text)
, _ngSubnetId :: !(Maybe Text)
, _ngDeleteTime :: !(Maybe ISO8601)
, _ngProvisionedBandwidth :: !(Maybe ProvisionedBandwidth)
, _ngNatGatewayAddresses :: !(Maybe [NatGatewayAddress])
, _ngCreateTime :: !(Maybe ISO8601)
, _ngTags :: !(Maybe [Tag])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
natGateway
:: NatGateway
natGateway =
NatGateway'
{ _ngState = Nothing
, _ngFailureCode = Nothing
, _ngVPCId = Nothing
, _ngFailureMessage = Nothing
, _ngNatGatewayId = Nothing
, _ngSubnetId = Nothing
, _ngDeleteTime = Nothing
, _ngProvisionedBandwidth = Nothing
, _ngNatGatewayAddresses = Nothing
, _ngCreateTime = Nothing
, _ngTags = Nothing
}
ngState :: Lens' NatGateway (Maybe NatGatewayState)
ngState = lens _ngState (\ s a -> s{_ngState = a})
ngFailureCode :: Lens' NatGateway (Maybe Text)
ngFailureCode = lens _ngFailureCode (\ s a -> s{_ngFailureCode = a})
ngVPCId :: Lens' NatGateway (Maybe Text)
ngVPCId = lens _ngVPCId (\ s a -> s{_ngVPCId = a})
ngFailureMessage :: Lens' NatGateway (Maybe Text)
ngFailureMessage = lens _ngFailureMessage (\ s a -> s{_ngFailureMessage = a})
ngNatGatewayId :: Lens' NatGateway (Maybe Text)
ngNatGatewayId = lens _ngNatGatewayId (\ s a -> s{_ngNatGatewayId = a})
ngSubnetId :: Lens' NatGateway (Maybe Text)
ngSubnetId = lens _ngSubnetId (\ s a -> s{_ngSubnetId = a})
ngDeleteTime :: Lens' NatGateway (Maybe UTCTime)
ngDeleteTime = lens _ngDeleteTime (\ s a -> s{_ngDeleteTime = a}) . mapping _Time
ngProvisionedBandwidth :: Lens' NatGateway (Maybe ProvisionedBandwidth)
ngProvisionedBandwidth = lens _ngProvisionedBandwidth (\ s a -> s{_ngProvisionedBandwidth = a})
ngNatGatewayAddresses :: Lens' NatGateway [NatGatewayAddress]
ngNatGatewayAddresses = lens _ngNatGatewayAddresses (\ s a -> s{_ngNatGatewayAddresses = a}) . _Default . _Coerce
ngCreateTime :: Lens' NatGateway (Maybe UTCTime)
ngCreateTime = lens _ngCreateTime (\ s a -> s{_ngCreateTime = a}) . mapping _Time
ngTags :: Lens' NatGateway [Tag]
ngTags = lens _ngTags (\ s a -> s{_ngTags = a}) . _Default . _Coerce
instance FromXML NatGateway where
parseXML x
= NatGateway' <$>
(x .@? "state") <*> (x .@? "failureCode") <*>
(x .@? "vpcId")
<*> (x .@? "failureMessage")
<*> (x .@? "natGatewayId")
<*> (x .@? "subnetId")
<*> (x .@? "deleteTime")
<*> (x .@? "provisionedBandwidth")
<*>
(x .@? "natGatewayAddressSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "createTime")
<*>
(x .@? "tagSet" .!@ mempty >>=
may (parseXMLList "item"))
instance Hashable NatGateway where
instance NFData NatGateway where
data NatGatewayAddress = NatGatewayAddress'
{ _ngaPrivateIP :: !(Maybe Text)
, _ngaAllocationId :: !(Maybe Text)
, _ngaNetworkInterfaceId :: !(Maybe Text)
, _ngaPublicIP :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
natGatewayAddress
:: NatGatewayAddress
natGatewayAddress =
NatGatewayAddress'
{ _ngaPrivateIP = Nothing
, _ngaAllocationId = Nothing
, _ngaNetworkInterfaceId = Nothing
, _ngaPublicIP = Nothing
}
ngaPrivateIP :: Lens' NatGatewayAddress (Maybe Text)
ngaPrivateIP = lens _ngaPrivateIP (\ s a -> s{_ngaPrivateIP = a})
ngaAllocationId :: Lens' NatGatewayAddress (Maybe Text)
ngaAllocationId = lens _ngaAllocationId (\ s a -> s{_ngaAllocationId = a})
ngaNetworkInterfaceId :: Lens' NatGatewayAddress (Maybe Text)
ngaNetworkInterfaceId = lens _ngaNetworkInterfaceId (\ s a -> s{_ngaNetworkInterfaceId = a})
ngaPublicIP :: Lens' NatGatewayAddress (Maybe Text)
ngaPublicIP = lens _ngaPublicIP (\ s a -> s{_ngaPublicIP = a})
instance FromXML NatGatewayAddress where
parseXML x
= NatGatewayAddress' <$>
(x .@? "privateIp") <*> (x .@? "allocationId") <*>
(x .@? "networkInterfaceId")
<*> (x .@? "publicIp")
instance Hashable NatGatewayAddress where
instance NFData NatGatewayAddress where
data NetworkACL = NetworkACL'
{ _naEntries :: !(Maybe [NetworkACLEntry])
, _naNetworkACLId :: !(Maybe Text)
, _naVPCId :: !(Maybe Text)
, _naAssociations :: !(Maybe [NetworkACLAssociation])
, _naTags :: !(Maybe [Tag])
, _naIsDefault :: !(Maybe Bool)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
networkACL
:: NetworkACL
networkACL =
NetworkACL'
{ _naEntries = Nothing
, _naNetworkACLId = Nothing
, _naVPCId = Nothing
, _naAssociations = Nothing
, _naTags = Nothing
, _naIsDefault = Nothing
}
naEntries :: Lens' NetworkACL [NetworkACLEntry]
naEntries = lens _naEntries (\ s a -> s{_naEntries = a}) . _Default . _Coerce
naNetworkACLId :: Lens' NetworkACL (Maybe Text)
naNetworkACLId = lens _naNetworkACLId (\ s a -> s{_naNetworkACLId = a})
naVPCId :: Lens' NetworkACL (Maybe Text)
naVPCId = lens _naVPCId (\ s a -> s{_naVPCId = a})
naAssociations :: Lens' NetworkACL [NetworkACLAssociation]
naAssociations = lens _naAssociations (\ s a -> s{_naAssociations = a}) . _Default . _Coerce
naTags :: Lens' NetworkACL [Tag]
naTags = lens _naTags (\ s a -> s{_naTags = a}) . _Default . _Coerce
naIsDefault :: Lens' NetworkACL (Maybe Bool)
naIsDefault = lens _naIsDefault (\ s a -> s{_naIsDefault = a})
instance FromXML NetworkACL where
parseXML x
= NetworkACL' <$>
(x .@? "entrySet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "networkAclId")
<*> (x .@? "vpcId")
<*>
(x .@? "associationSet" .!@ mempty >>=
may (parseXMLList "item"))
<*>
(x .@? "tagSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "default")
instance Hashable NetworkACL where
instance NFData NetworkACL where
data NetworkACLAssociation = NetworkACLAssociation'
{ _naaNetworkACLId :: !(Maybe Text)
, _naaSubnetId :: !(Maybe Text)
, _naaNetworkACLAssociationId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
networkACLAssociation
:: NetworkACLAssociation
networkACLAssociation =
NetworkACLAssociation'
{ _naaNetworkACLId = Nothing
, _naaSubnetId = Nothing
, _naaNetworkACLAssociationId = Nothing
}
naaNetworkACLId :: Lens' NetworkACLAssociation (Maybe Text)
naaNetworkACLId = lens _naaNetworkACLId (\ s a -> s{_naaNetworkACLId = a})
naaSubnetId :: Lens' NetworkACLAssociation (Maybe Text)
naaSubnetId = lens _naaSubnetId (\ s a -> s{_naaSubnetId = a})
naaNetworkACLAssociationId :: Lens' NetworkACLAssociation (Maybe Text)
naaNetworkACLAssociationId = lens _naaNetworkACLAssociationId (\ s a -> s{_naaNetworkACLAssociationId = a})
instance FromXML NetworkACLAssociation where
parseXML x
= NetworkACLAssociation' <$>
(x .@? "networkAclId") <*> (x .@? "subnetId") <*>
(x .@? "networkAclAssociationId")
instance Hashable NetworkACLAssociation where
instance NFData NetworkACLAssociation where
data NetworkACLEntry = NetworkACLEntry'
{ _naeIPv6CidrBlock :: !(Maybe Text)
, _naeICMPTypeCode :: !(Maybe ICMPTypeCode)
, _naeRuleNumber :: !(Maybe Int)
, _naeRuleAction :: !(Maybe RuleAction)
, _naeProtocol :: !(Maybe Text)
, _naePortRange :: !(Maybe PortRange)
, _naeCidrBlock :: !(Maybe Text)
, _naeEgress :: !(Maybe Bool)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
networkACLEntry
:: NetworkACLEntry
networkACLEntry =
NetworkACLEntry'
{ _naeIPv6CidrBlock = Nothing
, _naeICMPTypeCode = Nothing
, _naeRuleNumber = Nothing
, _naeRuleAction = Nothing
, _naeProtocol = Nothing
, _naePortRange = Nothing
, _naeCidrBlock = Nothing
, _naeEgress = Nothing
}
naeIPv6CidrBlock :: Lens' NetworkACLEntry (Maybe Text)
naeIPv6CidrBlock = lens _naeIPv6CidrBlock (\ s a -> s{_naeIPv6CidrBlock = a})
naeICMPTypeCode :: Lens' NetworkACLEntry (Maybe ICMPTypeCode)
naeICMPTypeCode = lens _naeICMPTypeCode (\ s a -> s{_naeICMPTypeCode = a})
naeRuleNumber :: Lens' NetworkACLEntry (Maybe Int)
naeRuleNumber = lens _naeRuleNumber (\ s a -> s{_naeRuleNumber = a})
naeRuleAction :: Lens' NetworkACLEntry (Maybe RuleAction)
naeRuleAction = lens _naeRuleAction (\ s a -> s{_naeRuleAction = a})
naeProtocol :: Lens' NetworkACLEntry (Maybe Text)
naeProtocol = lens _naeProtocol (\ s a -> s{_naeProtocol = a})
naePortRange :: Lens' NetworkACLEntry (Maybe PortRange)
naePortRange = lens _naePortRange (\ s a -> s{_naePortRange = a})
naeCidrBlock :: Lens' NetworkACLEntry (Maybe Text)
naeCidrBlock = lens _naeCidrBlock (\ s a -> s{_naeCidrBlock = a})
naeEgress :: Lens' NetworkACLEntry (Maybe Bool)
naeEgress = lens _naeEgress (\ s a -> s{_naeEgress = a})
instance FromXML NetworkACLEntry where
parseXML x
= NetworkACLEntry' <$>
(x .@? "ipv6CidrBlock") <*> (x .@? "icmpTypeCode")
<*> (x .@? "ruleNumber")
<*> (x .@? "ruleAction")
<*> (x .@? "protocol")
<*> (x .@? "portRange")
<*> (x .@? "cidrBlock")
<*> (x .@? "egress")
instance Hashable NetworkACLEntry where
instance NFData NetworkACLEntry where
data NetworkInterface = NetworkInterface'
{ _niGroups :: !(Maybe [GroupIdentifier])
, _niStatus :: !(Maybe NetworkInterfaceStatus)
, _niPrivateIPAddresses :: !(Maybe [NetworkInterfacePrivateIPAddress])
, _niSourceDestCheck :: !(Maybe Bool)
, _niInterfaceType :: !(Maybe NetworkInterfaceType)
, _niVPCId :: !(Maybe Text)
, _niTagSet :: !(Maybe [Tag])
, _niRequesterManaged :: !(Maybe Bool)
, _niNetworkInterfaceId :: !(Maybe Text)
, _niSubnetId :: !(Maybe Text)
, _niMACAddress :: !(Maybe Text)
, _niAttachment :: !(Maybe NetworkInterfaceAttachment)
, _niOwnerId :: !(Maybe Text)
, _niAvailabilityZone :: !(Maybe Text)
, _niPrivateIPAddress :: !(Maybe Text)
, _niPrivateDNSName :: !(Maybe Text)
, _niRequesterId :: !(Maybe Text)
, _niDescription :: !(Maybe Text)
, _niAssociation :: !(Maybe NetworkInterfaceAssociation)
, _niIPv6Addresses :: !(Maybe [NetworkInterfaceIPv6Address])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
networkInterface
:: NetworkInterface
networkInterface =
NetworkInterface'
{ _niGroups = Nothing
, _niStatus = Nothing
, _niPrivateIPAddresses = Nothing
, _niSourceDestCheck = Nothing
, _niInterfaceType = Nothing
, _niVPCId = Nothing
, _niTagSet = Nothing
, _niRequesterManaged = Nothing
, _niNetworkInterfaceId = Nothing
, _niSubnetId = Nothing
, _niMACAddress = Nothing
, _niAttachment = Nothing
, _niOwnerId = Nothing
, _niAvailabilityZone = Nothing
, _niPrivateIPAddress = Nothing
, _niPrivateDNSName = Nothing
, _niRequesterId = Nothing
, _niDescription = Nothing
, _niAssociation = Nothing
, _niIPv6Addresses = Nothing
}
niGroups :: Lens' NetworkInterface [GroupIdentifier]
niGroups = lens _niGroups (\ s a -> s{_niGroups = a}) . _Default . _Coerce
niStatus :: Lens' NetworkInterface (Maybe NetworkInterfaceStatus)
niStatus = lens _niStatus (\ s a -> s{_niStatus = a})
niPrivateIPAddresses :: Lens' NetworkInterface [NetworkInterfacePrivateIPAddress]
niPrivateIPAddresses = lens _niPrivateIPAddresses (\ s a -> s{_niPrivateIPAddresses = a}) . _Default . _Coerce
niSourceDestCheck :: Lens' NetworkInterface (Maybe Bool)
niSourceDestCheck = lens _niSourceDestCheck (\ s a -> s{_niSourceDestCheck = a})
niInterfaceType :: Lens' NetworkInterface (Maybe NetworkInterfaceType)
niInterfaceType = lens _niInterfaceType (\ s a -> s{_niInterfaceType = a})
niVPCId :: Lens' NetworkInterface (Maybe Text)
niVPCId = lens _niVPCId (\ s a -> s{_niVPCId = a})
niTagSet :: Lens' NetworkInterface [Tag]
niTagSet = lens _niTagSet (\ s a -> s{_niTagSet = a}) . _Default . _Coerce
niRequesterManaged :: Lens' NetworkInterface (Maybe Bool)
niRequesterManaged = lens _niRequesterManaged (\ s a -> s{_niRequesterManaged = a})
niNetworkInterfaceId :: Lens' NetworkInterface (Maybe Text)
niNetworkInterfaceId = lens _niNetworkInterfaceId (\ s a -> s{_niNetworkInterfaceId = a})
niSubnetId :: Lens' NetworkInterface (Maybe Text)
niSubnetId = lens _niSubnetId (\ s a -> s{_niSubnetId = a})
niMACAddress :: Lens' NetworkInterface (Maybe Text)
niMACAddress = lens _niMACAddress (\ s a -> s{_niMACAddress = a})
niAttachment :: Lens' NetworkInterface (Maybe NetworkInterfaceAttachment)
niAttachment = lens _niAttachment (\ s a -> s{_niAttachment = a})
niOwnerId :: Lens' NetworkInterface (Maybe Text)
niOwnerId = lens _niOwnerId (\ s a -> s{_niOwnerId = a})
niAvailabilityZone :: Lens' NetworkInterface (Maybe Text)
niAvailabilityZone = lens _niAvailabilityZone (\ s a -> s{_niAvailabilityZone = a})
niPrivateIPAddress :: Lens' NetworkInterface (Maybe Text)
niPrivateIPAddress = lens _niPrivateIPAddress (\ s a -> s{_niPrivateIPAddress = a})
niPrivateDNSName :: Lens' NetworkInterface (Maybe Text)
niPrivateDNSName = lens _niPrivateDNSName (\ s a -> s{_niPrivateDNSName = a})
niRequesterId :: Lens' NetworkInterface (Maybe Text)
niRequesterId = lens _niRequesterId (\ s a -> s{_niRequesterId = a})
niDescription :: Lens' NetworkInterface (Maybe Text)
niDescription = lens _niDescription (\ s a -> s{_niDescription = a})
niAssociation :: Lens' NetworkInterface (Maybe NetworkInterfaceAssociation)
niAssociation = lens _niAssociation (\ s a -> s{_niAssociation = a})
niIPv6Addresses :: Lens' NetworkInterface [NetworkInterfaceIPv6Address]
niIPv6Addresses = lens _niIPv6Addresses (\ s a -> s{_niIPv6Addresses = a}) . _Default . _Coerce
instance FromXML NetworkInterface where
parseXML x
= NetworkInterface' <$>
(x .@? "groupSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "status")
<*>
(x .@? "privateIpAddressesSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "sourceDestCheck")
<*> (x .@? "interfaceType")
<*> (x .@? "vpcId")
<*>
(x .@? "tagSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "requesterManaged")
<*> (x .@? "networkInterfaceId")
<*> (x .@? "subnetId")
<*> (x .@? "macAddress")
<*> (x .@? "attachment")
<*> (x .@? "ownerId")
<*> (x .@? "availabilityZone")
<*> (x .@? "privateIpAddress")
<*> (x .@? "privateDnsName")
<*> (x .@? "requesterId")
<*> (x .@? "description")
<*> (x .@? "association")
<*>
(x .@? "ipv6AddressesSet" .!@ mempty >>=
may (parseXMLList "item"))
instance Hashable NetworkInterface where
instance NFData NetworkInterface where
data NetworkInterfaceAssociation = NetworkInterfaceAssociation'
{ _niaAssociationId :: !(Maybe Text)
, _niaPublicDNSName :: !(Maybe Text)
, _niaAllocationId :: !(Maybe Text)
, _niaIPOwnerId :: !(Maybe Text)
, _niaPublicIP :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
networkInterfaceAssociation
:: NetworkInterfaceAssociation
networkInterfaceAssociation =
NetworkInterfaceAssociation'
{ _niaAssociationId = Nothing
, _niaPublicDNSName = Nothing
, _niaAllocationId = Nothing
, _niaIPOwnerId = Nothing
, _niaPublicIP = Nothing
}
niaAssociationId :: Lens' NetworkInterfaceAssociation (Maybe Text)
niaAssociationId = lens _niaAssociationId (\ s a -> s{_niaAssociationId = a})
niaPublicDNSName :: Lens' NetworkInterfaceAssociation (Maybe Text)
niaPublicDNSName = lens _niaPublicDNSName (\ s a -> s{_niaPublicDNSName = a})
niaAllocationId :: Lens' NetworkInterfaceAssociation (Maybe Text)
niaAllocationId = lens _niaAllocationId (\ s a -> s{_niaAllocationId = a})
niaIPOwnerId :: Lens' NetworkInterfaceAssociation (Maybe Text)
niaIPOwnerId = lens _niaIPOwnerId (\ s a -> s{_niaIPOwnerId = a})
niaPublicIP :: Lens' NetworkInterfaceAssociation (Maybe Text)
niaPublicIP = lens _niaPublicIP (\ s a -> s{_niaPublicIP = a})
instance FromXML NetworkInterfaceAssociation where
parseXML x
= NetworkInterfaceAssociation' <$>
(x .@? "associationId") <*> (x .@? "publicDnsName")
<*> (x .@? "allocationId")
<*> (x .@? "ipOwnerId")
<*> (x .@? "publicIp")
instance Hashable NetworkInterfaceAssociation where
instance NFData NetworkInterfaceAssociation where
data NetworkInterfaceAttachment = NetworkInterfaceAttachment'
{ _niaInstanceId :: !(Maybe Text)
, _niaStatus :: !(Maybe AttachmentStatus)
, _niaDeleteOnTermination :: !(Maybe Bool)
, _niaAttachmentId :: !(Maybe Text)
, _niaInstanceOwnerId :: !(Maybe Text)
, _niaAttachTime :: !(Maybe ISO8601)
, _niaDeviceIndex :: !(Maybe Int)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
networkInterfaceAttachment
:: NetworkInterfaceAttachment
networkInterfaceAttachment =
NetworkInterfaceAttachment'
{ _niaInstanceId = Nothing
, _niaStatus = Nothing
, _niaDeleteOnTermination = Nothing
, _niaAttachmentId = Nothing
, _niaInstanceOwnerId = Nothing
, _niaAttachTime = Nothing
, _niaDeviceIndex = Nothing
}
niaInstanceId :: Lens' NetworkInterfaceAttachment (Maybe Text)
niaInstanceId = lens _niaInstanceId (\ s a -> s{_niaInstanceId = a})
niaStatus :: Lens' NetworkInterfaceAttachment (Maybe AttachmentStatus)
niaStatus = lens _niaStatus (\ s a -> s{_niaStatus = a})
niaDeleteOnTermination :: Lens' NetworkInterfaceAttachment (Maybe Bool)
niaDeleteOnTermination = lens _niaDeleteOnTermination (\ s a -> s{_niaDeleteOnTermination = a})
niaAttachmentId :: Lens' NetworkInterfaceAttachment (Maybe Text)
niaAttachmentId = lens _niaAttachmentId (\ s a -> s{_niaAttachmentId = a})
niaInstanceOwnerId :: Lens' NetworkInterfaceAttachment (Maybe Text)
niaInstanceOwnerId = lens _niaInstanceOwnerId (\ s a -> s{_niaInstanceOwnerId = a})
niaAttachTime :: Lens' NetworkInterfaceAttachment (Maybe UTCTime)
niaAttachTime = lens _niaAttachTime (\ s a -> s{_niaAttachTime = a}) . mapping _Time
niaDeviceIndex :: Lens' NetworkInterfaceAttachment (Maybe Int)
niaDeviceIndex = lens _niaDeviceIndex (\ s a -> s{_niaDeviceIndex = a})
instance FromXML NetworkInterfaceAttachment where
parseXML x
= NetworkInterfaceAttachment' <$>
(x .@? "instanceId") <*> (x .@? "status") <*>
(x .@? "deleteOnTermination")
<*> (x .@? "attachmentId")
<*> (x .@? "instanceOwnerId")
<*> (x .@? "attachTime")
<*> (x .@? "deviceIndex")
instance Hashable NetworkInterfaceAttachment where
instance NFData NetworkInterfaceAttachment where
data NetworkInterfaceAttachmentChanges = NetworkInterfaceAttachmentChanges'
{ _niacDeleteOnTermination :: !(Maybe Bool)
, _niacAttachmentId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
networkInterfaceAttachmentChanges
:: NetworkInterfaceAttachmentChanges
networkInterfaceAttachmentChanges =
NetworkInterfaceAttachmentChanges'
{_niacDeleteOnTermination = Nothing, _niacAttachmentId = Nothing}
niacDeleteOnTermination :: Lens' NetworkInterfaceAttachmentChanges (Maybe Bool)
niacDeleteOnTermination = lens _niacDeleteOnTermination (\ s a -> s{_niacDeleteOnTermination = a})
niacAttachmentId :: Lens' NetworkInterfaceAttachmentChanges (Maybe Text)
niacAttachmentId = lens _niacAttachmentId (\ s a -> s{_niacAttachmentId = a})
instance Hashable NetworkInterfaceAttachmentChanges
where
instance NFData NetworkInterfaceAttachmentChanges
where
instance ToQuery NetworkInterfaceAttachmentChanges
where
toQuery NetworkInterfaceAttachmentChanges'{..}
= mconcat
["DeleteOnTermination" =: _niacDeleteOnTermination,
"AttachmentId" =: _niacAttachmentId]
newtype NetworkInterfaceIPv6Address = NetworkInterfaceIPv6Address'
{ _niiaIPv6Address :: Maybe Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
networkInterfaceIPv6Address
:: NetworkInterfaceIPv6Address
networkInterfaceIPv6Address =
NetworkInterfaceIPv6Address' {_niiaIPv6Address = Nothing}
niiaIPv6Address :: Lens' NetworkInterfaceIPv6Address (Maybe Text)
niiaIPv6Address = lens _niiaIPv6Address (\ s a -> s{_niiaIPv6Address = a})
instance FromXML NetworkInterfaceIPv6Address where
parseXML x
= NetworkInterfaceIPv6Address' <$>
(x .@? "ipv6Address")
instance Hashable NetworkInterfaceIPv6Address where
instance NFData NetworkInterfaceIPv6Address where
data NetworkInterfacePermission = NetworkInterfacePermission'
{ _nipPermissionState :: !(Maybe NetworkInterfacePermissionState)
, _nipNetworkInterfacePermissionId :: !(Maybe Text)
, _nipNetworkInterfaceId :: !(Maybe Text)
, _nipAWSAccountId :: !(Maybe Text)
, _nipAWSService :: !(Maybe Text)
, _nipPermission :: !(Maybe InterfacePermissionType)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
networkInterfacePermission
:: NetworkInterfacePermission
networkInterfacePermission =
NetworkInterfacePermission'
{ _nipPermissionState = Nothing
, _nipNetworkInterfacePermissionId = Nothing
, _nipNetworkInterfaceId = Nothing
, _nipAWSAccountId = Nothing
, _nipAWSService = Nothing
, _nipPermission = Nothing
}
nipPermissionState :: Lens' NetworkInterfacePermission (Maybe NetworkInterfacePermissionState)
nipPermissionState = lens _nipPermissionState (\ s a -> s{_nipPermissionState = a})
nipNetworkInterfacePermissionId :: Lens' NetworkInterfacePermission (Maybe Text)
nipNetworkInterfacePermissionId = lens _nipNetworkInterfacePermissionId (\ s a -> s{_nipNetworkInterfacePermissionId = a})
nipNetworkInterfaceId :: Lens' NetworkInterfacePermission (Maybe Text)
nipNetworkInterfaceId = lens _nipNetworkInterfaceId (\ s a -> s{_nipNetworkInterfaceId = a})
nipAWSAccountId :: Lens' NetworkInterfacePermission (Maybe Text)
nipAWSAccountId = lens _nipAWSAccountId (\ s a -> s{_nipAWSAccountId = a})
nipAWSService :: Lens' NetworkInterfacePermission (Maybe Text)
nipAWSService = lens _nipAWSService (\ s a -> s{_nipAWSService = a})
nipPermission :: Lens' NetworkInterfacePermission (Maybe InterfacePermissionType)
nipPermission = lens _nipPermission (\ s a -> s{_nipPermission = a})
instance FromXML NetworkInterfacePermission where
parseXML x
= NetworkInterfacePermission' <$>
(x .@? "permissionState") <*>
(x .@? "networkInterfacePermissionId")
<*> (x .@? "networkInterfaceId")
<*> (x .@? "awsAccountId")
<*> (x .@? "awsService")
<*> (x .@? "permission")
instance Hashable NetworkInterfacePermission where
instance NFData NetworkInterfacePermission where
data NetworkInterfacePermissionState = NetworkInterfacePermissionState'
{ _nipsState :: !(Maybe NetworkInterfacePermissionStateCode)
, _nipsStatusMessage :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
networkInterfacePermissionState
:: NetworkInterfacePermissionState
networkInterfacePermissionState =
NetworkInterfacePermissionState'
{_nipsState = Nothing, _nipsStatusMessage = Nothing}
nipsState :: Lens' NetworkInterfacePermissionState (Maybe NetworkInterfacePermissionStateCode)
nipsState = lens _nipsState (\ s a -> s{_nipsState = a})
nipsStatusMessage :: Lens' NetworkInterfacePermissionState (Maybe Text)
nipsStatusMessage = lens _nipsStatusMessage (\ s a -> s{_nipsStatusMessage = a})
instance FromXML NetworkInterfacePermissionState
where
parseXML x
= NetworkInterfacePermissionState' <$>
(x .@? "state") <*> (x .@? "statusMessage")
instance Hashable NetworkInterfacePermissionState
where
instance NFData NetworkInterfacePermissionState where
data NetworkInterfacePrivateIPAddress = NetworkInterfacePrivateIPAddress'
{ _nipiaPrimary :: !(Maybe Bool)
, _nipiaPrivateIPAddress :: !(Maybe Text)
, _nipiaPrivateDNSName :: !(Maybe Text)
, _nipiaAssociation :: !(Maybe NetworkInterfaceAssociation)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
networkInterfacePrivateIPAddress
:: NetworkInterfacePrivateIPAddress
networkInterfacePrivateIPAddress =
NetworkInterfacePrivateIPAddress'
{ _nipiaPrimary = Nothing
, _nipiaPrivateIPAddress = Nothing
, _nipiaPrivateDNSName = Nothing
, _nipiaAssociation = Nothing
}
nipiaPrimary :: Lens' NetworkInterfacePrivateIPAddress (Maybe Bool)
nipiaPrimary = lens _nipiaPrimary (\ s a -> s{_nipiaPrimary = a})
nipiaPrivateIPAddress :: Lens' NetworkInterfacePrivateIPAddress (Maybe Text)
nipiaPrivateIPAddress = lens _nipiaPrivateIPAddress (\ s a -> s{_nipiaPrivateIPAddress = a})
nipiaPrivateDNSName :: Lens' NetworkInterfacePrivateIPAddress (Maybe Text)
nipiaPrivateDNSName = lens _nipiaPrivateDNSName (\ s a -> s{_nipiaPrivateDNSName = a})
nipiaAssociation :: Lens' NetworkInterfacePrivateIPAddress (Maybe NetworkInterfaceAssociation)
nipiaAssociation = lens _nipiaAssociation (\ s a -> s{_nipiaAssociation = a})
instance FromXML NetworkInterfacePrivateIPAddress
where
parseXML x
= NetworkInterfacePrivateIPAddress' <$>
(x .@? "primary") <*> (x .@? "privateIpAddress") <*>
(x .@? "privateDnsName")
<*> (x .@? "association")
instance Hashable NetworkInterfacePrivateIPAddress
where
instance NFData NetworkInterfacePrivateIPAddress
where
data NewDHCPConfiguration = NewDHCPConfiguration'
{ _ndcValues :: !(Maybe [Text])
, _ndcKey :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
newDHCPConfiguration
:: NewDHCPConfiguration
newDHCPConfiguration =
NewDHCPConfiguration' {_ndcValues = Nothing, _ndcKey = Nothing}
ndcValues :: Lens' NewDHCPConfiguration [Text]
ndcValues = lens _ndcValues (\ s a -> s{_ndcValues = a}) . _Default . _Coerce
ndcKey :: Lens' NewDHCPConfiguration (Maybe Text)
ndcKey = lens _ndcKey (\ s a -> s{_ndcKey = a})
instance Hashable NewDHCPConfiguration where
instance NFData NewDHCPConfiguration where
instance ToQuery NewDHCPConfiguration where
toQuery NewDHCPConfiguration'{..}
= mconcat
[toQuery (toQueryList "Value" <$> _ndcValues),
"Key" =: _ndcKey]
data PciId = PciId'
{ _piSubsystemId :: !(Maybe Text)
, _piDeviceId :: !(Maybe Text)
, _piSubsystemVendorId :: !(Maybe Text)
, _piVendorId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
pciId
:: PciId
pciId =
PciId'
{ _piSubsystemId = Nothing
, _piDeviceId = Nothing
, _piSubsystemVendorId = Nothing
, _piVendorId = Nothing
}
piSubsystemId :: Lens' PciId (Maybe Text)
piSubsystemId = lens _piSubsystemId (\ s a -> s{_piSubsystemId = a})
piDeviceId :: Lens' PciId (Maybe Text)
piDeviceId = lens _piDeviceId (\ s a -> s{_piDeviceId = a})
piSubsystemVendorId :: Lens' PciId (Maybe Text)
piSubsystemVendorId = lens _piSubsystemVendorId (\ s a -> s{_piSubsystemVendorId = a})
piVendorId :: Lens' PciId (Maybe Text)
piVendorId = lens _piVendorId (\ s a -> s{_piVendorId = a})
instance FromXML PciId where
parseXML x
= PciId' <$>
(x .@? "SubsystemId") <*> (x .@? "DeviceId") <*>
(x .@? "SubsystemVendorId")
<*> (x .@? "VendorId")
instance Hashable PciId where
instance NFData PciId where
data PeeringConnectionOptions = PeeringConnectionOptions'
{ _pcoAllowEgressFromLocalVPCToRemoteClassicLink :: !(Maybe Bool)
, _pcoAllowEgressFromLocalClassicLinkToRemoteVPC :: !(Maybe Bool)
, _pcoAllowDNSResolutionFromRemoteVPC :: !(Maybe Bool)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
peeringConnectionOptions
:: PeeringConnectionOptions
peeringConnectionOptions =
PeeringConnectionOptions'
{ _pcoAllowEgressFromLocalVPCToRemoteClassicLink = Nothing
, _pcoAllowEgressFromLocalClassicLinkToRemoteVPC = Nothing
, _pcoAllowDNSResolutionFromRemoteVPC = Nothing
}
pcoAllowEgressFromLocalVPCToRemoteClassicLink :: Lens' PeeringConnectionOptions (Maybe Bool)
pcoAllowEgressFromLocalVPCToRemoteClassicLink = lens _pcoAllowEgressFromLocalVPCToRemoteClassicLink (\ s a -> s{_pcoAllowEgressFromLocalVPCToRemoteClassicLink = a})
pcoAllowEgressFromLocalClassicLinkToRemoteVPC :: Lens' PeeringConnectionOptions (Maybe Bool)
pcoAllowEgressFromLocalClassicLinkToRemoteVPC = lens _pcoAllowEgressFromLocalClassicLinkToRemoteVPC (\ s a -> s{_pcoAllowEgressFromLocalClassicLinkToRemoteVPC = a})
pcoAllowDNSResolutionFromRemoteVPC :: Lens' PeeringConnectionOptions (Maybe Bool)
pcoAllowDNSResolutionFromRemoteVPC = lens _pcoAllowDNSResolutionFromRemoteVPC (\ s a -> s{_pcoAllowDNSResolutionFromRemoteVPC = a})
instance FromXML PeeringConnectionOptions where
parseXML x
= PeeringConnectionOptions' <$>
(x .@? "allowEgressFromLocalVpcToRemoteClassicLink")
<*>
(x .@? "allowEgressFromLocalClassicLinkToRemoteVpc")
<*> (x .@? "allowDnsResolutionFromRemoteVpc")
instance Hashable PeeringConnectionOptions where
instance NFData PeeringConnectionOptions where
data PeeringConnectionOptionsRequest = PeeringConnectionOptionsRequest'
{ _pcorAllowEgressFromLocalVPCToRemoteClassicLink :: !(Maybe Bool)
, _pcorAllowEgressFromLocalClassicLinkToRemoteVPC :: !(Maybe Bool)
, _pcorAllowDNSResolutionFromRemoteVPC :: !(Maybe Bool)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
peeringConnectionOptionsRequest
:: PeeringConnectionOptionsRequest
peeringConnectionOptionsRequest =
PeeringConnectionOptionsRequest'
{ _pcorAllowEgressFromLocalVPCToRemoteClassicLink = Nothing
, _pcorAllowEgressFromLocalClassicLinkToRemoteVPC = Nothing
, _pcorAllowDNSResolutionFromRemoteVPC = Nothing
}
pcorAllowEgressFromLocalVPCToRemoteClassicLink :: Lens' PeeringConnectionOptionsRequest (Maybe Bool)
pcorAllowEgressFromLocalVPCToRemoteClassicLink = lens _pcorAllowEgressFromLocalVPCToRemoteClassicLink (\ s a -> s{_pcorAllowEgressFromLocalVPCToRemoteClassicLink = a})
pcorAllowEgressFromLocalClassicLinkToRemoteVPC :: Lens' PeeringConnectionOptionsRequest (Maybe Bool)
pcorAllowEgressFromLocalClassicLinkToRemoteVPC = lens _pcorAllowEgressFromLocalClassicLinkToRemoteVPC (\ s a -> s{_pcorAllowEgressFromLocalClassicLinkToRemoteVPC = a})
pcorAllowDNSResolutionFromRemoteVPC :: Lens' PeeringConnectionOptionsRequest (Maybe Bool)
pcorAllowDNSResolutionFromRemoteVPC = lens _pcorAllowDNSResolutionFromRemoteVPC (\ s a -> s{_pcorAllowDNSResolutionFromRemoteVPC = a})
instance Hashable PeeringConnectionOptionsRequest
where
instance NFData PeeringConnectionOptionsRequest where
instance ToQuery PeeringConnectionOptionsRequest
where
toQuery PeeringConnectionOptionsRequest'{..}
= mconcat
["AllowEgressFromLocalVpcToRemoteClassicLink" =:
_pcorAllowEgressFromLocalVPCToRemoteClassicLink,
"AllowEgressFromLocalClassicLinkToRemoteVpc" =:
_pcorAllowEgressFromLocalClassicLinkToRemoteVPC,
"AllowDnsResolutionFromRemoteVpc" =:
_pcorAllowDNSResolutionFromRemoteVPC]
data Placement = Placement'
{ _pAffinity :: !(Maybe Text)
, _pHostId :: !(Maybe Text)
, _pSpreadDomain :: !(Maybe Text)
, _pAvailabilityZone :: !(Maybe Text)
, _pTenancy :: !(Maybe Tenancy)
, _pGroupName :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
placement
:: Placement
placement =
Placement'
{ _pAffinity = Nothing
, _pHostId = Nothing
, _pSpreadDomain = Nothing
, _pAvailabilityZone = Nothing
, _pTenancy = Nothing
, _pGroupName = Nothing
}
pAffinity :: Lens' Placement (Maybe Text)
pAffinity = lens _pAffinity (\ s a -> s{_pAffinity = a})
pHostId :: Lens' Placement (Maybe Text)
pHostId = lens _pHostId (\ s a -> s{_pHostId = a})
pSpreadDomain :: Lens' Placement (Maybe Text)
pSpreadDomain = lens _pSpreadDomain (\ s a -> s{_pSpreadDomain = a})
pAvailabilityZone :: Lens' Placement (Maybe Text)
pAvailabilityZone = lens _pAvailabilityZone (\ s a -> s{_pAvailabilityZone = a})
pTenancy :: Lens' Placement (Maybe Tenancy)
pTenancy = lens _pTenancy (\ s a -> s{_pTenancy = a})
pGroupName :: Lens' Placement (Maybe Text)
pGroupName = lens _pGroupName (\ s a -> s{_pGroupName = a})
instance FromXML Placement where
parseXML x
= Placement' <$>
(x .@? "affinity") <*> (x .@? "hostId") <*>
(x .@? "spreadDomain")
<*> (x .@? "availabilityZone")
<*> (x .@? "tenancy")
<*> (x .@? "groupName")
instance Hashable Placement where
instance NFData Placement where
instance ToQuery Placement where
toQuery Placement'{..}
= mconcat
["Affinity" =: _pAffinity, "HostId" =: _pHostId,
"SpreadDomain" =: _pSpreadDomain,
"AvailabilityZone" =: _pAvailabilityZone,
"Tenancy" =: _pTenancy, "GroupName" =: _pGroupName]
data PlacementGroup = PlacementGroup'
{ _pgState :: !(Maybe PlacementGroupState)
, _pgStrategy :: !(Maybe PlacementStrategy)
, _pgGroupName :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
placementGroup
:: PlacementGroup
placementGroup =
PlacementGroup'
{_pgState = Nothing, _pgStrategy = Nothing, _pgGroupName = Nothing}
pgState :: Lens' PlacementGroup (Maybe PlacementGroupState)
pgState = lens _pgState (\ s a -> s{_pgState = a})
pgStrategy :: Lens' PlacementGroup (Maybe PlacementStrategy)
pgStrategy = lens _pgStrategy (\ s a -> s{_pgStrategy = a})
pgGroupName :: Lens' PlacementGroup (Maybe Text)
pgGroupName = lens _pgGroupName (\ s a -> s{_pgGroupName = a})
instance FromXML PlacementGroup where
parseXML x
= PlacementGroup' <$>
(x .@? "state") <*> (x .@? "strategy") <*>
(x .@? "groupName")
instance Hashable PlacementGroup where
instance NFData PlacementGroup where
data PortRange = PortRange'
{ _prTo :: !(Maybe Int)
, _prFrom :: !(Maybe Int)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
portRange
:: PortRange
portRange = PortRange' {_prTo = Nothing, _prFrom = Nothing}
prTo :: Lens' PortRange (Maybe Int)
prTo = lens _prTo (\ s a -> s{_prTo = a})
prFrom :: Lens' PortRange (Maybe Int)
prFrom = lens _prFrom (\ s a -> s{_prFrom = a})
instance FromXML PortRange where
parseXML x
= PortRange' <$> (x .@? "to") <*> (x .@? "from")
instance Hashable PortRange where
instance NFData PortRange where
instance ToQuery PortRange where
toQuery PortRange'{..}
= mconcat ["To" =: _prTo, "From" =: _prFrom]
data PrefixList = PrefixList'
{ _plCidrs :: !(Maybe [Text])
, _plPrefixListId :: !(Maybe Text)
, _plPrefixListName :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
prefixList
:: PrefixList
prefixList =
PrefixList'
{_plCidrs = Nothing, _plPrefixListId = Nothing, _plPrefixListName = Nothing}
plCidrs :: Lens' PrefixList [Text]
plCidrs = lens _plCidrs (\ s a -> s{_plCidrs = a}) . _Default . _Coerce
plPrefixListId :: Lens' PrefixList (Maybe Text)
plPrefixListId = lens _plPrefixListId (\ s a -> s{_plPrefixListId = a})
plPrefixListName :: Lens' PrefixList (Maybe Text)
plPrefixListName = lens _plPrefixListName (\ s a -> s{_plPrefixListName = a})
instance FromXML PrefixList where
parseXML x
= PrefixList' <$>
(x .@? "cidrSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "prefixListId")
<*> (x .@? "prefixListName")
instance Hashable PrefixList where
instance NFData PrefixList where
data PrefixListId = PrefixListId'
{ _pliPrefixListId :: !(Maybe Text)
, _pliDescription :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
prefixListId
:: PrefixListId
prefixListId =
PrefixListId' {_pliPrefixListId = Nothing, _pliDescription = Nothing}
pliPrefixListId :: Lens' PrefixListId (Maybe Text)
pliPrefixListId = lens _pliPrefixListId (\ s a -> s{_pliPrefixListId = a})
pliDescription :: Lens' PrefixListId (Maybe Text)
pliDescription = lens _pliDescription (\ s a -> s{_pliDescription = a})
instance FromXML PrefixListId where
parseXML x
= PrefixListId' <$>
(x .@? "prefixListId") <*> (x .@? "description")
instance Hashable PrefixListId where
instance NFData PrefixListId where
instance ToQuery PrefixListId where
toQuery PrefixListId'{..}
= mconcat
["PrefixListId" =: _pliPrefixListId,
"Description" =: _pliDescription]
data PriceSchedule = PriceSchedule'
{ _psCurrencyCode :: !(Maybe CurrencyCodeValues)
, _psTerm :: !(Maybe Integer)
, _psActive :: !(Maybe Bool)
, _psPrice :: !(Maybe Double)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
priceSchedule
:: PriceSchedule
priceSchedule =
PriceSchedule'
{ _psCurrencyCode = Nothing
, _psTerm = Nothing
, _psActive = Nothing
, _psPrice = Nothing
}
psCurrencyCode :: Lens' PriceSchedule (Maybe CurrencyCodeValues)
psCurrencyCode = lens _psCurrencyCode (\ s a -> s{_psCurrencyCode = a})
psTerm :: Lens' PriceSchedule (Maybe Integer)
psTerm = lens _psTerm (\ s a -> s{_psTerm = a})
psActive :: Lens' PriceSchedule (Maybe Bool)
psActive = lens _psActive (\ s a -> s{_psActive = a})
psPrice :: Lens' PriceSchedule (Maybe Double)
psPrice = lens _psPrice (\ s a -> s{_psPrice = a})
instance FromXML PriceSchedule where
parseXML x
= PriceSchedule' <$>
(x .@? "currencyCode") <*> (x .@? "term") <*>
(x .@? "active")
<*> (x .@? "price")
instance Hashable PriceSchedule where
instance NFData PriceSchedule where
data PriceScheduleSpecification = PriceScheduleSpecification'
{ _pssCurrencyCode :: !(Maybe CurrencyCodeValues)
, _pssTerm :: !(Maybe Integer)
, _pssPrice :: !(Maybe Double)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
priceScheduleSpecification
:: PriceScheduleSpecification
priceScheduleSpecification =
PriceScheduleSpecification'
{_pssCurrencyCode = Nothing, _pssTerm = Nothing, _pssPrice = Nothing}
pssCurrencyCode :: Lens' PriceScheduleSpecification (Maybe CurrencyCodeValues)
pssCurrencyCode = lens _pssCurrencyCode (\ s a -> s{_pssCurrencyCode = a})
pssTerm :: Lens' PriceScheduleSpecification (Maybe Integer)
pssTerm = lens _pssTerm (\ s a -> s{_pssTerm = a})
pssPrice :: Lens' PriceScheduleSpecification (Maybe Double)
pssPrice = lens _pssPrice (\ s a -> s{_pssPrice = a})
instance Hashable PriceScheduleSpecification where
instance NFData PriceScheduleSpecification where
instance ToQuery PriceScheduleSpecification where
toQuery PriceScheduleSpecification'{..}
= mconcat
["CurrencyCode" =: _pssCurrencyCode,
"Term" =: _pssTerm, "Price" =: _pssPrice]
data PricingDetail = PricingDetail'
{ _pdCount :: !(Maybe Int)
, _pdPrice :: !(Maybe Double)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
pricingDetail
:: PricingDetail
pricingDetail = PricingDetail' {_pdCount = Nothing, _pdPrice = Nothing}
pdCount :: Lens' PricingDetail (Maybe Int)
pdCount = lens _pdCount (\ s a -> s{_pdCount = a})
pdPrice :: Lens' PricingDetail (Maybe Double)
pdPrice = lens _pdPrice (\ s a -> s{_pdPrice = a})
instance FromXML PricingDetail where
parseXML x
= PricingDetail' <$>
(x .@? "count") <*> (x .@? "price")
instance Hashable PricingDetail where
instance NFData PricingDetail where
data PrincipalIdFormat = PrincipalIdFormat'
{ _pifARN :: !(Maybe Text)
, _pifStatuses :: !(Maybe [IdFormat])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
principalIdFormat
:: PrincipalIdFormat
principalIdFormat =
PrincipalIdFormat' {_pifARN = Nothing, _pifStatuses = Nothing}
pifARN :: Lens' PrincipalIdFormat (Maybe Text)
pifARN = lens _pifARN (\ s a -> s{_pifARN = a})
pifStatuses :: Lens' PrincipalIdFormat [IdFormat]
pifStatuses = lens _pifStatuses (\ s a -> s{_pifStatuses = a}) . _Default . _Coerce
instance FromXML PrincipalIdFormat where
parseXML x
= PrincipalIdFormat' <$>
(x .@? "arn") <*>
(x .@? "statusSet" .!@ mempty >>=
may (parseXMLList "item"))
instance Hashable PrincipalIdFormat where
instance NFData PrincipalIdFormat where
data PrivateIPAddressSpecification = PrivateIPAddressSpecification'
{ _piasPrimary :: !(Maybe Bool)
, _piasPrivateIPAddress :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
privateIPAddressSpecification
:: Text
-> PrivateIPAddressSpecification
privateIPAddressSpecification pPrivateIPAddress_ =
PrivateIPAddressSpecification'
{_piasPrimary = Nothing, _piasPrivateIPAddress = pPrivateIPAddress_}
piasPrimary :: Lens' PrivateIPAddressSpecification (Maybe Bool)
piasPrimary = lens _piasPrimary (\ s a -> s{_piasPrimary = a})
piasPrivateIPAddress :: Lens' PrivateIPAddressSpecification Text
piasPrivateIPAddress = lens _piasPrivateIPAddress (\ s a -> s{_piasPrivateIPAddress = a})
instance FromXML PrivateIPAddressSpecification where
parseXML x
= PrivateIPAddressSpecification' <$>
(x .@? "primary") <*> (x .@ "privateIpAddress")
instance Hashable PrivateIPAddressSpecification where
instance NFData PrivateIPAddressSpecification where
instance ToQuery PrivateIPAddressSpecification where
toQuery PrivateIPAddressSpecification'{..}
= mconcat
["Primary" =: _piasPrimary,
"PrivateIpAddress" =: _piasPrivateIPAddress]
data ProductCode = ProductCode'
{ _pcProductCodeType :: !(Maybe ProductCodeValues)
, _pcProductCodeId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
productCode
:: ProductCode
productCode =
ProductCode' {_pcProductCodeType = Nothing, _pcProductCodeId = Nothing}
pcProductCodeType :: Lens' ProductCode (Maybe ProductCodeValues)
pcProductCodeType = lens _pcProductCodeType (\ s a -> s{_pcProductCodeType = a})
pcProductCodeId :: Lens' ProductCode (Maybe Text)
pcProductCodeId = lens _pcProductCodeId (\ s a -> s{_pcProductCodeId = a})
instance FromXML ProductCode where
parseXML x
= ProductCode' <$>
(x .@? "type") <*> (x .@? "productCode")
instance Hashable ProductCode where
instance NFData ProductCode where
newtype PropagatingVGW = PropagatingVGW'
{ _pvGatewayId :: Maybe Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
propagatingVGW
:: PropagatingVGW
propagatingVGW = PropagatingVGW' {_pvGatewayId = Nothing}
pvGatewayId :: Lens' PropagatingVGW (Maybe Text)
pvGatewayId = lens _pvGatewayId (\ s a -> s{_pvGatewayId = a})
instance FromXML PropagatingVGW where
parseXML x = PropagatingVGW' <$> (x .@? "gatewayId")
instance Hashable PropagatingVGW where
instance NFData PropagatingVGW where
data ProvisionedBandwidth = ProvisionedBandwidth'
{ _pbStatus :: !(Maybe Text)
, _pbRequested :: !(Maybe Text)
, _pbProvisioned :: !(Maybe Text)
, _pbRequestTime :: !(Maybe ISO8601)
, _pbProvisionTime :: !(Maybe ISO8601)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
provisionedBandwidth
:: ProvisionedBandwidth
provisionedBandwidth =
ProvisionedBandwidth'
{ _pbStatus = Nothing
, _pbRequested = Nothing
, _pbProvisioned = Nothing
, _pbRequestTime = Nothing
, _pbProvisionTime = Nothing
}
pbStatus :: Lens' ProvisionedBandwidth (Maybe Text)
pbStatus = lens _pbStatus (\ s a -> s{_pbStatus = a})
pbRequested :: Lens' ProvisionedBandwidth (Maybe Text)
pbRequested = lens _pbRequested (\ s a -> s{_pbRequested = a})
pbProvisioned :: Lens' ProvisionedBandwidth (Maybe Text)
pbProvisioned = lens _pbProvisioned (\ s a -> s{_pbProvisioned = a})
pbRequestTime :: Lens' ProvisionedBandwidth (Maybe UTCTime)
pbRequestTime = lens _pbRequestTime (\ s a -> s{_pbRequestTime = a}) . mapping _Time
pbProvisionTime :: Lens' ProvisionedBandwidth (Maybe UTCTime)
pbProvisionTime = lens _pbProvisionTime (\ s a -> s{_pbProvisionTime = a}) . mapping _Time
instance FromXML ProvisionedBandwidth where
parseXML x
= ProvisionedBandwidth' <$>
(x .@? "status") <*> (x .@? "requested") <*>
(x .@? "provisioned")
<*> (x .@? "requestTime")
<*> (x .@? "provisionTime")
instance Hashable ProvisionedBandwidth where
instance NFData ProvisionedBandwidth where
data Purchase = Purchase'
{ _pInstanceFamily :: !(Maybe Text)
, _pCurrencyCode :: !(Maybe CurrencyCodeValues)
, _pHostReservationId :: !(Maybe Text)
, _pHourlyPrice :: !(Maybe Text)
, _pUpfrontPrice :: !(Maybe Text)
, _pHostIdSet :: !(Maybe [Text])
, _pDuration :: !(Maybe Int)
, _pPaymentOption :: !(Maybe PaymentOption)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
purchase
:: Purchase
purchase =
Purchase'
{ _pInstanceFamily = Nothing
, _pCurrencyCode = Nothing
, _pHostReservationId = Nothing
, _pHourlyPrice = Nothing
, _pUpfrontPrice = Nothing
, _pHostIdSet = Nothing
, _pDuration = Nothing
, _pPaymentOption = Nothing
}
pInstanceFamily :: Lens' Purchase (Maybe Text)
pInstanceFamily = lens _pInstanceFamily (\ s a -> s{_pInstanceFamily = a})
pCurrencyCode :: Lens' Purchase (Maybe CurrencyCodeValues)
pCurrencyCode = lens _pCurrencyCode (\ s a -> s{_pCurrencyCode = a})
pHostReservationId :: Lens' Purchase (Maybe Text)
pHostReservationId = lens _pHostReservationId (\ s a -> s{_pHostReservationId = a})
pHourlyPrice :: Lens' Purchase (Maybe Text)
pHourlyPrice = lens _pHourlyPrice (\ s a -> s{_pHourlyPrice = a})
pUpfrontPrice :: Lens' Purchase (Maybe Text)
pUpfrontPrice = lens _pUpfrontPrice (\ s a -> s{_pUpfrontPrice = a})
pHostIdSet :: Lens' Purchase [Text]
pHostIdSet = lens _pHostIdSet (\ s a -> s{_pHostIdSet = a}) . _Default . _Coerce
pDuration :: Lens' Purchase (Maybe Int)
pDuration = lens _pDuration (\ s a -> s{_pDuration = a})
pPaymentOption :: Lens' Purchase (Maybe PaymentOption)
pPaymentOption = lens _pPaymentOption (\ s a -> s{_pPaymentOption = a})
instance FromXML Purchase where
parseXML x
= Purchase' <$>
(x .@? "instanceFamily") <*> (x .@? "currencyCode")
<*> (x .@? "hostReservationId")
<*> (x .@? "hourlyPrice")
<*> (x .@? "upfrontPrice")
<*>
(x .@? "hostIdSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "duration")
<*> (x .@? "paymentOption")
instance Hashable Purchase where
instance NFData Purchase where
data PurchaseRequest = PurchaseRequest'
{ _prInstanceCount :: !Int
, _prPurchaseToken :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
purchaseRequest
:: Int
-> Text
-> PurchaseRequest
purchaseRequest pInstanceCount_ pPurchaseToken_ =
PurchaseRequest'
{_prInstanceCount = pInstanceCount_, _prPurchaseToken = pPurchaseToken_}
prInstanceCount :: Lens' PurchaseRequest Int
prInstanceCount = lens _prInstanceCount (\ s a -> s{_prInstanceCount = a})
prPurchaseToken :: Lens' PurchaseRequest Text
prPurchaseToken = lens _prPurchaseToken (\ s a -> s{_prPurchaseToken = a})
instance Hashable PurchaseRequest where
instance NFData PurchaseRequest where
instance ToQuery PurchaseRequest where
toQuery PurchaseRequest'{..}
= mconcat
["InstanceCount" =: _prInstanceCount,
"PurchaseToken" =: _prPurchaseToken]
data RecurringCharge = RecurringCharge'
{ _rcAmount :: !(Maybe Double)
, _rcFrequency :: !(Maybe RecurringChargeFrequency)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
recurringCharge
:: RecurringCharge
recurringCharge = RecurringCharge' {_rcAmount = Nothing, _rcFrequency = Nothing}
rcAmount :: Lens' RecurringCharge (Maybe Double)
rcAmount = lens _rcAmount (\ s a -> s{_rcAmount = a})
rcFrequency :: Lens' RecurringCharge (Maybe RecurringChargeFrequency)
rcFrequency = lens _rcFrequency (\ s a -> s{_rcFrequency = a})
instance FromXML RecurringCharge where
parseXML x
= RecurringCharge' <$>
(x .@? "amount") <*> (x .@? "frequency")
instance Hashable RecurringCharge where
instance NFData RecurringCharge where
data RegionInfo = RegionInfo'
{ _riRegionName :: !(Maybe Text)
, _riEndpoint :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
regionInfo
:: RegionInfo
regionInfo = RegionInfo' {_riRegionName = Nothing, _riEndpoint = Nothing}
riRegionName :: Lens' RegionInfo (Maybe Text)
riRegionName = lens _riRegionName (\ s a -> s{_riRegionName = a})
riEndpoint :: Lens' RegionInfo (Maybe Text)
riEndpoint = lens _riEndpoint (\ s a -> s{_riEndpoint = a})
instance FromXML RegionInfo where
parseXML x
= RegionInfo' <$>
(x .@? "regionName") <*> (x .@? "regionEndpoint")
instance Hashable RegionInfo where
instance NFData RegionInfo where
data RequestLaunchTemplateData = RequestLaunchTemplateData'
{ _rltdSecurityGroupIds :: !(Maybe [Text])
, _rltdSecurityGroups :: !(Maybe [Text])
, _rltdInstanceMarketOptions :: !(Maybe LaunchTemplateInstanceMarketOptionsRequest)
, _rltdDisableAPITermination :: !(Maybe Bool)
, _rltdKeyName :: !(Maybe Text)
, _rltdNetworkInterfaces :: !(Maybe [LaunchTemplateInstanceNetworkInterfaceSpecificationRequest])
, _rltdRamDiskId :: !(Maybe Text)
, _rltdKernelId :: !(Maybe Text)
, _rltdElasticGpuSpecifications :: !(Maybe [ElasticGpuSpecification])
, _rltdInstanceType :: !(Maybe InstanceType)
, _rltdEBSOptimized :: !(Maybe Bool)
, _rltdUserData :: !(Maybe Text)
, _rltdMonitoring :: !(Maybe LaunchTemplatesMonitoringRequest)
, _rltdTagSpecifications :: !(Maybe [LaunchTemplateTagSpecificationRequest])
, _rltdIAMInstanceProfile :: !(Maybe LaunchTemplateIAMInstanceProfileSpecificationRequest)
, _rltdImageId :: !(Maybe Text)
, _rltdInstanceInitiatedShutdownBehavior :: !(Maybe ShutdownBehavior)
, _rltdCreditSpecification :: !(Maybe CreditSpecificationRequest)
, _rltdBlockDeviceMappings :: !(Maybe [LaunchTemplateBlockDeviceMappingRequest])
, _rltdPlacement :: !(Maybe LaunchTemplatePlacementRequest)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
requestLaunchTemplateData
:: RequestLaunchTemplateData
requestLaunchTemplateData =
RequestLaunchTemplateData'
{ _rltdSecurityGroupIds = Nothing
, _rltdSecurityGroups = Nothing
, _rltdInstanceMarketOptions = Nothing
, _rltdDisableAPITermination = Nothing
, _rltdKeyName = Nothing
, _rltdNetworkInterfaces = Nothing
, _rltdRamDiskId = Nothing
, _rltdKernelId = Nothing
, _rltdElasticGpuSpecifications = Nothing
, _rltdInstanceType = Nothing
, _rltdEBSOptimized = Nothing
, _rltdUserData = Nothing
, _rltdMonitoring = Nothing
, _rltdTagSpecifications = Nothing
, _rltdIAMInstanceProfile = Nothing
, _rltdImageId = Nothing
, _rltdInstanceInitiatedShutdownBehavior = Nothing
, _rltdCreditSpecification = Nothing
, _rltdBlockDeviceMappings = Nothing
, _rltdPlacement = Nothing
}
rltdSecurityGroupIds :: Lens' RequestLaunchTemplateData [Text]
rltdSecurityGroupIds = lens _rltdSecurityGroupIds (\ s a -> s{_rltdSecurityGroupIds = a}) . _Default . _Coerce
rltdSecurityGroups :: Lens' RequestLaunchTemplateData [Text]
rltdSecurityGroups = lens _rltdSecurityGroups (\ s a -> s{_rltdSecurityGroups = a}) . _Default . _Coerce
rltdInstanceMarketOptions :: Lens' RequestLaunchTemplateData (Maybe LaunchTemplateInstanceMarketOptionsRequest)
rltdInstanceMarketOptions = lens _rltdInstanceMarketOptions (\ s a -> s{_rltdInstanceMarketOptions = a})
rltdDisableAPITermination :: Lens' RequestLaunchTemplateData (Maybe Bool)
rltdDisableAPITermination = lens _rltdDisableAPITermination (\ s a -> s{_rltdDisableAPITermination = a})
rltdKeyName :: Lens' RequestLaunchTemplateData (Maybe Text)
rltdKeyName = lens _rltdKeyName (\ s a -> s{_rltdKeyName = a})
rltdNetworkInterfaces :: Lens' RequestLaunchTemplateData [LaunchTemplateInstanceNetworkInterfaceSpecificationRequest]
rltdNetworkInterfaces = lens _rltdNetworkInterfaces (\ s a -> s{_rltdNetworkInterfaces = a}) . _Default . _Coerce
rltdRamDiskId :: Lens' RequestLaunchTemplateData (Maybe Text)
rltdRamDiskId = lens _rltdRamDiskId (\ s a -> s{_rltdRamDiskId = a})
rltdKernelId :: Lens' RequestLaunchTemplateData (Maybe Text)
rltdKernelId = lens _rltdKernelId (\ s a -> s{_rltdKernelId = a})
rltdElasticGpuSpecifications :: Lens' RequestLaunchTemplateData [ElasticGpuSpecification]
rltdElasticGpuSpecifications = lens _rltdElasticGpuSpecifications (\ s a -> s{_rltdElasticGpuSpecifications = a}) . _Default . _Coerce
rltdInstanceType :: Lens' RequestLaunchTemplateData (Maybe InstanceType)
rltdInstanceType = lens _rltdInstanceType (\ s a -> s{_rltdInstanceType = a})
rltdEBSOptimized :: Lens' RequestLaunchTemplateData (Maybe Bool)
rltdEBSOptimized = lens _rltdEBSOptimized (\ s a -> s{_rltdEBSOptimized = a})
rltdUserData :: Lens' RequestLaunchTemplateData (Maybe Text)
rltdUserData = lens _rltdUserData (\ s a -> s{_rltdUserData = a})
rltdMonitoring :: Lens' RequestLaunchTemplateData (Maybe LaunchTemplatesMonitoringRequest)
rltdMonitoring = lens _rltdMonitoring (\ s a -> s{_rltdMonitoring = a})
rltdTagSpecifications :: Lens' RequestLaunchTemplateData [LaunchTemplateTagSpecificationRequest]
rltdTagSpecifications = lens _rltdTagSpecifications (\ s a -> s{_rltdTagSpecifications = a}) . _Default . _Coerce
rltdIAMInstanceProfile :: Lens' RequestLaunchTemplateData (Maybe LaunchTemplateIAMInstanceProfileSpecificationRequest)
rltdIAMInstanceProfile = lens _rltdIAMInstanceProfile (\ s a -> s{_rltdIAMInstanceProfile = a})
rltdImageId :: Lens' RequestLaunchTemplateData (Maybe Text)
rltdImageId = lens _rltdImageId (\ s a -> s{_rltdImageId = a})
rltdInstanceInitiatedShutdownBehavior :: Lens' RequestLaunchTemplateData (Maybe ShutdownBehavior)
rltdInstanceInitiatedShutdownBehavior = lens _rltdInstanceInitiatedShutdownBehavior (\ s a -> s{_rltdInstanceInitiatedShutdownBehavior = a})
rltdCreditSpecification :: Lens' RequestLaunchTemplateData (Maybe CreditSpecificationRequest)
rltdCreditSpecification = lens _rltdCreditSpecification (\ s a -> s{_rltdCreditSpecification = a})
rltdBlockDeviceMappings :: Lens' RequestLaunchTemplateData [LaunchTemplateBlockDeviceMappingRequest]
rltdBlockDeviceMappings = lens _rltdBlockDeviceMappings (\ s a -> s{_rltdBlockDeviceMappings = a}) . _Default . _Coerce
rltdPlacement :: Lens' RequestLaunchTemplateData (Maybe LaunchTemplatePlacementRequest)
rltdPlacement = lens _rltdPlacement (\ s a -> s{_rltdPlacement = a})
instance Hashable RequestLaunchTemplateData where
instance NFData RequestLaunchTemplateData where
instance ToQuery RequestLaunchTemplateData where
toQuery RequestLaunchTemplateData'{..}
= mconcat
[toQuery
(toQueryList "SecurityGroupId" <$>
_rltdSecurityGroupIds),
toQuery
(toQueryList "SecurityGroup" <$>
_rltdSecurityGroups),
"InstanceMarketOptions" =:
_rltdInstanceMarketOptions,
"DisableApiTermination" =:
_rltdDisableAPITermination,
"KeyName" =: _rltdKeyName,
toQuery
(toQueryList "NetworkInterface" <$>
_rltdNetworkInterfaces),
"RamDiskId" =: _rltdRamDiskId,
"KernelId" =: _rltdKernelId,
toQuery
(toQueryList "ElasticGpuSpecification" <$>
_rltdElasticGpuSpecifications),
"InstanceType" =: _rltdInstanceType,
"EbsOptimized" =: _rltdEBSOptimized,
"UserData" =: _rltdUserData,
"Monitoring" =: _rltdMonitoring,
toQuery
(toQueryList "TagSpecification" <$>
_rltdTagSpecifications),
"IamInstanceProfile" =: _rltdIAMInstanceProfile,
"ImageId" =: _rltdImageId,
"InstanceInitiatedShutdownBehavior" =:
_rltdInstanceInitiatedShutdownBehavior,
"CreditSpecification" =: _rltdCreditSpecification,
toQuery
(toQueryList "BlockDeviceMapping" <$>
_rltdBlockDeviceMappings),
"Placement" =: _rltdPlacement]
data RequestSpotLaunchSpecification = RequestSpotLaunchSpecification'
{ _rslsSecurityGroupIds :: !(Maybe [Text])
, _rslsSecurityGroups :: !(Maybe [Text])
, _rslsKeyName :: !(Maybe Text)
, _rslsNetworkInterfaces :: !(Maybe [InstanceNetworkInterfaceSpecification])
, _rslsRAMDiskId :: !(Maybe Text)
, _rslsSubnetId :: !(Maybe Text)
, _rslsKernelId :: !(Maybe Text)
, _rslsInstanceType :: !(Maybe InstanceType)
, _rslsEBSOptimized :: !(Maybe Bool)
, _rslsUserData :: !(Maybe Text)
, _rslsMonitoring :: !(Maybe RunInstancesMonitoringEnabled)
, _rslsIAMInstanceProfile :: !(Maybe IAMInstanceProfileSpecification)
, _rslsImageId :: !(Maybe Text)
, _rslsAddressingType :: !(Maybe Text)
, _rslsBlockDeviceMappings :: !(Maybe [BlockDeviceMapping])
, _rslsPlacement :: !(Maybe SpotPlacement)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
requestSpotLaunchSpecification
:: RequestSpotLaunchSpecification
requestSpotLaunchSpecification =
RequestSpotLaunchSpecification'
{ _rslsSecurityGroupIds = Nothing
, _rslsSecurityGroups = Nothing
, _rslsKeyName = Nothing
, _rslsNetworkInterfaces = Nothing
, _rslsRAMDiskId = Nothing
, _rslsSubnetId = Nothing
, _rslsKernelId = Nothing
, _rslsInstanceType = Nothing
, _rslsEBSOptimized = Nothing
, _rslsUserData = Nothing
, _rslsMonitoring = Nothing
, _rslsIAMInstanceProfile = Nothing
, _rslsImageId = Nothing
, _rslsAddressingType = Nothing
, _rslsBlockDeviceMappings = Nothing
, _rslsPlacement = Nothing
}
rslsSecurityGroupIds :: Lens' RequestSpotLaunchSpecification [Text]
rslsSecurityGroupIds = lens _rslsSecurityGroupIds (\ s a -> s{_rslsSecurityGroupIds = a}) . _Default . _Coerce
rslsSecurityGroups :: Lens' RequestSpotLaunchSpecification [Text]
rslsSecurityGroups = lens _rslsSecurityGroups (\ s a -> s{_rslsSecurityGroups = a}) . _Default . _Coerce
rslsKeyName :: Lens' RequestSpotLaunchSpecification (Maybe Text)
rslsKeyName = lens _rslsKeyName (\ s a -> s{_rslsKeyName = a})
rslsNetworkInterfaces :: Lens' RequestSpotLaunchSpecification [InstanceNetworkInterfaceSpecification]
rslsNetworkInterfaces = lens _rslsNetworkInterfaces (\ s a -> s{_rslsNetworkInterfaces = a}) . _Default . _Coerce
rslsRAMDiskId :: Lens' RequestSpotLaunchSpecification (Maybe Text)
rslsRAMDiskId = lens _rslsRAMDiskId (\ s a -> s{_rslsRAMDiskId = a})
rslsSubnetId :: Lens' RequestSpotLaunchSpecification (Maybe Text)
rslsSubnetId = lens _rslsSubnetId (\ s a -> s{_rslsSubnetId = a})
rslsKernelId :: Lens' RequestSpotLaunchSpecification (Maybe Text)
rslsKernelId = lens _rslsKernelId (\ s a -> s{_rslsKernelId = a})
rslsInstanceType :: Lens' RequestSpotLaunchSpecification (Maybe InstanceType)
rslsInstanceType = lens _rslsInstanceType (\ s a -> s{_rslsInstanceType = a})
rslsEBSOptimized :: Lens' RequestSpotLaunchSpecification (Maybe Bool)
rslsEBSOptimized = lens _rslsEBSOptimized (\ s a -> s{_rslsEBSOptimized = a})
rslsUserData :: Lens' RequestSpotLaunchSpecification (Maybe Text)
rslsUserData = lens _rslsUserData (\ s a -> s{_rslsUserData = a})
rslsMonitoring :: Lens' RequestSpotLaunchSpecification (Maybe RunInstancesMonitoringEnabled)
rslsMonitoring = lens _rslsMonitoring (\ s a -> s{_rslsMonitoring = a})
rslsIAMInstanceProfile :: Lens' RequestSpotLaunchSpecification (Maybe IAMInstanceProfileSpecification)
rslsIAMInstanceProfile = lens _rslsIAMInstanceProfile (\ s a -> s{_rslsIAMInstanceProfile = a})
rslsImageId :: Lens' RequestSpotLaunchSpecification (Maybe Text)
rslsImageId = lens _rslsImageId (\ s a -> s{_rslsImageId = a})
rslsAddressingType :: Lens' RequestSpotLaunchSpecification (Maybe Text)
rslsAddressingType = lens _rslsAddressingType (\ s a -> s{_rslsAddressingType = a})
rslsBlockDeviceMappings :: Lens' RequestSpotLaunchSpecification [BlockDeviceMapping]
rslsBlockDeviceMappings = lens _rslsBlockDeviceMappings (\ s a -> s{_rslsBlockDeviceMappings = a}) . _Default . _Coerce
rslsPlacement :: Lens' RequestSpotLaunchSpecification (Maybe SpotPlacement)
rslsPlacement = lens _rslsPlacement (\ s a -> s{_rslsPlacement = a})
instance Hashable RequestSpotLaunchSpecification
where
instance NFData RequestSpotLaunchSpecification where
instance ToQuery RequestSpotLaunchSpecification where
toQuery RequestSpotLaunchSpecification'{..}
= mconcat
[toQuery
(toQueryList "SecurityGroupId" <$>
_rslsSecurityGroupIds),
toQuery
(toQueryList "SecurityGroup" <$>
_rslsSecurityGroups),
"KeyName" =: _rslsKeyName,
toQuery
(toQueryList "NetworkInterface" <$>
_rslsNetworkInterfaces),
"RamdiskId" =: _rslsRAMDiskId,
"SubnetId" =: _rslsSubnetId,
"KernelId" =: _rslsKernelId,
"InstanceType" =: _rslsInstanceType,
"EbsOptimized" =: _rslsEBSOptimized,
"UserData" =: _rslsUserData,
"Monitoring" =: _rslsMonitoring,
"IamInstanceProfile" =: _rslsIAMInstanceProfile,
"ImageId" =: _rslsImageId,
"AddressingType" =: _rslsAddressingType,
toQuery
(toQueryList "BlockDeviceMapping" <$>
_rslsBlockDeviceMappings),
"Placement" =: _rslsPlacement]
data Reservation = Reservation'
{ _rGroups :: !(Maybe [GroupIdentifier])
, _rInstances :: !(Maybe [Instance])
, _rRequesterId :: !(Maybe Text)
, _rReservationId :: !Text
, _rOwnerId :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
reservation
:: Text
-> Text
-> Reservation
reservation pReservationId_ pOwnerId_ =
Reservation'
{ _rGroups = Nothing
, _rInstances = Nothing
, _rRequesterId = Nothing
, _rReservationId = pReservationId_
, _rOwnerId = pOwnerId_
}
rGroups :: Lens' Reservation [GroupIdentifier]
rGroups = lens _rGroups (\ s a -> s{_rGroups = a}) . _Default . _Coerce
rInstances :: Lens' Reservation [Instance]
rInstances = lens _rInstances (\ s a -> s{_rInstances = a}) . _Default . _Coerce
rRequesterId :: Lens' Reservation (Maybe Text)
rRequesterId = lens _rRequesterId (\ s a -> s{_rRequesterId = a})
rReservationId :: Lens' Reservation Text
rReservationId = lens _rReservationId (\ s a -> s{_rReservationId = a})
rOwnerId :: Lens' Reservation Text
rOwnerId = lens _rOwnerId (\ s a -> s{_rOwnerId = a})
instance FromXML Reservation where
parseXML x
= Reservation' <$>
(x .@? "groupSet" .!@ mempty >>=
may (parseXMLList "item"))
<*>
(x .@? "instancesSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "requesterId")
<*> (x .@ "reservationId")
<*> (x .@ "ownerId")
instance Hashable Reservation where
instance NFData Reservation where
data ReservationValue = ReservationValue'
{ _rvHourlyPrice :: !(Maybe Text)
, _rvRemainingTotalValue :: !(Maybe Text)
, _rvRemainingUpfrontValue :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
reservationValue
:: ReservationValue
reservationValue =
ReservationValue'
{ _rvHourlyPrice = Nothing
, _rvRemainingTotalValue = Nothing
, _rvRemainingUpfrontValue = Nothing
}
rvHourlyPrice :: Lens' ReservationValue (Maybe Text)
rvHourlyPrice = lens _rvHourlyPrice (\ s a -> s{_rvHourlyPrice = a})
rvRemainingTotalValue :: Lens' ReservationValue (Maybe Text)
rvRemainingTotalValue = lens _rvRemainingTotalValue (\ s a -> s{_rvRemainingTotalValue = a})
rvRemainingUpfrontValue :: Lens' ReservationValue (Maybe Text)
rvRemainingUpfrontValue = lens _rvRemainingUpfrontValue (\ s a -> s{_rvRemainingUpfrontValue = a})
instance FromXML ReservationValue where
parseXML x
= ReservationValue' <$>
(x .@? "hourlyPrice") <*>
(x .@? "remainingTotalValue")
<*> (x .@? "remainingUpfrontValue")
instance Hashable ReservationValue where
instance NFData ReservationValue where
data ReservedInstanceLimitPrice = ReservedInstanceLimitPrice'
{ _rilpAmount :: !(Maybe Double)
, _rilpCurrencyCode :: !(Maybe CurrencyCodeValues)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
reservedInstanceLimitPrice
:: ReservedInstanceLimitPrice
reservedInstanceLimitPrice =
ReservedInstanceLimitPrice'
{_rilpAmount = Nothing, _rilpCurrencyCode = Nothing}
rilpAmount :: Lens' ReservedInstanceLimitPrice (Maybe Double)
rilpAmount = lens _rilpAmount (\ s a -> s{_rilpAmount = a})
rilpCurrencyCode :: Lens' ReservedInstanceLimitPrice (Maybe CurrencyCodeValues)
rilpCurrencyCode = lens _rilpCurrencyCode (\ s a -> s{_rilpCurrencyCode = a})
instance Hashable ReservedInstanceLimitPrice where
instance NFData ReservedInstanceLimitPrice where
instance ToQuery ReservedInstanceLimitPrice where
toQuery ReservedInstanceLimitPrice'{..}
= mconcat
["Amount" =: _rilpAmount,
"CurrencyCode" =: _rilpCurrencyCode]
data ReservedInstanceReservationValue = ReservedInstanceReservationValue'
{ _rirvReservationValue :: !(Maybe ReservationValue)
, _rirvReservedInstanceId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
reservedInstanceReservationValue
:: ReservedInstanceReservationValue
reservedInstanceReservationValue =
ReservedInstanceReservationValue'
{_rirvReservationValue = Nothing, _rirvReservedInstanceId = Nothing}
rirvReservationValue :: Lens' ReservedInstanceReservationValue (Maybe ReservationValue)
rirvReservationValue = lens _rirvReservationValue (\ s a -> s{_rirvReservationValue = a})
rirvReservedInstanceId :: Lens' ReservedInstanceReservationValue (Maybe Text)
rirvReservedInstanceId = lens _rirvReservedInstanceId (\ s a -> s{_rirvReservedInstanceId = a})
instance FromXML ReservedInstanceReservationValue
where
parseXML x
= ReservedInstanceReservationValue' <$>
(x .@? "reservationValue") <*>
(x .@? "reservedInstanceId")
instance Hashable ReservedInstanceReservationValue
where
instance NFData ReservedInstanceReservationValue
where
data ReservedInstances = ReservedInstances'
{ _riState :: !(Maybe ReservedInstanceState)
, _riCurrencyCode :: !(Maybe CurrencyCodeValues)
, _riInstanceCount :: !(Maybe Int)
, _riProductDescription :: !(Maybe RIProductDescription)
, _riStart :: !(Maybe ISO8601)
, _riInstanceType :: !(Maybe InstanceType)
, _riEnd :: !(Maybe ISO8601)
, _riAvailabilityZone :: !(Maybe Text)
, _riScope :: !(Maybe Scope)
, _riRecurringCharges :: !(Maybe [RecurringCharge])
, _riOfferingType :: !(Maybe OfferingTypeValues)
, _riUsagePrice :: !(Maybe Double)
, _riFixedPrice :: !(Maybe Double)
, _riReservedInstancesId :: !(Maybe Text)
, _riInstanceTenancy :: !(Maybe Tenancy)
, _riOfferingClass :: !(Maybe OfferingClassType)
, _riDuration :: !(Maybe Integer)
, _riTags :: !(Maybe [Tag])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
reservedInstances
:: ReservedInstances
reservedInstances =
ReservedInstances'
{ _riState = Nothing
, _riCurrencyCode = Nothing
, _riInstanceCount = Nothing
, _riProductDescription = Nothing
, _riStart = Nothing
, _riInstanceType = Nothing
, _riEnd = Nothing
, _riAvailabilityZone = Nothing
, _riScope = Nothing
, _riRecurringCharges = Nothing
, _riOfferingType = Nothing
, _riUsagePrice = Nothing
, _riFixedPrice = Nothing
, _riReservedInstancesId = Nothing
, _riInstanceTenancy = Nothing
, _riOfferingClass = Nothing
, _riDuration = Nothing
, _riTags = Nothing
}
riState :: Lens' ReservedInstances (Maybe ReservedInstanceState)
riState = lens _riState (\ s a -> s{_riState = a})
riCurrencyCode :: Lens' ReservedInstances (Maybe CurrencyCodeValues)
riCurrencyCode = lens _riCurrencyCode (\ s a -> s{_riCurrencyCode = a})
riInstanceCount :: Lens' ReservedInstances (Maybe Int)
riInstanceCount = lens _riInstanceCount (\ s a -> s{_riInstanceCount = a})
riProductDescription :: Lens' ReservedInstances (Maybe RIProductDescription)
riProductDescription = lens _riProductDescription (\ s a -> s{_riProductDescription = a})
riStart :: Lens' ReservedInstances (Maybe UTCTime)
riStart = lens _riStart (\ s a -> s{_riStart = a}) . mapping _Time
riInstanceType :: Lens' ReservedInstances (Maybe InstanceType)
riInstanceType = lens _riInstanceType (\ s a -> s{_riInstanceType = a})
riEnd :: Lens' ReservedInstances (Maybe UTCTime)
riEnd = lens _riEnd (\ s a -> s{_riEnd = a}) . mapping _Time
riAvailabilityZone :: Lens' ReservedInstances (Maybe Text)
riAvailabilityZone = lens _riAvailabilityZone (\ s a -> s{_riAvailabilityZone = a})
riScope :: Lens' ReservedInstances (Maybe Scope)
riScope = lens _riScope (\ s a -> s{_riScope = a})
riRecurringCharges :: Lens' ReservedInstances [RecurringCharge]
riRecurringCharges = lens _riRecurringCharges (\ s a -> s{_riRecurringCharges = a}) . _Default . _Coerce
riOfferingType :: Lens' ReservedInstances (Maybe OfferingTypeValues)
riOfferingType = lens _riOfferingType (\ s a -> s{_riOfferingType = a})
riUsagePrice :: Lens' ReservedInstances (Maybe Double)
riUsagePrice = lens _riUsagePrice (\ s a -> s{_riUsagePrice = a})
riFixedPrice :: Lens' ReservedInstances (Maybe Double)
riFixedPrice = lens _riFixedPrice (\ s a -> s{_riFixedPrice = a})
riReservedInstancesId :: Lens' ReservedInstances (Maybe Text)
riReservedInstancesId = lens _riReservedInstancesId (\ s a -> s{_riReservedInstancesId = a})
riInstanceTenancy :: Lens' ReservedInstances (Maybe Tenancy)
riInstanceTenancy = lens _riInstanceTenancy (\ s a -> s{_riInstanceTenancy = a})
riOfferingClass :: Lens' ReservedInstances (Maybe OfferingClassType)
riOfferingClass = lens _riOfferingClass (\ s a -> s{_riOfferingClass = a})
riDuration :: Lens' ReservedInstances (Maybe Integer)
riDuration = lens _riDuration (\ s a -> s{_riDuration = a})
riTags :: Lens' ReservedInstances [Tag]
riTags = lens _riTags (\ s a -> s{_riTags = a}) . _Default . _Coerce
instance FromXML ReservedInstances where
parseXML x
= ReservedInstances' <$>
(x .@? "state") <*> (x .@? "currencyCode") <*>
(x .@? "instanceCount")
<*> (x .@? "productDescription")
<*> (x .@? "start")
<*> (x .@? "instanceType")
<*> (x .@? "end")
<*> (x .@? "availabilityZone")
<*> (x .@? "scope")
<*>
(x .@? "recurringCharges" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "offeringType")
<*> (x .@? "usagePrice")
<*> (x .@? "fixedPrice")
<*> (x .@? "reservedInstancesId")
<*> (x .@? "instanceTenancy")
<*> (x .@? "offeringClass")
<*> (x .@? "duration")
<*>
(x .@? "tagSet" .!@ mempty >>=
may (parseXMLList "item"))
instance Hashable ReservedInstances where
instance NFData ReservedInstances where
data ReservedInstancesConfiguration = ReservedInstancesConfiguration'
{ _ricPlatform :: !(Maybe Text)
, _ricInstanceCount :: !(Maybe Int)
, _ricInstanceType :: !(Maybe InstanceType)
, _ricAvailabilityZone :: !(Maybe Text)
, _ricScope :: !(Maybe Scope)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
reservedInstancesConfiguration
:: ReservedInstancesConfiguration
reservedInstancesConfiguration =
ReservedInstancesConfiguration'
{ _ricPlatform = Nothing
, _ricInstanceCount = Nothing
, _ricInstanceType = Nothing
, _ricAvailabilityZone = Nothing
, _ricScope = Nothing
}
ricPlatform :: Lens' ReservedInstancesConfiguration (Maybe Text)
ricPlatform = lens _ricPlatform (\ s a -> s{_ricPlatform = a})
ricInstanceCount :: Lens' ReservedInstancesConfiguration (Maybe Int)
ricInstanceCount = lens _ricInstanceCount (\ s a -> s{_ricInstanceCount = a})
ricInstanceType :: Lens' ReservedInstancesConfiguration (Maybe InstanceType)
ricInstanceType = lens _ricInstanceType (\ s a -> s{_ricInstanceType = a})
ricAvailabilityZone :: Lens' ReservedInstancesConfiguration (Maybe Text)
ricAvailabilityZone = lens _ricAvailabilityZone (\ s a -> s{_ricAvailabilityZone = a})
ricScope :: Lens' ReservedInstancesConfiguration (Maybe Scope)
ricScope = lens _ricScope (\ s a -> s{_ricScope = a})
instance FromXML ReservedInstancesConfiguration where
parseXML x
= ReservedInstancesConfiguration' <$>
(x .@? "platform") <*> (x .@? "instanceCount") <*>
(x .@? "instanceType")
<*> (x .@? "availabilityZone")
<*> (x .@? "scope")
instance Hashable ReservedInstancesConfiguration
where
instance NFData ReservedInstancesConfiguration where
instance ToQuery ReservedInstancesConfiguration where
toQuery ReservedInstancesConfiguration'{..}
= mconcat
["Platform" =: _ricPlatform,
"InstanceCount" =: _ricInstanceCount,
"InstanceType" =: _ricInstanceType,
"AvailabilityZone" =: _ricAvailabilityZone,
"Scope" =: _ricScope]
newtype ReservedInstancesId = ReservedInstancesId'
{ _riiReservedInstancesId :: Maybe Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
reservedInstancesId
:: ReservedInstancesId
reservedInstancesId = ReservedInstancesId' {_riiReservedInstancesId = Nothing}
riiReservedInstancesId :: Lens' ReservedInstancesId (Maybe Text)
riiReservedInstancesId = lens _riiReservedInstancesId (\ s a -> s{_riiReservedInstancesId = a})
instance FromXML ReservedInstancesId where
parseXML x
= ReservedInstancesId' <$>
(x .@? "reservedInstancesId")
instance Hashable ReservedInstancesId where
instance NFData ReservedInstancesId where
data ReservedInstancesListing = ReservedInstancesListing'
{ _rilStatus :: !(Maybe ListingStatus)
, _rilClientToken :: !(Maybe Text)
, _rilUpdateDate :: !(Maybe ISO8601)
, _rilCreateDate :: !(Maybe ISO8601)
, _rilPriceSchedules :: !(Maybe [PriceSchedule])
, _rilStatusMessage :: !(Maybe Text)
, _rilReservedInstancesId :: !(Maybe Text)
, _rilTags :: !(Maybe [Tag])
, _rilInstanceCounts :: !(Maybe [InstanceCount])
, _rilReservedInstancesListingId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
reservedInstancesListing
:: ReservedInstancesListing
reservedInstancesListing =
ReservedInstancesListing'
{ _rilStatus = Nothing
, _rilClientToken = Nothing
, _rilUpdateDate = Nothing
, _rilCreateDate = Nothing
, _rilPriceSchedules = Nothing
, _rilStatusMessage = Nothing
, _rilReservedInstancesId = Nothing
, _rilTags = Nothing
, _rilInstanceCounts = Nothing
, _rilReservedInstancesListingId = Nothing
}
rilStatus :: Lens' ReservedInstancesListing (Maybe ListingStatus)
rilStatus = lens _rilStatus (\ s a -> s{_rilStatus = a})
rilClientToken :: Lens' ReservedInstancesListing (Maybe Text)
rilClientToken = lens _rilClientToken (\ s a -> s{_rilClientToken = a})
rilUpdateDate :: Lens' ReservedInstancesListing (Maybe UTCTime)
rilUpdateDate = lens _rilUpdateDate (\ s a -> s{_rilUpdateDate = a}) . mapping _Time
rilCreateDate :: Lens' ReservedInstancesListing (Maybe UTCTime)
rilCreateDate = lens _rilCreateDate (\ s a -> s{_rilCreateDate = a}) . mapping _Time
rilPriceSchedules :: Lens' ReservedInstancesListing [PriceSchedule]
rilPriceSchedules = lens _rilPriceSchedules (\ s a -> s{_rilPriceSchedules = a}) . _Default . _Coerce
rilStatusMessage :: Lens' ReservedInstancesListing (Maybe Text)
rilStatusMessage = lens _rilStatusMessage (\ s a -> s{_rilStatusMessage = a})
rilReservedInstancesId :: Lens' ReservedInstancesListing (Maybe Text)
rilReservedInstancesId = lens _rilReservedInstancesId (\ s a -> s{_rilReservedInstancesId = a})
rilTags :: Lens' ReservedInstancesListing [Tag]
rilTags = lens _rilTags (\ s a -> s{_rilTags = a}) . _Default . _Coerce
rilInstanceCounts :: Lens' ReservedInstancesListing [InstanceCount]
rilInstanceCounts = lens _rilInstanceCounts (\ s a -> s{_rilInstanceCounts = a}) . _Default . _Coerce
rilReservedInstancesListingId :: Lens' ReservedInstancesListing (Maybe Text)
rilReservedInstancesListingId = lens _rilReservedInstancesListingId (\ s a -> s{_rilReservedInstancesListingId = a})
instance FromXML ReservedInstancesListing where
parseXML x
= ReservedInstancesListing' <$>
(x .@? "status") <*> (x .@? "clientToken") <*>
(x .@? "updateDate")
<*> (x .@? "createDate")
<*>
(x .@? "priceSchedules" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "statusMessage")
<*> (x .@? "reservedInstancesId")
<*>
(x .@? "tagSet" .!@ mempty >>=
may (parseXMLList "item"))
<*>
(x .@? "instanceCounts" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "reservedInstancesListingId")
instance Hashable ReservedInstancesListing where
instance NFData ReservedInstancesListing where
data ReservedInstancesModification = ReservedInstancesModification'
{ _rimModificationResults :: !(Maybe [ReservedInstancesModificationResult])
, _rimStatus :: !(Maybe Text)
, _rimClientToken :: !(Maybe Text)
, _rimUpdateDate :: !(Maybe ISO8601)
, _rimCreateDate :: !(Maybe ISO8601)
, _rimEffectiveDate :: !(Maybe ISO8601)
, _rimStatusMessage :: !(Maybe Text)
, _rimReservedInstancesModificationId :: !(Maybe Text)
, _rimReservedInstancesIds :: !(Maybe [ReservedInstancesId])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
reservedInstancesModification
:: ReservedInstancesModification
reservedInstancesModification =
ReservedInstancesModification'
{ _rimModificationResults = Nothing
, _rimStatus = Nothing
, _rimClientToken = Nothing
, _rimUpdateDate = Nothing
, _rimCreateDate = Nothing
, _rimEffectiveDate = Nothing
, _rimStatusMessage = Nothing
, _rimReservedInstancesModificationId = Nothing
, _rimReservedInstancesIds = Nothing
}
rimModificationResults :: Lens' ReservedInstancesModification [ReservedInstancesModificationResult]
rimModificationResults = lens _rimModificationResults (\ s a -> s{_rimModificationResults = a}) . _Default . _Coerce
rimStatus :: Lens' ReservedInstancesModification (Maybe Text)
rimStatus = lens _rimStatus (\ s a -> s{_rimStatus = a})
rimClientToken :: Lens' ReservedInstancesModification (Maybe Text)
rimClientToken = lens _rimClientToken (\ s a -> s{_rimClientToken = a})
rimUpdateDate :: Lens' ReservedInstancesModification (Maybe UTCTime)
rimUpdateDate = lens _rimUpdateDate (\ s a -> s{_rimUpdateDate = a}) . mapping _Time
rimCreateDate :: Lens' ReservedInstancesModification (Maybe UTCTime)
rimCreateDate = lens _rimCreateDate (\ s a -> s{_rimCreateDate = a}) . mapping _Time
rimEffectiveDate :: Lens' ReservedInstancesModification (Maybe UTCTime)
rimEffectiveDate = lens _rimEffectiveDate (\ s a -> s{_rimEffectiveDate = a}) . mapping _Time
rimStatusMessage :: Lens' ReservedInstancesModification (Maybe Text)
rimStatusMessage = lens _rimStatusMessage (\ s a -> s{_rimStatusMessage = a})
rimReservedInstancesModificationId :: Lens' ReservedInstancesModification (Maybe Text)
rimReservedInstancesModificationId = lens _rimReservedInstancesModificationId (\ s a -> s{_rimReservedInstancesModificationId = a})
rimReservedInstancesIds :: Lens' ReservedInstancesModification [ReservedInstancesId]
rimReservedInstancesIds = lens _rimReservedInstancesIds (\ s a -> s{_rimReservedInstancesIds = a}) . _Default . _Coerce
instance FromXML ReservedInstancesModification where
parseXML x
= ReservedInstancesModification' <$>
(x .@? "modificationResultSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "status")
<*> (x .@? "clientToken")
<*> (x .@? "updateDate")
<*> (x .@? "createDate")
<*> (x .@? "effectiveDate")
<*> (x .@? "statusMessage")
<*> (x .@? "reservedInstancesModificationId")
<*>
(x .@? "reservedInstancesSet" .!@ mempty >>=
may (parseXMLList "item"))
instance Hashable ReservedInstancesModification where
instance NFData ReservedInstancesModification where
data ReservedInstancesModificationResult = ReservedInstancesModificationResult'
{ _rimrReservedInstancesId :: !(Maybe Text)
, _rimrTargetConfiguration :: !(Maybe ReservedInstancesConfiguration)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
reservedInstancesModificationResult
:: ReservedInstancesModificationResult
reservedInstancesModificationResult =
ReservedInstancesModificationResult'
{_rimrReservedInstancesId = Nothing, _rimrTargetConfiguration = Nothing}
rimrReservedInstancesId :: Lens' ReservedInstancesModificationResult (Maybe Text)
rimrReservedInstancesId = lens _rimrReservedInstancesId (\ s a -> s{_rimrReservedInstancesId = a})
rimrTargetConfiguration :: Lens' ReservedInstancesModificationResult (Maybe ReservedInstancesConfiguration)
rimrTargetConfiguration = lens _rimrTargetConfiguration (\ s a -> s{_rimrTargetConfiguration = a})
instance FromXML ReservedInstancesModificationResult
where
parseXML x
= ReservedInstancesModificationResult' <$>
(x .@? "reservedInstancesId") <*>
(x .@? "targetConfiguration")
instance Hashable ReservedInstancesModificationResult
where
instance NFData ReservedInstancesModificationResult
where
data ReservedInstancesOffering = ReservedInstancesOffering'
{ _rioMarketplace :: !(Maybe Bool)
, _rioCurrencyCode :: !(Maybe CurrencyCodeValues)
, _rioProductDescription :: !(Maybe RIProductDescription)
, _rioInstanceType :: !(Maybe InstanceType)
, _rioAvailabilityZone :: !(Maybe Text)
, _rioPricingDetails :: !(Maybe [PricingDetail])
, _rioScope :: !(Maybe Scope)
, _rioRecurringCharges :: !(Maybe [RecurringCharge])
, _rioOfferingType :: !(Maybe OfferingTypeValues)
, _rioUsagePrice :: !(Maybe Double)
, _rioFixedPrice :: !(Maybe Double)
, _rioInstanceTenancy :: !(Maybe Tenancy)
, _rioReservedInstancesOfferingId :: !(Maybe Text)
, _rioOfferingClass :: !(Maybe OfferingClassType)
, _rioDuration :: !(Maybe Integer)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
reservedInstancesOffering
:: ReservedInstancesOffering
reservedInstancesOffering =
ReservedInstancesOffering'
{ _rioMarketplace = Nothing
, _rioCurrencyCode = Nothing
, _rioProductDescription = Nothing
, _rioInstanceType = Nothing
, _rioAvailabilityZone = Nothing
, _rioPricingDetails = Nothing
, _rioScope = Nothing
, _rioRecurringCharges = Nothing
, _rioOfferingType = Nothing
, _rioUsagePrice = Nothing
, _rioFixedPrice = Nothing
, _rioInstanceTenancy = Nothing
, _rioReservedInstancesOfferingId = Nothing
, _rioOfferingClass = Nothing
, _rioDuration = Nothing
}
rioMarketplace :: Lens' ReservedInstancesOffering (Maybe Bool)
rioMarketplace = lens _rioMarketplace (\ s a -> s{_rioMarketplace = a})
rioCurrencyCode :: Lens' ReservedInstancesOffering (Maybe CurrencyCodeValues)
rioCurrencyCode = lens _rioCurrencyCode (\ s a -> s{_rioCurrencyCode = a})
rioProductDescription :: Lens' ReservedInstancesOffering (Maybe RIProductDescription)
rioProductDescription = lens _rioProductDescription (\ s a -> s{_rioProductDescription = a})
rioInstanceType :: Lens' ReservedInstancesOffering (Maybe InstanceType)
rioInstanceType = lens _rioInstanceType (\ s a -> s{_rioInstanceType = a})
rioAvailabilityZone :: Lens' ReservedInstancesOffering (Maybe Text)
rioAvailabilityZone = lens _rioAvailabilityZone (\ s a -> s{_rioAvailabilityZone = a})
rioPricingDetails :: Lens' ReservedInstancesOffering [PricingDetail]
rioPricingDetails = lens _rioPricingDetails (\ s a -> s{_rioPricingDetails = a}) . _Default . _Coerce
rioScope :: Lens' ReservedInstancesOffering (Maybe Scope)
rioScope = lens _rioScope (\ s a -> s{_rioScope = a})
rioRecurringCharges :: Lens' ReservedInstancesOffering [RecurringCharge]
rioRecurringCharges = lens _rioRecurringCharges (\ s a -> s{_rioRecurringCharges = a}) . _Default . _Coerce
rioOfferingType :: Lens' ReservedInstancesOffering (Maybe OfferingTypeValues)
rioOfferingType = lens _rioOfferingType (\ s a -> s{_rioOfferingType = a})
rioUsagePrice :: Lens' ReservedInstancesOffering (Maybe Double)
rioUsagePrice = lens _rioUsagePrice (\ s a -> s{_rioUsagePrice = a})
rioFixedPrice :: Lens' ReservedInstancesOffering (Maybe Double)
rioFixedPrice = lens _rioFixedPrice (\ s a -> s{_rioFixedPrice = a})
rioInstanceTenancy :: Lens' ReservedInstancesOffering (Maybe Tenancy)
rioInstanceTenancy = lens _rioInstanceTenancy (\ s a -> s{_rioInstanceTenancy = a})
rioReservedInstancesOfferingId :: Lens' ReservedInstancesOffering (Maybe Text)
rioReservedInstancesOfferingId = lens _rioReservedInstancesOfferingId (\ s a -> s{_rioReservedInstancesOfferingId = a})
rioOfferingClass :: Lens' ReservedInstancesOffering (Maybe OfferingClassType)
rioOfferingClass = lens _rioOfferingClass (\ s a -> s{_rioOfferingClass = a})
rioDuration :: Lens' ReservedInstancesOffering (Maybe Integer)
rioDuration = lens _rioDuration (\ s a -> s{_rioDuration = a})
instance FromXML ReservedInstancesOffering where
parseXML x
= ReservedInstancesOffering' <$>
(x .@? "marketplace") <*> (x .@? "currencyCode") <*>
(x .@? "productDescription")
<*> (x .@? "instanceType")
<*> (x .@? "availabilityZone")
<*>
(x .@? "pricingDetailsSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "scope")
<*>
(x .@? "recurringCharges" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "offeringType")
<*> (x .@? "usagePrice")
<*> (x .@? "fixedPrice")
<*> (x .@? "instanceTenancy")
<*> (x .@? "reservedInstancesOfferingId")
<*> (x .@? "offeringClass")
<*> (x .@? "duration")
instance Hashable ReservedInstancesOffering where
instance NFData ReservedInstancesOffering where
data ResponseError = ResponseError'
{ _reCode :: !(Maybe LaunchTemplateErrorCode)
, _reMessage :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
responseError
:: ResponseError
responseError = ResponseError' {_reCode = Nothing, _reMessage = Nothing}
reCode :: Lens' ResponseError (Maybe LaunchTemplateErrorCode)
reCode = lens _reCode (\ s a -> s{_reCode = a})
reMessage :: Lens' ResponseError (Maybe Text)
reMessage = lens _reMessage (\ s a -> s{_reMessage = a})
instance FromXML ResponseError where
parseXML x
= ResponseError' <$>
(x .@? "code") <*> (x .@? "message")
instance Hashable ResponseError where
instance NFData ResponseError where
data ResponseLaunchTemplateData = ResponseLaunchTemplateData'
{ _rSecurityGroupIds :: !(Maybe [Text])
, _rSecurityGroups :: !(Maybe [Text])
, _rInstanceMarketOptions :: !(Maybe LaunchTemplateInstanceMarketOptions)
, _rDisableAPITermination :: !(Maybe Bool)
, _rKeyName :: !(Maybe Text)
, _rNetworkInterfaces :: !(Maybe [LaunchTemplateInstanceNetworkInterfaceSpecification])
, _rRamDiskId :: !(Maybe Text)
, _rKernelId :: !(Maybe Text)
, _rElasticGpuSpecifications :: !(Maybe [ElasticGpuSpecificationResponse])
, _rInstanceType :: !(Maybe InstanceType)
, _rEBSOptimized :: !(Maybe Bool)
, _rUserData :: !(Maybe Text)
, _rMonitoring :: !(Maybe LaunchTemplatesMonitoring)
, _rTagSpecifications :: !(Maybe [LaunchTemplateTagSpecification])
, _rIAMInstanceProfile :: !(Maybe LaunchTemplateIAMInstanceProfileSpecification)
, _rImageId :: !(Maybe Text)
, _rInstanceInitiatedShutdownBehavior :: !(Maybe ShutdownBehavior)
, _rCreditSpecification :: !(Maybe CreditSpecification)
, _rBlockDeviceMappings :: !(Maybe [LaunchTemplateBlockDeviceMapping])
, _rPlacement :: !(Maybe LaunchTemplatePlacement)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
responseLaunchTemplateData
:: ResponseLaunchTemplateData
responseLaunchTemplateData =
ResponseLaunchTemplateData'
{ _rSecurityGroupIds = Nothing
, _rSecurityGroups = Nothing
, _rInstanceMarketOptions = Nothing
, _rDisableAPITermination = Nothing
, _rKeyName = Nothing
, _rNetworkInterfaces = Nothing
, _rRamDiskId = Nothing
, _rKernelId = Nothing
, _rElasticGpuSpecifications = Nothing
, _rInstanceType = Nothing
, _rEBSOptimized = Nothing
, _rUserData = Nothing
, _rMonitoring = Nothing
, _rTagSpecifications = Nothing
, _rIAMInstanceProfile = Nothing
, _rImageId = Nothing
, _rInstanceInitiatedShutdownBehavior = Nothing
, _rCreditSpecification = Nothing
, _rBlockDeviceMappings = Nothing
, _rPlacement = Nothing
}
rSecurityGroupIds :: Lens' ResponseLaunchTemplateData [Text]
rSecurityGroupIds = lens _rSecurityGroupIds (\ s a -> s{_rSecurityGroupIds = a}) . _Default . _Coerce
rSecurityGroups :: Lens' ResponseLaunchTemplateData [Text]
rSecurityGroups = lens _rSecurityGroups (\ s a -> s{_rSecurityGroups = a}) . _Default . _Coerce
rInstanceMarketOptions :: Lens' ResponseLaunchTemplateData (Maybe LaunchTemplateInstanceMarketOptions)
rInstanceMarketOptions = lens _rInstanceMarketOptions (\ s a -> s{_rInstanceMarketOptions = a})
rDisableAPITermination :: Lens' ResponseLaunchTemplateData (Maybe Bool)
rDisableAPITermination = lens _rDisableAPITermination (\ s a -> s{_rDisableAPITermination = a})
rKeyName :: Lens' ResponseLaunchTemplateData (Maybe Text)
rKeyName = lens _rKeyName (\ s a -> s{_rKeyName = a})
rNetworkInterfaces :: Lens' ResponseLaunchTemplateData [LaunchTemplateInstanceNetworkInterfaceSpecification]
rNetworkInterfaces = lens _rNetworkInterfaces (\ s a -> s{_rNetworkInterfaces = a}) . _Default . _Coerce
rRamDiskId :: Lens' ResponseLaunchTemplateData (Maybe Text)
rRamDiskId = lens _rRamDiskId (\ s a -> s{_rRamDiskId = a})
rKernelId :: Lens' ResponseLaunchTemplateData (Maybe Text)
rKernelId = lens _rKernelId (\ s a -> s{_rKernelId = a})
rElasticGpuSpecifications :: Lens' ResponseLaunchTemplateData [ElasticGpuSpecificationResponse]
rElasticGpuSpecifications = lens _rElasticGpuSpecifications (\ s a -> s{_rElasticGpuSpecifications = a}) . _Default . _Coerce
rInstanceType :: Lens' ResponseLaunchTemplateData (Maybe InstanceType)
rInstanceType = lens _rInstanceType (\ s a -> s{_rInstanceType = a})
rEBSOptimized :: Lens' ResponseLaunchTemplateData (Maybe Bool)
rEBSOptimized = lens _rEBSOptimized (\ s a -> s{_rEBSOptimized = a})
rUserData :: Lens' ResponseLaunchTemplateData (Maybe Text)
rUserData = lens _rUserData (\ s a -> s{_rUserData = a})
rMonitoring :: Lens' ResponseLaunchTemplateData (Maybe LaunchTemplatesMonitoring)
rMonitoring = lens _rMonitoring (\ s a -> s{_rMonitoring = a})
rTagSpecifications :: Lens' ResponseLaunchTemplateData [LaunchTemplateTagSpecification]
rTagSpecifications = lens _rTagSpecifications (\ s a -> s{_rTagSpecifications = a}) . _Default . _Coerce
rIAMInstanceProfile :: Lens' ResponseLaunchTemplateData (Maybe LaunchTemplateIAMInstanceProfileSpecification)
rIAMInstanceProfile = lens _rIAMInstanceProfile (\ s a -> s{_rIAMInstanceProfile = a})
rImageId :: Lens' ResponseLaunchTemplateData (Maybe Text)
rImageId = lens _rImageId (\ s a -> s{_rImageId = a})
rInstanceInitiatedShutdownBehavior :: Lens' ResponseLaunchTemplateData (Maybe ShutdownBehavior)
rInstanceInitiatedShutdownBehavior = lens _rInstanceInitiatedShutdownBehavior (\ s a -> s{_rInstanceInitiatedShutdownBehavior = a})
rCreditSpecification :: Lens' ResponseLaunchTemplateData (Maybe CreditSpecification)
rCreditSpecification = lens _rCreditSpecification (\ s a -> s{_rCreditSpecification = a})
rBlockDeviceMappings :: Lens' ResponseLaunchTemplateData [LaunchTemplateBlockDeviceMapping]
rBlockDeviceMappings = lens _rBlockDeviceMappings (\ s a -> s{_rBlockDeviceMappings = a}) . _Default . _Coerce
rPlacement :: Lens' ResponseLaunchTemplateData (Maybe LaunchTemplatePlacement)
rPlacement = lens _rPlacement (\ s a -> s{_rPlacement = a})
instance FromXML ResponseLaunchTemplateData where
parseXML x
= ResponseLaunchTemplateData' <$>
(x .@? "securityGroupIdSet" .!@ mempty >>=
may (parseXMLList "item"))
<*>
(x .@? "securityGroupSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "instanceMarketOptions")
<*> (x .@? "disableApiTermination")
<*> (x .@? "keyName")
<*>
(x .@? "networkInterfaceSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "ramDiskId")
<*> (x .@? "kernelId")
<*>
(x .@? "elasticGpuSpecificationSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "instanceType")
<*> (x .@? "ebsOptimized")
<*> (x .@? "userData")
<*> (x .@? "monitoring")
<*>
(x .@? "tagSpecificationSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "iamInstanceProfile")
<*> (x .@? "imageId")
<*> (x .@? "instanceInitiatedShutdownBehavior")
<*> (x .@? "creditSpecification")
<*>
(x .@? "blockDeviceMappingSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "placement")
instance Hashable ResponseLaunchTemplateData where
instance NFData ResponseLaunchTemplateData where
data Route = Route'
{ _rVPCPeeringConnectionId :: !(Maybe Text)
, _rInstanceId :: !(Maybe Text)
, _rOrigin :: !(Maybe RouteOrigin)
, _rState :: !(Maybe RouteState)
, _rEgressOnlyInternetGatewayId :: !(Maybe Text)
, _rDestinationIPv6CidrBlock :: !(Maybe Text)
, _rNatGatewayId :: !(Maybe Text)
, _rNetworkInterfaceId :: !(Maybe Text)
, _rGatewayId :: !(Maybe Text)
, _rInstanceOwnerId :: !(Maybe Text)
, _rDestinationPrefixListId :: !(Maybe Text)
, _rDestinationCidrBlock :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
route
:: Route
route =
Route'
{ _rVPCPeeringConnectionId = Nothing
, _rInstanceId = Nothing
, _rOrigin = Nothing
, _rState = Nothing
, _rEgressOnlyInternetGatewayId = Nothing
, _rDestinationIPv6CidrBlock = Nothing
, _rNatGatewayId = Nothing
, _rNetworkInterfaceId = Nothing
, _rGatewayId = Nothing
, _rInstanceOwnerId = Nothing
, _rDestinationPrefixListId = Nothing
, _rDestinationCidrBlock = Nothing
}
rVPCPeeringConnectionId :: Lens' Route (Maybe Text)
rVPCPeeringConnectionId = lens _rVPCPeeringConnectionId (\ s a -> s{_rVPCPeeringConnectionId = a})
rInstanceId :: Lens' Route (Maybe Text)
rInstanceId = lens _rInstanceId (\ s a -> s{_rInstanceId = a})
rOrigin :: Lens' Route (Maybe RouteOrigin)
rOrigin = lens _rOrigin (\ s a -> s{_rOrigin = a})
rState :: Lens' Route (Maybe RouteState)
rState = lens _rState (\ s a -> s{_rState = a})
rEgressOnlyInternetGatewayId :: Lens' Route (Maybe Text)
rEgressOnlyInternetGatewayId = lens _rEgressOnlyInternetGatewayId (\ s a -> s{_rEgressOnlyInternetGatewayId = a})
rDestinationIPv6CidrBlock :: Lens' Route (Maybe Text)
rDestinationIPv6CidrBlock = lens _rDestinationIPv6CidrBlock (\ s a -> s{_rDestinationIPv6CidrBlock = a})
rNatGatewayId :: Lens' Route (Maybe Text)
rNatGatewayId = lens _rNatGatewayId (\ s a -> s{_rNatGatewayId = a})
rNetworkInterfaceId :: Lens' Route (Maybe Text)
rNetworkInterfaceId = lens _rNetworkInterfaceId (\ s a -> s{_rNetworkInterfaceId = a})
rGatewayId :: Lens' Route (Maybe Text)
rGatewayId = lens _rGatewayId (\ s a -> s{_rGatewayId = a})
rInstanceOwnerId :: Lens' Route (Maybe Text)
rInstanceOwnerId = lens _rInstanceOwnerId (\ s a -> s{_rInstanceOwnerId = a})
rDestinationPrefixListId :: Lens' Route (Maybe Text)
rDestinationPrefixListId = lens _rDestinationPrefixListId (\ s a -> s{_rDestinationPrefixListId = a})
rDestinationCidrBlock :: Lens' Route (Maybe Text)
rDestinationCidrBlock = lens _rDestinationCidrBlock (\ s a -> s{_rDestinationCidrBlock = a})
instance FromXML Route where
parseXML x
= Route' <$>
(x .@? "vpcPeeringConnectionId") <*>
(x .@? "instanceId")
<*> (x .@? "origin")
<*> (x .@? "state")
<*> (x .@? "egressOnlyInternetGatewayId")
<*> (x .@? "destinationIpv6CidrBlock")
<*> (x .@? "natGatewayId")
<*> (x .@? "networkInterfaceId")
<*> (x .@? "gatewayId")
<*> (x .@? "instanceOwnerId")
<*> (x .@? "destinationPrefixListId")
<*> (x .@? "destinationCidrBlock")
instance Hashable Route where
instance NFData Route where
data RouteTable = RouteTable'
{ _rtRouteTableId :: !(Maybe Text)
, _rtRoutes :: !(Maybe [Route])
, _rtVPCId :: !(Maybe Text)
, _rtPropagatingVGWs :: !(Maybe [PropagatingVGW])
, _rtAssociations :: !(Maybe [RouteTableAssociation])
, _rtTags :: !(Maybe [Tag])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
routeTable
:: RouteTable
routeTable =
RouteTable'
{ _rtRouteTableId = Nothing
, _rtRoutes = Nothing
, _rtVPCId = Nothing
, _rtPropagatingVGWs = Nothing
, _rtAssociations = Nothing
, _rtTags = Nothing
}
rtRouteTableId :: Lens' RouteTable (Maybe Text)
rtRouteTableId = lens _rtRouteTableId (\ s a -> s{_rtRouteTableId = a})
rtRoutes :: Lens' RouteTable [Route]
rtRoutes = lens _rtRoutes (\ s a -> s{_rtRoutes = a}) . _Default . _Coerce
rtVPCId :: Lens' RouteTable (Maybe Text)
rtVPCId = lens _rtVPCId (\ s a -> s{_rtVPCId = a})
rtPropagatingVGWs :: Lens' RouteTable [PropagatingVGW]
rtPropagatingVGWs = lens _rtPropagatingVGWs (\ s a -> s{_rtPropagatingVGWs = a}) . _Default . _Coerce
rtAssociations :: Lens' RouteTable [RouteTableAssociation]
rtAssociations = lens _rtAssociations (\ s a -> s{_rtAssociations = a}) . _Default . _Coerce
rtTags :: Lens' RouteTable [Tag]
rtTags = lens _rtTags (\ s a -> s{_rtTags = a}) . _Default . _Coerce
instance FromXML RouteTable where
parseXML x
= RouteTable' <$>
(x .@? "routeTableId") <*>
(x .@? "routeSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "vpcId")
<*>
(x .@? "propagatingVgwSet" .!@ mempty >>=
may (parseXMLList "item"))
<*>
(x .@? "associationSet" .!@ mempty >>=
may (parseXMLList "item"))
<*>
(x .@? "tagSet" .!@ mempty >>=
may (parseXMLList "item"))
instance Hashable RouteTable where
instance NFData RouteTable where
data RouteTableAssociation = RouteTableAssociation'
{ _rtaRouteTableId :: !(Maybe Text)
, _rtaRouteTableAssociationId :: !(Maybe Text)
, _rtaMain :: !(Maybe Bool)
, _rtaSubnetId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
routeTableAssociation
:: RouteTableAssociation
routeTableAssociation =
RouteTableAssociation'
{ _rtaRouteTableId = Nothing
, _rtaRouteTableAssociationId = Nothing
, _rtaMain = Nothing
, _rtaSubnetId = Nothing
}
rtaRouteTableId :: Lens' RouteTableAssociation (Maybe Text)
rtaRouteTableId = lens _rtaRouteTableId (\ s a -> s{_rtaRouteTableId = a})
rtaRouteTableAssociationId :: Lens' RouteTableAssociation (Maybe Text)
rtaRouteTableAssociationId = lens _rtaRouteTableAssociationId (\ s a -> s{_rtaRouteTableAssociationId = a})
rtaMain :: Lens' RouteTableAssociation (Maybe Bool)
rtaMain = lens _rtaMain (\ s a -> s{_rtaMain = a})
rtaSubnetId :: Lens' RouteTableAssociation (Maybe Text)
rtaSubnetId = lens _rtaSubnetId (\ s a -> s{_rtaSubnetId = a})
instance FromXML RouteTableAssociation where
parseXML x
= RouteTableAssociation' <$>
(x .@? "routeTableId") <*>
(x .@? "routeTableAssociationId")
<*> (x .@? "main")
<*> (x .@? "subnetId")
instance Hashable RouteTableAssociation where
instance NFData RouteTableAssociation where
newtype RunInstancesMonitoringEnabled = RunInstancesMonitoringEnabled'
{ _rimeEnabled :: Bool
} deriving (Eq, Read, Show, Data, Typeable, Generic)
runInstancesMonitoringEnabled
:: Bool
-> RunInstancesMonitoringEnabled
runInstancesMonitoringEnabled pEnabled_ =
RunInstancesMonitoringEnabled' {_rimeEnabled = pEnabled_}
rimeEnabled :: Lens' RunInstancesMonitoringEnabled Bool
rimeEnabled = lens _rimeEnabled (\ s a -> s{_rimeEnabled = a})
instance FromXML RunInstancesMonitoringEnabled where
parseXML x
= RunInstancesMonitoringEnabled' <$> (x .@ "enabled")
instance Hashable RunInstancesMonitoringEnabled where
instance NFData RunInstancesMonitoringEnabled where
instance ToQuery RunInstancesMonitoringEnabled where
toQuery RunInstancesMonitoringEnabled'{..}
= mconcat ["Enabled" =: _rimeEnabled]
data S3Storage = S3Storage'
{ _ssPrefix :: !(Maybe Text)
, _ssUploadPolicy :: !(Maybe Base64)
, _ssBucket :: !(Maybe Text)
, _ssUploadPolicySignature :: !(Maybe Text)
, _ssAWSAccessKeyId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
s3Storage
:: S3Storage
s3Storage =
S3Storage'
{ _ssPrefix = Nothing
, _ssUploadPolicy = Nothing
, _ssBucket = Nothing
, _ssUploadPolicySignature = Nothing
, _ssAWSAccessKeyId = Nothing
}
ssPrefix :: Lens' S3Storage (Maybe Text)
ssPrefix = lens _ssPrefix (\ s a -> s{_ssPrefix = a})
ssUploadPolicy :: Lens' S3Storage (Maybe ByteString)
ssUploadPolicy = lens _ssUploadPolicy (\ s a -> s{_ssUploadPolicy = a}) . mapping _Base64
ssBucket :: Lens' S3Storage (Maybe Text)
ssBucket = lens _ssBucket (\ s a -> s{_ssBucket = a})
ssUploadPolicySignature :: Lens' S3Storage (Maybe Text)
ssUploadPolicySignature = lens _ssUploadPolicySignature (\ s a -> s{_ssUploadPolicySignature = a})
ssAWSAccessKeyId :: Lens' S3Storage (Maybe Text)
ssAWSAccessKeyId = lens _ssAWSAccessKeyId (\ s a -> s{_ssAWSAccessKeyId = a})
instance FromXML S3Storage where
parseXML x
= S3Storage' <$>
(x .@? "prefix") <*> (x .@? "uploadPolicy") <*>
(x .@? "bucket")
<*> (x .@? "uploadPolicySignature")
<*> (x .@? "AWSAccessKeyId")
instance Hashable S3Storage where
instance NFData S3Storage where
instance ToQuery S3Storage where
toQuery S3Storage'{..}
= mconcat
["Prefix" =: _ssPrefix,
"UploadPolicy" =: _ssUploadPolicy,
"Bucket" =: _ssBucket,
"UploadPolicySignature" =: _ssUploadPolicySignature,
"AWSAccessKeyId" =: _ssAWSAccessKeyId]
data ScheduledInstance = ScheduledInstance'
{ _siPreviousSlotEndTime :: !(Maybe ISO8601)
, _siPlatform :: !(Maybe Text)
, _siTermStartDate :: !(Maybe ISO8601)
, _siInstanceCount :: !(Maybe Int)
, _siScheduledInstanceId :: !(Maybe Text)
, _siHourlyPrice :: !(Maybe Text)
, _siCreateDate :: !(Maybe ISO8601)
, _siSlotDurationInHours :: !(Maybe Int)
, _siTotalScheduledInstanceHours :: !(Maybe Int)
, _siInstanceType :: !(Maybe Text)
, _siRecurrence :: !(Maybe ScheduledInstanceRecurrence)
, _siAvailabilityZone :: !(Maybe Text)
, _siTermEndDate :: !(Maybe ISO8601)
, _siNextSlotStartTime :: !(Maybe ISO8601)
, _siNetworkPlatform :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
scheduledInstance
:: ScheduledInstance
scheduledInstance =
ScheduledInstance'
{ _siPreviousSlotEndTime = Nothing
, _siPlatform = Nothing
, _siTermStartDate = Nothing
, _siInstanceCount = Nothing
, _siScheduledInstanceId = Nothing
, _siHourlyPrice = Nothing
, _siCreateDate = Nothing
, _siSlotDurationInHours = Nothing
, _siTotalScheduledInstanceHours = Nothing
, _siInstanceType = Nothing
, _siRecurrence = Nothing
, _siAvailabilityZone = Nothing
, _siTermEndDate = Nothing
, _siNextSlotStartTime = Nothing
, _siNetworkPlatform = Nothing
}
siPreviousSlotEndTime :: Lens' ScheduledInstance (Maybe UTCTime)
siPreviousSlotEndTime = lens _siPreviousSlotEndTime (\ s a -> s{_siPreviousSlotEndTime = a}) . mapping _Time
siPlatform :: Lens' ScheduledInstance (Maybe Text)
siPlatform = lens _siPlatform (\ s a -> s{_siPlatform = a})
siTermStartDate :: Lens' ScheduledInstance (Maybe UTCTime)
siTermStartDate = lens _siTermStartDate (\ s a -> s{_siTermStartDate = a}) . mapping _Time
siInstanceCount :: Lens' ScheduledInstance (Maybe Int)
siInstanceCount = lens _siInstanceCount (\ s a -> s{_siInstanceCount = a})
siScheduledInstanceId :: Lens' ScheduledInstance (Maybe Text)
siScheduledInstanceId = lens _siScheduledInstanceId (\ s a -> s{_siScheduledInstanceId = a})
siHourlyPrice :: Lens' ScheduledInstance (Maybe Text)
siHourlyPrice = lens _siHourlyPrice (\ s a -> s{_siHourlyPrice = a})
siCreateDate :: Lens' ScheduledInstance (Maybe UTCTime)
siCreateDate = lens _siCreateDate (\ s a -> s{_siCreateDate = a}) . mapping _Time
siSlotDurationInHours :: Lens' ScheduledInstance (Maybe Int)
siSlotDurationInHours = lens _siSlotDurationInHours (\ s a -> s{_siSlotDurationInHours = a})
siTotalScheduledInstanceHours :: Lens' ScheduledInstance (Maybe Int)
siTotalScheduledInstanceHours = lens _siTotalScheduledInstanceHours (\ s a -> s{_siTotalScheduledInstanceHours = a})
siInstanceType :: Lens' ScheduledInstance (Maybe Text)
siInstanceType = lens _siInstanceType (\ s a -> s{_siInstanceType = a})
siRecurrence :: Lens' ScheduledInstance (Maybe ScheduledInstanceRecurrence)
siRecurrence = lens _siRecurrence (\ s a -> s{_siRecurrence = a})
siAvailabilityZone :: Lens' ScheduledInstance (Maybe Text)
siAvailabilityZone = lens _siAvailabilityZone (\ s a -> s{_siAvailabilityZone = a})
siTermEndDate :: Lens' ScheduledInstance (Maybe UTCTime)
siTermEndDate = lens _siTermEndDate (\ s a -> s{_siTermEndDate = a}) . mapping _Time
siNextSlotStartTime :: Lens' ScheduledInstance (Maybe UTCTime)
siNextSlotStartTime = lens _siNextSlotStartTime (\ s a -> s{_siNextSlotStartTime = a}) . mapping _Time
siNetworkPlatform :: Lens' ScheduledInstance (Maybe Text)
siNetworkPlatform = lens _siNetworkPlatform (\ s a -> s{_siNetworkPlatform = a})
instance FromXML ScheduledInstance where
parseXML x
= ScheduledInstance' <$>
(x .@? "previousSlotEndTime") <*> (x .@? "platform")
<*> (x .@? "termStartDate")
<*> (x .@? "instanceCount")
<*> (x .@? "scheduledInstanceId")
<*> (x .@? "hourlyPrice")
<*> (x .@? "createDate")
<*> (x .@? "slotDurationInHours")
<*> (x .@? "totalScheduledInstanceHours")
<*> (x .@? "instanceType")
<*> (x .@? "recurrence")
<*> (x .@? "availabilityZone")
<*> (x .@? "termEndDate")
<*> (x .@? "nextSlotStartTime")
<*> (x .@? "networkPlatform")
instance Hashable ScheduledInstance where
instance NFData ScheduledInstance where
data ScheduledInstanceAvailability = ScheduledInstanceAvailability'
{ _siaMaxTermDurationInDays :: !(Maybe Int)
, _siaPlatform :: !(Maybe Text)
, _siaPurchaseToken :: !(Maybe Text)
, _siaHourlyPrice :: !(Maybe Text)
, _siaAvailableInstanceCount :: !(Maybe Int)
, _siaSlotDurationInHours :: !(Maybe Int)
, _siaTotalScheduledInstanceHours :: !(Maybe Int)
, _siaInstanceType :: !(Maybe Text)
, _siaRecurrence :: !(Maybe ScheduledInstanceRecurrence)
, _siaAvailabilityZone :: !(Maybe Text)
, _siaMinTermDurationInDays :: !(Maybe Int)
, _siaFirstSlotStartTime :: !(Maybe ISO8601)
, _siaNetworkPlatform :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
scheduledInstanceAvailability
:: ScheduledInstanceAvailability
scheduledInstanceAvailability =
ScheduledInstanceAvailability'
{ _siaMaxTermDurationInDays = Nothing
, _siaPlatform = Nothing
, _siaPurchaseToken = Nothing
, _siaHourlyPrice = Nothing
, _siaAvailableInstanceCount = Nothing
, _siaSlotDurationInHours = Nothing
, _siaTotalScheduledInstanceHours = Nothing
, _siaInstanceType = Nothing
, _siaRecurrence = Nothing
, _siaAvailabilityZone = Nothing
, _siaMinTermDurationInDays = Nothing
, _siaFirstSlotStartTime = Nothing
, _siaNetworkPlatform = Nothing
}
siaMaxTermDurationInDays :: Lens' ScheduledInstanceAvailability (Maybe Int)
siaMaxTermDurationInDays = lens _siaMaxTermDurationInDays (\ s a -> s{_siaMaxTermDurationInDays = a})
siaPlatform :: Lens' ScheduledInstanceAvailability (Maybe Text)
siaPlatform = lens _siaPlatform (\ s a -> s{_siaPlatform = a})
siaPurchaseToken :: Lens' ScheduledInstanceAvailability (Maybe Text)
siaPurchaseToken = lens _siaPurchaseToken (\ s a -> s{_siaPurchaseToken = a})
siaHourlyPrice :: Lens' ScheduledInstanceAvailability (Maybe Text)
siaHourlyPrice = lens _siaHourlyPrice (\ s a -> s{_siaHourlyPrice = a})
siaAvailableInstanceCount :: Lens' ScheduledInstanceAvailability (Maybe Int)
siaAvailableInstanceCount = lens _siaAvailableInstanceCount (\ s a -> s{_siaAvailableInstanceCount = a})
siaSlotDurationInHours :: Lens' ScheduledInstanceAvailability (Maybe Int)
siaSlotDurationInHours = lens _siaSlotDurationInHours (\ s a -> s{_siaSlotDurationInHours = a})
siaTotalScheduledInstanceHours :: Lens' ScheduledInstanceAvailability (Maybe Int)
siaTotalScheduledInstanceHours = lens _siaTotalScheduledInstanceHours (\ s a -> s{_siaTotalScheduledInstanceHours = a})
siaInstanceType :: Lens' ScheduledInstanceAvailability (Maybe Text)
siaInstanceType = lens _siaInstanceType (\ s a -> s{_siaInstanceType = a})
siaRecurrence :: Lens' ScheduledInstanceAvailability (Maybe ScheduledInstanceRecurrence)
siaRecurrence = lens _siaRecurrence (\ s a -> s{_siaRecurrence = a})
siaAvailabilityZone :: Lens' ScheduledInstanceAvailability (Maybe Text)
siaAvailabilityZone = lens _siaAvailabilityZone (\ s a -> s{_siaAvailabilityZone = a})
siaMinTermDurationInDays :: Lens' ScheduledInstanceAvailability (Maybe Int)
siaMinTermDurationInDays = lens _siaMinTermDurationInDays (\ s a -> s{_siaMinTermDurationInDays = a})
siaFirstSlotStartTime :: Lens' ScheduledInstanceAvailability (Maybe UTCTime)
siaFirstSlotStartTime = lens _siaFirstSlotStartTime (\ s a -> s{_siaFirstSlotStartTime = a}) . mapping _Time
siaNetworkPlatform :: Lens' ScheduledInstanceAvailability (Maybe Text)
siaNetworkPlatform = lens _siaNetworkPlatform (\ s a -> s{_siaNetworkPlatform = a})
instance FromXML ScheduledInstanceAvailability where
parseXML x
= ScheduledInstanceAvailability' <$>
(x .@? "maxTermDurationInDays") <*>
(x .@? "platform")
<*> (x .@? "purchaseToken")
<*> (x .@? "hourlyPrice")
<*> (x .@? "availableInstanceCount")
<*> (x .@? "slotDurationInHours")
<*> (x .@? "totalScheduledInstanceHours")
<*> (x .@? "instanceType")
<*> (x .@? "recurrence")
<*> (x .@? "availabilityZone")
<*> (x .@? "minTermDurationInDays")
<*> (x .@? "firstSlotStartTime")
<*> (x .@? "networkPlatform")
instance Hashable ScheduledInstanceAvailability where
instance NFData ScheduledInstanceAvailability where
data ScheduledInstanceRecurrence = ScheduledInstanceRecurrence'
{ _sirFrequency :: !(Maybe Text)
, _sirOccurrenceRelativeToEnd :: !(Maybe Bool)
, _sirOccurrenceUnit :: !(Maybe Text)
, _sirInterval :: !(Maybe Int)
, _sirOccurrenceDaySet :: !(Maybe [Int])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
scheduledInstanceRecurrence
:: ScheduledInstanceRecurrence
scheduledInstanceRecurrence =
ScheduledInstanceRecurrence'
{ _sirFrequency = Nothing
, _sirOccurrenceRelativeToEnd = Nothing
, _sirOccurrenceUnit = Nothing
, _sirInterval = Nothing
, _sirOccurrenceDaySet = Nothing
}
sirFrequency :: Lens' ScheduledInstanceRecurrence (Maybe Text)
sirFrequency = lens _sirFrequency (\ s a -> s{_sirFrequency = a})
sirOccurrenceRelativeToEnd :: Lens' ScheduledInstanceRecurrence (Maybe Bool)
sirOccurrenceRelativeToEnd = lens _sirOccurrenceRelativeToEnd (\ s a -> s{_sirOccurrenceRelativeToEnd = a})
sirOccurrenceUnit :: Lens' ScheduledInstanceRecurrence (Maybe Text)
sirOccurrenceUnit = lens _sirOccurrenceUnit (\ s a -> s{_sirOccurrenceUnit = a})
sirInterval :: Lens' ScheduledInstanceRecurrence (Maybe Int)
sirInterval = lens _sirInterval (\ s a -> s{_sirInterval = a})
sirOccurrenceDaySet :: Lens' ScheduledInstanceRecurrence [Int]
sirOccurrenceDaySet = lens _sirOccurrenceDaySet (\ s a -> s{_sirOccurrenceDaySet = a}) . _Default . _Coerce
instance FromXML ScheduledInstanceRecurrence where
parseXML x
= ScheduledInstanceRecurrence' <$>
(x .@? "frequency") <*>
(x .@? "occurrenceRelativeToEnd")
<*> (x .@? "occurrenceUnit")
<*> (x .@? "interval")
<*>
(x .@? "occurrenceDaySet" .!@ mempty >>=
may (parseXMLList "item"))
instance Hashable ScheduledInstanceRecurrence where
instance NFData ScheduledInstanceRecurrence where
data ScheduledInstanceRecurrenceRequest = ScheduledInstanceRecurrenceRequest'
{ _sirrFrequency :: !(Maybe Text)
, _sirrOccurrenceRelativeToEnd :: !(Maybe Bool)
, _sirrOccurrenceDays :: !(Maybe [Int])
, _sirrOccurrenceUnit :: !(Maybe Text)
, _sirrInterval :: !(Maybe Int)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
scheduledInstanceRecurrenceRequest
:: ScheduledInstanceRecurrenceRequest
scheduledInstanceRecurrenceRequest =
ScheduledInstanceRecurrenceRequest'
{ _sirrFrequency = Nothing
, _sirrOccurrenceRelativeToEnd = Nothing
, _sirrOccurrenceDays = Nothing
, _sirrOccurrenceUnit = Nothing
, _sirrInterval = Nothing
}
sirrFrequency :: Lens' ScheduledInstanceRecurrenceRequest (Maybe Text)
sirrFrequency = lens _sirrFrequency (\ s a -> s{_sirrFrequency = a})
sirrOccurrenceRelativeToEnd :: Lens' ScheduledInstanceRecurrenceRequest (Maybe Bool)
sirrOccurrenceRelativeToEnd = lens _sirrOccurrenceRelativeToEnd (\ s a -> s{_sirrOccurrenceRelativeToEnd = a})
sirrOccurrenceDays :: Lens' ScheduledInstanceRecurrenceRequest [Int]
sirrOccurrenceDays = lens _sirrOccurrenceDays (\ s a -> s{_sirrOccurrenceDays = a}) . _Default . _Coerce
sirrOccurrenceUnit :: Lens' ScheduledInstanceRecurrenceRequest (Maybe Text)
sirrOccurrenceUnit = lens _sirrOccurrenceUnit (\ s a -> s{_sirrOccurrenceUnit = a})
sirrInterval :: Lens' ScheduledInstanceRecurrenceRequest (Maybe Int)
sirrInterval = lens _sirrInterval (\ s a -> s{_sirrInterval = a})
instance Hashable ScheduledInstanceRecurrenceRequest
where
instance NFData ScheduledInstanceRecurrenceRequest
where
instance ToQuery ScheduledInstanceRecurrenceRequest
where
toQuery ScheduledInstanceRecurrenceRequest'{..}
= mconcat
["Frequency" =: _sirrFrequency,
"OccurrenceRelativeToEnd" =:
_sirrOccurrenceRelativeToEnd,
toQuery
(toQueryList "OccurrenceDay" <$>
_sirrOccurrenceDays),
"OccurrenceUnit" =: _sirrOccurrenceUnit,
"Interval" =: _sirrInterval]
data ScheduledInstancesBlockDeviceMapping = ScheduledInstancesBlockDeviceMapping'
{ _sibdmVirtualName :: !(Maybe Text)
, _sibdmNoDevice :: !(Maybe Text)
, _sibdmEBS :: !(Maybe ScheduledInstancesEBS)
, _sibdmDeviceName :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
scheduledInstancesBlockDeviceMapping
:: ScheduledInstancesBlockDeviceMapping
scheduledInstancesBlockDeviceMapping =
ScheduledInstancesBlockDeviceMapping'
{ _sibdmVirtualName = Nothing
, _sibdmNoDevice = Nothing
, _sibdmEBS = Nothing
, _sibdmDeviceName = Nothing
}
sibdmVirtualName :: Lens' ScheduledInstancesBlockDeviceMapping (Maybe Text)
sibdmVirtualName = lens _sibdmVirtualName (\ s a -> s{_sibdmVirtualName = a})
sibdmNoDevice :: Lens' ScheduledInstancesBlockDeviceMapping (Maybe Text)
sibdmNoDevice = lens _sibdmNoDevice (\ s a -> s{_sibdmNoDevice = a})
sibdmEBS :: Lens' ScheduledInstancesBlockDeviceMapping (Maybe ScheduledInstancesEBS)
sibdmEBS = lens _sibdmEBS (\ s a -> s{_sibdmEBS = a})
sibdmDeviceName :: Lens' ScheduledInstancesBlockDeviceMapping (Maybe Text)
sibdmDeviceName = lens _sibdmDeviceName (\ s a -> s{_sibdmDeviceName = a})
instance Hashable
ScheduledInstancesBlockDeviceMapping
where
instance NFData ScheduledInstancesBlockDeviceMapping
where
instance ToQuery ScheduledInstancesBlockDeviceMapping
where
toQuery ScheduledInstancesBlockDeviceMapping'{..}
= mconcat
["VirtualName" =: _sibdmVirtualName,
"NoDevice" =: _sibdmNoDevice, "Ebs" =: _sibdmEBS,
"DeviceName" =: _sibdmDeviceName]
data ScheduledInstancesEBS = ScheduledInstancesEBS'
{ _sieDeleteOnTermination :: !(Maybe Bool)
, _sieVolumeSize :: !(Maybe Int)
, _sieIOPS :: !(Maybe Int)
, _sieEncrypted :: !(Maybe Bool)
, _sieVolumeType :: !(Maybe Text)
, _sieSnapshotId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
scheduledInstancesEBS
:: ScheduledInstancesEBS
scheduledInstancesEBS =
ScheduledInstancesEBS'
{ _sieDeleteOnTermination = Nothing
, _sieVolumeSize = Nothing
, _sieIOPS = Nothing
, _sieEncrypted = Nothing
, _sieVolumeType = Nothing
, _sieSnapshotId = Nothing
}
sieDeleteOnTermination :: Lens' ScheduledInstancesEBS (Maybe Bool)
sieDeleteOnTermination = lens _sieDeleteOnTermination (\ s a -> s{_sieDeleteOnTermination = a})
sieVolumeSize :: Lens' ScheduledInstancesEBS (Maybe Int)
sieVolumeSize = lens _sieVolumeSize (\ s a -> s{_sieVolumeSize = a})
sieIOPS :: Lens' ScheduledInstancesEBS (Maybe Int)
sieIOPS = lens _sieIOPS (\ s a -> s{_sieIOPS = a})
sieEncrypted :: Lens' ScheduledInstancesEBS (Maybe Bool)
sieEncrypted = lens _sieEncrypted (\ s a -> s{_sieEncrypted = a})
sieVolumeType :: Lens' ScheduledInstancesEBS (Maybe Text)
sieVolumeType = lens _sieVolumeType (\ s a -> s{_sieVolumeType = a})
sieSnapshotId :: Lens' ScheduledInstancesEBS (Maybe Text)
sieSnapshotId = lens _sieSnapshotId (\ s a -> s{_sieSnapshotId = a})
instance Hashable ScheduledInstancesEBS where
instance NFData ScheduledInstancesEBS where
instance ToQuery ScheduledInstancesEBS where
toQuery ScheduledInstancesEBS'{..}
= mconcat
["DeleteOnTermination" =: _sieDeleteOnTermination,
"VolumeSize" =: _sieVolumeSize, "Iops" =: _sieIOPS,
"Encrypted" =: _sieEncrypted,
"VolumeType" =: _sieVolumeType,
"SnapshotId" =: _sieSnapshotId]
data ScheduledInstancesIAMInstanceProfile = ScheduledInstancesIAMInstanceProfile'
{ _siiapARN :: !(Maybe Text)
, _siiapName :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
scheduledInstancesIAMInstanceProfile
:: ScheduledInstancesIAMInstanceProfile
scheduledInstancesIAMInstanceProfile =
ScheduledInstancesIAMInstanceProfile'
{_siiapARN = Nothing, _siiapName = Nothing}
siiapARN :: Lens' ScheduledInstancesIAMInstanceProfile (Maybe Text)
siiapARN = lens _siiapARN (\ s a -> s{_siiapARN = a})
siiapName :: Lens' ScheduledInstancesIAMInstanceProfile (Maybe Text)
siiapName = lens _siiapName (\ s a -> s{_siiapName = a})
instance Hashable
ScheduledInstancesIAMInstanceProfile
where
instance NFData ScheduledInstancesIAMInstanceProfile
where
instance ToQuery ScheduledInstancesIAMInstanceProfile
where
toQuery ScheduledInstancesIAMInstanceProfile'{..}
= mconcat ["Arn" =: _siiapARN, "Name" =: _siiapName]
newtype ScheduledInstancesIPv6Address = ScheduledInstancesIPv6Address'
{ _siiaIPv6Address :: Maybe Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
scheduledInstancesIPv6Address
:: ScheduledInstancesIPv6Address
scheduledInstancesIPv6Address =
ScheduledInstancesIPv6Address' {_siiaIPv6Address = Nothing}
siiaIPv6Address :: Lens' ScheduledInstancesIPv6Address (Maybe Text)
siiaIPv6Address = lens _siiaIPv6Address (\ s a -> s{_siiaIPv6Address = a})
instance Hashable ScheduledInstancesIPv6Address where
instance NFData ScheduledInstancesIPv6Address where
instance ToQuery ScheduledInstancesIPv6Address where
toQuery ScheduledInstancesIPv6Address'{..}
= mconcat ["Ipv6Address" =: _siiaIPv6Address]
data ScheduledInstancesLaunchSpecification = ScheduledInstancesLaunchSpecification'
{ _silsSecurityGroupIds :: !(Maybe [Text])
, _silsKeyName :: !(Maybe Text)
, _silsNetworkInterfaces :: !(Maybe [ScheduledInstancesNetworkInterface])
, _silsRAMDiskId :: !(Maybe Text)
, _silsSubnetId :: !(Maybe Text)
, _silsKernelId :: !(Maybe Text)
, _silsInstanceType :: !(Maybe Text)
, _silsEBSOptimized :: !(Maybe Bool)
, _silsUserData :: !(Maybe Text)
, _silsMonitoring :: !(Maybe ScheduledInstancesMonitoring)
, _silsIAMInstanceProfile :: !(Maybe ScheduledInstancesIAMInstanceProfile)
, _silsBlockDeviceMappings :: !(Maybe [ScheduledInstancesBlockDeviceMapping])
, _silsPlacement :: !(Maybe ScheduledInstancesPlacement)
, _silsImageId :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
scheduledInstancesLaunchSpecification
:: Text
-> ScheduledInstancesLaunchSpecification
scheduledInstancesLaunchSpecification pImageId_ =
ScheduledInstancesLaunchSpecification'
{ _silsSecurityGroupIds = Nothing
, _silsKeyName = Nothing
, _silsNetworkInterfaces = Nothing
, _silsRAMDiskId = Nothing
, _silsSubnetId = Nothing
, _silsKernelId = Nothing
, _silsInstanceType = Nothing
, _silsEBSOptimized = Nothing
, _silsUserData = Nothing
, _silsMonitoring = Nothing
, _silsIAMInstanceProfile = Nothing
, _silsBlockDeviceMappings = Nothing
, _silsPlacement = Nothing
, _silsImageId = pImageId_
}
silsSecurityGroupIds :: Lens' ScheduledInstancesLaunchSpecification [Text]
silsSecurityGroupIds = lens _silsSecurityGroupIds (\ s a -> s{_silsSecurityGroupIds = a}) . _Default . _Coerce
silsKeyName :: Lens' ScheduledInstancesLaunchSpecification (Maybe Text)
silsKeyName = lens _silsKeyName (\ s a -> s{_silsKeyName = a})
silsNetworkInterfaces :: Lens' ScheduledInstancesLaunchSpecification [ScheduledInstancesNetworkInterface]
silsNetworkInterfaces = lens _silsNetworkInterfaces (\ s a -> s{_silsNetworkInterfaces = a}) . _Default . _Coerce
silsRAMDiskId :: Lens' ScheduledInstancesLaunchSpecification (Maybe Text)
silsRAMDiskId = lens _silsRAMDiskId (\ s a -> s{_silsRAMDiskId = a})
silsSubnetId :: Lens' ScheduledInstancesLaunchSpecification (Maybe Text)
silsSubnetId = lens _silsSubnetId (\ s a -> s{_silsSubnetId = a})
silsKernelId :: Lens' ScheduledInstancesLaunchSpecification (Maybe Text)
silsKernelId = lens _silsKernelId (\ s a -> s{_silsKernelId = a})
silsInstanceType :: Lens' ScheduledInstancesLaunchSpecification (Maybe Text)
silsInstanceType = lens _silsInstanceType (\ s a -> s{_silsInstanceType = a})
silsEBSOptimized :: Lens' ScheduledInstancesLaunchSpecification (Maybe Bool)
silsEBSOptimized = lens _silsEBSOptimized (\ s a -> s{_silsEBSOptimized = a})
silsUserData :: Lens' ScheduledInstancesLaunchSpecification (Maybe Text)
silsUserData = lens _silsUserData (\ s a -> s{_silsUserData = a})
silsMonitoring :: Lens' ScheduledInstancesLaunchSpecification (Maybe ScheduledInstancesMonitoring)
silsMonitoring = lens _silsMonitoring (\ s a -> s{_silsMonitoring = a})
silsIAMInstanceProfile :: Lens' ScheduledInstancesLaunchSpecification (Maybe ScheduledInstancesIAMInstanceProfile)
silsIAMInstanceProfile = lens _silsIAMInstanceProfile (\ s a -> s{_silsIAMInstanceProfile = a})
silsBlockDeviceMappings :: Lens' ScheduledInstancesLaunchSpecification [ScheduledInstancesBlockDeviceMapping]
silsBlockDeviceMappings = lens _silsBlockDeviceMappings (\ s a -> s{_silsBlockDeviceMappings = a}) . _Default . _Coerce
silsPlacement :: Lens' ScheduledInstancesLaunchSpecification (Maybe ScheduledInstancesPlacement)
silsPlacement = lens _silsPlacement (\ s a -> s{_silsPlacement = a})
silsImageId :: Lens' ScheduledInstancesLaunchSpecification Text
silsImageId = lens _silsImageId (\ s a -> s{_silsImageId = a})
instance Hashable
ScheduledInstancesLaunchSpecification
where
instance NFData ScheduledInstancesLaunchSpecification
where
instance ToQuery
ScheduledInstancesLaunchSpecification
where
toQuery ScheduledInstancesLaunchSpecification'{..}
= mconcat
[toQuery
(toQueryList "SecurityGroupId" <$>
_silsSecurityGroupIds),
"KeyName" =: _silsKeyName,
toQuery
(toQueryList "NetworkInterface" <$>
_silsNetworkInterfaces),
"RamdiskId" =: _silsRAMDiskId,
"SubnetId" =: _silsSubnetId,
"KernelId" =: _silsKernelId,
"InstanceType" =: _silsInstanceType,
"EbsOptimized" =: _silsEBSOptimized,
"UserData" =: _silsUserData,
"Monitoring" =: _silsMonitoring,
"IamInstanceProfile" =: _silsIAMInstanceProfile,
toQuery
(toQueryList "BlockDeviceMapping" <$>
_silsBlockDeviceMappings),
"Placement" =: _silsPlacement,
"ImageId" =: _silsImageId]
newtype ScheduledInstancesMonitoring = ScheduledInstancesMonitoring'
{ _simEnabled :: Maybe Bool
} deriving (Eq, Read, Show, Data, Typeable, Generic)
scheduledInstancesMonitoring
:: ScheduledInstancesMonitoring
scheduledInstancesMonitoring =
ScheduledInstancesMonitoring' {_simEnabled = Nothing}
simEnabled :: Lens' ScheduledInstancesMonitoring (Maybe Bool)
simEnabled = lens _simEnabled (\ s a -> s{_simEnabled = a})
instance Hashable ScheduledInstancesMonitoring where
instance NFData ScheduledInstancesMonitoring where
instance ToQuery ScheduledInstancesMonitoring where
toQuery ScheduledInstancesMonitoring'{..}
= mconcat ["Enabled" =: _simEnabled]
data ScheduledInstancesNetworkInterface = ScheduledInstancesNetworkInterface'
{ _siniGroups :: !(Maybe [Text])
, _siniDeleteOnTermination :: !(Maybe Bool)
, _siniAssociatePublicIPAddress :: !(Maybe Bool)
, _siniPrivateIPAddressConfigs :: !(Maybe [ScheduledInstancesPrivateIPAddressConfig])
, _siniNetworkInterfaceId :: !(Maybe Text)
, _siniSubnetId :: !(Maybe Text)
, _siniIPv6AddressCount :: !(Maybe Int)
, _siniPrivateIPAddress :: !(Maybe Text)
, _siniSecondaryPrivateIPAddressCount :: !(Maybe Int)
, _siniDescription :: !(Maybe Text)
, _siniDeviceIndex :: !(Maybe Int)
, _siniIPv6Addresses :: !(Maybe [ScheduledInstancesIPv6Address])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
scheduledInstancesNetworkInterface
:: ScheduledInstancesNetworkInterface
scheduledInstancesNetworkInterface =
ScheduledInstancesNetworkInterface'
{ _siniGroups = Nothing
, _siniDeleteOnTermination = Nothing
, _siniAssociatePublicIPAddress = Nothing
, _siniPrivateIPAddressConfigs = Nothing
, _siniNetworkInterfaceId = Nothing
, _siniSubnetId = Nothing
, _siniIPv6AddressCount = Nothing
, _siniPrivateIPAddress = Nothing
, _siniSecondaryPrivateIPAddressCount = Nothing
, _siniDescription = Nothing
, _siniDeviceIndex = Nothing
, _siniIPv6Addresses = Nothing
}
siniGroups :: Lens' ScheduledInstancesNetworkInterface [Text]
siniGroups = lens _siniGroups (\ s a -> s{_siniGroups = a}) . _Default . _Coerce
siniDeleteOnTermination :: Lens' ScheduledInstancesNetworkInterface (Maybe Bool)
siniDeleteOnTermination = lens _siniDeleteOnTermination (\ s a -> s{_siniDeleteOnTermination = a})
siniAssociatePublicIPAddress :: Lens' ScheduledInstancesNetworkInterface (Maybe Bool)
siniAssociatePublicIPAddress = lens _siniAssociatePublicIPAddress (\ s a -> s{_siniAssociatePublicIPAddress = a})
siniPrivateIPAddressConfigs :: Lens' ScheduledInstancesNetworkInterface [ScheduledInstancesPrivateIPAddressConfig]
siniPrivateIPAddressConfigs = lens _siniPrivateIPAddressConfigs (\ s a -> s{_siniPrivateIPAddressConfigs = a}) . _Default . _Coerce
siniNetworkInterfaceId :: Lens' ScheduledInstancesNetworkInterface (Maybe Text)
siniNetworkInterfaceId = lens _siniNetworkInterfaceId (\ s a -> s{_siniNetworkInterfaceId = a})
siniSubnetId :: Lens' ScheduledInstancesNetworkInterface (Maybe Text)
siniSubnetId = lens _siniSubnetId (\ s a -> s{_siniSubnetId = a})
siniIPv6AddressCount :: Lens' ScheduledInstancesNetworkInterface (Maybe Int)
siniIPv6AddressCount = lens _siniIPv6AddressCount (\ s a -> s{_siniIPv6AddressCount = a})
siniPrivateIPAddress :: Lens' ScheduledInstancesNetworkInterface (Maybe Text)
siniPrivateIPAddress = lens _siniPrivateIPAddress (\ s a -> s{_siniPrivateIPAddress = a})
siniSecondaryPrivateIPAddressCount :: Lens' ScheduledInstancesNetworkInterface (Maybe Int)
siniSecondaryPrivateIPAddressCount = lens _siniSecondaryPrivateIPAddressCount (\ s a -> s{_siniSecondaryPrivateIPAddressCount = a})
siniDescription :: Lens' ScheduledInstancesNetworkInterface (Maybe Text)
siniDescription = lens _siniDescription (\ s a -> s{_siniDescription = a})
siniDeviceIndex :: Lens' ScheduledInstancesNetworkInterface (Maybe Int)
siniDeviceIndex = lens _siniDeviceIndex (\ s a -> s{_siniDeviceIndex = a})
siniIPv6Addresses :: Lens' ScheduledInstancesNetworkInterface [ScheduledInstancesIPv6Address]
siniIPv6Addresses = lens _siniIPv6Addresses (\ s a -> s{_siniIPv6Addresses = a}) . _Default . _Coerce
instance Hashable ScheduledInstancesNetworkInterface
where
instance NFData ScheduledInstancesNetworkInterface
where
instance ToQuery ScheduledInstancesNetworkInterface
where
toQuery ScheduledInstancesNetworkInterface'{..}
= mconcat
[toQuery (toQueryList "Group" <$> _siniGroups),
"DeleteOnTermination" =: _siniDeleteOnTermination,
"AssociatePublicIpAddress" =:
_siniAssociatePublicIPAddress,
toQuery
(toQueryList "PrivateIpAddressConfig" <$>
_siniPrivateIPAddressConfigs),
"NetworkInterfaceId" =: _siniNetworkInterfaceId,
"SubnetId" =: _siniSubnetId,
"Ipv6AddressCount" =: _siniIPv6AddressCount,
"PrivateIpAddress" =: _siniPrivateIPAddress,
"SecondaryPrivateIpAddressCount" =:
_siniSecondaryPrivateIPAddressCount,
"Description" =: _siniDescription,
"DeviceIndex" =: _siniDeviceIndex,
toQuery
(toQueryList "Ipv6Address" <$> _siniIPv6Addresses)]
data ScheduledInstancesPlacement = ScheduledInstancesPlacement'
{ _sipAvailabilityZone :: !(Maybe Text)
, _sipGroupName :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
scheduledInstancesPlacement
:: ScheduledInstancesPlacement
scheduledInstancesPlacement =
ScheduledInstancesPlacement'
{_sipAvailabilityZone = Nothing, _sipGroupName = Nothing}
sipAvailabilityZone :: Lens' ScheduledInstancesPlacement (Maybe Text)
sipAvailabilityZone = lens _sipAvailabilityZone (\ s a -> s{_sipAvailabilityZone = a})
sipGroupName :: Lens' ScheduledInstancesPlacement (Maybe Text)
sipGroupName = lens _sipGroupName (\ s a -> s{_sipGroupName = a})
instance Hashable ScheduledInstancesPlacement where
instance NFData ScheduledInstancesPlacement where
instance ToQuery ScheduledInstancesPlacement where
toQuery ScheduledInstancesPlacement'{..}
= mconcat
["AvailabilityZone" =: _sipAvailabilityZone,
"GroupName" =: _sipGroupName]
data ScheduledInstancesPrivateIPAddressConfig = ScheduledInstancesPrivateIPAddressConfig'
{ _sipiacPrimary :: !(Maybe Bool)
, _sipiacPrivateIPAddress :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
scheduledInstancesPrivateIPAddressConfig
:: ScheduledInstancesPrivateIPAddressConfig
scheduledInstancesPrivateIPAddressConfig =
ScheduledInstancesPrivateIPAddressConfig'
{_sipiacPrimary = Nothing, _sipiacPrivateIPAddress = Nothing}
sipiacPrimary :: Lens' ScheduledInstancesPrivateIPAddressConfig (Maybe Bool)
sipiacPrimary = lens _sipiacPrimary (\ s a -> s{_sipiacPrimary = a})
sipiacPrivateIPAddress :: Lens' ScheduledInstancesPrivateIPAddressConfig (Maybe Text)
sipiacPrivateIPAddress = lens _sipiacPrivateIPAddress (\ s a -> s{_sipiacPrivateIPAddress = a})
instance Hashable
ScheduledInstancesPrivateIPAddressConfig
where
instance NFData
ScheduledInstancesPrivateIPAddressConfig
where
instance ToQuery
ScheduledInstancesPrivateIPAddressConfig
where
toQuery ScheduledInstancesPrivateIPAddressConfig'{..}
= mconcat
["Primary" =: _sipiacPrimary,
"PrivateIpAddress" =: _sipiacPrivateIPAddress]
data SecurityGroup = SecurityGroup'
{ _sgVPCId :: !(Maybe Text)
, _sgIPPermissions :: !(Maybe [IPPermission])
, _sgIPPermissionsEgress :: !(Maybe [IPPermission])
, _sgTags :: !(Maybe [Tag])
, _sgOwnerId :: !Text
, _sgGroupId :: !Text
, _sgGroupName :: !Text
, _sgDescription :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
securityGroup
:: Text
-> Text
-> Text
-> Text
-> SecurityGroup
securityGroup pOwnerId_ pGroupId_ pGroupName_ pDescription_ =
SecurityGroup'
{ _sgVPCId = Nothing
, _sgIPPermissions = Nothing
, _sgIPPermissionsEgress = Nothing
, _sgTags = Nothing
, _sgOwnerId = pOwnerId_
, _sgGroupId = pGroupId_
, _sgGroupName = pGroupName_
, _sgDescription = pDescription_
}
sgVPCId :: Lens' SecurityGroup (Maybe Text)
sgVPCId = lens _sgVPCId (\ s a -> s{_sgVPCId = a})
sgIPPermissions :: Lens' SecurityGroup [IPPermission]
sgIPPermissions = lens _sgIPPermissions (\ s a -> s{_sgIPPermissions = a}) . _Default . _Coerce
sgIPPermissionsEgress :: Lens' SecurityGroup [IPPermission]
sgIPPermissionsEgress = lens _sgIPPermissionsEgress (\ s a -> s{_sgIPPermissionsEgress = a}) . _Default . _Coerce
sgTags :: Lens' SecurityGroup [Tag]
sgTags = lens _sgTags (\ s a -> s{_sgTags = a}) . _Default . _Coerce
sgOwnerId :: Lens' SecurityGroup Text
sgOwnerId = lens _sgOwnerId (\ s a -> s{_sgOwnerId = a})
sgGroupId :: Lens' SecurityGroup Text
sgGroupId = lens _sgGroupId (\ s a -> s{_sgGroupId = a})
sgGroupName :: Lens' SecurityGroup Text
sgGroupName = lens _sgGroupName (\ s a -> s{_sgGroupName = a})
sgDescription :: Lens' SecurityGroup Text
sgDescription = lens _sgDescription (\ s a -> s{_sgDescription = a})
instance FromXML SecurityGroup where
parseXML x
= SecurityGroup' <$>
(x .@? "vpcId") <*>
(x .@? "ipPermissions" .!@ mempty >>=
may (parseXMLList "item"))
<*>
(x .@? "ipPermissionsEgress" .!@ mempty >>=
may (parseXMLList "item"))
<*>
(x .@? "tagSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@ "ownerId")
<*> (x .@ "groupId")
<*> (x .@ "groupName")
<*> (x .@ "groupDescription")
instance Hashable SecurityGroup where
instance NFData SecurityGroup where
data SecurityGroupIdentifier = SecurityGroupIdentifier'
{ _sgiGroupId :: !(Maybe Text)
, _sgiGroupName :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
securityGroupIdentifier
:: SecurityGroupIdentifier
securityGroupIdentifier =
SecurityGroupIdentifier' {_sgiGroupId = Nothing, _sgiGroupName = Nothing}
sgiGroupId :: Lens' SecurityGroupIdentifier (Maybe Text)
sgiGroupId = lens _sgiGroupId (\ s a -> s{_sgiGroupId = a})
sgiGroupName :: Lens' SecurityGroupIdentifier (Maybe Text)
sgiGroupName = lens _sgiGroupName (\ s a -> s{_sgiGroupName = a})
instance FromXML SecurityGroupIdentifier where
parseXML x
= SecurityGroupIdentifier' <$>
(x .@? "groupId") <*> (x .@? "groupName")
instance Hashable SecurityGroupIdentifier where
instance NFData SecurityGroupIdentifier where
data SecurityGroupReference = SecurityGroupReference'
{ _sgrVPCPeeringConnectionId :: !(Maybe Text)
, _sgrGroupId :: !Text
, _sgrReferencingVPCId :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
securityGroupReference
:: Text
-> Text
-> SecurityGroupReference
securityGroupReference pGroupId_ pReferencingVPCId_ =
SecurityGroupReference'
{ _sgrVPCPeeringConnectionId = Nothing
, _sgrGroupId = pGroupId_
, _sgrReferencingVPCId = pReferencingVPCId_
}
sgrVPCPeeringConnectionId :: Lens' SecurityGroupReference (Maybe Text)
sgrVPCPeeringConnectionId = lens _sgrVPCPeeringConnectionId (\ s a -> s{_sgrVPCPeeringConnectionId = a})
sgrGroupId :: Lens' SecurityGroupReference Text
sgrGroupId = lens _sgrGroupId (\ s a -> s{_sgrGroupId = a})
sgrReferencingVPCId :: Lens' SecurityGroupReference Text
sgrReferencingVPCId = lens _sgrReferencingVPCId (\ s a -> s{_sgrReferencingVPCId = a})
instance FromXML SecurityGroupReference where
parseXML x
= SecurityGroupReference' <$>
(x .@? "vpcPeeringConnectionId") <*> (x .@ "groupId")
<*> (x .@ "referencingVpcId")
instance Hashable SecurityGroupReference where
instance NFData SecurityGroupReference where
data ServiceConfiguration = ServiceConfiguration'
{ _scNetworkLoadBalancerARNs :: !(Maybe [Text])
, _scBaseEndpointDNSNames :: !(Maybe [Text])
, _scAvailabilityZones :: !(Maybe [Text])
, _scServiceName :: !(Maybe Text)
, _scServiceState :: !(Maybe ServiceState)
, _scServiceType :: !(Maybe [ServiceTypeDetail])
, _scAcceptanceRequired :: !(Maybe Bool)
, _scServiceId :: !(Maybe Text)
, _scPrivateDNSName :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
serviceConfiguration
:: ServiceConfiguration
serviceConfiguration =
ServiceConfiguration'
{ _scNetworkLoadBalancerARNs = Nothing
, _scBaseEndpointDNSNames = Nothing
, _scAvailabilityZones = Nothing
, _scServiceName = Nothing
, _scServiceState = Nothing
, _scServiceType = Nothing
, _scAcceptanceRequired = Nothing
, _scServiceId = Nothing
, _scPrivateDNSName = Nothing
}
scNetworkLoadBalancerARNs :: Lens' ServiceConfiguration [Text]
scNetworkLoadBalancerARNs = lens _scNetworkLoadBalancerARNs (\ s a -> s{_scNetworkLoadBalancerARNs = a}) . _Default . _Coerce
scBaseEndpointDNSNames :: Lens' ServiceConfiguration [Text]
scBaseEndpointDNSNames = lens _scBaseEndpointDNSNames (\ s a -> s{_scBaseEndpointDNSNames = a}) . _Default . _Coerce
scAvailabilityZones :: Lens' ServiceConfiguration [Text]
scAvailabilityZones = lens _scAvailabilityZones (\ s a -> s{_scAvailabilityZones = a}) . _Default . _Coerce
scServiceName :: Lens' ServiceConfiguration (Maybe Text)
scServiceName = lens _scServiceName (\ s a -> s{_scServiceName = a})
scServiceState :: Lens' ServiceConfiguration (Maybe ServiceState)
scServiceState = lens _scServiceState (\ s a -> s{_scServiceState = a})
scServiceType :: Lens' ServiceConfiguration [ServiceTypeDetail]
scServiceType = lens _scServiceType (\ s a -> s{_scServiceType = a}) . _Default . _Coerce
scAcceptanceRequired :: Lens' ServiceConfiguration (Maybe Bool)
scAcceptanceRequired = lens _scAcceptanceRequired (\ s a -> s{_scAcceptanceRequired = a})
scServiceId :: Lens' ServiceConfiguration (Maybe Text)
scServiceId = lens _scServiceId (\ s a -> s{_scServiceId = a})
scPrivateDNSName :: Lens' ServiceConfiguration (Maybe Text)
scPrivateDNSName = lens _scPrivateDNSName (\ s a -> s{_scPrivateDNSName = a})
instance FromXML ServiceConfiguration where
parseXML x
= ServiceConfiguration' <$>
(x .@? "networkLoadBalancerArnSet" .!@ mempty >>=
may (parseXMLList "item"))
<*>
(x .@? "baseEndpointDnsNameSet" .!@ mempty >>=
may (parseXMLList "item"))
<*>
(x .@? "availabilityZoneSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "serviceName")
<*> (x .@? "serviceState")
<*>
(x .@? "serviceType" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "acceptanceRequired")
<*> (x .@? "serviceId")
<*> (x .@? "privateDnsName")
instance Hashable ServiceConfiguration where
instance NFData ServiceConfiguration where
data ServiceDetail = ServiceDetail'
{ _sdVPCEndpointPolicySupported :: !(Maybe Bool)
, _sdBaseEndpointDNSNames :: !(Maybe [Text])
, _sdOwner :: !(Maybe Text)
, _sdAvailabilityZones :: !(Maybe [Text])
, _sdServiceName :: !(Maybe Text)
, _sdServiceType :: !(Maybe [ServiceTypeDetail])
, _sdAcceptanceRequired :: !(Maybe Bool)
, _sdPrivateDNSName :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
serviceDetail
:: ServiceDetail
serviceDetail =
ServiceDetail'
{ _sdVPCEndpointPolicySupported = Nothing
, _sdBaseEndpointDNSNames = Nothing
, _sdOwner = Nothing
, _sdAvailabilityZones = Nothing
, _sdServiceName = Nothing
, _sdServiceType = Nothing
, _sdAcceptanceRequired = Nothing
, _sdPrivateDNSName = Nothing
}
sdVPCEndpointPolicySupported :: Lens' ServiceDetail (Maybe Bool)
sdVPCEndpointPolicySupported = lens _sdVPCEndpointPolicySupported (\ s a -> s{_sdVPCEndpointPolicySupported = a})
sdBaseEndpointDNSNames :: Lens' ServiceDetail [Text]
sdBaseEndpointDNSNames = lens _sdBaseEndpointDNSNames (\ s a -> s{_sdBaseEndpointDNSNames = a}) . _Default . _Coerce
sdOwner :: Lens' ServiceDetail (Maybe Text)
sdOwner = lens _sdOwner (\ s a -> s{_sdOwner = a})
sdAvailabilityZones :: Lens' ServiceDetail [Text]
sdAvailabilityZones = lens _sdAvailabilityZones (\ s a -> s{_sdAvailabilityZones = a}) . _Default . _Coerce
sdServiceName :: Lens' ServiceDetail (Maybe Text)
sdServiceName = lens _sdServiceName (\ s a -> s{_sdServiceName = a})
sdServiceType :: Lens' ServiceDetail [ServiceTypeDetail]
sdServiceType = lens _sdServiceType (\ s a -> s{_sdServiceType = a}) . _Default . _Coerce
sdAcceptanceRequired :: Lens' ServiceDetail (Maybe Bool)
sdAcceptanceRequired = lens _sdAcceptanceRequired (\ s a -> s{_sdAcceptanceRequired = a})
sdPrivateDNSName :: Lens' ServiceDetail (Maybe Text)
sdPrivateDNSName = lens _sdPrivateDNSName (\ s a -> s{_sdPrivateDNSName = a})
instance FromXML ServiceDetail where
parseXML x
= ServiceDetail' <$>
(x .@? "vpcEndpointPolicySupported") <*>
(x .@? "baseEndpointDnsNameSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "owner")
<*>
(x .@? "availabilityZoneSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "serviceName")
<*>
(x .@? "serviceType" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "acceptanceRequired")
<*> (x .@? "privateDnsName")
instance Hashable ServiceDetail where
instance NFData ServiceDetail where
newtype ServiceTypeDetail = ServiceTypeDetail'
{ _stdServiceType :: Maybe ServiceType
} deriving (Eq, Read, Show, Data, Typeable, Generic)
serviceTypeDetail
:: ServiceTypeDetail
serviceTypeDetail = ServiceTypeDetail' {_stdServiceType = Nothing}
stdServiceType :: Lens' ServiceTypeDetail (Maybe ServiceType)
stdServiceType = lens _stdServiceType (\ s a -> s{_stdServiceType = a})
instance FromXML ServiceTypeDetail where
parseXML x
= ServiceTypeDetail' <$> (x .@? "serviceType")
instance Hashable ServiceTypeDetail where
instance NFData ServiceTypeDetail where
data SlotDateTimeRangeRequest = SlotDateTimeRangeRequest'
{ _sdtrrEarliestTime :: !ISO8601
, _sdtrrLatestTime :: !ISO8601
} deriving (Eq, Read, Show, Data, Typeable, Generic)
slotDateTimeRangeRequest
:: UTCTime
-> UTCTime
-> SlotDateTimeRangeRequest
slotDateTimeRangeRequest pEarliestTime_ pLatestTime_ =
SlotDateTimeRangeRequest'
{ _sdtrrEarliestTime = _Time # pEarliestTime_
, _sdtrrLatestTime = _Time # pLatestTime_
}
sdtrrEarliestTime :: Lens' SlotDateTimeRangeRequest UTCTime
sdtrrEarliestTime = lens _sdtrrEarliestTime (\ s a -> s{_sdtrrEarliestTime = a}) . _Time
sdtrrLatestTime :: Lens' SlotDateTimeRangeRequest UTCTime
sdtrrLatestTime = lens _sdtrrLatestTime (\ s a -> s{_sdtrrLatestTime = a}) . _Time
instance Hashable SlotDateTimeRangeRequest where
instance NFData SlotDateTimeRangeRequest where
instance ToQuery SlotDateTimeRangeRequest where
toQuery SlotDateTimeRangeRequest'{..}
= mconcat
["EarliestTime" =: _sdtrrEarliestTime,
"LatestTime" =: _sdtrrLatestTime]
data SlotStartTimeRangeRequest = SlotStartTimeRangeRequest'
{ _sstrrLatestTime :: !(Maybe ISO8601)
, _sstrrEarliestTime :: !(Maybe ISO8601)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
slotStartTimeRangeRequest
:: SlotStartTimeRangeRequest
slotStartTimeRangeRequest =
SlotStartTimeRangeRequest'
{_sstrrLatestTime = Nothing, _sstrrEarliestTime = Nothing}
sstrrLatestTime :: Lens' SlotStartTimeRangeRequest (Maybe UTCTime)
sstrrLatestTime = lens _sstrrLatestTime (\ s a -> s{_sstrrLatestTime = a}) . mapping _Time
sstrrEarliestTime :: Lens' SlotStartTimeRangeRequest (Maybe UTCTime)
sstrrEarliestTime = lens _sstrrEarliestTime (\ s a -> s{_sstrrEarliestTime = a}) . mapping _Time
instance Hashable SlotStartTimeRangeRequest where
instance NFData SlotStartTimeRangeRequest where
instance ToQuery SlotStartTimeRangeRequest where
toQuery SlotStartTimeRangeRequest'{..}
= mconcat
["LatestTime" =: _sstrrLatestTime,
"EarliestTime" =: _sstrrEarliestTime]
data Snapshot = Snapshot'
{ _sStateMessage :: !(Maybe Text)
, _sOwnerAlias :: !(Maybe Text)
, _sDataEncryptionKeyId :: !(Maybe Text)
, _sKMSKeyId :: !(Maybe Text)
, _sTags :: !(Maybe [Tag])
, _sSnapshotId :: !Text
, _sOwnerId :: !Text
, _sVolumeId :: !Text
, _sVolumeSize :: !Int
, _sDescription :: !Text
, _sStartTime :: !ISO8601
, _sProgress :: !Text
, _sState :: !SnapshotState
, _sEncrypted :: !Bool
} deriving (Eq, Read, Show, Data, Typeable, Generic)
snapshot
:: Text
-> Text
-> Text
-> Int
-> Text
-> UTCTime
-> Text
-> SnapshotState
-> Bool
-> Snapshot
snapshot pSnapshotId_ pOwnerId_ pVolumeId_ pVolumeSize_ pDescription_ pStartTime_ pProgress_ pState_ pEncrypted_ =
Snapshot'
{ _sStateMessage = Nothing
, _sOwnerAlias = Nothing
, _sDataEncryptionKeyId = Nothing
, _sKMSKeyId = Nothing
, _sTags = Nothing
, _sSnapshotId = pSnapshotId_
, _sOwnerId = pOwnerId_
, _sVolumeId = pVolumeId_
, _sVolumeSize = pVolumeSize_
, _sDescription = pDescription_
, _sStartTime = _Time # pStartTime_
, _sProgress = pProgress_
, _sState = pState_
, _sEncrypted = pEncrypted_
}
sStateMessage :: Lens' Snapshot (Maybe Text)
sStateMessage = lens _sStateMessage (\ s a -> s{_sStateMessage = a})
sOwnerAlias :: Lens' Snapshot (Maybe Text)
sOwnerAlias = lens _sOwnerAlias (\ s a -> s{_sOwnerAlias = a})
sDataEncryptionKeyId :: Lens' Snapshot (Maybe Text)
sDataEncryptionKeyId = lens _sDataEncryptionKeyId (\ s a -> s{_sDataEncryptionKeyId = a})
sKMSKeyId :: Lens' Snapshot (Maybe Text)
sKMSKeyId = lens _sKMSKeyId (\ s a -> s{_sKMSKeyId = a})
sTags :: Lens' Snapshot [Tag]
sTags = lens _sTags (\ s a -> s{_sTags = a}) . _Default . _Coerce
sSnapshotId :: Lens' Snapshot Text
sSnapshotId = lens _sSnapshotId (\ s a -> s{_sSnapshotId = a})
sOwnerId :: Lens' Snapshot Text
sOwnerId = lens _sOwnerId (\ s a -> s{_sOwnerId = a})
sVolumeId :: Lens' Snapshot Text
sVolumeId = lens _sVolumeId (\ s a -> s{_sVolumeId = a})
sVolumeSize :: Lens' Snapshot Int
sVolumeSize = lens _sVolumeSize (\ s a -> s{_sVolumeSize = a})
sDescription :: Lens' Snapshot Text
sDescription = lens _sDescription (\ s a -> s{_sDescription = a})
sStartTime :: Lens' Snapshot UTCTime
sStartTime = lens _sStartTime (\ s a -> s{_sStartTime = a}) . _Time
sProgress :: Lens' Snapshot Text
sProgress = lens _sProgress (\ s a -> s{_sProgress = a})
sState :: Lens' Snapshot SnapshotState
sState = lens _sState (\ s a -> s{_sState = a})
sEncrypted :: Lens' Snapshot Bool
sEncrypted = lens _sEncrypted (\ s a -> s{_sEncrypted = a})
instance FromXML Snapshot where
parseXML x
= Snapshot' <$>
(x .@? "statusMessage") <*> (x .@? "ownerAlias") <*>
(x .@? "dataEncryptionKeyId")
<*> (x .@? "kmsKeyId")
<*>
(x .@? "tagSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@ "snapshotId")
<*> (x .@ "ownerId")
<*> (x .@ "volumeId")
<*> (x .@ "volumeSize")
<*> (x .@ "description")
<*> (x .@ "startTime")
<*> (x .@ "progress")
<*> (x .@ "status")
<*> (x .@ "encrypted")
instance Hashable Snapshot where
instance NFData Snapshot where
data SnapshotDetail = SnapshotDetail'
{ _sdStatus :: !(Maybe Text)
, _sdProgress :: !(Maybe Text)
, _sdFormat :: !(Maybe Text)
, _sdURL :: !(Maybe Text)
, _sdDeviceName :: !(Maybe Text)
, _sdStatusMessage :: !(Maybe Text)
, _sdUserBucket :: !(Maybe UserBucketDetails)
, _sdDiskImageSize :: !(Maybe Double)
, _sdDescription :: !(Maybe Text)
, _sdSnapshotId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
snapshotDetail
:: SnapshotDetail
snapshotDetail =
SnapshotDetail'
{ _sdStatus = Nothing
, _sdProgress = Nothing
, _sdFormat = Nothing
, _sdURL = Nothing
, _sdDeviceName = Nothing
, _sdStatusMessage = Nothing
, _sdUserBucket = Nothing
, _sdDiskImageSize = Nothing
, _sdDescription = Nothing
, _sdSnapshotId = Nothing
}
sdStatus :: Lens' SnapshotDetail (Maybe Text)
sdStatus = lens _sdStatus (\ s a -> s{_sdStatus = a})
sdProgress :: Lens' SnapshotDetail (Maybe Text)
sdProgress = lens _sdProgress (\ s a -> s{_sdProgress = a})
sdFormat :: Lens' SnapshotDetail (Maybe Text)
sdFormat = lens _sdFormat (\ s a -> s{_sdFormat = a})
sdURL :: Lens' SnapshotDetail (Maybe Text)
sdURL = lens _sdURL (\ s a -> s{_sdURL = a})
sdDeviceName :: Lens' SnapshotDetail (Maybe Text)
sdDeviceName = lens _sdDeviceName (\ s a -> s{_sdDeviceName = a})
sdStatusMessage :: Lens' SnapshotDetail (Maybe Text)
sdStatusMessage = lens _sdStatusMessage (\ s a -> s{_sdStatusMessage = a})
sdUserBucket :: Lens' SnapshotDetail (Maybe UserBucketDetails)
sdUserBucket = lens _sdUserBucket (\ s a -> s{_sdUserBucket = a})
sdDiskImageSize :: Lens' SnapshotDetail (Maybe Double)
sdDiskImageSize = lens _sdDiskImageSize (\ s a -> s{_sdDiskImageSize = a})
sdDescription :: Lens' SnapshotDetail (Maybe Text)
sdDescription = lens _sdDescription (\ s a -> s{_sdDescription = a})
sdSnapshotId :: Lens' SnapshotDetail (Maybe Text)
sdSnapshotId = lens _sdSnapshotId (\ s a -> s{_sdSnapshotId = a})
instance FromXML SnapshotDetail where
parseXML x
= SnapshotDetail' <$>
(x .@? "status") <*> (x .@? "progress") <*>
(x .@? "format")
<*> (x .@? "url")
<*> (x .@? "deviceName")
<*> (x .@? "statusMessage")
<*> (x .@? "userBucket")
<*> (x .@? "diskImageSize")
<*> (x .@? "description")
<*> (x .@? "snapshotId")
instance Hashable SnapshotDetail where
instance NFData SnapshotDetail where
data SnapshotDiskContainer = SnapshotDiskContainer'
{ _sdcFormat :: !(Maybe Text)
, _sdcURL :: !(Maybe Text)
, _sdcUserBucket :: !(Maybe UserBucket)
, _sdcDescription :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
snapshotDiskContainer
:: SnapshotDiskContainer
snapshotDiskContainer =
SnapshotDiskContainer'
{ _sdcFormat = Nothing
, _sdcURL = Nothing
, _sdcUserBucket = Nothing
, _sdcDescription = Nothing
}
sdcFormat :: Lens' SnapshotDiskContainer (Maybe Text)
sdcFormat = lens _sdcFormat (\ s a -> s{_sdcFormat = a})
sdcURL :: Lens' SnapshotDiskContainer (Maybe Text)
sdcURL = lens _sdcURL (\ s a -> s{_sdcURL = a})
sdcUserBucket :: Lens' SnapshotDiskContainer (Maybe UserBucket)
sdcUserBucket = lens _sdcUserBucket (\ s a -> s{_sdcUserBucket = a})
sdcDescription :: Lens' SnapshotDiskContainer (Maybe Text)
sdcDescription = lens _sdcDescription (\ s a -> s{_sdcDescription = a})
instance Hashable SnapshotDiskContainer where
instance NFData SnapshotDiskContainer where
instance ToQuery SnapshotDiskContainer where
toQuery SnapshotDiskContainer'{..}
= mconcat
["Format" =: _sdcFormat, "Url" =: _sdcURL,
"UserBucket" =: _sdcUserBucket,
"Description" =: _sdcDescription]
data SnapshotTaskDetail = SnapshotTaskDetail'
{ _stdStatus :: !(Maybe Text)
, _stdProgress :: !(Maybe Text)
, _stdFormat :: !(Maybe Text)
, _stdURL :: !(Maybe Text)
, _stdStatusMessage :: !(Maybe Text)
, _stdUserBucket :: !(Maybe UserBucketDetails)
, _stdDiskImageSize :: !(Maybe Double)
, _stdDescription :: !(Maybe Text)
, _stdSnapshotId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
snapshotTaskDetail
:: SnapshotTaskDetail
snapshotTaskDetail =
SnapshotTaskDetail'
{ _stdStatus = Nothing
, _stdProgress = Nothing
, _stdFormat = Nothing
, _stdURL = Nothing
, _stdStatusMessage = Nothing
, _stdUserBucket = Nothing
, _stdDiskImageSize = Nothing
, _stdDescription = Nothing
, _stdSnapshotId = Nothing
}
stdStatus :: Lens' SnapshotTaskDetail (Maybe Text)
stdStatus = lens _stdStatus (\ s a -> s{_stdStatus = a})
stdProgress :: Lens' SnapshotTaskDetail (Maybe Text)
stdProgress = lens _stdProgress (\ s a -> s{_stdProgress = a})
stdFormat :: Lens' SnapshotTaskDetail (Maybe Text)
stdFormat = lens _stdFormat (\ s a -> s{_stdFormat = a})
stdURL :: Lens' SnapshotTaskDetail (Maybe Text)
stdURL = lens _stdURL (\ s a -> s{_stdURL = a})
stdStatusMessage :: Lens' SnapshotTaskDetail (Maybe Text)
stdStatusMessage = lens _stdStatusMessage (\ s a -> s{_stdStatusMessage = a})
stdUserBucket :: Lens' SnapshotTaskDetail (Maybe UserBucketDetails)
stdUserBucket = lens _stdUserBucket (\ s a -> s{_stdUserBucket = a})
stdDiskImageSize :: Lens' SnapshotTaskDetail (Maybe Double)
stdDiskImageSize = lens _stdDiskImageSize (\ s a -> s{_stdDiskImageSize = a})
stdDescription :: Lens' SnapshotTaskDetail (Maybe Text)
stdDescription = lens _stdDescription (\ s a -> s{_stdDescription = a})
stdSnapshotId :: Lens' SnapshotTaskDetail (Maybe Text)
stdSnapshotId = lens _stdSnapshotId (\ s a -> s{_stdSnapshotId = a})
instance FromXML SnapshotTaskDetail where
parseXML x
= SnapshotTaskDetail' <$>
(x .@? "status") <*> (x .@? "progress") <*>
(x .@? "format")
<*> (x .@? "url")
<*> (x .@? "statusMessage")
<*> (x .@? "userBucket")
<*> (x .@? "diskImageSize")
<*> (x .@? "description")
<*> (x .@? "snapshotId")
instance Hashable SnapshotTaskDetail where
instance NFData SnapshotTaskDetail where
data SpotDatafeedSubscription = SpotDatafeedSubscription'
{ _sdsState :: !(Maybe DatafeedSubscriptionState)
, _sdsPrefix :: !(Maybe Text)
, _sdsBucket :: !(Maybe Text)
, _sdsOwnerId :: !(Maybe Text)
, _sdsFault :: !(Maybe SpotInstanceStateFault)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
spotDatafeedSubscription
:: SpotDatafeedSubscription
spotDatafeedSubscription =
SpotDatafeedSubscription'
{ _sdsState = Nothing
, _sdsPrefix = Nothing
, _sdsBucket = Nothing
, _sdsOwnerId = Nothing
, _sdsFault = Nothing
}
sdsState :: Lens' SpotDatafeedSubscription (Maybe DatafeedSubscriptionState)
sdsState = lens _sdsState (\ s a -> s{_sdsState = a})
sdsPrefix :: Lens' SpotDatafeedSubscription (Maybe Text)
sdsPrefix = lens _sdsPrefix (\ s a -> s{_sdsPrefix = a})
sdsBucket :: Lens' SpotDatafeedSubscription (Maybe Text)
sdsBucket = lens _sdsBucket (\ s a -> s{_sdsBucket = a})
sdsOwnerId :: Lens' SpotDatafeedSubscription (Maybe Text)
sdsOwnerId = lens _sdsOwnerId (\ s a -> s{_sdsOwnerId = a})
sdsFault :: Lens' SpotDatafeedSubscription (Maybe SpotInstanceStateFault)
sdsFault = lens _sdsFault (\ s a -> s{_sdsFault = a})
instance FromXML SpotDatafeedSubscription where
parseXML x
= SpotDatafeedSubscription' <$>
(x .@? "state") <*> (x .@? "prefix") <*>
(x .@? "bucket")
<*> (x .@? "ownerId")
<*> (x .@? "fault")
instance Hashable SpotDatafeedSubscription where
instance NFData SpotDatafeedSubscription where
data SpotFleetLaunchSpecification = SpotFleetLaunchSpecification'
{ _sflsSecurityGroups :: !(Maybe [GroupIdentifier])
, _sflsSpotPrice :: !(Maybe Text)
, _sflsWeightedCapacity :: !(Maybe Double)
, _sflsKeyName :: !(Maybe Text)
, _sflsNetworkInterfaces :: !(Maybe [InstanceNetworkInterfaceSpecification])
, _sflsRAMDiskId :: !(Maybe Text)
, _sflsSubnetId :: !(Maybe Text)
, _sflsKernelId :: !(Maybe Text)
, _sflsInstanceType :: !(Maybe InstanceType)
, _sflsEBSOptimized :: !(Maybe Bool)
, _sflsUserData :: !(Maybe Text)
, _sflsMonitoring :: !(Maybe SpotFleetMonitoring)
, _sflsTagSpecifications :: !(Maybe [SpotFleetTagSpecification])
, _sflsIAMInstanceProfile :: !(Maybe IAMInstanceProfileSpecification)
, _sflsImageId :: !(Maybe Text)
, _sflsAddressingType :: !(Maybe Text)
, _sflsBlockDeviceMappings :: !(Maybe [BlockDeviceMapping])
, _sflsPlacement :: !(Maybe SpotPlacement)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
spotFleetLaunchSpecification
:: SpotFleetLaunchSpecification
spotFleetLaunchSpecification =
SpotFleetLaunchSpecification'
{ _sflsSecurityGroups = Nothing
, _sflsSpotPrice = Nothing
, _sflsWeightedCapacity = Nothing
, _sflsKeyName = Nothing
, _sflsNetworkInterfaces = Nothing
, _sflsRAMDiskId = Nothing
, _sflsSubnetId = Nothing
, _sflsKernelId = Nothing
, _sflsInstanceType = Nothing
, _sflsEBSOptimized = Nothing
, _sflsUserData = Nothing
, _sflsMonitoring = Nothing
, _sflsTagSpecifications = Nothing
, _sflsIAMInstanceProfile = Nothing
, _sflsImageId = Nothing
, _sflsAddressingType = Nothing
, _sflsBlockDeviceMappings = Nothing
, _sflsPlacement = Nothing
}
sflsSecurityGroups :: Lens' SpotFleetLaunchSpecification [GroupIdentifier]
sflsSecurityGroups = lens _sflsSecurityGroups (\ s a -> s{_sflsSecurityGroups = a}) . _Default . _Coerce
sflsSpotPrice :: Lens' SpotFleetLaunchSpecification (Maybe Text)
sflsSpotPrice = lens _sflsSpotPrice (\ s a -> s{_sflsSpotPrice = a})
sflsWeightedCapacity :: Lens' SpotFleetLaunchSpecification (Maybe Double)
sflsWeightedCapacity = lens _sflsWeightedCapacity (\ s a -> s{_sflsWeightedCapacity = a})
sflsKeyName :: Lens' SpotFleetLaunchSpecification (Maybe Text)
sflsKeyName = lens _sflsKeyName (\ s a -> s{_sflsKeyName = a})
sflsNetworkInterfaces :: Lens' SpotFleetLaunchSpecification [InstanceNetworkInterfaceSpecification]
sflsNetworkInterfaces = lens _sflsNetworkInterfaces (\ s a -> s{_sflsNetworkInterfaces = a}) . _Default . _Coerce
sflsRAMDiskId :: Lens' SpotFleetLaunchSpecification (Maybe Text)
sflsRAMDiskId = lens _sflsRAMDiskId (\ s a -> s{_sflsRAMDiskId = a})
sflsSubnetId :: Lens' SpotFleetLaunchSpecification (Maybe Text)
sflsSubnetId = lens _sflsSubnetId (\ s a -> s{_sflsSubnetId = a})
sflsKernelId :: Lens' SpotFleetLaunchSpecification (Maybe Text)
sflsKernelId = lens _sflsKernelId (\ s a -> s{_sflsKernelId = a})
sflsInstanceType :: Lens' SpotFleetLaunchSpecification (Maybe InstanceType)
sflsInstanceType = lens _sflsInstanceType (\ s a -> s{_sflsInstanceType = a})
sflsEBSOptimized :: Lens' SpotFleetLaunchSpecification (Maybe Bool)
sflsEBSOptimized = lens _sflsEBSOptimized (\ s a -> s{_sflsEBSOptimized = a})
sflsUserData :: Lens' SpotFleetLaunchSpecification (Maybe Text)
sflsUserData = lens _sflsUserData (\ s a -> s{_sflsUserData = a})
sflsMonitoring :: Lens' SpotFleetLaunchSpecification (Maybe SpotFleetMonitoring)
sflsMonitoring = lens _sflsMonitoring (\ s a -> s{_sflsMonitoring = a})
sflsTagSpecifications :: Lens' SpotFleetLaunchSpecification [SpotFleetTagSpecification]
sflsTagSpecifications = lens _sflsTagSpecifications (\ s a -> s{_sflsTagSpecifications = a}) . _Default . _Coerce
sflsIAMInstanceProfile :: Lens' SpotFleetLaunchSpecification (Maybe IAMInstanceProfileSpecification)
sflsIAMInstanceProfile = lens _sflsIAMInstanceProfile (\ s a -> s{_sflsIAMInstanceProfile = a})
sflsImageId :: Lens' SpotFleetLaunchSpecification (Maybe Text)
sflsImageId = lens _sflsImageId (\ s a -> s{_sflsImageId = a})
sflsAddressingType :: Lens' SpotFleetLaunchSpecification (Maybe Text)
sflsAddressingType = lens _sflsAddressingType (\ s a -> s{_sflsAddressingType = a})
sflsBlockDeviceMappings :: Lens' SpotFleetLaunchSpecification [BlockDeviceMapping]
sflsBlockDeviceMappings = lens _sflsBlockDeviceMappings (\ s a -> s{_sflsBlockDeviceMappings = a}) . _Default . _Coerce
sflsPlacement :: Lens' SpotFleetLaunchSpecification (Maybe SpotPlacement)
sflsPlacement = lens _sflsPlacement (\ s a -> s{_sflsPlacement = a})
instance FromXML SpotFleetLaunchSpecification where
parseXML x
= SpotFleetLaunchSpecification' <$>
(x .@? "groupSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "spotPrice")
<*> (x .@? "weightedCapacity")
<*> (x .@? "keyName")
<*>
(x .@? "networkInterfaceSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "ramdiskId")
<*> (x .@? "subnetId")
<*> (x .@? "kernelId")
<*> (x .@? "instanceType")
<*> (x .@? "ebsOptimized")
<*> (x .@? "userData")
<*> (x .@? "monitoring")
<*>
(x .@? "tagSpecificationSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "iamInstanceProfile")
<*> (x .@? "imageId")
<*> (x .@? "addressingType")
<*>
(x .@? "blockDeviceMapping" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "placement")
instance Hashable SpotFleetLaunchSpecification where
instance NFData SpotFleetLaunchSpecification where
instance ToQuery SpotFleetLaunchSpecification where
toQuery SpotFleetLaunchSpecification'{..}
= mconcat
[toQuery
(toQueryList "GroupSet" <$> _sflsSecurityGroups),
"SpotPrice" =: _sflsSpotPrice,
"WeightedCapacity" =: _sflsWeightedCapacity,
"KeyName" =: _sflsKeyName,
toQuery
(toQueryList "NetworkInterfaceSet" <$>
_sflsNetworkInterfaces),
"RamdiskId" =: _sflsRAMDiskId,
"SubnetId" =: _sflsSubnetId,
"KernelId" =: _sflsKernelId,
"InstanceType" =: _sflsInstanceType,
"EbsOptimized" =: _sflsEBSOptimized,
"UserData" =: _sflsUserData,
"Monitoring" =: _sflsMonitoring,
toQuery
(toQueryList "TagSpecificationSet" <$>
_sflsTagSpecifications),
"IamInstanceProfile" =: _sflsIAMInstanceProfile,
"ImageId" =: _sflsImageId,
"AddressingType" =: _sflsAddressingType,
toQuery
(toQueryList "BlockDeviceMapping" <$>
_sflsBlockDeviceMappings),
"Placement" =: _sflsPlacement]
newtype SpotFleetMonitoring = SpotFleetMonitoring'
{ _sfmEnabled :: Maybe Bool
} deriving (Eq, Read, Show, Data, Typeable, Generic)
spotFleetMonitoring
:: SpotFleetMonitoring
spotFleetMonitoring = SpotFleetMonitoring' {_sfmEnabled = Nothing}
sfmEnabled :: Lens' SpotFleetMonitoring (Maybe Bool)
sfmEnabled = lens _sfmEnabled (\ s a -> s{_sfmEnabled = a})
instance FromXML SpotFleetMonitoring where
parseXML x
= SpotFleetMonitoring' <$> (x .@? "enabled")
instance Hashable SpotFleetMonitoring where
instance NFData SpotFleetMonitoring where
instance ToQuery SpotFleetMonitoring where
toQuery SpotFleetMonitoring'{..}
= mconcat ["Enabled" =: _sfmEnabled]
data SpotFleetRequestConfig = SpotFleetRequestConfig'
{ _sfrcActivityStatus :: !(Maybe ActivityStatus)
, _sfrcCreateTime :: !ISO8601
, _sfrcSpotFleetRequestConfig :: !SpotFleetRequestConfigData
, _sfrcSpotFleetRequestId :: !Text
, _sfrcSpotFleetRequestState :: !BatchState
} deriving (Eq, Read, Show, Data, Typeable, Generic)
spotFleetRequestConfig
:: UTCTime
-> SpotFleetRequestConfigData
-> Text
-> BatchState
-> SpotFleetRequestConfig
spotFleetRequestConfig pCreateTime_ pSpotFleetRequestConfig_ pSpotFleetRequestId_ pSpotFleetRequestState_ =
SpotFleetRequestConfig'
{ _sfrcActivityStatus = Nothing
, _sfrcCreateTime = _Time # pCreateTime_
, _sfrcSpotFleetRequestConfig = pSpotFleetRequestConfig_
, _sfrcSpotFleetRequestId = pSpotFleetRequestId_
, _sfrcSpotFleetRequestState = pSpotFleetRequestState_
}
sfrcActivityStatus :: Lens' SpotFleetRequestConfig (Maybe ActivityStatus)
sfrcActivityStatus = lens _sfrcActivityStatus (\ s a -> s{_sfrcActivityStatus = a})
sfrcCreateTime :: Lens' SpotFleetRequestConfig UTCTime
sfrcCreateTime = lens _sfrcCreateTime (\ s a -> s{_sfrcCreateTime = a}) . _Time
sfrcSpotFleetRequestConfig :: Lens' SpotFleetRequestConfig SpotFleetRequestConfigData
sfrcSpotFleetRequestConfig = lens _sfrcSpotFleetRequestConfig (\ s a -> s{_sfrcSpotFleetRequestConfig = a})
sfrcSpotFleetRequestId :: Lens' SpotFleetRequestConfig Text
sfrcSpotFleetRequestId = lens _sfrcSpotFleetRequestId (\ s a -> s{_sfrcSpotFleetRequestId = a})
sfrcSpotFleetRequestState :: Lens' SpotFleetRequestConfig BatchState
sfrcSpotFleetRequestState = lens _sfrcSpotFleetRequestState (\ s a -> s{_sfrcSpotFleetRequestState = a})
instance FromXML SpotFleetRequestConfig where
parseXML x
= SpotFleetRequestConfig' <$>
(x .@? "activityStatus") <*> (x .@ "createTime") <*>
(x .@ "spotFleetRequestConfig")
<*> (x .@ "spotFleetRequestId")
<*> (x .@ "spotFleetRequestState")
instance Hashable SpotFleetRequestConfig where
instance NFData SpotFleetRequestConfig where
data SpotFleetRequestConfigData = SpotFleetRequestConfigData'
{ _sfrcdClientToken :: !(Maybe Text)
, _sfrcdInstanceInterruptionBehavior :: !(Maybe InstanceInterruptionBehavior)
, _sfrcdSpotPrice :: !(Maybe Text)
, _sfrcdLoadBalancersConfig :: !(Maybe LoadBalancersConfig)
, _sfrcdExcessCapacityTerminationPolicy :: !(Maybe ExcessCapacityTerminationPolicy)
, _sfrcdOnDemandTargetCapacity :: !(Maybe Int)
, _sfrcdLaunchTemplateConfigs :: !(Maybe [LaunchTemplateConfig])
, _sfrcdValidUntil :: !(Maybe ISO8601)
, _sfrcdTerminateInstancesWithExpiration :: !(Maybe Bool)
, _sfrcdFulfilledCapacity :: !(Maybe Double)
, _sfrcdType :: !(Maybe FleetType)
, _sfrcdValidFrom :: !(Maybe ISO8601)
, _sfrcdReplaceUnhealthyInstances :: !(Maybe Bool)
, _sfrcdLaunchSpecifications :: !(Maybe [SpotFleetLaunchSpecification])
, _sfrcdOnDemandFulfilledCapacity :: !(Maybe Double)
, _sfrcdAllocationStrategy :: !(Maybe AllocationStrategy)
, _sfrcdIAMFleetRole :: !Text
, _sfrcdTargetCapacity :: !Int
} deriving (Eq, Read, Show, Data, Typeable, Generic)
spotFleetRequestConfigData
:: Text
-> Int
-> SpotFleetRequestConfigData
spotFleetRequestConfigData pIAMFleetRole_ pTargetCapacity_ =
SpotFleetRequestConfigData'
{ _sfrcdClientToken = Nothing
, _sfrcdInstanceInterruptionBehavior = Nothing
, _sfrcdSpotPrice = Nothing
, _sfrcdLoadBalancersConfig = Nothing
, _sfrcdExcessCapacityTerminationPolicy = Nothing
, _sfrcdOnDemandTargetCapacity = Nothing
, _sfrcdLaunchTemplateConfigs = Nothing
, _sfrcdValidUntil = Nothing
, _sfrcdTerminateInstancesWithExpiration = Nothing
, _sfrcdFulfilledCapacity = Nothing
, _sfrcdType = Nothing
, _sfrcdValidFrom = Nothing
, _sfrcdReplaceUnhealthyInstances = Nothing
, _sfrcdLaunchSpecifications = Nothing
, _sfrcdOnDemandFulfilledCapacity = Nothing
, _sfrcdAllocationStrategy = Nothing
, _sfrcdIAMFleetRole = pIAMFleetRole_
, _sfrcdTargetCapacity = pTargetCapacity_
}
sfrcdClientToken :: Lens' SpotFleetRequestConfigData (Maybe Text)
sfrcdClientToken = lens _sfrcdClientToken (\ s a -> s{_sfrcdClientToken = a})
sfrcdInstanceInterruptionBehavior :: Lens' SpotFleetRequestConfigData (Maybe InstanceInterruptionBehavior)
sfrcdInstanceInterruptionBehavior = lens _sfrcdInstanceInterruptionBehavior (\ s a -> s{_sfrcdInstanceInterruptionBehavior = a})
sfrcdSpotPrice :: Lens' SpotFleetRequestConfigData (Maybe Text)
sfrcdSpotPrice = lens _sfrcdSpotPrice (\ s a -> s{_sfrcdSpotPrice = a})
sfrcdLoadBalancersConfig :: Lens' SpotFleetRequestConfigData (Maybe LoadBalancersConfig)
sfrcdLoadBalancersConfig = lens _sfrcdLoadBalancersConfig (\ s a -> s{_sfrcdLoadBalancersConfig = a})
sfrcdExcessCapacityTerminationPolicy :: Lens' SpotFleetRequestConfigData (Maybe ExcessCapacityTerminationPolicy)
sfrcdExcessCapacityTerminationPolicy = lens _sfrcdExcessCapacityTerminationPolicy (\ s a -> s{_sfrcdExcessCapacityTerminationPolicy = a})
sfrcdOnDemandTargetCapacity :: Lens' SpotFleetRequestConfigData (Maybe Int)
sfrcdOnDemandTargetCapacity = lens _sfrcdOnDemandTargetCapacity (\ s a -> s{_sfrcdOnDemandTargetCapacity = a})
sfrcdLaunchTemplateConfigs :: Lens' SpotFleetRequestConfigData [LaunchTemplateConfig]
sfrcdLaunchTemplateConfigs = lens _sfrcdLaunchTemplateConfigs (\ s a -> s{_sfrcdLaunchTemplateConfigs = a}) . _Default . _Coerce
sfrcdValidUntil :: Lens' SpotFleetRequestConfigData (Maybe UTCTime)
sfrcdValidUntil = lens _sfrcdValidUntil (\ s a -> s{_sfrcdValidUntil = a}) . mapping _Time
sfrcdTerminateInstancesWithExpiration :: Lens' SpotFleetRequestConfigData (Maybe Bool)
sfrcdTerminateInstancesWithExpiration = lens _sfrcdTerminateInstancesWithExpiration (\ s a -> s{_sfrcdTerminateInstancesWithExpiration = a})
sfrcdFulfilledCapacity :: Lens' SpotFleetRequestConfigData (Maybe Double)
sfrcdFulfilledCapacity = lens _sfrcdFulfilledCapacity (\ s a -> s{_sfrcdFulfilledCapacity = a})
sfrcdType :: Lens' SpotFleetRequestConfigData (Maybe FleetType)
sfrcdType = lens _sfrcdType (\ s a -> s{_sfrcdType = a})
sfrcdValidFrom :: Lens' SpotFleetRequestConfigData (Maybe UTCTime)
sfrcdValidFrom = lens _sfrcdValidFrom (\ s a -> s{_sfrcdValidFrom = a}) . mapping _Time
sfrcdReplaceUnhealthyInstances :: Lens' SpotFleetRequestConfigData (Maybe Bool)
sfrcdReplaceUnhealthyInstances = lens _sfrcdReplaceUnhealthyInstances (\ s a -> s{_sfrcdReplaceUnhealthyInstances = a})
sfrcdLaunchSpecifications :: Lens' SpotFleetRequestConfigData [SpotFleetLaunchSpecification]
sfrcdLaunchSpecifications = lens _sfrcdLaunchSpecifications (\ s a -> s{_sfrcdLaunchSpecifications = a}) . _Default . _Coerce
sfrcdOnDemandFulfilledCapacity :: Lens' SpotFleetRequestConfigData (Maybe Double)
sfrcdOnDemandFulfilledCapacity = lens _sfrcdOnDemandFulfilledCapacity (\ s a -> s{_sfrcdOnDemandFulfilledCapacity = a})
sfrcdAllocationStrategy :: Lens' SpotFleetRequestConfigData (Maybe AllocationStrategy)
sfrcdAllocationStrategy = lens _sfrcdAllocationStrategy (\ s a -> s{_sfrcdAllocationStrategy = a})
sfrcdIAMFleetRole :: Lens' SpotFleetRequestConfigData Text
sfrcdIAMFleetRole = lens _sfrcdIAMFleetRole (\ s a -> s{_sfrcdIAMFleetRole = a})
sfrcdTargetCapacity :: Lens' SpotFleetRequestConfigData Int
sfrcdTargetCapacity = lens _sfrcdTargetCapacity (\ s a -> s{_sfrcdTargetCapacity = a})
instance FromXML SpotFleetRequestConfigData where
parseXML x
= SpotFleetRequestConfigData' <$>
(x .@? "clientToken") <*>
(x .@? "instanceInterruptionBehavior")
<*> (x .@? "spotPrice")
<*> (x .@? "loadBalancersConfig")
<*> (x .@? "excessCapacityTerminationPolicy")
<*> (x .@? "onDemandTargetCapacity")
<*>
(x .@? "launchTemplateConfigs" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "validUntil")
<*> (x .@? "terminateInstancesWithExpiration")
<*> (x .@? "fulfilledCapacity")
<*> (x .@? "type")
<*> (x .@? "validFrom")
<*> (x .@? "replaceUnhealthyInstances")
<*>
(x .@? "launchSpecifications" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "onDemandFulfilledCapacity")
<*> (x .@? "allocationStrategy")
<*> (x .@ "iamFleetRole")
<*> (x .@ "targetCapacity")
instance Hashable SpotFleetRequestConfigData where
instance NFData SpotFleetRequestConfigData where
instance ToQuery SpotFleetRequestConfigData where
toQuery SpotFleetRequestConfigData'{..}
= mconcat
["ClientToken" =: _sfrcdClientToken,
"InstanceInterruptionBehavior" =:
_sfrcdInstanceInterruptionBehavior,
"SpotPrice" =: _sfrcdSpotPrice,
"LoadBalancersConfig" =: _sfrcdLoadBalancersConfig,
"ExcessCapacityTerminationPolicy" =:
_sfrcdExcessCapacityTerminationPolicy,
"OnDemandTargetCapacity" =:
_sfrcdOnDemandTargetCapacity,
toQuery
(toQueryList "LaunchTemplateConfigs" <$>
_sfrcdLaunchTemplateConfigs),
"ValidUntil" =: _sfrcdValidUntil,
"TerminateInstancesWithExpiration" =:
_sfrcdTerminateInstancesWithExpiration,
"FulfilledCapacity" =: _sfrcdFulfilledCapacity,
"Type" =: _sfrcdType, "ValidFrom" =: _sfrcdValidFrom,
"ReplaceUnhealthyInstances" =:
_sfrcdReplaceUnhealthyInstances,
toQuery
(toQueryList "LaunchSpecifications" <$>
_sfrcdLaunchSpecifications),
"OnDemandFulfilledCapacity" =:
_sfrcdOnDemandFulfilledCapacity,
"AllocationStrategy" =: _sfrcdAllocationStrategy,
"IamFleetRole" =: _sfrcdIAMFleetRole,
"TargetCapacity" =: _sfrcdTargetCapacity]
data SpotFleetTagSpecification = SpotFleetTagSpecification'
{ _sftsResourceType :: !(Maybe ResourceType)
, _sftsTags :: !(Maybe [Tag])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
spotFleetTagSpecification
:: SpotFleetTagSpecification
spotFleetTagSpecification =
SpotFleetTagSpecification' {_sftsResourceType = Nothing, _sftsTags = Nothing}
sftsResourceType :: Lens' SpotFleetTagSpecification (Maybe ResourceType)
sftsResourceType = lens _sftsResourceType (\ s a -> s{_sftsResourceType = a})
sftsTags :: Lens' SpotFleetTagSpecification [Tag]
sftsTags = lens _sftsTags (\ s a -> s{_sftsTags = a}) . _Default . _Coerce
instance FromXML SpotFleetTagSpecification where
parseXML x
= SpotFleetTagSpecification' <$>
(x .@? "resourceType") <*>
(x .@? "tag" .!@ mempty >>=
may (parseXMLList "item"))
instance Hashable SpotFleetTagSpecification where
instance NFData SpotFleetTagSpecification where
instance ToQuery SpotFleetTagSpecification where
toQuery SpotFleetTagSpecification'{..}
= mconcat
["ResourceType" =: _sftsResourceType,
toQuery (toQueryList "Tag" <$> _sftsTags)]
data SpotInstanceRequest = SpotInstanceRequest'
{ _sirInstanceId :: !(Maybe Text)
, _sirStatus :: !(Maybe SpotInstanceStatus)
, _sirState :: !(Maybe SpotInstanceState)
, _sirActualBlockHourlyPrice :: !(Maybe Text)
, _sirBlockDurationMinutes :: !(Maybe Int)
, _sirInstanceInterruptionBehavior :: !(Maybe InstanceInterruptionBehavior)
, _sirProductDescription :: !(Maybe RIProductDescription)
, _sirSpotPrice :: !(Maybe Text)
, _sirLaunchSpecification :: !(Maybe LaunchSpecification)
, _sirAvailabilityZoneGroup :: !(Maybe Text)
, _sirLaunchedAvailabilityZone :: !(Maybe Text)
, _sirValidUntil :: !(Maybe ISO8601)
, _sirLaunchGroup :: !(Maybe Text)
, _sirFault :: !(Maybe SpotInstanceStateFault)
, _sirSpotInstanceRequestId :: !(Maybe Text)
, _sirType :: !(Maybe SpotInstanceType)
, _sirValidFrom :: !(Maybe ISO8601)
, _sirCreateTime :: !(Maybe ISO8601)
, _sirTags :: !(Maybe [Tag])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
spotInstanceRequest
:: SpotInstanceRequest
spotInstanceRequest =
SpotInstanceRequest'
{ _sirInstanceId = Nothing
, _sirStatus = Nothing
, _sirState = Nothing
, _sirActualBlockHourlyPrice = Nothing
, _sirBlockDurationMinutes = Nothing
, _sirInstanceInterruptionBehavior = Nothing
, _sirProductDescription = Nothing
, _sirSpotPrice = Nothing
, _sirLaunchSpecification = Nothing
, _sirAvailabilityZoneGroup = Nothing
, _sirLaunchedAvailabilityZone = Nothing
, _sirValidUntil = Nothing
, _sirLaunchGroup = Nothing
, _sirFault = Nothing
, _sirSpotInstanceRequestId = Nothing
, _sirType = Nothing
, _sirValidFrom = Nothing
, _sirCreateTime = Nothing
, _sirTags = Nothing
}
sirInstanceId :: Lens' SpotInstanceRequest (Maybe Text)
sirInstanceId = lens _sirInstanceId (\ s a -> s{_sirInstanceId = a})
sirStatus :: Lens' SpotInstanceRequest (Maybe SpotInstanceStatus)
sirStatus = lens _sirStatus (\ s a -> s{_sirStatus = a})
sirState :: Lens' SpotInstanceRequest (Maybe SpotInstanceState)
sirState = lens _sirState (\ s a -> s{_sirState = a})
sirActualBlockHourlyPrice :: Lens' SpotInstanceRequest (Maybe Text)
sirActualBlockHourlyPrice = lens _sirActualBlockHourlyPrice (\ s a -> s{_sirActualBlockHourlyPrice = a})
sirBlockDurationMinutes :: Lens' SpotInstanceRequest (Maybe Int)
sirBlockDurationMinutes = lens _sirBlockDurationMinutes (\ s a -> s{_sirBlockDurationMinutes = a})
sirInstanceInterruptionBehavior :: Lens' SpotInstanceRequest (Maybe InstanceInterruptionBehavior)
sirInstanceInterruptionBehavior = lens _sirInstanceInterruptionBehavior (\ s a -> s{_sirInstanceInterruptionBehavior = a})
sirProductDescription :: Lens' SpotInstanceRequest (Maybe RIProductDescription)
sirProductDescription = lens _sirProductDescription (\ s a -> s{_sirProductDescription = a})
sirSpotPrice :: Lens' SpotInstanceRequest (Maybe Text)
sirSpotPrice = lens _sirSpotPrice (\ s a -> s{_sirSpotPrice = a})
sirLaunchSpecification :: Lens' SpotInstanceRequest (Maybe LaunchSpecification)
sirLaunchSpecification = lens _sirLaunchSpecification (\ s a -> s{_sirLaunchSpecification = a})
sirAvailabilityZoneGroup :: Lens' SpotInstanceRequest (Maybe Text)
sirAvailabilityZoneGroup = lens _sirAvailabilityZoneGroup (\ s a -> s{_sirAvailabilityZoneGroup = a})
sirLaunchedAvailabilityZone :: Lens' SpotInstanceRequest (Maybe Text)
sirLaunchedAvailabilityZone = lens _sirLaunchedAvailabilityZone (\ s a -> s{_sirLaunchedAvailabilityZone = a})
sirValidUntil :: Lens' SpotInstanceRequest (Maybe UTCTime)
sirValidUntil = lens _sirValidUntil (\ s a -> s{_sirValidUntil = a}) . mapping _Time
sirLaunchGroup :: Lens' SpotInstanceRequest (Maybe Text)
sirLaunchGroup = lens _sirLaunchGroup (\ s a -> s{_sirLaunchGroup = a})
sirFault :: Lens' SpotInstanceRequest (Maybe SpotInstanceStateFault)
sirFault = lens _sirFault (\ s a -> s{_sirFault = a})
sirSpotInstanceRequestId :: Lens' SpotInstanceRequest (Maybe Text)
sirSpotInstanceRequestId = lens _sirSpotInstanceRequestId (\ s a -> s{_sirSpotInstanceRequestId = a})
sirType :: Lens' SpotInstanceRequest (Maybe SpotInstanceType)
sirType = lens _sirType (\ s a -> s{_sirType = a})
sirValidFrom :: Lens' SpotInstanceRequest (Maybe UTCTime)
sirValidFrom = lens _sirValidFrom (\ s a -> s{_sirValidFrom = a}) . mapping _Time
sirCreateTime :: Lens' SpotInstanceRequest (Maybe UTCTime)
sirCreateTime = lens _sirCreateTime (\ s a -> s{_sirCreateTime = a}) . mapping _Time
sirTags :: Lens' SpotInstanceRequest [Tag]
sirTags = lens _sirTags (\ s a -> s{_sirTags = a}) . _Default . _Coerce
instance FromXML SpotInstanceRequest where
parseXML x
= SpotInstanceRequest' <$>
(x .@? "instanceId") <*> (x .@? "status") <*>
(x .@? "state")
<*> (x .@? "actualBlockHourlyPrice")
<*> (x .@? "blockDurationMinutes")
<*> (x .@? "instanceInterruptionBehavior")
<*> (x .@? "productDescription")
<*> (x .@? "spotPrice")
<*> (x .@? "launchSpecification")
<*> (x .@? "availabilityZoneGroup")
<*> (x .@? "launchedAvailabilityZone")
<*> (x .@? "validUntil")
<*> (x .@? "launchGroup")
<*> (x .@? "fault")
<*> (x .@? "spotInstanceRequestId")
<*> (x .@? "type")
<*> (x .@? "validFrom")
<*> (x .@? "createTime")
<*>
(x .@? "tagSet" .!@ mempty >>=
may (parseXMLList "item"))
instance Hashable SpotInstanceRequest where
instance NFData SpotInstanceRequest where
data SpotInstanceStateFault = SpotInstanceStateFault'
{ _sisfCode :: !(Maybe Text)
, _sisfMessage :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
spotInstanceStateFault
:: SpotInstanceStateFault
spotInstanceStateFault =
SpotInstanceStateFault' {_sisfCode = Nothing, _sisfMessage = Nothing}
sisfCode :: Lens' SpotInstanceStateFault (Maybe Text)
sisfCode = lens _sisfCode (\ s a -> s{_sisfCode = a})
sisfMessage :: Lens' SpotInstanceStateFault (Maybe Text)
sisfMessage = lens _sisfMessage (\ s a -> s{_sisfMessage = a})
instance FromXML SpotInstanceStateFault where
parseXML x
= SpotInstanceStateFault' <$>
(x .@? "code") <*> (x .@? "message")
instance Hashable SpotInstanceStateFault where
instance NFData SpotInstanceStateFault where
data SpotInstanceStatus = SpotInstanceStatus'
{ _sisUpdateTime :: !(Maybe ISO8601)
, _sisCode :: !(Maybe Text)
, _sisMessage :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
spotInstanceStatus
:: SpotInstanceStatus
spotInstanceStatus =
SpotInstanceStatus'
{_sisUpdateTime = Nothing, _sisCode = Nothing, _sisMessage = Nothing}
sisUpdateTime :: Lens' SpotInstanceStatus (Maybe UTCTime)
sisUpdateTime = lens _sisUpdateTime (\ s a -> s{_sisUpdateTime = a}) . mapping _Time
sisCode :: Lens' SpotInstanceStatus (Maybe Text)
sisCode = lens _sisCode (\ s a -> s{_sisCode = a})
sisMessage :: Lens' SpotInstanceStatus (Maybe Text)
sisMessage = lens _sisMessage (\ s a -> s{_sisMessage = a})
instance FromXML SpotInstanceStatus where
parseXML x
= SpotInstanceStatus' <$>
(x .@? "updateTime") <*> (x .@? "code") <*>
(x .@? "message")
instance Hashable SpotInstanceStatus where
instance NFData SpotInstanceStatus where
data SpotMarketOptions = SpotMarketOptions'
{ _smoBlockDurationMinutes :: !(Maybe Int)
, _smoInstanceInterruptionBehavior :: !(Maybe InstanceInterruptionBehavior)
, _smoValidUntil :: !(Maybe ISO8601)
, _smoSpotInstanceType :: !(Maybe SpotInstanceType)
, _smoMaxPrice :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
spotMarketOptions
:: SpotMarketOptions
spotMarketOptions =
SpotMarketOptions'
{ _smoBlockDurationMinutes = Nothing
, _smoInstanceInterruptionBehavior = Nothing
, _smoValidUntil = Nothing
, _smoSpotInstanceType = Nothing
, _smoMaxPrice = Nothing
}
smoBlockDurationMinutes :: Lens' SpotMarketOptions (Maybe Int)
smoBlockDurationMinutes = lens _smoBlockDurationMinutes (\ s a -> s{_smoBlockDurationMinutes = a})
smoInstanceInterruptionBehavior :: Lens' SpotMarketOptions (Maybe InstanceInterruptionBehavior)
smoInstanceInterruptionBehavior = lens _smoInstanceInterruptionBehavior (\ s a -> s{_smoInstanceInterruptionBehavior = a})
smoValidUntil :: Lens' SpotMarketOptions (Maybe UTCTime)
smoValidUntil = lens _smoValidUntil (\ s a -> s{_smoValidUntil = a}) . mapping _Time
smoSpotInstanceType :: Lens' SpotMarketOptions (Maybe SpotInstanceType)
smoSpotInstanceType = lens _smoSpotInstanceType (\ s a -> s{_smoSpotInstanceType = a})
smoMaxPrice :: Lens' SpotMarketOptions (Maybe Text)
smoMaxPrice = lens _smoMaxPrice (\ s a -> s{_smoMaxPrice = a})
instance Hashable SpotMarketOptions where
instance NFData SpotMarketOptions where
instance ToQuery SpotMarketOptions where
toQuery SpotMarketOptions'{..}
= mconcat
["BlockDurationMinutes" =: _smoBlockDurationMinutes,
"InstanceInterruptionBehavior" =:
_smoInstanceInterruptionBehavior,
"ValidUntil" =: _smoValidUntil,
"SpotInstanceType" =: _smoSpotInstanceType,
"MaxPrice" =: _smoMaxPrice]
data SpotOptions = SpotOptions'
{ _soInstanceInterruptionBehavior :: !(Maybe SpotInstanceInterruptionBehavior)
, _soAllocationStrategy :: !(Maybe SpotAllocationStrategy)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
spotOptions
:: SpotOptions
spotOptions =
SpotOptions'
{_soInstanceInterruptionBehavior = Nothing, _soAllocationStrategy = Nothing}
soInstanceInterruptionBehavior :: Lens' SpotOptions (Maybe SpotInstanceInterruptionBehavior)
soInstanceInterruptionBehavior = lens _soInstanceInterruptionBehavior (\ s a -> s{_soInstanceInterruptionBehavior = a})
soAllocationStrategy :: Lens' SpotOptions (Maybe SpotAllocationStrategy)
soAllocationStrategy = lens _soAllocationStrategy (\ s a -> s{_soAllocationStrategy = a})
instance FromXML SpotOptions where
parseXML x
= SpotOptions' <$>
(x .@? "instanceInterruptionBehavior") <*>
(x .@? "allocationStrategy")
instance Hashable SpotOptions where
instance NFData SpotOptions where
data SpotOptionsRequest = SpotOptionsRequest'
{ _sorInstanceInterruptionBehavior :: !(Maybe SpotInstanceInterruptionBehavior)
, _sorAllocationStrategy :: !(Maybe SpotAllocationStrategy)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
spotOptionsRequest
:: SpotOptionsRequest
spotOptionsRequest =
SpotOptionsRequest'
{ _sorInstanceInterruptionBehavior = Nothing
, _sorAllocationStrategy = Nothing
}
sorInstanceInterruptionBehavior :: Lens' SpotOptionsRequest (Maybe SpotInstanceInterruptionBehavior)
sorInstanceInterruptionBehavior = lens _sorInstanceInterruptionBehavior (\ s a -> s{_sorInstanceInterruptionBehavior = a})
sorAllocationStrategy :: Lens' SpotOptionsRequest (Maybe SpotAllocationStrategy)
sorAllocationStrategy = lens _sorAllocationStrategy (\ s a -> s{_sorAllocationStrategy = a})
instance Hashable SpotOptionsRequest where
instance NFData SpotOptionsRequest where
instance ToQuery SpotOptionsRequest where
toQuery SpotOptionsRequest'{..}
= mconcat
["InstanceInterruptionBehavior" =:
_sorInstanceInterruptionBehavior,
"AllocationStrategy" =: _sorAllocationStrategy]
data SpotPlacement = SpotPlacement'
{ _spAvailabilityZone :: !(Maybe Text)
, _spTenancy :: !(Maybe Tenancy)
, _spGroupName :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
spotPlacement
:: SpotPlacement
spotPlacement =
SpotPlacement'
{ _spAvailabilityZone = Nothing
, _spTenancy = Nothing
, _spGroupName = Nothing
}
spAvailabilityZone :: Lens' SpotPlacement (Maybe Text)
spAvailabilityZone = lens _spAvailabilityZone (\ s a -> s{_spAvailabilityZone = a})
spTenancy :: Lens' SpotPlacement (Maybe Tenancy)
spTenancy = lens _spTenancy (\ s a -> s{_spTenancy = a})
spGroupName :: Lens' SpotPlacement (Maybe Text)
spGroupName = lens _spGroupName (\ s a -> s{_spGroupName = a})
instance FromXML SpotPlacement where
parseXML x
= SpotPlacement' <$>
(x .@? "availabilityZone") <*> (x .@? "tenancy") <*>
(x .@? "groupName")
instance Hashable SpotPlacement where
instance NFData SpotPlacement where
instance ToQuery SpotPlacement where
toQuery SpotPlacement'{..}
= mconcat
["AvailabilityZone" =: _spAvailabilityZone,
"Tenancy" =: _spTenancy, "GroupName" =: _spGroupName]
data SpotPrice = SpotPrice'
{ _sProductDescription :: !(Maybe RIProductDescription)
, _sSpotPrice :: !(Maybe Text)
, _sInstanceType :: !(Maybe InstanceType)
, _sAvailabilityZone :: !(Maybe Text)
, _sTimestamp :: !(Maybe ISO8601)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
spotPrice
:: SpotPrice
spotPrice =
SpotPrice'
{ _sProductDescription = Nothing
, _sSpotPrice = Nothing
, _sInstanceType = Nothing
, _sAvailabilityZone = Nothing
, _sTimestamp = Nothing
}
sProductDescription :: Lens' SpotPrice (Maybe RIProductDescription)
sProductDescription = lens _sProductDescription (\ s a -> s{_sProductDescription = a})
sSpotPrice :: Lens' SpotPrice (Maybe Text)
sSpotPrice = lens _sSpotPrice (\ s a -> s{_sSpotPrice = a})
sInstanceType :: Lens' SpotPrice (Maybe InstanceType)
sInstanceType = lens _sInstanceType (\ s a -> s{_sInstanceType = a})
sAvailabilityZone :: Lens' SpotPrice (Maybe Text)
sAvailabilityZone = lens _sAvailabilityZone (\ s a -> s{_sAvailabilityZone = a})
sTimestamp :: Lens' SpotPrice (Maybe UTCTime)
sTimestamp = lens _sTimestamp (\ s a -> s{_sTimestamp = a}) . mapping _Time
instance FromXML SpotPrice where
parseXML x
= SpotPrice' <$>
(x .@? "productDescription") <*> (x .@? "spotPrice")
<*> (x .@? "instanceType")
<*> (x .@? "availabilityZone")
<*> (x .@? "timestamp")
instance Hashable SpotPrice where
instance NFData SpotPrice where
data StaleIPPermission = StaleIPPermission'
{ _sipFromPort :: !(Maybe Int)
, _sipUserIdGroupPairs :: !(Maybe [UserIdGroupPair])
, _sipPrefixListIds :: !(Maybe [Text])
, _sipIPProtocol :: !(Maybe Text)
, _sipToPort :: !(Maybe Int)
, _sipIPRanges :: !(Maybe [Text])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
staleIPPermission
:: StaleIPPermission
staleIPPermission =
StaleIPPermission'
{ _sipFromPort = Nothing
, _sipUserIdGroupPairs = Nothing
, _sipPrefixListIds = Nothing
, _sipIPProtocol = Nothing
, _sipToPort = Nothing
, _sipIPRanges = Nothing
}
sipFromPort :: Lens' StaleIPPermission (Maybe Int)
sipFromPort = lens _sipFromPort (\ s a -> s{_sipFromPort = a})
sipUserIdGroupPairs :: Lens' StaleIPPermission [UserIdGroupPair]
sipUserIdGroupPairs = lens _sipUserIdGroupPairs (\ s a -> s{_sipUserIdGroupPairs = a}) . _Default . _Coerce
sipPrefixListIds :: Lens' StaleIPPermission [Text]
sipPrefixListIds = lens _sipPrefixListIds (\ s a -> s{_sipPrefixListIds = a}) . _Default . _Coerce
sipIPProtocol :: Lens' StaleIPPermission (Maybe Text)
sipIPProtocol = lens _sipIPProtocol (\ s a -> s{_sipIPProtocol = a})
sipToPort :: Lens' StaleIPPermission (Maybe Int)
sipToPort = lens _sipToPort (\ s a -> s{_sipToPort = a})
sipIPRanges :: Lens' StaleIPPermission [Text]
sipIPRanges = lens _sipIPRanges (\ s a -> s{_sipIPRanges = a}) . _Default . _Coerce
instance FromXML StaleIPPermission where
parseXML x
= StaleIPPermission' <$>
(x .@? "fromPort") <*>
(x .@? "groups" .!@ mempty >>=
may (parseXMLList "item"))
<*>
(x .@? "prefixListIds" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "ipProtocol")
<*> (x .@? "toPort")
<*>
(x .@? "ipRanges" .!@ mempty >>=
may (parseXMLList "item"))
instance Hashable StaleIPPermission where
instance NFData StaleIPPermission where
data StaleSecurityGroup = StaleSecurityGroup'
{ _ssgVPCId :: !(Maybe Text)
, _ssgGroupName :: !(Maybe Text)
, _ssgStaleIPPermissionsEgress :: !(Maybe [StaleIPPermission])
, _ssgStaleIPPermissions :: !(Maybe [StaleIPPermission])
, _ssgDescription :: !(Maybe Text)
, _ssgGroupId :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
staleSecurityGroup
:: Text
-> StaleSecurityGroup
staleSecurityGroup pGroupId_ =
StaleSecurityGroup'
{ _ssgVPCId = Nothing
, _ssgGroupName = Nothing
, _ssgStaleIPPermissionsEgress = Nothing
, _ssgStaleIPPermissions = Nothing
, _ssgDescription = Nothing
, _ssgGroupId = pGroupId_
}
ssgVPCId :: Lens' StaleSecurityGroup (Maybe Text)
ssgVPCId = lens _ssgVPCId (\ s a -> s{_ssgVPCId = a})
ssgGroupName :: Lens' StaleSecurityGroup (Maybe Text)
ssgGroupName = lens _ssgGroupName (\ s a -> s{_ssgGroupName = a})
ssgStaleIPPermissionsEgress :: Lens' StaleSecurityGroup [StaleIPPermission]
ssgStaleIPPermissionsEgress = lens _ssgStaleIPPermissionsEgress (\ s a -> s{_ssgStaleIPPermissionsEgress = a}) . _Default . _Coerce
ssgStaleIPPermissions :: Lens' StaleSecurityGroup [StaleIPPermission]
ssgStaleIPPermissions = lens _ssgStaleIPPermissions (\ s a -> s{_ssgStaleIPPermissions = a}) . _Default . _Coerce
ssgDescription :: Lens' StaleSecurityGroup (Maybe Text)
ssgDescription = lens _ssgDescription (\ s a -> s{_ssgDescription = a})
ssgGroupId :: Lens' StaleSecurityGroup Text
ssgGroupId = lens _ssgGroupId (\ s a -> s{_ssgGroupId = a})
instance FromXML StaleSecurityGroup where
parseXML x
= StaleSecurityGroup' <$>
(x .@? "vpcId") <*> (x .@? "groupName") <*>
(x .@? "staleIpPermissionsEgress" .!@ mempty >>=
may (parseXMLList "item"))
<*>
(x .@? "staleIpPermissions" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "description")
<*> (x .@ "groupId")
instance Hashable StaleSecurityGroup where
instance NFData StaleSecurityGroup where
data StateReason = StateReason'
{ _srCode :: !(Maybe Text)
, _srMessage :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
stateReason
:: StateReason
stateReason = StateReason' {_srCode = Nothing, _srMessage = Nothing}
srCode :: Lens' StateReason (Maybe Text)
srCode = lens _srCode (\ s a -> s{_srCode = a})
srMessage :: Lens' StateReason (Maybe Text)
srMessage = lens _srMessage (\ s a -> s{_srMessage = a})
instance FromXML StateReason where
parseXML x
= StateReason' <$>
(x .@? "code") <*> (x .@? "message")
instance Hashable StateReason where
instance NFData StateReason where
newtype Storage = Storage'
{ _sS3 :: Maybe S3Storage
} deriving (Eq, Read, Show, Data, Typeable, Generic)
storage
:: Storage
storage = Storage' {_sS3 = Nothing}
sS3 :: Lens' Storage (Maybe S3Storage)
sS3 = lens _sS3 (\ s a -> s{_sS3 = a})
instance FromXML Storage where
parseXML x = Storage' <$> (x .@? "S3")
instance Hashable Storage where
instance NFData Storage where
instance ToQuery Storage where
toQuery Storage'{..} = mconcat ["S3" =: _sS3]
data StorageLocation = StorageLocation'
{ _slBucket :: !(Maybe Text)
, _slKey :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
storageLocation
:: StorageLocation
storageLocation = StorageLocation' {_slBucket = Nothing, _slKey = Nothing}
slBucket :: Lens' StorageLocation (Maybe Text)
slBucket = lens _slBucket (\ s a -> s{_slBucket = a})
slKey :: Lens' StorageLocation (Maybe Text)
slKey = lens _slKey (\ s a -> s{_slKey = a})
instance Hashable StorageLocation where
instance NFData StorageLocation where
instance ToQuery StorageLocation where
toQuery StorageLocation'{..}
= mconcat ["Bucket" =: _slBucket, "Key" =: _slKey]
data Subnet = Subnet'
{ _subIPv6CidrBlockAssociationSet :: !(Maybe [SubnetIPv6CidrBlockAssociation])
, _subAssignIPv6AddressOnCreation :: !(Maybe Bool)
, _subMapPublicIPOnLaunch :: !(Maybe Bool)
, _subDefaultForAz :: !(Maybe Bool)
, _subTags :: !(Maybe [Tag])
, _subAvailabilityZone :: !Text
, _subAvailableIPAddressCount :: !Int
, _subCidrBlock :: !Text
, _subState :: !SubnetState
, _subSubnetId :: !Text
, _subVPCId :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
subnet
:: Text
-> Int
-> Text
-> SubnetState
-> Text
-> Text
-> Subnet
subnet pAvailabilityZone_ pAvailableIPAddressCount_ pCidrBlock_ pState_ pSubnetId_ pVPCId_ =
Subnet'
{ _subIPv6CidrBlockAssociationSet = Nothing
, _subAssignIPv6AddressOnCreation = Nothing
, _subMapPublicIPOnLaunch = Nothing
, _subDefaultForAz = Nothing
, _subTags = Nothing
, _subAvailabilityZone = pAvailabilityZone_
, _subAvailableIPAddressCount = pAvailableIPAddressCount_
, _subCidrBlock = pCidrBlock_
, _subState = pState_
, _subSubnetId = pSubnetId_
, _subVPCId = pVPCId_
}
subIPv6CidrBlockAssociationSet :: Lens' Subnet [SubnetIPv6CidrBlockAssociation]
subIPv6CidrBlockAssociationSet = lens _subIPv6CidrBlockAssociationSet (\ s a -> s{_subIPv6CidrBlockAssociationSet = a}) . _Default . _Coerce
subAssignIPv6AddressOnCreation :: Lens' Subnet (Maybe Bool)
subAssignIPv6AddressOnCreation = lens _subAssignIPv6AddressOnCreation (\ s a -> s{_subAssignIPv6AddressOnCreation = a})
subMapPublicIPOnLaunch :: Lens' Subnet (Maybe Bool)
subMapPublicIPOnLaunch = lens _subMapPublicIPOnLaunch (\ s a -> s{_subMapPublicIPOnLaunch = a})
subDefaultForAz :: Lens' Subnet (Maybe Bool)
subDefaultForAz = lens _subDefaultForAz (\ s a -> s{_subDefaultForAz = a})
subTags :: Lens' Subnet [Tag]
subTags = lens _subTags (\ s a -> s{_subTags = a}) . _Default . _Coerce
subAvailabilityZone :: Lens' Subnet Text
subAvailabilityZone = lens _subAvailabilityZone (\ s a -> s{_subAvailabilityZone = a})
subAvailableIPAddressCount :: Lens' Subnet Int
subAvailableIPAddressCount = lens _subAvailableIPAddressCount (\ s a -> s{_subAvailableIPAddressCount = a})
subCidrBlock :: Lens' Subnet Text
subCidrBlock = lens _subCidrBlock (\ s a -> s{_subCidrBlock = a})
subState :: Lens' Subnet SubnetState
subState = lens _subState (\ s a -> s{_subState = a})
subSubnetId :: Lens' Subnet Text
subSubnetId = lens _subSubnetId (\ s a -> s{_subSubnetId = a})
subVPCId :: Lens' Subnet Text
subVPCId = lens _subVPCId (\ s a -> s{_subVPCId = a})
instance FromXML Subnet where
parseXML x
= Subnet' <$>
(x .@? "ipv6CidrBlockAssociationSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "assignIpv6AddressOnCreation")
<*> (x .@? "mapPublicIpOnLaunch")
<*> (x .@? "defaultForAz")
<*>
(x .@? "tagSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@ "availabilityZone")
<*> (x .@ "availableIpAddressCount")
<*> (x .@ "cidrBlock")
<*> (x .@ "state")
<*> (x .@ "subnetId")
<*> (x .@ "vpcId")
instance Hashable Subnet where
instance NFData Subnet where
data SubnetCidrBlockState = SubnetCidrBlockState'
{ _scbsState :: !(Maybe SubnetCidrBlockStateCode)
, _scbsStatusMessage :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
subnetCidrBlockState
:: SubnetCidrBlockState
subnetCidrBlockState =
SubnetCidrBlockState' {_scbsState = Nothing, _scbsStatusMessage = Nothing}
scbsState :: Lens' SubnetCidrBlockState (Maybe SubnetCidrBlockStateCode)
scbsState = lens _scbsState (\ s a -> s{_scbsState = a})
scbsStatusMessage :: Lens' SubnetCidrBlockState (Maybe Text)
scbsStatusMessage = lens _scbsStatusMessage (\ s a -> s{_scbsStatusMessage = a})
instance FromXML SubnetCidrBlockState where
parseXML x
= SubnetCidrBlockState' <$>
(x .@? "state") <*> (x .@? "statusMessage")
instance Hashable SubnetCidrBlockState where
instance NFData SubnetCidrBlockState where
data SubnetIPv6CidrBlockAssociation = SubnetIPv6CidrBlockAssociation'
{ _sicbaAssociationId :: !(Maybe Text)
, _sicbaIPv6CidrBlock :: !(Maybe Text)
, _sicbaIPv6CidrBlockState :: !(Maybe SubnetCidrBlockState)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
subnetIPv6CidrBlockAssociation
:: SubnetIPv6CidrBlockAssociation
subnetIPv6CidrBlockAssociation =
SubnetIPv6CidrBlockAssociation'
{ _sicbaAssociationId = Nothing
, _sicbaIPv6CidrBlock = Nothing
, _sicbaIPv6CidrBlockState = Nothing
}
sicbaAssociationId :: Lens' SubnetIPv6CidrBlockAssociation (Maybe Text)
sicbaAssociationId = lens _sicbaAssociationId (\ s a -> s{_sicbaAssociationId = a})
sicbaIPv6CidrBlock :: Lens' SubnetIPv6CidrBlockAssociation (Maybe Text)
sicbaIPv6CidrBlock = lens _sicbaIPv6CidrBlock (\ s a -> s{_sicbaIPv6CidrBlock = a})
sicbaIPv6CidrBlockState :: Lens' SubnetIPv6CidrBlockAssociation (Maybe SubnetCidrBlockState)
sicbaIPv6CidrBlockState = lens _sicbaIPv6CidrBlockState (\ s a -> s{_sicbaIPv6CidrBlockState = a})
instance FromXML SubnetIPv6CidrBlockAssociation where
parseXML x
= SubnetIPv6CidrBlockAssociation' <$>
(x .@? "associationId") <*> (x .@? "ipv6CidrBlock")
<*> (x .@? "ipv6CidrBlockState")
instance Hashable SubnetIPv6CidrBlockAssociation
where
instance NFData SubnetIPv6CidrBlockAssociation where
newtype SuccessfulInstanceCreditSpecificationItem = SuccessfulInstanceCreditSpecificationItem'
{ _sicsiInstanceId :: Maybe Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
successfulInstanceCreditSpecificationItem
:: SuccessfulInstanceCreditSpecificationItem
successfulInstanceCreditSpecificationItem =
SuccessfulInstanceCreditSpecificationItem' {_sicsiInstanceId = Nothing}
sicsiInstanceId :: Lens' SuccessfulInstanceCreditSpecificationItem (Maybe Text)
sicsiInstanceId = lens _sicsiInstanceId (\ s a -> s{_sicsiInstanceId = a})
instance FromXML
SuccessfulInstanceCreditSpecificationItem
where
parseXML x
= SuccessfulInstanceCreditSpecificationItem' <$>
(x .@? "instanceId")
instance Hashable
SuccessfulInstanceCreditSpecificationItem
where
instance NFData
SuccessfulInstanceCreditSpecificationItem
where
data Tag = Tag'
{ _tagKey :: !Text
, _tagValue :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
tag
:: Text
-> Text
-> Tag
tag pKey_ pValue_ = Tag' {_tagKey = pKey_, _tagValue = pValue_}
tagKey :: Lens' Tag Text
tagKey = lens _tagKey (\ s a -> s{_tagKey = a})
tagValue :: Lens' Tag Text
tagValue = lens _tagValue (\ s a -> s{_tagValue = a})
instance FromXML Tag where
parseXML x = Tag' <$> (x .@ "key") <*> (x .@ "value")
instance Hashable Tag where
instance NFData Tag where
instance ToQuery Tag where
toQuery Tag'{..}
= mconcat ["Key" =: _tagKey, "Value" =: _tagValue]
data TagDescription = TagDescription'
{ _tdResourceId :: !Text
, _tdResourceType :: !ResourceType
, _tdKey :: !Text
, _tdValue :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
tagDescription
:: Text
-> ResourceType
-> Text
-> Text
-> TagDescription
tagDescription pResourceId_ pResourceType_ pKey_ pValue_ =
TagDescription'
{ _tdResourceId = pResourceId_
, _tdResourceType = pResourceType_
, _tdKey = pKey_
, _tdValue = pValue_
}
tdResourceId :: Lens' TagDescription Text
tdResourceId = lens _tdResourceId (\ s a -> s{_tdResourceId = a})
tdResourceType :: Lens' TagDescription ResourceType
tdResourceType = lens _tdResourceType (\ s a -> s{_tdResourceType = a})
tdKey :: Lens' TagDescription Text
tdKey = lens _tdKey (\ s a -> s{_tdKey = a})
tdValue :: Lens' TagDescription Text
tdValue = lens _tdValue (\ s a -> s{_tdValue = a})
instance FromXML TagDescription where
parseXML x
= TagDescription' <$>
(x .@ "resourceId") <*> (x .@ "resourceType") <*>
(x .@ "key")
<*> (x .@ "value")
instance Hashable TagDescription where
instance NFData TagDescription where
data TagSpecification = TagSpecification'
{ _tsResourceType :: !(Maybe ResourceType)
, _tsTags :: !(Maybe [Tag])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
tagSpecification
:: TagSpecification
tagSpecification =
TagSpecification' {_tsResourceType = Nothing, _tsTags = Nothing}
tsResourceType :: Lens' TagSpecification (Maybe ResourceType)
tsResourceType = lens _tsResourceType (\ s a -> s{_tsResourceType = a})
tsTags :: Lens' TagSpecification [Tag]
tsTags = lens _tsTags (\ s a -> s{_tsTags = a}) . _Default . _Coerce
instance Hashable TagSpecification where
instance NFData TagSpecification where
instance ToQuery TagSpecification where
toQuery TagSpecification'{..}
= mconcat
["ResourceType" =: _tsResourceType,
toQuery (toQueryList "Tag" <$> _tsTags)]
data TargetCapacitySpecification = TargetCapacitySpecification'
{ _tcsOnDemandTargetCapacity :: !(Maybe Int)
, _tcsDefaultTargetCapacityType :: !(Maybe DefaultTargetCapacityType)
, _tcsTotalTargetCapacity :: !(Maybe Int)
, _tcsSpotTargetCapacity :: !(Maybe Int)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
targetCapacitySpecification
:: TargetCapacitySpecification
targetCapacitySpecification =
TargetCapacitySpecification'
{ _tcsOnDemandTargetCapacity = Nothing
, _tcsDefaultTargetCapacityType = Nothing
, _tcsTotalTargetCapacity = Nothing
, _tcsSpotTargetCapacity = Nothing
}
tcsOnDemandTargetCapacity :: Lens' TargetCapacitySpecification (Maybe Int)
tcsOnDemandTargetCapacity = lens _tcsOnDemandTargetCapacity (\ s a -> s{_tcsOnDemandTargetCapacity = a})
tcsDefaultTargetCapacityType :: Lens' TargetCapacitySpecification (Maybe DefaultTargetCapacityType)
tcsDefaultTargetCapacityType = lens _tcsDefaultTargetCapacityType (\ s a -> s{_tcsDefaultTargetCapacityType = a})
tcsTotalTargetCapacity :: Lens' TargetCapacitySpecification (Maybe Int)
tcsTotalTargetCapacity = lens _tcsTotalTargetCapacity (\ s a -> s{_tcsTotalTargetCapacity = a})
tcsSpotTargetCapacity :: Lens' TargetCapacitySpecification (Maybe Int)
tcsSpotTargetCapacity = lens _tcsSpotTargetCapacity (\ s a -> s{_tcsSpotTargetCapacity = a})
instance FromXML TargetCapacitySpecification where
parseXML x
= TargetCapacitySpecification' <$>
(x .@? "onDemandTargetCapacity") <*>
(x .@? "defaultTargetCapacityType")
<*> (x .@? "totalTargetCapacity")
<*> (x .@? "spotTargetCapacity")
instance Hashable TargetCapacitySpecification where
instance NFData TargetCapacitySpecification where
data TargetCapacitySpecificationRequest = TargetCapacitySpecificationRequest'
{ _tcsrOnDemandTargetCapacity :: !(Maybe Int)
, _tcsrDefaultTargetCapacityType :: !(Maybe DefaultTargetCapacityType)
, _tcsrSpotTargetCapacity :: !(Maybe Int)
, _tcsrTotalTargetCapacity :: !Int
} deriving (Eq, Read, Show, Data, Typeable, Generic)
targetCapacitySpecificationRequest
:: Int
-> TargetCapacitySpecificationRequest
targetCapacitySpecificationRequest pTotalTargetCapacity_ =
TargetCapacitySpecificationRequest'
{ _tcsrOnDemandTargetCapacity = Nothing
, _tcsrDefaultTargetCapacityType = Nothing
, _tcsrSpotTargetCapacity = Nothing
, _tcsrTotalTargetCapacity = pTotalTargetCapacity_
}
tcsrOnDemandTargetCapacity :: Lens' TargetCapacitySpecificationRequest (Maybe Int)
tcsrOnDemandTargetCapacity = lens _tcsrOnDemandTargetCapacity (\ s a -> s{_tcsrOnDemandTargetCapacity = a})
tcsrDefaultTargetCapacityType :: Lens' TargetCapacitySpecificationRequest (Maybe DefaultTargetCapacityType)
tcsrDefaultTargetCapacityType = lens _tcsrDefaultTargetCapacityType (\ s a -> s{_tcsrDefaultTargetCapacityType = a})
tcsrSpotTargetCapacity :: Lens' TargetCapacitySpecificationRequest (Maybe Int)
tcsrSpotTargetCapacity = lens _tcsrSpotTargetCapacity (\ s a -> s{_tcsrSpotTargetCapacity = a})
tcsrTotalTargetCapacity :: Lens' TargetCapacitySpecificationRequest Int
tcsrTotalTargetCapacity = lens _tcsrTotalTargetCapacity (\ s a -> s{_tcsrTotalTargetCapacity = a})
instance Hashable TargetCapacitySpecificationRequest
where
instance NFData TargetCapacitySpecificationRequest
where
instance ToQuery TargetCapacitySpecificationRequest
where
toQuery TargetCapacitySpecificationRequest'{..}
= mconcat
["OnDemandTargetCapacity" =:
_tcsrOnDemandTargetCapacity,
"DefaultTargetCapacityType" =:
_tcsrDefaultTargetCapacityType,
"SpotTargetCapacity" =: _tcsrSpotTargetCapacity,
"TotalTargetCapacity" =: _tcsrTotalTargetCapacity]
data TargetConfiguration = TargetConfiguration'
{ _tcInstanceCount :: !(Maybe Int)
, _tcOfferingId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
targetConfiguration
:: TargetConfiguration
targetConfiguration =
TargetConfiguration' {_tcInstanceCount = Nothing, _tcOfferingId = Nothing}
tcInstanceCount :: Lens' TargetConfiguration (Maybe Int)
tcInstanceCount = lens _tcInstanceCount (\ s a -> s{_tcInstanceCount = a})
tcOfferingId :: Lens' TargetConfiguration (Maybe Text)
tcOfferingId = lens _tcOfferingId (\ s a -> s{_tcOfferingId = a})
instance FromXML TargetConfiguration where
parseXML x
= TargetConfiguration' <$>
(x .@? "instanceCount") <*> (x .@? "offeringId")
instance Hashable TargetConfiguration where
instance NFData TargetConfiguration where
data TargetConfigurationRequest = TargetConfigurationRequest'
{ _tcrInstanceCount :: !(Maybe Int)
, _tcrOfferingId :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
targetConfigurationRequest
:: Text
-> TargetConfigurationRequest
targetConfigurationRequest pOfferingId_ =
TargetConfigurationRequest'
{_tcrInstanceCount = Nothing, _tcrOfferingId = pOfferingId_}
tcrInstanceCount :: Lens' TargetConfigurationRequest (Maybe Int)
tcrInstanceCount = lens _tcrInstanceCount (\ s a -> s{_tcrInstanceCount = a})
tcrOfferingId :: Lens' TargetConfigurationRequest Text
tcrOfferingId = lens _tcrOfferingId (\ s a -> s{_tcrOfferingId = a})
instance Hashable TargetConfigurationRequest where
instance NFData TargetConfigurationRequest where
instance ToQuery TargetConfigurationRequest where
toQuery TargetConfigurationRequest'{..}
= mconcat
["InstanceCount" =: _tcrInstanceCount,
"OfferingId" =: _tcrOfferingId]
newtype TargetGroup = TargetGroup'
{ _tgARN :: Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
targetGroup
:: Text
-> TargetGroup
targetGroup pARN_ = TargetGroup' {_tgARN = pARN_}
tgARN :: Lens' TargetGroup Text
tgARN = lens _tgARN (\ s a -> s{_tgARN = a})
instance FromXML TargetGroup where
parseXML x = TargetGroup' <$> (x .@ "arn")
instance Hashable TargetGroup where
instance NFData TargetGroup where
instance ToQuery TargetGroup where
toQuery TargetGroup'{..} = mconcat ["Arn" =: _tgARN]
newtype TargetGroupsConfig = TargetGroupsConfig'
{ _tgcTargetGroups :: List1 TargetGroup
} deriving (Eq, Read, Show, Data, Typeable, Generic)
targetGroupsConfig
:: NonEmpty TargetGroup
-> TargetGroupsConfig
targetGroupsConfig pTargetGroups_ =
TargetGroupsConfig' {_tgcTargetGroups = _List1 # pTargetGroups_}
tgcTargetGroups :: Lens' TargetGroupsConfig (NonEmpty TargetGroup)
tgcTargetGroups = lens _tgcTargetGroups (\ s a -> s{_tgcTargetGroups = a}) . _List1
instance FromXML TargetGroupsConfig where
parseXML x
= TargetGroupsConfig' <$>
(x .@? "targetGroups" .!@ mempty >>=
parseXMLList1 "item")
instance Hashable TargetGroupsConfig where
instance NFData TargetGroupsConfig where
instance ToQuery TargetGroupsConfig where
toQuery TargetGroupsConfig'{..}
= mconcat
[toQueryList "TargetGroups" _tgcTargetGroups]
data TargetReservationValue = TargetReservationValue'
{ _trvReservationValue :: !(Maybe ReservationValue)
, _trvTargetConfiguration :: !(Maybe TargetConfiguration)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
targetReservationValue
:: TargetReservationValue
targetReservationValue =
TargetReservationValue'
{_trvReservationValue = Nothing, _trvTargetConfiguration = Nothing}
trvReservationValue :: Lens' TargetReservationValue (Maybe ReservationValue)
trvReservationValue = lens _trvReservationValue (\ s a -> s{_trvReservationValue = a})
trvTargetConfiguration :: Lens' TargetReservationValue (Maybe TargetConfiguration)
trvTargetConfiguration = lens _trvTargetConfiguration (\ s a -> s{_trvTargetConfiguration = a})
instance FromXML TargetReservationValue where
parseXML x
= TargetReservationValue' <$>
(x .@? "reservationValue") <*>
(x .@? "targetConfiguration")
instance Hashable TargetReservationValue where
instance NFData TargetReservationValue where
data UnsuccessfulInstanceCreditSpecificationItem = UnsuccessfulInstanceCreditSpecificationItem'
{ _uicsiInstanceId :: !(Maybe Text)
, _uicsiError :: !(Maybe UnsuccessfulInstanceCreditSpecificationItemError)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
unsuccessfulInstanceCreditSpecificationItem
:: UnsuccessfulInstanceCreditSpecificationItem
unsuccessfulInstanceCreditSpecificationItem =
UnsuccessfulInstanceCreditSpecificationItem'
{_uicsiInstanceId = Nothing, _uicsiError = Nothing}
uicsiInstanceId :: Lens' UnsuccessfulInstanceCreditSpecificationItem (Maybe Text)
uicsiInstanceId = lens _uicsiInstanceId (\ s a -> s{_uicsiInstanceId = a})
uicsiError :: Lens' UnsuccessfulInstanceCreditSpecificationItem (Maybe UnsuccessfulInstanceCreditSpecificationItemError)
uicsiError = lens _uicsiError (\ s a -> s{_uicsiError = a})
instance FromXML
UnsuccessfulInstanceCreditSpecificationItem
where
parseXML x
= UnsuccessfulInstanceCreditSpecificationItem' <$>
(x .@? "instanceId") <*> (x .@? "error")
instance Hashable
UnsuccessfulInstanceCreditSpecificationItem
where
instance NFData
UnsuccessfulInstanceCreditSpecificationItem
where
data UnsuccessfulInstanceCreditSpecificationItemError = UnsuccessfulInstanceCreditSpecificationItemError'
{ _uicsieCode :: !(Maybe UnsuccessfulInstanceCreditSpecificationErrorCode)
, _uicsieMessage :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
unsuccessfulInstanceCreditSpecificationItemError
:: UnsuccessfulInstanceCreditSpecificationItemError
unsuccessfulInstanceCreditSpecificationItemError =
UnsuccessfulInstanceCreditSpecificationItemError'
{_uicsieCode = Nothing, _uicsieMessage = Nothing}
uicsieCode :: Lens' UnsuccessfulInstanceCreditSpecificationItemError (Maybe UnsuccessfulInstanceCreditSpecificationErrorCode)
uicsieCode = lens _uicsieCode (\ s a -> s{_uicsieCode = a})
uicsieMessage :: Lens' UnsuccessfulInstanceCreditSpecificationItemError (Maybe Text)
uicsieMessage = lens _uicsieMessage (\ s a -> s{_uicsieMessage = a})
instance FromXML
UnsuccessfulInstanceCreditSpecificationItemError
where
parseXML x
= UnsuccessfulInstanceCreditSpecificationItemError'
<$> (x .@? "code") <*> (x .@? "message")
instance Hashable
UnsuccessfulInstanceCreditSpecificationItemError
where
instance NFData
UnsuccessfulInstanceCreditSpecificationItemError
where
data UnsuccessfulItem = UnsuccessfulItem'
{ _uiResourceId :: !(Maybe Text)
, _uiError :: !UnsuccessfulItemError
} deriving (Eq, Read, Show, Data, Typeable, Generic)
unsuccessfulItem
:: UnsuccessfulItemError
-> UnsuccessfulItem
unsuccessfulItem pError_ =
UnsuccessfulItem' {_uiResourceId = Nothing, _uiError = pError_}
uiResourceId :: Lens' UnsuccessfulItem (Maybe Text)
uiResourceId = lens _uiResourceId (\ s a -> s{_uiResourceId = a})
uiError :: Lens' UnsuccessfulItem UnsuccessfulItemError
uiError = lens _uiError (\ s a -> s{_uiError = a})
instance FromXML UnsuccessfulItem where
parseXML x
= UnsuccessfulItem' <$>
(x .@? "resourceId") <*> (x .@ "error")
instance Hashable UnsuccessfulItem where
instance NFData UnsuccessfulItem where
data UnsuccessfulItemError = UnsuccessfulItemError'
{ _uieCode :: !Text
, _uieMessage :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
unsuccessfulItemError
:: Text
-> Text
-> UnsuccessfulItemError
unsuccessfulItemError pCode_ pMessage_ =
UnsuccessfulItemError' {_uieCode = pCode_, _uieMessage = pMessage_}
uieCode :: Lens' UnsuccessfulItemError Text
uieCode = lens _uieCode (\ s a -> s{_uieCode = a})
uieMessage :: Lens' UnsuccessfulItemError Text
uieMessage = lens _uieMessage (\ s a -> s{_uieMessage = a})
instance FromXML UnsuccessfulItemError where
parseXML x
= UnsuccessfulItemError' <$>
(x .@ "code") <*> (x .@ "message")
instance Hashable UnsuccessfulItemError where
instance NFData UnsuccessfulItemError where
data UserBucket = UserBucket'
{ _ubS3Key :: !(Maybe Text)
, _ubS3Bucket :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
userBucket
:: UserBucket
userBucket = UserBucket' {_ubS3Key = Nothing, _ubS3Bucket = Nothing}
ubS3Key :: Lens' UserBucket (Maybe Text)
ubS3Key = lens _ubS3Key (\ s a -> s{_ubS3Key = a})
ubS3Bucket :: Lens' UserBucket (Maybe Text)
ubS3Bucket = lens _ubS3Bucket (\ s a -> s{_ubS3Bucket = a})
instance Hashable UserBucket where
instance NFData UserBucket where
instance ToQuery UserBucket where
toQuery UserBucket'{..}
= mconcat
["S3Key" =: _ubS3Key, "S3Bucket" =: _ubS3Bucket]
data UserBucketDetails = UserBucketDetails'
{ _ubdS3Key :: !(Maybe Text)
, _ubdS3Bucket :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
userBucketDetails
:: UserBucketDetails
userBucketDetails =
UserBucketDetails' {_ubdS3Key = Nothing, _ubdS3Bucket = Nothing}
ubdS3Key :: Lens' UserBucketDetails (Maybe Text)
ubdS3Key = lens _ubdS3Key (\ s a -> s{_ubdS3Key = a})
ubdS3Bucket :: Lens' UserBucketDetails (Maybe Text)
ubdS3Bucket = lens _ubdS3Bucket (\ s a -> s{_ubdS3Bucket = a})
instance FromXML UserBucketDetails where
parseXML x
= UserBucketDetails' <$>
(x .@? "s3Key") <*> (x .@? "s3Bucket")
instance Hashable UserBucketDetails where
instance NFData UserBucketDetails where
newtype UserData = UserData'
{ _udData :: Maybe Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
userData
:: UserData
userData = UserData' {_udData = Nothing}
udData :: Lens' UserData (Maybe Text)
udData = lens _udData (\ s a -> s{_udData = a})
instance Hashable UserData where
instance NFData UserData where
instance ToQuery UserData where
toQuery UserData'{..} = mconcat ["Data" =: _udData]
data UserIdGroupPair = UserIdGroupPair'
{ _uigpVPCPeeringConnectionId :: !(Maybe Text)
, _uigpVPCId :: !(Maybe Text)
, _uigpUserId :: !(Maybe Text)
, _uigpGroupId :: !(Maybe Text)
, _uigpGroupName :: !(Maybe Text)
, _uigpDescription :: !(Maybe Text)
, _uigpPeeringStatus :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
userIdGroupPair
:: UserIdGroupPair
userIdGroupPair =
UserIdGroupPair'
{ _uigpVPCPeeringConnectionId = Nothing
, _uigpVPCId = Nothing
, _uigpUserId = Nothing
, _uigpGroupId = Nothing
, _uigpGroupName = Nothing
, _uigpDescription = Nothing
, _uigpPeeringStatus = Nothing
}
uigpVPCPeeringConnectionId :: Lens' UserIdGroupPair (Maybe Text)
uigpVPCPeeringConnectionId = lens _uigpVPCPeeringConnectionId (\ s a -> s{_uigpVPCPeeringConnectionId = a})
uigpVPCId :: Lens' UserIdGroupPair (Maybe Text)
uigpVPCId = lens _uigpVPCId (\ s a -> s{_uigpVPCId = a})
uigpUserId :: Lens' UserIdGroupPair (Maybe Text)
uigpUserId = lens _uigpUserId (\ s a -> s{_uigpUserId = a})
uigpGroupId :: Lens' UserIdGroupPair (Maybe Text)
uigpGroupId = lens _uigpGroupId (\ s a -> s{_uigpGroupId = a})
uigpGroupName :: Lens' UserIdGroupPair (Maybe Text)
uigpGroupName = lens _uigpGroupName (\ s a -> s{_uigpGroupName = a})
uigpDescription :: Lens' UserIdGroupPair (Maybe Text)
uigpDescription = lens _uigpDescription (\ s a -> s{_uigpDescription = a})
uigpPeeringStatus :: Lens' UserIdGroupPair (Maybe Text)
uigpPeeringStatus = lens _uigpPeeringStatus (\ s a -> s{_uigpPeeringStatus = a})
instance FromXML UserIdGroupPair where
parseXML x
= UserIdGroupPair' <$>
(x .@? "vpcPeeringConnectionId") <*> (x .@? "vpcId")
<*> (x .@? "userId")
<*> (x .@? "groupId")
<*> (x .@? "groupName")
<*> (x .@? "description")
<*> (x .@? "peeringStatus")
instance Hashable UserIdGroupPair where
instance NFData UserIdGroupPair where
instance ToQuery UserIdGroupPair where
toQuery UserIdGroupPair'{..}
= mconcat
["VpcPeeringConnectionId" =:
_uigpVPCPeeringConnectionId,
"VpcId" =: _uigpVPCId, "UserId" =: _uigpUserId,
"GroupId" =: _uigpGroupId,
"GroupName" =: _uigpGroupName,
"Description" =: _uigpDescription,
"PeeringStatus" =: _uigpPeeringStatus]
data VGWTelemetry = VGWTelemetry'
{ _vtStatus :: !(Maybe TelemetryStatus)
, _vtOutsideIPAddress :: !(Maybe Text)
, _vtLastStatusChange :: !(Maybe ISO8601)
, _vtAcceptedRouteCount :: !(Maybe Int)
, _vtStatusMessage :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
vgwTelemetry
:: VGWTelemetry
vgwTelemetry =
VGWTelemetry'
{ _vtStatus = Nothing
, _vtOutsideIPAddress = Nothing
, _vtLastStatusChange = Nothing
, _vtAcceptedRouteCount = Nothing
, _vtStatusMessage = Nothing
}
vtStatus :: Lens' VGWTelemetry (Maybe TelemetryStatus)
vtStatus = lens _vtStatus (\ s a -> s{_vtStatus = a})
vtOutsideIPAddress :: Lens' VGWTelemetry (Maybe Text)
vtOutsideIPAddress = lens _vtOutsideIPAddress (\ s a -> s{_vtOutsideIPAddress = a})
vtLastStatusChange :: Lens' VGWTelemetry (Maybe UTCTime)
vtLastStatusChange = lens _vtLastStatusChange (\ s a -> s{_vtLastStatusChange = a}) . mapping _Time
vtAcceptedRouteCount :: Lens' VGWTelemetry (Maybe Int)
vtAcceptedRouteCount = lens _vtAcceptedRouteCount (\ s a -> s{_vtAcceptedRouteCount = a})
vtStatusMessage :: Lens' VGWTelemetry (Maybe Text)
vtStatusMessage = lens _vtStatusMessage (\ s a -> s{_vtStatusMessage = a})
instance FromXML VGWTelemetry where
parseXML x
= VGWTelemetry' <$>
(x .@? "status") <*> (x .@? "outsideIpAddress") <*>
(x .@? "lastStatusChange")
<*> (x .@? "acceptedRouteCount")
<*> (x .@? "statusMessage")
instance Hashable VGWTelemetry where
instance NFData VGWTelemetry where
data VPC = VPC'
{ _vpcIPv6CidrBlockAssociationSet :: !(Maybe [VPCIPv6CidrBlockAssociation])
, _vpcCidrBlockAssociationSet :: !(Maybe [VPCCidrBlockAssociation])
, _vpcTags :: !(Maybe [Tag])
, _vpcIsDefault :: !(Maybe Bool)
, _vpcCidrBlock :: !Text
, _vpcDHCPOptionsId :: !Text
, _vpcInstanceTenancy :: !Tenancy
, _vpcState :: !VPCState
, _vpcVPCId :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
vpc
:: Text
-> Text
-> Tenancy
-> VPCState
-> Text
-> VPC
vpc pCidrBlock_ pDHCPOptionsId_ pInstanceTenancy_ pState_ pVPCId_ =
VPC'
{ _vpcIPv6CidrBlockAssociationSet = Nothing
, _vpcCidrBlockAssociationSet = Nothing
, _vpcTags = Nothing
, _vpcIsDefault = Nothing
, _vpcCidrBlock = pCidrBlock_
, _vpcDHCPOptionsId = pDHCPOptionsId_
, _vpcInstanceTenancy = pInstanceTenancy_
, _vpcState = pState_
, _vpcVPCId = pVPCId_
}
vpcIPv6CidrBlockAssociationSet :: Lens' VPC [VPCIPv6CidrBlockAssociation]
vpcIPv6CidrBlockAssociationSet = lens _vpcIPv6CidrBlockAssociationSet (\ s a -> s{_vpcIPv6CidrBlockAssociationSet = a}) . _Default . _Coerce
vpcCidrBlockAssociationSet :: Lens' VPC [VPCCidrBlockAssociation]
vpcCidrBlockAssociationSet = lens _vpcCidrBlockAssociationSet (\ s a -> s{_vpcCidrBlockAssociationSet = a}) . _Default . _Coerce
vpcTags :: Lens' VPC [Tag]
vpcTags = lens _vpcTags (\ s a -> s{_vpcTags = a}) . _Default . _Coerce
vpcIsDefault :: Lens' VPC (Maybe Bool)
vpcIsDefault = lens _vpcIsDefault (\ s a -> s{_vpcIsDefault = a})
vpcCidrBlock :: Lens' VPC Text
vpcCidrBlock = lens _vpcCidrBlock (\ s a -> s{_vpcCidrBlock = a})
vpcDHCPOptionsId :: Lens' VPC Text
vpcDHCPOptionsId = lens _vpcDHCPOptionsId (\ s a -> s{_vpcDHCPOptionsId = a})
vpcInstanceTenancy :: Lens' VPC Tenancy
vpcInstanceTenancy = lens _vpcInstanceTenancy (\ s a -> s{_vpcInstanceTenancy = a})
vpcState :: Lens' VPC VPCState
vpcState = lens _vpcState (\ s a -> s{_vpcState = a})
vpcVPCId :: Lens' VPC Text
vpcVPCId = lens _vpcVPCId (\ s a -> s{_vpcVPCId = a})
instance FromXML VPC where
parseXML x
= VPC' <$>
(x .@? "ipv6CidrBlockAssociationSet" .!@ mempty >>=
may (parseXMLList "item"))
<*>
(x .@? "cidrBlockAssociationSet" .!@ mempty >>=
may (parseXMLList "item"))
<*>
(x .@? "tagSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "isDefault")
<*> (x .@ "cidrBlock")
<*> (x .@ "dhcpOptionsId")
<*> (x .@ "instanceTenancy")
<*> (x .@ "state")
<*> (x .@ "vpcId")
instance Hashable VPC where
instance NFData VPC where
data VPCAttachment = VPCAttachment'
{ _vaState :: !(Maybe AttachmentStatus)
, _vaVPCId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
vpcAttachment
:: VPCAttachment
vpcAttachment = VPCAttachment' {_vaState = Nothing, _vaVPCId = Nothing}
vaState :: Lens' VPCAttachment (Maybe AttachmentStatus)
vaState = lens _vaState (\ s a -> s{_vaState = a})
vaVPCId :: Lens' VPCAttachment (Maybe Text)
vaVPCId = lens _vaVPCId (\ s a -> s{_vaVPCId = a})
instance FromXML VPCAttachment where
parseXML x
= VPCAttachment' <$>
(x .@? "state") <*> (x .@? "vpcId")
instance Hashable VPCAttachment where
instance NFData VPCAttachment where
data VPCCidrBlockAssociation = VPCCidrBlockAssociation'
{ _vcbaAssociationId :: !(Maybe Text)
, _vcbaCidrBlockState :: !(Maybe VPCCidrBlockState)
, _vcbaCidrBlock :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
vpcCidrBlockAssociation
:: VPCCidrBlockAssociation
vpcCidrBlockAssociation =
VPCCidrBlockAssociation'
{ _vcbaAssociationId = Nothing
, _vcbaCidrBlockState = Nothing
, _vcbaCidrBlock = Nothing
}
vcbaAssociationId :: Lens' VPCCidrBlockAssociation (Maybe Text)
vcbaAssociationId = lens _vcbaAssociationId (\ s a -> s{_vcbaAssociationId = a})
vcbaCidrBlockState :: Lens' VPCCidrBlockAssociation (Maybe VPCCidrBlockState)
vcbaCidrBlockState = lens _vcbaCidrBlockState (\ s a -> s{_vcbaCidrBlockState = a})
vcbaCidrBlock :: Lens' VPCCidrBlockAssociation (Maybe Text)
vcbaCidrBlock = lens _vcbaCidrBlock (\ s a -> s{_vcbaCidrBlock = a})
instance FromXML VPCCidrBlockAssociation where
parseXML x
= VPCCidrBlockAssociation' <$>
(x .@? "associationId") <*> (x .@? "cidrBlockState")
<*> (x .@? "cidrBlock")
instance Hashable VPCCidrBlockAssociation where
instance NFData VPCCidrBlockAssociation where
data VPCCidrBlockState = VPCCidrBlockState'
{ _vcbsState :: !(Maybe VPCCidrBlockStateCode)
, _vcbsStatusMessage :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
vpcCidrBlockState
:: VPCCidrBlockState
vpcCidrBlockState =
VPCCidrBlockState' {_vcbsState = Nothing, _vcbsStatusMessage = Nothing}
vcbsState :: Lens' VPCCidrBlockState (Maybe VPCCidrBlockStateCode)
vcbsState = lens _vcbsState (\ s a -> s{_vcbsState = a})
vcbsStatusMessage :: Lens' VPCCidrBlockState (Maybe Text)
vcbsStatusMessage = lens _vcbsStatusMessage (\ s a -> s{_vcbsStatusMessage = a})
instance FromXML VPCCidrBlockState where
parseXML x
= VPCCidrBlockState' <$>
(x .@? "state") <*> (x .@? "statusMessage")
instance Hashable VPCCidrBlockState where
instance NFData VPCCidrBlockState where
data VPCClassicLink = VPCClassicLink'
{ _vclVPCId :: !(Maybe Text)
, _vclTags :: !(Maybe [Tag])
, _vclClassicLinkEnabled :: !(Maybe Bool)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
vpcClassicLink
:: VPCClassicLink
vpcClassicLink =
VPCClassicLink'
{_vclVPCId = Nothing, _vclTags = Nothing, _vclClassicLinkEnabled = Nothing}
vclVPCId :: Lens' VPCClassicLink (Maybe Text)
vclVPCId = lens _vclVPCId (\ s a -> s{_vclVPCId = a})
vclTags :: Lens' VPCClassicLink [Tag]
vclTags = lens _vclTags (\ s a -> s{_vclTags = a}) . _Default . _Coerce
vclClassicLinkEnabled :: Lens' VPCClassicLink (Maybe Bool)
vclClassicLinkEnabled = lens _vclClassicLinkEnabled (\ s a -> s{_vclClassicLinkEnabled = a})
instance FromXML VPCClassicLink where
parseXML x
= VPCClassicLink' <$>
(x .@? "vpcId") <*>
(x .@? "tagSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "classicLinkEnabled")
instance Hashable VPCClassicLink where
instance NFData VPCClassicLink where
data VPCEndpoint = VPCEndpoint'
{ _veGroups :: !(Maybe [SecurityGroupIdentifier])
, _veState :: !(Maybe State)
, _vePolicyDocument :: !(Maybe Text)
, _veSubnetIds :: !(Maybe [Text])
, _veNetworkInterfaceIds :: !(Maybe [Text])
, _veVPCId :: !(Maybe Text)
, _veDNSEntries :: !(Maybe [DNSEntry])
, _veVPCEndpointType :: !(Maybe VPCEndpointType)
, _vePrivateDNSEnabled :: !(Maybe Bool)
, _veCreationTimestamp :: !(Maybe ISO8601)
, _veServiceName :: !(Maybe Text)
, _veVPCEndpointId :: !(Maybe Text)
, _veRouteTableIds :: !(Maybe [Text])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
vpcEndpoint
:: VPCEndpoint
vpcEndpoint =
VPCEndpoint'
{ _veGroups = Nothing
, _veState = Nothing
, _vePolicyDocument = Nothing
, _veSubnetIds = Nothing
, _veNetworkInterfaceIds = Nothing
, _veVPCId = Nothing
, _veDNSEntries = Nothing
, _veVPCEndpointType = Nothing
, _vePrivateDNSEnabled = Nothing
, _veCreationTimestamp = Nothing
, _veServiceName = Nothing
, _veVPCEndpointId = Nothing
, _veRouteTableIds = Nothing
}
veGroups :: Lens' VPCEndpoint [SecurityGroupIdentifier]
veGroups = lens _veGroups (\ s a -> s{_veGroups = a}) . _Default . _Coerce
veState :: Lens' VPCEndpoint (Maybe State)
veState = lens _veState (\ s a -> s{_veState = a})
vePolicyDocument :: Lens' VPCEndpoint (Maybe Text)
vePolicyDocument = lens _vePolicyDocument (\ s a -> s{_vePolicyDocument = a})
veSubnetIds :: Lens' VPCEndpoint [Text]
veSubnetIds = lens _veSubnetIds (\ s a -> s{_veSubnetIds = a}) . _Default . _Coerce
veNetworkInterfaceIds :: Lens' VPCEndpoint [Text]
veNetworkInterfaceIds = lens _veNetworkInterfaceIds (\ s a -> s{_veNetworkInterfaceIds = a}) . _Default . _Coerce
veVPCId :: Lens' VPCEndpoint (Maybe Text)
veVPCId = lens _veVPCId (\ s a -> s{_veVPCId = a})
veDNSEntries :: Lens' VPCEndpoint [DNSEntry]
veDNSEntries = lens _veDNSEntries (\ s a -> s{_veDNSEntries = a}) . _Default . _Coerce
veVPCEndpointType :: Lens' VPCEndpoint (Maybe VPCEndpointType)
veVPCEndpointType = lens _veVPCEndpointType (\ s a -> s{_veVPCEndpointType = a})
vePrivateDNSEnabled :: Lens' VPCEndpoint (Maybe Bool)
vePrivateDNSEnabled = lens _vePrivateDNSEnabled (\ s a -> s{_vePrivateDNSEnabled = a})
veCreationTimestamp :: Lens' VPCEndpoint (Maybe UTCTime)
veCreationTimestamp = lens _veCreationTimestamp (\ s a -> s{_veCreationTimestamp = a}) . mapping _Time
veServiceName :: Lens' VPCEndpoint (Maybe Text)
veServiceName = lens _veServiceName (\ s a -> s{_veServiceName = a})
veVPCEndpointId :: Lens' VPCEndpoint (Maybe Text)
veVPCEndpointId = lens _veVPCEndpointId (\ s a -> s{_veVPCEndpointId = a})
veRouteTableIds :: Lens' VPCEndpoint [Text]
veRouteTableIds = lens _veRouteTableIds (\ s a -> s{_veRouteTableIds = a}) . _Default . _Coerce
instance FromXML VPCEndpoint where
parseXML x
= VPCEndpoint' <$>
(x .@? "groupSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "state")
<*> (x .@? "policyDocument")
<*>
(x .@? "subnetIdSet" .!@ mempty >>=
may (parseXMLList "item"))
<*>
(x .@? "networkInterfaceIdSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "vpcId")
<*>
(x .@? "dnsEntrySet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "vpcEndpointType")
<*> (x .@? "privateDnsEnabled")
<*> (x .@? "creationTimestamp")
<*> (x .@? "serviceName")
<*> (x .@? "vpcEndpointId")
<*>
(x .@? "routeTableIdSet" .!@ mempty >>=
may (parseXMLList "item"))
instance Hashable VPCEndpoint where
instance NFData VPCEndpoint where
data VPCEndpointConnection = VPCEndpointConnection'
{ _vecVPCEndpointOwner :: !(Maybe Text)
, _vecVPCEndpointState :: !(Maybe State)
, _vecCreationTimestamp :: !(Maybe ISO8601)
, _vecServiceId :: !(Maybe Text)
, _vecVPCEndpointId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
vpcEndpointConnection
:: VPCEndpointConnection
vpcEndpointConnection =
VPCEndpointConnection'
{ _vecVPCEndpointOwner = Nothing
, _vecVPCEndpointState = Nothing
, _vecCreationTimestamp = Nothing
, _vecServiceId = Nothing
, _vecVPCEndpointId = Nothing
}
vecVPCEndpointOwner :: Lens' VPCEndpointConnection (Maybe Text)
vecVPCEndpointOwner = lens _vecVPCEndpointOwner (\ s a -> s{_vecVPCEndpointOwner = a})
vecVPCEndpointState :: Lens' VPCEndpointConnection (Maybe State)
vecVPCEndpointState = lens _vecVPCEndpointState (\ s a -> s{_vecVPCEndpointState = a})
vecCreationTimestamp :: Lens' VPCEndpointConnection (Maybe UTCTime)
vecCreationTimestamp = lens _vecCreationTimestamp (\ s a -> s{_vecCreationTimestamp = a}) . mapping _Time
vecServiceId :: Lens' VPCEndpointConnection (Maybe Text)
vecServiceId = lens _vecServiceId (\ s a -> s{_vecServiceId = a})
vecVPCEndpointId :: Lens' VPCEndpointConnection (Maybe Text)
vecVPCEndpointId = lens _vecVPCEndpointId (\ s a -> s{_vecVPCEndpointId = a})
instance FromXML VPCEndpointConnection where
parseXML x
= VPCEndpointConnection' <$>
(x .@? "vpcEndpointOwner") <*>
(x .@? "vpcEndpointState")
<*> (x .@? "creationTimestamp")
<*> (x .@? "serviceId")
<*> (x .@? "vpcEndpointId")
instance Hashable VPCEndpointConnection where
instance NFData VPCEndpointConnection where
data VPCIPv6CidrBlockAssociation = VPCIPv6CidrBlockAssociation'
{ _vicbaAssociationId :: !(Maybe Text)
, _vicbaIPv6CidrBlock :: !(Maybe Text)
, _vicbaIPv6CidrBlockState :: !(Maybe VPCCidrBlockState)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
vpcIPv6CidrBlockAssociation
:: VPCIPv6CidrBlockAssociation
vpcIPv6CidrBlockAssociation =
VPCIPv6CidrBlockAssociation'
{ _vicbaAssociationId = Nothing
, _vicbaIPv6CidrBlock = Nothing
, _vicbaIPv6CidrBlockState = Nothing
}
vicbaAssociationId :: Lens' VPCIPv6CidrBlockAssociation (Maybe Text)
vicbaAssociationId = lens _vicbaAssociationId (\ s a -> s{_vicbaAssociationId = a})
vicbaIPv6CidrBlock :: Lens' VPCIPv6CidrBlockAssociation (Maybe Text)
vicbaIPv6CidrBlock = lens _vicbaIPv6CidrBlock (\ s a -> s{_vicbaIPv6CidrBlock = a})
vicbaIPv6CidrBlockState :: Lens' VPCIPv6CidrBlockAssociation (Maybe VPCCidrBlockState)
vicbaIPv6CidrBlockState = lens _vicbaIPv6CidrBlockState (\ s a -> s{_vicbaIPv6CidrBlockState = a})
instance FromXML VPCIPv6CidrBlockAssociation where
parseXML x
= VPCIPv6CidrBlockAssociation' <$>
(x .@? "associationId") <*> (x .@? "ipv6CidrBlock")
<*> (x .@? "ipv6CidrBlockState")
instance Hashable VPCIPv6CidrBlockAssociation where
instance NFData VPCIPv6CidrBlockAssociation where
data VPCPeeringConnection = VPCPeeringConnection'
{ _vpcpcVPCPeeringConnectionId :: !(Maybe Text)
, _vpcpcStatus :: !(Maybe VPCPeeringConnectionStateReason)
, _vpcpcAccepterVPCInfo :: !(Maybe VPCPeeringConnectionVPCInfo)
, _vpcpcRequesterVPCInfo :: !(Maybe VPCPeeringConnectionVPCInfo)
, _vpcpcExpirationTime :: !(Maybe ISO8601)
, _vpcpcTags :: !(Maybe [Tag])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
vpcPeeringConnection
:: VPCPeeringConnection
vpcPeeringConnection =
VPCPeeringConnection'
{ _vpcpcVPCPeeringConnectionId = Nothing
, _vpcpcStatus = Nothing
, _vpcpcAccepterVPCInfo = Nothing
, _vpcpcRequesterVPCInfo = Nothing
, _vpcpcExpirationTime = Nothing
, _vpcpcTags = Nothing
}
vpcpcVPCPeeringConnectionId :: Lens' VPCPeeringConnection (Maybe Text)
vpcpcVPCPeeringConnectionId = lens _vpcpcVPCPeeringConnectionId (\ s a -> s{_vpcpcVPCPeeringConnectionId = a})
vpcpcStatus :: Lens' VPCPeeringConnection (Maybe VPCPeeringConnectionStateReason)
vpcpcStatus = lens _vpcpcStatus (\ s a -> s{_vpcpcStatus = a})
vpcpcAccepterVPCInfo :: Lens' VPCPeeringConnection (Maybe VPCPeeringConnectionVPCInfo)
vpcpcAccepterVPCInfo = lens _vpcpcAccepterVPCInfo (\ s a -> s{_vpcpcAccepterVPCInfo = a})
vpcpcRequesterVPCInfo :: Lens' VPCPeeringConnection (Maybe VPCPeeringConnectionVPCInfo)
vpcpcRequesterVPCInfo = lens _vpcpcRequesterVPCInfo (\ s a -> s{_vpcpcRequesterVPCInfo = a})
vpcpcExpirationTime :: Lens' VPCPeeringConnection (Maybe UTCTime)
vpcpcExpirationTime = lens _vpcpcExpirationTime (\ s a -> s{_vpcpcExpirationTime = a}) . mapping _Time
vpcpcTags :: Lens' VPCPeeringConnection [Tag]
vpcpcTags = lens _vpcpcTags (\ s a -> s{_vpcpcTags = a}) . _Default . _Coerce
instance FromXML VPCPeeringConnection where
parseXML x
= VPCPeeringConnection' <$>
(x .@? "vpcPeeringConnectionId") <*> (x .@? "status")
<*> (x .@? "accepterVpcInfo")
<*> (x .@? "requesterVpcInfo")
<*> (x .@? "expirationTime")
<*>
(x .@? "tagSet" .!@ mempty >>=
may (parseXMLList "item"))
instance Hashable VPCPeeringConnection where
instance NFData VPCPeeringConnection where
data VPCPeeringConnectionOptionsDescription = VPCPeeringConnectionOptionsDescription'
{ _vpcodAllowEgressFromLocalVPCToRemoteClassicLink :: !(Maybe Bool)
, _vpcodAllowEgressFromLocalClassicLinkToRemoteVPC :: !(Maybe Bool)
, _vpcodAllowDNSResolutionFromRemoteVPC :: !(Maybe Bool)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
vpcPeeringConnectionOptionsDescription
:: VPCPeeringConnectionOptionsDescription
vpcPeeringConnectionOptionsDescription =
VPCPeeringConnectionOptionsDescription'
{ _vpcodAllowEgressFromLocalVPCToRemoteClassicLink = Nothing
, _vpcodAllowEgressFromLocalClassicLinkToRemoteVPC = Nothing
, _vpcodAllowDNSResolutionFromRemoteVPC = Nothing
}
vpcodAllowEgressFromLocalVPCToRemoteClassicLink :: Lens' VPCPeeringConnectionOptionsDescription (Maybe Bool)
vpcodAllowEgressFromLocalVPCToRemoteClassicLink = lens _vpcodAllowEgressFromLocalVPCToRemoteClassicLink (\ s a -> s{_vpcodAllowEgressFromLocalVPCToRemoteClassicLink = a})
vpcodAllowEgressFromLocalClassicLinkToRemoteVPC :: Lens' VPCPeeringConnectionOptionsDescription (Maybe Bool)
vpcodAllowEgressFromLocalClassicLinkToRemoteVPC = lens _vpcodAllowEgressFromLocalClassicLinkToRemoteVPC (\ s a -> s{_vpcodAllowEgressFromLocalClassicLinkToRemoteVPC = a})
vpcodAllowDNSResolutionFromRemoteVPC :: Lens' VPCPeeringConnectionOptionsDescription (Maybe Bool)
vpcodAllowDNSResolutionFromRemoteVPC = lens _vpcodAllowDNSResolutionFromRemoteVPC (\ s a -> s{_vpcodAllowDNSResolutionFromRemoteVPC = a})
instance FromXML
VPCPeeringConnectionOptionsDescription
where
parseXML x
= VPCPeeringConnectionOptionsDescription' <$>
(x .@? "allowEgressFromLocalVpcToRemoteClassicLink")
<*>
(x .@? "allowEgressFromLocalClassicLinkToRemoteVpc")
<*> (x .@? "allowDnsResolutionFromRemoteVpc")
instance Hashable
VPCPeeringConnectionOptionsDescription
where
instance NFData
VPCPeeringConnectionOptionsDescription
where
data VPCPeeringConnectionStateReason = VPCPeeringConnectionStateReason'
{ _vpcsrCode :: !(Maybe VPCPeeringConnectionStateReasonCode)
, _vpcsrMessage :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
vpcPeeringConnectionStateReason
:: VPCPeeringConnectionStateReason
vpcPeeringConnectionStateReason =
VPCPeeringConnectionStateReason'
{_vpcsrCode = Nothing, _vpcsrMessage = Nothing}
vpcsrCode :: Lens' VPCPeeringConnectionStateReason (Maybe VPCPeeringConnectionStateReasonCode)
vpcsrCode = lens _vpcsrCode (\ s a -> s{_vpcsrCode = a})
vpcsrMessage :: Lens' VPCPeeringConnectionStateReason (Maybe Text)
vpcsrMessage = lens _vpcsrMessage (\ s a -> s{_vpcsrMessage = a})
instance FromXML VPCPeeringConnectionStateReason
where
parseXML x
= VPCPeeringConnectionStateReason' <$>
(x .@? "code") <*> (x .@? "message")
instance Hashable VPCPeeringConnectionStateReason
where
instance NFData VPCPeeringConnectionStateReason where
data VPCPeeringConnectionVPCInfo = VPCPeeringConnectionVPCInfo'
{ _vpcviCidrBlockSet :: !(Maybe [CidrBlock])
, _vpcviVPCId :: !(Maybe Text)
, _vpcviOwnerId :: !(Maybe Text)
, _vpcviPeeringOptions :: !(Maybe VPCPeeringConnectionOptionsDescription)
, _vpcviCidrBlock :: !(Maybe Text)
, _vpcviRegion :: !(Maybe Text)
, _vpcviIPv6CidrBlockSet :: !(Maybe [IPv6CidrBlock])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
vpcPeeringConnectionVPCInfo
:: VPCPeeringConnectionVPCInfo
vpcPeeringConnectionVPCInfo =
VPCPeeringConnectionVPCInfo'
{ _vpcviCidrBlockSet = Nothing
, _vpcviVPCId = Nothing
, _vpcviOwnerId = Nothing
, _vpcviPeeringOptions = Nothing
, _vpcviCidrBlock = Nothing
, _vpcviRegion = Nothing
, _vpcviIPv6CidrBlockSet = Nothing
}
vpcviCidrBlockSet :: Lens' VPCPeeringConnectionVPCInfo [CidrBlock]
vpcviCidrBlockSet = lens _vpcviCidrBlockSet (\ s a -> s{_vpcviCidrBlockSet = a}) . _Default . _Coerce
vpcviVPCId :: Lens' VPCPeeringConnectionVPCInfo (Maybe Text)
vpcviVPCId = lens _vpcviVPCId (\ s a -> s{_vpcviVPCId = a})
vpcviOwnerId :: Lens' VPCPeeringConnectionVPCInfo (Maybe Text)
vpcviOwnerId = lens _vpcviOwnerId (\ s a -> s{_vpcviOwnerId = a})
vpcviPeeringOptions :: Lens' VPCPeeringConnectionVPCInfo (Maybe VPCPeeringConnectionOptionsDescription)
vpcviPeeringOptions = lens _vpcviPeeringOptions (\ s a -> s{_vpcviPeeringOptions = a})
vpcviCidrBlock :: Lens' VPCPeeringConnectionVPCInfo (Maybe Text)
vpcviCidrBlock = lens _vpcviCidrBlock (\ s a -> s{_vpcviCidrBlock = a})
vpcviRegion :: Lens' VPCPeeringConnectionVPCInfo (Maybe Text)
vpcviRegion = lens _vpcviRegion (\ s a -> s{_vpcviRegion = a})
vpcviIPv6CidrBlockSet :: Lens' VPCPeeringConnectionVPCInfo [IPv6CidrBlock]
vpcviIPv6CidrBlockSet = lens _vpcviIPv6CidrBlockSet (\ s a -> s{_vpcviIPv6CidrBlockSet = a}) . _Default . _Coerce
instance FromXML VPCPeeringConnectionVPCInfo where
parseXML x
= VPCPeeringConnectionVPCInfo' <$>
(x .@? "cidrBlockSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "vpcId")
<*> (x .@? "ownerId")
<*> (x .@? "peeringOptions")
<*> (x .@? "cidrBlock")
<*> (x .@? "region")
<*>
(x .@? "ipv6CidrBlockSet" .!@ mempty >>=
may (parseXMLList "item"))
instance Hashable VPCPeeringConnectionVPCInfo where
instance NFData VPCPeeringConnectionVPCInfo where
data VPNConnection = VPNConnection'
{ _vcCustomerGatewayConfiguration :: !(Maybe Text)
, _vcRoutes :: !(Maybe [VPNStaticRoute])
, _vcVPNGatewayId :: !(Maybe Text)
, _vcCategory :: !(Maybe Text)
, _vcOptions :: !(Maybe VPNConnectionOptions)
, _vcTags :: !(Maybe [Tag])
, _vcVGWTelemetry :: !(Maybe [VGWTelemetry])
, _vcVPNConnectionId :: !Text
, _vcCustomerGatewayId :: !Text
, _vcState :: !VPNState
, _vcType :: !GatewayType
} deriving (Eq, Read, Show, Data, Typeable, Generic)
vpnConnection
:: Text
-> Text
-> VPNState
-> GatewayType
-> VPNConnection
vpnConnection pVPNConnectionId_ pCustomerGatewayId_ pState_ pType_ =
VPNConnection'
{ _vcCustomerGatewayConfiguration = Nothing
, _vcRoutes = Nothing
, _vcVPNGatewayId = Nothing
, _vcCategory = Nothing
, _vcOptions = Nothing
, _vcTags = Nothing
, _vcVGWTelemetry = Nothing
, _vcVPNConnectionId = pVPNConnectionId_
, _vcCustomerGatewayId = pCustomerGatewayId_
, _vcState = pState_
, _vcType = pType_
}
vcCustomerGatewayConfiguration :: Lens' VPNConnection (Maybe Text)
vcCustomerGatewayConfiguration = lens _vcCustomerGatewayConfiguration (\ s a -> s{_vcCustomerGatewayConfiguration = a})
vcRoutes :: Lens' VPNConnection [VPNStaticRoute]
vcRoutes = lens _vcRoutes (\ s a -> s{_vcRoutes = a}) . _Default . _Coerce
vcVPNGatewayId :: Lens' VPNConnection (Maybe Text)
vcVPNGatewayId = lens _vcVPNGatewayId (\ s a -> s{_vcVPNGatewayId = a})
vcCategory :: Lens' VPNConnection (Maybe Text)
vcCategory = lens _vcCategory (\ s a -> s{_vcCategory = a})
vcOptions :: Lens' VPNConnection (Maybe VPNConnectionOptions)
vcOptions = lens _vcOptions (\ s a -> s{_vcOptions = a})
vcTags :: Lens' VPNConnection [Tag]
vcTags = lens _vcTags (\ s a -> s{_vcTags = a}) . _Default . _Coerce
vcVGWTelemetry :: Lens' VPNConnection [VGWTelemetry]
vcVGWTelemetry = lens _vcVGWTelemetry (\ s a -> s{_vcVGWTelemetry = a}) . _Default . _Coerce
vcVPNConnectionId :: Lens' VPNConnection Text
vcVPNConnectionId = lens _vcVPNConnectionId (\ s a -> s{_vcVPNConnectionId = a})
vcCustomerGatewayId :: Lens' VPNConnection Text
vcCustomerGatewayId = lens _vcCustomerGatewayId (\ s a -> s{_vcCustomerGatewayId = a})
vcState :: Lens' VPNConnection VPNState
vcState = lens _vcState (\ s a -> s{_vcState = a})
vcType :: Lens' VPNConnection GatewayType
vcType = lens _vcType (\ s a -> s{_vcType = a})
instance FromXML VPNConnection where
parseXML x
= VPNConnection' <$>
(x .@? "customerGatewayConfiguration") <*>
(x .@? "routes" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "vpnGatewayId")
<*> (x .@? "category")
<*> (x .@? "options")
<*>
(x .@? "tagSet" .!@ mempty >>=
may (parseXMLList "item"))
<*>
(x .@? "vgwTelemetry" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@ "vpnConnectionId")
<*> (x .@ "customerGatewayId")
<*> (x .@ "state")
<*> (x .@ "type")
instance Hashable VPNConnection where
instance NFData VPNConnection where
newtype VPNConnectionOptions = VPNConnectionOptions'
{ _vcoStaticRoutesOnly :: Maybe Bool
} deriving (Eq, Read, Show, Data, Typeable, Generic)
vpnConnectionOptions
:: VPNConnectionOptions
vpnConnectionOptions = VPNConnectionOptions' {_vcoStaticRoutesOnly = Nothing}
vcoStaticRoutesOnly :: Lens' VPNConnectionOptions (Maybe Bool)
vcoStaticRoutesOnly = lens _vcoStaticRoutesOnly (\ s a -> s{_vcoStaticRoutesOnly = a})
instance FromXML VPNConnectionOptions where
parseXML x
= VPNConnectionOptions' <$>
(x .@? "staticRoutesOnly")
instance Hashable VPNConnectionOptions where
instance NFData VPNConnectionOptions where
data VPNConnectionOptionsSpecification = VPNConnectionOptionsSpecification'
{ _vcosTunnelOptions :: !(Maybe [VPNTunnelOptionsSpecification])
, _vcosStaticRoutesOnly :: !(Maybe Bool)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
vpnConnectionOptionsSpecification
:: VPNConnectionOptionsSpecification
vpnConnectionOptionsSpecification =
VPNConnectionOptionsSpecification'
{_vcosTunnelOptions = Nothing, _vcosStaticRoutesOnly = Nothing}
vcosTunnelOptions :: Lens' VPNConnectionOptionsSpecification [VPNTunnelOptionsSpecification]
vcosTunnelOptions = lens _vcosTunnelOptions (\ s a -> s{_vcosTunnelOptions = a}) . _Default . _Coerce
vcosStaticRoutesOnly :: Lens' VPNConnectionOptionsSpecification (Maybe Bool)
vcosStaticRoutesOnly = lens _vcosStaticRoutesOnly (\ s a -> s{_vcosStaticRoutesOnly = a})
instance Hashable VPNConnectionOptionsSpecification
where
instance NFData VPNConnectionOptionsSpecification
where
instance ToQuery VPNConnectionOptionsSpecification
where
toQuery VPNConnectionOptionsSpecification'{..}
= mconcat
[toQuery
(toQueryList "TunnelOptions" <$> _vcosTunnelOptions),
"StaticRoutesOnly" =: _vcosStaticRoutesOnly]
data VPNGateway = VPNGateway'
{ _vgState :: !(Maybe VPNState)
, _vgVPCAttachments :: !(Maybe [VPCAttachment])
, _vgVPNGatewayId :: !(Maybe Text)
, _vgAmazonSideASN :: !(Maybe Integer)
, _vgAvailabilityZone :: !(Maybe Text)
, _vgType :: !(Maybe GatewayType)
, _vgTags :: !(Maybe [Tag])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
vpnGateway
:: VPNGateway
vpnGateway =
VPNGateway'
{ _vgState = Nothing
, _vgVPCAttachments = Nothing
, _vgVPNGatewayId = Nothing
, _vgAmazonSideASN = Nothing
, _vgAvailabilityZone = Nothing
, _vgType = Nothing
, _vgTags = Nothing
}
vgState :: Lens' VPNGateway (Maybe VPNState)
vgState = lens _vgState (\ s a -> s{_vgState = a})
vgVPCAttachments :: Lens' VPNGateway [VPCAttachment]
vgVPCAttachments = lens _vgVPCAttachments (\ s a -> s{_vgVPCAttachments = a}) . _Default . _Coerce
vgVPNGatewayId :: Lens' VPNGateway (Maybe Text)
vgVPNGatewayId = lens _vgVPNGatewayId (\ s a -> s{_vgVPNGatewayId = a})
vgAmazonSideASN :: Lens' VPNGateway (Maybe Integer)
vgAmazonSideASN = lens _vgAmazonSideASN (\ s a -> s{_vgAmazonSideASN = a})
vgAvailabilityZone :: Lens' VPNGateway (Maybe Text)
vgAvailabilityZone = lens _vgAvailabilityZone (\ s a -> s{_vgAvailabilityZone = a})
vgType :: Lens' VPNGateway (Maybe GatewayType)
vgType = lens _vgType (\ s a -> s{_vgType = a})
vgTags :: Lens' VPNGateway [Tag]
vgTags = lens _vgTags (\ s a -> s{_vgTags = a}) . _Default . _Coerce
instance FromXML VPNGateway where
parseXML x
= VPNGateway' <$>
(x .@? "state") <*>
(x .@? "attachments" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "vpnGatewayId")
<*> (x .@? "amazonSideAsn")
<*> (x .@? "availabilityZone")
<*> (x .@? "type")
<*>
(x .@? "tagSet" .!@ mempty >>=
may (parseXMLList "item"))
instance Hashable VPNGateway where
instance NFData VPNGateway where
data VPNStaticRoute = VPNStaticRoute'
{ _vsrState :: !(Maybe VPNState)
, _vsrSource :: !(Maybe VPNStaticRouteSource)
, _vsrDestinationCidrBlock :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
vpnStaticRoute
:: VPNStaticRoute
vpnStaticRoute =
VPNStaticRoute'
{ _vsrState = Nothing
, _vsrSource = Nothing
, _vsrDestinationCidrBlock = Nothing
}
vsrState :: Lens' VPNStaticRoute (Maybe VPNState)
vsrState = lens _vsrState (\ s a -> s{_vsrState = a})
vsrSource :: Lens' VPNStaticRoute (Maybe VPNStaticRouteSource)
vsrSource = lens _vsrSource (\ s a -> s{_vsrSource = a})
vsrDestinationCidrBlock :: Lens' VPNStaticRoute (Maybe Text)
vsrDestinationCidrBlock = lens _vsrDestinationCidrBlock (\ s a -> s{_vsrDestinationCidrBlock = a})
instance FromXML VPNStaticRoute where
parseXML x
= VPNStaticRoute' <$>
(x .@? "state") <*> (x .@? "source") <*>
(x .@? "destinationCidrBlock")
instance Hashable VPNStaticRoute where
instance NFData VPNStaticRoute where
data VPNTunnelOptionsSpecification = VPNTunnelOptionsSpecification'
{ _vtosTunnelInsideCidr :: !(Maybe Text)
, _vtosPreSharedKey :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
vpnTunnelOptionsSpecification
:: VPNTunnelOptionsSpecification
vpnTunnelOptionsSpecification =
VPNTunnelOptionsSpecification'
{_vtosTunnelInsideCidr = Nothing, _vtosPreSharedKey = Nothing}
vtosTunnelInsideCidr :: Lens' VPNTunnelOptionsSpecification (Maybe Text)
vtosTunnelInsideCidr = lens _vtosTunnelInsideCidr (\ s a -> s{_vtosTunnelInsideCidr = a})
vtosPreSharedKey :: Lens' VPNTunnelOptionsSpecification (Maybe Text)
vtosPreSharedKey = lens _vtosPreSharedKey (\ s a -> s{_vtosPreSharedKey = a})
instance Hashable VPNTunnelOptionsSpecification where
instance NFData VPNTunnelOptionsSpecification where
instance ToQuery VPNTunnelOptionsSpecification where
toQuery VPNTunnelOptionsSpecification'{..}
= mconcat
["TunnelInsideCidr" =: _vtosTunnelInsideCidr,
"PreSharedKey" =: _vtosPreSharedKey]
data Volume = Volume'
{ _vAttachments :: !(Maybe [VolumeAttachment])
, _vIOPS :: !(Maybe Int)
, _vKMSKeyId :: !(Maybe Text)
, _vTags :: !(Maybe [Tag])
, _vAvailabilityZone :: !Text
, _vCreateTime :: !ISO8601
, _vEncrypted :: !Bool
, _vSize :: !Int
, _vSnapshotId :: !Text
, _vState :: !VolumeState
, _vVolumeId :: !Text
, _vVolumeType :: !VolumeType
} deriving (Eq, Read, Show, Data, Typeable, Generic)
volume
:: Text
-> UTCTime
-> Bool
-> Int
-> Text
-> VolumeState
-> Text
-> VolumeType
-> Volume
volume pAvailabilityZone_ pCreateTime_ pEncrypted_ pSize_ pSnapshotId_ pState_ pVolumeId_ pVolumeType_ =
Volume'
{ _vAttachments = Nothing
, _vIOPS = Nothing
, _vKMSKeyId = Nothing
, _vTags = Nothing
, _vAvailabilityZone = pAvailabilityZone_
, _vCreateTime = _Time # pCreateTime_
, _vEncrypted = pEncrypted_
, _vSize = pSize_
, _vSnapshotId = pSnapshotId_
, _vState = pState_
, _vVolumeId = pVolumeId_
, _vVolumeType = pVolumeType_
}
vAttachments :: Lens' Volume [VolumeAttachment]
vAttachments = lens _vAttachments (\ s a -> s{_vAttachments = a}) . _Default . _Coerce
vIOPS :: Lens' Volume (Maybe Int)
vIOPS = lens _vIOPS (\ s a -> s{_vIOPS = a})
vKMSKeyId :: Lens' Volume (Maybe Text)
vKMSKeyId = lens _vKMSKeyId (\ s a -> s{_vKMSKeyId = a})
vTags :: Lens' Volume [Tag]
vTags = lens _vTags (\ s a -> s{_vTags = a}) . _Default . _Coerce
vAvailabilityZone :: Lens' Volume Text
vAvailabilityZone = lens _vAvailabilityZone (\ s a -> s{_vAvailabilityZone = a})
vCreateTime :: Lens' Volume UTCTime
vCreateTime = lens _vCreateTime (\ s a -> s{_vCreateTime = a}) . _Time
vEncrypted :: Lens' Volume Bool
vEncrypted = lens _vEncrypted (\ s a -> s{_vEncrypted = a})
vSize :: Lens' Volume Int
vSize = lens _vSize (\ s a -> s{_vSize = a})
vSnapshotId :: Lens' Volume Text
vSnapshotId = lens _vSnapshotId (\ s a -> s{_vSnapshotId = a})
vState :: Lens' Volume VolumeState
vState = lens _vState (\ s a -> s{_vState = a})
vVolumeId :: Lens' Volume Text
vVolumeId = lens _vVolumeId (\ s a -> s{_vVolumeId = a})
vVolumeType :: Lens' Volume VolumeType
vVolumeType = lens _vVolumeType (\ s a -> s{_vVolumeType = a})
instance FromXML Volume where
parseXML x
= Volume' <$>
(x .@? "attachmentSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "iops")
<*> (x .@? "kmsKeyId")
<*>
(x .@? "tagSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@ "availabilityZone")
<*> (x .@ "createTime")
<*> (x .@ "encrypted")
<*> (x .@ "size")
<*> (x .@ "snapshotId")
<*> (x .@ "status")
<*> (x .@ "volumeId")
<*> (x .@ "volumeType")
instance Hashable Volume where
instance NFData Volume where
data VolumeAttachment = VolumeAttachment'
{ _volInstanceId :: !(Maybe Text)
, _volDeleteOnTermination :: !(Maybe Bool)
, _volState :: !(Maybe VolumeAttachmentState)
, _volDevice :: !(Maybe Text)
, _volVolumeId :: !(Maybe Text)
, _volAttachTime :: !(Maybe ISO8601)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
volumeAttachment
:: VolumeAttachment
volumeAttachment =
VolumeAttachment'
{ _volInstanceId = Nothing
, _volDeleteOnTermination = Nothing
, _volState = Nothing
, _volDevice = Nothing
, _volVolumeId = Nothing
, _volAttachTime = Nothing
}
volInstanceId :: Lens' VolumeAttachment (Maybe Text)
volInstanceId = lens _volInstanceId (\ s a -> s{_volInstanceId = a})
volDeleteOnTermination :: Lens' VolumeAttachment (Maybe Bool)
volDeleteOnTermination = lens _volDeleteOnTermination (\ s a -> s{_volDeleteOnTermination = a})
volState :: Lens' VolumeAttachment (Maybe VolumeAttachmentState)
volState = lens _volState (\ s a -> s{_volState = a})
volDevice :: Lens' VolumeAttachment (Maybe Text)
volDevice = lens _volDevice (\ s a -> s{_volDevice = a})
volVolumeId :: Lens' VolumeAttachment (Maybe Text)
volVolumeId = lens _volVolumeId (\ s a -> s{_volVolumeId = a})
volAttachTime :: Lens' VolumeAttachment (Maybe UTCTime)
volAttachTime = lens _volAttachTime (\ s a -> s{_volAttachTime = a}) . mapping _Time
instance FromXML VolumeAttachment where
parseXML x
= VolumeAttachment' <$>
(x .@? "instanceId") <*>
(x .@? "deleteOnTermination")
<*> (x .@? "status")
<*> (x .@? "device")
<*> (x .@? "volumeId")
<*> (x .@? "attachTime")
instance Hashable VolumeAttachment where
instance NFData VolumeAttachment where
newtype VolumeDetail = VolumeDetail'
{ _vdSize :: Integer
} deriving (Eq, Read, Show, Data, Typeable, Generic)
volumeDetail
:: Integer
-> VolumeDetail
volumeDetail pSize_ = VolumeDetail' {_vdSize = pSize_}
vdSize :: Lens' VolumeDetail Integer
vdSize = lens _vdSize (\ s a -> s{_vdSize = a})
instance Hashable VolumeDetail where
instance NFData VolumeDetail where
instance ToQuery VolumeDetail where
toQuery VolumeDetail'{..}
= mconcat ["Size" =: _vdSize]
data VolumeModification = VolumeModification'
{ _vmProgress :: !(Maybe Integer)
, _vmStartTime :: !(Maybe ISO8601)
, _vmModificationState :: !(Maybe VolumeModificationState)
, _vmTargetVolumeType :: !(Maybe VolumeType)
, _vmOriginalVolumeType :: !(Maybe VolumeType)
, _vmTargetSize :: !(Maybe Int)
, _vmTargetIOPS :: !(Maybe Int)
, _vmOriginalSize :: !(Maybe Int)
, _vmOriginalIOPS :: !(Maybe Int)
, _vmStatusMessage :: !(Maybe Text)
, _vmEndTime :: !(Maybe ISO8601)
, _vmVolumeId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
volumeModification
:: VolumeModification
volumeModification =
VolumeModification'
{ _vmProgress = Nothing
, _vmStartTime = Nothing
, _vmModificationState = Nothing
, _vmTargetVolumeType = Nothing
, _vmOriginalVolumeType = Nothing
, _vmTargetSize = Nothing
, _vmTargetIOPS = Nothing
, _vmOriginalSize = Nothing
, _vmOriginalIOPS = Nothing
, _vmStatusMessage = Nothing
, _vmEndTime = Nothing
, _vmVolumeId = Nothing
}
vmProgress :: Lens' VolumeModification (Maybe Integer)
vmProgress = lens _vmProgress (\ s a -> s{_vmProgress = a})
vmStartTime :: Lens' VolumeModification (Maybe UTCTime)
vmStartTime = lens _vmStartTime (\ s a -> s{_vmStartTime = a}) . mapping _Time
vmModificationState :: Lens' VolumeModification (Maybe VolumeModificationState)
vmModificationState = lens _vmModificationState (\ s a -> s{_vmModificationState = a})
vmTargetVolumeType :: Lens' VolumeModification (Maybe VolumeType)
vmTargetVolumeType = lens _vmTargetVolumeType (\ s a -> s{_vmTargetVolumeType = a})
vmOriginalVolumeType :: Lens' VolumeModification (Maybe VolumeType)
vmOriginalVolumeType = lens _vmOriginalVolumeType (\ s a -> s{_vmOriginalVolumeType = a})
vmTargetSize :: Lens' VolumeModification (Maybe Int)
vmTargetSize = lens _vmTargetSize (\ s a -> s{_vmTargetSize = a})
vmTargetIOPS :: Lens' VolumeModification (Maybe Int)
vmTargetIOPS = lens _vmTargetIOPS (\ s a -> s{_vmTargetIOPS = a})
vmOriginalSize :: Lens' VolumeModification (Maybe Int)
vmOriginalSize = lens _vmOriginalSize (\ s a -> s{_vmOriginalSize = a})
vmOriginalIOPS :: Lens' VolumeModification (Maybe Int)
vmOriginalIOPS = lens _vmOriginalIOPS (\ s a -> s{_vmOriginalIOPS = a})
vmStatusMessage :: Lens' VolumeModification (Maybe Text)
vmStatusMessage = lens _vmStatusMessage (\ s a -> s{_vmStatusMessage = a})
vmEndTime :: Lens' VolumeModification (Maybe UTCTime)
vmEndTime = lens _vmEndTime (\ s a -> s{_vmEndTime = a}) . mapping _Time
vmVolumeId :: Lens' VolumeModification (Maybe Text)
vmVolumeId = lens _vmVolumeId (\ s a -> s{_vmVolumeId = a})
instance FromXML VolumeModification where
parseXML x
= VolumeModification' <$>
(x .@? "progress") <*> (x .@? "startTime") <*>
(x .@? "modificationState")
<*> (x .@? "targetVolumeType")
<*> (x .@? "originalVolumeType")
<*> (x .@? "targetSize")
<*> (x .@? "targetIops")
<*> (x .@? "originalSize")
<*> (x .@? "originalIops")
<*> (x .@? "statusMessage")
<*> (x .@? "endTime")
<*> (x .@? "volumeId")
instance Hashable VolumeModification where
instance NFData VolumeModification where
data VolumeStatusAction = VolumeStatusAction'
{ _vsaEventType :: !(Maybe Text)
, _vsaCode :: !(Maybe Text)
, _vsaDescription :: !(Maybe Text)
, _vsaEventId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
volumeStatusAction
:: VolumeStatusAction
volumeStatusAction =
VolumeStatusAction'
{ _vsaEventType = Nothing
, _vsaCode = Nothing
, _vsaDescription = Nothing
, _vsaEventId = Nothing
}
vsaEventType :: Lens' VolumeStatusAction (Maybe Text)
vsaEventType = lens _vsaEventType (\ s a -> s{_vsaEventType = a})
vsaCode :: Lens' VolumeStatusAction (Maybe Text)
vsaCode = lens _vsaCode (\ s a -> s{_vsaCode = a})
vsaDescription :: Lens' VolumeStatusAction (Maybe Text)
vsaDescription = lens _vsaDescription (\ s a -> s{_vsaDescription = a})
vsaEventId :: Lens' VolumeStatusAction (Maybe Text)
vsaEventId = lens _vsaEventId (\ s a -> s{_vsaEventId = a})
instance FromXML VolumeStatusAction where
parseXML x
= VolumeStatusAction' <$>
(x .@? "eventType") <*> (x .@? "code") <*>
(x .@? "description")
<*> (x .@? "eventId")
instance Hashable VolumeStatusAction where
instance NFData VolumeStatusAction where
data VolumeStatusDetails = VolumeStatusDetails'
{ _vsdStatus :: !(Maybe Text)
, _vsdName :: !(Maybe VolumeStatusName)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
volumeStatusDetails
:: VolumeStatusDetails
volumeStatusDetails =
VolumeStatusDetails' {_vsdStatus = Nothing, _vsdName = Nothing}
vsdStatus :: Lens' VolumeStatusDetails (Maybe Text)
vsdStatus = lens _vsdStatus (\ s a -> s{_vsdStatus = a})
vsdName :: Lens' VolumeStatusDetails (Maybe VolumeStatusName)
vsdName = lens _vsdName (\ s a -> s{_vsdName = a})
instance FromXML VolumeStatusDetails where
parseXML x
= VolumeStatusDetails' <$>
(x .@? "status") <*> (x .@? "name")
instance Hashable VolumeStatusDetails where
instance NFData VolumeStatusDetails where
data VolumeStatusEvent = VolumeStatusEvent'
{ _vseNotBefore :: !(Maybe ISO8601)
, _vseEventType :: !(Maybe Text)
, _vseDescription :: !(Maybe Text)
, _vseNotAfter :: !(Maybe ISO8601)
, _vseEventId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
volumeStatusEvent
:: VolumeStatusEvent
volumeStatusEvent =
VolumeStatusEvent'
{ _vseNotBefore = Nothing
, _vseEventType = Nothing
, _vseDescription = Nothing
, _vseNotAfter = Nothing
, _vseEventId = Nothing
}
vseNotBefore :: Lens' VolumeStatusEvent (Maybe UTCTime)
vseNotBefore = lens _vseNotBefore (\ s a -> s{_vseNotBefore = a}) . mapping _Time
vseEventType :: Lens' VolumeStatusEvent (Maybe Text)
vseEventType = lens _vseEventType (\ s a -> s{_vseEventType = a})
vseDescription :: Lens' VolumeStatusEvent (Maybe Text)
vseDescription = lens _vseDescription (\ s a -> s{_vseDescription = a})
vseNotAfter :: Lens' VolumeStatusEvent (Maybe UTCTime)
vseNotAfter = lens _vseNotAfter (\ s a -> s{_vseNotAfter = a}) . mapping _Time
vseEventId :: Lens' VolumeStatusEvent (Maybe Text)
vseEventId = lens _vseEventId (\ s a -> s{_vseEventId = a})
instance FromXML VolumeStatusEvent where
parseXML x
= VolumeStatusEvent' <$>
(x .@? "notBefore") <*> (x .@? "eventType") <*>
(x .@? "description")
<*> (x .@? "notAfter")
<*> (x .@? "eventId")
instance Hashable VolumeStatusEvent where
instance NFData VolumeStatusEvent where
data VolumeStatusInfo = VolumeStatusInfo'
{ _vsiStatus :: !(Maybe VolumeStatusInfoStatus)
, _vsiDetails :: !(Maybe [VolumeStatusDetails])
} deriving (Eq, Read, Show, Data, Typeable, Generic)
volumeStatusInfo
:: VolumeStatusInfo
volumeStatusInfo =
VolumeStatusInfo' {_vsiStatus = Nothing, _vsiDetails = Nothing}
vsiStatus :: Lens' VolumeStatusInfo (Maybe VolumeStatusInfoStatus)
vsiStatus = lens _vsiStatus (\ s a -> s{_vsiStatus = a})
vsiDetails :: Lens' VolumeStatusInfo [VolumeStatusDetails]
vsiDetails = lens _vsiDetails (\ s a -> s{_vsiDetails = a}) . _Default . _Coerce
instance FromXML VolumeStatusInfo where
parseXML x
= VolumeStatusInfo' <$>
(x .@? "status") <*>
(x .@? "details" .!@ mempty >>=
may (parseXMLList "item"))
instance Hashable VolumeStatusInfo where
instance NFData VolumeStatusInfo where
data VolumeStatusItem = VolumeStatusItem'
{ _vsiVolumeStatus :: !(Maybe VolumeStatusInfo)
, _vsiActions :: !(Maybe [VolumeStatusAction])
, _vsiEvents :: !(Maybe [VolumeStatusEvent])
, _vsiAvailabilityZone :: !(Maybe Text)
, _vsiVolumeId :: !(Maybe Text)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
volumeStatusItem
:: VolumeStatusItem
volumeStatusItem =
VolumeStatusItem'
{ _vsiVolumeStatus = Nothing
, _vsiActions = Nothing
, _vsiEvents = Nothing
, _vsiAvailabilityZone = Nothing
, _vsiVolumeId = Nothing
}
vsiVolumeStatus :: Lens' VolumeStatusItem (Maybe VolumeStatusInfo)
vsiVolumeStatus = lens _vsiVolumeStatus (\ s a -> s{_vsiVolumeStatus = a})
vsiActions :: Lens' VolumeStatusItem [VolumeStatusAction]
vsiActions = lens _vsiActions (\ s a -> s{_vsiActions = a}) . _Default . _Coerce
vsiEvents :: Lens' VolumeStatusItem [VolumeStatusEvent]
vsiEvents = lens _vsiEvents (\ s a -> s{_vsiEvents = a}) . _Default . _Coerce
vsiAvailabilityZone :: Lens' VolumeStatusItem (Maybe Text)
vsiAvailabilityZone = lens _vsiAvailabilityZone (\ s a -> s{_vsiAvailabilityZone = a})
vsiVolumeId :: Lens' VolumeStatusItem (Maybe Text)
vsiVolumeId = lens _vsiVolumeId (\ s a -> s{_vsiVolumeId = a})
instance FromXML VolumeStatusItem where
parseXML x
= VolumeStatusItem' <$>
(x .@? "volumeStatus") <*>
(x .@? "actionsSet" .!@ mempty >>=
may (parseXMLList "item"))
<*>
(x .@? "eventsSet" .!@ mempty >>=
may (parseXMLList "item"))
<*> (x .@? "availabilityZone")
<*> (x .@? "volumeId")
instance Hashable VolumeStatusItem where
instance NFData VolumeStatusItem where