Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Control.Monad.AWS.ViaMock
Description
DerivingVia
machinery for mocking AWS interactions in tests
This module assumes your specs run in a custom transformer that can provide a
reader environment. If you define HasMatchers
for that environment, you can
then derive MonadAWS
for this transformer via MockAWS
.
For a more explicit alternative, see Control.Monad.AWS.MockT.
Example:
Assuming you have some implementation you wanted to test:
getBucketsByPrefix :: (MonadIO m, MonadAWS) m => Text -> m [Bucket]
getBucketsByPrefix p = do
resp <- send newListBuckets
pure
$ maybe [] (filter matchesPrefix)
$ resp ^. listBucketsResponse_buckets
where
matchesPrefix b = p isPrefixOf
toText (b ^. bucket_name)
And assuming you've set up your example monad with MonadAWS
via MockAWS
,
you can now test it without talking to AWS:
describe "getBucketsByPrefix" $ do
it "works" $ do
now <- getCurrentTime
let
bucketA = newBucket now "a-bucket"
bucketB = newBucket now "b-bucket"
bucketC = newBucket now "c-bucket"
buckets = [bucketA, bucketB, bucketC]
matcher =
SendMatcher (== newListBuckets)
$ Right
$ newListBucketsResponse 200
& listBucketsResponse_buckets ?~ buckets
withMatcher matcher $ do
buckets <- getBucketsByPrefix "b-"
buckets shouldBe
[bucketB]
Synopsis
- data Matchers
- class HasMatchers env where
- 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
- newtype MockAWS m a = MockAWS {
- unMockAWS :: m a
Documentation
Since: 0.1.0.0
class HasMatchers env where Source #
Since: 0.1.0.0
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
Since: 0.1.0.0
Instances
MonadReader env m => MonadReader env (MockAWS m) Source # | |
(MonadIO m, MonadReader env m, HasMatchers env) => MonadAWS (MockAWS m) Source # | |
Defined in Control.Monad.AWS.ViaMock Methods sendEither :: (AWSRequest a, Typeable a, Typeable (AWSResponse a)) => a -> MockAWS m (Either Error (AWSResponse a)) Source # awaitEither :: (AWSRequest a, Typeable a) => Wait a -> a -> MockAWS m (Either Error Accept) Source # withAuth :: (AuthEnv -> MockAWS m a) -> MockAWS m a Source # localEnv :: (Env -> Env) -> MockAWS m a -> MockAWS m a Source # | |
MonadIO m => MonadIO (MockAWS m) Source # | |
Defined in Control.Monad.AWS.ViaMock | |
Applicative m => Applicative (MockAWS m) Source # | |
Defined in Control.Monad.AWS.ViaMock | |
Functor m => Functor (MockAWS m) Source # | |
Monad m => Monad (MockAWS m) Source # | |