aws-simple-0.4.0.0: Dead simple bindings to commonly used AWS Services

Safe HaskellNone
LanguageHaskell2010

Network.AWS.Simple

Contents

Synopsis

Documentation

data Region :: * #

The available AWS regions.

Constructors

NorthVirginia

US East ('us-east-1').

Ohio

US East ('us-east-2').

NorthCalifornia

US West ('us-west-1').

Oregon

US West ('us-west-2').

Tokyo

Asia Pacific ('ap-northeast-1').

Seoul

Asia Pacific ('ap-northeast-2').

Mumbai

Asia Pacific ('ap-south-1').

Singapore

Asia Pacific ('ap-southeast-1').

Sydney

Asia Pacific ('ap-southeast-2').

SaoPaulo

South America ('sa-east-1').

Ireland

EU ('eu-west-1').

Frankfurt

EU ('eu-central-1').

GovCloud

US GovCloud ('us-gov-west-1').

GovCloudFIPS

US GovCloud FIPS (S3 Only, 'fips-us-gov-west-1').

Beijing

China ('cn-north-1').

Instances

Eq Region 

Methods

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

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

Data Region 

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 
Read Region 
Show Region 
Generic Region 

Associated Types

type Rep Region :: * -> * #

Methods

from :: Region -> Rep Region x #

to :: Rep Region x -> Region #

Hashable Region 

Methods

hashWithSalt :: Int -> Region -> Int #

hash :: Region -> Int #

ToJSON Region 
FromJSON Region 
ToText Region 

Methods

toText :: Region -> Text #

FromText Region 

Methods

parser :: Parser Region #

ToByteString Region 

Methods

toBS :: Region -> ByteString #

ToLog Region 

Methods

build :: Region -> Builder #

NFData Region 

Methods

rnf :: Region -> () #

FromXML Region 
ToXML Region 

Methods

toXML :: Region -> XML #

type Rep Region 
type Rep Region = D1 (MetaData "Region" "Network.AWS.Types" "amazonka-core-1.4.5-Kiyq2Ip1p934jf84mgW5Yr" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "NorthVirginia" PrefixI False) U1) ((:+:) (C1 (MetaCons "Ohio" PrefixI False) U1) (C1 (MetaCons "NorthCalifornia" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Oregon" PrefixI False) U1) (C1 (MetaCons "Tokyo" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Seoul" PrefixI False) U1) (C1 (MetaCons "Mumbai" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Singapore" PrefixI False) U1) (C1 (MetaCons "Sydney" PrefixI False) U1)) ((:+:) (C1 (MetaCons "SaoPaulo" PrefixI False) U1) (C1 (MetaCons "Ireland" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Frankfurt" PrefixI False) U1) (C1 (MetaCons "GovCloud" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GovCloudFIPS" PrefixI False) U1) (C1 (MetaCons "Beijing" PrefixI False) U1)))))

Logging

data LogLevel :: * #

Constructors

Info

Info messages supplied by the user - this level is not emitted by the library.

Error

Error messages only.

Debug

Useful debug information + info + error levels.

Trace

Includes potentially sensitive signing metadata, and non-streaming response bodies.

Instances

Enum LogLevel 
Eq LogLevel 
Data LogLevel 

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 
Show LogLevel 
ToText LogLevel 

Methods

toText :: LogLevel -> Text #

FromText LogLevel 
ToByteString LogLevel 

Methods

toBS :: LogLevel -> ByteString #

S3

SQS

data GetMessageCfg Source #

Constructors

GetMessageCfg 

Fields

data MessageHandle Source #

Amazon SQS receipt handle id