Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data LogLevel
- type Logger = LogLevel -> Text -> IO ()
- defaultLog :: LogLevel -> Logger
- data Configuration = Configuration {}
- baseConfiguration :: MonadIO io => io Configuration
- dbgConfiguration :: MonadIO io => io Configuration
- aws :: Transaction r a => Configuration -> ServiceConfiguration r NormalQuery -> Manager -> r -> ResourceT IO (Response (ResponseMetadata a) a)
- awsRef :: Transaction r a => Configuration -> ServiceConfiguration r NormalQuery -> Manager -> IORef (ResponseMetadata a) -> r -> ResourceT IO a
- pureAws :: Transaction r a => Configuration -> ServiceConfiguration r NormalQuery -> Manager -> r -> ResourceT IO a
- simpleAws :: (Transaction r a, AsMemoryResponse a, MonadIO io) => Configuration -> ServiceConfiguration r NormalQuery -> r -> io (MemoryResponse a)
- unsafeAws :: (ResponseConsumer r a, Monoid (ResponseMetadata a), Loggable (ResponseMetadata a), SignQuery r) => Configuration -> ServiceConfiguration r NormalQuery -> Manager -> r -> ResourceT IO (Response (ResponseMetadata a) a)
- unsafeAwsRef :: (ResponseConsumer r a, Monoid (ResponseMetadata a), SignQuery r) => Configuration -> ServiceConfiguration r NormalQuery -> Manager -> IORef (ResponseMetadata a) -> r -> ResourceT IO a
- awsUri :: (SignQuery request, MonadIO io) => Configuration -> ServiceConfiguration request UriOnlyQuery -> request -> io ByteString
- awsIteratedSource :: IteratedTransaction r a => Configuration -> ServiceConfiguration r NormalQuery -> Manager -> r -> Producer (ResourceT IO) (Response (ResponseMetadata a) a)
- awsIteratedList :: (IteratedTransaction r a, ListResponse a i) => Configuration -> ServiceConfiguration r NormalQuery -> Manager -> r -> Producer (ResourceT IO) i
- type HTTPResponseConsumer a = Response (ResumableSource (ResourceT IO) ByteString) -> ResourceT IO a
- data Response m a = Response {}
- readResponse :: MonadThrow n => Response m a -> n a
- readResponseIO :: MonadIO io => Response m a -> io a
- class AsMemoryResponse resp where
- type MemoryResponse resp :: *
- loadToMemory :: resp -> ResourceT IO (MemoryResponse resp)
- newtype XmlException = XmlException {}
- newtype HeaderException = HeaderException {}
- newtype FormException = FormException {}
- class DefaultServiceConfiguration config where
- defServiceConfig :: config
- debugServiceConfig :: config
- data NormalQuery
- data UriOnlyQuery
- data TimeInfo
- class (SignQuery r, ResponseConsumer r a, Loggable (ResponseMetadata a)) => Transaction r a | r -> a
- class Transaction r a => IteratedTransaction r a | r -> a
- data Credentials = Credentials {
- accessKeyID :: ByteString
- secretAccessKey :: ByteString
- v4SigningKeys :: IORef [V4Key]
- iamToken :: Maybe ByteString
- makeCredentials :: MonadIO io => ByteString -> ByteString -> io Credentials
- credentialsDefaultFile :: MonadIO io => io 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)
Logging
The severity of a log message, in rising order.
type Logger = LogLevel -> Text -> IO () Source
The interface for any logging function. Takes log level and a log message, and can perform an arbitrary IO action.
defaultLog :: LogLevel -> Logger Source
The default logger defaultLog minLevel
, which prints log messages above level minLevel
to stderr
.
Configuration
data Configuration Source
The configuration for an AWS request. You can use multiple configurations in parallel, even over the same HTTP connection manager.
Configuration | |
|
baseConfiguration :: MonadIO io => io Configuration Source
The default configuration, with credentials loaded from environment variable or configuration file
(see loadCredentialsDefault
).
dbgConfiguration :: MonadIO io => io Configuration Source
Debug configuration, which logs much more verbosely.
Transaction runners
Safe runners
aws :: Transaction r a => Configuration -> ServiceConfiguration r NormalQuery -> Manager -> r -> ResourceT IO (Response (ResponseMetadata a) a) Source
awsRef :: Transaction r a => Configuration -> ServiceConfiguration r NormalQuery -> Manager -> IORef (ResponseMetadata a) -> r -> ResourceT IO a Source
pureAws :: Transaction r a => Configuration -> ServiceConfiguration r NormalQuery -> Manager -> r -> ResourceT IO a Source
simpleAws :: (Transaction r a, AsMemoryResponse a, MonadIO io) => Configuration -> ServiceConfiguration r NormalQuery -> r -> io (MemoryResponse a) Source
Unsafe runners
unsafeAws :: (ResponseConsumer r a, Monoid (ResponseMetadata a), Loggable (ResponseMetadata a), SignQuery r) => Configuration -> ServiceConfiguration r NormalQuery -> Manager -> r -> ResourceT IO (Response (ResponseMetadata a) a) Source
Run an AWS transaction, without enforcing that response and request type form a valid transaction pair.
This is especially useful for debugging and development, you should not have to use it in production.
All errors are caught and wrapped in the Response
value.
Metadata is wrapped in the Response, and also logged at level Info
.
unsafeAwsRef :: (ResponseConsumer r a, Monoid (ResponseMetadata a), SignQuery r) => Configuration -> ServiceConfiguration r NormalQuery -> Manager -> IORef (ResponseMetadata a) -> r -> ResourceT IO a Source
Run an AWS transaction, without enforcing that response and request type form a valid transaction pair.
This is especially useful for debugging and development, you should not have to use it in production.
Errors are not caught, and need to be handled with exception handlers.
Metadata is put in the IORef
, but not logged.
URI runners
awsUri :: (SignQuery request, MonadIO io) => Configuration -> ServiceConfiguration request UriOnlyQuery -> request -> io ByteString Source
Run a URI-only AWS transaction. Returns a URI that can be sent anywhere. Does not work with all requests.
Usage:
uri <- awsUri cfg request
Iterated runners
awsIteratedSource :: IteratedTransaction r a => Configuration -> ServiceConfiguration r NormalQuery -> Manager -> r -> Producer (ResourceT IO) (Response (ResponseMetadata a) a) Source
awsIteratedList :: (IteratedTransaction r a, ListResponse a i) => Configuration -> ServiceConfiguration r NormalQuery -> Manager -> r -> Producer (ResourceT IO) i Source
Response
Full HTTP response
type HTTPResponseConsumer a = Response (ResumableSource (ResourceT IO) ByteString) -> ResourceT IO a Source
A full HTTP response parser. Takes HTTP status, response headers, and response body.
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.
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.
Memory responses
class AsMemoryResponse resp where Source
Class for responses that are fully loaded into memory
type MemoryResponse resp :: * Source
loadToMemory :: resp -> ResourceT IO (MemoryResponse resp) Source
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.
Query
Service configuration
class DefaultServiceConfiguration config where Source
Default configuration for a specific service.
defServiceConfig :: config Source
Default service configuration.
debugServiceConfig :: config Source
Default debugging-only configuration. (Normally using HTTP instead of HTTPS for easier debugging.)
data NormalQuery Source
Tag type for normal queries.
data UriOnlyQuery Source
Tag type for URI-only queries.
Expiration
Whether to restrict the signature validity with a plain timestamp, or with explicit expiration (absolute or relative).
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.
class Transaction r a => IteratedTransaction r a | r -> a Source
A transaction that may need to be split over multiple requests, for example because of upstream response size limits.
Credentials
data Credentials Source
AWS access credentials.
Credentials | |
|
:: MonadIO io | |
=> ByteString | AWS Access Key ID |
-> ByteString | AWS Secret Access Key |
-> io Credentials |
credentialsDefaultFile :: MonadIO io => io FilePath Source
The file where access credentials are loaded, when using loadCredentialsDefault
.
Value: directory/.aws-keys
credentialsDefaultKey :: Text Source
The key to be used in the access credential file that is loaded, when using loadCredentialsDefault
.
Value: default
loadCredentialsFromFile :: MonadIO io => FilePath -> Text -> io (Maybe Credentials) Source
Load credentials from a (text) file given a key name.
The file consists of a sequence of lines, each in the following format:
keyName awsKeyID awsKeySecret
loadCredentialsFromEnv :: MonadIO io => io (Maybe Credentials) Source
Load credentials from the environment variables AWS_ACCESS_KEY_ID
and AWS_ACCESS_KEY_SECRET
(or AWS_SECRET_ACCESS_KEY
), if possible.
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.