amazonka-core-0.3.0: 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 :: * -> *

A CI s provides Case Insensitive comparison for the string-like type s (for example: String, Text, ByteString, etc.).

Note that CI s has an instance for IsString which together with the OverloadedStrings language extension allows you to write case insensitive string literals as in:

> ("Content-Type" :: CI Text) == ("CONTENT-TYPE" :: CI Text)
True

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) 
FoldCase (CI s) 
NFData s => NFData (CI s) 
Hashable s => Hashable (CI s) 
ToText a => ToText (CI a) Source 
ToBuilder [Header] Source 
ToBuilder a => ToBuilder (CI a) Source 
ToByteString a => ToByteString (CI a) Source 
ToHeader (Map (CI Text) Text) Source 

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

A map from keys to values. A map cannot contain duplicate keys; each key can map to at most one value.

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) 
(Hashable k, Eq k) => Semigroup (HashMap k a) 
(Eq k, Hashable k) => Ixed (HashMap k a) 
(Eq k, Hashable k) => At (HashMap k a) 
(Hashable k, Eq k) => Wrapped (HashMap k a) 
(ToByteString k, ToByteString v) => ToHeader (HashMap k v) Source 
((~) * t (HashMap k' a'), Hashable k, Eq k) => Rewrapped (HashMap k a) t

Use wrapping fromList. Unwrapping returns some permutation of the list.

type Item (HashMap k v) = (k, v) 
type Index (HashMap k a) = k 
type IxValue (HashMap k a) = a 
type Unwrapped (HashMap k a) = [(k, a)] 

data NonEmpty a :: * -> *

Constructors

a :| [a] infixr 5 

Instances

data RequestBody :: *

When using one of the RequestBodyStream / RequestBodyStreamChunked constructors, you must ensure that the GivesPopper can be called multiple times. Usually this is not a problem.

The RequestBodyStreamChunked will send a chunked request body. Note that not all servers support this. Only use RequestBodyStreamChunked if you know the server you're sending to supports chunked request bodies.

Since 0.1.0

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.

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.

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 Exp 
Generic Match 
Generic Clause 
Generic Pat 
Generic Type 
Generic Dec 
Generic Name 
Generic FunDep 
Generic TyVarBndr 
Generic () 
Generic Con 
Generic Void 
Generic All 
Generic Any 
Generic Arity 
Generic Fixity 
Generic Associativity 
Generic WindowBits 
Generic URI 
Generic Doc 
Generic TextDetails 
Generic Style 
Generic Mode 
Generic ModName 
Generic PkgName 
Generic Module 
Generic OccName 
Generic NameFlavour 
Generic NameSpace 
Generic Loc 
Generic Info 
Generic ModuleInfo 
Generic Fixity 
Generic FixityDirection 
Generic Lit 
Generic Body 
Generic Guard 
Generic Stmt 
Generic Range 
Generic TySynEqn 
Generic FamFlavour 
Generic Foreign 
Generic Callconv 
Generic Safety 
Generic Pragma 
Generic Inline 
Generic RuleMatch 
Generic Phases 
Generic RuleBndr 
Generic AnnTarget 
Generic Strict 
Generic TyLit 
Generic Role 
Generic AnnLookup 
Generic Event 
Generic ExternalID 
Generic Doctype 
Generic Name 
Generic Miscellaneous 
Generic Instruction 
Generic Prologue 
Generic Document 
Generic Node 
Generic Element 
Generic Content 
Generic Format 
Generic Method 
Generic CompressionLevel 
Generic MemoryLevel 
Generic CompressionStrategy 
Generic Base64 
Generic Region 
Generic RESTError 
Generic ErrorType 
Generic ErrorCode 
Generic JSONError 
Generic [a] 
Generic (U1 p) 
Generic (Par1 p) 
Generic (Maybe a) 
Generic (Identity a) 
Generic (ZipList a) 
Generic (Dual a) 
Generic (Endo a) 
Generic (Sum a) 
Generic (Product a) 
Generic (First a) 
Generic (Last a) 
Generic (HistoriedResponse body) 
Generic (Min a) 
Generic (Max a) 
Generic (First a) 
Generic (Last a) 
Generic (WrappedMonoid m) 
Generic (Option a) 
Generic (NonEmpty a) 
Generic (Either a b) 
Generic (Rec1 f p) 
Generic (a, b) 
Generic (Const a b) 
Generic (WrappedMonad m a) 
Generic (Proxy * t) 
Generic (Arg a b) 
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 (Alt k f a) 
Generic (Tagged k s b) 
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 ByteString 
Semigroup Builder 
Semigroup Builder 
Semigroup ByteString 
Semigroup Text 
Semigroup Text 
Semigroup Void 
Semigroup All 
Semigroup Any 
Semigroup ShortByteString 
Semigroup IntSet 
Semigroup [a] 
Semigroup a => Semigroup (Maybe 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 (IntMap v) 
Ord a => Semigroup (Set a) 
Semigroup (Seq a) 
Semigroup (Comparison a) 
Semigroup (Equivalence a) 
(Hashable a, Eq a) => Semigroup (HashSet a) 
Semigroup a => Semigroup (May a) 
Ord a => Semigroup (Min a) 
Ord a => Semigroup (Max a) 
Semigroup (First a) 
Semigroup (Last a) 
Monoid m => Semigroup (WrappedMonoid m) 
Semigroup a => Semigroup (Option a) 
Semigroup (NonEmpty a) 
Semigroup b => Semigroup (a -> b) 
Semigroup (Either a b) 
(Semigroup a, Semigroup b) => Semigroup (a, b) 
Semigroup a => Semigroup (Op a b) 
(Hashable k, Eq k) => Semigroup (HashMap k a) 
Ord k => Semigroup (Map k v) 
Semigroup a => Semigroup (Const a b) 
Semigroup (Proxy k s) 
Semigroup (ReifiedFold s a) 
Semigroup a => Semigroup (Err e a) 
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) 
Alternative f => Semigroup (Alt * f a) 
Semigroup (ReifiedIndexedFold i s a) 
(Apply m, Semigroup r) => Semigroup (Effect m r a) 
Semigroup a => Semigroup (Tagged k s 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 

HTTP

data StdMethod :: *

HTTP standard method (as defined by RFC 2616, and PATCH which is defined by RFC 5789).

Constructors

GET 
POST 
HEAD 
PUT 
DELETE 
TRACE 
CONNECT 
OPTIONS 
PATCH 

data Status :: *

HTTP Status.

Only the statusCode is used for comparisons.

Please use mkStatus to create status codes from code and message, or the Enum instance or the status code constants (like ok200). There might be additional record members in the future.

Note that the Show instance is only for debugging.

Constructors

Status