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

Safe HaskellNone
LanguageHaskell2010

Aws.Core

Contents

Synopsis

Logging

class Loggable a where Source #

Types that can be logged (textually).

Methods

toLogText :: a -> Text Source #

Instances
Loggable IamMetadata Source # 
Instance details

Defined in Aws.Iam.Core

Loggable DdbResponse Source # 
Instance details

Defined in Aws.DynamoDb.Core

Loggable S3Metadata Source # 
Instance details

Defined in Aws.S3.Core

Loggable SesMetadata Source # 
Instance details

Defined in Aws.Ses.Core

Loggable SdbMetadata Source # 
Instance details

Defined in Aws.SimpleDb.Core

Loggable SqsMetadata Source # 
Instance details

Defined in Aws.Sqs.Core

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
Monoid m => Monad (Response m) Source # 
Instance details

Defined in Aws.Core

Methods

(>>=) :: Response m a -> (a -> Response m b) -> Response m b #

(>>) :: Response m a -> Response m b -> Response m b #

return :: a -> Response m a #

fail :: String -> Response m a #

Functor (Response m) Source # 
Instance details

Defined in Aws.Core

Methods

fmap :: (a -> b) -> Response m a -> Response m b #

(<$) :: a -> Response m b -> Response m a #

Monoid m => Applicative (Response m) Source # 
Instance details

Defined in Aws.Core

Methods

pure :: a -> Response m a #

(<*>) :: Response m (a -> b) -> Response m a -> Response m b #

liftA2 :: (a -> b -> c) -> Response m a -> Response m b -> Response m c #

(*>) :: Response m a -> Response m b -> Response m b #

(<*) :: Response m a -> Response m b -> Response m a #

Monoid m => MonadThrow (Response m) Source # 
Instance details

Defined in Aws.Core

Methods

throwM :: Exception e => e -> Response m a #

(Show m, Show a) => Show (Response m a) Source # 
Instance details

Defined in Aws.Core

Methods

showsPrec :: Int -> Response m a -> ShowS #

show :: Response m a -> String #

showList :: [Response m a] -> ShowS #

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 (ConduitM () ByteString (ResourceT IO) ()) -> 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 :: Request -> req -> IORef (ResponseMetadata resp) -> HTTPResponseConsumer resp Source #

Response parser. Takes the corresponding AWS request, the derived http-client request (for error reporting), an IORef for metadata, and HTTP response data.

Instances
ResponseConsumer r UpdateItemResponse Source # 
Instance details

Defined in Aws.DynamoDb.Commands.UpdateItem

ResponseConsumer r ListTablesResult Source # 
Instance details

Defined in Aws.DynamoDb.Commands.Table

ResponseConsumer r DeleteTableResult Source # 
Instance details

Defined in Aws.DynamoDb.Commands.Table

ResponseConsumer r UpdateTableResult Source # 
Instance details

Defined in Aws.DynamoDb.Commands.Table

ResponseConsumer r DescribeTableResult Source # 
Instance details

Defined in Aws.DynamoDb.Commands.Table

ResponseConsumer r CreateTableResult Source # 
Instance details

Defined in Aws.DynamoDb.Commands.Table

ResponseConsumer r ScanResponse Source # 
Instance details

Defined in Aws.DynamoDb.Commands.Scan

Associated Types

type ResponseMetadata ScanResponse :: Type Source #

ResponseConsumer r QueryResponse Source # 
Instance details

Defined in Aws.DynamoDb.Commands.Query

Associated Types

type ResponseMetadata QueryResponse :: Type Source #

ResponseConsumer r PutItemResponse Source # 
Instance details

Defined in Aws.DynamoDb.Commands.PutItem

Associated Types

type ResponseMetadata PutItemResponse :: Type Source #

ResponseConsumer r GetItemResponse Source # 
Instance details

Defined in Aws.DynamoDb.Commands.GetItem

Associated Types

type ResponseMetadata GetItemResponse :: Type Source #

ResponseConsumer r DeleteItemResponse Source # 
Instance details

Defined in Aws.DynamoDb.Commands.DeleteItem

ResponseConsumer r BatchWriteItemResponse Source # 
Instance details

Defined in Aws.DynamoDb.Commands.BatchWriteItem

ResponseConsumer r BatchGetItemResponse Source # 
Instance details

Defined in Aws.DynamoDb.Commands.BatchGetItem

ResponseConsumer r PutBucketResponse Source # 
Instance details

Defined in Aws.S3.Commands.PutBucket

ResponseConsumer r AbortMultipartUploadResponse Source # 
Instance details

Defined in Aws.S3.Commands.Multipart

ResponseConsumer r CompleteMultipartUploadResponse Source # 
Instance details

Defined in Aws.S3.Commands.Multipart

ResponseConsumer r InitiateMultipartUploadResponse Source # 
Instance details

Defined in Aws.S3.Commands.Multipart

ResponseConsumer r GetServiceResponse Source # 
Instance details

Defined in Aws.S3.Commands.GetService

ResponseConsumer r GetBucketObjectVersionsResponse Source # 
Instance details

Defined in Aws.S3.Commands.GetBucketObjectVersions

ResponseConsumer r GetBucketLocationResponse Source # 
Instance details

Defined in Aws.S3.Commands.GetBucketLocation

ResponseConsumer r GetBucketResponse Source # 
Instance details

Defined in Aws.S3.Commands.GetBucket

ResponseConsumer r SelectResponse Source # 
Instance details

Defined in Aws.SimpleDb.Commands.Select

Associated Types

type ResponseMetadata SelectResponse :: Type Source #

ResponseConsumer r ListDomainsResponse Source # 
Instance details

Defined in Aws.SimpleDb.Commands.Domain

ResponseConsumer r DomainMetadataResponse Source # 
Instance details

Defined in Aws.SimpleDb.Commands.Domain

ResponseConsumer r DeleteDomainResponse Source # 
Instance details

Defined in Aws.SimpleDb.Commands.Domain

ResponseConsumer r CreateDomainResponse Source # 
Instance details

Defined in Aws.SimpleDb.Commands.Domain

ResponseConsumer r BatchDeleteAttributesResponse Source # 
Instance details

Defined in Aws.SimpleDb.Commands.Attributes

ResponseConsumer r BatchPutAttributesResponse Source # 
Instance details

Defined in Aws.SimpleDb.Commands.Attributes

ResponseConsumer r DeleteAttributesResponse Source # 
Instance details

Defined in Aws.SimpleDb.Commands.Attributes

ResponseConsumer r PutAttributesResponse Source # 
Instance details

Defined in Aws.SimpleDb.Commands.Attributes

ResponseConsumer r GetAttributesResponse Source # 
Instance details

Defined in Aws.SimpleDb.Commands.Attributes

ResponseConsumer r SetQueueAttributesResponse Source # 
Instance details

Defined in Aws.Sqs.Commands.QueueAttributes

ResponseConsumer r GetQueueAttributesResponse Source # 
Instance details

Defined in Aws.Sqs.Commands.QueueAttributes

ResponseConsumer r ListQueuesResponse Source # 
Instance details

Defined in Aws.Sqs.Commands.Queue

ResponseConsumer r DeleteQueueResponse Source # 
Instance details

Defined in Aws.Sqs.Commands.Queue

ResponseConsumer r CreateQueueResponse Source # 
Instance details

Defined in Aws.Sqs.Commands.Queue

ResponseConsumer r RemovePermissionResponse Source # 
Instance details

Defined in Aws.Sqs.Commands.Permission

ResponseConsumer r AddPermissionResponse Source # 
Instance details

Defined in Aws.Sqs.Commands.Permission

ResponseConsumer r ChangeMessageVisibilityResponse Source # 
Instance details

Defined in Aws.Sqs.Commands.Message

ResponseConsumer r ReceiveMessageResponse Source # 
Instance details

Defined in Aws.Sqs.Commands.Message

ResponseConsumer r DeleteMessageResponse Source # 
Instance details

Defined in Aws.Sqs.Commands.Message

ResponseConsumer r SendMessageResponse Source # 
Instance details

Defined in Aws.Sqs.Commands.Message

ResponseConsumer UpdateUser UpdateUserResponse Source # 
Instance details

Defined in Aws.Iam.Commands.UpdateUser

ResponseConsumer UpdateAccessKey UpdateAccessKeyResponse Source # 
Instance details

Defined in Aws.Iam.Commands.UpdateAccessKey

ResponseConsumer PutUserPolicy PutUserPolicyResponse Source # 
Instance details

Defined in Aws.Iam.Commands.PutUserPolicy

ResponseConsumer ListUsers ListUsersResponse Source # 
Instance details

Defined in Aws.Iam.Commands.ListUsers

ResponseConsumer ListUserPolicies ListUserPoliciesResponse Source # 
Instance details

Defined in Aws.Iam.Commands.ListUserPolicies

ResponseConsumer ListMfaDevices ListMfaDevicesResponse Source # 
Instance details

Defined in Aws.Iam.Commands.ListMfaDevices

ResponseConsumer ListAccessKeys ListAccessKeysResponse Source # 
Instance details

Defined in Aws.Iam.Commands.ListAccessKeys

ResponseConsumer GetUserPolicy GetUserPolicyResponse Source # 
Instance details

Defined in Aws.Iam.Commands.GetUserPolicy

ResponseConsumer GetUser GetUserResponse Source # 
Instance details

Defined in Aws.Iam.Commands.GetUser

Associated Types

type ResponseMetadata GetUserResponse :: Type Source #

ResponseConsumer DeleteUserPolicy DeleteUserPolicyResponse Source # 
Instance details

Defined in Aws.Iam.Commands.DeleteUserPolicy

ResponseConsumer DeleteUser DeleteUserResponse Source # 
Instance details

Defined in Aws.Iam.Commands.DeleteUser

ResponseConsumer DeleteAccessKey DeleteAccessKeyResponse Source # 
Instance details

Defined in Aws.Iam.Commands.DeleteAccessKey

ResponseConsumer CreateUser CreateUserResponse Source # 
Instance details

Defined in Aws.Iam.Commands.CreateUser

ResponseConsumer CreateAccessKey CreateAccessKeyResponse Source # 
Instance details

Defined in Aws.Iam.Commands.CreateAccessKey

ResponseConsumer PutObject PutObjectResponse Source # 
Instance details

Defined in Aws.S3.Commands.PutObject

ResponseConsumer UploadPart UploadPartResponse Source # 
Instance details

Defined in Aws.S3.Commands.Multipart

ResponseConsumer HeadObject HeadObjectResponse Source # 
Instance details

Defined in Aws.S3.Commands.HeadObject

ResponseConsumer GetObject GetObjectResponse Source # 
Instance details

Defined in Aws.S3.Commands.GetObject

ResponseConsumer DeleteObjects DeleteObjectsResponse Source # 
Instance details

Defined in Aws.S3.Commands.DeleteObjects

ResponseConsumer DeleteObjectVersion DeleteObjectVersionResponse Source # 
Instance details

Defined in Aws.S3.Commands.DeleteObjectVersion

ResponseConsumer DeleteObject DeleteObjectResponse Source # 
Instance details

Defined in Aws.S3.Commands.DeleteObject

ResponseConsumer DeleteBucket DeleteBucketResponse Source # 
Instance details

Defined in Aws.S3.Commands.DeleteBucket

ResponseConsumer CopyObject CopyObjectResponse Source # 
Instance details

Defined in Aws.S3.Commands.CopyObject

ResponseConsumer VerifyEmailIdentity VerifyEmailIdentityResponse Source # 
Instance details

Defined in Aws.Ses.Commands.VerifyEmailIdentity

ResponseConsumer VerifyDomainIdentity VerifyDomainIdentityResponse Source # 
Instance details

Defined in Aws.Ses.Commands.VerifyDomainIdentity

ResponseConsumer VerifyDomainDkim VerifyDomainDkimResponse Source # 
Instance details

Defined in Aws.Ses.Commands.VerifyDomainDkim

ResponseConsumer SetIdentityNotificationTopic SetIdentityNotificationTopicResponse Source # 
Instance details

Defined in Aws.Ses.Commands.SetIdentityNotificationTopic

ResponseConsumer SetIdentityFeedbackForwardingEnabled SetIdentityFeedbackForwardingEnabledResponse Source # 
Instance details

Defined in Aws.Ses.Commands.SetIdentityFeedbackForwardingEnabled

ResponseConsumer SetIdentityDkimEnabled SetIdentityDkimEnabledResponse Source # 
Instance details

Defined in Aws.Ses.Commands.SetIdentityDkimEnabled

ResponseConsumer SendRawEmail SendRawEmailResponse Source # 
Instance details

Defined in Aws.Ses.Commands.SendRawEmail

ResponseConsumer ListIdentities ListIdentitiesResponse Source # 
Instance details

Defined in Aws.Ses.Commands.ListIdentities

ResponseConsumer GetIdentityVerificationAttributes GetIdentityVerificationAttributesResponse Source # 
Instance details

Defined in Aws.Ses.Commands.GetIdentityVerificationAttributes

ResponseConsumer GetIdentityNotificationAttributes GetIdentityNotificationAttributesResponse Source # 
Instance details

Defined in Aws.Ses.Commands.GetIdentityNotificationAttributes

ResponseConsumer GetIdentityDkimAttributes GetIdentityDkimAttributesResponse Source # 
Instance details

Defined in Aws.Ses.Commands.GetIdentityDkimAttributes

ResponseConsumer DeleteIdentity DeleteIdentityResponse Source # 
Instance details

Defined in Aws.Ses.Commands.DeleteIdentity

ResponseConsumer r (Response ByteString) Source #

Does not parse response. For debugging.

Instance details

Defined in Aws.Core

Associated Types

type ResponseMetadata (Response ByteString) :: Type Source #

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 UpdateUserResponse Source # 
Instance details

Defined in Aws.Iam.Commands.UpdateUser

AsMemoryResponse UpdateAccessKeyResponse Source # 
Instance details

Defined in Aws.Iam.Commands.UpdateAccessKey

AsMemoryResponse PutUserPolicyResponse Source # 
Instance details

Defined in Aws.Iam.Commands.PutUserPolicy

AsMemoryResponse ListUsersResponse Source # 
Instance details

Defined in Aws.Iam.Commands.ListUsers

Associated Types

type MemoryResponse ListUsersResponse :: Type Source #

AsMemoryResponse ListUserPoliciesResponse Source # 
Instance details

Defined in Aws.Iam.Commands.ListUserPolicies

AsMemoryResponse ListMfaDevicesResponse Source # 
Instance details

Defined in Aws.Iam.Commands.ListMfaDevices

AsMemoryResponse ListAccessKeysResponse Source # 
Instance details

Defined in Aws.Iam.Commands.ListAccessKeys

AsMemoryResponse GetUserPolicyResponse Source # 
Instance details

Defined in Aws.Iam.Commands.GetUserPolicy

AsMemoryResponse GetUserResponse Source # 
Instance details

Defined in Aws.Iam.Commands.GetUser

Associated Types

type MemoryResponse GetUserResponse :: Type Source #

AsMemoryResponse DeleteUserPolicyResponse Source # 
Instance details

Defined in Aws.Iam.Commands.DeleteUserPolicy

AsMemoryResponse DeleteUserResponse Source # 
Instance details

Defined in Aws.Iam.Commands.DeleteUser

AsMemoryResponse DeleteAccessKeyResponse Source # 
Instance details

Defined in Aws.Iam.Commands.DeleteAccessKey

AsMemoryResponse CreateUserResponse Source # 
Instance details

Defined in Aws.Iam.Commands.CreateUser

AsMemoryResponse CreateAccessKeyResponse Source # 
Instance details

Defined in Aws.Iam.Commands.CreateAccessKey

AsMemoryResponse UpdateItemResponse Source # 
Instance details

Defined in Aws.DynamoDb.Commands.UpdateItem

AsMemoryResponse ListTablesResult Source # 
Instance details

Defined in Aws.DynamoDb.Commands.Table

Associated Types

type MemoryResponse ListTablesResult :: Type Source #

AsMemoryResponse DeleteTableResult Source # 
Instance details

Defined in Aws.DynamoDb.Commands.Table

Associated Types

type MemoryResponse DeleteTableResult :: Type Source #

AsMemoryResponse UpdateTableResult Source # 
Instance details

Defined in Aws.DynamoDb.Commands.Table

Associated Types

type MemoryResponse UpdateTableResult :: Type Source #

AsMemoryResponse DescribeTableResult Source # 
Instance details

Defined in Aws.DynamoDb.Commands.Table

AsMemoryResponse CreateTableResult Source # 
Instance details

Defined in Aws.DynamoDb.Commands.Table

Associated Types

type MemoryResponse CreateTableResult :: Type Source #

AsMemoryResponse ScanResponse Source # 
Instance details

Defined in Aws.DynamoDb.Commands.Scan

Associated Types

type MemoryResponse ScanResponse :: Type Source #

AsMemoryResponse QueryResponse Source # 
Instance details

Defined in Aws.DynamoDb.Commands.Query

Associated Types

type MemoryResponse QueryResponse :: Type Source #

AsMemoryResponse PutItemResponse Source # 
Instance details

Defined in Aws.DynamoDb.Commands.PutItem

Associated Types

type MemoryResponse PutItemResponse :: Type Source #

AsMemoryResponse GetItemResponse Source # 
Instance details

Defined in Aws.DynamoDb.Commands.GetItem

Associated Types

type MemoryResponse GetItemResponse :: Type Source #

AsMemoryResponse DeleteItemResponse Source # 
Instance details

Defined in Aws.DynamoDb.Commands.DeleteItem

AsMemoryResponse BatchWriteItemResponse Source # 
Instance details

Defined in Aws.DynamoDb.Commands.BatchWriteItem

AsMemoryResponse BatchGetItemResponse Source # 
Instance details

Defined in Aws.DynamoDb.Commands.BatchGetItem

AsMemoryResponse PutObjectResponse Source # 
Instance details

Defined in Aws.S3.Commands.PutObject

Associated Types

type MemoryResponse PutObjectResponse :: Type Source #

AsMemoryResponse PutBucketResponse Source # 
Instance details

Defined in Aws.S3.Commands.PutBucket

Associated Types

type MemoryResponse PutBucketResponse :: Type Source #

AsMemoryResponse AbortMultipartUploadResponse Source # 
Instance details

Defined in Aws.S3.Commands.Multipart

AsMemoryResponse CompleteMultipartUploadResponse Source # 
Instance details

Defined in Aws.S3.Commands.Multipart

AsMemoryResponse UploadPartResponse Source # 
Instance details

Defined in Aws.S3.Commands.Multipart

AsMemoryResponse InitiateMultipartUploadResponse Source # 
Instance details

Defined in Aws.S3.Commands.Multipart

AsMemoryResponse HeadObjectResponse Source # 
Instance details

Defined in Aws.S3.Commands.HeadObject

AsMemoryResponse GetServiceResponse Source # 
Instance details

Defined in Aws.S3.Commands.GetService

AsMemoryResponse GetObjectResponse Source # 
Instance details

Defined in Aws.S3.Commands.GetObject

Associated Types

type MemoryResponse GetObjectResponse :: Type Source #

AsMemoryResponse GetBucketObjectVersionsResponse Source # 
Instance details

Defined in Aws.S3.Commands.GetBucketObjectVersions

AsMemoryResponse GetBucketLocationResponse Source # 
Instance details

Defined in Aws.S3.Commands.GetBucketLocation

AsMemoryResponse GetBucketResponse Source # 
Instance details

Defined in Aws.S3.Commands.GetBucket

Associated Types

type MemoryResponse GetBucketResponse :: Type Source #

AsMemoryResponse DeleteObjectsResponse Source # 
Instance details

Defined in Aws.S3.Commands.DeleteObjects

AsMemoryResponse DeleteObjectVersionResponse Source # 
Instance details

Defined in Aws.S3.Commands.DeleteObjectVersion

AsMemoryResponse DeleteObjectResponse Source # 
Instance details

Defined in Aws.S3.Commands.DeleteObject

AsMemoryResponse DeleteBucketResponse Source # 
Instance details

Defined in Aws.S3.Commands.DeleteBucket

AsMemoryResponse CopyObjectResponse Source # 
Instance details

Defined in Aws.S3.Commands.CopyObject

AsMemoryResponse VerifyEmailIdentityResponse Source # 
Instance details

Defined in Aws.Ses.Commands.VerifyEmailIdentity

AsMemoryResponse VerifyDomainIdentityResponse Source # 
Instance details

Defined in Aws.Ses.Commands.VerifyDomainIdentity

AsMemoryResponse VerifyDomainDkimResponse Source # 
Instance details

Defined in Aws.Ses.Commands.VerifyDomainDkim

AsMemoryResponse SetIdentityNotificationTopicResponse Source # 
Instance details

Defined in Aws.Ses.Commands.SetIdentityNotificationTopic

AsMemoryResponse SetIdentityFeedbackForwardingEnabledResponse Source # 
Instance details

Defined in Aws.Ses.Commands.SetIdentityFeedbackForwardingEnabled

AsMemoryResponse SetIdentityDkimEnabledResponse Source # 
Instance details

Defined in Aws.Ses.Commands.SetIdentityDkimEnabled

AsMemoryResponse SendRawEmailResponse Source # 
Instance details

Defined in Aws.Ses.Commands.SendRawEmail

AsMemoryResponse ListIdentitiesResponse Source # 
Instance details

Defined in Aws.Ses.Commands.ListIdentities

AsMemoryResponse GetIdentityVerificationAttributesResponse Source # 
Instance details

Defined in Aws.Ses.Commands.GetIdentityVerificationAttributes

AsMemoryResponse GetIdentityNotificationAttributesResponse Source # 
Instance details

Defined in Aws.Ses.Commands.GetIdentityNotificationAttributes

AsMemoryResponse GetIdentityDkimAttributesResponse Source # 
Instance details

Defined in Aws.Ses.Commands.GetIdentityDkimAttributes

AsMemoryResponse DeleteIdentityResponse Source # 
Instance details

Defined in Aws.Ses.Commands.DeleteIdentity

AsMemoryResponse SelectResponse Source # 
Instance details

Defined in Aws.SimpleDb.Commands.Select

Associated Types

type MemoryResponse SelectResponse :: Type Source #

AsMemoryResponse ListDomainsResponse Source # 
Instance details

Defined in Aws.SimpleDb.Commands.Domain

AsMemoryResponse DomainMetadataResponse Source # 
Instance details

Defined in Aws.SimpleDb.Commands.Domain

AsMemoryResponse DeleteDomainResponse Source # 
Instance details

Defined in Aws.SimpleDb.Commands.Domain

AsMemoryResponse CreateDomainResponse Source # 
Instance details

Defined in Aws.SimpleDb.Commands.Domain

AsMemoryResponse BatchDeleteAttributesResponse Source # 
Instance details

Defined in Aws.SimpleDb.Commands.Attributes

AsMemoryResponse BatchPutAttributesResponse Source # 
Instance details

Defined in Aws.SimpleDb.Commands.Attributes

AsMemoryResponse DeleteAttributesResponse Source # 
Instance details

Defined in Aws.SimpleDb.Commands.Attributes

AsMemoryResponse PutAttributesResponse Source # 
Instance details

Defined in Aws.SimpleDb.Commands.Attributes

AsMemoryResponse GetAttributesResponse Source # 
Instance details

Defined in Aws.SimpleDb.Commands.Attributes

AsMemoryResponse SetQueueAttributesResponse Source # 
Instance details

Defined in Aws.Sqs.Commands.QueueAttributes

AsMemoryResponse GetQueueAttributesResponse Source # 
Instance details

Defined in Aws.Sqs.Commands.QueueAttributes

AsMemoryResponse ListQueuesResponse Source # 
Instance details

Defined in Aws.Sqs.Commands.Queue

AsMemoryResponse DeleteQueueResponse Source # 
Instance details

Defined in Aws.Sqs.Commands.Queue

AsMemoryResponse CreateQueueResponse Source # 
Instance details

Defined in Aws.Sqs.Commands.Queue

AsMemoryResponse RemovePermissionResponse Source # 
Instance details

Defined in Aws.Sqs.Commands.Permission

AsMemoryResponse AddPermissionResponse Source # 
Instance details

Defined in Aws.Sqs.Commands.Permission

AsMemoryResponse ChangeMessageVisibilityResponse Source # 
Instance details

Defined in Aws.Sqs.Commands.Message

AsMemoryResponse ReceiveMessageResponse Source # 
Instance details

Defined in Aws.Sqs.Commands.Message

AsMemoryResponse DeleteMessageResponse Source # 
Instance details

Defined in Aws.Sqs.Commands.Message

AsMemoryResponse SendMessageResponse Source # 
Instance details

Defined in Aws.Sqs.Commands.Message

List response

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.

textReadBool :: MonadThrow m => Text -> m Bool Source #

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

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

data NormalQuery Source #

Tag type for normal queries.

Instances
Default (DdbConfiguration NormalQuery) Source # 
Instance details

Defined in Aws.DynamoDb.Core

DefaultServiceConfiguration (IamConfiguration NormalQuery) Source # 
Instance details

Defined in Aws.Iam.Core

DefaultServiceConfiguration (DdbConfiguration NormalQuery) Source # 
Instance details

Defined in Aws.DynamoDb.Core

DefaultServiceConfiguration (S3Configuration NormalQuery) Source # 
Instance details

Defined in Aws.S3.Core

DefaultServiceConfiguration (SesConfiguration NormalQuery) Source # 
Instance details

Defined in Aws.Ses.Core

DefaultServiceConfiguration (SdbConfiguration NormalQuery) Source # 
Instance details

Defined in Aws.SimpleDb.Core

DefaultServiceConfiguration (SqsConfiguration NormalQuery) Source # 
Instance details

Defined in Aws.Sqs.Core

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
Show TimeInfo Source # 
Instance details

Defined in Aws.Core

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

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 UpdateUser Source # 
Instance details

Defined in Aws.Iam.Commands.UpdateUser

Associated Types

type ServiceConfiguration UpdateUser :: Type -> Type Source #

SignQuery UpdateAccessKey Source # 
Instance details

Defined in Aws.Iam.Commands.UpdateAccessKey

SignQuery PutUserPolicy Source # 
Instance details

Defined in Aws.Iam.Commands.PutUserPolicy

Associated Types

type ServiceConfiguration PutUserPolicy :: Type -> Type Source #

SignQuery ListUsers Source # 
Instance details

Defined in Aws.Iam.Commands.ListUsers

Associated Types

type ServiceConfiguration ListUsers :: Type -> Type Source #

SignQuery ListUserPolicies Source # 
Instance details

Defined in Aws.Iam.Commands.ListUserPolicies

SignQuery ListMfaDevices Source # 
Instance details

Defined in Aws.Iam.Commands.ListMfaDevices

SignQuery ListAccessKeys Source # 
Instance details

Defined in Aws.Iam.Commands.ListAccessKeys

SignQuery GetUserPolicy Source # 
Instance details

Defined in Aws.Iam.Commands.GetUserPolicy

Associated Types

type ServiceConfiguration GetUserPolicy :: Type -> Type Source #

SignQuery GetUser Source # 
Instance details

Defined in Aws.Iam.Commands.GetUser

Associated Types

type ServiceConfiguration GetUser :: Type -> Type Source #

SignQuery DeleteUserPolicy Source # 
Instance details

Defined in Aws.Iam.Commands.DeleteUserPolicy

SignQuery DeleteUser Source # 
Instance details

Defined in Aws.Iam.Commands.DeleteUser

Associated Types

type ServiceConfiguration DeleteUser :: Type -> Type Source #

SignQuery DeleteAccessKey Source # 
Instance details

Defined in Aws.Iam.Commands.DeleteAccessKey

SignQuery CreateUser Source # 
Instance details

Defined in Aws.Iam.Commands.CreateUser

Associated Types

type ServiceConfiguration CreateUser :: Type -> Type Source #

SignQuery CreateAccessKey Source # 
Instance details

Defined in Aws.Iam.Commands.CreateAccessKey

SignQuery UpdateItem Source # 
Instance details

Defined in Aws.DynamoDb.Commands.UpdateItem

Associated Types

type ServiceConfiguration UpdateItem :: Type -> Type Source #

SignQuery ListTables Source #

ServiceConfiguration: DdbConfiguration

Instance details

Defined in Aws.DynamoDb.Commands.Table

Associated Types

type ServiceConfiguration ListTables :: Type -> Type Source #

SignQuery DeleteTable Source #

ServiceConfiguration: DdbConfiguration

Instance details

Defined in Aws.DynamoDb.Commands.Table

Associated Types

type ServiceConfiguration DeleteTable :: Type -> Type Source #

SignQuery UpdateTable Source #

ServiceConfiguration: DdbConfiguration

Instance details

Defined in Aws.DynamoDb.Commands.Table

Associated Types

type ServiceConfiguration UpdateTable :: Type -> Type Source #

SignQuery DescribeTable Source #

ServiceConfiguration: DdbConfiguration

Instance details

Defined in Aws.DynamoDb.Commands.Table

Associated Types

type ServiceConfiguration DescribeTable :: Type -> Type Source #

SignQuery CreateTable Source #

ServiceConfiguration: DdbConfiguration

Instance details

Defined in Aws.DynamoDb.Commands.Table

Associated Types

type ServiceConfiguration CreateTable :: Type -> Type Source #

SignQuery Scan Source # 
Instance details

Defined in Aws.DynamoDb.Commands.Scan

Associated Types

type ServiceConfiguration Scan :: Type -> Type Source #

SignQuery Query Source # 
Instance details

Defined in Aws.DynamoDb.Commands.Query

Associated Types

type ServiceConfiguration Query :: Type -> Type Source #

SignQuery PutItem Source # 
Instance details

Defined in Aws.DynamoDb.Commands.PutItem

Associated Types

type ServiceConfiguration PutItem :: Type -> Type Source #

SignQuery GetItem Source # 
Instance details

Defined in Aws.DynamoDb.Commands.GetItem

Associated Types

type ServiceConfiguration GetItem :: Type -> Type Source #

SignQuery DeleteItem Source # 
Instance details

Defined in Aws.DynamoDb.Commands.DeleteItem

Associated Types

type ServiceConfiguration DeleteItem :: Type -> Type Source #

SignQuery BatchWriteItem Source # 
Instance details

Defined in Aws.DynamoDb.Commands.BatchWriteItem

SignQuery BatchGetItem Source # 
Instance details

Defined in Aws.DynamoDb.Commands.BatchGetItem

Associated Types

type ServiceConfiguration BatchGetItem :: Type -> Type Source #

SignQuery PutObject Source #

ServiceConfiguration: S3Configuration

Instance details

Defined in Aws.S3.Commands.PutObject

Associated Types

type ServiceConfiguration PutObject :: Type -> Type Source #

SignQuery PutBucket Source #

ServiceConfiguration: S3Configuration

Instance details

Defined in Aws.S3.Commands.PutBucket

Associated Types

type ServiceConfiguration PutBucket :: Type -> Type Source #

SignQuery AbortMultipartUpload Source #

ServiceConfiguration: S3Configuration

Instance details

Defined in Aws.S3.Commands.Multipart

SignQuery CompleteMultipartUpload Source #

ServiceConfiguration: S3Configuration

Instance details

Defined in Aws.S3.Commands.Multipart

SignQuery UploadPart Source #

ServiceConfiguration: S3Configuration

Instance details

Defined in Aws.S3.Commands.Multipart

Associated Types

type ServiceConfiguration UploadPart :: Type -> Type Source #

SignQuery InitiateMultipartUpload Source #

ServiceConfiguration: S3Configuration

Instance details

Defined in Aws.S3.Commands.Multipart

SignQuery HeadObject Source #

ServiceConfiguration: S3Configuration

Instance details

Defined in Aws.S3.Commands.HeadObject

Associated Types

type ServiceConfiguration HeadObject :: Type -> Type Source #

SignQuery GetService Source #

ServiceConfiguration: S3Configuration

Instance details

Defined in Aws.S3.Commands.GetService

Associated Types

type ServiceConfiguration GetService :: Type -> Type Source #

SignQuery GetObject Source #

ServiceConfiguration: S3Configuration

Instance details

Defined in Aws.S3.Commands.GetObject

Associated Types

type ServiceConfiguration GetObject :: Type -> Type Source #

SignQuery GetBucketObjectVersions Source #

ServiceConfiguration: S3Configuration

Instance details

Defined in Aws.S3.Commands.GetBucketObjectVersions

SignQuery GetBucketLocation Source # 
Instance details

Defined in Aws.S3.Commands.GetBucketLocation

SignQuery GetBucket Source #

ServiceConfiguration: S3Configuration

Instance details

Defined in Aws.S3.Commands.GetBucket

Associated Types

type ServiceConfiguration GetBucket :: Type -> Type Source #

SignQuery DeleteObjects Source #

ServiceConfiguration: S3Configuration

Instance details

Defined in Aws.S3.Commands.DeleteObjects

Associated Types

type ServiceConfiguration DeleteObjects :: Type -> Type Source #

SignQuery DeleteObjectVersion Source #

ServiceConfiguration: S3Configuration

Instance details

Defined in Aws.S3.Commands.DeleteObjectVersion

SignQuery DeleteObject Source #

ServiceConfiguration: S3Configuration

Instance details

Defined in Aws.S3.Commands.DeleteObject

Associated Types

type ServiceConfiguration DeleteObject :: Type -> Type Source #

SignQuery DeleteBucket Source #

ServiceConfiguration: S3Configuration

Instance details

Defined in Aws.S3.Commands.DeleteBucket

Associated Types

type ServiceConfiguration DeleteBucket :: Type -> Type Source #

SignQuery CopyObject Source #

ServiceConfiguration: S3Configuration

Instance details

Defined in Aws.S3.Commands.CopyObject

Associated Types

type ServiceConfiguration CopyObject :: Type -> Type Source #

SignQuery VerifyEmailIdentity Source #

ServiceConfiguration: SesConfiguration

Instance details

Defined in Aws.Ses.Commands.VerifyEmailIdentity

SignQuery VerifyDomainIdentity Source #

ServiceConfiguration: SesConfiguration

Instance details

Defined in Aws.Ses.Commands.VerifyDomainIdentity

SignQuery VerifyDomainDkim Source #

ServiceConfiguration: SesConfiguration

Instance details

Defined in Aws.Ses.Commands.VerifyDomainDkim

SignQuery SetIdentityNotificationTopic Source #

ServiceConfiguration: SesConfiguration

Instance details

Defined in Aws.Ses.Commands.SetIdentityNotificationTopic

SignQuery SetIdentityFeedbackForwardingEnabled Source #

ServiceConfiguration: SesConfiguration

Instance details

Defined in Aws.Ses.Commands.SetIdentityFeedbackForwardingEnabled

SignQuery SetIdentityDkimEnabled Source #

ServiceConfiguration: SesConfiguration

Instance details

Defined in Aws.Ses.Commands.SetIdentityDkimEnabled

SignQuery SendRawEmail Source #

ServiceConfiguration: SesConfiguration

Instance details

Defined in Aws.Ses.Commands.SendRawEmail

Associated Types

type ServiceConfiguration SendRawEmail :: Type -> Type Source #

SignQuery ListIdentities Source #

ServiceConfiguration: SesConfiguration

Instance details

Defined in Aws.Ses.Commands.ListIdentities

SignQuery GetIdentityVerificationAttributes Source #

ServiceConfiguration: SesConfiguration

Instance details

Defined in Aws.Ses.Commands.GetIdentityVerificationAttributes

SignQuery GetIdentityNotificationAttributes Source #

ServiceConfiguration: SesConfiguration

Instance details

Defined in Aws.Ses.Commands.GetIdentityNotificationAttributes

SignQuery GetIdentityDkimAttributes Source #

ServiceConfiguration: SesConfiguration

Instance details

Defined in Aws.Ses.Commands.GetIdentityDkimAttributes

SignQuery DeleteIdentity Source #

ServiceConfiguration: SesConfiguration

Instance details

Defined in Aws.Ses.Commands.DeleteIdentity

SignQuery Select Source #

ServiceConfiguration: SdbConfiguration

Instance details

Defined in Aws.SimpleDb.Commands.Select

Associated Types

type ServiceConfiguration Select :: Type -> Type Source #

SignQuery ListDomains Source #

ServiceConfiguration: SdbConfiguration

Instance details

Defined in Aws.SimpleDb.Commands.Domain

Associated Types

type ServiceConfiguration ListDomains :: Type -> Type Source #

SignQuery DomainMetadata Source #

ServiceConfiguration: SdbConfiguration

Instance details

Defined in Aws.SimpleDb.Commands.Domain

SignQuery DeleteDomain Source #

ServiceConfiguration: SdbConfiguration

Instance details

Defined in Aws.SimpleDb.Commands.Domain

Associated Types

type ServiceConfiguration DeleteDomain :: Type -> Type Source #

SignQuery CreateDomain Source #

ServiceConfiguration: SdbConfiguration

Instance details

Defined in Aws.SimpleDb.Commands.Domain

Associated Types

type ServiceConfiguration CreateDomain :: Type -> Type Source #

SignQuery BatchDeleteAttributes Source #

ServiceConfiguration: SdbConfiguration

Instance details

Defined in Aws.SimpleDb.Commands.Attributes

SignQuery BatchPutAttributes Source #

ServiceConfiguration: SdbConfiguration

Instance details

Defined in Aws.SimpleDb.Commands.Attributes

SignQuery DeleteAttributes Source #

ServiceConfiguration: SdbConfiguration

Instance details

Defined in Aws.SimpleDb.Commands.Attributes

SignQuery PutAttributes Source #

ServiceConfiguration: SdbConfiguration

Instance details

Defined in Aws.SimpleDb.Commands.Attributes

Associated Types

type ServiceConfiguration PutAttributes :: Type -> Type Source #

SignQuery GetAttributes Source #

ServiceConfiguration: SdbConfiguration

Instance details

Defined in Aws.SimpleDb.Commands.Attributes

Associated Types

type ServiceConfiguration GetAttributes :: Type -> Type Source #

SignQuery SetQueueAttributes Source #

ServiceConfiguration: SqsConfiguration

Instance details

Defined in Aws.Sqs.Commands.QueueAttributes

SignQuery GetQueueAttributes Source #

ServiceConfiguration: SqsConfiguration

Instance details

Defined in Aws.Sqs.Commands.QueueAttributes

SignQuery ListQueues Source #

ServiceConfiguration: SqsConfiguration

Instance details

Defined in Aws.Sqs.Commands.Queue

Associated Types

type ServiceConfiguration ListQueues :: Type -> Type Source #

SignQuery DeleteQueue Source #

ServiceConfiguration: SqsConfiguration

Instance details

Defined in Aws.Sqs.Commands.Queue

Associated Types

type ServiceConfiguration DeleteQueue :: Type -> Type Source #

SignQuery CreateQueue Source #

ServiceConfiguration: SqsConfiguration

Instance details

Defined in Aws.Sqs.Commands.Queue

Associated Types

type ServiceConfiguration CreateQueue :: Type -> Type Source #

SignQuery RemovePermission Source #

ServiceConfiguration: SqsConfiguration

Instance details

Defined in Aws.Sqs.Commands.Permission

SignQuery AddPermission Source #

ServiceConfiguration: SqsConfiguration

Instance details

Defined in Aws.Sqs.Commands.Permission

Associated Types

type ServiceConfiguration AddPermission :: Type -> Type Source #

SignQuery ChangeMessageVisibility Source #

ServiceConfiguration: SqsConfiguration

Instance details

Defined in Aws.Sqs.Commands.Message

SignQuery ReceiveMessage Source # 
Instance details

Defined in Aws.Sqs.Commands.Message

SignQuery DeleteMessage Source # 
Instance details

Defined in Aws.Sqs.Commands.Message

Associated Types

type ServiceConfiguration DeleteMessage :: Type -> Type Source #

SignQuery SendMessage Source # 
Instance details

Defined in Aws.Sqs.Commands.Message

Associated Types

type ServiceConfiguration SendMessage :: Type -> Type Source #

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.

credentialV4 Source #

Arguments

:: SignatureData 
-> ByteString

region, e.g. us-east-1

-> ByteString

service, e.g. dynamodb

-> ByteString 

Generates the Credential string, required for V4 signatures.

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.

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)

-> ByteString 

IO free version of authorizationV4, use this if you need to compute the signature outside of IO.

signatureV4 Source #

Arguments

:: SignatureData 
-> AuthorizationHash 
-> ByteString

region, e.g. us-east-1

-> ByteString

service, e.g. dynamodb

-> ByteString

canonicalRequest (before hashing)

-> ByteString 

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 UpdateUser UpdateUserResponse Source # 
Instance details

Defined in Aws.Iam.Commands.UpdateUser

Transaction UpdateAccessKey UpdateAccessKeyResponse Source # 
Instance details

Defined in Aws.Iam.Commands.UpdateAccessKey

Transaction PutUserPolicy PutUserPolicyResponse Source # 
Instance details

Defined in Aws.Iam.Commands.PutUserPolicy

Transaction ListUsers ListUsersResponse Source # 
Instance details

Defined in Aws.Iam.Commands.ListUsers

Transaction ListUserPolicies ListUserPoliciesResponse Source # 
Instance details

Defined in Aws.Iam.Commands.ListUserPolicies

Transaction ListMfaDevices ListMfaDevicesResponse Source # 
Instance details

Defined in Aws.Iam.Commands.ListMfaDevices

Transaction ListAccessKeys ListAccessKeysResponse Source # 
Instance details

Defined in Aws.Iam.Commands.ListAccessKeys

Transaction GetUserPolicy GetUserPolicyResponse Source # 
Instance details

Defined in Aws.Iam.Commands.GetUserPolicy

Transaction GetUser GetUserResponse Source # 
Instance details

Defined in Aws.Iam.Commands.GetUser

Transaction DeleteUserPolicy DeleteUserPolicyResponse Source # 
Instance details

Defined in Aws.Iam.Commands.DeleteUserPolicy

Transaction DeleteUser DeleteUserResponse Source # 
Instance details

Defined in Aws.Iam.Commands.DeleteUser

Transaction DeleteAccessKey DeleteAccessKeyResponse Source # 
Instance details

Defined in Aws.Iam.Commands.DeleteAccessKey

Transaction CreateUser CreateUserResponse Source # 
Instance details

Defined in Aws.Iam.Commands.CreateUser

Transaction CreateAccessKey CreateAccessKeyResponse Source # 
Instance details

Defined in Aws.Iam.Commands.CreateAccessKey

Transaction UpdateItem UpdateItemResponse Source # 
Instance details

Defined in Aws.DynamoDb.Commands.UpdateItem

Transaction ListTables ListTablesResult Source # 
Instance details

Defined in Aws.DynamoDb.Commands.Table

Transaction DeleteTable DeleteTableResult Source # 
Instance details

Defined in Aws.DynamoDb.Commands.Table

Transaction UpdateTable UpdateTableResult Source # 
Instance details

Defined in Aws.DynamoDb.Commands.Table

Transaction DescribeTable DescribeTableResult Source # 
Instance details

Defined in Aws.DynamoDb.Commands.Table

Transaction CreateTable CreateTableResult Source # 
Instance details

Defined in Aws.DynamoDb.Commands.Table

Transaction Scan ScanResponse Source # 
Instance details

Defined in Aws.DynamoDb.Commands.Scan

Transaction Query QueryResponse Source # 
Instance details

Defined in Aws.DynamoDb.Commands.Query

Transaction PutItem PutItemResponse Source # 
Instance details

Defined in Aws.DynamoDb.Commands.PutItem

Transaction GetItem GetItemResponse Source # 
Instance details

Defined in Aws.DynamoDb.Commands.GetItem

Transaction DeleteItem DeleteItemResponse Source # 
Instance details

Defined in Aws.DynamoDb.Commands.DeleteItem

Transaction BatchWriteItem BatchWriteItemResponse Source # 
Instance details

Defined in Aws.DynamoDb.Commands.BatchWriteItem

Transaction BatchGetItem BatchGetItemResponse Source # 
Instance details

Defined in Aws.DynamoDb.Commands.BatchGetItem

Transaction PutObject PutObjectResponse Source # 
Instance details

Defined in Aws.S3.Commands.PutObject

Transaction PutBucket PutBucketResponse Source # 
Instance details

Defined in Aws.S3.Commands.PutBucket

Transaction AbortMultipartUpload AbortMultipartUploadResponse Source # 
Instance details

Defined in Aws.S3.Commands.Multipart

Transaction CompleteMultipartUpload CompleteMultipartUploadResponse Source # 
Instance details

Defined in Aws.S3.Commands.Multipart

Transaction UploadPart UploadPartResponse Source # 
Instance details

Defined in Aws.S3.Commands.Multipart

Transaction InitiateMultipartUpload InitiateMultipartUploadResponse Source # 
Instance details

Defined in Aws.S3.Commands.Multipart

Transaction HeadObject HeadObjectResponse Source # 
Instance details

Defined in Aws.S3.Commands.HeadObject

Transaction GetService GetServiceResponse Source # 
Instance details

Defined in Aws.S3.Commands.GetService

Transaction GetObject GetObjectResponse Source # 
Instance details

Defined in Aws.S3.Commands.GetObject

Transaction GetBucketObjectVersions GetBucketObjectVersionsResponse Source # 
Instance details

Defined in Aws.S3.Commands.GetBucketObjectVersions

Transaction GetBucketLocation GetBucketLocationResponse Source # 
Instance details

Defined in Aws.S3.Commands.GetBucketLocation

Transaction GetBucket GetBucketResponse Source # 
Instance details

Defined in Aws.S3.Commands.GetBucket

Transaction DeleteObjects DeleteObjectsResponse Source # 
Instance details

Defined in Aws.S3.Commands.DeleteObjects

Transaction DeleteObjectVersion DeleteObjectVersionResponse Source # 
Instance details

Defined in Aws.S3.Commands.DeleteObjectVersion

Transaction DeleteObject DeleteObjectResponse Source # 
Instance details

Defined in Aws.S3.Commands.DeleteObject

Transaction DeleteBucket DeleteBucketResponse Source # 
Instance details

Defined in Aws.S3.Commands.DeleteBucket

Transaction CopyObject CopyObjectResponse Source # 
Instance details

Defined in Aws.S3.Commands.CopyObject

Transaction VerifyEmailIdentity VerifyEmailIdentityResponse Source # 
Instance details

Defined in Aws.Ses.Commands.VerifyEmailIdentity

Transaction VerifyDomainIdentity VerifyDomainIdentityResponse Source # 
Instance details

Defined in Aws.Ses.Commands.VerifyDomainIdentity

Transaction VerifyDomainDkim VerifyDomainDkimResponse Source # 
Instance details

Defined in Aws.Ses.Commands.VerifyDomainDkim

Transaction SetIdentityNotificationTopic SetIdentityNotificationTopicResponse Source # 
Instance details

Defined in Aws.Ses.Commands.SetIdentityNotificationTopic

Transaction SetIdentityFeedbackForwardingEnabled SetIdentityFeedbackForwardingEnabledResponse Source # 
Instance details

Defined in Aws.Ses.Commands.SetIdentityFeedbackForwardingEnabled

Transaction SetIdentityDkimEnabled SetIdentityDkimEnabledResponse Source # 
Instance details

Defined in Aws.Ses.Commands.SetIdentityDkimEnabled

Transaction SendRawEmail SendRawEmailResponse Source # 
Instance details

Defined in Aws.Ses.Commands.SendRawEmail

Transaction ListIdentities ListIdentitiesResponse Source # 
Instance details

Defined in Aws.Ses.Commands.ListIdentities

Transaction GetIdentityVerificationAttributes GetIdentityVerificationAttributesResponse Source # 
Instance details

Defined in Aws.Ses.Commands.GetIdentityVerificationAttributes

Transaction GetIdentityNotificationAttributes GetIdentityNotificationAttributesResponse Source # 
Instance details

Defined in Aws.Ses.Commands.GetIdentityNotificationAttributes

Transaction GetIdentityDkimAttributes GetIdentityDkimAttributesResponse Source # 
Instance details

Defined in Aws.Ses.Commands.GetIdentityDkimAttributes

Transaction DeleteIdentity DeleteIdentityResponse Source # 
Instance details

Defined in Aws.Ses.Commands.DeleteIdentity

Transaction Select SelectResponse Source # 
Instance details

Defined in Aws.SimpleDb.Commands.Select

Transaction ListDomains ListDomainsResponse Source # 
Instance details

Defined in Aws.SimpleDb.Commands.Domain

Transaction DomainMetadata DomainMetadataResponse Source # 
Instance details

Defined in Aws.SimpleDb.Commands.Domain

Transaction DeleteDomain DeleteDomainResponse Source # 
Instance details

Defined in Aws.SimpleDb.Commands.Domain

Transaction CreateDomain CreateDomainResponse Source # 
Instance details

Defined in Aws.SimpleDb.Commands.Domain

Transaction BatchDeleteAttributes BatchDeleteAttributesResponse Source # 
Instance details

Defined in Aws.SimpleDb.Commands.Attributes

Transaction BatchPutAttributes BatchPutAttributesResponse Source # 
Instance details

Defined in Aws.SimpleDb.Commands.Attributes

Transaction DeleteAttributes DeleteAttributesResponse Source # 
Instance details

Defined in Aws.SimpleDb.Commands.Attributes

Transaction PutAttributes PutAttributesResponse Source # 
Instance details

Defined in Aws.SimpleDb.Commands.Attributes

Transaction GetAttributes GetAttributesResponse Source # 
Instance details

Defined in Aws.SimpleDb.Commands.Attributes

Transaction SetQueueAttributes SetQueueAttributesResponse Source # 
Instance details

Defined in Aws.Sqs.Commands.QueueAttributes

Transaction GetQueueAttributes GetQueueAttributesResponse Source # 
Instance details

Defined in Aws.Sqs.Commands.QueueAttributes

Transaction ListQueues ListQueuesResponse Source # 
Instance details

Defined in Aws.Sqs.Commands.Queue

Transaction DeleteQueue DeleteQueueResponse Source # 
Instance details

Defined in Aws.Sqs.Commands.Queue

Transaction CreateQueue CreateQueueResponse Source # 
Instance details

Defined in Aws.Sqs.Commands.Queue

Transaction RemovePermission RemovePermissionResponse Source # 
Instance details

Defined in Aws.Sqs.Commands.Permission

Transaction AddPermission AddPermissionResponse Source # 
Instance details

Defined in Aws.Sqs.Commands.Permission

Transaction ChangeMessageVisibility ChangeMessageVisibilityResponse Source # 
Instance details

Defined in Aws.Sqs.Commands.Message

Transaction ReceiveMessage ReceiveMessageResponse Source # 
Instance details

Defined in Aws.Sqs.Commands.Message

Transaction DeleteMessage DeleteMessageResponse Source # 
Instance details

Defined in Aws.Sqs.Commands.Message

Transaction SendMessage SendMessageResponse Source # 
Instance details

Defined in Aws.Sqs.Commands.Message

class Transaction r a => IteratedTransaction r a | r -> a where Source #

A transaction that may need to be split over multiple requests, for example because of upstream response size limits.

Methods

nextIteratedRequest :: r -> a -> Maybe r Source #

Instances
IteratedTransaction ListUsers ListUsersResponse Source # 
Instance details

Defined in Aws.Iam.Commands.ListUsers

IteratedTransaction ListUserPolicies ListUserPoliciesResponse Source # 
Instance details

Defined in Aws.Iam.Commands.ListUserPolicies

IteratedTransaction ListMfaDevices ListMfaDevicesResponse Source # 
Instance details

Defined in Aws.Iam.Commands.ListMfaDevices

IteratedTransaction ListAccessKeys ListAccessKeysResponse Source # 
Instance details

Defined in Aws.Iam.Commands.ListAccessKeys

IteratedTransaction Scan ScanResponse Source # 
Instance details

Defined in Aws.DynamoDb.Commands.Scan

IteratedTransaction Query QueryResponse Source # 
Instance details

Defined in Aws.DynamoDb.Commands.Query

IteratedTransaction GetBucketObjectVersions GetBucketObjectVersionsResponse Source # 
Instance details

Defined in Aws.S3.Commands.GetBucketObjectVersions

IteratedTransaction GetBucket GetBucketResponse Source # 
Instance details

Defined in Aws.S3.Commands.GetBucket

IteratedTransaction Select SelectResponse Source # 
Instance details

Defined in Aws.SimpleDb.Commands.Select

IteratedTransaction ListDomains ListDomainsResponse Source # 
Instance details

Defined in Aws.SimpleDb.Commands.Domain

Credentials

data Credentials Source #

AWS access credentials.

Constructors

Credentials 

Fields

Instances
Show Credentials Source # 
Instance details

Defined in Aws.Core

makeCredentials Source #

Arguments

:: MonadIO io 
=> ByteString

AWS Access Key ID

-> ByteString

AWS Secret Access Key

-> io Credentials 

credentialsDefaultFile :: MonadIO io => io (Maybe FilePath) Source #

The file where access credentials are loaded, when using loadCredentialsDefault. May return Nothing if HOME is unset.

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

class DefaultServiceConfiguration config where Source #

Default configuration for a specific service.

Minimal complete definition

defServiceConfig

Methods

defServiceConfig :: config Source #

Default service configuration.

debugServiceConfig :: config Source #

Default debugging-only configuration. (Normally using HTTP instead of HTTPS for easier debugging.)

Instances
DefaultServiceConfiguration (IamConfiguration UriOnlyQuery) Source # 
Instance details

Defined in Aws.Iam.Core

DefaultServiceConfiguration (IamConfiguration NormalQuery) Source # 
Instance details

Defined in Aws.Iam.Core

DefaultServiceConfiguration (DdbConfiguration NormalQuery) Source # 
Instance details

Defined in Aws.DynamoDb.Core

DefaultServiceConfiguration (S3Configuration UriOnlyQuery) Source # 
Instance details

Defined in Aws.S3.Core

DefaultServiceConfiguration (S3Configuration NormalQuery) Source # 
Instance details

Defined in Aws.S3.Core

DefaultServiceConfiguration (SesConfiguration UriOnlyQuery) Source # 
Instance details

Defined in Aws.Ses.Core

DefaultServiceConfiguration (SesConfiguration NormalQuery) Source # 
Instance details

Defined in Aws.Ses.Core

DefaultServiceConfiguration (SdbConfiguration UriOnlyQuery) Source # 
Instance details

Defined in Aws.SimpleDb.Core

DefaultServiceConfiguration (SdbConfiguration NormalQuery) Source # 
Instance details

Defined in Aws.SimpleDb.Core

DefaultServiceConfiguration (SqsConfiguration UriOnlyQuery) Source # 
Instance details

Defined in Aws.Sqs.Core

DefaultServiceConfiguration (SqsConfiguration NormalQuery) Source # 
Instance details

Defined in Aws.Sqs.Core

HTTP types

data Protocol Source #

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

Constructors

HTTP 
HTTPS 
Instances
Eq Protocol Source # 
Instance details

Defined in Aws.Core

Ord Protocol Source # 
Instance details

Defined in Aws.Core

Read Protocol Source # 
Instance details

Defined in Aws.Core

Show Protocol Source # 
Instance details

Defined in Aws.Core

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
Eq Method Source # 
Instance details

Defined in Aws.Core

Methods

(==) :: Method -> Method -> Bool #

(/=) :: Method -> Method -> Bool #

Ord Method Source # 
Instance details

Defined in Aws.Core

Show Method Source # 
Instance details

Defined in Aws.Core

httpMethod :: Method -> Method Source #

HTTP method associated with a request method.