ImpSpec-0.1.0.0: Imperative approach to testing stateful applications. ImpSpec is build on top of HSpec and QuickCheck
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.ImpSpec.Expectations.Lifted

Synopsis

Lifted Expectations

io :: IO a -> IO a Source #

Enforce the type of expectation

Useful with polymorphic expectations that are defined below.

Example

Expand

Because shouldBeExpr is polymorphic in m, compiler will choke with a unification error. This is due to the fact that hspec's it expects a polymorphic Example.

it "MyTest" $ do
  "foo" `shouldBeExpr` "bar"

However, this is easily solved by io:

it "MyTest" $ io $ do
  "foo" `shouldBeExpr` "bar"

Common

assertBool :: (HasCallStack, MonadIO m) => String -> Bool -> m () Source #

Lifted version of assertBool

assertFailure :: (HasCallStack, MonadIO m) => String -> m a Source #

Just like expectationFailure, but does not force the return type to unit. Lifted version of assertFailure

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

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

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

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

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

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

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

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

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

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 #

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 #

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

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

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 #

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

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

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 #

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

shouldThrow :: (HasCallStack, Exception e, MonadUnliftIO m) => m a -> Selector e -> m () infix 1 Source #

Lifted version of shouldThrow.

type Selector a = a -> Bool #

A Selector is a predicate; it can simultaneously constrain the type and value of an exception.

Custom

Either

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

Same as shouldBe, except it checks that the value is Right

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

Same as shouldBe, except it checks that the value is Left

expectRight :: (HasCallStack, Show a, MonadIO m) => Either a b -> m b Source #

Return value on the Right and fail otherwise. Lifted version of expectRight.

expectRightDeep :: (HasCallStack, Show a, NFData b, MonadIO m) => Either a b -> m b Source #

Same as expectRight, but also evaluate the returned value to NF

expectRightDeep_ :: (HasCallStack, Show a, NFData b, MonadIO m) => Either a b -> m () Source #

Same as expectRightDeep, but discards the result

expectLeft :: (HasCallStack, Show b, MonadIO m) => Either a b -> m a Source #

Return value on the Left and fail otherwise

expectLeftDeep :: (HasCallStack, NFData a, Show b, MonadIO m) => Either a b -> m a Source #

Same as expectLeft, but also evaluate the returned value to NF

expectLeftDeep_ :: (HasCallStack, NFData a, Show b, MonadIO m) => Either a b -> m () Source #

Same as expectLeftDeep, but discards the result

Maybe

shouldBeJust :: (HasCallStack, Show a, Eq a, MonadIO m) => Maybe a -> a -> m () Source #

Same as shouldBe, except it checks that the value is Just