Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Control.Monad.AWS.MockT
Contents
Description
Concrete reader monad over Matchers
Its MonadAWS
instance can be used in tests where you don't have or
want your own test-app transformer:
import Amazonka.S3 import Control.Monad.AWS spec :: Spec spec = do describe "someAction" $ do it "works" $ do let matcher =SendMatcher
(const_
ListBuckets True) -- match all calls $ Right $newListBucketsResponse
-- return no buckets &listBucketsResponse_buckets
?~ [] names <-runMockT
$withMatcher
matcher $ someAction namesshouldBe
[] someAction :: (MonadIO m,MonadAWS
) m => m [BucketName] someAction = do resp <-send
newListBuckets
pure $ maybe [] (map (^. bucket_name)) $ resp ^. listBucketsResponse_buckets
Synopsis
- data MockT m a
- runMockT :: MockT m a -> m a
- data Matcher where
- SendMatcher :: forall a. (AWSRequest a, Typeable a, Typeable (AWSResponse a)) => (a -> Bool) -> Either Error (AWSResponse a) -> Matcher
- AwaitMatcher :: forall a. (AWSRequest a, Typeable a) => (Wait a -> a -> Bool) -> Either Error Accept -> Matcher
- withMatcher :: (MonadReader env m, HasMatchers env) => Matcher -> m a -> m a
- withMatchers :: (MonadReader env m, HasMatchers env) => [Matcher] -> m a -> m a
Documentation
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 |
Setting up Matchers
Define a response to provide for any matched requests
Constructors
SendMatcher :: forall a. (AWSRequest a, Typeable a, Typeable (AWSResponse a)) => (a -> Bool) -> Either Error (AWSResponse a) -> Matcher | Matches calls to Since: 0.1.0.0 |
AwaitMatcher :: forall a. (AWSRequest a, Typeable a) => (Wait a -> a -> Bool) -> Either Error Accept -> Matcher | Matches calls to Since: 0.1.0.0 |
withMatcher :: (MonadReader env m, HasMatchers env) => Matcher -> m a -> m a Source #
Add a Matcher
for the duration of the block
Since: 0.1.0.0
withMatchers :: (MonadReader env m, HasMatchers env) => [Matcher] -> m a -> m a Source #
Add multiple Matcher
s for the duration of the block
Since: 0.1.0.0