hspec2-0.4.0: Alpha version of Hspec 2.0

Stabilitystable
Safe HaskellNone

Test.Hspec

Contents

Description

Hspec is a testing library for Haskell.

This is the library reference for Hspec. The User's Manual contains more in-depth documentation.

Synopsis

Types

type SpecWith a = SpecM a ()Source

type ActionWith a = a -> IO ()Source

An IO action that expects an argument of type a.

class Example e Source

A type class for examples.

Associated Types

type Arg e Source

Setting expectations

Defining a spec

describe :: String -> SpecWith a -> SpecWith aSource

Combine a list of specs into a larger spec.

context :: String -> SpecWith a -> SpecWith aSource

An alias for describe.

it :: Example e => String -> e -> SpecWith (Arg e)Source

Create 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) == 1

example :: Expectation -> ExpectationSource

This 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

pending :: ExpectationSource

Specifies a pending example.

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" $
     pending

pendingWith :: String -> ExpectationSource

Specifies a pending example with a reason for why it's pending.

 describe "fancyFormatter" $ do
   it "can format text in a way that everyone likes" $
     pendingWith "waiting for clarification from the designers"

before :: IO a -> SpecWith a -> SpecSource

Run a custom action before every spec item.

beforeWith :: (b -> IO a) -> SpecWith a -> SpecWith bSource

Run a custom action before every spec item.

beforeAll :: IO a -> SpecWith a -> SpecWith ()Source

Run a custom action before all spec items.

beforeAllWith :: (b -> IO a) -> SpecWith a -> SpecWith bSource

Run a custom action before all spec items.

after :: ActionWith a -> SpecWith a -> SpecWith aSource

Run a custom action after every spec item.

after_ :: IO () -> Spec -> SpecSource

Run a custom action after every spec item.

around :: (ActionWith a -> IO ()) -> SpecWith a -> SpecSource

Run a custom action before and/or after every spec item.

around_ :: (IO () -> IO ()) -> Spec -> SpecSource

Run a custom action before and/or after every spec item.

aroundWith :: (ActionWith a -> ActionWith b) -> SpecWith a -> SpecWith bSource

Run a custom action before and/or after every spec item.

parallel :: SpecWith a -> SpecWith aSource

Run examples of given spec in parallel.

runIO :: IO r -> SpecM a rSource

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).

Running a spec

hspec :: Spec -> IO ()Source

Run given spec and write a report to stdout. Exit with exitFailure if at least one spec item fails.