amazonka-2.0: Comprehensive Amazon Web Services SDK.
Copyright(c) 2013-2023 Brendan Hay
LicenseMozilla Public License, v. 2.0.
MaintainerBrendan Hay <brendan.g.hay+amazonka@gmail.com>
Stabilityprovisional
Portabilitynon-portable (GHC extensions)
Safe HaskellSafe-Inferred
LanguageHaskell2010

Amazonka

Description

This module provides simple Env and IO-based operations which can be performed against remote Amazon Web Services APIs, for use with the types supplied by the various amazonka-* libraries.

Synopsis

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:

{-# LANGUAGE OverloadedStrings #-}

import qualified Amazonka as AWS
import qualified Amazonka.S3 as S3
import qualified System.IO as IO

example :: IO S3.PutObjectResponse
example = do
    -- A new Logger to replace the default noop logger is created, with the logger
    -- set to print debug information and errors to stdout:
    logger <- AWS.newLogger AWS.Debug IO.stdout

    -- To specify configuration preferences, newEnv is used to create a new
    -- configuration environment. The argument to newEnv is used to specify the
    -- 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 and identity document:
    discoveredEnv <- AWS.newEnv AWS.discover

    let env =
            discoveredEnv
                { AWS.logger = logger
                , AWS.region = AWS.Frankfurt
                }

    -- The payload (and hash) for the S3 object is retrieved from a FilePath,
    -- either hashedFile or chunkedFile can be used, with the latter ensuring
    -- the contents of the file is enumerated exactly once, during send:
    body <- AWS.chunkedFile AWS.defaultChunkSize "local/path/to/object-payload"

    -- We now run the AWS computation with the overriden logger, performing the
    -- PutObject request.
    AWS.runResourceT $
        AWS.send env (S3.newPutObject "bucket-name" "object-key" body)

Authentication and Environment

type Env = Env' Identity Source #

An environment with auth credentials. Most AWS requests need one of these, and you can create one with newEnv.

type EnvNoAuth = Env' Proxy Source #

An environment with no auth credentials. Used for certain requests which need to be unsigned, like sts:AssumeRoleWithWebIdentity, and you can create one with newEnvNoAuth if you need it.

data Env' withAuth Source #

The environment containing the parameters required to make AWS requests.

This type tracks whether or not we have credentials at the type level, to avoid "presigning" requests when we lack auth information.

Constructors

Env 

Instances

Instances details
Generic (Env' withAuth) Source # 
Instance details

Defined in Amazonka.Env

Associated Types

type Rep (Env' withAuth) :: Type -> Type #

Methods

from :: Env' withAuth -> Rep (Env' withAuth) x #

to :: Rep (Env' withAuth) x -> Env' withAuth #

type Rep (Env' withAuth) Source # 
Instance details

Defined in Amazonka.Env

newEnv Source #

Arguments

:: MonadIO m 
=> (EnvNoAuth -> m Env)

Credential discovery mechanism, often discover.

-> m Env 

Creates a new environment with a new Manager without debug logging and uses the provided function to expand/discover credentials. Record updates or lenses 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 updating its $sel:region:Env field.

Since: 1.3.6 - The default logic for retrying HttpExceptions 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's $sel:retryCheck:Env field to (\_ _ -> False).

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

See: newEnvFromManager.

newEnvFromManager Source #

Arguments

:: MonadIO m 
=> Manager 
-> (EnvNoAuth -> m Env)

Credential discovery mechanism.

-> m Env 

Creates a new environment, but with an existing Manager.

newEnvNoAuth :: MonadIO m => m EnvNoAuth Source #

Generate an environment without credentials, which may only make unsigned requests. Sets the region based on the AWS_REGION environment variable, or NorthVirginia if unset.

This lets us support calls like the sts:AssumeRoleWithWebIdentity operation, which needs to make an unsigned request to pass the token from an identity provider.

newEnvNoAuthFromManager :: MonadIO m => Manager -> m EnvNoAuth Source #

Generate an environment without credentials, passing in an explicit Manager.

authMaybe :: Foldable withAuth => Env' withAuth -> Maybe Auth Source #

Get "the" Auth from an Env', if we can.

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 defaultService configuration when sending PutItem, Query and all other operations.

You can modify a specific Service's default configuration by using configureService. To modify all configurations simultaneously, see overrideService.

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:

import qualified Amazonka as AWS
import qualified Amazonka.DynamoDB as DynamoDB

let dynamo :: AWS.Service
    dynamo = AWS.setEndpoint False "localhost" 8000 DynamoDB.defaultService

The updated configuration is then passed to the Env during setup:

env <- AWS.configureService dynamo <$> AWS.newEnv AWS.discover

AWS.runResourceT $ do
    -- This S3 operation will communicate with remote AWS APIs.
    x <- AWS.send env newListBuckets

    -- DynamoDB operations will communicate with localhost:8000.
    y <- AWS.send env Dynamo.newListTables

    -- Any operations for services other than DynamoDB, are not affected.
    ...

You can also scope the service configuration modifications to specific actions:

env <- AWS.newEnv AWS.discover

AWS.runResourceT $ do
    -- Service operations here will communicate with AWS, even remote DynamoDB.
    x <- AWS.send env Dynamo.newListTables

    -- Here DynamoDB operations will communicate with localhost:8000.
    y <- AWS.send (AWS.configure dynamo env) Dynamo.newListTables

Functions such as once and globalTimeout can also be used to modify service configuration for all (or specific) requests.

overrideService :: (Service -> Service) -> Env' withAuth -> Env' withAuth Source #

Provide a function which will be added to the existing stack of overrides applied to all service configurations.

configureService :: Service -> Env' withAuth -> Env' withAuth Source #

Configure a specific service. All requests belonging to the supplied service will use this configuration instead of the default.

It's suggested you modify the default service configuration, such as Amazonka.DynamoDB.defaultService.

globalTimeout :: Seconds -> Env' withAuth -> Env' withAuth Source #

Override the timeout value for this Env.

Default timeouts are chosen by considering:

  • This timeout, if set.
  • The related Service timeout for the sent request if set. (Usually 70s)
  • The $sel:manager:Env timeout if set.
  • The default ClientRequest timeout. (Approximately 30s)

once :: Env' withAuth -> Env' withAuth Source #

Disable any retry logic for an Env, so that any requests will at most be sent once.

Running AWS Actions

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

Credential Discovery

AuthN/AuthZ information is handled similarly to other AWS SDKs. You can read some of the options available here.

discover should be your default way of requesting credentials, as it searches the standard places that the official AWS SDKs use.

Authentication methods which return short-lived credentials (e.g., when running on an EC2 instance) fork a background thread which transparently handles the expiry and subsequent refresh of IAM profile information. See fetchAuthInBackground for more information.

See: Amazonka.Auth, if you want to commit to specific authentication methods.

See: runCredentialChain if you want to build your own credential chain.

newtype AccessKey #

An access key ID.

For example: AKIAIOSFODNN7EXAMPLE

See: Understanding and Getting Your Security Credentials.

Constructors

AccessKey ByteString 

Instances

Instances details
FromJSON AccessKey 
Instance details

Defined in Amazonka.Types

ToJSON AccessKey 
Instance details

Defined in Amazonka.Types

ToByteString AccessKey 
Instance details

Defined in Amazonka.Types

Methods

toBS :: AccessKey -> ByteString #

ToLog AccessKey 
Instance details

Defined in Amazonka.Types

ToQuery AccessKey 
Instance details

Defined in Amazonka.Types

FromText AccessKey 
Instance details

Defined in Amazonka.Types

ToText AccessKey 
Instance details

Defined in Amazonka.Types

Methods

toText :: AccessKey -> Text #

FromXML AccessKey 
Instance details

Defined in Amazonka.Types

ToXML AccessKey 
Instance details

Defined in Amazonka.Types

Methods

toXML :: AccessKey -> XML #

IsString AccessKey 
Instance details

Defined in Amazonka.Types

Generic AccessKey 
Instance details

Defined in Amazonka.Types

Associated Types

type Rep AccessKey :: Type -> Type #

Read AccessKey 
Instance details

Defined in Amazonka.Types

Show AccessKey 
Instance details

Defined in Amazonka.Types

NFData AccessKey 
Instance details

Defined in Amazonka.Types

Methods

rnf :: AccessKey -> () #

Eq AccessKey 
Instance details

Defined in Amazonka.Types

Hashable AccessKey 
Instance details

Defined in Amazonka.Types

type Rep AccessKey 
Instance details

Defined in Amazonka.Types

type Rep AccessKey = D1 ('MetaData "AccessKey" "Amazonka.Types" "amazonka-core-2.0-BFuA7FRvuklLoYhn4b6A6p" 'True) (C1 ('MetaCons "AccessKey" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

newtype SecretKey #

Secret access key credential.

For example: wJalrXUtnFEMIK7MDENGbPxRfiCYEXAMPLEKE

See: Understanding and Getting Your Security Credentials.

Constructors

SecretKey ByteString 

Instances

Instances details
FromJSON SecretKey 
Instance details

Defined in Amazonka.Types

ToJSON SecretKey 
Instance details

Defined in Amazonka.Types

ToByteString SecretKey 
Instance details

Defined in Amazonka.Types

Methods

toBS :: SecretKey -> ByteString #

FromText SecretKey 
Instance details

Defined in Amazonka.Types

ToText SecretKey 
Instance details

Defined in Amazonka.Types

Methods

toText :: SecretKey -> Text #

FromXML SecretKey 
Instance details

Defined in Amazonka.Types

ToXML SecretKey 
Instance details

Defined in Amazonka.Types

Methods

toXML :: SecretKey -> XML #

IsString SecretKey 
Instance details

Defined in Amazonka.Types

Generic SecretKey 
Instance details

Defined in Amazonka.Types

Associated Types

type Rep SecretKey :: Type -> Type #

NFData SecretKey 
Instance details

Defined in Amazonka.Types

Methods

rnf :: SecretKey -> () #

Eq SecretKey 
Instance details

Defined in Amazonka.Types

Hashable SecretKey 
Instance details

Defined in Amazonka.Types

type Rep SecretKey 
Instance details

Defined in Amazonka.Types

type Rep SecretKey = D1 ('MetaData "SecretKey" "Amazonka.Types" "amazonka-core-2.0-BFuA7FRvuklLoYhn4b6A6p" 'True) (C1 ('MetaCons "SecretKey" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

newtype SessionToken #

A session token used by STS to temporarily authorise access to an AWS resource.

See: Temporary Security Credentials.

Constructors

SessionToken ByteString 

Instances

Instances details
FromJSON SessionToken 
Instance details

Defined in Amazonka.Types

ToJSON SessionToken 
Instance details

Defined in Amazonka.Types

ToByteString SessionToken 
Instance details

Defined in Amazonka.Types

FromText SessionToken 
Instance details

Defined in Amazonka.Types

ToText SessionToken 
Instance details

Defined in Amazonka.Types

Methods

toText :: SessionToken -> Text #

FromXML SessionToken 
Instance details

Defined in Amazonka.Types

ToXML SessionToken 
Instance details

Defined in Amazonka.Types

Methods

toXML :: SessionToken -> XML #

IsString SessionToken 
Instance details

Defined in Amazonka.Types

Generic SessionToken 
Instance details

Defined in Amazonka.Types

Associated Types

type Rep SessionToken :: Type -> Type #

NFData SessionToken 
Instance details

Defined in Amazonka.Types

Methods

rnf :: SessionToken -> () #

Eq SessionToken 
Instance details

Defined in Amazonka.Types

Hashable SessionToken 
Instance details

Defined in Amazonka.Types

type Rep SessionToken 
Instance details

Defined in Amazonka.Types

type Rep SessionToken = D1 ('MetaData "SessionToken" "Amazonka.Types" "amazonka-core-2.0-BFuA7FRvuklLoYhn4b6A6p" 'True) (C1 ('MetaCons "SessionToken" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

discover :: (MonadCatch m, MonadIO m, Foldable withAuth) => Env' withAuth -> m Env Source #

Attempt to fetch credentials in a way similar to the official AWS SDKs. The C++ SDK lists the following sequence:

  • Check environment variables for keys provided directly (AWS_ACCESS_KEY_ID, AWS_SECRET_ACCESS_KEY, optionally AWS_SESSION_TOKEN)
  • Check credentials/config files for authentication information, respecting the AWS_PROFILE environment variable.
  • Exchange a Web Identity for AWS Credentials using sts:AssumeRoleWithWebIdentity, respecting the AWS_WEB_IDENTITY_TOKEN_FILE, AWS_ROLE_ARN, and optionally the AWS_ROLE_SESSION_NAME environment variables.
  • Retrieve credentials from the ECS Container Agent if the AWS_CONTAINER_CREDENTIALS_RELATIVE_URI environment variable is set.
  • If we think we're running on EC2, retrieve the first available IAM profile from the instance identity document, and use this to set the Placement. We attempt to resolve http://instance-data rather than directly retrieving http://169.254.169.254 for IAM profile information. This ensures that the DNS lookup terminates promptly if not running on EC2, but means that your VPC must have enableDnsSupport and enableDnsHostnames set.

    NOTE: This is not 100% consistent with the AWS SDKs, which does not attempt to query the ECS service if either AWS_CONTAINER_CREDENTIALS_RELATIVE_URI or AWS_CONTAINER_CREDENTIALS_FULL_URI are set.

    See: https://docs.aws.amazon.com/AWSJavaSDK/latest/javadoc/com/amazonaws/auth/EC2ContainerCredentialsProviderWrapper.html

Supported Regions

newtype Region #

The available AWS regions.

Constructors

Region' 

Fields

Bundled Patterns

pattern Ningxia :: Region 
pattern Beijing :: Region 
pattern GovCloudWest :: Region 
pattern GovCloudEast :: Region 
pattern SaoPaulo :: Region 
pattern UAE :: Region 
pattern Bahrain :: Region 
pattern Zurich :: Region 
pattern Stockholm :: Region 
pattern Spain :: Region 
pattern Paris :: Region 
pattern Milan :: Region 
pattern London :: Region 
pattern Ireland :: Region 
pattern Frankfurt :: Region 
pattern Montreal :: Region 
pattern Tokyo :: Region 
pattern Sydney :: Region 
pattern Singapore :: Region 
pattern Seoul :: Region 
pattern Osaka :: Region 
pattern Mumbai :: Region 
pattern Melbourne :: Region 
pattern Jakarta :: Region 
pattern Hyderabad :: Region 
pattern HongKong :: Region 
pattern CapeTown :: Region 
pattern Oregon :: Region 
pattern NorthCalifornia :: Region 
pattern NorthVirginia :: Region 
pattern Ohio :: Region 

Instances

Instances details
FromJSON Region 
Instance details

Defined in Amazonka.Types

ToJSON Region 
Instance details

Defined in Amazonka.Types

ToByteString Region 
Instance details

Defined in Amazonka.Types

Methods

toBS :: Region -> ByteString #

ToLog Region 
Instance details

Defined in Amazonka.Types

ToQuery Region 
Instance details

Defined in Amazonka.Types

FromText Region 
Instance details

Defined in Amazonka.Types

ToText Region 
Instance details

Defined in Amazonka.Types

Methods

toText :: Region -> Text #

FromXML Region 
Instance details

Defined in Amazonka.Types

ToXML Region 
Instance details

Defined in Amazonka.Types

Methods

toXML :: Region -> XML #

IsString Region 
Instance details

Defined in Amazonka.Types

Methods

fromString :: String -> Region #

Generic Region 
Instance details

Defined in Amazonka.Types

Associated Types

type Rep Region :: Type -> Type #

Methods

from :: Region -> Rep Region x #

to :: Rep Region x -> Region #

Read Region 
Instance details

Defined in Amazonka.Types

Show Region 
Instance details

Defined in Amazonka.Types

NFData Region 
Instance details

Defined in Amazonka.Types

Methods

rnf :: Region -> () #

Eq Region 
Instance details

Defined in Amazonka.Types

Methods

(==) :: Region -> Region -> Bool #

(/=) :: Region -> Region -> Bool #

Ord Region 
Instance details

Defined in Amazonka.Types

Hashable Region 
Instance details

Defined in Amazonka.Types

Methods

hashWithSalt :: Int -> Region -> Int #

hash :: Region -> Int #

type Rep Region 
Instance details

Defined in Amazonka.Types

type Rep Region = D1 ('MetaData "Region" "Amazonka.Types" "amazonka-core-2.0-BFuA7FRvuklLoYhn4b6A6p" 'True) (C1 ('MetaCons "Region'" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromRegion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

Service Endpoints

data Endpoint #

Constructors

Endpoint 

Fields

  • host :: ByteString

    The host to make requests to. Usually something like s3.us-east-1.amazonaws.com.

  • basePath :: RawPath

    Path segment prepended to the request path of any request made to this endpoint. This is useful if you want to use the AWS API Gateway Management API, which requires you to override the client endpoint including a leading path segment (either the stage or, on a custom domain, the mapped base path).

  • secure :: Bool
     
  • port :: Int
     
  • scope :: ByteString

    Signing scope, usually a region like us-east-1.

Instances

Instances details
Generic Endpoint 
Instance details

Defined in Amazonka.Types

Associated Types

type Rep Endpoint :: Type -> Type #

Methods

from :: Endpoint -> Rep Endpoint x #

to :: Rep Endpoint x -> Endpoint #

Show Endpoint 
Instance details

Defined in Amazonka.Types

Eq Endpoint 
Instance details

Defined in Amazonka.Types

type Rep Endpoint 
Instance details

Defined in Amazonka.Types

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: $sel:endpoint:Service.

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 :: (MonadResource m, AWSRequest a, Typeable a, Typeable (AWSResponse a)) => Env -> a -> m (AWSResponse a) Source #

Send a request, returning the associated response if successful.

Errors are thrown in IO.

See sendEither.

sendEither :: (MonadResource m, AWSRequest a, Typeable a, Typeable (AWSResponse a)) => Env -> a -> m (Either Error (AWSResponse a)) Source #

Send a request, returning the associated response if successful.

See send.

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 :: (MonadResource m, AWSPager a, Typeable a, Typeable (AWSResponse a)) => Env -> a -> ConduitM () (AWSResponse a) m () Source #

Repeatedly send a request, automatically setting markers and performing pagination. Exits on the first encountered error.

Errors are thrown in IO.

See paginateEither.

paginateEither :: (MonadResource m, AWSPager a, Typeable a, Typeable (AWSResponse a)) => Env -> a -> ConduitM () (AWSResponse a) m (Either Error ()) Source #

Repeatedly send a request, automatically setting markers and performing pagination.

Exits on the first encountered error.

See paginate.

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 Amazonka.{ServiceName}.Waiters namespace for services which support await.

await :: (MonadResource m, AWSRequest a, Typeable a) => Env -> Wait a -> a -> m Accept Source #

Poll the API with the supplied request until a specific Wait condition is fulfilled.

Errors are thrown in IO.

See awaitEither.

awaitEither :: (MonadResource m, AWSRequest a, Typeable a) => Env -> Wait a -> a -> m (Either Error Accept) Source #

Poll the API with the supplied request until a specific Wait condition is fulfilled.

See await.

Unsigned

sendUnsigned :: (MonadResource m, AWSRequest a, Typeable a, Typeable (AWSResponse a)) => Env' withAuth -> a -> m (AWSResponse a) Source #

Make an unsigned request, returning the associated response if successful.

Errors are thrown in IO.

See sendUnsignedEither.

sendUnsignedEither :: (MonadResource m, AWSRequest a, Typeable a, Typeable (AWSResponse a)) => Env' withAuth -> a -> m (Either Error (AWSResponse a)) Source #

Make a request without signing it. You will almost never need to do this, but some authentication methods (e.g. sts:AssumeRoleWithWebIdentity and sso:GetRoleCredentials) require you to exchange a token using an unsigned request. Amazonka's support for these authentication methods calls sendUnsigned, and we re-export these functions in case you need to support similar authentication methods in your code.

See sendUnsigned.

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.

class ToBody a where #

Anything that can be converted to a streaming request Body.

Minimal complete definition

Nothing

Methods

toBody :: a -> RequestBody #

Convert a value to a request body.

Instances

Instances details
ToBody Value 
Instance details

Defined in Amazonka.Data.Body

Methods

toBody :: Value -> RequestBody #

ToBody Base64 
Instance details

Defined in Amazonka.Data.Base64

Methods

toBody :: Base64 -> RequestBody #

ToBody ChunkedBody 
Instance details

Defined in Amazonka.Data.Body

ToBody HashedBody 
Instance details

Defined in Amazonka.Data.Body

ToBody RequestBody 
Instance details

Defined in Amazonka.Data.Body

ToBody QueryString 
Instance details

Defined in Amazonka.Data.Body

ToBody ByteStringLazy 
Instance details

Defined in Amazonka.Data.Body

ToBody TextLazy 
Instance details

Defined in Amazonka.Data.Body

ToBody ByteString 
Instance details

Defined in Amazonka.Data.Body

ToBody Text 
Instance details

Defined in Amazonka.Data.Body

Methods

toBody :: Text -> RequestBody #

ToBody Element 
Instance details

Defined in Amazonka.Data.Body

ToBody String 
Instance details

Defined in Amazonka.Data.Body

Methods

toBody :: String -> RequestBody #

ToBody (KeyMap Value) 
Instance details

Defined in Amazonka.Data.Body

ToBody a => ToBody (Sensitive a) 
Instance details

Defined in Amazonka.Data.Sensitive

Methods

toBody :: Sensitive a -> RequestBody #

ToHashedBody a => ToBody (Maybe a) 
Instance details

Defined in Amazonka.Data.Body

Methods

toBody :: Maybe a -> RequestBody #

data RequestBody #

Invariant: only services that support both standard and chunked signing expose RequestBody as a parameter.

Constructors

Chunked ChunkedBody

Currently S3 only, see ChunkedBody for details.

Hashed HashedBody 

Instances

Instances details
ToBody RequestBody 
Instance details

Defined in Amazonka.Data.Body

IsString RequestBody 
Instance details

Defined in Amazonka.Data.Body

Show RequestBody 
Instance details

Defined in Amazonka.Data.Body

newtype ResponseBody #

A streaming, exception safe response body.

newtype for show/orhpan instance purposes.

Constructors

ResponseBody 

Fields

Instances

Instances details
Generic ResponseBody 
Instance details

Defined in Amazonka.Data.Body

Associated Types

type Rep ResponseBody :: Type -> Type #

Show ResponseBody 
Instance details

Defined in Amazonka.Data.Body

type Rep ResponseBody 
Instance details

Defined in Amazonka.Data.Body

type Rep ResponseBody = D1 ('MetaData "ResponseBody" "Amazonka.Data.Body" "amazonka-core-2.0-BFuA7FRvuklLoYhn4b6A6p" 'True) (C1 ('MetaCons "ResponseBody" 'PrefixI 'True) (S1 ('MetaSel ('Just "body") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ConduitM () ByteString (ResourceT IO) ()))))

Hashed Request Bodies

class ToHashedBody a where #

Anything that can be safely converted to a HashedBody.

Methods

toHashed :: a -> HashedBody #

Convert a value to a hashed request body.

Instances

Instances details
ToHashedBody Value 
Instance details

Defined in Amazonka.Data.Body

Methods

toHashed :: Value -> HashedBody #

ToHashedBody Base64 
Instance details

Defined in Amazonka.Data.Base64

ToHashedBody HashedBody 
Instance details

Defined in Amazonka.Data.Body

ToHashedBody QueryString 
Instance details

Defined in Amazonka.Data.Body

ToHashedBody ByteStringLazy 
Instance details

Defined in Amazonka.Data.Body

ToHashedBody TextLazy 
Instance details

Defined in Amazonka.Data.Body

ToHashedBody ByteString 
Instance details

Defined in Amazonka.Data.Body

ToHashedBody Text 
Instance details

Defined in Amazonka.Data.Body

Methods

toHashed :: Text -> HashedBody #

ToHashedBody Element 
Instance details

Defined in Amazonka.Data.Body

ToHashedBody String 
Instance details

Defined in Amazonka.Data.Body

ToHashedBody (KeyMap Value) 
Instance details

Defined in Amazonka.Data.Body

data HashedBody #

An opaque request body containing a SHA256 hash.

Instances

Instances details
ToBody HashedBody 
Instance details

Defined in Amazonka.Data.Body

ToHashedBody HashedBody 
Instance details

Defined in Amazonka.Data.Body

IsString HashedBody 
Instance details

Defined in Amazonka.Data.Body

Show HashedBody 
Instance details

Defined in Amazonka.Data.Body

hashedFile #

Arguments

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

hashedFileRange #

Arguments

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

hashedBody #

Arguments

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

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.

Constructors

ChunkedBody 

Instances

Instances details
ToBody ChunkedBody 
Instance details

Defined in Amazonka.Data.Body

Show ChunkedBody 
Instance details

Defined in Amazonka.Data.Body

newtype ChunkSize #

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

See: defaultChunk.

Constructors

ChunkSize Int 

Instances

Instances details
ToLog ChunkSize 
Instance details

Defined in Amazonka.Data.Body

Enum ChunkSize 
Instance details

Defined in Amazonka.Data.Body

Num ChunkSize 
Instance details

Defined in Amazonka.Data.Body

Integral ChunkSize 
Instance details

Defined in Amazonka.Data.Body

Real ChunkSize 
Instance details

Defined in Amazonka.Data.Body

Show ChunkSize 
Instance details

Defined in Amazonka.Data.Body

Eq ChunkSize 
Instance details

Defined in Amazonka.Data.Body

Ord ChunkSize 
Instance details

Defined in Amazonka.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 RequestBody #

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.

chunkedFileRange #

Arguments

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

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.

unsafeChunkedBody #

Arguments

:: ChunkSize

The idealized size of chunks that will be yielded downstream.

-> Integer

The size of the stream in bytes.

-> ConduitM () ByteString (ResourceT IO) () 
-> RequestBody 

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 => ResponseBody -> ConduitM ByteString Void (ResourceT IO) a -> m a #

Connect a Sink to a response stream.

File Size and MD5/SHA256

getFileSize :: MonadIO m => FilePath -> m Integer #

Convenience function for obtaining the size of a file.

sinkMD5 :: forall (m :: Type -> Type) o. Monad m => ConduitM ByteString o m (Digest MD5) #

Incrementally calculate a MD5 Digest.

sinkSHA256 :: forall (m :: Type -> Type) o. Monad m => ConduitM ByteString o m (Digest SHA256) #

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

:: (MonadIO m, AWSRequest a) 
=> Env 
-> 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.

presign Source #

Arguments

:: (MonadIO m, AWSRequest a) 
=> Env 
-> UTCTime

Signing time.

-> Seconds

Expiry time.

-> a

Request to presign.

-> m ClientRequest 

Presign an HTTP request that is valid from the specified time until the number of seconds expiry has elapsed.

Running Asynchronous Actions

Requests can be sent asynchronously, but due to guarantees about resource closure require the use of UnliftIO.Async.

The following example demonstrates retrieving two objects from S3 concurrently:

{-# LANGUAGE OverloadedStrings #-}
import qualified Amazonka as AWS
import qualified Amazonka.S3 as S3
import qualified UnliftIO.Async as Async

let requestA = S3.newGetObject "bucket" "prefix/object-a"
let requestB = S3.newGetObject "bucket" "prefix/object-b"

runResourceT $
  Async.withAsync (send env requestA) $ \asyncA ->
    Async.withAsync (send env requestB) $ \asyncB -> do
      Async.waitBoth asyncA asyncB

If you are running many async requests in parallel, using ContT can hide the giant callback pyramid:

runResourceT . evalContT $ do
  asyncA <- ContT $ Async.withAsync (send env requestA)
  asyncB <- ContT $ Async.withAsync (send env requestB)
  Async.waitBoth asyncA asyncB

Handling Errors

Errors are either returned or thrown by the library using IO. Sub-errors of the canonical LogLevel type can be caught using trying or catching and the appropriate AsError Prism when using the non-Either send variants:

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

Many of the individual amazonka-* libraries export compatible Folds 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 #

The named environment variable was not found.

_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 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 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 => ReifiedGetter SomeException a     -> m r -> (a -> m r) -> m r
catching :: MonadCatch m => ReifiedFold SomeException a       -> m r -> (a -> m r) -> m r

Building Error Prisms

_MatchServiceError :: AsError a => Service -> ErrorCode -> Fold 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 Amazonka.ServiceName.Types do not cover all the thrown error codes. For example to define a new error prism:

{-# LANGUAGE OverloadedStrings #-}

import Amazonka.S3 (ServiceError, s3)

_NoSuchBucketPolicy :: AsError a => Fold 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)

Logging

The exposed logging interface is a primitive Logger function which the hooks system calls throughout the request/response process. 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 tinylog or fast-logger.

data LogLevel Source #

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.

Instances

Instances details
ToByteString LogLevel Source # 
Instance details

Defined in Amazonka.Logger

Methods

toBS :: LogLevel -> ByteString #

FromText LogLevel Source # 
Instance details

Defined in Amazonka.Logger

ToText LogLevel Source # 
Instance details

Defined in Amazonka.Logger

Methods

toText :: LogLevel -> Text #

Enum LogLevel Source # 
Instance details

Defined in Amazonka.Logger

Generic LogLevel Source # 
Instance details

Defined in Amazonka.Logger

Associated Types

type Rep LogLevel :: Type -> Type #

Methods

from :: LogLevel -> Rep LogLevel x #

to :: Rep LogLevel x -> LogLevel #

Show LogLevel Source # 
Instance details

Defined in Amazonka.Logger

Eq LogLevel Source # 
Instance details

Defined in Amazonka.Logger

Ord LogLevel Source # 
Instance details

Defined in Amazonka.Logger

type Rep LogLevel Source # 
Instance details

Defined in Amazonka.Logger

type Rep LogLevel = D1 ('MetaData "LogLevel" "Amazonka.Logger" "amazonka-2.0-48plDWnPMAk3PGO79vdSa0" 'False) ((C1 ('MetaCons "Info" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Error" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Debug" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Trace" 'PrefixI 'False) (U1 :: Type -> Type)))

type Logger = LogLevel -> ByteStringBuilder -> IO () Source #

A logging function called by various default hooks to log informational and debug messages.

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.

Re-exported Types

data UTCTime #

This is the simplest representation of UTC. It consists of the day number, and a time offset from midnight. Note that if a day has a leap second added to it, it will have 86401 seconds.

Instances

Instances details
FromJSON UTCTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey UTCTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

ToJSON UTCTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey UTCTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToByteString UTCTime 
Instance details

Defined in Amazonka.Data.ByteString

Methods

toBS :: UTCTime -> ByteString #

ToLog UTCTime 
Instance details

Defined in Amazonka.Data.Log

Data UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UTCTime -> c UTCTime #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UTCTime #

toConstr :: UTCTime -> Constr #

dataTypeOf :: UTCTime -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UTCTime) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UTCTime) #

gmapT :: (forall b. Data b => b -> b) -> UTCTime -> UTCTime #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UTCTime -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UTCTime -> r #

gmapQ :: (forall d. Data d => d -> u) -> UTCTime -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UTCTime -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime #

NFData UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

Methods

rnf :: UTCTime -> () #

Eq UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

Methods

(==) :: UTCTime -> UTCTime -> Bool #

(/=) :: UTCTime -> UTCTime -> Bool #

Ord UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

may :: Applicative f => ([a] -> f b) -> [a] -> f (Maybe b) #

(.!@) :: Functor f => f (Maybe a) -> a -> f a infixl 7 #

matchAny :: Eq b => b -> Accept -> Fold (AWSResponse a) b -> Acceptor a #

matchAll :: Eq b => b -> Accept -> Fold (AWSResponse a) b -> Acceptor a #

accept :: Wait a -> Acceptor a #

data Accept #

Instances

Instances details
ToLog Accept 
Instance details

Defined in Amazonka.Waiter

Show Accept 
Instance details

Defined in Amazonka.Waiter

Eq Accept 
Instance details

Defined in Amazonka.Waiter

Methods

(==) :: Accept -> Accept -> Bool #

(/=) :: Accept -> Accept -> Bool #

data Wait a #

Timing and acceptance criteria to check fulfillment of a remote operation.

Constructors

Wait 

defaultEndpoint :: Service -> Region -> Endpoint #

Determine the full host address and credential scope within the specified Region.

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: $sel:endpoint:Service.

_MatchServiceError :: AsError a => Service -> ErrorCode -> Fold 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 Amazonka.ServiceName.Types do not cover all the thrown error codes. For example to define a new error prism:

{-# LANGUAGE OverloadedStrings #-}

import Amazonka.S3 (ServiceError, s3)

_NoSuchBucketPolicy :: AsError a => Fold 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)

choice :: (Alternative f, ToText a, ToText b) => (s -> f a) -> (s -> f b) -> Getter s (f Text) #

stop :: AWSTruncated a => a -> Bool #

class AWSRequest a => AWSPager a where #

Specify how an AWSRequest and it's associated Rs response can generate a subsequent request, if available.

Methods

page :: a -> AWSResponse a -> Maybe a #

class AWSTruncated a where #

Generalise IsTruncated and other optional/required response pagination fields.

Methods

truncated :: a -> Bool #

Instances

Instances details
AWSTruncated Bool 
Instance details

Defined in Amazonka.Pager

Methods

truncated :: Bool -> Bool #

AWSTruncated (Maybe Bool) 
Instance details

Defined in Amazonka.Pager

Methods

truncated :: Maybe Bool -> Bool #

AWSTruncated (Maybe a) 
Instance details

Defined in Amazonka.Pager

Methods

truncated :: Maybe a -> Bool #

AWSTruncated [a] 
Instance details

Defined in Amazonka.Pager

Methods

truncated :: [a] -> Bool #

AWSTruncated (HashMap k v) 
Instance details

Defined in Amazonka.Pager

Methods

truncated :: HashMap k v -> Bool #

withAuth :: MonadIO m => Auth -> (AuthEnv -> m a) -> m a #

requestUnsigned :: Request a -> Region -> ClientRequest #

Create an unsigned ClientRequest. You will almost never need to do this.

newClientRequest :: Endpoint -> Maybe Seconds -> ClientRequest #

Construct a ClientRequest using common parameters such as TLS and prevent throwing errors when receiving erroneous status codes in respones.

type ClientRequest = Request #

A convenience alias to avoid type ambiguity.

type ClientResponse = Response #

A convenience alias encapsulating the common Response.

type ClientBody = ConduitM () ByteString (ResourceT IO) () #

A convenience alias encapsulating the common Response body.

data Abbrev #

Abbreviated service name.

Instances

Instances details
FromJSON Abbrev 
Instance details

Defined in Amazonka.Types

ToLog Abbrev 
Instance details

Defined in Amazonka.Types

FromText Abbrev 
Instance details

Defined in Amazonka.Types

ToText Abbrev 
Instance details

Defined in Amazonka.Types

Methods

toText :: Abbrev -> Text #

FromXML Abbrev 
Instance details

Defined in Amazonka.Types

IsString Abbrev 
Instance details

Defined in Amazonka.Types

Methods

fromString :: String -> Abbrev #

Generic Abbrev 
Instance details

Defined in Amazonka.Types

Associated Types

type Rep Abbrev :: Type -> Type #

Methods

from :: Abbrev -> Rep Abbrev x #

to :: Rep Abbrev x -> Abbrev #

Show Abbrev 
Instance details

Defined in Amazonka.Types

Eq Abbrev 
Instance details

Defined in Amazonka.Types

Methods

(==) :: Abbrev -> Abbrev -> Bool #

(/=) :: Abbrev -> Abbrev -> Bool #

Ord Abbrev 
Instance details

Defined in Amazonka.Types

type Rep Abbrev 
Instance details

Defined in Amazonka.Types

type Rep Abbrev = D1 ('MetaData "Abbrev" "Amazonka.Types" "amazonka-core-2.0-BFuA7FRvuklLoYhn4b6A6p" 'True) (C1 ('MetaCons "Abbrev" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromAbbrev") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype ErrorCode #

Constructors

ErrorCode Text 

Instances

Instances details
FromJSON ErrorCode 
Instance details

Defined in Amazonka.Types

ToLog ErrorCode 
Instance details

Defined in Amazonka.Types

FromText ErrorCode 
Instance details

Defined in Amazonka.Types

ToText ErrorCode 
Instance details

Defined in Amazonka.Types

Methods

toText :: ErrorCode -> Text #

FromXML ErrorCode 
Instance details

Defined in Amazonka.Types

IsString ErrorCode 
Instance details

Defined in Amazonka.Types

Show ErrorCode 
Instance details

Defined in Amazonka.Types

Eq ErrorCode 
Instance details

Defined in Amazonka.Types

Ord ErrorCode 
Instance details

Defined in Amazonka.Types

newtype ErrorMessage #

Constructors

ErrorMessage 

Instances

Instances details
FromJSON ErrorMessage 
Instance details

Defined in Amazonka.Types

ToLog ErrorMessage 
Instance details

Defined in Amazonka.Types

FromText ErrorMessage 
Instance details

Defined in Amazonka.Types

ToText ErrorMessage 
Instance details

Defined in Amazonka.Types

Methods

toText :: ErrorMessage -> Text #

FromXML ErrorMessage 
Instance details

Defined in Amazonka.Types

IsString ErrorMessage 
Instance details

Defined in Amazonka.Types

Generic ErrorMessage 
Instance details

Defined in Amazonka.Types

Associated Types

type Rep ErrorMessage :: Type -> Type #

Show ErrorMessage 
Instance details

Defined in Amazonka.Types

Eq ErrorMessage 
Instance details

Defined in Amazonka.Types

Ord ErrorMessage 
Instance details

Defined in Amazonka.Types

type Rep ErrorMessage 
Instance details

Defined in Amazonka.Types

type Rep ErrorMessage = D1 ('MetaData "ErrorMessage" "Amazonka.Types" "amazonka-core-2.0-BFuA7FRvuklLoYhn4b6A6p" 'True) (C1 ('MetaCons "ErrorMessage" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromErrorMessage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype RequestId #

Constructors

RequestId 

Fields

Instances

Instances details
FromJSON RequestId 
Instance details

Defined in Amazonka.Types

ToLog RequestId 
Instance details

Defined in Amazonka.Types

FromText RequestId 
Instance details

Defined in Amazonka.Types

ToText RequestId 
Instance details

Defined in Amazonka.Types

Methods

toText :: RequestId -> Text #

FromXML RequestId 
Instance details

Defined in Amazonka.Types

IsString RequestId 
Instance details

Defined in Amazonka.Types

Generic RequestId 
Instance details

Defined in Amazonka.Types

Associated Types

type Rep RequestId :: Type -> Type #

Show RequestId 
Instance details

Defined in Amazonka.Types

Eq RequestId 
Instance details

Defined in Amazonka.Types

Ord RequestId 
Instance details

Defined in Amazonka.Types

type Rep RequestId 
Instance details

Defined in Amazonka.Types

type Rep RequestId = D1 ('MetaData "RequestId" "Amazonka.Types" "amazonka-core-2.0-BFuA7FRvuklLoYhn4b6A6p" 'True) (C1 ('MetaCons "RequestId" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromRequestId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data Error #

An error type representing errors that can be attributed to this library.

Instances

Instances details
ToLog Error 
Instance details

Defined in Amazonka.Types

AsError Error 
Instance details

Defined in Amazonka.Types

Exception Error 
Instance details

Defined in Amazonka.Types

Generic Error 
Instance details

Defined in Amazonka.Types

Associated Types

type Rep Error :: Type -> Type #

Methods

from :: Error -> Rep Error x #

to :: Rep Error x -> Error #

Show Error 
Instance details

Defined in Amazonka.Types

Methods

showsPrec :: Int -> Error -> ShowS #

show :: Error -> String #

showList :: [Error] -> ShowS #

type Rep Error 
Instance details

Defined in Amazonka.Types

data SerializeError #

Constructors

SerializeError' 

Fields

Instances

Instances details
ToLog SerializeError 
Instance details

Defined in Amazonka.Types

Generic SerializeError 
Instance details

Defined in Amazonka.Types

Associated Types

type Rep SerializeError :: Type -> Type #

Show SerializeError 
Instance details

Defined in Amazonka.Types

Eq SerializeError 
Instance details

Defined in Amazonka.Types

type Rep SerializeError 
Instance details

Defined in Amazonka.Types

data ServiceError #

Instances

Instances details
ToLog ServiceError 
Instance details

Defined in Amazonka.Types

Generic ServiceError 
Instance details

Defined in Amazonka.Types

Associated Types

type Rep ServiceError :: Type -> Type #

Show ServiceError 
Instance details

Defined in Amazonka.Types

Eq ServiceError 
Instance details

Defined in Amazonka.Types

type Rep ServiceError 
Instance details

Defined in Amazonka.Types

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.

data Endpoint #

Constructors

Endpoint 

Fields

  • host :: ByteString

    The host to make requests to. Usually something like s3.us-east-1.amazonaws.com.

  • basePath :: RawPath

    Path segment prepended to the request path of any request made to this endpoint. This is useful if you want to use the AWS API Gateway Management API, which requires you to override the client endpoint including a leading path segment (either the stage or, on a custom domain, the mapped base path).

  • secure :: Bool
     
  • port :: Int
     
  • scope :: ByteString

    Signing scope, usually a region like us-east-1.

Instances

Instances details
Generic Endpoint 
Instance details

Defined in Amazonka.Types

Associated Types

type Rep Endpoint :: Type -> Type #

Methods

from :: Endpoint -> Rep Endpoint x #

to :: Rep Endpoint x -> Endpoint #

Show Endpoint 
Instance details

Defined in Amazonka.Types

Eq Endpoint 
Instance details

Defined in Amazonka.Types

type Rep Endpoint 
Instance details

Defined in Amazonka.Types

data Retry #

Constants and predicates used to create a RetryPolicy.

Constructors

Exponential 

Fields

Instances

Instances details
Generic Retry 
Instance details

Defined in Amazonka.Types

Associated Types

type Rep Retry :: Type -> Type #

Methods

from :: Retry -> Rep Retry x #

to :: Rep Retry x -> Retry #

type Rep Retry 
Instance details

Defined in Amazonka.Types

data Meta where #

Signing algorithm specific metadata.

Constructors

Meta :: forall a. ToLog a => a -> Meta 

Instances

Instances details
ToLog Meta 
Instance details

Defined in Amazonka.Types

data Signed a #

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, AWSResponse a.

Constructors

Signed 

type Algorithm a = Request a -> AuthEnv -> Region -> UTCTime -> Signed a #

data Signer #

Constructors

Signer (forall a. Algorithm a) (forall a. Seconds -> Algorithm a) 

data Service #

Attributes and functions specific to an AWS service.

Constructors

Service 

Fields

Instances

Instances details
Generic Service 
Instance details

Defined in Amazonka.Types

Associated Types

type Rep Service :: Type -> Type #

Methods

from :: Service -> Rep Service x #

to :: Rep Service x -> Service #

type Rep Service 
Instance details

Defined in Amazonka.Types

data S3AddressingStyle #

When to rewrite S3 requests into virtual-hosted style.

Requests to S3 can be rewritten to access buckets by setting the Host: header, which allows you to point a CNAME record at an Amazon S3 Bucket.

Non-S3 object stores usually do not support this, which is usually the only time you'll need to change this.

See: Virtual hosting of buckets in the Amazon S3 User Guide.

See: Changing the Addressing Style for the corresponding option in Boto 3.

Constructors

S3AddressingStyleAuto

Rewrite S3 request paths only if they can be expressed as a DNS label. This is the default.

S3AddressingStylePath

Do not ever rewrite S3 request paths.

S3AddressingStyleVirtual

Force virtual hosted style rewrites without checking the bucket name.

Instances

Instances details
Generic S3AddressingStyle 
Instance details

Defined in Amazonka.Types

Associated Types

type Rep S3AddressingStyle :: Type -> Type #

Show S3AddressingStyle 
Instance details

Defined in Amazonka.Types

Eq S3AddressingStyle 
Instance details

Defined in Amazonka.Types

type Rep S3AddressingStyle 
Instance details

Defined in Amazonka.Types

type Rep S3AddressingStyle = D1 ('MetaData "S3AddressingStyle" "Amazonka.Types" "amazonka-core-2.0-BFuA7FRvuklLoYhn4b6A6p" 'False) (C1 ('MetaCons "S3AddressingStyleAuto" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "S3AddressingStylePath" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "S3AddressingStyleVirtual" 'PrefixI 'False) (U1 :: Type -> Type)))

data Request a #

An unsigned request.

Instances

Instances details
Generic (Request a) 
Instance details

Defined in Amazonka.Types

Associated Types

type Rep (Request a) :: Type -> Type #

Methods

from :: Request a -> Rep (Request a) x #

to :: Rep (Request a) x -> Request a #

type Rep (Request a) 
Instance details

Defined in Amazonka.Types

type family AWSResponse a #

The successful, expected response associated with a request.

class AWSRequest a where #

Specify how a request can be de/serialised.

Associated Types

type AWSResponse a #

The successful, expected response associated with a request.

Methods

request #

Arguments

:: (Service -> Service)

Overrides applied to the default Service.

-> a 
-> Request a 

response #

Arguments

:: MonadResource m 
=> (ByteStringLazy -> IO ByteStringLazy)

Raw response body hook.

-> Service 
-> Proxy a 
-> ClientResponse ClientBody 
-> m (Either Error (ClientResponse (AWSResponse a))) 

Instances

Instances details
AWSRequest GetRoleCredentials 
Instance details

Defined in Amazonka.SSO.GetRoleCredentials

Associated Types

type AWSResponse GetRoleCredentials #

AWSRequest AssumeRole 
Instance details

Defined in Amazonka.STS.AssumeRole

Associated Types

type AWSResponse AssumeRole #

AWSRequest AssumeRoleWithSAML 
Instance details

Defined in Amazonka.STS.AssumeRoleWithSAML

Associated Types

type AWSResponse AssumeRoleWithSAML #

AWSRequest AssumeRoleWithWebIdentity 
Instance details

Defined in Amazonka.STS.AssumeRoleWithWebIdentity

AWSRequest DecodeAuthorizationMessage 
Instance details

Defined in Amazonka.STS.DecodeAuthorizationMessage

AWSRequest GetAccessKeyInfo 
Instance details

Defined in Amazonka.STS.GetAccessKeyInfo

Associated Types

type AWSResponse GetAccessKeyInfo #

AWSRequest GetCallerIdentity 
Instance details

Defined in Amazonka.STS.GetCallerIdentity

Associated Types

type AWSResponse GetCallerIdentity #

AWSRequest GetFederationToken 
Instance details

Defined in Amazonka.STS.GetFederationToken

Associated Types

type AWSResponse GetFederationToken #

AWSRequest GetSessionToken 
Instance details

Defined in Amazonka.STS.GetSessionToken

Associated Types

type AWSResponse GetSessionToken #

newtype AccessKey #

An access key ID.

For example: AKIAIOSFODNN7EXAMPLE

See: Understanding and Getting Your Security Credentials.

Constructors

AccessKey ByteString 

Instances

Instances details
FromJSON AccessKey 
Instance details

Defined in Amazonka.Types

ToJSON AccessKey 
Instance details

Defined in Amazonka.Types

ToByteString AccessKey 
Instance details

Defined in Amazonka.Types

Methods

toBS :: AccessKey -> ByteString #

ToLog AccessKey 
Instance details

Defined in Amazonka.Types

ToQuery AccessKey 
Instance details

Defined in Amazonka.Types

FromText AccessKey 
Instance details

Defined in Amazonka.Types

ToText AccessKey 
Instance details

Defined in Amazonka.Types

Methods

toText :: AccessKey -> Text #

FromXML AccessKey 
Instance details

Defined in Amazonka.Types

ToXML AccessKey 
Instance details

Defined in Amazonka.Types

Methods

toXML :: AccessKey -> XML #

IsString AccessKey 
Instance details

Defined in Amazonka.Types

Generic AccessKey 
Instance details

Defined in Amazonka.Types

Associated Types

type Rep AccessKey :: Type -> Type #

Read AccessKey 
Instance details

Defined in Amazonka.Types

Show AccessKey 
Instance details

Defined in Amazonka.Types

NFData AccessKey 
Instance details

Defined in Amazonka.Types

Methods

rnf :: AccessKey -> () #

Eq AccessKey 
Instance details

Defined in Amazonka.Types

Hashable AccessKey 
Instance details

Defined in Amazonka.Types

type Rep AccessKey 
Instance details

Defined in Amazonka.Types

type Rep AccessKey = D1 ('MetaData "AccessKey" "Amazonka.Types" "amazonka-core-2.0-BFuA7FRvuklLoYhn4b6A6p" 'True) (C1 ('MetaCons "AccessKey" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

newtype SecretKey #

Secret access key credential.

For example: wJalrXUtnFEMIK7MDENGbPxRfiCYEXAMPLEKE

See: Understanding and Getting Your Security Credentials.

Constructors

SecretKey ByteString 

Instances

Instances details
FromJSON SecretKey 
Instance details

Defined in Amazonka.Types

ToJSON SecretKey 
Instance details

Defined in Amazonka.Types

ToByteString SecretKey 
Instance details

Defined in Amazonka.Types

Methods

toBS :: SecretKey -> ByteString #

FromText SecretKey 
Instance details

Defined in Amazonka.Types

ToText SecretKey 
Instance details

Defined in Amazonka.Types

Methods

toText :: SecretKey -> Text #

FromXML SecretKey 
Instance details

Defined in Amazonka.Types

ToXML SecretKey 
Instance details

Defined in Amazonka.Types

Methods

toXML :: SecretKey -> XML #

IsString SecretKey 
Instance details

Defined in Amazonka.Types

Generic SecretKey 
Instance details

Defined in Amazonka.Types

Associated Types

type Rep SecretKey :: Type -> Type #

NFData SecretKey 
Instance details

Defined in Amazonka.Types

Methods

rnf :: SecretKey -> () #

Eq SecretKey 
Instance details

Defined in Amazonka.Types

Hashable SecretKey 
Instance details

Defined in Amazonka.Types

type Rep SecretKey 
Instance details

Defined in Amazonka.Types

type Rep SecretKey = D1 ('MetaData "SecretKey" "Amazonka.Types" "amazonka-core-2.0-BFuA7FRvuklLoYhn4b6A6p" 'True) (C1 ('MetaCons "SecretKey" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

newtype SessionToken #

A session token used by STS to temporarily authorise access to an AWS resource.

See: Temporary Security Credentials.

Constructors

SessionToken ByteString 

Instances

Instances details
FromJSON SessionToken 
Instance details

Defined in Amazonka.Types

ToJSON SessionToken 
Instance details

Defined in Amazonka.Types

ToByteString SessionToken 
Instance details

Defined in Amazonka.Types

FromText SessionToken 
Instance details

Defined in Amazonka.Types

ToText SessionToken 
Instance details

Defined in Amazonka.Types

Methods

toText :: SessionToken -> Text #

FromXML SessionToken 
Instance details

Defined in Amazonka.Types

ToXML SessionToken 
Instance details

Defined in Amazonka.Types

Methods

toXML :: SessionToken -> XML #

IsString SessionToken 
Instance details

Defined in Amazonka.Types

Generic SessionToken 
Instance details

Defined in Amazonka.Types

Associated Types

type Rep SessionToken :: Type -> Type #

NFData SessionToken 
Instance details

Defined in Amazonka.Types

Methods

rnf :: SessionToken -> () #

Eq SessionToken 
Instance details

Defined in Amazonka.Types

Hashable SessionToken 
Instance details

Defined in Amazonka.Types

type Rep SessionToken 
Instance details

Defined in Amazonka.Types

type Rep SessionToken = D1 ('MetaData "SessionToken" "Amazonka.Types" "amazonka-core-2.0-BFuA7FRvuklLoYhn4b6A6p" 'True) (C1 ('MetaCons "SessionToken" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

data AuthEnv #

The AuthN/AuthZ credential environment.

Instances

Instances details
FromJSON AuthEnv 
Instance details

Defined in Amazonka.Types

ToLog AuthEnv 
Instance details

Defined in Amazonka.Types

FromXML AuthEnv 
Instance details

Defined in Amazonka.Types

Generic AuthEnv 
Instance details

Defined in Amazonka.Types

Associated Types

type Rep AuthEnv :: Type -> Type #

Methods

from :: AuthEnv -> Rep AuthEnv x #

to :: Rep AuthEnv x -> AuthEnv #

Show AuthEnv 
Instance details

Defined in Amazonka.Types

NFData AuthEnv 
Instance details

Defined in Amazonka.Types

Methods

rnf :: AuthEnv -> () #

Eq AuthEnv 
Instance details

Defined in Amazonka.Types

Methods

(==) :: AuthEnv -> AuthEnv -> Bool #

(/=) :: AuthEnv -> AuthEnv -> Bool #

type Rep AuthEnv 
Instance details

Defined in Amazonka.Types

type Rep AuthEnv = D1 ('MetaData "AuthEnv" "Amazonka.Types" "amazonka-core-2.0-BFuA7FRvuklLoYhn4b6A6p" 'False) (C1 ('MetaCons "AuthEnv" 'PrefixI 'True) ((S1 ('MetaSel ('Just "accessKeyId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 AccessKey) :*: S1 ('MetaSel ('Just "secretAccessKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Sensitive SecretKey))) :*: (S1 ('MetaSel ('Just "sessionToken") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe (Sensitive SessionToken))) :*: S1 ('MetaSel ('Just "expiration") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe ISO8601)))))

data Auth #

An authorisation environment containing AWS credentials, and potentially a reference which can be refreshed out-of-band as temporary credentials expire.

Instances

Instances details
ToLog Auth 
Instance details

Defined in Amazonka.Types

newtype Region #

The available AWS regions.

Constructors

Region' 

Fields

Bundled Patterns

pattern Ohio :: Region 
pattern NorthVirginia :: Region 
pattern NorthCalifornia :: Region 
pattern Oregon :: Region 
pattern CapeTown :: Region 
pattern HongKong :: Region 
pattern Hyderabad :: Region 
pattern Jakarta :: Region 
pattern Melbourne :: Region 
pattern Mumbai :: Region 
pattern Osaka :: Region 
pattern Seoul :: Region 
pattern Singapore :: Region 
pattern Sydney :: Region 
pattern Tokyo :: Region 
pattern Montreal :: Region 
pattern Frankfurt :: Region 
pattern Ireland :: Region 
pattern London :: Region 
pattern Milan :: Region 
pattern Paris :: Region 
pattern Spain :: Region 
pattern Stockholm :: Region 
pattern Zurich :: Region 
pattern Bahrain :: Region 
pattern UAE :: Region 
pattern SaoPaulo :: Region 
pattern GovCloudEast :: Region 
pattern GovCloudWest :: Region 
pattern Beijing :: Region 
pattern Ningxia :: Region 

Instances

Instances details
FromJSON Region 
Instance details

Defined in Amazonka.Types

ToJSON Region 
Instance details

Defined in Amazonka.Types

ToByteString Region 
Instance details

Defined in Amazonka.Types

Methods

toBS :: Region -> ByteString #

ToLog Region 
Instance details

Defined in Amazonka.Types

ToQuery Region 
Instance details

Defined in Amazonka.Types

FromText Region 
Instance details

Defined in Amazonka.Types

ToText Region 
Instance details

Defined in Amazonka.Types

Methods

toText :: Region -> Text #

FromXML Region 
Instance details

Defined in Amazonka.Types

ToXML Region 
Instance details

Defined in Amazonka.Types

Methods

toXML :: Region -> XML #

IsString Region 
Instance details

Defined in Amazonka.Types

Methods

fromString :: String -> Region #

Generic Region 
Instance details

Defined in Amazonka.Types

Associated Types

type Rep Region :: Type -> Type #

Methods

from :: Region -> Rep Region x #

to :: Rep Region x -> Region #

Read Region 
Instance details

Defined in Amazonka.Types

Show Region 
Instance details

Defined in Amazonka.Types

NFData Region 
Instance details

Defined in Amazonka.Types

Methods

rnf :: Region -> () #

Eq Region 
Instance details

Defined in Amazonka.Types

Methods

(==) :: Region -> Region -> Bool #

(/=) :: Region -> Region -> Bool #

Ord Region 
Instance details

Defined in Amazonka.Types

Hashable Region 
Instance details

Defined in Amazonka.Types

Methods

hashWithSalt :: Int -> Region -> Int #

hash :: Region -> Int #

type Rep Region 
Instance details

Defined in Amazonka.Types

type Rep Region = D1 ('MetaData "Region" "Amazonka.Types" "amazonka-core-2.0-BFuA7FRvuklLoYhn4b6A6p" 'True) (C1 ('MetaCons "Region'" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromRegion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype Seconds #

A numeric value representing seconds.

Constructors

Seconds DiffTime 

Instances

Instances details
ToByteString Seconds 
Instance details

Defined in Amazonka.Types

Methods

toBS :: Seconds -> ByteString #

ToLog Seconds 
Instance details

Defined in Amazonka.Types

ToQuery Seconds 
Instance details

Defined in Amazonka.Types

FromText Seconds 
Instance details

Defined in Amazonka.Types

ToText Seconds 
Instance details

Defined in Amazonka.Types

Methods

toText :: Seconds -> Text #

Enum Seconds 
Instance details

Defined in Amazonka.Types

Generic Seconds 
Instance details

Defined in Amazonka.Types

Associated Types

type Rep Seconds :: Type -> Type #

Methods

from :: Seconds -> Rep Seconds x #

to :: Rep Seconds x -> Seconds #

Num Seconds 
Instance details

Defined in Amazonka.Types

Read Seconds 
Instance details

Defined in Amazonka.Types

Real Seconds 
Instance details

Defined in Amazonka.Types

Show Seconds 
Instance details

Defined in Amazonka.Types

NFData Seconds 
Instance details

Defined in Amazonka.Types

Methods

rnf :: Seconds -> () #

Eq Seconds 
Instance details

Defined in Amazonka.Types

Methods

(==) :: Seconds -> Seconds -> Bool #

(/=) :: Seconds -> Seconds -> Bool #

Ord Seconds 
Instance details

Defined in Amazonka.Types

Hashable Seconds 
Instance details

Defined in Amazonka.Types

Methods

hashWithSalt :: Int -> Seconds -> Int #

hash :: Seconds -> Int #

type Rep Seconds 
Instance details

Defined in Amazonka.Types

type Rep Seconds = D1 ('MetaData "Seconds" "Amazonka.Types" "amazonka-core-2.0-BFuA7FRvuklLoYhn4b6A6p" 'True) (C1 ('MetaCons "Seconds" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DiffTime)))

newtype Base64 #

Base64 encoded binary data.

Encoding/decoding is automatically deferred to serialisation and deserialisation respectively.

Constructors

Base64 

Fields

Instances

Instances details
FromJSON Base64 
Instance details

Defined in Amazonka.Data.Base64

ToJSON Base64 
Instance details

Defined in Amazonka.Data.Base64

ToBody Base64 
Instance details

Defined in Amazonka.Data.Base64

Methods

toBody :: Base64 -> RequestBody #

ToHashedBody Base64 
Instance details

Defined in Amazonka.Data.Base64

ToByteString Base64 
Instance details

Defined in Amazonka.Data.Base64

Methods

toBS :: Base64 -> ByteString #

ToQuery Base64 
Instance details

Defined in Amazonka.Data.Base64

FromText Base64 
Instance details

Defined in Amazonka.Data.Base64

ToText Base64 
Instance details

Defined in Amazonka.Data.Base64

Methods

toText :: Base64 -> Text #

FromXML Base64 
Instance details

Defined in Amazonka.Data.Base64

ToXML Base64 
Instance details

Defined in Amazonka.Data.Base64

Methods

toXML :: Base64 -> XML #

Generic Base64 
Instance details

Defined in Amazonka.Data.Base64

Associated Types

type Rep Base64 :: Type -> Type #

Methods

from :: Base64 -> Rep Base64 x #

to :: Rep Base64 x -> Base64 #

Read Base64 
Instance details

Defined in Amazonka.Data.Base64

Show Base64 
Instance details

Defined in Amazonka.Data.Base64

NFData Base64 
Instance details

Defined in Amazonka.Data.Base64

Methods

rnf :: Base64 -> () #

Eq Base64 
Instance details

Defined in Amazonka.Data.Base64

Methods

(==) :: Base64 -> Base64 -> Bool #

(/=) :: Base64 -> Base64 -> Bool #

Ord Base64 
Instance details

Defined in Amazonka.Data.Base64

Hashable Base64 
Instance details

Defined in Amazonka.Data.Base64

Methods

hashWithSalt :: Int -> Base64 -> Int #

hash :: Base64 -> Int #

type Rep Base64 
Instance details

Defined in Amazonka.Data.Base64

type Rep Base64 = D1 ('MetaData "Base64" "Amazonka.Data.Base64" "amazonka-core-2.0-BFuA7FRvuklLoYhn4b6A6p" 'True) (C1 ('MetaCons "Base64" 'PrefixI 'True) (S1 ('MetaSel ('Just "unBase64") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

newtype Sensitive a #

Note: read . show /= isomorphic

Constructors

Sensitive 

Fields

Instances

Instances details
Functor Sensitive 
Instance details

Defined in Amazonka.Data.Sensitive

Methods

fmap :: (a -> b) -> Sensitive a -> Sensitive b #

(<$) :: a -> Sensitive b -> Sensitive a #

FromJSON a => FromJSON (Sensitive a) 
Instance details

Defined in Amazonka.Data.Sensitive

ToJSON a => ToJSON (Sensitive a) 
Instance details

Defined in Amazonka.Data.Sensitive

ToBody a => ToBody (Sensitive a) 
Instance details

Defined in Amazonka.Data.Sensitive

Methods

toBody :: Sensitive a -> RequestBody #

ToByteString a => ToByteString (Sensitive a) 
Instance details

Defined in Amazonka.Data.Sensitive

Methods

toBS :: Sensitive a -> ByteString #

ToHeader a => ToHeader (Sensitive a) 
Instance details

Defined in Amazonka.Data.Sensitive

Methods

toHeader :: HeaderName -> Sensitive a -> [Header] #

ToLog (Sensitive a) 
Instance details

Defined in Amazonka.Data.Sensitive

ToQuery a => ToQuery (Sensitive a) 
Instance details

Defined in Amazonka.Data.Sensitive

FromText a => FromText (Sensitive a) 
Instance details

Defined in Amazonka.Data.Sensitive

ToText a => ToText (Sensitive a) 
Instance details

Defined in Amazonka.Data.Sensitive

Methods

toText :: Sensitive a -> Text #

FromXML a => FromXML (Sensitive a) 
Instance details

Defined in Amazonka.Data.Sensitive

Methods

parseXML :: [Node] -> Either String (Sensitive a) #

ToXML a => ToXML (Sensitive a) 
Instance details

Defined in Amazonka.Data.Sensitive

Methods

toXML :: Sensitive a -> XML #

IsString a => IsString (Sensitive a) 
Instance details

Defined in Amazonka.Data.Sensitive

Methods

fromString :: String -> Sensitive a #

Monoid a => Monoid (Sensitive a) 
Instance details

Defined in Amazonka.Data.Sensitive

Semigroup a => Semigroup (Sensitive a) 
Instance details

Defined in Amazonka.Data.Sensitive

Methods

(<>) :: Sensitive a -> Sensitive a -> Sensitive a #

sconcat :: NonEmpty (Sensitive a) -> Sensitive a #

stimes :: Integral b => b -> Sensitive a -> Sensitive a #

IsList a => IsList (Sensitive a) 
Instance details

Defined in Amazonka.Data.Sensitive

Associated Types

type Item (Sensitive a) #

Methods

fromList :: [Item (Sensitive a)] -> Sensitive a #

fromListN :: Int -> [Item (Sensitive a)] -> Sensitive a #

toList :: Sensitive a -> [Item (Sensitive a)] #

Generic (Sensitive a) 
Instance details

Defined in Amazonka.Data.Sensitive

Associated Types

type Rep (Sensitive a) :: Type -> Type #

Methods

from :: Sensitive a -> Rep (Sensitive a) x #

to :: Rep (Sensitive a) x -> Sensitive a #

Show (Sensitive a) 
Instance details

Defined in Amazonka.Data.Sensitive

NFData a => NFData (Sensitive a) 
Instance details

Defined in Amazonka.Data.Sensitive

Methods

rnf :: Sensitive a -> () #

Eq a => Eq (Sensitive a) 
Instance details

Defined in Amazonka.Data.Sensitive

Methods

(==) :: Sensitive a -> Sensitive a -> Bool #

(/=) :: Sensitive a -> Sensitive a -> Bool #

Ord a => Ord (Sensitive a) 
Instance details

Defined in Amazonka.Data.Sensitive

Hashable a => Hashable (Sensitive a) 
Instance details

Defined in Amazonka.Data.Sensitive

Methods

hashWithSalt :: Int -> Sensitive a -> Int #

hash :: Sensitive a -> Int #

type Item (Sensitive a) 
Instance details

Defined in Amazonka.Data.Sensitive

type Item (Sensitive a) = Item a
type Rep (Sensitive a) 
Instance details

Defined in Amazonka.Data.Sensitive

type Rep (Sensitive a) = D1 ('MetaData "Sensitive" "Amazonka.Data.Sensitive" "amazonka-core-2.0-BFuA7FRvuklLoYhn4b6A6p" 'True) (C1 ('MetaCons "Sensitive" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromSensitive") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

hashedBody #

Arguments

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

hashedFileRange #

Arguments

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

hashedFile #

Arguments

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

sourceFileRangeChunks #

Arguments

:: forall (m :: Type -> Type). MonadResource 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.

-> ConduitM () ByteString m () 

unsafeChunkedBody #

Arguments

:: ChunkSize

The idealized size of chunks that will be yielded downstream.

-> Integer

The size of the stream in bytes.

-> ConduitM () ByteString (ResourceT IO) () 
-> RequestBody 

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.

chunkedFileRange #

Arguments

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

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.

chunkedFile :: MonadIO m => ChunkSize -> FilePath -> m RequestBody #

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.

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.

sinkBody :: MonadIO m => ResponseBody -> ConduitM ByteString Void (ResourceT IO) a -> m a #

Connect a Sink to a response stream.

getFileSize :: MonadIO m => FilePath -> m Integer #

Convenience function for obtaining the size of a file.

newtype ResponseBody #

A streaming, exception safe response body.

newtype for show/orhpan instance purposes.

Constructors

ResponseBody 

Fields

Instances

Instances details
Generic ResponseBody 
Instance details

Defined in Amazonka.Data.Body

Associated Types

type Rep ResponseBody :: Type -> Type #

Show ResponseBody 
Instance details

Defined in Amazonka.Data.Body

type Rep ResponseBody 
Instance details

Defined in Amazonka.Data.Body

type Rep ResponseBody = D1 ('MetaData "ResponseBody" "Amazonka.Data.Body" "amazonka-core-2.0-BFuA7FRvuklLoYhn4b6A6p" 'True) (C1 ('MetaCons "ResponseBody" 'PrefixI 'True) (S1 ('MetaSel ('Just "body") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ConduitM () ByteString (ResourceT IO) ()))))

newtype ChunkSize #

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

See: defaultChunk.

Constructors

ChunkSize Int 

Instances

Instances details
ToLog ChunkSize 
Instance details

Defined in Amazonka.Data.Body

Enum ChunkSize 
Instance details

Defined in Amazonka.Data.Body

Num ChunkSize 
Instance details

Defined in Amazonka.Data.Body

Integral ChunkSize 
Instance details

Defined in Amazonka.Data.Body

Real ChunkSize 
Instance details

Defined in Amazonka.Data.Body

Show ChunkSize 
Instance details

Defined in Amazonka.Data.Body

Eq ChunkSize 
Instance details

Defined in Amazonka.Data.Body

Ord ChunkSize 
Instance details

Defined in Amazonka.Data.Body

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.

Constructors

ChunkedBody 

Instances

Instances details
ToBody ChunkedBody 
Instance details

Defined in Amazonka.Data.Body

Show ChunkedBody 
Instance details

Defined in Amazonka.Data.Body

data HashedBody #

An opaque request body containing a SHA256 hash.

Instances

Instances details
ToBody HashedBody 
Instance details

Defined in Amazonka.Data.Body

ToHashedBody HashedBody 
Instance details

Defined in Amazonka.Data.Body

IsString HashedBody 
Instance details

Defined in Amazonka.Data.Body

Show HashedBody 
Instance details

Defined in Amazonka.Data.Body

data RequestBody #

Invariant: only services that support both standard and chunked signing expose RequestBody as a parameter.

Constructors

Chunked ChunkedBody

Currently S3 only, see ChunkedBody for details.

Hashed HashedBody 

Instances

Instances details
ToBody RequestBody 
Instance details

Defined in Amazonka.Data.Body

IsString RequestBody 
Instance details

Defined in Amazonka.Data.Body

Show RequestBody 
Instance details

Defined in Amazonka.Data.Body

class ToHashedBody a where #

Anything that can be safely converted to a HashedBody.

Methods

toHashed :: a -> HashedBody #

Convert a value to a hashed request body.

Instances

Instances details
ToHashedBody Value 
Instance details

Defined in Amazonka.Data.Body

Methods

toHashed :: Value -> HashedBody #

ToHashedBody Base64 
Instance details

Defined in Amazonka.Data.Base64

ToHashedBody HashedBody 
Instance details

Defined in Amazonka.Data.Body

ToHashedBody QueryString 
Instance details

Defined in Amazonka.Data.Body

ToHashedBody ByteStringLazy 
Instance details

Defined in Amazonka.Data.Body

ToHashedBody TextLazy 
Instance details

Defined in Amazonka.Data.Body

ToHashedBody ByteString 
Instance details

Defined in Amazonka.Data.Body

ToHashedBody Text 
Instance details

Defined in Amazonka.Data.Body

Methods

toHashed :: Text -> HashedBody #

ToHashedBody Element 
Instance details

Defined in Amazonka.Data.Body

ToHashedBody String 
Instance details

Defined in Amazonka.Data.Body

ToHashedBody (KeyMap Value) 
Instance details

Defined in Amazonka.Data.Body

class ToBody a where #

Anything that can be converted to a streaming request Body.

Minimal complete definition

Nothing

Methods

toBody :: a -> RequestBody #

Convert a value to a request body.

Instances

Instances details
ToBody Value 
Instance details

Defined in Amazonka.Data.Body

Methods

toBody :: Value -> RequestBody #

ToBody Base64 
Instance details

Defined in Amazonka.Data.Base64

Methods

toBody :: Base64 -> RequestBody #

ToBody ChunkedBody 
Instance details

Defined in Amazonka.Data.Body

ToBody HashedBody 
Instance details

Defined in Amazonka.Data.Body

ToBody RequestBody 
Instance details

Defined in Amazonka.Data.Body

ToBody QueryString 
Instance details

Defined in Amazonka.Data.Body

ToBody ByteStringLazy 
Instance details

Defined in Amazonka.Data.Body

ToBody TextLazy 
Instance details

Defined in Amazonka.Data.Body

ToBody ByteString 
Instance details

Defined in Amazonka.Data.Body

ToBody Text 
Instance details

Defined in Amazonka.Data.Body

Methods

toBody :: Text -> RequestBody #

ToBody Element 
Instance details

Defined in Amazonka.Data.Body

ToBody String 
Instance details

Defined in Amazonka.Data.Body

Methods

toBody :: String -> RequestBody #

ToBody (KeyMap Value) 
Instance details

Defined in Amazonka.Data.Body

ToBody a => ToBody (Sensitive a) 
Instance details

Defined in Amazonka.Data.Sensitive

Methods

toBody :: Sensitive a -> RequestBody #

ToHashedBody a => ToBody (Maybe a) 
Instance details

Defined in Amazonka.Data.Body

Methods

toBody :: Maybe a -> RequestBody #

buildLines :: [ByteStringBuilder] -> ByteStringBuilder #

Intercalate a list of ByteStringBuilders with newlines.

class ToLog a where #

Methods

build :: a -> ByteStringBuilder #

Convert a value to a loggable builder.

Instances

Instances details
ToLog AuthError Source # 
Instance details

Defined in Amazonka.Auth.Exception

ToLog ChunkSize 
Instance details

Defined in Amazonka.Data.Body

ToLog EscapedPath 
Instance details

Defined in Amazonka.Data.Log

ToLog QueryString 
Instance details

Defined in Amazonka.Data.Log

ToLog ByteStringBuilder 
Instance details

Defined in Amazonka.Data.Log

ToLog ByteStringLazy 
Instance details

Defined in Amazonka.Data.Log

ToLog TextLazy 
Instance details

Defined in Amazonka.Data.Log

ToLog Abbrev 
Instance details

Defined in Amazonka.Types

ToLog AccessKey 
Instance details

Defined in Amazonka.Types

ToLog Auth 
Instance details

Defined in Amazonka.Types

ToLog AuthEnv 
Instance details

Defined in Amazonka.Types

ToLog Error 
Instance details

Defined in Amazonka.Types

ToLog ErrorCode 
Instance details

Defined in Amazonka.Types

ToLog ErrorMessage 
Instance details

Defined in Amazonka.Types

ToLog Meta 
Instance details

Defined in Amazonka.Types

ToLog Region 
Instance details

Defined in Amazonka.Types

ToLog RequestId 
Instance details

Defined in Amazonka.Types

ToLog Seconds 
Instance details

Defined in Amazonka.Types

ToLog SerializeError 
Instance details

Defined in Amazonka.Types

ToLog ServiceError 
Instance details

Defined in Amazonka.Types

ToLog Accept 
Instance details

Defined in Amazonka.Waiter

ToLog Int16 
Instance details

Defined in Amazonka.Data.Log

ToLog Int32 
Instance details

Defined in Amazonka.Data.Log

ToLog Int64 
Instance details

Defined in Amazonka.Data.Log

ToLog Int8 
Instance details

Defined in Amazonka.Data.Log

ToLog Word16 
Instance details

Defined in Amazonka.Data.Log

ToLog Word32 
Instance details

Defined in Amazonka.Data.Log

ToLog Word64 
Instance details

Defined in Amazonka.Data.Log

ToLog Word8 
Instance details

Defined in Amazonka.Data.Log

ToLog ByteString 
Instance details

Defined in Amazonka.Data.Log

ToLog HttpException 
Instance details

Defined in Amazonka.Data.Log

ToLog HttpExceptionContent 
Instance details

Defined in Amazonka.Data.Log

ToLog Request 
Instance details

Defined in Amazonka.Data.Log

ToLog RequestBody 
Instance details

Defined in Amazonka.Data.Log

ToLog StdMethod 
Instance details

Defined in Amazonka.Data.Log

ToLog Status 
Instance details

Defined in Amazonka.Data.Log

ToLog HttpVersion 
Instance details

Defined in Amazonka.Data.Log

ToLog Text 
Instance details

Defined in Amazonka.Data.Log

ToLog UTCTime 
Instance details

Defined in Amazonka.Data.Log

ToLog Integer 
Instance details

Defined in Amazonka.Data.Log

ToLog Bool 
Instance details

Defined in Amazonka.Data.Log

ToLog Char 
Instance details

Defined in Amazonka.Data.Log

ToLog Double 
Instance details

Defined in Amazonka.Data.Log

ToLog Float 
Instance details

Defined in Amazonka.Data.Log

ToLog Int 
Instance details

Defined in Amazonka.Data.Log

ToLog Word 
Instance details

Defined in Amazonka.Data.Log

ToLog (Sensitive a) 
Instance details

Defined in Amazonka.Data.Sensitive

ToLog a => ToLog (CI a) 
Instance details

Defined in Amazonka.Data.Log

Methods

build :: CI a -> ByteStringBuilder #

ToLog (Response a) 
Instance details

Defined in Amazonka.Data.Log

ToLog a => ToLog (Maybe a) 
Instance details

Defined in Amazonka.Data.Log

ToLog [Header] 
Instance details

Defined in Amazonka.Data.Log

ToLog [Char] 
Instance details

Defined in Amazonka.Data.Log

Methods

build :: [Char] -> ByteStringBuilder #

_Time :: forall (a :: Format). Iso' (Time a) UTCTime #

data Format #

Instances

Instances details
Generic Format 
Instance details

Defined in Amazonka.Data.Time

Associated Types

type Rep Format :: Type -> Type #

Methods

from :: Format -> Rep Format x #

to :: Rep Format x -> Format #

Read Format 
Instance details

Defined in Amazonka.Data.Time

Show Format 
Instance details

Defined in Amazonka.Data.Time

Eq Format 
Instance details

Defined in Amazonka.Data.Time

Methods

(==) :: Format -> Format -> Bool #

(/=) :: Format -> Format -> Bool #

type Rep Format 
Instance details

Defined in Amazonka.Data.Time

type Rep Format = D1 ('MetaData "Format" "Amazonka.Data.Time" "amazonka-core-2.0-BFuA7FRvuklLoYhn4b6A6p" 'False) ((C1 ('MetaCons "RFC822Format" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ISO8601Format" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BasicFormat" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AWSFormat" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "POSIXFormat" 'PrefixI 'False) (U1 :: Type -> Type))))

newtype Time (a :: Format) #

Constructors

Time 

Fields

Instances

Instances details
FromJSON AWSTime 
Instance details

Defined in Amazonka.Data.Time

FromJSON BasicTime 
Instance details

Defined in Amazonka.Data.Time

FromJSON ISO8601 
Instance details

Defined in Amazonka.Data.Time

FromJSON POSIX 
Instance details

Defined in Amazonka.Data.Time

FromJSON RFC822 
Instance details

Defined in Amazonka.Data.Time

ToJSON AWSTime 
Instance details

Defined in Amazonka.Data.Time

ToJSON BasicTime 
Instance details

Defined in Amazonka.Data.Time

ToJSON ISO8601 
Instance details

Defined in Amazonka.Data.Time

ToJSON POSIX 
Instance details

Defined in Amazonka.Data.Time

ToJSON RFC822 
Instance details

Defined in Amazonka.Data.Time

ToByteString AWSTime 
Instance details

Defined in Amazonka.Data.Time

Methods

toBS :: AWSTime -> ByteString #

ToByteString BasicTime 
Instance details

Defined in Amazonka.Data.Time

Methods

toBS :: BasicTime -> ByteString #

ToByteString ISO8601 
Instance details

Defined in Amazonka.Data.Time

Methods

toBS :: ISO8601 -> ByteString #

ToByteString RFC822 
Instance details

Defined in Amazonka.Data.Time

Methods

toBS :: RFC822 -> ByteString #

ToQuery AWSTime 
Instance details

Defined in Amazonka.Data.Time

ToQuery BasicTime 
Instance details

Defined in Amazonka.Data.Time

ToQuery ISO8601 
Instance details

Defined in Amazonka.Data.Time

ToQuery POSIX 
Instance details

Defined in Amazonka.Data.Time

Methods

toQuery :: POSIX -> QueryString #

ToQuery RFC822 
Instance details

Defined in Amazonka.Data.Time

ToText AWSTime 
Instance details

Defined in Amazonka.Data.Time

Methods

toText :: AWSTime -> Text #

ToText BasicTime 
Instance details

Defined in Amazonka.Data.Time

Methods

toText :: BasicTime -> Text #

ToText ISO8601 
Instance details

Defined in Amazonka.Data.Time

Methods

toText :: ISO8601 -> Text #

ToText POSIX 
Instance details

Defined in Amazonka.Data.Time

Methods

toText :: POSIX -> Text #

ToText RFC822 
Instance details

Defined in Amazonka.Data.Time

Methods

toText :: RFC822 -> Text #

TimeFormat AWSTime 
Instance details

Defined in Amazonka.Data.Time

Methods

format :: proxy AWSTime -> String

TimeFormat BasicTime 
Instance details

Defined in Amazonka.Data.Time

Methods

format :: proxy BasicTime -> String

TimeFormat ISO8601 
Instance details

Defined in Amazonka.Data.Time

Methods

format :: proxy ISO8601 -> String

TimeFormat RFC822 
Instance details

Defined in Amazonka.Data.Time

Methods

format :: proxy RFC822 -> String

FromXML AWSTime 
Instance details

Defined in Amazonka.Data.Time

FromXML BasicTime 
Instance details

Defined in Amazonka.Data.Time

FromXML ISO8601 
Instance details

Defined in Amazonka.Data.Time

FromXML RFC822 
Instance details

Defined in Amazonka.Data.Time

ToXML AWSTime 
Instance details

Defined in Amazonka.Data.Time

Methods

toXML :: AWSTime -> XML #

ToXML BasicTime 
Instance details

Defined in Amazonka.Data.Time

Methods

toXML :: BasicTime -> XML #

ToXML ISO8601 
Instance details

Defined in Amazonka.Data.Time

Methods

toXML :: ISO8601 -> XML #

ToXML RFC822 
Instance details

Defined in Amazonka.Data.Time

Methods

toXML :: RFC822 -> XML #

FromText (Time fmt) 
Instance details

Defined in Amazonka.Data.Time

Methods

fromText :: Text -> Either String (Time fmt) #

Generic (Time a) 
Instance details

Defined in Amazonka.Data.Time

Associated Types

type Rep (Time a) :: Type -> Type #

Methods

from :: Time a -> Rep (Time a) x #

to :: Rep (Time a) x -> Time a #

Read (Time a) 
Instance details

Defined in Amazonka.Data.Time

Show (Time a) 
Instance details

Defined in Amazonka.Data.Time

Methods

showsPrec :: Int -> Time a -> ShowS #

show :: Time a -> String #

showList :: [Time a] -> ShowS #

NFData (Time a) 
Instance details

Defined in Amazonka.Data.Time

Methods

rnf :: Time a -> () #

Eq (Time a) 
Instance details

Defined in Amazonka.Data.Time

Methods

(==) :: Time a -> Time a -> Bool #

(/=) :: Time a -> Time a -> Bool #

Ord (Time a) 
Instance details

Defined in Amazonka.Data.Time

Methods

compare :: Time a -> Time a -> Ordering #

(<) :: Time a -> Time a -> Bool #

(<=) :: Time a -> Time a -> Bool #

(>) :: Time a -> Time a -> Bool #

(>=) :: Time a -> Time a -> Bool #

max :: Time a -> Time a -> Time a #

min :: Time a -> Time a -> Time a #

Hashable (Time a) 
Instance details

Defined in Amazonka.Data.Time

Methods

hashWithSalt :: Int -> Time a -> Int #

hash :: Time a -> Int #

type Rep (Time a) 
Instance details

Defined in Amazonka.Data.Time

type Rep (Time a) = D1 ('MetaData "Time" "Amazonka.Data.Time" "amazonka-core-2.0-BFuA7FRvuklLoYhn4b6A6p" 'True) (C1 ('MetaCons "Time" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromTime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UTCTime)))

data HttpException #

An exception which may be generated by this library

Since: http-client-0.5.0