| Stability | stable |
|---|---|
| Safe Haskell | None |
| Language | Haskell2010 |
Test.Hspec.Api.Formatters.V3
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
- registerFormatter :: (String, Formatter) -> Config -> Config
- useFormatter :: (String, Formatter) -> Config -> Config
- formatterToFormat :: Formatter -> FormatConfig -> IO Format
- silent :: Formatter
- checks :: Formatter
- specdoc :: Formatter
- progress :: Formatter
- failed_examples :: Formatter
- data Formatter = Formatter {
- formatterStarted :: FormatM ()
- formatterGroupStarted :: Path -> FormatM ()
- formatterGroupDone :: Path -> FormatM ()
- formatterProgress :: Path -> Progress -> FormatM ()
- formatterItemStarted :: Path -> FormatM ()
- formatterItemDone :: Path -> Item -> FormatM ()
- formatterDone :: FormatM ()
- type Path = ([String], String)
- type Progress = (Int, Int)
- data Location = Location {}
- data Item = Item {}
- data Result
- data FailureReason
- data FormatM a
- getConfig :: FormatM FormatConfig
- getConfigValue :: (FormatConfig -> a) -> FormatM a
- data FormatConfig = FormatConfig {
- formatConfigUseColor :: Bool
- formatConfigReportProgress :: Bool
- formatConfigOutputUnicode :: Bool
- formatConfigUseDiff :: Bool
- formatConfigDiffContext :: Maybe Int
- formatConfigExternalDiff :: Maybe (String -> String -> IO ())
- formatConfigPrettyPrintFunction :: Maybe (String -> String -> (String, String))
- formatConfigFormatException :: SomeException -> String
- formatConfigPrintTimes :: Bool
- formatConfigHtmlOutput :: Bool
- formatConfigPrintCpuTime :: Bool
- formatConfigUsedSeed :: Integer
- formatConfigExpectedTotalCount :: Int
- defaultFormatConfig :: FormatConfig
- getSuccessCount :: FormatM Int
- getPendingCount :: FormatM Int
- getFailCount :: FormatM Int
- getTotalCount :: FormatM Int
- getExpectedTotalCount :: FormatM Int
- data FailureRecord = FailureRecord {}
- getFailMessages :: FormatM [FailureRecord]
- usedSeed :: FormatM Integer
- printTimes :: FormatM Bool
- newtype Seconds = Seconds Double
- getCPUTime :: FormatM (Maybe Seconds)
- getRealTime :: FormatM Seconds
- write :: String -> FormatM ()
- writeLine :: String -> FormatM ()
- writeTransient :: String -> FormatM ()
- withInfoColor :: FormatM a -> FormatM a
- withSuccessColor :: FormatM a -> FormatM a
- withPendingColor :: FormatM a -> FormatM a
- withFailColor :: FormatM a -> FormatM a
- outputUnicode :: FormatM Bool
- useDiff :: FormatM Bool
- diffContext :: FormatM (Maybe Int)
- externalDiffAction :: FormatM (Maybe (String -> String -> IO ()))
- prettyPrint :: FormatM Bool
- prettyPrintFunction :: FormatM (Maybe (String -> String -> (String, String)))
- extraChunk :: String -> FormatM ()
- missingChunk :: String -> FormatM ()
- unlessExpert :: FormatM () -> FormatM ()
- formatLocation :: Location -> String
- formatException :: SomeException -> String
- type SpecWith a = SpecM a ()
- data Config
- modifyConfig :: (Config -> Config) -> SpecWith a
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.
formatterToFormat :: Formatter -> FormatConfig -> IO Format #
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.
Constructors
| Formatter | |
Fields
| |
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
Location is used to represent source locations.
Constructors
| Location | |
Fields
| |
Constructors
| Item | |
Fields
| |
data FailureReason #
Constructors
| NoReason | |
| Reason String | |
| ColorizedReason String | |
| ExpectedButGot (Maybe String) String String | |
| Error (Maybe String) SomeException |
Instances
| Show FailureReason | |
Defined in Test.Hspec.Core.Example Methods showsPrec :: Int -> FailureReason -> ShowS # show :: FailureReason -> String # showList :: [FailureReason] -> ShowS # | |
| NFData FailureReason | |
Defined in Test.Hspec.Core.Example Methods rnf :: FailureReason -> () # | |
Instances
Accessing config values
getConfig :: FormatM FormatConfig Source #
Since: 2.11.5
getConfigValue :: (FormatConfig -> a) -> FormatM a Source #
Since: 2.11.5
data FormatConfig Source #
Since: 2.11.5
Constructors
| FormatConfig | |
Fields
| |
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
data FailureRecord #
Constructors
| FailureRecord | |
getFailMessages :: FormatM [FailureRecord] #
Get the list of accumulated failure messages.
printTimes :: FormatM Bool #
Instances
| Num Seconds | |
| Fractional Seconds | |
| Show Seconds | |
| PrintfArg Seconds | |
Defined in Test.Hspec.Core.Clock | |
| Eq Seconds | |
| Ord Seconds | |
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
writeTransient :: String -> FormatM () #
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.
diffContext :: FormatM (Maybe Int) #
Return the value of configDiffContext.
Since: hspec-core-2.10.6
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.
expert mode
unlessExpert :: FormatM () -> FormatM () #
Do nothing on `--expert`, otherwise run the given action.
Since: hspec-core-2.11.2
Helpers
formatLocation :: Location -> String #
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 () #
A represents a test or group of tests that require an SpecWith aa
value to run.
In the common case, a Spec is a which requires SpecWith ()() 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.
modifyConfig :: (Config -> Config) -> SpecWith a #
Since: hspec-core-2.10.0