hspec-2.7.10: A Testing Framework for Haskell
Stabilitystable
Safe HaskellNone
LanguageHaskell2010

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.

Synopsis

Types

type Spec = SpecWith () #

type SpecWith a = SpecM a () #

type family Arg e #

Instances

Instances details
type Arg Bool 
Instance details

Defined in Test.Hspec.Core.Example

type Arg Bool = ()
type Arg Property 
Instance details

Defined in Test.Hspec.Core.Example

type Arg Property = ()
type Arg Result 
Instance details

Defined in Test.Hspec.Core.Example

type Arg Result = ()
type Arg Expectation 
Instance details

Defined in Test.Hspec.Core.Example

type Arg Expectation = ()
type Arg (a -> Property) 
Instance details

Defined in Test.Hspec.Core.Example

type Arg (a -> Property) = a
type Arg (a -> Expectation) 
Instance details

Defined in Test.Hspec.Core.Example

type Arg (a -> Expectation) = a
type Arg (a -> Bool) 
Instance details

Defined in Test.Hspec.Core.Example

type Arg (a -> Bool) = a
type Arg (a -> Result) 
Instance details

Defined in Test.Hspec.Core.Example

type Arg (a -> Result) = a

class Example e #

A type class for examples

Minimal complete definition

evaluateExample

Instances

Instances details
Example Bool 
Instance details

Defined in Test.Hspec.Core.Example

Associated Types

type Arg Bool #

Example Property 
Instance details

Defined in Test.Hspec.Core.Example

Associated Types

type Arg Property #

Example Result 
Instance details

Defined in Test.Hspec.Core.Example

Associated Types

type Arg Result #

Example Expectation 
Instance details

Defined in Test.Hspec.Core.Example

Associated Types

type Arg Expectation #

Example (a -> Result) 
Instance details

Defined in Test.Hspec.Core.Example

Associated Types

type Arg (a -> Result) #

Methods

evaluateExample :: (a -> Result) -> Params -> (ActionWith (Arg (a -> Result)) -> IO ()) -> ProgressCallback -> IO Result #

Example (a -> Bool) 
Instance details

Defined in Test.Hspec.Core.Example

Associated Types

type Arg (a -> Bool) #

Methods

evaluateExample :: (a -> Bool) -> Params -> (ActionWith (Arg (a -> Bool)) -> IO ()) -> ProgressCallback -> IO Result #

Example (a -> Expectation) 
Instance details

Defined in Test.Hspec.Core.Example

Associated Types

type Arg (a -> Expectation) #

Methods

evaluateExample :: (a -> Expectation) -> Params -> (ActionWith (Arg (a -> Expectation)) -> IO ()) -> ProgressCallback -> IO Result #

Example (a -> Property) 
Instance details

Defined in Test.Hspec.Core.Example

Associated Types

type Arg (a -> Property) #

Methods

evaluateExample :: (a -> Property) -> Params -> (ActionWith (Arg (a -> Property)) -> IO ()) -> ProgressCallback -> IO Result #

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

specify :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a) #

specify is an alias for it.

describe :: HasCallStack => String -> SpecWith a -> SpecWith a #

The describe function combines a list of specs into a larger spec.

context :: HasCallStack => String -> SpecWith a -> SpecWith a #

context is an alias for describe.

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.

runIO :: IO r -> SpecM a r #

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:

  1. not executed
  2. 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" $
    pending

pendingWith :: 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.

xit :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a) #

Changing it to xit marks the corresponding spec item as pending.

This can be used to temporarily disable a spec item.

xspecify :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a) #

xspecify is an alias for xit.

xdescribe :: HasCallStack => String -> SpecWith a -> SpecWith a #

Changing describe to xdescribe marks all spec items of the corresponding subtree as pending.

This can be used to temporarily disable spec items.

xcontext :: HasCallStack => String -> SpecWith a -> SpecWith a #

xcontext is an alias for xdescribe.

Focused spec items

During a test run, when a spec contains focused spec items, all other spec items are ignored.

focus :: SpecWith a -> SpecWith a #

focus focuses all spec items of the given spec.

Applying focus to a spec with focused spec items has no effect.

fit :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a) #

fit is an alias for fmap focus . it

fspecify :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a) #

fspecify is an alias for fit.

fdescribe :: HasCallStack => String -> SpecWith a -> SpecWith a #

fdescribe is an alias for fmap focus . describe

fcontext :: HasCallStack => String -> SpecWith a -> SpecWith a #

fcontext is an alias for fdescribe.

Hooks

type ActionWith a = a -> IO () #

An IO action that expects an argument of type a

before :: IO a -> SpecWith a -> Spec #

Run a custom action before every spec item.

before_ :: IO () -> SpecWith a -> SpecWith a #

Run a custom action before every spec item.

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

Run a custom action before every spec item.

beforeAll :: IO a -> SpecWith a -> Spec #

Run a custom action before the first spec item.

beforeAll_ :: IO () -> SpecWith a -> SpecWith a #

Run a custom action before the first spec item.

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

Run a custom action with an argument before the first spec item.

after :: ActionWith a -> SpecWith a -> SpecWith a #

Run a custom action after every spec item.

after_ :: IO () -> 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.

afterAll_ :: IO () -> 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.

aroundAll :: (ActionWith a -> IO ()) -> SpecWith a -> Spec #

Wrap an action around the given spec.

aroundAllWith :: (ActionWith a -> ActionWith b) -> SpecWith a -> SpecWith b #

Wrap an action around the given spec. Changes the arg type inside.

Running a spec

hspec :: Spec -> IO () #

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

Note: hspec handles command-line options and reads config files. This is not always desired. Use runSpec if you need more control over these aspects.