| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Network.AWS.Prelude
- data ByteString :: *
- data CI s :: * -> *
- type ClientRequest = Request
- type ClientResponse = Response ResponseBody
- class (Typeable * e, Show e) => Exception e
- data HashMap k v :: * -> * -> *
- data HttpException :: *
- data Natural :: *
- data NonEmpty a :: * -> *
- data RequestBody :: *
- type Response a = Either (ServiceError (Er (Sv a))) (Rs a)
- data Text :: *
- class AWSError a where- awsError :: a -> ServiceError String
 
- class AWSRequest a => AWSPager a where
- class (AWSService (Sv a), AWSSigner (Sg (Sv a))) => AWSRequest a where- type Sv a :: *
- type Rs a :: *
- request :: a -> Request a
- response :: MonadResource m => a -> Either HttpException ClientResponse -> m (Response a)
 
- class (AWSSigner (Sg a), Show (Er a)) => AWSService a where
- class Generic a
- class IsString a where- fromString :: String -> a
 
- class Semigroup a
- class Integral n => Whole n
- data Empty = Empty
- data Service a = Service {}
- data ServiceError a
- data StdMethod :: *
- data Status :: *
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.
Instances
| Eq ByteString | |
| Data ByteString | |
| Ord ByteString | |
| Read ByteString | |
| Show ByteString | |
| IsString ByteString | |
| Chunk ByteString | |
| Monoid ByteString | |
| FoldCase ByteString | Note that  | 
| NFData ByteString | |
| Hashable ByteString | |
| Semigroup ByteString | |
| Ixed ByteString | |
| ToText ByteString | |
| FromText ByteString | |
| ToBuilder ByteString | |
| ToByteString ByteString | |
| ToBody ByteString | |
| ToHeader ByteString | |
| ToQuery ByteString | |
| Typeable * ByteString | |
| Strict ByteString ByteString | |
| (~) * a ByteString => IsString (Parser a) | |
| ToBuilder [Header] | |
| type State ByteString = Buffer | |
| type ChunkElem ByteString = Word8 | |
| type Index ByteString = Int | |
| type IxValue ByteString = Word8 | 
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) | |
| 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 MyExceptionThe 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 = frontendExceptionFromExceptionWe can now catch a MismatchedParentheses exception as
MismatchedParentheses, SomeFrontendException or
SomeCompilerException, but not other types, e.g. IOException:
*Main> throw MismatchedParenthesescatche -> putStrLn ("Caught " ++ show (e :: MismatchedParentheses)) Caught MismatchedParentheses *Main> throw MismatchedParenthesescatche -> putStrLn ("Caught " ++ show (e :: SomeFrontendException)) Caught MismatchedParentheses *Main> throw MismatchedParenthesescatche -> putStrLn ("Caught " ++ show (e :: SomeCompilerException)) Caught MismatchedParentheses *Main> throw MismatchedParenthesescatche -> putStrLn ("Caught " ++ show (e :: IOException)) *** Exception: MismatchedParentheses
Instances
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
data HttpException :: *
Instances
data Natural :: *
Instances
data NonEmpty a :: * -> *
Instances
| Monad NonEmpty | |
| Functor NonEmpty | |
| Applicative NonEmpty | |
| Foldable NonEmpty | |
| Traversable 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) | |
| Semigroup (NonEmpty a) | |
| Ixed (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 Index (NonEmpty a) = Int | |
| type IxValue (NonEmpty a) = a | 
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
Instances
data Text :: *
A space efficient, packed, unboxed Unicode text type.
Instances
| IsList Text | |
| Eq Text | |
| Data Text | This instance preserves data abstraction at the cost of inefficiency. We omit reflection services for the sake of data abstraction. This instance was created by copying the updated behavior of
  The original discussion is archived here: could we get a Data instance for Data.Text.Text? The followup discussion that changed the behavior of  | 
| Ord Text | |
| Read Text | |
| Show Text | |
| IsString Text | |
| ToJSON Text | |
| FromJSON Text | |
| Chunk Text | |
| Monoid Text | |
| FoldCase Text | |
| NFData Text | |
| Hashable Text | |
| Semigroup Text | |
| Ixed Text | |
| ToPath Text | |
| ToText Text | |
| FromText Text | |
| ToBuilder Text | |
| ToByteString Text | |
| ToHeader Text | |
| ToQuery Text | |
| ToXML Text | |
| FromXML Text | |
| Typeable * Text | |
| Strict Text Text | |
| (~) * a Text => IsString (Parser a) | |
| ToJSON v => ToJSON (HashMap Text v) | |
| ToJSON v => ToJSON (Map Text v) | |
| FromJSON v => FromJSON (HashMap Text v) | |
| FromJSON v => FromJSON (Map Text v) | |
| ToHeader (Map (CI Text) Text) | |
| type State Text = Buffer | |
| type ChunkElem Text = Char | |
| type Item Text = Char | |
| type Index Text = Int | |
| type IxValue Text = Char | 
Classes
Methods
awsError :: a -> ServiceError String Source
Instances
| Show a => AWSError (ServiceError a) | 
class AWSRequest a => AWSPager a where Source
Specify how an AWSRequest and it's associated Rs response can generate
 a subsequent request, if available.
class (AWSService (Sv a), AWSSigner (Sg (Sv a))) => AWSRequest a where Source
Specify how a request can be de/serialised.
Associated Types
The service definition for a request.
The successful, expected response associated with a request.
Methods
request :: a -> Request a Source
response :: MonadResource m => 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
Signing algorithm supported by the service.
The general service error.
class Generic a
Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.
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 Void | |
| Generic Base64 | |
| Generic Region | |
| Generic RESTError | |
| Generic ErrorType | |
| Generic JSONError | |
| Generic [a] | |
| Generic (U1 p) | |
| Generic (Par1 p) | |
| Generic (Maybe 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 (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
Instances
| IsString ByteString | |
| IsString Builder | |
| IsString Builder | |
| IsString ByteString | |
| IsString Text | |
| IsString Value | |
| IsString Text | |
| IsString ShortByteString | |
| IsString Request | |
| IsString Doc | |
| IsString FilePath | |
| IsString Name | |
| IsString RqBody | |
| IsString Query | |
| IsString Action | |
| IsString SecurityToken | |
| IsString SecretKey | |
| IsString AccessKey | |
| IsString [Char] | |
| (~) * a Text => IsString (Parser a) | |
| (~) * a ByteString => IsString (Parser a) | |
| (IsString s, FoldCase s) => IsString (CI s) | |
| IsString (DList Char) | |
| IsString a => IsString (Sensitive a) | 
class Semigroup a
Instances
A refinement of Integral to represent types that do not contain negative numbers.
Minimal complete definition
Shared
Attributes specific to an AWS service.
Constructors
| Service | |
| Fields | |
Errors
data ServiceError a Source
An error type representing the subset of errors that can be directly attributed to this library.
Constructors
| HttpError HttpException | |
| SerializerError Abbrev String | |
| ServiceError Abbrev Status a | |
| Errors [ServiceError a] | 
Instances
| Show a => Show (ServiceError a) | |
| (Show a, Typeable * a) => Exception (ServiceError a) | |
| Monoid (ServiceError a) | |
| Show a => AWSError (ServiceError a) | |
| Typeable (* -> *) ServiceError | 
HTTP
data StdMethod :: *
HTTP standard method (as defined by RFC 2616, and PATCH which is defined by RFC 5789).
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.