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

Safe HaskellNone

Aws.Core

Contents

Synopsis

Logging

class Loggable a whereSource

Types that can be logged (textually).

Methods

toLogText :: a -> TextSource

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.

Constructors

Response 

Instances

(Monoid m, Exception e) => Failure e (Response m) 
Monoid m => Monad (Response m) 
Functor (Response m) 
(Show m, Show a) => Show (Response m a) 

readResponse :: FromAttempt f => Response m a -> f aSource

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

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

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 aSource

Apply a function to the metadata.

Response data consumers

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

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

class Monoid (ResponseMetadata resp) => ResponseConsumer req resp whereSource

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 respSource

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

Memory response

List response

class ListResponse resp item | resp -> item whereSource

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 Word8Source

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 :: Failure XmlException m => String -> [a] -> m aSource

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

forceM :: Failure XmlException m => String -> [m a] -> m aSource

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

textReadInt :: (Failure XmlException m, Num a) => Text -> m aSource

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

readInt :: (Failure XmlException m, Num a) => String -> m aSource

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

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

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 ByteString

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

sqContentType :: Maybe ByteString

Request body content type.

sqContentMd5 :: Maybe MD5

Request body content MD5.

sqAmzHeaders :: RequestHeaders

Additional Amazon amz headers.

sqOtherHeaders :: RequestHeaders

Additional non-amz headers.

sqBody :: Maybe (RequestBody (ResourceT IO))

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 -> Request (ResourceT IO)Source

Create a HTTP request from a SignedQuery object.

queryToUri :: SignedQuery -> ByteStringSource

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 -> UTCTimeSource

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 SignatureDataSource

Create signature data using the current system time.

class SignQuery request whereSource

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 -> SignedQuerySource

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

Instances

SignQuery CopyObject

ServiceConfiguration: S3Configuration

SignQuery DeleteObject

ServiceConfiguration: S3Configuration

SignQuery GetBucket

ServiceConfiguration: S3Configuration

SignQuery GetObject

ServiceConfiguration: S3Configuration

SignQuery GetService

ServiceConfiguration: S3Configuration

SignQuery PutBucket

ServiceConfiguration: S3Configuration

SignQuery PutObject

ServiceConfiguration: S3Configuration

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

ServiceConfiguration: SqsConfiguration

SignQuery DeleteMessage

ServiceConfiguration: SqsConfiguration

SignQuery SendMessage

ServiceConfiguration: SqsConfiguration

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 SendRawEmail

ServiceConfiguration: SesConfiguration

data AuthorizationHash Source

Supported crypto hashes for the signature.

Constructors

HmacSHA1 
HmacSHA256 

amzHash :: AuthorizationHash -> ByteStringSource

Authorization hash identifier as expected by Amazon.

signature :: Credentials -> AuthorizationHash -> ByteString -> ByteStringSource

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.

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 -> ByteStringSource

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

fmtTime :: String -> UTCTime -> ByteStringSource

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

fmtRfc822Time :: UTCTime -> ByteStringSource

Format time in RFC 822 format.

fmtAmzTime :: UTCTime -> ByteStringSource

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

fmtTimeEpochSeconds :: UTCTime -> ByteStringSource

Format time as seconds since the Unix epoch.

parseHttpDate :: String -> Maybe UTCTimeSource

Parse HTTP-date (section 3.3.1 of RFC 2616)

httpDate1 :: StringSource

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

textHttpDate :: UTCTime -> TextSource

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 -> rSource

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.

class Transaction r a => IteratedTransaction r a | r -> a, a -> r whereSource

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

Methods

nextIteratedRequest :: r -> a -> Maybe rSource

Credentials

data Credentials Source

AWS access credentials.

Constructors

Credentials 

Fields

accessKeyID :: ByteString

AWS Access Key ID.

secretAccessKey :: ByteString

AWS Secret Access Key.

Instances

credentialsDefaultFile :: MonadIO io => io FilePathSource

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

Value: <user directory>/.aws-keys

credentialsDefaultKey :: TextSource

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.

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: <user 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 

Instances

defaultPort :: Protocol -> IntSource

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

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 -> MethodSource

HTTP method associated with a request method.