Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module implements a number of response types for the aws-ec2
library. All commands from the library are written to return a JSON
Value
, but we provide more specific types for some responses
where possible. Implementing and especially testing response types
is a cumbersome job because the AWS documentation is not accurate
and response types might be missing in various ways (absent, there
but empty, sometimes there). Although the ideal would be to be
feature complete, a lot of trial and error is needed to get the
response types right so we've not yet done this.
However, it's useful to have more specific return types in common cases, even without full coverage. Since decoding of return values is type-driven, if you need more specific response decoding or coverage of features not implemented here, just define a new response type and use that.
- data BlockDeviceMapping = BlockDeviceMapping {}
- data BlockDevice
- = Ephemeral { }
- | EBS EbsBlockDevice
- data EbsBlockDevice = EbsBlockDevice {}
- queryEbsBlockDevice :: EbsBlockDevice -> [(ByteString, Maybe ByteString)]
- type CidrIp = Text
- type SgGroupId = Text
- data SgPermission
- = IpPermission IpProtocol (Maybe Int) (Maybe Int) [CidrIp]
- | SgPermission IpProtocol (Maybe Int) (Maybe Int) [SgGroupId]
- data Region = Region {
- regionEndpoint :: Text
- regionName :: Text
- data Reservation = Reservation {}
- data Group = Group {}
- data Instance = Instance {
- instanceId :: Text
- instanceImageId :: Text
- instanceState :: InstanceState
- instancePrivateDnsName :: Maybe Text
- instancePublicDnsName :: Maybe Text
- instanceStateTransitionReason :: Maybe Text
- instanceKeyName :: Maybe Text
- instanceAmiLaunchIndex :: Int
- instanceProductCodes :: [ProductCode]
- instanceType :: Text
- instanceLaunchTime :: UTCTime
- instancePlacement :: Placement
- instanceMonitoring :: Monitoring
- instanceSecurityGroups :: [Group]
- instanceArchitecture :: Architecture
- instanceRootDeviceType :: RootDeviceType
- instanceRootDeviceName :: Maybe Text
- instanceHypervisor :: Hypervisor
- instanceVirtualizationType :: VirtualizationType
- instanceClientToken :: Maybe Text
- instanceBlockDeviceMapping :: [InstanceBlockDeviceMapping]
- instanceEbsOptimized :: Bool
- instanceStateReason :: Maybe StateReason
- instanceNetworkInterfaces :: [InstanceNetworkInterface]
- instancePrivateIpAddress :: Maybe IPv4
- instancePublicIpAddress :: Maybe IPv4
- instanceTags :: [Tag]
- instanceKernelId :: Maybe Text
- instanceSourceDestCheck :: Maybe Bool
- instanceVpcId :: Maybe Text
- instanceSubnetId :: Maybe Text
- data ProductCode = ProductCode {}
- data InstanceNetworkInterface = InstanceNetworkInterface {
- iniNetworkInterfaceId :: Text
- iniSubnetId :: Maybe Text
- iniVpcId :: Maybe Text
- iniDescription :: Maybe Text
- iniOwnerId :: Text
- iniStatus :: Text
- iniMacAddress :: Maybe Text
- iniPrivateIpAddress :: Maybe IPv4
- iniSourceDestCheck :: Maybe Bool
- iniSecurityGroups :: [Group]
- iniAttachment :: Value
- iniAssociation :: Maybe Value
- data Tag = Tag {}
- data InstanceBlockDeviceMapping = InstanceBlockDeviceMapping {}
- data EbsInstanceBlockDevice = EbsInstanceBlockDevice {}
- data InstanceState = InstanceState {
- isName :: InstanceStateName
- isCode :: Int
- data Placement = Placement {
- pAvailabilityZone :: Text
- pTenancy :: Text
- pGroupName :: Maybe Text
- data Monitoring = Monitoring {}
- data StateReason = StateReason {}
- data AvailabilityZone = AvailabilityZone {
- azRegionName :: Text
- azZoneName :: Text
- azZoneState :: Text
- azMessageSet :: Value
- data SecurityGroup = SecurityGroup {}
- data PlacementGroup = PlacementGroup {
- pgGroupName :: Text
- pgStrategy :: Text
- pgState :: Text
- data KeyPair = KeyPair {
- keyName :: Text
- keyFingerprint :: Text
- data Vpc = Vpc {
- vpcId :: Text
- vpcState :: Text
- vpcCIDR :: Text
- vpcDHCPOptions :: Text
- vpcInstanceTenacity :: Text
- vpcIsDefault :: Maybe Bool
- data Subnet = Subnet {}
- data InstanceTenancy
- data VolumeType
- data IpProtocol
- data VirtualizationType
- = HVM
- | PARAVIRTUAL
- data RootDeviceType
- data Architecture
- data Hypervisor
- data InstanceStateName
- enumeratePermissions :: [SgPermission] -> Query
- maybeToList :: Maybe [a] -> [a]
- readBool :: String -> Bool
Documentation
data BlockDeviceMapping Source #
data BlockDevice Source #
queryEbsBlockDevice :: EbsBlockDevice -> [(ByteString, Maybe ByteString)] Source #
data SgPermission Source #
IpPermission IpProtocol (Maybe Int) (Maybe Int) [CidrIp] | |
SgPermission IpProtocol (Maybe Int) (Maybe Int) [SgGroupId] |
Region | |
|
The respose type describing an instance.
Note: this response type is not complete (according to the docs) but only contains the types we have encountered. The other types that could be present are commented out, as they could not be tested.
data ProductCode Source #
data InstanceNetworkInterface Source #
data InstanceState Source #
Placement | |
|
data Monitoring Source #
data AvailabilityZone Source #
AvailabilityZone | |
|
data SecurityGroup Source #
SecurityGroup | |
|
data PlacementGroup Source #
PlacementGroup | |
|
KeyPair | |
|
Vpc | |
|
Subnet | |
|
data VirtualizationType Source #
data RootDeviceType Source #
data Architecture Source #
data Hypervisor Source #
data InstanceStateName Source #
enumeratePermissions :: [SgPermission] -> Query Source #
maybeToList :: Maybe [a] -> [a] Source #