module Test.Hspec.Expectations (
Expectation
, expectationFailure
, shouldBe
, shouldSatisfy
, shouldStartWith
, shouldEndWith
, shouldContain
, shouldMatchList
, shouldReturn
, shouldNotBe
, shouldNotSatisfy
, shouldNotContain
, shouldNotReturn
, shouldThrow
, Selector
, anyException
, anyErrorCall
, anyIOException
, anyArithException
, errorCall
, HasCallStack
) where
import qualified Test.HUnit
import Test.HUnit ((@?=))
import Control.Exception
import Data.Typeable
import Data.List
import Control.Monad (unless)
import Test.Hspec.Expectations.Matcher
#if MIN_VERSION_HUnit(1,4,0)
import Data.CallStack (HasCallStack)
#else
#if MIN_VERSION_base(4,8,1)
import qualified GHC.Stack as GHC
type HasCallStack = (?loc :: GHC.CallStack)
#else
import GHC.Exts (Constraint)
type HasCallStack = (() :: Constraint)
#endif
#endif
type Expectation = Test.HUnit.Assertion
expectationFailure :: HasCallStack => String -> Expectation
expectationFailure = Test.HUnit.assertFailure
expectTrue :: HasCallStack => String -> Bool -> Expectation
expectTrue msg b = unless b (expectationFailure msg)
infix 1 `shouldBe`, `shouldSatisfy`, `shouldStartWith`, `shouldEndWith`, `shouldContain`, `shouldMatchList`, `shouldReturn`, `shouldThrow`
infix 1 `shouldNotBe`, `shouldNotSatisfy`, `shouldNotContain`, `shouldNotReturn`
shouldBe :: (HasCallStack, Show a, Eq a) => a -> a -> Expectation
actual `shouldBe` expected = actual @?= expected
shouldSatisfy :: (HasCallStack, Show a) => a -> (a -> Bool) -> Expectation
v `shouldSatisfy` p = expectTrue ("predicate failed on: " ++ show v) (p v)
compareWith :: (HasCallStack, Show a) => (a -> a -> Bool) -> String -> a -> a -> Expectation
compareWith comparator errorDesc result expected = expectTrue errorMsg (comparator expected result)
where
errorMsg = show result ++ " " ++ errorDesc ++ " " ++ show expected
shouldStartWith :: (HasCallStack, Show a, Eq a) => [a] -> [a] -> Expectation
shouldStartWith = compareWith isPrefixOf "does not start with"
shouldEndWith :: (HasCallStack, Show a, Eq a) => [a] -> [a] -> Expectation
shouldEndWith = compareWith isSuffixOf "does not end with"
shouldContain :: (HasCallStack, Show a, Eq a) => [a] -> [a] -> Expectation
shouldContain = compareWith isInfixOf "does not contain"
shouldMatchList :: (HasCallStack, Show a, Eq a) => [a] -> [a] -> Expectation
xs `shouldMatchList` ys = maybe (return ()) expectationFailure (matchList xs ys)
shouldReturn :: (HasCallStack, Show a, Eq a) => IO a -> a -> Expectation
action `shouldReturn` expected = action >>= (`shouldBe` expected)
shouldNotBe :: (HasCallStack, Show a, Eq a) => a -> a -> Expectation
actual `shouldNotBe` notExpected = expectTrue ("not expected: " ++ show actual) (actual /= notExpected)
shouldNotSatisfy :: (HasCallStack, Show a) => a -> (a -> Bool) -> Expectation
v `shouldNotSatisfy` p = expectTrue ("predicate succeeded on: " ++ show v) ((not . p) v)
shouldNotContain :: (HasCallStack, Show a, Eq a) => [a] -> [a] -> Expectation
list `shouldNotContain` sublist = expectTrue errorMsg ((not . isInfixOf sublist) list)
where
errorMsg = show list ++ " does contain " ++ show sublist
shouldNotReturn :: (HasCallStack, Show a, Eq a) => IO a -> a -> Expectation
action `shouldNotReturn` notExpected = action >>= (`shouldNotBe` notExpected)
type Selector a = (a -> Bool)
shouldThrow :: (HasCallStack, Exception e) => IO a -> Selector e -> Expectation
action `shouldThrow` p = do
r <- try action
case r of
Right _ ->
expectationFailure $
"did not get expected exception: " ++ exceptionType
Left e ->
(`expectTrue` p e) $
"predicate failed on expected exception: " ++ exceptionType ++ " (" ++ show e ++ ")"
where
exceptionType = (show . typeOf . instanceOf) p
where
instanceOf :: Selector a -> a
instanceOf _ = error "Test.Hspec.Expectations.shouldThrow: broken Typeable instance"
anyException :: Selector SomeException
anyException = const True
anyErrorCall :: Selector ErrorCall
anyErrorCall = const True
errorCall :: String -> Selector ErrorCall
#if MIN_VERSION_base(4,9,0)
errorCall s (ErrorCallWithLocation msg _) = s == msg
#else
errorCall s (ErrorCall msg) = s == msg
#endif
anyIOException :: Selector IOException
anyIOException = const True
anyArithException :: Selector ArithException
anyArithException = const True