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

Safe HaskellNone
LanguageHaskell2010

Network.AWS.Prelude

Contents

Synopsis

Re-exported

Primitives

data ByteString :: *

A space-efficient representation of a Word8 vector, supporting many efficient operations.

A ByteString contains 8-bit bytes, or by using the operations from Data.ByteString.Char8 it can be interpreted as containing 8-bit characters.

data CI s :: * -> *

Instances

Eq s => Eq (CI s) 
Data s => Data (CI s) 
Ord s => Ord (CI s) 
(Read s, FoldCase s) => Read (CI s) 
Show s => Show (CI s) 
(IsString s, FoldCase s) => IsString (CI s) 
Monoid s => Monoid (CI s) 
NFData s => NFData (CI s) 
FoldCase (CI s) 
Hashable s => Hashable (CI s) 
ToText a => ToText (CI a) 
ToBuilder [Header] 
ToBuilder a => ToBuilder (CI a) 
ToByteString a => ToByteString (CI a) 
ToHeader (Map (CI Text) Text) 
Typeable (* -> *) CI 

type ClientRequest = Request Source

A convenience alias to avoid type ambiguity.

type ClientResponse = Response ResponseBody Source

A convenience alias encapsulating the common Response.

class (Typeable * e, Show e) => Exception e

Any type that you wish to throw or catch as an exception must be an instance of the Exception class. The simplest case is a new exception type directly below the root:

data MyException = ThisException | ThatException
    deriving (Show, Typeable)

instance Exception MyException

The default method definitions in the Exception class do what we need in this case. You can now throw and catch ThisException and ThatException as exceptions:

*Main> throw ThisException `catch` \e -> putStrLn ("Caught " ++ show (e :: MyException))
Caught ThisException

In more complicated examples, you may wish to define a whole hierarchy of exceptions:

---------------------------------------------------------------------
-- Make the root exception type for all the exceptions in a compiler

data SomeCompilerException = forall e . Exception e => SomeCompilerException e
    deriving Typeable

instance Show SomeCompilerException where
    show (SomeCompilerException e) = show e

instance Exception SomeCompilerException

compilerExceptionToException :: Exception e => e -> SomeException
compilerExceptionToException = toException . SomeCompilerException

compilerExceptionFromException :: Exception e => SomeException -> Maybe e
compilerExceptionFromException x = do
    SomeCompilerException a <- fromException x
    cast a

---------------------------------------------------------------------
-- Make a subhierarchy for exceptions in the frontend of the compiler

data SomeFrontendException = forall e . Exception e => SomeFrontendException e
    deriving Typeable

instance Show SomeFrontendException where
    show (SomeFrontendException e) = show e

instance Exception SomeFrontendException where
    toException = compilerExceptionToException
    fromException = compilerExceptionFromException

frontendExceptionToException :: Exception e => e -> SomeException
frontendExceptionToException = toException . SomeFrontendException

frontendExceptionFromException :: Exception e => SomeException -> Maybe e
frontendExceptionFromException x = do
    SomeFrontendException a <- fromException x
    cast a

---------------------------------------------------------------------
-- Make an exception type for a particular frontend compiler exception

data MismatchedParentheses = MismatchedParentheses
    deriving (Typeable, Show)

instance Exception MismatchedParentheses where
    toException   = frontendExceptionToException
    fromException = frontendExceptionFromException

We can now catch a MismatchedParentheses exception as MismatchedParentheses, SomeFrontendException or SomeCompilerException, but not other types, e.g. IOException:

*Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: MismatchedParentheses))
Caught MismatchedParentheses
*Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: SomeFrontendException))
Caught MismatchedParentheses
*Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: SomeCompilerException))
Caught MismatchedParentheses
*Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: IOException))
*** Exception: MismatchedParentheses

data HashMap k v :: * -> * -> *

Instances

Functor (HashMap k) 
Foldable (HashMap k) 
Traversable (HashMap k) 
(Eq k, Hashable k) => IsList (HashMap k v) 
(Eq k, Eq v) => Eq (HashMap k v) 
(Data k, Data v, Eq k, Hashable k) => Data (HashMap k v) 
(Eq k, Hashable k, Read k, Read e) => Read (HashMap k e) 
(Show k, Show v) => Show (HashMap k v) 
(Eq k, Hashable k) => Monoid (HashMap k v) 
(NFData k, NFData v) => NFData (HashMap k v) 
ToJSON v => ToJSON (HashMap String v) 
ToJSON v => ToJSON (HashMap Text v) 
ToJSON v => ToJSON (HashMap Text v) 
FromJSON v => FromJSON (HashMap String v) 
FromJSON v => FromJSON (HashMap Text v) 
FromJSON v => FromJSON (HashMap Text v) 
(Hashable k, Eq k) => Wrapped (HashMap k a) 
(Eq k, Hashable k) => Ixed (HashMap k a) 
(Eq k, Hashable k) => At (HashMap k a) 
(Hashable k, Eq k) => Semigroup (HashMap k a) 
(ToByteString k, ToByteString v) => ToHeader (HashMap k v) 
Typeable (* -> * -> *) HashMap 
((~) * t (HashMap k' a'), Hashable k, Eq k) => Rewrapped (HashMap k a) t 
type Item (HashMap k v) = (k, v) 
type Unwrapped (HashMap k a) = [(k, a)] 
type IxValue (HashMap k a) = a 
type Index (HashMap k a) = k 

data NonEmpty a :: * -> *

Constructors

a :| [a] 

Instances

Monad NonEmpty 
Functor NonEmpty 
MonadFix NonEmpty 
Applicative NonEmpty 
Foldable NonEmpty 
Traversable NonEmpty 
MonadZip NonEmpty 
Comonad NonEmpty 
ComonadApply NonEmpty 
IsList (NonEmpty a) 
Eq a => Eq (NonEmpty a) 
Data a => Data (NonEmpty a) 
Ord a => Ord (NonEmpty a) 
Read a => Read (NonEmpty a) 
Show a => Show (NonEmpty a) 
Generic (NonEmpty a) 
NFData a => NFData (NonEmpty a) 
Hashable a => Hashable (NonEmpty a) 
Ixed (NonEmpty a) 
Semigroup (NonEmpty a) 
Typeable (* -> *) NonEmpty 
type Rep (NonEmpty a) = D1 D1NonEmpty (C1 C1_0NonEmpty ((:*:) (S1 NoSelector (Rec0 a)) (S1 NoSelector (Rec0 [a])))) 
type Item (NonEmpty a) = a 
type IxValue (NonEmpty a) = a 
type Index (NonEmpty a) = Int 

type Response a = Either (ServiceError (Er (Sv a))) (Rs a) Source

An alias for the common response Either containing a service error in the Left case, or the expected response in the Right.

data Text :: *

Instances

IsList Text 
Eq Text 
Data Text 
Ord Text 
Read Text 
Show Text 
IsString Text 
Monoid Text 
NFData Text 
ToPath Text 
FoldCase Text 
Hashable Text 
Chunk Text 
ToText Text 
FromText Text 
ToJSON Text 
FromJSON Text 
ToBuilder Text 
ToByteString Text 
Ixed Text 
Semigroup Text 
ToHeader Text 
ToQuery Text 
ToXML Text 
FromXML Text 
Typeable * Text 
Strict Text Text 
(~) * a Text => IsString (Parser a) 
ToJSON v => ToJSON (Map Text v) 
ToJSON v => ToJSON (HashMap Text v) 
FromJSON v => FromJSON (Map Text v) 
FromJSON v => FromJSON (HashMap Text v) 
ToHeader (Map (CI Text) Text) 
type Item Text = Char 
type State Text = Buffer 
type ChunkElem Text = Char 
type IxValue Text = Char 
type Index Text = Int 

Classes

class AWSRequest a => AWSPager a where Source

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

Methods

page :: a -> Rs a -> Maybe a Source

class (AWSService (Sv a), AWSSigner (Sg (Sv a))) => AWSRequest a where Source

Specify how a request can be de/serialised.

Associated Types

type Sv a :: * Source

The service definition for a request.

type Rs a :: * Source

The successful, expected response associated with a request.

Methods

request :: a -> Request a Source

response :: MonadResource m => Logger -> Request a -> Either HttpException ClientResponse -> m (Response' a) Source

class (AWSSigner (Sg a), Show (Er a)) => AWSService a where Source

The properties (such as endpoint) for a service, as well as it's associated signing algorithm and error types.

Associated Types

type Sg a :: * Source

Signing algorithm supported by the service.

type Er a :: * Source

The general service error.

Methods

service :: Service a Source

class Generic a

Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.

Minimal complete definition

from, to

Instances

Generic Bool 
Generic Char 
Generic Double 
Generic Float 
Generic Int 
Generic Ordering 
Generic () 
Generic All 
Generic Any 
Generic Arity 
Generic Fixity 
Generic Associativity 
Generic TimeSpec 
Generic Clock 
Generic Void 
Generic Base64 
Generic Region 
Generic RESTError 
Generic ErrorType 
Generic ErrorCode 
Generic JSONError 
Generic [a] 
Generic (U1 p) 
Generic (Par1 p) 
Generic (ZipList a) 
Generic (Dual a) 
Generic (Endo a) 
Generic (Sum a) 
Generic (Product a) 
Generic (First a) 
Generic (Last a) 
Generic (Maybe a) 
Generic (HistoriedResponse body) 
Generic (NonEmpty a) 
Generic (WrappedMonoid m) 
Generic (Option a) 
Generic (Min a) 
Generic (Max a) 
Generic (Last a) 
Generic (First a) 
Generic (Either a b) 
Generic (Rec1 f p) 
Generic (a, b) 
Generic (Const a b) 
Generic (WrappedMonad m a) 
Generic (Proxy * t) 
Generic (K1 i c p) 
Generic ((:+:) f g p) 
Generic ((:*:) f g p) 
Generic ((:.:) f g p) 
Generic (a, b, c) 
Generic (WrappedArrow a b c) 
Generic (M1 i c f p) 
Generic (a, b, c, d) 
Generic (a, b, c, d, e) 
Generic (a, b, c, d, e, f) 
Generic (a, b, c, d, e, f, g) 

class IsString a where

Class for string-like datastructures; used by the overloaded string extension (-XOverloadedStrings in GHC).

Methods

fromString :: String -> a

class Semigroup a

Instances

Semigroup Ordering 
Semigroup () 
Semigroup All 
Semigroup Any 
Semigroup Builder 
Semigroup ByteString 
Semigroup ShortByteString 
Semigroup ByteString 
Semigroup IntSet 
Semigroup Text 
Semigroup Text 
Semigroup Builder 
Semigroup Void 
Semigroup [a] 
Semigroup a => Semigroup (Dual a) 
Semigroup (Endo a) 
Num a => Semigroup (Sum a) 
Num a => Semigroup (Product a) 
Semigroup (First a) 
Semigroup (Last a) 
Semigroup a => Semigroup (Maybe a) 
Semigroup (IntMap v) 
Ord a => Semigroup (Set a) 
Semigroup (Seq a) 
(Hashable a, Eq a) => Semigroup (HashSet a) 
Semigroup (NonEmpty a) 
Semigroup a => Semigroup (May a) 
Monoid m => Semigroup (WrappedMonoid m) 
Semigroup a => Semigroup (Option a) 
Ord a => Semigroup (Min a) 
Ord a => Semigroup (Max a) 
Semigroup (Last a) 
Semigroup (First a) 
Semigroup (Equivalence a) 
Semigroup (Comparison a) 
Semigroup b => Semigroup (a -> b) 
Semigroup (Either a b) 
(Semigroup a, Semigroup b) => Semigroup (a, b) 
Semigroup a => Semigroup (Const a b) 
Ord k => Semigroup (Map k v) 
(Hashable k, Eq k) => Semigroup (HashMap k a) 
Semigroup (ReifiedFold s a) 
Semigroup a => Semigroup (Err e a) 
Semigroup a => Semigroup (Op a b) 
Semigroup (List1 e a) 
Semigroup (List e a) 
(Eq k, Hashable k) => Semigroup (Map k v) 
(Semigroup a, Semigroup b, Semigroup c) => Semigroup (a, b, c) 
Semigroup (ReifiedIndexedFold i s a) 
(Apply m, Semigroup r) => Semigroup (Effect m r a) 
(Semigroup a, Semigroup b, Semigroup c, Semigroup d) => Semigroup (a, b, c, d) 
(Semigroup a, Semigroup b, Semigroup c, Semigroup d, Semigroup e) => Semigroup (a, b, c, d, e) 
Contravariant g => Semigroup (BazaarT p g a b t) 
Contravariant g => Semigroup (BazaarT1 p g a b t) 
(Eq k, Hashable k) => Semigroup (EMap e i j k v) 

Retries

data Retry a Source

Constants and predicates used to create a RetryPolicy.

Constructors

Exponential 

Errors

class AWSError a where Source

Instances

data ServiceError a Source

An error type representing the subset of errors that can be directly attributed to this library.

Shared

data Empty Source

Constructors

Empty 

Instances

HTTP

data Status :: *

Constructors

Status