Safe Haskell | None |
---|
Introductory documentation: https://github.com/sol/hspec-expectations#readme
- type Expectation = Assertion
- expectationFailure :: String -> Expectation
- shouldBe :: (Show a, Eq a) => a -> a -> Expectation
- shouldSatisfy :: Show a => a -> (a -> Bool) -> Expectation
- shouldContain :: (Show a, Eq a) => [a] -> [a] -> Expectation
- shouldReturn :: (Show a, Eq a) => IO a -> a -> Expectation
- shouldThrow :: Exception e => IO a -> Selector e -> Expectation
- type Selector a = a -> Bool
- anyException :: Selector SomeException
- anyErrorCall :: Selector ErrorCall
- anyIOException :: Selector IOException
- anyArithException :: Selector ArithException
- errorCall :: String -> Selector ErrorCall
Setting expectations
type Expectation = AssertionSource
expectationFailure :: String -> ExpectationSource
This is just an alias for HUnit's assertFailure
.
shouldBe :: (Show a, Eq a) => a -> a -> ExpectationSource
actual `shouldBe` expected
sets the expectation that actual
is equal
to expected
(this is just an alias for @?=
).
shouldSatisfy :: Show a => a -> (a -> Bool) -> ExpectationSource
v `shouldSatisfy` p
sets the expectation that p v
is True
.
shouldContain :: (Show a, Eq a) => [a] -> [a] -> ExpectationSource
list `shouldContain` sublist
sets the expectation that sublist
is contained,
wholly and intact, anywhere in the second.
shouldReturn :: (Show a, Eq a) => IO a -> a -> ExpectationSource
action `shouldReturn` expected
sets the expectation that action
returns expected
.
Expecting exceptions
shouldThrow :: Exception e => IO a -> Selector e -> ExpectationSource
action `shouldThrow` selector
sets the expectation that action
throws
an exception. The precise nature of the expected exception is described
with a Selector
.
Selecting exceptions
type Selector a = a -> BoolSource
A Selector
is a predicate; it can simultaneously constrain the type and
value of an exception.
Predefined type-based selectors
There are predefined selectors for some standard exceptions. Each selector
is just const True
with an appropriate type.
Combinators for defining value-based selectors
Some exceptions (most prominently ErrorCall
) have no Eq
instance.
Selecting a specific value would require pattern matching.
For such exceptions, combinators that construct selectors are provided. Each combinator corresponds to a constructor; it takes the same arguments, and has the same name (but starting with a lower-case letter).