amazonka-1.3.5.1: Comprehensive Amazon Web Services SDK.

Copyright(c) 2013-2015 Brendan Hay
LicenseMozilla Public License, v. 2.0.
MaintainerBrendan Hay <brendan.g.hay@gmail.com>
Stabilityprovisional
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Network.AWS

Contents

Description

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

Usage

The key functions dealing with the request/response lifecycle are:

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 determine 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
    -- To specify configuration preferences, newEnv is used to create a new Env. The Region denotes the AWS region requests will be performed against,
    -- and Credentials is used to specify the desired mechanism for supplying or retrieving AuthN/AuthZ information.
    -- In this case, Discover will cause the library to try a number of options such as default environment variables, or an instance's IAM Profile:
    e <- newEnv Frankfurt Discover

    -- A new Logger to replace the default noop logger is created, with the logger set to print debug information and errors to stdout:
    l <- newLogger Debug stdout

    -- The payload (and hash) for the S3 object is retrieved from a FilePath:
    b <- sourceFileIO "local/path/to/object-payload"

    -- We now run the AWS computation with the overriden logger, performing the PutObject request:
    runResourceT . runAWS (e & envLogger .~ l) $
        send (putObject "bucket-name" "object-key" b)

Running AWS Actions

type AWS = AWST (ResourceT IO) Source

A specialisation of the AWST transformer.

class (Functor m, Applicative m, Monad m, MonadIO m, MonadCatch m) => MonadAWS m where Source

Monads in which AWS actions may be embedded.

Methods

liftAWS :: AWS a -> m a Source

Lift a computation to the AWS monad.

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 Error, which will include HTTPExceptions, serialisation errors, or any particular errors returned by the respective AWS service.

See: runAWST, runResourceT.

runResourceT :: MonadBaseControl IO 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.

Since 0.3.0

Authentication and Environment

newEnv Source

Arguments

:: (Applicative m, MonadIO m, MonadCatch m) 
=> Region

Initial region to operate in.

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

Throws AuthError when environment variables or IAM profiles cannot be read.

See: newEnvWith.

data Env Source

The environment containing the parameters required to make AWS requests.

class HasEnv a where Source

Minimal complete definition

environment

Methods

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

Credential Discovery

data Credentials Source

Determines how AuthN/AuthZ information is retrieved.

Constructors

FromKeys AccessKey SecretKey

Explicit access and secret keys. See fromKeys.

FromSession AccessKey SecretKey SessionToken

Explicit access key, secret key and a session token. See fromSession.

FromEnv Text Text (Maybe Text)

Lookup specific environment variables for access key, secret key, and an optional session token 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.

Discover

Attempt credentials discovery via the following steps:

  • Read the envAccessKey and envSecretKey from the environment if they are set.
  • Read the credentials file if credFile exists.
  • Retrieve the first available IAM profile if running on EC2.

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.

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

data Region :: *

The sum of available AWS regions.

Constructors

Ireland

Europe / eu-west-1

Frankfurt

Europe / eu-central-1

Tokyo

Asia Pacific / ap-northeast-1

Singapore

Asia Pacific / ap-southeast-1

Sydney

Asia Pacific / ap-southeast-2

Beijing

China / cn-north-1

NorthVirginia

US / us-east-1

NorthCalifornia

US / us-west-1

Oregon

US / us-west-2

GovCloud

AWS GovCloud / us-gov-west-1

GovCloudFIPS

AWS GovCloud (FIPS 140-2) S3 Only / fips-us-gov-west-1

SaoPaulo

South America / sa-east-1

Instances

Eq Region 
Data Region 
Ord Region 
Read Region 
Show Region 
Generic Region 
Hashable Region 
ToLog Region 
FromXML Region 
ToXML Region 
ToByteString Region 
FromText Region 
ToText Region 
type Rep Region = D1 D1Region ((:+:) ((:+:) ((:+:) (C1 C1_0Region U1) ((:+:) (C1 C1_1Region U1) (C1 C1_2Region U1))) ((:+:) (C1 C1_3Region U1) ((:+:) (C1 C1_4Region U1) (C1 C1_5Region U1)))) ((:+:) ((:+:) (C1 C1_6Region U1) ((:+:) (C1 C1_7Region U1) (C1 C1_8Region U1))) ((:+:) (C1 C1_9Region U1) ((:+:) (C1 C1_10Region U1) (C1 C1_11Region U1))))) 

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 -> Source m (Rs a) 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 () 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.

within :: MonadAWS m => Region -> AWS a -> m a Source

Scope an action within the specific Region.

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

hashedFile :: MonadIO m => FilePath -> m HashedBody Source

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.

hashedBody :: Digest SHA256 -> Integer -> Source (ResourceT IO) ByteString -> HashedBody Source

Construct a HashedBody from a source, manually specifying the SHA256 hash and file size.

See: ToHashedBody.

Chunked Request Bodies

class ToBody a where

Anything that can be converted to a streaming request Body.

Minimal complete definition

Nothing

Methods

toBody :: a -> RqBody

Convert a value to a request body.

newtype ChunkSize :: *

Specifies the transmitted size of the 'Transfer-Encoding' chunks.

See: defaultChunk.

Constructors

ChunkSize Int 

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

Something something.

Will intelligently revert to HashedBody if the file is smaller than the specified ChunkSize.

Add note about how it selects chunk size.

See: ToBody.

unsafeChunkedBody :: ChunkSize -> Integer -> Source (ResourceT IO) ByteString -> RqBody Source

Something something.

Marked as 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 :: MonadResource m => RsBody -> Sink ByteString m 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.

sinkMD5 :: Monad m => Consumer ByteString m (Digest MD5) Source

Incrementally calculate a MD5 Digest.

sinkSHA256 :: Monad m => Consumer ByteString m (Digest SHA256) Source

Incrementally calculate a SHA256 Digest.

Presigning Requests

Presigning requires the Service signer to be an instance of AWSPresigner. Not all signing algorithms support this.

presignURL Source

Arguments

:: (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.

dynamic :: MonadAWS m => Dynamic -> m ByteString Source

Retrieve the specified Dynamic data.

metadata :: MonadAWS m => Metadata -> m ByteString Source

Retrieve the specified Metadata.

userdata :: MonadAWS m => m (Maybe ByteString) Source

Retrieve the user data. Returns Nothing if no user data is assigned to the instance.

data Dynamic Source

Constructors

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.

PKCS7

Used to verify the document's authenticity and content against the signature.

Signature 

data Metadata Source

Constructors

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

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

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

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

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

See: Control.Concurrent.Async.Lifted

Handling Errors

Errors are thrown by the library using MonadThrow (unless Control.Monad.Error.AWS is used). Sub-errors of the canonical Error type can be caught using trying or catching and the appropriate AsError Prism:

trying _Error          (send $ ListObjects "bucket-name") :: Either Error          ListObjectsResponse
trying _TransportError (send $ ListObjects "bucket-name") :: Either HttpException  ListObjectsResponse
trying _SerializeError (send $ ListObjects "bucket-name") :: Either SerializeError ListObjectsResponse
trying _ServiceError   (send $ ListObjects "bucket-name") :: Either ServiceError   ListObjectsResponse

Many of the individual amazonka-* libraries export compatible Getters for matching service specific error codes and messages in the style above. See the Error Matchers heading in each respective library for details.

class AsError a where

Minimal complete definition

_Error

Methods

_Error :: Prism' a Error

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.

class AsAuthError a where Source

Minimal complete definition

_AuthError

Methods

_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

An error occured looking up a named environment variable.

_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.

trying :: MonadCatch m => Getting (First a) SomeException a -> m r -> m (Either a r)

A variant of try that takes a Prism (or any Fold) 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 => Getter     SomeException a -> m r -> m (Either a r)
trying :: MonadCatch m => Fold       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 Prism (or any Fold, really).

>>> catching _AssertionFailed (assert False (return "uncaught")) $ \ _ -> return "caught"
"caught"
catching :: MonadCatch m => Prism' SomeException a     -> m r -> (a -> m r) -> m r
catching :: MonadCatch m => Lens' SomeException a      -> m r -> (a -> m r) -> m r
catching :: MonadCatch m => Traversal' SomeException a -> m r -> (a -> m r) -> m r
catching :: MonadCatch m => Iso' SomeException a       -> m r -> (a -> m r) -> m r
catching :: MonadCatch m => Getter SomeException a     -> m r -> (a -> m r) -> m r
catching :: MonadCatch m => Fold SomeException a       -> m r -> (a -> m r) -> m r

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.

data LogLevel :: *

Constructors

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.

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

setEndpoint

Arguments

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

data RqBody :: *

Invariant: only services that support _both_ standard and chunked signing expose RqBody as a parameter.

data HashedBody :: *

An opaque request body containing a SHA256 hash.

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.

data RsBody :: *

A streaming, exception safe response body.

Instances