hspec-api-2.11.1: A Testing Framework for Haskell
Stabilitystable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.Hspec.Api.Formatters.V2

Description

This module contains formatters that can be used with hspecWith:

import Test.Hspec
import Test.Hspec.Api.Formatters.V1

main :: IO ()
main = hspecWith (useFormatter ("my-formatter", formatter) defaultConfig) spec

formatter :: Formatter
formatter = ...

spec :: Spec
spec = ...
Synopsis

Register a formatter

registerFormatter :: (String, Formatter) -> Config -> Config Source #

Make a formatter available for use with --format.

useFormatter :: (String, Formatter) -> Config -> Config Source #

Make a formatter available for use with --format and use it by default.

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.

type Path = ([String], String) #

A Path describes the location of a spec item within a spec tree.

It consists of a list of group descriptions and a requirement description.

Since: hspec-core-2.0.0

type Progress = (Int, Int) #

data Location #

Location is used to represent source locations.

Instances

Instances details
Read Location 
Instance details

Defined in Test.Hspec.Core.Example.Location

Show Location 
Instance details

Defined in Test.Hspec.Core.Example.Location

Eq Location 
Instance details

Defined in Test.Hspec.Core.Example.Location

data Item Source #

Instances

Instances details
Show Item Source # 
Instance details

Defined in Test.Hspec.Api.Format.V1.Internal

Methods

showsPrec :: Int -> Item -> ShowS #

show :: Item -> String #

showList :: [Item] -> ShowS #

data Result Source #

Instances

Instances details
Show Result Source # 
Instance details

Defined in Test.Hspec.Api.Format.V1.Internal

data FormatM a #

Instances

Instances details
MonadIO FormatM 
Instance details

Defined in Test.Hspec.Core.Formatters.Internal

Methods

liftIO :: IO a -> FormatM a #

Applicative FormatM 
Instance details

Defined in Test.Hspec.Core.Formatters.Internal

Methods

pure :: a -> FormatM a #

(<*>) :: FormatM (a -> b) -> FormatM a -> FormatM b #

liftA2 :: (a -> b -> c) -> FormatM a -> FormatM b -> FormatM c #

(*>) :: FormatM a -> FormatM b -> FormatM b #

(<*) :: FormatM a -> FormatM b -> FormatM a #

Functor FormatM 
Instance details

Defined in Test.Hspec.Core.Formatters.Internal

Methods

fmap :: (a -> b) -> FormatM a -> FormatM b #

(<$) :: a -> FormatM b -> FormatM a #

Monad FormatM 
Instance details

Defined in Test.Hspec.Core.Formatters.Internal

Methods

(>>=) :: FormatM a -> (a -> FormatM b) -> FormatM b #

(>>) :: FormatM a -> FormatM b -> FormatM b #

return :: a -> FormatM a #

Accessing the runner state

getSuccessCount :: FormatM Int #

Get the number of successful examples encountered so far.

getPendingCount :: FormatM Int #

Get the number of pending examples encountered so far.

getFailCount :: FormatM Int #

Get the number of failed examples encountered so far.

getTotalCount :: FormatM Int #

Get the total number of examples encountered so far.

getExpectedTotalCount :: FormatM Int #

Get the number of spec items that will have been encountered when this run completes (if it is not terminated early).

Since: hspec-core-2.9.0

getFailMessages :: FormatM [FailureRecord] Source #

Get the list of accumulated failure messages.

usedSeed :: FormatM Integer #

The random seed that is used for QuickCheck.

printTimes :: FormatM Bool #

Return True if the user requested time reporting for individual spec items, False otherwise.

newtype Seconds #

Constructors

Seconds Double 

Instances

Instances details
Num Seconds 
Instance details

Defined in Test.Hspec.Core.Clock

Fractional Seconds 
Instance details

Defined in Test.Hspec.Core.Clock

Show Seconds 
Instance details

Defined in Test.Hspec.Core.Clock

PrintfArg Seconds 
Instance details

Defined in Test.Hspec.Core.Clock

Eq Seconds 
Instance details

Defined in Test.Hspec.Core.Clock

Methods

(==) :: Seconds -> Seconds -> Bool #

(/=) :: Seconds -> Seconds -> Bool #

Ord Seconds 
Instance details

Defined in Test.Hspec.Core.Clock

getCPUTime :: FormatM (Maybe Seconds) #

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

getRealTime :: FormatM Seconds #

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

Appending to the generated report

write :: String -> FormatM () #

Append some output to the report.

writeLine :: String -> FormatM () #

The same as write, but adds a newline character.

Dealing with colors

withInfoColor :: FormatM a -> FormatM a #

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

withSuccessColor :: FormatM a -> FormatM a #

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

withPendingColor :: FormatM a -> FormatM a #

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

withFailColor :: FormatM a -> FormatM a #

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

outputUnicode :: FormatM Bool #

Return True if the user requested unicode output, False otherwise.

Since: hspec-core-2.9.0

useDiff :: FormatM Bool #

Return True if the user requested colorized diffs, False otherwise.

diffContext :: FormatM (Maybe Int) #

Return the value of configDiffContext.

Since: hspec-core-2.10.6

externalDiffAction :: FormatM (Maybe (String -> String -> IO ())) #

An action for printing diffs.

The action takes expected and actual as arguments.

When this is a Just-value then it should be used instead of any built-in diff implementation. A Just-value also implies that useDiff returns True.

Since: hspec-core-2.10.6

prettyPrint :: FormatM Bool #

Return True if the user requested pretty diffs, False otherwise.

prettyPrintFunction :: FormatM (Maybe (String -> String -> (String, String))) #

Return a function for pretty-printing if the user requested pretty diffs, Nothing otherwise.

Since: hspec-core-2.10.0

extraChunk :: String -> FormatM () #

Output given chunk in red.

missingChunk :: String -> FormatM () #

Output given chunk in green.

Helpers

formatException :: SomeException -> String #

The function formatException converts an exception to a string.

This is different from show. The type of the exception is included, e.g.:

>>> formatException (toException DivideByZero)
"ArithException\ndivide by zero"

For IOExceptions the IOErrorType is included, as well.

Since: hspec-core-2.0.0

Re-exports

type SpecWith a = SpecM a () #

data Config #

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

Since: hspec-core-2.10.0