hspec-1.9.2: Behavior-Driven Development for Haskell

Stabilityexperimental
Safe HaskellNone

Test.Hspec.Formatters

Contents

Description

This module contains formatters that can be used with hspecWith.

Synopsis

Formatters

Implementing a custom Formatter

A formatter is a set of actions. Each action is evaluated when a certain situation is encountered during a test run.

Actions live in the FormatM monad. It provides access to the runner state and primitives for appending to the generated report.

data Formatter Source

Constructors

Formatter 

Fields

headerFormatter :: FormatM ()
 
exampleGroupStarted :: Int -> [String] -> String -> FormatM ()

evaluated before each test group

The given number indicates the position within the parent group.

exampleGroupDone :: FormatM ()
 
exampleProgress :: Handle -> Path -> Progress -> IO ()

used to notify the progress of the currently evaluated example

NOTE: This is only called when interactive/color mode.

exampleSucceeded :: Path -> FormatM ()

evaluated after each successful example

exampleFailed :: Path -> Either SomeException String -> FormatM ()

evaluated after each failed example

examplePending :: Path -> Maybe String -> FormatM ()

evaluated after each pending example

failedFormatter :: FormatM ()

evaluated after a test run

footerFormatter :: FormatM ()

evaluated after failuresFormatter

Accessing the runner state

getSuccessCount :: FormatM IntSource

Get the number of successful examples encountered so far.

getPendingCount :: FormatM IntSource

Get the number of pending examples encountered so far.

getFailCount :: FormatM IntSource

Get the number of failed examples encountered so far.

getTotalCount :: FormatM IntSource

Get the total number of examples encountered so far.

getFailMessages :: FormatM [FailureRecord]Source

Get the list of accumulated failure messages.

usedSeed :: FormatM IntegerSource

The random seed that is used for QuickCheck.

getCPUTime :: FormatM (Maybe Double)Source

Get the used CPU time since the test run has been started.

getRealTime :: FormatM DoubleSource

Get the passed real time since the test run has been started.

Appending to the gerenated report

write :: String -> FormatM ()Source

Append some output to the report.

writeLine :: String -> FormatM ()Source

The same as write, but adds a newline character.

newParagraph :: FormatM ()Source

Append an empty line to the report.

Calling this multiple times has the same effect as calling it once.

Dealing with colors

withSuccessColor :: FormatM a -> FormatM aSource

Set output to color green, run given action, and finally restore the default color.

withPendingColor :: FormatM a -> FormatM aSource

Set output color to yellow, run given action, and finally restore the default color.

withFailColor :: FormatM a -> FormatM aSource

Set output color to red, run given action, and finally restore the default color.

Helpers

formatException :: SomeException -> StringSource

Convert an exception to a string.

The type of the exception is included. Here is an example:

>>> import Control.Applicative
>>> import Control.Exception
>>> either formatException show <$> (try . evaluate) (1 `div` 0)
"ArithException (divide by zero)"

Using custom formatters with hspec-discover

Anything that is an instance of IsFormatter can be used by hspec-discover as the default formatter for a spec. If you have a formatter myFormatter in the module Custom.Formatters you can use it by passing an additional argument to hspec-discover.

{-# OPTIONS_GHC -F -pgmF hspec-discover -optF --formatter=Custom.Formatters.myFormatter #-}