| Stability | stable | 
|---|---|
| Safe Haskell | None | 
| Language | Haskell2010 | 
Test.Hspec
Description
Hspec is a testing framework for Haskell.
This is the library reference for Hspec. The User's Manual contains more in-depth documentation.
- type Spec = SpecWith ()
- type SpecWith a = SpecM a ()
- type family Arg e :: *
- class Example e where
- module Test.Hspec.Expectations
- it :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a)
- specify :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a)
- describe :: String -> SpecWith a -> SpecWith a
- context :: String -> SpecWith a -> SpecWith a
- example :: Expectation -> Expectation
- parallel :: SpecWith a -> SpecWith a
- runIO :: IO r -> SpecM a r
- pending :: HasCallStack -> Expectation
- pendingWith :: HasCallStack -> String -> Expectation
- xit :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a)
- xspecify :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a)
- xdescribe :: String -> SpecWith a -> SpecWith a
- xcontext :: String -> SpecWith a -> SpecWith a
- type ActionWith a = a -> IO ()
- before :: IO a -> SpecWith a -> Spec
- before_ :: IO () -> SpecWith a -> SpecWith a
- beforeWith :: (b -> IO a) -> SpecWith a -> SpecWith b
- beforeAll :: IO a -> SpecWith a -> Spec
- beforeAll_ :: IO () -> SpecWith a -> SpecWith a
- after :: ActionWith a -> SpecWith a -> SpecWith a
- after_ :: IO () -> SpecWith a -> SpecWith a
- afterAll :: ActionWith a -> SpecWith a -> SpecWith a
- afterAll_ :: IO () -> SpecWith a -> SpecWith a
- around :: (ActionWith a -> IO ()) -> SpecWith a -> Spec
- around_ :: (IO () -> IO ()) -> SpecWith a -> SpecWith a
- aroundWith :: (ActionWith a -> ActionWith b) -> SpecWith a -> SpecWith b
- hspec :: Spec -> IO ()
Types
A type class for examples
Minimal complete definition
Setting expectations
module Test.Hspec.Expectations
Defining a spec
it :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a) #
The it function creates a spec item.
A spec item consists of:
- a textual description of a desired behavior
- an example for that behavior
describe "absolute" $ do
  it "returns a positive number when given a negative number" $
    absolute (-1) == 1specify :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a) #
specify is an alias for it.
describe :: String -> SpecWith a -> SpecWith a #
The describe function combines a list of specs into a larger spec.
example :: Expectation -> Expectation Source #
example is a type restricted version of id.  It can be used to get better
 error messages on type mismatches.
Compare e.g.
it "exposes some behavior" $ example $ do putStrLn
with
it "exposes some behavior" $ do putStrLn
parallel :: SpecWith a -> SpecWith a #
parallel marks all spec items of the given spec to be safe for parallel
 evaluation.
Run an IO action while constructing the spec tree.
SpecM is a monad to construct a spec tree, without executing any spec
 items.  runIO allows you to run IO actions during this construction phase.
 The IO action is always run when the spec tree is constructed (e.g. even
 when --dry-run is specified).
 If you do not need the result of the IO action to construct the spec tree,
 beforeAll may be more suitable for your use case.
Pending spec items
During a test run a pending spec item is:
- not executed
- reported as "pending"
pending :: HasCallStack -> Expectation #
pending can be used to mark a spec item as pending.
If you want to textually specify a behavior but do not have an example yet, use this:
describe "fancyFormatter" $ do
  it "can format text in a way that everyone likes" $
    pendingpendingWith :: HasCallStack -> String -> Expectation #
pendingWith is similar to pending, but it takes an additional string
 argument that can be used to specify the reason for why the spec item is pending.
xspecify :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a) #
xspecify is an alias for xit.
Hooks
type ActionWith a = a -> IO () #
An IO action that expects an argument of type a
beforeWith :: (b -> IO a) -> SpecWith a -> SpecWith b #
Run a custom action before every spec item.
beforeAll_ :: IO () -> SpecWith a -> SpecWith a #
Run a custom action before the first spec item.
after :: ActionWith a -> SpecWith a -> SpecWith a #
Run a custom action after every spec item.
afterAll :: ActionWith a -> SpecWith a -> SpecWith a #
Run a custom action after the last spec item.
around :: (ActionWith a -> IO ()) -> SpecWith a -> Spec #
Run a custom action before and/or after every spec item.
around_ :: (IO () -> IO ()) -> SpecWith a -> SpecWith a #
Run a custom action before and/or after every spec item.
aroundWith :: (ActionWith a -> ActionWith b) -> SpecWith a -> SpecWith b #
Run a custom action before and/or after every spec item.