Safe Haskell | Safe-Infered |
---|
- data Response m a = Response m (Attempt a)
- tellMetadata :: m -> Response m ()
- tellMetadataRef :: Monoid m => IORef m -> m -> IO ()
- type HTTPResponseConsumer a = Status -> ResponseHeaders -> Source (ResourceT IO) ByteString -> ResourceT IO a
- class Monoid (ResponseMetadata resp) => ResponseConsumer req resp where
- type ResponseMetadata resp
- responseConsumer :: req -> IORef (ResponseMetadata resp) -> HTTPResponseConsumer resp
- newtype XmlException = XmlException {}
- newtype HeaderException = HeaderException {}
- newtype FormException = FormException {}
- readHex2 :: [Char] -> Maybe Word8
- elContent :: Text -> Cursor -> [Text]
- elCont :: Text -> Cursor -> [String]
- force :: Failure XmlException m => String -> [a] -> m a
- forceM :: Failure XmlException m => String -> [m a] -> m a
- textReadInt :: (Failure XmlException m, Num a) => Text -> m a
- readInt :: (Failure XmlException m, Num a) => String -> m a
- xmlCursorConsumer :: Monoid m => (Cursor -> Response m a) -> IORef m -> HTTPResponseConsumer a
- data SignedQuery = SignedQuery {
- sqMethod :: Method
- sqProtocol :: Protocol
- sqHost :: ByteString
- sqPort :: Int
- sqPath :: ByteString
- sqQuery :: Query
- sqDate :: Maybe UTCTime
- sqAuthorization :: Maybe ByteString
- sqContentType :: Maybe ByteString
- sqContentMd5 :: Maybe ByteString
- sqAmzHeaders :: RequestHeaders
- sqOtherHeaders :: RequestHeaders
- sqBody :: Maybe (RequestBody (ResourceT IO))
- sqStringToSign :: ByteString
- queryToHttpRequest :: SignedQuery -> Request (ResourceT IO)
- queryToUri :: SignedQuery -> ByteString
- data TimeInfo
- data AbsoluteTimeInfo
- = AbsoluteTimestamp { }
- | AbsoluteExpires { }
- fromAbsoluteTimeInfo :: AbsoluteTimeInfo -> UTCTime
- makeAbsoluteTimeInfo :: TimeInfo -> UTCTime -> AbsoluteTimeInfo
- data SignatureData = SignatureData {}
- signatureData :: TimeInfo -> Credentials -> IO SignatureData
- class SignQuery r where
- type ServiceConfiguration r :: *
- signQuery :: r -> ServiceConfiguration r -> SignatureData -> SignedQuery
- data AuthorizationHash
- = HmacSHA1
- | HmacSHA256
- amzHash :: AuthorizationHash -> ByteString
- signature :: Credentials -> AuthorizationHash -> ByteString -> ByteString
- queryList :: (a -> [(ByteString, ByteString)]) -> ByteString -> [a] -> [(ByteString, ByteString)]
- awsBool :: Bool -> ByteString
- awsTrue :: ByteString
- awsFalse :: ByteString
- fmtTime :: String -> UTCTime -> ByteString
- fmtRfc822Time :: UTCTime -> ByteString
- rfc822Time :: String
- fmtAmzTime :: UTCTime -> ByteString
- fmtTimeEpochSeconds :: UTCTime -> ByteString
- class (SignQuery r, ResponseConsumer r a) => Transaction r a | r -> a, a -> r
- data Credentials = Credentials {}
- credentialsDefaultFile :: MonadIO io => io FilePath
- credentialsDefaultKey :: Text
- loadCredentialsFromFile :: MonadIO io => FilePath -> Text -> io (Maybe Credentials)
- loadCredentialsFromEnv :: MonadIO io => io (Maybe Credentials)
- loadCredentialsFromEnvOrFile :: MonadIO io => FilePath -> Text -> io (Maybe Credentials)
- loadCredentialsDefault :: MonadIO io => io (Maybe Credentials)
- class DefaultServiceConfiguration config where
- defaultConfiguration :: config
- defaultConfigurationUri :: config
- debugConfiguration :: config
- debugConfigurationUri :: config
- data Protocol
- defaultPort :: Protocol -> Int
- data Method
- httpMethod :: Method -> Method
Response
Metadata in responses
A response with metadata. Can also contain an error response, or an internal error, via Attempt
.
Response forms a Writer-like monad.
tellMetadata :: m -> Response m ()Source
An empty response with some metadata.
Response data consumers
type HTTPResponseConsumer a = Status -> ResponseHeaders -> Source (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
.
type ResponseMetadata resp Source
Metadata associated with a response. Typically there is one metadata type for each AWS service.
responseConsumer :: req -> IORef (ResponseMetadata resp) -> HTTPResponseConsumer respSource
Response parser. Takes the corresponding request, an IORef
for metadata, and HTTP response data.
Exception types
newtype XmlException Source
An error that occurred during XML parsing / validation.
newtype HeaderException Source
An error that occurred during header parsing / validation.
newtype FormException Source
An error that occurred during form parsing / validation.
Response deconstruction helpers
XML
elContent :: Text -> Cursor -> [Text]Source
A specific element (case-insensitive, ignoring namespace - sadly necessary), extracting only the textual contents.
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.
SignedQuery | |
|
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
Whether to restrict the signature validity with a plain timestamp, or with explicit expiration (absolute or relative).
data AbsoluteTimeInfo Source
Like TimeInfo
, but with all relative times replaced by absolute UTC.
fromAbsoluteTimeInfo :: AbsoluteTimeInfo -> UTCTimeSource
Just the UTC time value.
makeAbsoluteTimeInfo :: TimeInfo -> UTCTime -> AbsoluteTimeInfoSource
Convert TimeInfo
to AbsoluteTimeInfo
given the current UTC time.
Signature
data SignatureData Source
Data that is always required for signing requests.
SignatureData | |
|
signatureData :: TimeInfo -> Credentials -> IO SignatureDataSource
Create signature data using the current system time.
A signable request object. Assembles together the Query, and signs it in one go.
type ServiceConfiguration r :: *Source
Additional information, like API endpoints and service-specific preferences.
signQuery :: r -> ServiceConfiguration r -> SignatureData -> SignedQuerySource
Create a SignedQuery
from a request, additional Info
, and SignatureData
.
data AuthorizationHash Source
Supported crypto hashes for the signature.
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.
"true"
"false"
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.
Transactions
class (SignQuery r, ResponseConsumer r 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.
Credentials
data Credentials Source
AWS access credentials.
Credentials | |
|
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
class DefaultServiceConfiguration config whereSource
Default configuration for a specific service.
defaultConfiguration :: configSource
Default service configuration for normal requests.
defaultConfigurationUri :: configSource
Default service configuration for URI-only requests.
debugConfiguration :: configSource
Default debugging-only configuration for normal requests. (Normally using HTTP instead of HTTPS for easier debugging.)
debugConfigurationUri :: configSource
Default debugging-only configuration for URI-only requests. (Normally using HTTP instead of HTTPS for easier debugging.)
HTTP types
Protocols supported by AWS. Currently, all AWS services use the HTTP or HTTPS protocols.
defaultPort :: Protocol -> IntSource
The default port to be used for a protocol if no specific port is specified.
Request method. Not all request methods are supported by all services.
Get | GET method. Put all request parameters in a query string and HTTP headers. |
PostQuery | POST method. Put all request parameters in a query string and HTTP headers, but send the query string as a POST payload |
Post | POST method. Sends a service- and request-specific request body. |
Put | PUT method. |
Delete | DELETE method. |
httpMethod :: Method -> MethodSource
HTTP method associated with a request method.