hspec-meta-2.5.6: A version of Hspec which is used to test Hspec itself

Safe HaskellNone
LanguageHaskell2010

Test.Hspec.Meta

Contents

Synopsis

Types

type Spec = SpecWith () Source #

type SpecWith a = SpecM a () Source #

type family Arg e Source #

Instances
type Arg Bool Source # 
Instance details

Defined in Test.Hspec.Core.Example

type Arg Bool = ()
type Arg Property Source # 
Instance details

Defined in Test.Hspec.Core.Example

type Arg Property = ()
type Arg Expectation Source # 
Instance details

Defined in Test.Hspec.Core.Example

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

Defined in Test.Hspec.Core.Example

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

Defined in Test.Hspec.Core.Example

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

Defined in Test.Hspec.Core.Example

type Arg (a -> Bool) = a

class Example e Source #

A type class for examples

Minimal complete definition

evaluateExample

Instances
Example Bool Source # 
Instance details

Defined in Test.Hspec.Core.Example

Associated Types

type Arg Bool :: * Source #

Methods

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

Example Property Source # 
Instance details

Defined in Test.Hspec.Core.Example

Associated Types

type Arg Property :: * Source #

Methods

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

Example Expectation Source # 
Instance details

Defined in Test.Hspec.Core.Example

Associated Types

type Arg Expectation :: * Source #

Methods

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

Example (a -> Property) Source # 
Instance details

Defined in Test.Hspec.Core.Example

Associated Types

type Arg (a -> Property) :: * Source #

Methods

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

Example (a -> Expectation) Source # 
Instance details

Defined in Test.Hspec.Core.Example

Associated Types

type Arg (a -> Expectation) :: * Source #

Methods

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

Example (a -> Bool) Source # 
Instance details

Defined in Test.Hspec.Core.Example

Associated Types

type Arg (a -> Bool) :: * Source #

Methods

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

Setting expectations

Defining a spec

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

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) Source #

specify is an alias for it.

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

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

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

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 Source #

parallel marks all spec items of the given spec to be safe for parallel evaluation.

runIO :: IO r -> SpecM a r Source #

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 Source #

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 Source #

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) Source #

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) Source #

xspecify is an alias for xit.

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

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 Source #

xcontext is an alias for xdescribe.

Hooks

type ActionWith a = a -> IO () Source #

An IO action that expects an argument of type a

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

Run a custom action before every spec item.

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

Run a custom action before every spec item.

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

Run a custom action before every spec item.

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

Run a custom action before the first spec item.

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

Run a custom action before the first spec item.

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

Run a custom action after every spec item.

after_ :: IO () -> SpecWith a -> SpecWith a Source #

Run a custom action after every spec item.

afterAll :: ActionWith a -> SpecWith a -> SpecWith a Source #

Run a custom action after the last spec item.

afterAll_ :: IO () -> SpecWith a -> SpecWith a Source #

Run a custom action after the last spec item.

around :: (ActionWith a -> IO ()) -> SpecWith a -> Spec Source #

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

around_ :: (IO () -> IO ()) -> SpecWith a -> SpecWith a Source #

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

aroundWith :: (ActionWith a -> ActionWith b) -> SpecWith a -> SpecWith b Source #

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

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.

type Spec = SpecWith () Source #

hspec :: Spec -> IO () Source #

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

class IsFormatter a where Source #

Minimal complete definition

toFormatter

Methods

toFormatter :: a -> IO Formatter Source #

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

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

hspecResult :: Spec -> IO Summary Source #

Run given spec and returns a summary of the test run.

Note: hspecResult does not exit with exitFailure on failing spec items. If you need this, you have to check the Summary yourself and act accordingly.