Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Introductory documentation: https://github.com/sol/hspec-expectations#readme
- type Expectation = Assertion
- expectationFailure :: HasCallStack => String -> Expectation
- shouldBe :: (HasCallStack, Show a, Eq a) => a -> a -> Expectation
- shouldSatisfy :: (HasCallStack, Show a) => a -> (a -> Bool) -> Expectation
- shouldStartWith :: (HasCallStack, Show a, Eq a) => [a] -> [a] -> Expectation
- shouldEndWith :: (HasCallStack, Show a, Eq a) => [a] -> [a] -> Expectation
- shouldContain :: (HasCallStack, Show a, Eq a) => [a] -> [a] -> Expectation
- shouldMatchList :: (HasCallStack, Show a, Eq a) => [a] -> [a] -> Expectation
- shouldReturn :: (HasCallStack, Show a, Eq a) => IO a -> a -> Expectation
- shouldNotBe :: (HasCallStack, Show a, Eq a) => a -> a -> Expectation
- shouldNotSatisfy :: (HasCallStack, Show a) => a -> (a -> Bool) -> Expectation
- shouldNotContain :: (HasCallStack, Show a, Eq a) => [a] -> [a] -> Expectation
- shouldNotReturn :: (HasCallStack, Show a, Eq a) => IO a -> a -> Expectation
- shouldThrow :: (HasCallStack, 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
- type HasCallStack = ?callStack :: CallStack
Setting expectations
type Expectation = Assertion Source #
expectationFailure :: HasCallStack => String -> Expectation Source #
shouldBe :: (HasCallStack, Show a, Eq a) => a -> a -> Expectation infix 1 Source #
actual `shouldBe` expected
sets the expectation that actual
is equal
to expected
.
shouldSatisfy :: (HasCallStack, Show a) => a -> (a -> Bool) -> Expectation infix 1 Source #
v `shouldSatisfy` p
sets the expectation that p v
is True
.
shouldStartWith :: (HasCallStack, Show a, Eq a) => [a] -> [a] -> Expectation infix 1 Source #
list `shouldStartWith` prefix
sets the expectation that list
starts with prefix
,
shouldEndWith :: (HasCallStack, Show a, Eq a) => [a] -> [a] -> Expectation infix 1 Source #
list `shouldEndWith` suffix
sets the expectation that list
ends with suffix
,
shouldContain :: (HasCallStack, Show a, Eq a) => [a] -> [a] -> Expectation infix 1 Source #
list `shouldContain` sublist
sets the expectation that sublist
is contained,
wholly and intact, anywhere in list
.
shouldMatchList :: (HasCallStack, Show a, Eq a) => [a] -> [a] -> Expectation infix 1 Source #
xs `shouldMatchList` ys
sets the expectation that xs
has the same
elements that ys
has, possibly in another order
shouldReturn :: (HasCallStack, Show a, Eq a) => IO a -> a -> Expectation infix 1 Source #
action `shouldReturn` expected
sets the expectation that action
returns expected
.
shouldNotBe :: (HasCallStack, Show a, Eq a) => a -> a -> Expectation infix 1 Source #
actual `shouldNotBe` notExpected
sets the expectation that actual
is not
equal to notExpected
shouldNotSatisfy :: (HasCallStack, Show a) => a -> (a -> Bool) -> Expectation infix 1 Source #
v `shouldNotSatisfy` p
sets the expectation that p v
is False
.
shouldNotContain :: (HasCallStack, Show a, Eq a) => [a] -> [a] -> Expectation infix 1 Source #
list `shouldNotContain` sublist
sets the expectation that sublist
is not
contained anywhere in list
.
shouldNotReturn :: (HasCallStack, Show a, Eq a) => IO a -> a -> Expectation infix 1 Source #
action `shouldNotReturn` notExpected
sets the expectation that action
does not return notExpected
.
Expecting exceptions
shouldThrow :: (HasCallStack, Exception e) => IO a -> Selector e -> Expectation infix 1 Source #
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 -> Bool Source #
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).
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