Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Control.Monad.AWS
Contents
Synopsis
- class Monad m => MonadAWS m where
- sendEither :: (AWSRequest a, Typeable a, Typeable (AWSResponse a)) => a -> m (Either Error (AWSResponse a))
- awaitEither :: (AWSRequest a, Typeable a) => Wait a -> a -> m (Either Error Accept)
- withAuth :: (AuthEnv -> m a) -> m a
- localEnv :: (Env -> Env) -> m a -> m a
- send :: (MonadIO m, MonadAWS m, AWSRequest a, Typeable a, Typeable (AWSResponse a)) => a -> m (AWSResponse a)
- paginate :: (MonadIO m, MonadAWS m, AWSPager a, Typeable a, Typeable (AWSResponse a)) => a -> ConduitM () (AWSResponse a) m ()
- paginateEither :: (MonadAWS m, AWSPager a, Typeable a, Typeable (AWSResponse a)) => a -> ConduitM () (AWSResponse a) m (Either Error ())
- await :: (MonadIO m, MonadAWS m, AWSRequest a, Typeable a) => Wait a -> a -> m Accept
- data EnvT m a
- runEnvT :: MonadUnliftIO m => EnvT m a -> Env -> m a
- data MockT m a
- runMockT :: MockT m a -> m a
Documentation
class Monad m => MonadAWS m where Source #
Typeclass for making AWS requests via Amazonka
For out-of-the-box transformers, see:
For DerivingVia
usage, see:
Methods
sendEither :: (AWSRequest a, Typeable a, Typeable (AWSResponse a)) => a -> m (Either Error (AWSResponse a)) Source #
The type-class version of sendEither
.
Since: 0.1.0.0
awaitEither :: (AWSRequest a, Typeable a) => Wait a -> a -> m (Either Error Accept) Source #
The type-class version of awaitEither
.
Since: 0.1.0.0
withAuth :: (AuthEnv -> m a) -> m a Source #
Supply the current credentials to the given action.
Since: 0.1.1.0
Instances
send :: (MonadIO m, MonadAWS m, AWSRequest a, Typeable a, Typeable (AWSResponse a)) => a -> m (AWSResponse a) Source #
Version of send
built on our sendEither
Since: 0.1.0.0
paginate :: (MonadIO m, MonadAWS m, AWSPager a, Typeable a, Typeable (AWSResponse a)) => a -> ConduitM () (AWSResponse a) m () Source #
Version of paginate
built on our paginateEither
Since: 0.1.0.0
paginateEither :: (MonadAWS m, AWSPager a, Typeable a, Typeable (AWSResponse a)) => a -> ConduitM () (AWSResponse a) m (Either Error ()) Source #
Version of paginateEither
built on our sendEither
Since: 0.1.0.0
await :: (MonadIO m, MonadAWS m, AWSRequest a, Typeable a) => Wait a -> a -> m Accept Source #
Version of await
built on our awaitEither
Since: 0.1.0.0
Concrete transformers
Since: 0.1.0.0
Instances
Since: 0.1.0.0
Instances
Monad m => MonadReader Matchers (MockT m) Source # | |
MonadIO m => MonadAWS (MockT m) Source # | |
Defined in Control.Monad.AWS.MockT Methods sendEither :: (AWSRequest a, Typeable a, Typeable (AWSResponse a)) => a -> MockT m (Either Error (AWSResponse a)) Source # awaitEither :: (AWSRequest a, Typeable a) => Wait a -> a -> MockT m (Either Error Accept) Source # | |
MonadIO m => MonadIO (MockT m) Source # | |
Defined in Control.Monad.AWS.MockT | |
Applicative m => Applicative (MockT m) Source # | |
Functor m => Functor (MockT m) Source # | |
Monad m => Monad (MockT m) Source # | |
MonadUnliftIO m => MonadUnliftIO (MockT m) Source # | |
Defined in Control.Monad.AWS.MockT |