| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Aws.Core
Synopsis
- class Loggable a where
- data Response m a = Response {}
- readResponse :: MonadThrow n => Response m a -> n a
- readResponseIO :: MonadIO io => Response m a -> io a
- tellMetadata :: m -> Response m ()
- tellMetadataRef :: Monoid m => IORef m -> m -> IO ()
- mapMetadata :: (m -> n) -> Response m a -> Response n a
- type HTTPResponseConsumer a = Response (ConduitM () ByteString (ResourceT IO) ()) -> ResourceT IO a
- class Monoid (ResponseMetadata resp) => ResponseConsumer req resp where- type ResponseMetadata resp
- responseConsumer :: Request -> req -> IORef (ResponseMetadata resp) -> HTTPResponseConsumer resp
 
- class AsMemoryResponse resp where- type MemoryResponse resp :: Type
- loadToMemory :: resp -> ResourceT IO (MemoryResponse resp)
 
- class ListResponse resp item | resp -> item where- listResponse :: resp -> [item]
 
- newtype XmlException = XmlException {}
- newtype HeaderException = HeaderException {}
- newtype FormException = FormException {}
- newtype NoCredentialsException = NoCredentialsException {}
- throwStatusCodeException :: MonadThrow m => Request -> Response (ConduitM () ByteString m ()) -> m a
- readHex2 :: [Char] -> Maybe Word8
- elContent :: Text -> Cursor -> [Text]
- elCont :: Text -> Cursor -> [String]
- force :: MonadThrow m => String -> [a] -> m a
- forceM :: MonadThrow m => String -> [m a] -> m a
- textReadBool :: MonadThrow m => Text -> m Bool
- textReadInt :: (MonadThrow m, Num a) => Text -> m a
- readInt :: (MonadThrow 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 (IO ByteString))
- sqContentType :: !(Maybe ByteString)
- sqContentMd5 :: !(Maybe (Digest MD5))
- sqAmzHeaders :: !RequestHeaders
- sqOtherHeaders :: !RequestHeaders
- sqBody :: !(Maybe RequestBody)
- sqStringToSign :: !ByteString
 
- data NormalQuery
- data UriOnlyQuery
- queryToHttpRequest :: SignedQuery -> IO Request
- 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 request where- type ServiceConfiguration request :: Type -> Type
- signQuery :: request -> ServiceConfiguration request queryType -> SignatureData -> SignedQuery
 
- data AuthorizationHash
- amzHash :: AuthorizationHash -> ByteString
- signature :: Credentials -> AuthorizationHash -> ByteString -> ByteString
- credentialV4 :: SignatureData -> ByteString -> ByteString -> ByteString
- authorizationV4 :: SignatureData -> AuthorizationHash -> ByteString -> ByteString -> ByteString -> ByteString -> IO ByteString
- authorizationV4' :: SignatureData -> AuthorizationHash -> ByteString -> ByteString -> ByteString -> ByteString -> ByteString
- signatureV4 :: SignatureData -> AuthorizationHash -> ByteString -> ByteString -> 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
- parseHttpDate :: String -> Maybe UTCTime
- httpDate1 :: String
- textHttpDate :: UTCTime -> Text
- iso8601UtcDate :: String
- class (SignQuery r, ResponseConsumer r a, Loggable (ResponseMetadata a)) => Transaction r a | r -> a
- class Transaction r a => IteratedTransaction r a | r -> a where- nextIteratedRequest :: r -> a -> Maybe r
 
- data Credentials = Credentials {- accessKeyID :: ByteString
- secretAccessKey :: ByteString
- v4SigningKeys :: IORef [V4Key]
- iamToken :: Maybe ByteString
- isAnonymousCredentials :: Bool
 
- makeCredentials :: MonadIO io => ByteString -> ByteString -> io Credentials
- credentialsDefaultFile :: MonadIO io => io (Maybe FilePath)
- credentialsDefaultKey :: Text
- loadCredentialsFromFile :: MonadIO io => FilePath -> Text -> io (Maybe Credentials)
- loadCredentialsFromEnv :: MonadIO io => io (Maybe Credentials)
- loadCredentialsFromInstanceMetadata :: MonadIO io => io (Maybe Credentials)
- loadCredentialsFromEnvOrFile :: MonadIO io => FilePath -> Text -> io (Maybe Credentials)
- loadCredentialsFromEnvOrFileOrInstanceMetadata :: MonadIO io => FilePath -> Text -> io (Maybe Credentials)
- loadCredentialsDefault :: MonadIO io => io (Maybe Credentials)
- anonymousCredentials :: MonadIO io => io Credentials
- class DefaultServiceConfiguration config where- defServiceConfig :: config
- debugServiceConfig :: config
 
- data Protocol
- defaultPort :: Protocol -> Int
- data Method
- httpMethod :: Method -> Method
Logging
class Loggable a where Source #
Types that can be logged (textually).
Instances
| Loggable DdbResponse Source # | |
| Defined in Aws.DynamoDb.Core Methods toLogText :: DdbResponse -> Text Source # | |
| Loggable IamMetadata Source # | |
| Defined in Aws.Iam.Core Methods toLogText :: IamMetadata -> Text Source # | |
| Loggable S3Metadata Source # | |
| Defined in Aws.S3.Core Methods toLogText :: S3Metadata -> Text Source # | |
| Loggable SesMetadata Source # | |
| Defined in Aws.Ses.Core Methods toLogText :: SesMetadata -> Text Source # | |
| Loggable SdbMetadata Source # | |
| Defined in Aws.SimpleDb.Core Methods toLogText :: SdbMetadata -> Text Source # | |
| Loggable SqsMetadata Source # | |
| Defined in Aws.Sqs.Core Methods toLogText :: SqsMetadata -> Text Source # | |
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.
Constructors
| Response | |
| Fields 
 | |
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.
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
Memory response
class AsMemoryResponse resp where Source #
Class for responses that are fully loaded into memory
Associated Types
type MemoryResponse resp :: Type Source #
Methods
loadToMemory :: resp -> ResourceT IO (MemoryResponse resp) Source #
Instances
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 #
Instances
| ListResponse QueryResponse Item Source # | |
| Defined in Aws.DynamoDb.Commands.Query Methods listResponse :: QueryResponse -> [Item] Source # | |
| ListResponse ScanResponse Item Source # | |
| Defined in Aws.DynamoDb.Commands.Scan Methods listResponse :: ScanResponse -> [Item] Source # | |
| ListResponse GetBucketResponse ObjectInfo Source # | |
| Defined in Aws.S3.Commands.GetBucket Methods listResponse :: GetBucketResponse -> [ObjectInfo] Source # | |
| ListResponse GetBucketObjectVersionsResponse ObjectVersionInfo Source # | |
| Defined in Aws.S3.Commands.GetBucketObjectVersions Methods listResponse :: GetBucketObjectVersionsResponse -> [ObjectVersionInfo] Source # | |
| ListResponse ListDomainsResponse Text Source # | |
| Defined in Aws.SimpleDb.Commands.Domain Methods listResponse :: ListDomainsResponse -> [Text] Source # | |
| ListResponse SelectResponse (Item [Attribute Text]) Source # | |
| Defined in Aws.SimpleDb.Commands.Select Methods listResponse :: SelectResponse -> [Item [Attribute Text]] Source # | |
Exception types
newtype XmlException Source #
An error that occurred during XML parsing / validation.
Constructors
| XmlException | |
| Fields | |
Instances
| Exception XmlException Source # | |
| Defined in Aws.Core Methods toException :: XmlException -> SomeException # fromException :: SomeException -> Maybe XmlException # displayException :: XmlException -> String # | |
| Show XmlException Source # | |
| Defined in Aws.Core Methods showsPrec :: Int -> XmlException -> ShowS # show :: XmlException -> String # showList :: [XmlException] -> ShowS # | |
newtype HeaderException Source #
An error that occurred during header parsing / validation.
Constructors
| HeaderException | |
| Fields | |
Instances
| Exception HeaderException Source # | |
| Defined in Aws.Core Methods toException :: HeaderException -> SomeException # | |
| Show HeaderException Source # | |
| Defined in Aws.Core Methods showsPrec :: Int -> HeaderException -> ShowS # show :: HeaderException -> String # showList :: [HeaderException] -> ShowS # | |
newtype FormException Source #
An error that occurred during form parsing / validation.
Constructors
| FormException | |
| Fields | |
Instances
| Exception FormException Source # | |
| Defined in Aws.Core Methods toException :: FormException -> SomeException # fromException :: SomeException -> Maybe FormException # displayException :: FormException -> String # | |
| Show FormException Source # | |
| Defined in Aws.Core Methods showsPrec :: Int -> FormException -> ShowS # show :: FormException -> String # showList :: [FormException] -> ShowS # | |
newtype NoCredentialsException Source #
No credentials were found and an invariant was violated.
Constructors
| NoCredentialsException | |
| Fields | |
Instances
| Exception NoCredentialsException Source # | |
| Defined in Aws.Core | |
| Show NoCredentialsException Source # | |
| Defined in Aws.Core Methods showsPrec :: Int -> NoCredentialsException -> ShowS # show :: NoCredentialsException -> String # showList :: [NoCredentialsException] -> ShowS # | |
throwStatusCodeException :: MonadThrow m => Request -> Response (ConduitM () ByteString m ()) -> m a Source #
A helper to throw an StatusCodeException.
Response deconstruction helpers
XML
elContent :: Text -> Cursor -> [Text] Source #
A specific element (case-insensitive, ignoring namespace - sadly necessary), extracting only the textual contents.
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
| DefaultServiceConfiguration (DdbConfiguration NormalQuery) Source # | |
| Defined in Aws.DynamoDb.Core | |
| DefaultServiceConfiguration (IamConfiguration NormalQuery) Source # | |
| Defined in Aws.Iam.Core | |
| DefaultServiceConfiguration (S3Configuration NormalQuery) Source # | |
| Defined in Aws.S3.Core | |
| DefaultServiceConfiguration (SesConfiguration NormalQuery) Source # | |
| Defined in Aws.Ses.Core | |
| DefaultServiceConfiguration (SdbConfiguration NormalQuery) Source # | |
| Defined in Aws.SimpleDb.Core | |
| DefaultServiceConfiguration (SqsConfiguration NormalQuery) Source # | |
| Defined in Aws.Sqs.Core | |
| Default (DdbConfiguration NormalQuery) Source # | |
| Defined in Aws.DynamoDb.Core Methods | |
data UriOnlyQuery Source #
Tag type for URI-only queries.
Instances
| DefaultServiceConfiguration (IamConfiguration UriOnlyQuery) Source # | |
| Defined in Aws.Iam.Core | |
| DefaultServiceConfiguration (S3Configuration UriOnlyQuery) Source # | |
| Defined in Aws.S3.Core | |
| DefaultServiceConfiguration (SesConfiguration UriOnlyQuery) Source # | |
| Defined in Aws.Ses.Core | |
| DefaultServiceConfiguration (SdbConfiguration UriOnlyQuery) Source # | |
| Defined in Aws.SimpleDb.Core | |
| DefaultServiceConfiguration (SqsConfiguration UriOnlyQuery) Source # | |
| 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
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.
Constructors
| AbsoluteTimestamp | |
| Fields | |
| AbsoluteExpires | |
| Fields | |
Instances
| Show AbsoluteTimeInfo Source # | |
| Defined in Aws.Core Methods showsPrec :: Int -> AbsoluteTimeInfo -> ShowS # show :: AbsoluteTimeInfo -> String # showList :: [AbsoluteTimeInfo] -> ShowS # | |
fromAbsoluteTimeInfo :: AbsoluteTimeInfo -> UTCTime Source #
Just the UTC time value.
makeAbsoluteTimeInfo :: TimeInfo -> UTCTime -> AbsoluteTimeInfo Source #
Convert TimeInfo to AbsoluteTimeInfo given the current UTC time.
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 :: Type -> Type 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
data AuthorizationHash Source #
Supported crypto hashes for the signature.
Constructors
| HmacSHA1 | |
| HmacSHA256 | 
Instances
| Show AuthorizationHash Source # | |
| Defined in Aws.Core Methods showsPrec :: Int -> AuthorizationHash -> ShowS # show :: AuthorizationHash -> String # showList :: [AuthorizationHash] -> ShowS # | |
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.
Arguments
| :: SignatureData | |
| -> ByteString | region, e.g. us-east-1 | 
| -> ByteString | service, e.g. dynamodb | 
| -> ByteString | 
Generates the Credential string, required for V4 signatures.
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.
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.
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.
awsTrue :: ByteString Source #
"true"
awsFalse :: ByteString Source #
"false"
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.
rfc822Time :: String Source #
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.
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
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
Credentials
data Credentials Source #
AWS access credentials.
Constructors
| Credentials | |
| Fields 
 | |
Instances
| Show Credentials Source # | |
| Defined in Aws.Core Methods showsPrec :: Int -> Credentials -> ShowS # show :: Credentials -> String # showList :: [Credentials] -> ShowS # | |
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.
loadCredentialsFromInstanceMetadata :: MonadIO io => io (Maybe Credentials) Source #
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.
anonymousCredentials :: MonadIO io => io Credentials Source #
Make a dummy Credentials that can be used to access some AWS services anonymously.
Service configuration
class DefaultServiceConfiguration config where Source #
Default configuration for a specific service.
Minimal complete definition
Methods
defServiceConfig :: config Source #
Default service configuration.
debugServiceConfig :: config Source #
Default debugging-only configuration. (Normally using HTTP instead of HTTPS for easier debugging.)
Instances
HTTP types
Protocols supported by AWS. Currently, all AWS services use the HTTP or HTTPS protocols.
defaultPort :: Protocol -> Int Source #
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.
Constructors
| Head | HEAD method. Put all request parameters in a query string and HTTP headers. | 
| Get | GET method. Put all request parameters in a query string and HTTP headers. | 
| PostQuery | POST method. Put all request parameters in a query string and HTTP headers, but send the query string as a POST payload | 
| Post | POST method. Sends a service- and request-specific request body. | 
| Put | PUT method. | 
| Delete | DELETE method. | 
httpMethod :: Method -> Method Source #
HTTP method associated with a request method.