hspec-core-2.1.4: A Testing Framework for Haskell

Stabilityunstable
Safe HaskellNone
LanguageHaskell2010

Test.Hspec.Core.Spec

Contents

Description

This module provides access to Hspec's internals. It is less stable than other parts of the API. For most users Test.Hspec is more suitable!

Synopsis

Defining a spec

describe :: String -> SpecWith a -> SpecWith a Source

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

it :: 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

pending :: Expectation Source

pending can be used to indicate that an example is 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 :: 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 it's pending.

parallel :: SpecWith a -> SpecWith a Source

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

The SpecM monad

type Spec = SpecWith () Source

type SpecWith a = SpecM a () Source

newtype SpecM a r Source

A writer monad for SpecTree forests

Constructors

SpecM (WriterT [SpecTree a] IO r) 

Instances

runSpecM :: SpecWith a -> IO [SpecTree a] Source

Convert a Spec to a forest of SpecTrees.

fromSpecList :: [SpecTree a] -> SpecWith a Source

Create a Spec from a forest of SpecTrees.

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.

mapSpecItem :: (ActionWith a -> ActionWith b) -> (Item a -> Item b) -> SpecWith a -> SpecWith b Source

A type class for examples

class Example e where Source

A type class for examples

Associated Types

type Arg e Source

Methods

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

type ActionWith a = a -> IO () Source

An IO action that expects an argument of type a

data Result Source

The result of running an example

Internal representation of a spec tree

type SpecTree a = Tree (ActionWith a) (Item a) Source

A tree is used to represent a spec internally. The tree is parametrize over the type of cleanup actions and the type of the actual spec items.

data Tree c a Source

Internal tree data structure

Constructors

Node String [Tree c a] 
NodeWithCleanup c [Tree c a] 
Leaf a 

Instances

data Item a Source

Item is used to represent spec items internally. A spec item consists of:

  • a textual description of a desired behavior
  • an example for that behavior
  • additional meta information

Everything that is an instance of the Example type class can be used as an example, including QuickCheck properties, Hspec expectations and HUnit assertions.

Constructors

Item 

Fields

itemRequirement :: String

Textual description of behavior

itemLocation :: Maybe Location

Source location of the spec item

itemIsParallelizable :: Bool

A flag that indicates whether it is safe to evaluate this spec item in parallel with other spec items

itemExample :: Params -> (ActionWith a -> IO ()) -> ProgressCallback -> IO Result

Example for behavior

data Location Source

Location is used to represent source locations.

Instances

data LocationAccuracy Source

A marker for source locations

Constructors

ExactLocation

The source location is accurate

BestEffort

The source location was determined on a best-effort basis and my be wrong or inaccurate

specGroup :: String -> [SpecTree a] -> SpecTree a Source

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

specItem :: Example a => String -> a -> SpecTree (Arg a) Source

The specItem function creates a spec item.