Safe Haskell | None |
---|---|
Language | Haskell2010 |
Aws.Ec2.Types
Description
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
queryEbsBlockDevice :: EbsBlockDevice -> [(ByteString, Maybe ByteString)] Source #
data SgPermission Source #
Constructors
IpPermission IpProtocol (Maybe Int) (Maybe Int) [CidrIp] | |
SgPermission IpProtocol (Maybe Int) (Maybe Int) [SgGroupId] |
Instances
Constructors
Region | |
Fields
|
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.
Constructors
data ProductCode Source #
Constructors
ProductCode | |
Fields
|
Instances
data InstanceNetworkInterface Source #
Constructors
InstanceNetworkInterface | |
Fields
|
data InstanceBlockDeviceMapping Source #
Constructors
InstanceBlockDeviceMapping | |
Fields |
data EbsInstanceBlockDevice Source #
Constructors
EbsInstanceBlockDevice | |
Fields |
data InstanceState Source #
Constructors
InstanceState | |
Fields
|
Instances
Constructors
Placement | |
Fields
|
data AvailabilityZone Source #
Constructors
AvailabilityZone | |
Fields
|
Instances
data SecurityGroup Source #
Constructors
SecurityGroup | |
Fields
|
Instances
data PlacementGroup Source #
Constructors
PlacementGroup | |
Fields
|
Instances
Constructors
KeyPair | |
Fields
|
Constructors
Vpc | |
Fields
|
Constructors
Subnet | |
Fields
|
data IpProtocol Source #
Instances
data VirtualizationType Source #
Constructors
HVM | |
PARAVIRTUAL |
data Architecture Source #
Instances
data Hypervisor Source #
Instances
data InstanceStateName Source #
Constructors
Pending | |
Running | |
ShuttingDown | |
Terminated | |
Stopping | |
Stopped |
Instances
enumeratePermissions :: [SgPermission] -> Query Source #
maybeToList :: Maybe [a] -> [a] Source #