hspec-expectations-lifted-0.10.0: A version of hspec-expectations generalized to MonadIO

Safe HaskellSafe
LanguageHaskell98

Test.Hspec.Expectations.Lifted

Contents

Description

Synopsis

Setting expectations

shouldBe :: (HasCallStack, MonadIO m, Show a, Eq a) => a -> a -> m () infix 1 Source #

actual `shouldBe` expected sets the expectation that actual is equal to expected.

shouldSatisfy :: (HasCallStack, MonadIO m, Show a) => a -> (a -> Bool) -> m () infix 1 Source #

v `shouldSatisfy` p sets the expectation that p v is True.

shouldStartWith :: (HasCallStack, MonadIO m, Show a, Eq a) => [a] -> [a] -> m () infix 1 Source #

list `shouldStartWith` prefix sets the expectation that list starts with prefix,

shouldEndWith :: (HasCallStack, MonadIO m, Show a, Eq a) => [a] -> [a] -> m () infix 1 Source #

list `shouldEndWith` suffix sets the expectation that list ends with suffix,

shouldContain :: (HasCallStack, MonadIO m, Show a, Eq a) => [a] -> [a] -> m () infix 1 Source #

list `shouldContain` sublist sets the expectation that sublist is contained, wholly and intact, anywhere in list.

shouldMatchList :: (HasCallStack, MonadIO m, Show a, Eq a) => [a] -> [a] -> m () infix 1 Source #

xs `shouldMatchList` ys sets the expectation that xs has the same elements that ys has, possibly in another order

shouldReturn :: (HasCallStack, MonadIO m, Show a, Eq a) => m a -> a -> m () infix 1 Source #

action `shouldReturn` expected sets the expectation that action returns expected.

shouldNotBe :: (HasCallStack, MonadIO m, Show a, Eq a) => a -> a -> m () infix 1 Source #

actual `shouldNotBe` notExpected sets the expectation that actual is not equal to notExpected

shouldNotSatisfy :: (HasCallStack, MonadIO m, Show a) => a -> (a -> Bool) -> m () infix 1 Source #

v `shouldNotSatisfy` p sets the expectation that p v is False.

shouldNotContain :: (HasCallStack, MonadIO m, Show a, Eq a) => [a] -> [a] -> m () infix 1 Source #

list `shouldNotContain` sublist sets the expectation that sublist is not contained anywhere in list.

shouldNotReturn :: (HasCallStack, MonadIO m, Show a, Eq a) => m a -> a -> m () infix 1 Source #

action `shouldNotReturn` notExpected sets the expectation that action does not return notExpected.

Re-exports

type HasCallStack = ?callStack :: CallStack #

Request a CallStack.

NOTE: The implicit parameter ?callStack :: CallStack is an implementation detail and should not be considered part of the CallStack API, we may decide to change the implementation in the future.

Since: 4.9.0.0