| 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 :: * -> * = a :| [a]
- data RequestBody :: *
- type Response a = Either (ServiceError (Er (Sv a))) (Rs a)
- data Text :: *
- class AWSRequest a => AWSPager a where
- class (AWSService (Sv a), AWSSigner (Sg (Sv a))) => AWSRequest a where
- class (AWSSigner (Sg a), Show (Er a)) => AWSService a where
- class Generic a
- class IsString a where
- fromString :: String -> a
- class Semigroup a
- data Retry a = Exponential {
- _retryBase :: !Double
- _retryGrowth :: !Int
- _retryAttempts :: !Int
- _retryCheck :: Status -> Er a -> Bool
- class AWSError a where
- awsError :: a -> ServiceError String
- class AWSErrorCode a where
- awsErrorCode :: a -> ErrorCode
- data ServiceError a
- data RESTError
- restError :: FromXML (Er a) => (Status -> Bool) -> Service a -> Status -> Maybe (ByteString -> ServiceError (Er a))
- data JSONError
- jsonError :: FromJSON (Er a) => (Status -> Bool) -> Service a -> Status -> Maybe (ByteString -> ServiceError (Er a))
- statusSuccess :: Status -> Bool
- data Empty = Empty
- data Service a = Service {
- _svcAbbrev :: !Text
- _svcPrefix :: !ByteString
- _svcVersion :: !ByteString
- _svcTargetPrefix :: Maybe ByteString
- _svcJSONVersion :: Maybe ByteString
- _svcHandle :: Status -> Maybe (LazyByteString -> ServiceError (Er a))
- _svcRetry :: Retry a
- data StdMethod :: *
- data Status :: * = 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 | |
| Monoid ByteString | |
| NFData ByteString | |
| FoldCase ByteString | |
| Hashable ByteString | |
| Chunk ByteString | |
| ToText ByteString | |
| FromText ByteString | |
| ToBuilder ByteString | |
| ToByteString ByteString | |
| Ixed ByteString | |
| Semigroup 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 IxValue ByteString = Word8 | |
| type Index ByteString = Int |
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 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
| Exception PatternMatchFail | |
| Exception RecSelError | |
| Exception RecConError | |
| Exception RecUpdError | |
| Exception NoMethodError | |
| Exception NonTermination | |
| Exception NestedAtomically | |
| Exception BlockedIndefinitelyOnMVar | |
| Exception BlockedIndefinitelyOnSTM | |
| Exception Deadlock | |
| Exception AssertionFailed | |
| Exception SomeAsyncException | |
| Exception AsyncException | |
| Exception ArrayException | |
| Exception ExitCode | |
| Exception IOException | |
| Exception ErrorCall | |
| Exception ArithException | |
| Exception SomeException | |
| Exception UnicodeException | |
| Exception HttpException | |
| Exception InvalidAccess | |
| Exception Void | |
| Exception XMLException | |
| Exception UnresolvedEntityException | |
| Exception XmlException | |
| Exception InvalidEventStream | |
| Exception TimeoutTriggered | |
| Typeable * a => Exception (FieldException a) | |
| (Show a, Typeable * a) => Exception (ServiceError a) |
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 HttpException :: *
Instances
data Natural :: *
Instances
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 |
data RequestBody :: *
Instances
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.
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.
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
class IsString a where
Class for string-like datastructures; used by the overloaded string extension (-XOverloadedStrings in GHC).
Methods
fromString :: String -> a
Instances
| IsString Builder | |
| IsString ByteString | |
| IsString ShortByteString | |
| IsString ByteString | |
| IsString Doc | |
| IsString Text | |
| IsString Text | |
| IsString Builder | |
| IsString Request | |
| IsString Value | |
| IsString RqBody | |
| IsString Query | |
| IsString FilePath | |
| IsString Name | |
| IsString Action | |
| IsString SecurityToken | |
| IsString SecretKey | |
| IsString AccessKey | |
| IsString ErrorCode | |
| IsString [Char] | |
| (~) * a Text => IsString (Parser a) | |
| (IsString s, FoldCase s) => IsString (CI s) | |
| IsString (DList Char) | |
| (~) * a ByteString => IsString (Parser a) | |
| IsString a => IsString (Sensitive a) |
class Semigroup a
Instances
Retries
Constants and predicates used to create a RetryPolicy.
Constructors
| Exponential | |
Fields
| |
Errors
Methods
awsError :: a -> ServiceError String Source
Instances
| Show a => AWSError (ServiceError a) |
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 |
restError :: FromXML (Er a) => (Status -> Bool) -> Service a -> Status -> Maybe (ByteString -> ServiceError (Er a)) Source
jsonError :: FromJSON (Er a) => (Status -> Bool) -> Service a -> Status -> Maybe (ByteString -> ServiceError (Er a)) Source
statusSuccess :: Status -> Bool Source
Shared
Attributes specific to an AWS service.
Constructors
| Service | |
Fields
| |
HTTP
data StdMethod :: *
data Status :: *
Constructors
| Status | |
Fields
| |