aws-0.13.0: Amazon Web Services (AWS) for Haskell

Safe HaskellNone
LanguageHaskell2010

Aws.Core

Contents

Synopsis

Logging

Response

Metadata in responses

data Response m a Source

A response with metadata. Can also contain an error response, or an internal error, via Attempt.

Response forms a Writer-like monad.

readResponse :: MonadThrow n => Response m a -> n a Source

Read a response result (if it's a success response, fail otherwise).

readResponseIO :: MonadIO io => Response m a -> io a Source

Read a response result (if it's a success response, fail otherwise). In MonadIO.

tellMetadata :: m -> Response m () Source

An empty response with some metadata.

tellMetadataRef :: Monoid m => IORef m -> m -> IO () Source

Add metadata to an IORef (using mappend).

mapMetadata :: (m -> n) -> Response m a -> Response n a Source

Apply a function to the metadata.

Response data consumers

type HTTPResponseConsumer a = Response (ResumableSource (ResourceT IO) ByteString) -> ResourceT IO a Source

A full HTTP response parser. Takes HTTP status, response headers, and response body.

class Monoid (ResponseMetadata resp) => ResponseConsumer req resp where Source

Class for types that AWS HTTP responses can be parsed into.

The request is also passed for possibly required additional metadata.

Note that for debugging, there is an instance for ByteString.

Associated Types

type ResponseMetadata resp Source

Metadata associated with a response. Typically there is one metadata type for each AWS service.

Methods

responseConsumer :: req -> IORef (ResponseMetadata resp) -> HTTPResponseConsumer resp Source

Response parser. Takes the corresponding request, an IORef for metadata, and HTTP response data.

Instances

ResponseConsumer r DeleteItemResponse Source 
ResponseConsumer r GetItemResponse Source 
ResponseConsumer r PutItemResponse Source 
ResponseConsumer r QueryResponse Source 
ResponseConsumer r ScanResponse Source 
ResponseConsumer r ListTablesResult Source 
ResponseConsumer r DeleteTableResult Source 
ResponseConsumer r UpdateTableResult Source 
ResponseConsumer r DescribeTableResult Source 
ResponseConsumer r CreateTableResult Source 
ResponseConsumer r UpdateItemResponse Source 
ResponseConsumer r GetBucketResponse Source 
ResponseConsumer r GetBucketLocationResponse Source 
ResponseConsumer r GetServiceResponse Source 
ResponseConsumer r PutBucketResponse Source 
ResponseConsumer r BatchDeleteAttributesResponse Source 
ResponseConsumer r BatchPutAttributesResponse Source 
ResponseConsumer r DeleteAttributesResponse Source 
ResponseConsumer r PutAttributesResponse Source 
ResponseConsumer r GetAttributesResponse Source 
ResponseConsumer r ListDomainsResponse Source 
ResponseConsumer r DomainMetadataResponse Source 
ResponseConsumer r DeleteDomainResponse Source 
ResponseConsumer r CreateDomainResponse Source 
ResponseConsumer r SelectResponse Source 
ResponseConsumer r ChangeMessageVisibilityResponse Source 
ResponseConsumer r ReceiveMessageResponse Source 
ResponseConsumer r DeleteMessageResponse Source 
ResponseConsumer r SendMessageResponse Source 
ResponseConsumer r RemovePermissionResponse Source 
ResponseConsumer r AddPermissionResponse Source 
ResponseConsumer r ListQueuesResponse Source 
ResponseConsumer r DeleteQueueResponse Source 
ResponseConsumer r CreateQueueResponse Source 
ResponseConsumer r SetQueueAttributesResponse Source 
ResponseConsumer r GetQueueAttributesResponse Source 
ResponseConsumer r AbortMultipartUploadResponse Source 
ResponseConsumer r CompleteMultipartUploadResponse Source 
ResponseConsumer r InitiateMultipartUploadResponse Source 
ResponseConsumer CreateAccessKey CreateAccessKeyResponse Source 
ResponseConsumer CreateUser CreateUserResponse Source 
ResponseConsumer DeleteAccessKey DeleteAccessKeyResponse Source 
ResponseConsumer DeleteUser DeleteUserResponse Source 
ResponseConsumer DeleteUserPolicy DeleteUserPolicyResponse Source 
ResponseConsumer GetUser GetUserResponse Source 
ResponseConsumer GetUserPolicy GetUserPolicyResponse Source 
ResponseConsumer ListAccessKeys ListAccessKeysResponse Source 
ResponseConsumer ListMfaDevices ListMfaDevicesResponse Source 
ResponseConsumer ListUserPolicies ListUserPoliciesResponse Source 
ResponseConsumer ListUsers ListUsersResponse Source 
ResponseConsumer PutUserPolicy PutUserPolicyResponse Source 
ResponseConsumer UpdateAccessKey UpdateAccessKeyResponse Source 
ResponseConsumer UpdateUser UpdateUserResponse Source 
ResponseConsumer CopyObject CopyObjectResponse Source 
ResponseConsumer DeleteBucket DeleteBucketResponse Source 
ResponseConsumer DeleteObject DeleteObjectResponse Source 
ResponseConsumer DeleteObjects DeleteObjectsResponse Source 
ResponseConsumer GetObject GetObjectResponse Source 
ResponseConsumer HeadObject HeadObjectResponse Source 
ResponseConsumer PutObject PutObjectResponse Source 
ResponseConsumer SendRawEmail SendRawEmailResponse Source 
ResponseConsumer ListIdentities ListIdentitiesResponse Source 
ResponseConsumer VerifyEmailIdentity VerifyEmailIdentityResponse Source 
ResponseConsumer VerifyDomainIdentity VerifyDomainIdentityResponse Source 
ResponseConsumer VerifyDomainDkim VerifyDomainDkimResponse Source 
ResponseConsumer DeleteIdentity DeleteIdentityResponse Source 
ResponseConsumer GetIdentityDkimAttributes GetIdentityDkimAttributesResponse Source 
ResponseConsumer GetIdentityNotificationAttributes GetIdentityNotificationAttributesResponse Source 
ResponseConsumer GetIdentityVerificationAttributes GetIdentityVerificationAttributesResponse Source 
ResponseConsumer SetIdentityNotificationTopic SetIdentityNotificationTopicResponse Source 
ResponseConsumer SetIdentityDkimEnabled SetIdentityDkimEnabledResponse Source 
ResponseConsumer SetIdentityFeedbackForwardingEnabled SetIdentityFeedbackForwardingEnabledResponse Source 
ResponseConsumer UploadPart UploadPartResponse Source 
ResponseConsumer r (Response ByteString) Source

Does not parse response. For debugging.

Memory response

class AsMemoryResponse resp where Source

Class for responses that are fully loaded into memory

Associated Types

type MemoryResponse resp :: * Source

Methods

loadToMemory :: resp -> ResourceT IO (MemoryResponse resp) Source

Instances

AsMemoryResponse DeleteItemResponse Source 
AsMemoryResponse GetItemResponse Source 
AsMemoryResponse PutItemResponse Source 
AsMemoryResponse QueryResponse Source 
AsMemoryResponse ScanResponse Source 
AsMemoryResponse ListTablesResult Source 
AsMemoryResponse DeleteTableResult Source 
AsMemoryResponse UpdateTableResult Source 
AsMemoryResponse DescribeTableResult Source 
AsMemoryResponse CreateTableResult Source 
AsMemoryResponse UpdateItemResponse Source 
AsMemoryResponse CreateAccessKeyResponse Source 
AsMemoryResponse CreateUserResponse Source 
AsMemoryResponse DeleteAccessKeyResponse Source 
AsMemoryResponse DeleteUserResponse Source 
AsMemoryResponse DeleteUserPolicyResponse Source 
AsMemoryResponse GetUserResponse Source 
AsMemoryResponse GetUserPolicyResponse Source 
AsMemoryResponse ListAccessKeysResponse Source 
AsMemoryResponse ListMfaDevicesResponse Source 
AsMemoryResponse ListUserPoliciesResponse Source 
AsMemoryResponse ListUsersResponse Source 
AsMemoryResponse PutUserPolicyResponse Source 
AsMemoryResponse UpdateAccessKeyResponse Source 
AsMemoryResponse UpdateUserResponse Source 
AsMemoryResponse CopyObjectResponse Source 
AsMemoryResponse DeleteBucketResponse Source 
AsMemoryResponse DeleteObjectResponse Source 
AsMemoryResponse DeleteObjectsResponse Source 
AsMemoryResponse GetBucketResponse Source 
AsMemoryResponse GetBucketLocationResponse Source 
AsMemoryResponse GetObjectResponse Source 
AsMemoryResponse GetServiceResponse Source 
AsMemoryResponse HeadObjectResponse Source 
AsMemoryResponse PutBucketResponse Source 
AsMemoryResponse PutObjectResponse Source 
AsMemoryResponse SendRawEmailResponse Source 
AsMemoryResponse ListIdentitiesResponse Source 
AsMemoryResponse VerifyEmailIdentityResponse Source 
AsMemoryResponse VerifyDomainIdentityResponse Source 
AsMemoryResponse VerifyDomainDkimResponse Source 
AsMemoryResponse DeleteIdentityResponse Source 
AsMemoryResponse GetIdentityDkimAttributesResponse Source 
AsMemoryResponse GetIdentityNotificationAttributesResponse Source 
AsMemoryResponse GetIdentityVerificationAttributesResponse Source 
AsMemoryResponse SetIdentityNotificationTopicResponse Source 
AsMemoryResponse SetIdentityDkimEnabledResponse Source 
AsMemoryResponse SetIdentityFeedbackForwardingEnabledResponse Source 
AsMemoryResponse BatchDeleteAttributesResponse Source 
AsMemoryResponse BatchPutAttributesResponse Source 
AsMemoryResponse DeleteAttributesResponse Source 
AsMemoryResponse PutAttributesResponse Source 
AsMemoryResponse GetAttributesResponse Source 
AsMemoryResponse ListDomainsResponse Source 
AsMemoryResponse DomainMetadataResponse Source 
AsMemoryResponse DeleteDomainResponse Source 
AsMemoryResponse CreateDomainResponse Source 
AsMemoryResponse SelectResponse Source 
AsMemoryResponse ChangeMessageVisibilityResponse Source 
AsMemoryResponse ReceiveMessageResponse Source 
AsMemoryResponse DeleteMessageResponse Source 
AsMemoryResponse SendMessageResponse Source 
AsMemoryResponse RemovePermissionResponse Source 
AsMemoryResponse AddPermissionResponse Source 
AsMemoryResponse ListQueuesResponse Source 
AsMemoryResponse DeleteQueueResponse Source 
AsMemoryResponse CreateQueueResponse Source 
AsMemoryResponse SetQueueAttributesResponse Source 
AsMemoryResponse GetQueueAttributesResponse Source 
AsMemoryResponse AbortMultipartUploadResponse Source 
AsMemoryResponse CompleteMultipartUploadResponse Source 
AsMemoryResponse UploadPartResponse Source 
AsMemoryResponse InitiateMultipartUploadResponse Source 

List response

class ListResponse resp item | resp -> item where Source

Responses that have one main list in them, and perhaps some decoration.

Methods

listResponse :: resp -> [item] Source

Exception types

newtype XmlException Source

An error that occurred during XML parsing / validation.

Constructors

XmlException 

newtype HeaderException Source

An error that occurred during header parsing / validation.

Constructors

HeaderException 

newtype FormException Source

An error that occurred during form parsing / validation.

Constructors

FormException 

newtype NoCredentialsException Source

No credentials were found and an invariant was violated.

Response deconstruction helpers

readHex2 :: [Char] -> Maybe Word8 Source

Parse a two-digit hex number.

XML

elContent :: Text -> Cursor -> [Text] Source

A specific element (case-insensitive, ignoring namespace - sadly necessary), extracting only the textual contents.

elCont :: Text -> Cursor -> [String] Source

Like elContent, but extracts Strings instead of Text.

force :: MonadThrow m => String -> [a] -> m a Source

Extract the first element from a parser result list, and throw an XmlException if the list is empty.

forceM :: MonadThrow m => String -> [m a] -> m a Source

Extract the first element from a monadic parser result list, and throw an XmlException if the list is empty.

textReadInt :: (MonadThrow m, Num a) => Text -> m a Source

Read an integer from a Text, throwing an XmlException on failure.

readInt :: (MonadThrow m, Num a) => String -> m a Source

Read an integer from a String, throwing an XmlException on failure.

xmlCursorConsumer :: Monoid m => (Cursor -> Response m a) -> IORef m -> HTTPResponseConsumer a Source

Create a complete HTTPResponseConsumer from a simple function that takes a Cursor to XML in the response body.

This function is highly recommended for any services that parse relatively short XML responses. (If status and response headers are required, simply take them as function parameters, and pass them through to this function.)

Query

data SignedQuery Source

A pre-signed medium-level request object.

Constructors

SignedQuery 

Fields

sqMethod :: !Method

Request method.

sqProtocol :: !Protocol

Protocol to be used.

sqHost :: !ByteString

HTTP host.

sqPort :: !Int

IP port.

sqPath :: !ByteString

HTTP path.

sqQuery :: !Query

Query string list (used with Get and PostQuery).

sqDate :: !(Maybe UTCTime)

Request date/time.

sqAuthorization :: !(Maybe (IO ByteString))

Authorization string (if applicable), for Authorization header. See authorizationV4

sqContentType :: !(Maybe ByteString)

Request body content type.

sqContentMd5 :: !(Maybe (Digest MD5))

Request body content MD5.

sqAmzHeaders :: !RequestHeaders

Additional Amazon "amz" headers.

sqOtherHeaders :: !RequestHeaders

Additional non-"amz" headers.

sqBody :: !(Maybe RequestBody)

Request body (used with Post and Put).

sqStringToSign :: !ByteString

String to sign. Note that the string is already signed, this is passed mostly for debugging purposes.

queryToHttpRequest :: SignedQuery -> IO Request Source

Create a HTTP request from a SignedQuery object.

queryToUri :: SignedQuery -> ByteString Source

Create a URI fro a SignedQuery object.

Unused / incompatible fields will be silently ignored.

Expiration

data TimeInfo Source

Whether to restrict the signature validity with a plain timestamp, or with explicit expiration (absolute or relative).

Constructors

Timestamp

Use a simple timestamp to let AWS check the request validity.

ExpiresAt

Let requests expire at a specific fixed time.

ExpiresIn

Let requests expire a specific number of seconds after they were generated.

Instances

data AbsoluteTimeInfo Source

Like TimeInfo, but with all relative times replaced by absolute UTC.

fromAbsoluteTimeInfo :: AbsoluteTimeInfo -> UTCTime Source

Just the UTC time value.

Signature

data SignatureData Source

Data that is always required for signing requests.

Constructors

SignatureData 

Fields

signatureTimeInfo :: AbsoluteTimeInfo

Expiration or timestamp.

signatureTime :: UTCTime

Current time.

signatureCredentials :: Credentials

Access credentials.

signatureData :: TimeInfo -> Credentials -> IO SignatureData Source

Create signature data using the current system time.

class SignQuery request where Source

A "signable" request object. Assembles together the Query, and signs it in one go.

Associated Types

type ServiceConfiguration request :: * -> * Source

Additional information, like API endpoints and service-specific preferences.

Methods

signQuery :: request -> ServiceConfiguration request queryType -> SignatureData -> SignedQuery Source

Create a SignedQuery from a request, additional Info, and SignatureData.

Instances

SignQuery DeleteItem Source 
SignQuery GetItem Source 
SignQuery PutItem Source 
SignQuery Query Source 
SignQuery Scan Source 
SignQuery ListTables Source

ServiceConfiguration: DdbConfiguration

SignQuery DeleteTable Source

ServiceConfiguration: DdbConfiguration

SignQuery UpdateTable Source

ServiceConfiguration: DdbConfiguration

SignQuery DescribeTable Source

ServiceConfiguration: DdbConfiguration

SignQuery CreateTable Source

ServiceConfiguration: DdbConfiguration

SignQuery UpdateItem Source 
SignQuery CreateAccessKey Source 
SignQuery CreateUser Source 
SignQuery DeleteAccessKey Source 
SignQuery DeleteUser Source 
SignQuery DeleteUserPolicy Source 
SignQuery GetUser Source 
SignQuery GetUserPolicy Source 
SignQuery ListAccessKeys Source 
SignQuery ListMfaDevices Source 
SignQuery ListUserPolicies Source 
SignQuery ListUsers Source 
SignQuery PutUserPolicy Source 
SignQuery UpdateAccessKey Source 
SignQuery UpdateUser Source 
SignQuery CopyObject Source

ServiceConfiguration: S3Configuration

SignQuery DeleteBucket Source

ServiceConfiguration: S3Configuration

SignQuery DeleteObject Source

ServiceConfiguration: S3Configuration

SignQuery DeleteObjects Source

ServiceConfiguration: S3Configuration

SignQuery GetBucket Source

ServiceConfiguration: S3Configuration

SignQuery GetBucketLocation Source 
SignQuery GetObject Source

ServiceConfiguration: S3Configuration

SignQuery GetService Source

ServiceConfiguration: S3Configuration

SignQuery HeadObject Source

ServiceConfiguration: S3Configuration

SignQuery PutBucket Source

ServiceConfiguration: S3Configuration

SignQuery PutObject Source

ServiceConfiguration: S3Configuration

SignQuery SendRawEmail Source

ServiceConfiguration: SesConfiguration

SignQuery ListIdentities Source

ServiceConfiguration: SesConfiguration

SignQuery VerifyEmailIdentity Source

ServiceConfiguration: SesConfiguration

SignQuery VerifyDomainIdentity Source

ServiceConfiguration: SesConfiguration

SignQuery VerifyDomainDkim Source

ServiceConfiguration: SesConfiguration

SignQuery DeleteIdentity Source

ServiceConfiguration: SesConfiguration

SignQuery GetIdentityDkimAttributes Source

ServiceConfiguration: SesConfiguration

SignQuery GetIdentityNotificationAttributes Source

ServiceConfiguration: SesConfiguration

SignQuery GetIdentityVerificationAttributes Source

ServiceConfiguration: SesConfiguration

SignQuery SetIdentityNotificationTopic Source

ServiceConfiguration: SesConfiguration

SignQuery SetIdentityDkimEnabled Source

ServiceConfiguration: SesConfiguration

SignQuery SetIdentityFeedbackForwardingEnabled Source

ServiceConfiguration: SesConfiguration

SignQuery BatchDeleteAttributes Source

ServiceConfiguration: SdbConfiguration

SignQuery BatchPutAttributes Source

ServiceConfiguration: SdbConfiguration

SignQuery DeleteAttributes Source

ServiceConfiguration: SdbConfiguration

SignQuery PutAttributes Source

ServiceConfiguration: SdbConfiguration

SignQuery GetAttributes Source

ServiceConfiguration: SdbConfiguration

SignQuery ListDomains Source

ServiceConfiguration: SdbConfiguration

SignQuery DomainMetadata Source

ServiceConfiguration: SdbConfiguration

SignQuery DeleteDomain Source

ServiceConfiguration: SdbConfiguration

SignQuery CreateDomain Source

ServiceConfiguration: SdbConfiguration

SignQuery Select Source

ServiceConfiguration: SdbConfiguration

SignQuery ChangeMessageVisibility Source

ServiceConfiguration: SqsConfiguration

SignQuery ReceiveMessage Source 
SignQuery DeleteMessage Source 
SignQuery SendMessage Source 
SignQuery RemovePermission Source

ServiceConfiguration: SqsConfiguration

SignQuery AddPermission Source

ServiceConfiguration: SqsConfiguration

SignQuery ListQueues Source

ServiceConfiguration: SqsConfiguration

SignQuery DeleteQueue Source

ServiceConfiguration: SqsConfiguration

SignQuery CreateQueue Source

ServiceConfiguration: SqsConfiguration

SignQuery SetQueueAttributes Source

ServiceConfiguration: SqsConfiguration

SignQuery GetQueueAttributes Source

ServiceConfiguration: SqsConfiguration

SignQuery AbortMultipartUpload Source

ServiceConfiguration: S3Configuration

SignQuery CompleteMultipartUpload Source

ServiceConfiguration: S3Configuration

SignQuery UploadPart Source

ServiceConfiguration: S3Configuration

SignQuery InitiateMultipartUpload Source

ServiceConfiguration: S3Configuration

data AuthorizationHash Source

Supported crypto hashes for the signature.

Constructors

HmacSHA1 
HmacSHA256 

amzHash :: AuthorizationHash -> ByteString Source

Authorization hash identifier as expected by Amazon.

signature :: Credentials -> AuthorizationHash -> ByteString -> ByteString Source

Create a signature. Usually, AWS wants a specifically constructed string to be signed.

The signature is a HMAC-based hash of the string and the secret access key.

authorizationV4 Source

Arguments

:: SignatureData 
-> AuthorizationHash 
-> ByteString

region, e.g. us-east-1

-> ByteString

service, e.g. dynamodb

-> ByteString

SignedHeaders, e.g. content-type;host;x-amz-date;x-amz-target

-> ByteString

canonicalRequest (before hashing)

-> IO ByteString 

Use this to create the Authorization header to set into sqAuthorization. See http://docs.aws.amazon.com/general/latest/gr/signature-version-4.html: you must create the canonical request as explained by Step 1 and this function takes care of Steps 2 and 3.

Query construction helpers

queryList :: (a -> [(ByteString, ByteString)]) -> ByteString -> [a] -> [(ByteString, ByteString)] Source

queryList f prefix xs constructs a query list from a list of elements xs, using a common prefix prefix, and a transformer function f.

A dot (.) is interspersed between prefix and generated key.

Example:

queryList swap "pfx" [("a", "b"), ("c", "d")] evaluates to [("pfx.b", "a"), ("pfx.d", "c")] (except with ByteString instead of String, of course).

awsBool :: Bool -> ByteString Source

A "true"/"false" boolean as requested by some services.

fmtTime :: String -> UTCTime -> ByteString Source

Format time according to a format string, as a ByteString.

fmtRfc822Time :: UTCTime -> ByteString Source

Format time in RFC 822 format.

fmtAmzTime :: UTCTime -> ByteString Source

Format time in yyyy-mm-ddThh-mm-ss format.

fmtTimeEpochSeconds :: UTCTime -> ByteString Source

Format time as seconds since the Unix epoch.

parseHttpDate :: String -> Maybe UTCTime Source

Parse HTTP-date (section 3.3.1 of RFC 2616)

httpDate1 :: String Source

HTTP-date (section 3.3.1 of RFC 2616, first type - RFC1123-style)

textHttpDate :: UTCTime -> Text Source

Format (as Text) HTTP-date (section 3.3.1 of RFC 2616, first type - RFC1123-style)

Transactions

class (SignQuery r, ResponseConsumer r a, Loggable (ResponseMetadata a)) => Transaction r a | r -> a Source

Associates a request type and a response type in a bi-directional way.

This allows the type-checker to infer the response type when given the request type and vice versa.

Note that the actual request generation and response parsing resides in SignQuery and ResponseConsumer respectively.

Instances

Transaction DeleteItem DeleteItemResponse Source 
Transaction GetItem GetItemResponse Source 
Transaction PutItem PutItemResponse Source 
Transaction Query QueryResponse Source 
Transaction Scan ScanResponse Source 
Transaction ListTables ListTablesResult Source 
Transaction DeleteTable DeleteTableResult Source 
Transaction UpdateTable UpdateTableResult Source 
Transaction DescribeTable DescribeTableResult Source 
Transaction CreateTable CreateTableResult Source 
Transaction UpdateItem UpdateItemResponse Source 
Transaction CreateAccessKey CreateAccessKeyResponse Source 
Transaction CreateUser CreateUserResponse Source 
Transaction DeleteAccessKey DeleteAccessKeyResponse Source 
Transaction DeleteUser DeleteUserResponse Source 
Transaction DeleteUserPolicy DeleteUserPolicyResponse Source 
Transaction GetUser GetUserResponse Source 
Transaction GetUserPolicy GetUserPolicyResponse Source 
Transaction ListAccessKeys ListAccessKeysResponse Source 
Transaction ListMfaDevices ListMfaDevicesResponse Source 
Transaction ListUserPolicies ListUserPoliciesResponse Source 
Transaction ListUsers ListUsersResponse Source 
Transaction PutUserPolicy PutUserPolicyResponse Source 
Transaction UpdateAccessKey UpdateAccessKeyResponse Source 
Transaction UpdateUser UpdateUserResponse Source 
Transaction CopyObject CopyObjectResponse Source 
Transaction DeleteBucket DeleteBucketResponse Source 
Transaction DeleteObject DeleteObjectResponse Source 
Transaction DeleteObjects DeleteObjectsResponse Source 
Transaction GetBucket GetBucketResponse Source 
Transaction GetBucketLocation GetBucketLocationResponse Source 
Transaction GetObject GetObjectResponse Source 
Transaction GetService GetServiceResponse Source 
Transaction HeadObject HeadObjectResponse Source 
Transaction PutBucket PutBucketResponse Source 
Transaction PutObject PutObjectResponse Source 
Transaction SendRawEmail SendRawEmailResponse Source 
Transaction ListIdentities ListIdentitiesResponse Source 
Transaction VerifyEmailIdentity VerifyEmailIdentityResponse Source 
Transaction VerifyDomainIdentity VerifyDomainIdentityResponse Source 
Transaction VerifyDomainDkim VerifyDomainDkimResponse Source 
Transaction DeleteIdentity DeleteIdentityResponse Source 
Transaction GetIdentityDkimAttributes GetIdentityDkimAttributesResponse Source 
Transaction GetIdentityNotificationAttributes GetIdentityNotificationAttributesResponse Source 
Transaction GetIdentityVerificationAttributes GetIdentityVerificationAttributesResponse Source 
Transaction SetIdentityNotificationTopic SetIdentityNotificationTopicResponse Source 
Transaction SetIdentityDkimEnabled SetIdentityDkimEnabledResponse Source 
Transaction SetIdentityFeedbackForwardingEnabled SetIdentityFeedbackForwardingEnabledResponse Source 
Transaction BatchDeleteAttributes BatchDeleteAttributesResponse Source 
Transaction BatchPutAttributes BatchPutAttributesResponse Source 
Transaction DeleteAttributes DeleteAttributesResponse Source 
Transaction PutAttributes PutAttributesResponse Source 
Transaction GetAttributes GetAttributesResponse Source 
Transaction ListDomains ListDomainsResponse Source 
Transaction DomainMetadata DomainMetadataResponse Source 
Transaction DeleteDomain DeleteDomainResponse Source 
Transaction CreateDomain CreateDomainResponse Source 
Transaction Select SelectResponse Source 
Transaction ChangeMessageVisibility ChangeMessageVisibilityResponse Source 
Transaction ReceiveMessage ReceiveMessageResponse Source 
Transaction DeleteMessage DeleteMessageResponse Source 
Transaction SendMessage SendMessageResponse Source 
Transaction RemovePermission RemovePermissionResponse Source 
Transaction AddPermission AddPermissionResponse Source 
Transaction ListQueues ListQueuesResponse Source 
Transaction DeleteQueue DeleteQueueResponse Source 
Transaction CreateQueue CreateQueueResponse Source 
Transaction SetQueueAttributes SetQueueAttributesResponse Source 
Transaction GetQueueAttributes GetQueueAttributesResponse Source 
Transaction AbortMultipartUpload AbortMultipartUploadResponse Source 
Transaction CompleteMultipartUpload CompleteMultipartUploadResponse Source 
Transaction UploadPart UploadPartResponse Source 
Transaction InitiateMultipartUpload InitiateMultipartUploadResponse Source 

Credentials

data Credentials Source

AWS access credentials.

Constructors

Credentials 

Fields

accessKeyID :: ByteString

AWS Access Key ID.

secretAccessKey :: ByteString

AWS Secret Access Key.

v4SigningKeys :: IORef [V4Key]

Signing keys for signature version 4

iamToken :: Maybe ByteString

Signed IAM token

makeCredentials Source

Arguments

:: MonadIO io 
=> ByteString

AWS Access Key ID

-> ByteString

AWS Secret Access Key

-> io Credentials 

credentialsDefaultFile :: MonadIO io => io FilePath Source

The file where access credentials are loaded, when using loadCredentialsDefault.

Value: directory/.aws-keys

credentialsDefaultKey :: Text Source

The key to be used in the access credential file that is loaded, when using loadCredentialsDefault.

Value: default

loadCredentialsFromFile :: MonadIO io => FilePath -> Text -> io (Maybe Credentials) Source

Load credentials from a (text) file given a key name.

The file consists of a sequence of lines, each in the following format:

keyName awsKeyID awsKeySecret

loadCredentialsFromEnv :: MonadIO io => io (Maybe Credentials) Source

Load credentials from the environment variables AWS_ACCESS_KEY_ID and AWS_ACCESS_KEY_SECRET (or AWS_SECRET_ACCESS_KEY), if possible.

loadCredentialsFromEnvOrFile :: MonadIO io => FilePath -> Text -> io (Maybe Credentials) Source

Load credentials from environment variables if possible, or alternatively from a file with a given key name.

See loadCredentialsFromEnv and loadCredentialsFromFile for details.

loadCredentialsFromEnvOrFileOrInstanceMetadata :: MonadIO io => FilePath -> Text -> io (Maybe Credentials) Source

Load credentials from environment variables if possible, or alternatively from the instance metadata store, or alternatively from a file with a given key name.

See loadCredentialsFromEnv, loadCredentialsFromFile and loadCredentialsFromInstanceMetadata for details.

loadCredentialsDefault :: MonadIO io => io (Maybe Credentials) Source

Load credentials from environment variables if possible, or alternative from the default file with the default key name.

Default file: directory/.aws-keys Default key name: default

See loadCredentialsFromEnv and loadCredentialsFromFile for details.

Service configuration

HTTP types

data Protocol Source

Protocols supported by AWS. Currently, all AWS services use the HTTP or HTTPS protocols.

Constructors

HTTP 
HTTPS 

defaultPort :: Protocol -> Int Source

The default port to be used for a protocol if no specific port is specified.

data Method Source

Request method. Not all request methods are supported by all services.

Constructors

Head

HEAD method. Put all request parameters in a query string and HTTP headers.

Get

GET method. Put all request parameters in a query string and HTTP headers.

PostQuery

POST method. Put all request parameters in a query string and HTTP headers, but send the query string as a POST payload

Post

POST method. Sends a service- and request-specific request body.

Put

PUT method.

Delete

DELETE method.

httpMethod :: Method -> Method Source

HTTP method associated with a request method.