Copyright | (c) 2013-2018 Brendan Hay |
---|---|
License | Mozilla Public License, v. 2.0. |
Maintainer | Brendan Hay <brendan.g.hay+amazonka@gmail.com> |
Stability | provisional |
Portability | non-portable (GHC extensions) |
Safe Haskell | None |
Language | Haskell2010 |
This module provides a simple AWS
monad and a set of operations which
can be performed against remote Amazon Web Services APIs, for use with the types
supplied by the various amazonka-*
libraries.
A MonadAWS
typeclass is used as a function constraint to provide automatic
lifting of functions when embedding AWS
as a layer inside your own
application stack.
Control.Monad.Trans.AWS contains the underlying AWST
transformer.
Synopsis
- type AWS = AWST (ResourceT IO)
- class (Functor m, Applicative m, Monad m, MonadIO m, MonadCatch m) => MonadAWS m where
- runAWS :: (MonadResource m, HasEnv r) => r -> AWS a -> m a
- runResourceT :: MonadUnliftIO m => ResourceT m a -> m a
- newEnv :: (Applicative m, MonadIO m, MonadCatch m) => Credentials -> m Env
- data Env
- class HasEnv a where
- data Credentials
- data Region
- send :: (MonadAWS m, AWSRequest a) => a -> m (Rs a)
- paginate :: (MonadAWS m, AWSPager a) => a -> ConduitM () (Rs a) m ()
- await :: (MonadAWS m, AWSRequest a) => Wait a -> a -> m Accept
- configure :: HasEnv a => Service -> a -> a
- override :: HasEnv a => (Service -> Service) -> a -> a
- reconfigure :: MonadAWS m => Service -> AWS a -> m a
- within :: MonadAWS m => Region -> AWS a -> m a
- once :: MonadAWS m => AWS a -> m a
- timeout :: MonadAWS m => Seconds -> AWS a -> m a
- class ToHashedBody a where
- toHashed :: a -> HashedBody
- hashedFile :: MonadIO m => FilePath -> m HashedBody
- hashedFileRange :: MonadIO m => FilePath -> Integer -> Integer -> m HashedBody
- hashedBody :: Digest SHA256 -> Integer -> ConduitM () ByteString (ResourceT IO) () -> HashedBody
- class ToBody a where
- newtype ChunkSize = ChunkSize Int
- defaultChunkSize :: ChunkSize
- chunkedFile :: MonadIO m => ChunkSize -> FilePath -> m RqBody
- chunkedFileRange :: MonadIO m => ChunkSize -> FilePath -> Integer -> Integer -> m RqBody
- unsafeChunkedBody :: ChunkSize -> Integer -> ConduitM () ByteString (ResourceT IO) () -> RqBody
- sinkBody :: MonadIO m => RsBody -> ConduitM ByteString Void (ResourceT IO) a -> m a
- getFileSize :: MonadIO m => FilePath -> m Integer
- sinkMD5 :: Monad m => ConduitM ByteString o m (Digest MD5)
- sinkSHA256 :: Monad m => ConduitM ByteString o m (Digest SHA256)
- presignURL :: (MonadAWS m, AWSRequest a) => UTCTime -> Seconds -> a -> m ByteString
- isEC2 :: MonadAWS m => m Bool
- dynamic :: MonadAWS m => Dynamic -> m ByteString
- metadata :: MonadAWS m => Metadata -> m ByteString
- userdata :: MonadAWS m => m (Maybe ByteString)
- data Dynamic
- data Metadata
- = AMIId
- | AMILaunchIndex
- | AMIManifestPath
- | AncestorAMIIds
- | BlockDevice !Mapping
- | Hostname
- | IAM !Info
- | InstanceAction
- | InstanceId
- | InstanceType
- | KernelId
- | LocalHostname
- | LocalIPV4
- | MAC
- | Network !Text !Interface
- | AvailabilityZone
- | ProductCodes
- | PublicHostname
- | PublicIPV4
- | OpenSSHKey
- | RAMDiskId
- | ReservationId
- | SecurityGroups
- class AsError a where
- class AsAuthError a where
- _AuthError :: Prism' a AuthError
- _RetrievalError :: Prism' a HttpException
- _MissingEnvError :: Prism' a Text
- _InvalidEnvError :: Prism' a Text
- _MissingFileError :: Prism' a FilePath
- _InvalidFileError :: Prism' a Text
- _InvalidIAMError :: Prism' a Text
- trying :: MonadCatch m => Getting (First a) SomeException a -> m r -> m (Either a r)
- catching :: MonadCatch m => Getting (First a) SomeException a -> m r -> (a -> m r) -> m r
- _MatchServiceError :: AsError a => Service -> ErrorCode -> Getting (First ServiceError) a ServiceError
- hasService :: (Applicative f, Choice p) => Service -> Optic' p f ServiceError ServiceError
- hasStatus :: (Applicative f, Choice p) => Int -> Optic' p f ServiceError ServiceError
- hasCode :: (Applicative f, Choice p) => ErrorCode -> Optic' p f ServiceError ServiceError
- type Logger = LogLevel -> Builder -> IO ()
- data LogLevel
- newLogger :: MonadIO m => LogLevel -> Handle -> m Logger
- data Endpoint
- setEndpoint :: Bool -> ByteString -> Int -> Service -> Service
- _Default :: Monoid a => Iso' (Maybe a) a
- _Coerce :: (Coercible a b, Coercible b a) => Iso' a b
- microseconds :: Seconds -> Int
- seconds :: Seconds -> Int
- withAuth :: MonadIO m => Auth -> (AuthEnv -> m a) -> m a
- expiration :: Lens' AuthEnv (Maybe UTCTime)
- sessionToken :: Lens' AuthEnv (Maybe SessionToken)
- secretAccessKey :: Lens' AuthEnv SecretKey
- accessKeyId :: Lens' AuthEnv AccessKey
- rqPresign :: Seconds -> Algorithm a
- rqSign :: Algorithm a
- rqQuery :: Lens' (Request a) QueryString
- rqPath :: Lens' (Request a) RawPath
- rqMethod :: Lens' (Request a) StdMethod
- rqHeaders :: Lens' (Request a) [Header]
- rqBody :: Lens' (Request a) RqBody
- rqService :: Lens' (Request a) Service
- clientRequest :: Endpoint -> Maybe Seconds -> ClientRequest
- serviceRetry :: Lens' Service Retry
- serviceCheck :: Lens' Service (Status -> Bool)
- serviceTimeout :: Lens' Service (Maybe Seconds)
- serviceEndpoint :: Setter' Service Endpoint
- serviceSigner :: Lens' Service Signer
- retryCheck :: Lens' Retry (ServiceError -> Maybe Text)
- retryAttempts :: Lens' Retry Int
- exponentGrowth :: Lens' Retry Int
- exponentBase :: Lens' Retry Double
- endpointScope :: Lens' Endpoint ByteString
- endpointPort :: Lens' Endpoint Int
- endpointSecure :: Lens' Endpoint Bool
- endpointHost :: Lens' Endpoint ByteString
- serviceRequestId :: Lens' ServiceError (Maybe RequestId)
- serviceMessage :: Lens' ServiceError (Maybe ErrorMessage)
- serviceCode :: Lens' ServiceError ErrorCode
- serviceHeaders :: Lens' ServiceError [Header]
- serviceStatus :: Lens' ServiceError Status
- serviceAbbrev :: Lens' ServiceError Abbrev
- serializeMessage :: Lens' SerializeError String
- serializeStatus :: Lens' SerializeError Status
- serializeAbbrev :: Lens' SerializeError Abbrev
- errorCode :: Text -> ErrorCode
- type ClientRequest = Request
- type ClientResponse = Response ResponseBody
- type ResponseBody = ConduitM () ByteString (ResourceT IO) ()
- data Abbrev
- newtype ErrorCode = ErrorCode Text
- newtype ErrorMessage = ErrorMessage Text
- newtype RequestId = RequestId Text
- data Error
- data SerializeError = SerializeError' {}
- data ServiceError = ServiceError' {}
- class AsError a where
- data Endpoint = Endpoint {}
- type Logger = LogLevel -> Builder -> IO ()
- data Retry = Exponential {
- _retryBase :: !Double
- _retryGrowth :: !Int
- _retryAttempts :: !Int
- _retryCheck :: ServiceError -> Maybe Text
- data Meta where
- data Signed a = Signed {
- sgMeta :: !Meta
- sgRequest :: !ClientRequest
- type Algorithm a = Request a -> AuthEnv -> Region -> UTCTime -> Signed a
- data Signer = Signer {}
- data Service = Service {
- _svcAbbrev :: !Abbrev
- _svcSigner :: !Signer
- _svcPrefix :: !ByteString
- _svcVersion :: !ByteString
- _svcEndpoint :: !(Region -> Endpoint)
- _svcTimeout :: !(Maybe Seconds)
- _svcCheck :: !(Status -> Bool)
- _svcError :: !(Status -> [Header] -> LazyByteString -> Error)
- _svcRetry :: !Retry
- data Request a = Request {
- _rqService :: !Service
- _rqMethod :: !StdMethod
- _rqPath :: !RawPath
- _rqQuery :: !QueryString
- _rqHeaders :: ![Header]
- _rqBody :: !RqBody
- type Response a = (Status, Rs a)
- class AWSRequest a where
- type Rs a :: Type
- request :: a -> Request a
- response :: (MonadResource m, MonadThrow m) => Logger -> Service -> Proxy a -> ClientResponse -> m (Response a)
- newtype AccessKey = AccessKey ByteString
- newtype SecretKey = SecretKey ByteString
- newtype SessionToken = SessionToken ByteString
- data AuthEnv = AuthEnv {}
- data Auth
- data Region
- newtype Seconds = Seconds Int
- data HttpException
- data Wait a
- class AWSRequest a => AWSPager a
- data RqBody
- data HashedBody
- data ChunkedBody
- data RsBody
Usage
The key functions dealing with the request/response lifecycle are:
These functions have constraints that types from the amazonka-*
libraries
satisfy. To utilise these, you will need to specify what Region
you wish to
operate in and your Amazon credentials for AuthN/AuthZ purposes.
Credentials
can be supplied in a number of ways. Either via explicit keys,
via session profiles, or have Amazonka retrieve the credentials from an
underlying IAM Role/Profile.
As a basic example, you might wish to store an object in an S3 bucket using amazonka-s3:
import Control.Lens import Network.AWS import Network.AWS.S3 import System.IO example :: IO PutObjectResponse example = do -- A newLogger
to replace the default noop logger is created, with the logger -- set to print debug information and errors to stdout: lgr <- newLogger Debug stdout -- To specify configuration preferences,newEnv
is used to create a new -- configuration environment. TheCredentials
parameter is used to specify -- mechanism for supplying or retrieving AuthN/AuthZ information. -- In this caseDiscover
will cause the library to try a number of options such -- as default environment variables, or an instance's IAM Profile and identity document: env <- newEnv Discover -- The payload (and hash) for the S3 object is retrieved from aFilePath
, -- eitherhashedFile
orchunkedFile
can be used, with the latter ensuring -- the contents of the file is enumerated exactly once, during send: body <- chunkedFile defaultChunkSize "local/path/to/object-payload" -- We now run theAWS
computation with the overriden logger, performing the --PutObject
request.envRegion
orwithin
can be used to set the -- remote AWSRegion
: runResourceT $ runAWS (env & envLogger .~ lgr) $ within Frankfurt $ send (putObject "bucket-name" "object-key" body)
Running AWS Actions
class (Functor m, Applicative m, Monad m, MonadIO m, MonadCatch m) => MonadAWS m where Source #
Monads in which AWS
actions may be embedded.
Instances
MonadAWS AWS Source # | |
MonadAWS m => MonadAWS (MaybeT m) Source # | |
MonadAWS m => MonadAWS (ListT m) Source # | |
MonadAWS m => MonadAWS (IdentityT m) Source # | |
(Monoid w, MonadAWS m) => MonadAWS (WriterT w m) Source # | |
(Monoid w, MonadAWS m) => MonadAWS (WriterT w m) Source # | |
MonadAWS m => MonadAWS (StateT s m) Source # | |
MonadAWS m => MonadAWS (StateT s m) Source # | |
MonadAWS m => MonadAWS (ExceptT e m) Source # | |
MonadAWS m => MonadAWS (ReaderT r m) Source # | |
(Monoid w, MonadAWS m) => MonadAWS (RWST r w s m) Source # | |
(Monoid w, MonadAWS m) => MonadAWS (RWST r w s m) Source # | |
runAWS :: (MonadResource m, HasEnv r) => r -> AWS a -> m a Source #
Run the AWS
monad. Any outstanding HTTP responses' ResumableSource
will
be closed when the ResourceT
computation is unwrapped with runResourceT
.
Throws LogLevel
, which will include HTTPExceptions
, serialisation errors,
or any particular errors returned by the respective AWS service.
See: runAWST
, runResourceT
.
runResourceT :: MonadUnliftIO m => ResourceT m a -> m a #
Unwrap a ResourceT
transformer, and call all registered release actions.
Note that there is some reference counting involved due to resourceForkIO
.
If multiple threads are sharing the same collection of resources, only the
last call to runResourceT
will deallocate the resources.
NOTE Since version 1.2.0, this function will throw a
ResourceCleanupException
if any of the cleanup functions throw an
exception.
Since: resourcet-0.3.0
Authentication and Environment
:: (Applicative m, MonadIO m, MonadCatch m) | |
=> Credentials | Credential discovery mechanism. |
-> m Env |
Creates a new environment with a new Manager
without debug logging
and uses getAuth
to expand/discover the supplied Credentials
.
Lenses from HasEnv
can be used to further configure the resulting Env
.
Since: 1.5.0
- The region is now retrieved from the AWS_REGION
environment
variable (identical to official SDKs), or defaults to us-east-1
.
You can override the Env
region by using envRegion
, or the current operation's
region by using within
.
Since: 1.3.6
- The default logic for retrying HttpException
s now uses
retryConnectionFailure
to retry specific connection failure conditions up to 3 times.
Previously only service specific errors were automatically retried.
This can be reverted to the old behaviour by resetting the Env
using
envRetryCheck
lens to (\_ _ -> False)
.
Throws AuthError
when environment variables or IAM profiles cannot be read.
See: newEnvWith
.
The environment containing the parameters required to make AWS requests.
Instances
ToLog Env Source # | |
Defined in Network.AWS.Env | |
HasEnv Env Source # | |
Defined in Network.AWS.Env environment :: Lens' Env Env Source # envRegion :: Lens' Env Region Source # envLogger :: Lens' Env Logger Source # envRetryCheck :: Lens' Env (Int -> HttpException -> Bool) Source # envOverride :: Lens' Env (Dual (Endo Service)) Source # envManager :: Lens' Env Manager Source # | |
MonadAWS AWS Source # | |
environment :: Lens' a Env Source #
envRegion :: Lens' a Region Source #
The current region.
envLogger :: Lens' a Logger Source #
The function used to output log messages.
envRetryCheck :: Lens' a (Int -> HttpException -> Bool) Source #
The function used to determine if an HttpException
should be retried.
envOverride :: Lens' a (Dual (Endo Service)) Source #
The currently applied overrides to all Service
configuration.
envManager :: Lens' a Manager Source #
The Manager
used to create and manage open HTTP connections.
envAuth :: Lens' a Auth Source #
The credentials used to sign requests for authentication with AWS.
envEC2 :: Getter a (IORef (Maybe Bool)) Source #
A memoised predicate for whether the underlying host is an EC2 instance.
Instances
HasEnv Env Source # | |
Defined in Network.AWS.Env environment :: Lens' Env Env Source # envRegion :: Lens' Env Region Source # envLogger :: Lens' Env Logger Source # envRetryCheck :: Lens' Env (Int -> HttpException -> Bool) Source # envOverride :: Lens' Env (Dual (Endo Service)) Source # envManager :: Lens' Env Manager Source # |
Credential Discovery
data Credentials Source #
Determines how AuthN/AuthZ information is retrieved.
FromKeys AccessKey SecretKey | Explicit access and secret keys. See |
FromSession AccessKey SecretKey SessionToken | Explicit access key, secret key and a session token. See |
FromEnv Text Text (Maybe Text) (Maybe Text) | Lookup specific environment variables for access key, secret key, an optional session token, and an optional region, respectively. |
FromProfile Text | An IAM Profile name to lookup from the local EC2 instance-data. Environment variables to lookup for the access key, secret key and optional session token. |
FromFile Text FilePath | A credentials profile name (the INI section) and the path to the AWS credentials file. |
FromContainer | Obtain credentials by attempting to contact the ECS container agent
at http://169.254.170.2 using the path in |
Discover | Attempt credentials discovery via the following steps:
An attempt is made to resolve http://instance-data rather than directly retrieving http://169.254.169.254 for IAM profile information. This assists in ensuring the DNS lookup terminates promptly if not running on EC2. |
Instances
Eq Credentials Source # | |
Defined in Network.AWS.Auth (==) :: Credentials -> Credentials -> Bool # (/=) :: Credentials -> Credentials -> Bool # | |
Show Credentials Source # | |
Defined in Network.AWS.Auth showsPrec :: Int -> Credentials -> ShowS # show :: Credentials -> String # showList :: [Credentials] -> ShowS # | |
ToLog Credentials Source # | |
Defined in Network.AWS.Auth build :: Credentials -> Builder # |
AuthN/AuthZ information is handled similarly to other AWS SDKs. You can read some of the options available here.
When running on an EC2 instance and using FromProfile
or Discover
, a thread
is forked which transparently handles the expiry and subsequent refresh of IAM
profile information. See fromProfileName
for more information.
Supported Regions
The available AWS regions.
NorthVirginia | US East ('us-east-1'). |
Ohio | US East ('us-east-2'). |
NorthCalifornia | US West ('us-west-1'). |
Oregon | US West ('us-west-2'). |
Montreal | Canada ('ca-central-1'). |
Tokyo | Asia Pacific ('ap-northeast-1'). |
Seoul | Asia Pacific ('ap-northeast-2'). |
Mumbai | Asia Pacific ('ap-south-1'). |
Singapore | Asia Pacific ('ap-southeast-1'). |
Sydney | Asia Pacific ('ap-southeast-2'). |
SaoPaulo | South America ('sa-east-1'). |
Ireland | EU ('eu-west-1'). |
London | EU ('eu-west-2'). |
Frankfurt | EU ('eu-central-1'). |
GovCloud | US GovCloud ('us-gov-west-1'). |
GovCloudFIPS | US GovCloud FIPS (S3 Only, 'fips-us-gov-west-1'). |
Beijing | China ('cn-north-1'). |
Instances
Bounded Region | |
Enum Region | |
Defined in Network.AWS.Types | |
Eq Region | |
Data Region | |
Defined in Network.AWS.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Region -> c Region # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Region # toConstr :: Region -> Constr # dataTypeOf :: Region -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Region) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Region) # gmapT :: (forall b. Data b => b -> b) -> Region -> Region # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Region -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Region -> r # gmapQ :: (forall d. Data d => d -> u) -> Region -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Region -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Region -> m Region # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Region -> m Region # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Region -> m Region # | |
Ord Region | |
Read Region | |
Show Region | |
Generic Region | |
Hashable Region | |
Defined in Network.AWS.Types | |
ToJSON Region | |
Defined in Network.AWS.Types | |
FromJSON Region | |
FromXML Region | |
ToXML Region | |
Defined in Network.AWS.Types | |
ToLog Region | |
Defined in Network.AWS.Types | |
ToByteString Region | |
Defined in Network.AWS.Types toBS :: Region -> ByteString # | |
FromText Region | |
Defined in Network.AWS.Types | |
ToText Region | |
Defined in Network.AWS.Types | |
NFData Region | |
Defined in Network.AWS.Types | |
type Rep Region | |
Defined in Network.AWS.Types type Rep Region = D1 (MetaData "Region" "Network.AWS.Types" "amazonka-core-1.6.1-FZORvxk9gh76fGemhSgXQL" False) ((((C1 (MetaCons "NorthVirginia" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ohio" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "NorthCalifornia" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Oregon" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Montreal" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Tokyo" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Seoul" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Mumbai" PrefixI False) (U1 :: Type -> Type)))) :+: (((C1 (MetaCons "Singapore" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Sydney" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "SaoPaulo" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ireland" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "London" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Frankfurt" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "GovCloud" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "GovCloudFIPS" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Beijing" PrefixI False) (U1 :: Type -> Type)))))) |
Sending Requests
To send a request you need to create a value of the desired operation type using
the relevant constructor, as well as any further modifications of default/optional
parameters using the appropriate lenses. This value can then be sent using send
or paginate
and the library will take care of serialisation/authentication and
so forth.
The default Service
configuration for a request contains retry configuration that is used to
determine if a request can safely be retried and what kind of back off/on strategy
should be used. (Usually exponential.)
Typically services define retry strategies that handle throttling, general server
errors and transport errors. Streaming requests are never retried.
send :: (MonadAWS m, AWSRequest a) => a -> m (Rs a) Source #
Send a request, returning the associated response if successful.
Pagination
Some AWS operations return results that are incomplete and require subsequent
requests in order to obtain the entire result set. The process of sending
subsequent requests to continue where a previous request left off is called
pagination. For example, the ListObjects
operation of Amazon S3 returns up to
1000 objects at a time, and you must send subsequent requests with the
appropriate Marker in order to retrieve the next page of results.
Operations that have an AWSPager
instance can transparently perform subsequent
requests, correctly setting Markers and other request facets to iterate through
the entire result set of a truncated API operation. Operations which support
this have an additional note in the documentation.
Many operations have the ability to filter results on the server side. See the individual operation parameters for details.
paginate :: (MonadAWS m, AWSPager a) => a -> ConduitM () (Rs a) m () Source #
Repeatedly send a request, automatically setting markers and paginating over multiple responses while available.
Waiters
Waiters poll by repeatedly sending a request until some remote success condition
configured by the Wait
specification is fulfilled. The Wait
specification
determines how many attempts should be made, in addition to delay and retry strategies.
Error conditions that are not handled by the Wait
configuration will be thrown,
or the first successful response that fulfills the success condition will be
returned.
Wait
specifications can be found under the Network.AWS.{ServiceName}.Waiters
namespace for services which support await
.
await :: (MonadAWS m, AWSRequest a) => Wait a -> a -> m Accept Source #
Poll the API with the supplied request until a specific Wait
condition
is fulfilled.
Service Configuration
When a request is sent, various values such as the endpoint,
retry strategy, timeout and error handlers are taken from the associated Service
for a request. For example, DynamoDB
will use the dynamoDB
configuration when sending PutItem
, Query
and all other operations.
You can modify a specific Service'
s default configuration by using
configure
or reconfigure
. To modify all configurations simultaneously, see override
.
An example of how you might alter default configuration using these mechanisms
is demonstrated below. Firstly, the default dynamoDB
service is configured to
use non-SSL localhost as the endpoint:
let dynamo :: Service dynamo = setEndpoint False "localhost" 8000 dynamoDB
The updated configuration is then passed to the Env
during setup:
e <- newEnv Frankfurt Discover <&> configure dynamo runAWS e $ do -- This S3 operation will communicate with remote AWS APIs. x <- send listBuckets -- DynamoDB operations will communicate with localhost:8000. y <- send listTables -- Any operations for services other than DynamoDB, are not affected. ...
You can also scope the Endpoint
modifications (or any other Service
configuration)
to specific actions:
e <- newEnv Ireland Discover runAWS e $ do -- Service operations here will communicate with AWS, even DynamoDB. x <- send listTables reconfigure dynamo $ do -- In here, DynamoDB operations will communicate with localhost:8000, -- with operations for services not being affected. ...
Functions such as within
, once
, and timeout
likewise modify the underlying
configuration for all service requests within their respective scope.
Overriding Defaults
configure :: HasEnv a => Service -> a -> a Source #
Configure a specific service. All requests belonging to the supplied service will use this configuration instead of the default.
It's suggested you use a modified version of the default service, such
as Network.AWS.DynamoDB.dynamoDB
.
See: reconfigure
.
override :: HasEnv a => (Service -> Service) -> a -> a Source #
Provide a function which will be added to the existing stack of overrides applied to all service configuration.
To override a specific service, it's suggested you use
either configure
or reconfigure
with a modified version of the default
service, such as Network.AWS.DynamoDB.dynamoDB
.
Scoped Actions
reconfigure :: MonadAWS m => Service -> AWS a -> m a Source #
Scope an action such that all requests belonging to the supplied service will use this configuration instead of the default.
It's suggested you use a modified version of the default service, such
as Network.AWS.DynamoDB.dynamoDB
.
See: configure
.
once :: MonadAWS m => AWS a -> m a Source #
Scope an action such that any retry logic for the Service
is
ignored and any requests will at most be sent once.
timeout :: MonadAWS m => Seconds -> AWS a -> m a Source #
Scope an action such that any HTTP response will use this timeout value.
Streaming
Streaming comes in two flavours. HashedBody
represents a request
that requires a precomputed SHA256
hash, or a ChunkedBody
type for those services
that can perform incremental signing and do not require the entire payload to
be hashed (such as S3
). The type signatures for request smart constructors
advertise which respective body type is required, denoting the underlying signing
capabilities.
ToHashedBody
and ToBody
typeclass instances are available to construct the
streaming bodies, automatically calculating any hash or size as needed for types
such as Text
, ByteString
, or Aeson's Value
type. To read files and other
IO
primitives, functions such as hashedFile
, chunkedFile
, or hashedBody
should be used.
For responses that contain streaming bodies (such as GetObject
), you can use
sinkBody
to connect the response body to a conduit
compatible sink.
Request Bodies
class ToHashedBody a where #
Anything that can be safely converted to a HashedBody
.
toHashed :: a -> HashedBody #
Convert a value to a hashed request body.
Instances
ToHashedBody ByteString | |
Defined in Network.AWS.Data.Body toHashed :: ByteString -> HashedBody # | |
ToHashedBody ByteString | |
Defined in Network.AWS.Data.Body toHashed :: ByteString -> HashedBody # | |
ToHashedBody Text | |
Defined in Network.AWS.Data.Body toHashed :: Text -> HashedBody # | |
ToHashedBody Value | |
Defined in Network.AWS.Data.Body toHashed :: Value -> HashedBody # | |
ToHashedBody Element | |
Defined in Network.AWS.Data.Body toHashed :: Element -> HashedBody # | |
ToHashedBody Base64 | |
Defined in Network.AWS.Data.Base64 toHashed :: Base64 -> HashedBody # | |
ToHashedBody HashedBody | |
Defined in Network.AWS.Data.Body toHashed :: HashedBody -> HashedBody # | |
ToHashedBody QueryString | |
Defined in Network.AWS.Data.Body toHashed :: QueryString -> HashedBody # | |
ToHashedBody String | |
Defined in Network.AWS.Data.Body toHashed :: String -> HashedBody # | |
ToHashedBody Text | |
Defined in Network.AWS.Data.Body toHashed :: Text -> HashedBody # | |
ToHashedBody (HashMap Text Value) | |
Defined in Network.AWS.Data.Body |
:: MonadIO m | |
=> FilePath | The file path to read. |
-> m HashedBody |
Construct a HashedBody
from a FilePath
, calculating the SHA256
hash
and file size.
Note: While this function will perform in constant space, it will enumerate the entirety of the file contents _twice_. Firstly to calculate the SHA256 and lastly to stream the contents to the socket during sending.
See: ToHashedBody
.
:: MonadIO m | |
=> FilePath | The file path to read. |
-> Integer | The byte offset at which to start reading. |
-> Integer | The maximum number of bytes to read. |
-> m HashedBody |
Construct a HashedBody
from a FilePath
, specifying the range of bytes
to read. This can be useful for constructing multiple requests from a single
file, say for S3 multipart uploads.
See: hashedFile
, sourceFileRange
.
:: Digest SHA256 | A SHA256 hash of the file contents. |
-> Integer | The size of the stream in bytes. |
-> ConduitM () ByteString (ResourceT IO) () | |
-> HashedBody |
Construct a HashedBody
from a Source
, manually specifying the SHA256
hash and file size. It's left up to the caller to calculate these correctly,
otherwise AWS will return signing errors.
See: ToHashedBody
.
Chunked Request Bodies
Anything that can be converted to a streaming request Body
.
Nothing
Instances
ToBody ByteString | |
Defined in Network.AWS.Data.Body toBody :: ByteString -> RqBody # | |
ToBody ByteString | |
Defined in Network.AWS.Data.Body toBody :: ByteString -> RqBody # | |
ToBody Text | |
Defined in Network.AWS.Data.Body | |
ToBody Value | |
Defined in Network.AWS.Data.Body | |
ToBody Element | |
Defined in Network.AWS.Data.Body | |
ToBody Base64 | |
Defined in Network.AWS.Data.Base64 | |
ToBody ChunkedBody | |
Defined in Network.AWS.Data.Body toBody :: ChunkedBody -> RqBody # | |
ToBody HashedBody | |
Defined in Network.AWS.Data.Body toBody :: HashedBody -> RqBody # | |
ToBody RqBody | |
Defined in Network.AWS.Data.Body | |
ToBody QueryString | |
Defined in Network.AWS.Data.Body toBody :: QueryString -> RqBody # | |
ToBody String | |
Defined in Network.AWS.Data.Body | |
ToBody Text | |
Defined in Network.AWS.Data.Body | |
ToHashedBody a => ToBody (Maybe a) | |
Defined in Network.AWS.Data.Body | |
ToBody (HashMap Text Value) | |
Specifies the transmitted size of the 'Transfer-Encoding' chunks.
See: defaultChunk
.
Instances
Enum ChunkSize | |
Defined in Network.AWS.Data.Body succ :: ChunkSize -> ChunkSize # pred :: ChunkSize -> ChunkSize # fromEnum :: ChunkSize -> Int # enumFrom :: ChunkSize -> [ChunkSize] # enumFromThen :: ChunkSize -> ChunkSize -> [ChunkSize] # enumFromTo :: ChunkSize -> ChunkSize -> [ChunkSize] # enumFromThenTo :: ChunkSize -> ChunkSize -> ChunkSize -> [ChunkSize] # | |
Eq ChunkSize | |
Integral ChunkSize | |
Defined in Network.AWS.Data.Body | |
Num ChunkSize | |
Defined in Network.AWS.Data.Body | |
Ord ChunkSize | |
Defined in Network.AWS.Data.Body | |
Real ChunkSize | |
Defined in Network.AWS.Data.Body toRational :: ChunkSize -> Rational # | |
Show ChunkSize | |
ToLog ChunkSize | |
Defined in Network.AWS.Data.Body |
defaultChunkSize :: ChunkSize #
The default chunk size of 128 KB. The minimum chunk size accepted by AWS is 8 KB, unless the entirety of the request is below this threshold.
A chunk size of 64 KB or higher is recommended for performance reasons.
chunkedFile :: MonadIO m => ChunkSize -> FilePath -> m RqBody Source #
Construct a ChunkedBody
from a FilePath
, where the contents will be
read and signed incrementally in chunks if the target service supports it.
Will intelligently revert to HashedBody
if the file is smaller than the
specified ChunkSize
.
See: ToBody
.
:: MonadIO m | |
=> ChunkSize | The idealized size of chunks that will be yielded downstream. |
-> FilePath | The file path to read. |
-> Integer | The byte offset at which to start reading. |
-> Integer | The maximum number of bytes to read. |
-> m RqBody |
Construct a ChunkedBody
from a FilePath
, specifying the range of bytes
to read. This can be useful for constructing multiple requests from a single
file, say for S3 multipart uploads.
See: chunkedFile
.
:: ChunkSize | The idealized size of chunks that will be yielded downstream. |
-> Integer | The size of the stream in bytes. |
-> ConduitM () ByteString (ResourceT IO) () | |
-> RqBody |
Unsafely construct a ChunkedBody
.
This function is marked unsafe because it does nothing to enforce the chunk size.
Typically for conduit IO
functions, it's whatever ByteString's
defaultBufferSize
is, around 32 KB. If the chunk size is less than 8 KB,
the request will error. 64 KB or higher chunk size is recommended for
performance reasons.
Note that it will always create a chunked body even if the request is too small.
See: ToBody
.
Response Bodies
sinkBody :: MonadIO m => RsBody -> ConduitM ByteString Void (ResourceT IO) a -> m a Source #
Connect a Sink
to a response stream.
File Size and MD5/SHA256
getFileSize :: MonadIO m => FilePath -> m Integer Source #
Convenience function for obtaining the size of a file.
sinkSHA256 :: Monad m => ConduitM ByteString o m (Digest SHA256) Source #
Presigning Requests
Presigning requires the Service
signer to be an instance of AWSPresigner
.
Not all signing algorithms support this.
:: (MonadAWS m, AWSRequest a) | |
=> UTCTime | Signing time. |
-> Seconds | Expiry time. |
-> a | Request to presign. |
-> m ByteString |
Presign an URL that is valid from the specified time until the number of seconds expiry has elapsed.
EC2 Instance Metadata
Metadata can be retrieved from the underlying host assuming that you're running
the code on an EC2 instance or have a compatible instance-data
endpoint available.
isEC2 :: MonadAWS m => m Bool Source #
Test whether the underlying host is running on EC2. This is memoised and an HTTP request is made to the host's metadata endpoint for the first call only.
userdata :: MonadAWS m => m (Maybe ByteString) Source #
Retrieve the user data. Returns Nothing
if no user data is assigned
to the instance.
FWS | Value showing whether the customer has enabled detailed one-minute monitoring in CloudWatch. Valid values: enabled | disabled. |
Document | JSON containing instance attributes, such as instance-id,
private IP address, etc.
See: |
PKCS7 | Used to verify the document's authenticity and content against the signature. |
Signature |
AMIId | The AMI ID used to launch the instance. |
AMILaunchIndex | If you started more than one instance at the same time, this value indicates the order in which the instance was launched. The value of the first instance launched is 0. |
AMIManifestPath | The path to the AMI's manifest file in Amazon S3. If you used an Amazon EBS-backed AMI to launch the instance, the returned result is unknown. |
AncestorAMIIds | The AMI IDs of any instances that were rebundled to create this AMI. This value will only exist if the AMI manifest file contained an ancestor-amis key. |
BlockDevice !Mapping | See: |
Hostname | The private hostname of the instance. In cases where multiple network interfaces are present, this refers to the eth0 device (the device for which the device number is 0). |
IAM !Info | See: |
InstanceAction | Notifies the instance that it should reboot in preparation for bundling. Valid values: none | shutdown | bundle-pending. |
InstanceId | The ID of this instance. |
InstanceType | The type of instance. See: |
KernelId | The ID of the kernel launched with this instance, if applicable. |
LocalHostname | The private DNS hostname of the instance. In cases where multiple network interfaces are present, this refers to the eth0 device (the device for which the device number is 0). |
LocalIPV4 | The private IP address of the instance. In cases where multiple network interfaces are present, this refers to the eth0 device (the device for which the device number is 0). |
MAC | The instance's media access control (MAC) address. In cases where multiple network interfaces are present, this refers to the eth0 device (the device for which the device number is 0). |
Network !Text !Interface | See: |
AvailabilityZone | The Availability Zone in which the instance launched. |
ProductCodes | Product codes associated with the instance, if any. |
PublicHostname | The instance's public DNS. If the instance is in a VPC, this category is only returned if the enableDnsHostnames attribute is set to true. For more information, see Using DNS with Your VPC. |
PublicIPV4 | The public IP address. If an Elastic IP address is associated with the instance, the value returned is the Elastic IP address. |
OpenSSHKey | Public key. Only available if supplied at instance launch time. |
RAMDiskId | The ID of the RAM disk specified at launch time, if applicable. |
ReservationId | ID of the reservation. |
SecurityGroups | The names of the security groups applied to the instance. |
Running Asynchronous Actions
Requests can be sent asynchronously, but due to guarantees about resource closure require the use of lifted-async.
The following example demonstrates retrieving two objects from S3 concurrently:
import Control.Concurrent.Async.Lifted import Control.Lens import Control.Monad.Trans.AWS import Network.AWS.S3 do x <- async . send $ getObject "bucket" "prefix/object-foo" y <- async . send $ getObject "bucket" "prefix/object-bar" foo <- wait x bar <- wait y ...
Handling Errors
Errors are thrown by the library using MonadThrow
(unless Control.Monad.Error.AWS is used).
Sub-errors of the canonical LogLevel
type can be caught using trying
or
catching
and the appropriate AsError
Prism
:
trying_Error
(send $ ListObjects "bucket-name") :: EitherLogLevel
ListObjectsResponse trying_TransportError
(send $ ListObjects "bucket-name") :: EitherHttpException
ListObjectsResponse trying_SerializeError
(send $ ListObjects "bucket-name") :: EitherSerializeError
ListObjectsResponse trying_ServiceError
(send $ ListObjects "bucket-name") :: EitherServiceError
ListObjectsResponse
Many of the individual amazonka-*
libraries export compatible Getter
s for
matching service specific error codes and messages in the style above.
See the Error Matchers
heading in each respective library for details.
A general Amazonka error.
_TransportError :: Prism' a HttpException #
An error occured while communicating over HTTP with a remote service.
_SerializeError :: Prism' a SerializeError #
A serialisation error occured when attempting to deserialise a response.
_ServiceError :: Prism' a ServiceError #
A service specific error returned by the remote service.
Instances
AsError Error | |
Defined in Network.AWS.Types | |
AsError SomeException | |
class AsAuthError a where Source #
_AuthError :: Prism' a AuthError Source #
A general authentication error.
_RetrievalError :: Prism' a HttpException Source #
An error occured while communicating over HTTP with the local metadata endpoint.
_MissingEnvError :: Prism' a Text Source #
The named environment variable was not found.
_InvalidEnvError :: Prism' a Text Source #
An error occured parsing named environment variable's value.
_MissingFileError :: Prism' a FilePath Source #
The specified credentials file could not be found.
_InvalidFileError :: Prism' a Text Source #
An error occured parsing the credentials file.
_InvalidIAMError :: Prism' a Text Source #
The specified IAM profile could not be found or deserialised.
Instances
trying :: MonadCatch m => Getting (First a) SomeException a -> m r -> m (Either a r) #
A variant of try
that takes a ReifiedPrism
(or any ReifiedFold
) to select which
exceptions are caught (c.f. tryJust
, catchJust
). If the
Exception
does not match the predicate, it is re-thrown.
trying
::MonadCatch
m =>Prism'
SomeException
a -> m r -> m (Either
a r)trying
::MonadCatch
m =>Lens'
SomeException
a -> m r -> m (Either
a r)trying
::MonadCatch
m =>Traversal'
SomeException
a -> m r -> m (Either
a r)trying
::MonadCatch
m =>Iso'
SomeException
a -> m r -> m (Either
a r)trying
::MonadCatch
m =>ReifiedGetter
SomeException
a -> m r -> m (Either
a r)trying
::MonadCatch
m =>ReifiedFold
SomeException
a -> m r -> m (Either
a r)
catching :: MonadCatch m => Getting (First a) SomeException a -> m r -> (a -> m r) -> m r #
Catch exceptions that match a given ReifiedPrism
(or any ReifiedFold
, really).
>>>
catching _AssertionFailed (assert False (return "uncaught")) $ \ _ -> return "caught"
"caught"
catching
::MonadCatch
m =>Prism'
SomeException
a -> m r -> (a -> m r) -> m rcatching
::MonadCatch
m =>Lens'
SomeException
a -> m r -> (a -> m r) -> m rcatching
::MonadCatch
m =>Traversal'
SomeException
a -> m r -> (a -> m r) -> m rcatching
::MonadCatch
m =>Iso'
SomeException
a -> m r -> (a -> m r) -> m rcatching
::MonadCatch
m =>ReifiedGetter
SomeException
a -> m r -> (a -> m r) -> m rcatching
::MonadCatch
m =>ReifiedFold
SomeException
a -> m r -> (a -> m r) -> m r
Building Error Prisms
_MatchServiceError :: AsError a => Service -> ErrorCode -> Getting (First ServiceError) a ServiceError #
Provides a generalised prism for catching a specific service error identified by the opaque service abbreviation and error code.
This can be used if the generated error prisms provided by
Network.AWS.ServiceName.Types
do not cover all the thrown error codes.
For example to define a new error prism:
{-# LANGUAGE OverloadedStrings #-} import Network.AWS.S3 (ServiceError, s3) _NoSuchBucketPolicy :: AsError a => Getting (First ServiceError) a ServiceError _NoSuchBucketPolicy = _MatchServiceError s3 "NoSuchBucketPolicy"
With example usage being:
>>>
import Control.Exception.Lens (trying)
>>>
:t trying _NoSuchBucketPolicy
MonadCatch m => m a -> m (Either ServiceError a)
hasService :: (Applicative f, Choice p) => Service -> Optic' p f ServiceError ServiceError #
hasStatus :: (Applicative f, Choice p) => Int -> Optic' p f ServiceError ServiceError #
hasCode :: (Applicative f, Choice p) => ErrorCode -> Optic' p f ServiceError ServiceError #
Logging
The exposed logging interface is a primitive Logger
function which gets
threaded through service calls and serialisation routines. This allows the
library to output useful information and diagnostics.
The newLogger
function can be used to construct a simple logger which writes
output to a Handle
, but in most production code you should probably consider
using a more robust logging library such as
tiny-log or
fast-logger.
type Logger = LogLevel -> Builder -> IO () #
A function threaded through various request and serialisation routines to log informational and debug messages.
Info | Info messages supplied by the user - this level is not emitted by the library. |
Error | Error messages only. |
Debug | Useful debug information + info + error levels. |
Trace | Includes potentially sensitive signing metadata, and non-streaming response bodies. |
Instances
Enum LogLevel | |
Eq LogLevel | |
Data LogLevel | |
Defined in Network.AWS.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LogLevel -> c LogLevel # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LogLevel # toConstr :: LogLevel -> Constr # dataTypeOf :: LogLevel -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LogLevel) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LogLevel) # gmapT :: (forall b. Data b => b -> b) -> LogLevel -> LogLevel # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LogLevel -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LogLevel -> r # gmapQ :: (forall d. Data d => d -> u) -> LogLevel -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LogLevel -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LogLevel -> m LogLevel # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LogLevel -> m LogLevel # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LogLevel -> m LogLevel # | |
Ord LogLevel | |
Defined in Network.AWS.Types | |
Show LogLevel | |
ToByteString LogLevel | |
Defined in Network.AWS.Types toBS :: LogLevel -> ByteString # | |
FromText LogLevel | |
Defined in Network.AWS.Types | |
ToText LogLevel | |
Defined in Network.AWS.Types |
Constructing a Logger
newLogger :: MonadIO m => LogLevel -> Handle -> m Logger Source #
This is a primitive logger which can be used to log builds to a Handle
.
Note: A more sophisticated logging library such as tinylog or fast-logger should be used in production code.
Endpoints
Instances
Eq Endpoint | |
Data Endpoint | |
Defined in Network.AWS.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Endpoint -> c Endpoint # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Endpoint # toConstr :: Endpoint -> Constr # dataTypeOf :: Endpoint -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Endpoint) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Endpoint) # gmapT :: (forall b. Data b => b -> b) -> Endpoint -> Endpoint # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Endpoint -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Endpoint -> r # gmapQ :: (forall d. Data d => d -> u) -> Endpoint -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Endpoint -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Endpoint -> m Endpoint # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Endpoint -> m Endpoint # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Endpoint -> m Endpoint # | |
Show Endpoint | |
:: Bool | Whether to use HTTPS (ie. SSL). |
-> ByteString | The hostname to connect to. |
-> Int | The port number to connect to. |
-> Service | The service configuration to override. |
-> Service |
A convenience function for overriding the Service
Endpoint
.
See: serviceEndpoint
.
Re-exported Types
_Default :: Monoid a => Iso' (Maybe a) a #
Invalid Iso, should be a Prism but exists for ease of composition with the current 'Lens . Iso' chaining to hide internal types from the user.
microseconds :: Seconds -> Int #
sessionToken :: Lens' AuthEnv (Maybe SessionToken) #
The token that users must pass to the service API to use the temporary credentials.
secretAccessKey :: Lens' AuthEnv SecretKey #
The secret access key that can be used to sign requests.
accessKeyId :: Lens' AuthEnv AccessKey #
The access key ID that identifies the temporary security credentials.
rqQuery :: Lens' (Request a) QueryString #
clientRequest :: Endpoint -> Maybe Seconds -> ClientRequest #
Construct a ClientRequest
using common parameters such as TLS and prevent
throwing errors when receiving erroneous status codes in respones.
retryCheck :: Lens' Retry (ServiceError -> Maybe Text) #
retryAttempts :: Lens' Retry Int #
exponentGrowth :: Lens' Retry Int #
type ClientRequest = Request #
A convenience alias to avoid type ambiguity.
type ClientResponse = Response ResponseBody #
A convenience alias encapsulating the common Response
.
type ResponseBody = ConduitM () ByteString (ResourceT IO) () #
A convenience alias encapsulating the common Response
body.
Abbreviated service name.
Instances
Eq ErrorCode | |
Ord ErrorCode | |
Defined in Network.AWS.Types | |
Show ErrorCode | |
IsString ErrorCode | |
Defined in Network.AWS.Types fromString :: String -> ErrorCode # | |
FromJSON ErrorCode | |
FromXML ErrorCode | |
ToLog ErrorCode | |
Defined in Network.AWS.Types | |
FromText ErrorCode | |
Defined in Network.AWS.Types | |
ToText ErrorCode | |
Defined in Network.AWS.Types |
newtype ErrorMessage #
Instances
Instances
Eq RequestId | |
Ord RequestId | |
Defined in Network.AWS.Types | |
Show RequestId | |
IsString RequestId | |
Defined in Network.AWS.Types fromString :: String -> RequestId # | |
FromJSON RequestId | |
FromXML RequestId | |
ToLog RequestId | |
Defined in Network.AWS.Types | |
FromText RequestId | |
Defined in Network.AWS.Types | |
ToText RequestId | |
Defined in Network.AWS.Types |
An error type representing errors that can be attributed to this library.
Instances
Show Error | |
AsError Error | |
Defined in Network.AWS.Types | |
ToLog Error | |
Defined in Network.AWS.Types | |
Exception Error | |
Defined in Network.AWS.Types toException :: Error -> SomeException # fromException :: SomeException -> Maybe Error # displayException :: Error -> String # |
data SerializeError #
SerializeError' | |
|
Instances
Eq SerializeError | |
Defined in Network.AWS.Types (==) :: SerializeError -> SerializeError -> Bool # (/=) :: SerializeError -> SerializeError -> Bool # | |
Show SerializeError | |
Defined in Network.AWS.Types showsPrec :: Int -> SerializeError -> ShowS # show :: SerializeError -> String # showList :: [SerializeError] -> ShowS # | |
ToLog SerializeError | |
Defined in Network.AWS.Types build :: SerializeError -> Builder # |
data ServiceError #
Instances
Eq ServiceError | |
Defined in Network.AWS.Types (==) :: ServiceError -> ServiceError -> Bool # (/=) :: ServiceError -> ServiceError -> Bool # | |
Show ServiceError | |
Defined in Network.AWS.Types showsPrec :: Int -> ServiceError -> ShowS # show :: ServiceError -> String # showList :: [ServiceError] -> ShowS # | |
ToLog ServiceError | |
Defined in Network.AWS.Types build :: ServiceError -> Builder # |
A general Amazonka error.
_TransportError :: Prism' a HttpException #
An error occured while communicating over HTTP with a remote service.
_SerializeError :: Prism' a SerializeError #
A serialisation error occured when attempting to deserialise a response.
_ServiceError :: Prism' a ServiceError #
A service specific error returned by the remote service.
Instances
AsError Error | |
Defined in Network.AWS.Types | |
AsError SomeException | |
Endpoint | |
|
Instances
Eq Endpoint | |
Data Endpoint | |
Defined in Network.AWS.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Endpoint -> c Endpoint # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Endpoint # toConstr :: Endpoint -> Constr # dataTypeOf :: Endpoint -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Endpoint) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Endpoint) # gmapT :: (forall b. Data b => b -> b) -> Endpoint -> Endpoint # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Endpoint -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Endpoint -> r # gmapQ :: (forall d. Data d => d -> u) -> Endpoint -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Endpoint -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Endpoint -> m Endpoint # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Endpoint -> m Endpoint # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Endpoint -> m Endpoint # | |
Show Endpoint | |
type Logger = LogLevel -> Builder -> IO () #
A function threaded through various request and serialisation routines to log informational and debug messages.
Constants and predicates used to create a RetryPolicy
.
Exponential | |
|
Signing algorithm specific metadata.
A signed ClientRequest
and associated metadata specific
to the signing algorithm, tagged with the initial request type
to be able to obtain the associated response, 'Rs a'.
Signed | |
|
Attributes and functions specific to an AWS service.
Service | |
|
An unsigned request.
Request | |
|
class AWSRequest a where #
Specify how a request can be de/serialised.
response :: (MonadResource m, MonadThrow m) => Logger -> Service -> Proxy a -> ClientResponse -> m (Response a) #
An access key ID.
For example: AKIAIOSFODNN7EXAMPLE
Instances
Secret access key credential.
For example: wJalrXUtnFEMIK7MDENGbPxRfiCYEXAMPLEKE
Instances
Eq SecretKey | |
Data SecretKey | |
Defined in Network.AWS.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SecretKey -> c SecretKey # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SecretKey # toConstr :: SecretKey -> Constr # dataTypeOf :: SecretKey -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SecretKey) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SecretKey) # gmapT :: (forall b. Data b => b -> b) -> SecretKey -> SecretKey # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SecretKey -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SecretKey -> r # gmapQ :: (forall d. Data d => d -> u) -> SecretKey -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SecretKey -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SecretKey -> m SecretKey # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SecretKey -> m SecretKey # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SecretKey -> m SecretKey # | |
IsString SecretKey | |
Defined in Network.AWS.Types fromString :: String -> SecretKey # | |
Hashable SecretKey | |
Defined in Network.AWS.Types | |
ToJSON SecretKey | |
Defined in Network.AWS.Types | |
FromJSON SecretKey | |
FromXML SecretKey | |
ToXML SecretKey | |
Defined in Network.AWS.Types | |
ToByteString SecretKey | |
Defined in Network.AWS.Types toBS :: SecretKey -> ByteString # | |
FromText SecretKey | |
Defined in Network.AWS.Types | |
ToText SecretKey | |
Defined in Network.AWS.Types | |
NFData SecretKey | |
Defined in Network.AWS.Types |
newtype SessionToken #
A session token used by STS to temporarily authorise access to an AWS resource.
Instances
The AuthN/AuthZ credential environment.
AuthEnv | |
|
Instances
Eq AuthEnv | |
Data AuthEnv | |
Defined in Network.AWS.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AuthEnv -> c AuthEnv # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AuthEnv # toConstr :: AuthEnv -> Constr # dataTypeOf :: AuthEnv -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AuthEnv) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AuthEnv) # gmapT :: (forall b. Data b => b -> b) -> AuthEnv -> AuthEnv # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AuthEnv -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AuthEnv -> r # gmapQ :: (forall d. Data d => d -> u) -> AuthEnv -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AuthEnv -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AuthEnv -> m AuthEnv # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AuthEnv -> m AuthEnv # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AuthEnv -> m AuthEnv # | |
Show AuthEnv | |
Generic AuthEnv | |
FromJSON AuthEnv | |
FromXML AuthEnv | |
ToLog AuthEnv | |
Defined in Network.AWS.Types | |
NFData AuthEnv | |
Defined in Network.AWS.Types | |
type Rep AuthEnv | |
Defined in Network.AWS.Types type Rep AuthEnv = D1 (MetaData "AuthEnv" "Network.AWS.Types" "amazonka-core-1.6.1-FZORvxk9gh76fGemhSgXQL" False) (C1 (MetaCons "AuthEnv" PrefixI True) ((S1 (MetaSel (Just "_authAccess") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 AccessKey) :*: S1 (MetaSel (Just "_authSecret") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Sensitive SecretKey))) :*: (S1 (MetaSel (Just "_authToken") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Sensitive SessionToken))) :*: S1 (MetaSel (Just "_authExpiry") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ISO8601))))) |
An authorisation environment containing AWS credentials, and potentially a reference which can be refreshed out-of-band as temporary credentials expire.
The available AWS regions.
NorthVirginia | US East ('us-east-1'). |
Ohio | US East ('us-east-2'). |
NorthCalifornia | US West ('us-west-1'). |
Oregon | US West ('us-west-2'). |
Montreal | Canada ('ca-central-1'). |
Tokyo | Asia Pacific ('ap-northeast-1'). |
Seoul | Asia Pacific ('ap-northeast-2'). |
Mumbai | Asia Pacific ('ap-south-1'). |
Singapore | Asia Pacific ('ap-southeast-1'). |
Sydney | Asia Pacific ('ap-southeast-2'). |
SaoPaulo | South America ('sa-east-1'). |
Ireland | EU ('eu-west-1'). |
London | EU ('eu-west-2'). |
Frankfurt | EU ('eu-central-1'). |
GovCloud | US GovCloud ('us-gov-west-1'). |
GovCloudFIPS | US GovCloud FIPS (S3 Only, 'fips-us-gov-west-1'). |
Beijing | China ('cn-north-1'). |
Instances
Bounded Region | |
Enum Region | |
Defined in Network.AWS.Types | |
Eq Region | |
Data Region | |
Defined in Network.AWS.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Region -> c Region # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Region # toConstr :: Region -> Constr # dataTypeOf :: Region -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Region) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Region) # gmapT :: (forall b. Data b => b -> b) -> Region -> Region # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Region -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Region -> r # gmapQ :: (forall d. Data d => d -> u) -> Region -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Region -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Region -> m Region # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Region -> m Region # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Region -> m Region # | |
Ord Region | |
Read Region | |
Show Region | |
Generic Region | |
Hashable Region | |
Defined in Network.AWS.Types | |
ToJSON Region | |
Defined in Network.AWS.Types | |
FromJSON Region | |
FromXML Region | |
ToXML Region | |
Defined in Network.AWS.Types | |
ToLog Region | |
Defined in Network.AWS.Types | |
ToByteString Region | |
Defined in Network.AWS.Types toBS :: Region -> ByteString # | |
FromText Region | |
Defined in Network.AWS.Types | |
ToText Region | |
Defined in Network.AWS.Types | |
NFData Region | |
Defined in Network.AWS.Types | |
type Rep Region | |
Defined in Network.AWS.Types type Rep Region = D1 (MetaData "Region" "Network.AWS.Types" "amazonka-core-1.6.1-FZORvxk9gh76fGemhSgXQL" False) ((((C1 (MetaCons "NorthVirginia" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ohio" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "NorthCalifornia" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Oregon" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Montreal" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Tokyo" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Seoul" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Mumbai" PrefixI False) (U1 :: Type -> Type)))) :+: (((C1 (MetaCons "Singapore" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Sydney" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "SaoPaulo" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ireland" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "London" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Frankfurt" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "GovCloud" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "GovCloudFIPS" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Beijing" PrefixI False) (U1 :: Type -> Type)))))) |
An integral value representing seconds.
Instances
Bounded Seconds | |
Enum Seconds | |
Eq Seconds | |
Integral Seconds | |
Defined in Network.AWS.Types | |
Data Seconds | |
Defined in Network.AWS.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Seconds -> c Seconds # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Seconds # toConstr :: Seconds -> Constr # dataTypeOf :: Seconds -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Seconds) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Seconds) # gmapT :: (forall b. Data b => b -> b) -> Seconds -> Seconds # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Seconds -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Seconds -> r # gmapQ :: (forall d. Data d => d -> u) -> Seconds -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Seconds -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Seconds -> m Seconds # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Seconds -> m Seconds # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Seconds -> m Seconds # | |
Num Seconds | |
Ord Seconds | |
Read Seconds | |
Real Seconds | |
Defined in Network.AWS.Types toRational :: Seconds -> Rational # | |
Show Seconds | |
Generic Seconds | |
Hashable Seconds | |
Defined in Network.AWS.Types | |
ToLog Seconds | |
Defined in Network.AWS.Types | |
ToQuery Seconds | |
Defined in Network.AWS.Types toQuery :: Seconds -> QueryString # | |
ToByteString Seconds | |
Defined in Network.AWS.Types toBS :: Seconds -> ByteString # | |
FromText Seconds | |
Defined in Network.AWS.Types | |
ToText Seconds | |
Defined in Network.AWS.Types | |
NFData Seconds | |
Defined in Network.AWS.Types | |
type Rep Seconds | |
Defined in Network.AWS.Types |
data HttpException #
An exception which may be generated by this library
Since: http-client-0.5.0
Instances
Show HttpException | |
Defined in Network.HTTP.Client.Types showsPrec :: Int -> HttpException -> ShowS # show :: HttpException -> String # showList :: [HttpException] -> ShowS # | |
ToLog HttpException | |
Defined in Network.AWS.Data.Log build :: HttpException -> Builder # | |
Exception HttpException | |
Defined in Network.HTTP.Client.Types |
class AWSRequest a => AWSPager a #
Specify how an AWSRequest
and it's associated Rs
response can
generate a subsequent request, if available.
Invariant: only services that support _both_ standard and
chunked signing expose RqBody
as a parameter.
Instances
Show RqBody | |
IsString RqBody | |
Defined in Network.AWS.Data.Body fromString :: String -> RqBody # | |
ToBody RqBody | |
Defined in Network.AWS.Data.Body |
data HashedBody #
An opaque request body containing a SHA256
hash.
Instances
Show HashedBody | |
Defined in Network.AWS.Data.Body showsPrec :: Int -> HashedBody -> ShowS # show :: HashedBody -> String # showList :: [HashedBody] -> ShowS # | |
IsString HashedBody | |
Defined in Network.AWS.Data.Body fromString :: String -> HashedBody # | |
ToHashedBody HashedBody | |
Defined in Network.AWS.Data.Body toHashed :: HashedBody -> HashedBody # | |
ToBody HashedBody | |
Defined in Network.AWS.Data.Body toBody :: HashedBody -> RqBody # |
data ChunkedBody #
An opaque request body which will be transmitted via
Transfer-Encoding: chunked
.
Invariant: Only services that support chunked encoding can
accept a ChunkedBody
. (Currently S3.) This is enforced by the type
signatures emitted by the generator.
Instances
Show ChunkedBody | |
Defined in Network.AWS.Data.Body showsPrec :: Int -> ChunkedBody -> ShowS # show :: ChunkedBody -> String # showList :: [ChunkedBody] -> ShowS # | |
ToBody ChunkedBody | |
Defined in Network.AWS.Data.Body toBody :: ChunkedBody -> RqBody # |