aws-0.10.5: 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.

Instances

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

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

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 

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 GetItem 
SignQuery PutItem 
SignQuery Query 
SignQuery Scan 
SignQuery ListTables

ServiceConfiguration: DdbConfiguration

SignQuery DeleteTable

ServiceConfiguration: DdbConfiguration

SignQuery UpdateTable

ServiceConfiguration: DdbConfiguration

SignQuery DescribeTable

ServiceConfiguration: DdbConfiguration

SignQuery CreateTable

ServiceConfiguration: DdbConfiguration

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

ServiceConfiguration: S3Configuration

SignQuery DeleteBucket

ServiceConfiguration: S3Configuration

SignQuery DeleteObject

ServiceConfiguration: S3Configuration

SignQuery DeleteObjects

ServiceConfiguration: S3Configuration

SignQuery GetBucket

ServiceConfiguration: S3Configuration

SignQuery GetBucketLocation 
SignQuery GetObject

ServiceConfiguration: S3Configuration

SignQuery GetService

ServiceConfiguration: S3Configuration

SignQuery HeadObject

ServiceConfiguration: S3Configuration

SignQuery PutBucket

ServiceConfiguration: S3Configuration

SignQuery PutObject

ServiceConfiguration: S3Configuration

SignQuery SendRawEmail

ServiceConfiguration: SesConfiguration

SignQuery ListIdentities

ServiceConfiguration: SesConfiguration

SignQuery VerifyEmailIdentity

ServiceConfiguration: SesConfiguration

SignQuery VerifyDomainIdentity

ServiceConfiguration: SesConfiguration

SignQuery VerifyDomainDkim

ServiceConfiguration: SesConfiguration

SignQuery DeleteIdentity

ServiceConfiguration: SesConfiguration

SignQuery GetIdentityDkimAttributes

ServiceConfiguration: SesConfiguration

SignQuery GetIdentityNotificationAttributes

ServiceConfiguration: SesConfiguration

SignQuery GetIdentityVerificationAttributes

ServiceConfiguration: SesConfiguration

SignQuery SetIdentityNotificationTopic

ServiceConfiguration: SesConfiguration

SignQuery SetIdentityDkimEnabled

ServiceConfiguration: SesConfiguration

SignQuery SetIdentityFeedbackForwardingEnabled

ServiceConfiguration: SesConfiguration

SignQuery BatchDeleteAttributes

ServiceConfiguration: SdbConfiguration

SignQuery BatchPutAttributes

ServiceConfiguration: SdbConfiguration

SignQuery DeleteAttributes

ServiceConfiguration: SdbConfiguration

SignQuery PutAttributes

ServiceConfiguration: SdbConfiguration

SignQuery GetAttributes

ServiceConfiguration: SdbConfiguration

SignQuery ListDomains

ServiceConfiguration: SdbConfiguration

SignQuery DomainMetadata

ServiceConfiguration: SdbConfiguration

SignQuery DeleteDomain

ServiceConfiguration: SdbConfiguration

SignQuery CreateDomain

ServiceConfiguration: SdbConfiguration

SignQuery Select

ServiceConfiguration: SdbConfiguration

SignQuery ChangeMessageVisibility

ServiceConfiguration: SqsConfiguration

SignQuery ReceiveMessage 
SignQuery DeleteMessage 
SignQuery SendMessage 
SignQuery RemovePermission

ServiceConfiguration: SqsConfiguration

SignQuery AddPermission

ServiceConfiguration: SqsConfiguration

SignQuery ListQueues

ServiceConfiguration: SqsConfiguration

SignQuery DeleteQueue

ServiceConfiguration: SqsConfiguration

SignQuery CreateQueue

ServiceConfiguration: SqsConfiguration

SignQuery SetQueueAttributes

ServiceConfiguration: SqsConfiguration

SignQuery GetQueueAttributes

ServiceConfiguration: SqsConfiguration

SignQuery AbortMultipartUpload

ServiceConfiguration: S3Configuration

SignQuery CompleteMultipartUpload

ServiceConfiguration: S3Configuration

SignQuery UploadPart

ServiceConfiguration: S3Configuration

SignQuery InitiateMultipartUpload

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

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

Instances

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.

Instances

httpMethod :: Method -> Method Source

HTTP method associated with a request method.