hspec-core-2.11.14: A Testing Framework for Haskell
Stabilityunstable
Safe HaskellNone
LanguageHaskell2010

Test.Hspec.Core.Spec

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

Example a optionally accepts an argument Arg a, which is then given to the test body. This is useful for provisioning resources for a test which are created and cleaned up outside the test itself. See Arg for details.

Note that this function is often on the scene of nasty type errors due to GHC failing to infer the type of do notation in the test body. It can be helpful to use TypeApplications to explicitly specify the intended Example type.

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.

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

A SpecWith that can be evaluated directly by the hspec function as it does not require any parameters.

type SpecWith a = SpecM a () Source #

A SpecWith a represents a test or group of tests that require an a value to run.

In the common case, a Spec is a SpecWith () which requires () and can thus be executed with hspec.

To supply an argument to SpecWith tests to turn them into Spec, use functions from Test.Hspec.Core.Hooks such as around, before, mapSubject and similar.

Values of this type are created by it, describe and similar.

newtype SpecM a r Source #

A writer monad for SpecTree forests.

This is used by describe and is used to construct the forest of spec items.

It allows for dynamically generated spec trees, for example, by using data obtained by performing IO actions with runIO.

Constructors

SpecM (WriterT (Endo Config, [SpecTree a]) (ReaderT Env IO) r) 

Instances

Instances details
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 #

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 #

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 #

runSpecM :: SpecWith a -> IO (Endo Config, [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 itself. 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.

mapSpecForest :: ([SpecTree a] -> [SpecTree b]) -> SpecM a r -> SpecM b r Source #

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

Deprecated: Use mapSpecItem_ instead.

modifyParams :: (Params -> Params) -> SpecWith a -> SpecWith a Source #

Modifies the Params on the spec items to be generated by SpecWith.

modifyConfig :: (Config -> Config) -> SpecWith a Source #

Since: 2.10.0

getSpecDescriptionPath :: SpecM a [String] Source #

Get the path of describe labels, from the root all the way in to the call-site of this function.

Example

Expand
>>> :{
runSpecM $ do
  describe "foo" $ do
    describe "bar" $ do
      getSpecDescriptionPath >>= runIO . print
:}
["foo","bar"]

Since: 2.10.0

A type class for examples

class Example e where Source #

A type class for examples, that is to say, test bodies as used in it and similar functions.

Associated Types

type Arg e Source #

The argument type that is needed to run this Example. If Arg is (), no argument is required and the Example can be run as-is.

The value of Arg is the difference between Spec (aka SpecWith ()), which can be executed, and SpecWith a, which cannot be executed without turning it into Spec first.

To supply an argument to examples, use the functions in Test.Hspec.Core.Hooks such as around, before, mapSubject and similar.

type Arg e = ()

Methods

evaluateExample Source #

Arguments

:: e

The example being evaluated

-> Params

QuickCheck/SmallCheck settings

-> (ActionWith (Arg e) -> IO ())

Hook: takes an ActionWith (Arg e), namely, the IO action to run the test body, obtains Arg e from somewhere, then executes the test body (or possibly decides not to execute it!).

This is used to implement around and similar hook functionality.

-> ProgressCallback

Callback for composite tests like QuickCheck to report their progress.

-> IO Result 

Evaluates an example.

evaluateExample is expected to execute the test body inside the IO action passed to the hook. It's often necessary to use an IORef to pass data out like whether the test succeeded to the outer IO action so it can be returned as a Result.

Example:

newtype MyAction = MyAction (Int -> IO Bool)

instance Example MyAction where
  type Arg MyAction = Int

  evaluateExample (MyAction act) _params hook _progress = do
    result <- newIORef (Result "" Success)
    hook $ arg -> do
      -- e.g. determines if arg is 42
      ok <- act arg
      let result' = Result "" $ if ok then Success else Failure Nothing NoReason
      writeIORef result result'
    readIORef result

Instances

Instances details
Example Property Source # 
Instance details

Defined in Test.Hspec.Core.QuickCheck

Associated Types

type Arg Property 
Instance details

Defined in Test.Hspec.Core.QuickCheck

type Arg Property = ()
Example Result Source # 
Instance details

Defined in Test.Hspec.Core.Example

Associated Types

type Arg Result 
Instance details

Defined in Test.Hspec.Core.Example

type Arg Result = ()
Example Expectation Source # 
Instance details

Defined in Test.Hspec.Core.Example

Associated Types

type Arg Expectation 
Instance details

Defined in Test.Hspec.Core.Example

type Arg Expectation = ()
Example Bool Source # 
Instance details

Defined in Test.Hspec.Core.Example

Associated Types

type Arg Bool 
Instance details

Defined in Test.Hspec.Core.Example

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

Defined in Test.Hspec.Core.QuickCheck

Associated Types

type Arg (a -> Property) 
Instance details

Defined in Test.Hspec.Core.QuickCheck

type Arg (a -> Property) = a

Methods

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

Example (a -> Result) Source # 
Instance details

Defined in Test.Hspec.Core.Example

Associated Types

type Arg (a -> Result) 
Instance details

Defined in Test.Hspec.Core.Example

type Arg (a -> Result) = a

Methods

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

Example (a -> Expectation) Source # 
Instance details

Defined in Test.Hspec.Core.Example

Associated Types

type Arg (a -> Expectation) 
Instance details

Defined in Test.Hspec.Core.Example

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

Defined in Test.Hspec.Core.Example

Associated Types

type Arg (a -> Bool) 
Instance details

Defined in Test.Hspec.Core.Example

type Arg (a -> Bool) = a

Methods

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

data Params Source #

QuickCheck and SmallCheck related parameters.

Instances

Instances details
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.

This type is what Examples are ultimately unlifted into for execution.

type Progress = (Int, Int) Source #

(CurrentItem, TotalItems) tuple.

type ProgressCallback = Progress -> IO () Source #

Callback used by composite test items that contain many tests to report their progress towards finishing them all.

This is used, for example, to report how many QuickCheck examples are finished.

data Result Source #

The result of running an example

Constructors

Result 

Instances

Instances details
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 
Instance details

Defined in Test.Hspec.Core.Example

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

Defined in Test.Hspec.Core.Example

Associated Types

type Arg (a -> Result) 
Instance details

Defined in Test.Hspec.Core.Example

type Arg (a -> Result) = a

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 (IO ()) (Item a) Source #

A tree is used to represent a spec internally. The tree is parameterized 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 (Maybe (String, Location)) c [Tree c a] 
Leaf a 

Instances

Instances details
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 #

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

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 #

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

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

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 e) => String -> e -> SpecTree (Arg e) Source #

The specItem function creates a spec item.

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

bimapForest :: (a -> b) -> (c -> d) -> [Tree a c] -> [Tree b d] Source #

filterTree :: (a -> Bool) -> Tree c a -> Maybe (Tree c a) Source #

filterForest :: (a -> Bool) -> [Tree c a] -> [Tree c a] Source #

filterTreeWithLabels :: ([String] -> a -> Bool) -> Tree c a -> Maybe (Tree c a) Source #

filterForestWithLabels :: ([String] -> a -> Bool) -> [Tree c a] -> [Tree c a] Source #

pruneTree :: Tree c a -> Maybe (Tree c a) Source #

pruneForest :: [Tree c a] -> [Tree c a] Source #

focusForest :: [SpecTree a] -> [SpecTree a] Source #

Marks an entire spec forest as focused if nothing in it is already focused.

Re-exports

type HasCallStack = ?callStack :: CallStack #

Request a CallStack.

NOTE: The implicit parameter ?callStack :: CallStack is an implementation detail and should not be considered part of the CallStack API, we may decide to change the implementation in the future.

Since: base-4.9.0.0