amazonka-core-1.4.4: Core data types and functionality for Amazonka libraries.

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

Network.AWS.Types

Contents

Description

 

Synopsis

Authentication

Credentials

newtype SessionToken Source #

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

Constructors

SessionToken ByteString 

Environment

data AuthEnv Source #

The authorisation environment.

Instances

data Auth Source #

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

Instances

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

Logging

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

Enum LogLevel Source # 
Eq LogLevel Source # 
Data LogLevel Source # 

Methods

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

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

toConstr :: LogLevel -> Constr #

dataTypeOf :: LogLevel -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LogLevel Source # 
Show LogLevel Source # 
ToText LogLevel Source # 

Methods

toText :: LogLevel -> Text Source #

FromText LogLevel Source # 

Methods

parser :: Parser LogLevel Source #

ToByteString LogLevel Source # 

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

A function threaded through various request and serialisation routines to log informational and debug messages.

Signing

data Meta where Source #

Signing algorithm specific metadata.

Constructors

Meta :: ToLog a => a -> Meta 

Instances

data Signer Source #

Constructors

Signer 

Fields

data Signed a Source #

A signed ClientRequest and associated metadata specific to the signing algorithm, tagged with the initial request type to be able to obtain the associated response, 'Rs a'.

Constructors

Signed 

Service

data Service Source #

Attributes and functions specific to an AWS service.

Requests

class AWSRequest a where Source #

Specify how a request can be de/serialised.

Minimal complete definition

request, response

Associated Types

type Rs a :: * Source #

The successful, expected response associated with a request.

data Request a Source #

An unsigned request.

Responses

type Response a = (Status, Rs a) Source #

Retries

data Retry Source #

Constants and predicates used to create a RetryPolicy.

Constructors

Exponential 

Fields

Errors

class AsError a where Source #

Minimal complete definition

_Error

Methods

_Error :: Prism' a Error Source #

A general Amazonka error.

_TransportError :: Prism' a HttpException Source #

An error occured while communicating over HTTP with a remote service.

_SerializeError :: Prism' a SerializeError Source #

A serialisation error occured when attempting to deserialise a response.

_ServiceError :: Prism' a ServiceError Source #

A service specific error returned by the remote service.

HTTP Errors

Serialize Errors

Service Errors

Error Types

Regions

data Region Source #

The sum of available AWS regions.

Constructors

Ireland

Europe / eu-west-1

Frankfurt

Europe / eu-central-1

Tokyo

Asia Pacific / ap-northeast-1

Singapore

Asia Pacific / ap-southeast-1

Sydney

Asia Pacific / ap-southeast-2

Bombay

Asia Pacific / ap-south-1

Beijing

China / cn-north-1

NorthVirginia

US / us-east-1

NorthCalifornia

US / us-west-1

Oregon

US / us-west-2

GovCloud

AWS GovCloud / us-gov-west-1

GovCloudFIPS

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

SaoPaulo

South America / sa-east-1

Instances

Eq Region Source # 

Methods

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

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

Data Region Source # 

Methods

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

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

toConstr :: Region -> Constr #

dataTypeOf :: Region -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Region Source # 
Read Region Source # 
Show Region Source # 
Generic Region Source # 

Associated Types

type Rep Region :: * -> * #

Methods

from :: Region -> Rep Region x #

to :: Rep Region x -> Region #

NFData Region Source # 

Methods

rnf :: Region -> () #

Hashable Region Source # 

Methods

hashWithSalt :: Int -> Region -> Int #

hash :: Region -> Int #

ToText Region Source # 

Methods

toText :: Region -> Text Source #

FromText Region Source # 

Methods

parser :: Parser Region Source #

ToJSON Region Source # 

Methods

toJSON :: Region -> Value #

toEncoding :: Region -> Encoding #

FromJSON Region Source # 

Methods

parseJSON :: Value -> Parser Region #

ToByteString Region Source # 
ToXML Region Source # 

Methods

toXML :: Region -> XML Source #

FromXML Region Source # 

Methods

parseXML :: [Node] -> Either String Region Source #

ToLog Region Source # 

Methods

build :: Region -> Builder Source #

type Rep Region Source # 
type Rep Region = D1 (MetaData "Region" "Network.AWS.Types" "amazonka-core-1.4.4-37acnMZBU148gTrDuH4Pfk" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Ireland" PrefixI False) U1) ((:+:) (C1 (MetaCons "Frankfurt" PrefixI False) U1) (C1 (MetaCons "Tokyo" PrefixI False) U1))) ((:+:) (C1 (MetaCons "Singapore" PrefixI False) U1) ((:+:) (C1 (MetaCons "Sydney" PrefixI False) U1) (C1 (MetaCons "Bombay" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "Beijing" PrefixI False) U1) ((:+:) (C1 (MetaCons "NorthVirginia" PrefixI False) U1) (C1 (MetaCons "NorthCalifornia" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Oregon" PrefixI False) U1) (C1 (MetaCons "GovCloud" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GovCloudFIPS" PrefixI False) U1) (C1 (MetaCons "SaoPaulo" PrefixI False) U1)))))

Endpoints

data Endpoint Source #

Instances

Eq Endpoint Source # 
Data Endpoint Source # 

Methods

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

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

toConstr :: Endpoint -> Constr #

dataTypeOf :: Endpoint -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Endpoint Source # 

HTTP

type ClientRequest = Request Source #

A convenience alias to avoid type ambiguity.

type ClientResponse = Response ResponseBody Source #

A convenience alias encapsulating the common Response.

type ResponseBody = ResumableSource (ResourceT IO) ByteString Source #

A convenience alias encapsulating the common Response body.

clientRequest :: Endpoint -> Maybe Seconds -> ClientRequest Source #

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

Seconds

newtype Seconds Source #

An integral value representing seconds.

Constructors

Seconds Int 

Instances

Bounded Seconds Source # 
Enum Seconds Source # 
Eq Seconds Source # 

Methods

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

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

Integral Seconds Source # 
Data Seconds Source # 

Methods

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

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

toConstr :: Seconds -> Constr #

dataTypeOf :: Seconds -> DataType #

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

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

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

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

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

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

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

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

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

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

Num Seconds Source # 
Ord Seconds Source # 
Read Seconds Source # 
Real Seconds Source # 
Show Seconds Source # 
Generic Seconds Source # 

Associated Types

type Rep Seconds :: * -> * #

Methods

from :: Seconds -> Rep Seconds x #

to :: Rep Seconds x -> Seconds #

NFData Seconds Source # 

Methods

rnf :: Seconds -> () #

Hashable Seconds Source # 

Methods

hashWithSalt :: Int -> Seconds -> Int #

hash :: Seconds -> Int #

ToText Seconds Source # 

Methods

toText :: Seconds -> Text Source #

ToByteString Seconds Source # 
ToQuery Seconds Source # 
ToLog Seconds Source # 
type Rep Seconds Source # 
type Rep Seconds = D1 (MetaData "Seconds" "Network.AWS.Types" "amazonka-core-1.4.4-37acnMZBU148gTrDuH4Pfk" True) (C1 (MetaCons "Seconds" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

Isomorphisms

_Coerce :: (Coercible a b, Coercible b a) => Iso' a b Source #

_Default :: Monoid a => Iso' (Maybe a) a Source #

Invalid Iso, should be a Prism but exists for ease of composition with the current 'Lens . Iso' chaining to hide internal types from the user.