hspec-core-2.6.1: 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

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.

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.

focus :: SpecWith a -> SpecWith a Source #

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

fit is an alias for fmap focus . it

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

fspecify is an alias for fit.

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

fdescribe is an alias for fmap focus . describe

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

fcontext is an alias for fdescribe.

parallel :: SpecWith a -> SpecWith a Source #

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

sequential :: SpecWith a -> SpecWith a Source #

sequential marks all spec items of the given spec to be evaluated sequentially.

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
Monad (SpecM a) Source # 
Instance details

Defined in Test.Hspec.Core.Spec.Monad

Methods

(>>=) :: SpecM a a0 -> (a0 -> SpecM a b) -> SpecM a b #

(>>) :: SpecM a a0 -> SpecM a b -> SpecM a b #

return :: a0 -> SpecM a a0 #

fail :: String -> SpecM a a0 #

Functor (SpecM a) Source # 
Instance details

Defined in Test.Hspec.Core.Spec.Monad

Methods

fmap :: (a0 -> b) -> SpecM a a0 -> SpecM a b #

(<$) :: a0 -> SpecM a b -> SpecM a a0 #

Applicative (SpecM a) Source # 
Instance details

Defined in Test.Hspec.Core.Spec.Monad

Methods

pure :: a0 -> SpecM a a0 #

(<*>) :: SpecM a (a0 -> b) -> SpecM a a0 -> SpecM a b #

liftA2 :: (a0 -> b -> c) -> SpecM a a0 -> SpecM a b -> SpecM a c #

(*>) :: SpecM a a0 -> SpecM a b -> SpecM a b #

(<*) :: SpecM a a0 -> SpecM a b -> SpecM a a0 #

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 #

Instances
Example Bool Source # 
Instance details

Defined in Test.Hspec.Core.Example

Associated Types

type Arg Bool :: Type Source #

Example Property Source # 
Instance details

Defined in Test.Hspec.Core.Example

Associated Types

type Arg Property :: Type Source #

Example Expectation Source # 
Instance details

Defined in Test.Hspec.Core.Example

Associated Types

type Arg Expectation :: Type Source #

Example Result Source # 
Instance details

Defined in Test.Hspec.Core.Example

Associated Types

type Arg Result :: Type Source #

Example (a -> Property) Source # 
Instance details

Defined in Test.Hspec.Core.Example

Associated Types

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

Methods

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

Example (a -> Expectation) Source # 
Instance details

Defined in Test.Hspec.Core.Example

Associated Types

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

Example (a -> Bool) Source # 
Instance details

Defined in Test.Hspec.Core.Example

Associated Types

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

Methods

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

Example (a -> Result) Source # 
Instance details

Defined in Test.Hspec.Core.Example

Associated Types

type Arg (a -> Result) :: Type Source #

Methods

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

data Params Source #

Instances
Show Params Source # 
Instance details

Defined in Test.Hspec.Core.Example

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

An IO action that expects an argument of type a

type Progress = (Int, Int) Source #

data Result Source #

The result of running an example

Constructors

Result 
Instances
Show Result Source # 
Instance details

Defined in Test.Hspec.Core.Example

Example Result Source # 
Instance details

Defined in Test.Hspec.Core.Example

Associated Types

type Arg Result :: Type Source #

Example (a -> Result) Source # 
Instance details

Defined in Test.Hspec.Core.Example

Associated Types

type Arg (a -> Result) :: Type Source #

Methods

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

type Arg Result Source # 
Instance details

Defined in Test.Hspec.Core.Example

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

Defined in Test.Hspec.Core.Example

type Arg (a -> Result) = a

data Location Source #

Location is used to represent source locations.

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
Functor (Tree c) Source # 
Instance details

Defined in Test.Hspec.Core.Tree

Methods

fmap :: (a -> b) -> Tree c a -> Tree c b #

(<$) :: a -> Tree c b -> Tree c a #

Foldable (Tree c) Source # 
Instance details

Defined in Test.Hspec.Core.Tree

Methods

fold :: Monoid m => Tree c m -> m #

foldMap :: Monoid m => (a -> m) -> Tree c a -> m #

foldr :: (a -> b -> b) -> b -> Tree c a -> b #

foldr' :: (a -> b -> b) -> b -> Tree c a -> b #

foldl :: (b -> a -> b) -> b -> Tree c a -> b #

foldl' :: (b -> a -> b) -> b -> Tree c a -> b #

foldr1 :: (a -> a -> a) -> Tree c a -> a #

foldl1 :: (a -> a -> a) -> Tree c a -> a #

toList :: Tree c a -> [a] #

null :: Tree c a -> Bool #

length :: Tree c a -> Int #

elem :: Eq a => a -> Tree c a -> Bool #

maximum :: Ord a => Tree c a -> a #

minimum :: Ord a => Tree c a -> a #

sum :: Num a => Tree c a -> a #

product :: Num a => Tree c a -> a #

Traversable (Tree c) Source # 
Instance details

Defined in Test.Hspec.Core.Tree

Methods

traverse :: Applicative f => (a -> f b) -> Tree c a -> f (Tree c b) #

sequenceA :: Applicative f => Tree c (f a) -> f (Tree c a) #

mapM :: Monad m => (a -> m b) -> Tree c a -> m (Tree c b) #

sequence :: Monad m => Tree c (m a) -> m (Tree c a) #

(Eq c, Eq a) => Eq (Tree c a) Source # 
Instance details

Defined in Test.Hspec.Core.Tree

Methods

(==) :: Tree c a -> Tree c a -> Bool #

(/=) :: Tree c a -> Tree c a -> Bool #

(Show c, Show a) => Show (Tree c a) Source # 
Instance details

Defined in Test.Hspec.Core.Tree

Methods

showsPrec :: Int -> Tree c a -> ShowS #

show :: Tree c a -> String #

showList :: [Tree c a] -> ShowS #

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

specGroup :: HasCallStack => String -> [SpecTree a] -> SpecTree a Source #

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

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

The specItem function creates a spec item.

bimapTree :: (a -> b) -> (c -> d) -> Tree a c -> Tree b d Source #