| Stability | provisional | 
|---|---|
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
Test.Hspec.Core.Runner
Description
Synopsis
- hspec :: Spec -> IO ()
- hspecWith :: Config -> Spec -> IO ()
- hspecResult :: Spec -> IO Summary
- hspecWithResult :: Config -> Spec -> IO Summary
- data Summary = Summary {- summaryExamples :: !Int
- summaryFailures :: !Int
 
- isSuccess :: Summary -> Bool
- evaluateSummary :: Summary -> IO ()
- evalSpec :: Config -> SpecWith a -> IO (Config, [SpecTree a])
- runSpecForest :: [SpecTree ()] -> Config -> IO SpecResult
- evaluateResult :: SpecResult -> IO ()
- data SpecResult
- specResultItems :: SpecResult -> [ResultItem]
- specResultSuccess :: SpecResult -> Bool
- toSummary :: SpecResult -> Summary
- data ResultItem
- resultItemPath :: ResultItem -> Path
- resultItemStatus :: ResultItem -> ResultItemStatus
- resultItemIsFailure :: ResultItem -> Bool
- data ResultItemStatus
- data Config = Config {- configIgnoreConfigFile :: Bool
- configDryRun :: Bool
- configFocusedOnly :: Bool
- configFailOnEmpty :: Bool
- configFailOnFocused :: Bool
- configFailOnPending :: Bool
- configFailOnEmptyDescription :: Bool
- configPrintSlowItems :: Maybe Int
- configPrintCpuTime :: Bool
- configFailFast :: Bool
- configRandomize :: Bool
- configSeed :: Maybe Integer
- configQuickCheckSeed :: Maybe Integer
- configFailureReport :: Maybe FilePath
- configRerun :: Bool
- configRerunAllOnSuccess :: Bool
- configFilterPredicate :: Maybe (Path -> Bool)
- configSkipPredicate :: Maybe (Path -> Bool)
- configQuickCheckMaxSuccess :: Maybe Int
- configQuickCheckMaxDiscardRatio :: Maybe Int
- configQuickCheckMaxSize :: Maybe Int
- configQuickCheckMaxShrinks :: Maybe Int
- configSmallCheckDepth :: Maybe Int
- configColorMode :: ColorMode
- configUnicodeMode :: UnicodeMode
- configDiff :: Bool
- configDiffContext :: Maybe Int
- configExternalDiff :: Maybe (Maybe Int -> String -> String -> IO ())
- configPrettyPrint :: Bool
- configPrettyPrintFunction :: Bool -> String -> String -> (String, String)
- configFormatException :: SomeException -> String
- configTimes :: Bool
- configExpertMode :: Bool
- configAvailableFormatters :: [(String, FormatConfig -> IO Format)]
- configFormat :: Maybe (FormatConfig -> IO Format)
- configFormatter :: Maybe Formatter
- configHtmlOutput :: Bool
- configConcurrentJobs :: Maybe Int
- configAnnotations :: Annotations
 
- data ColorMode
- data UnicodeMode
- type Path = ([String], String)
- defaultConfig :: Config
- registerFormatter :: (String, FormatConfig -> IO Format) -> Config -> Config
- registerDefaultFormatter :: (String, FormatConfig -> IO Format) -> Config -> Config
- configAddFilter :: (Path -> Bool) -> Config -> Config
- readConfig :: Config -> [String] -> IO Config
- runSpec :: Spec -> Config -> IO Summary
- type Spec = SpecWith ()
- type SpecWith a = SpecM a ()
Simple interface
hspec :: Spec -> IO () Source #
Run a given spec and write a report to stdout.
 Exit with exitFailure if at least one spec item fails.
Note: hspec handles command-line options and reads config files.  This
 is not always desirable.  Use evalSpec and runSpecForest if you need
 more control over these aspects.
hspecWith :: Config -> Spec -> IO () Source #
Run given spec with custom options.
 This is similar to hspec, but more flexible.
hspecResult :: Spec -> IO Summary Source #
Run given spec and returns a summary of the test run.
Note: hspecResult does not exit with exitFailure on failing spec
 items.  If you need this, you have to check the Summary yourself and act
 accordingly.
hspecWithResult :: Config -> Spec -> IO Summary Source #
Run given spec with custom options and returns a summary of the test run.
Note: hspecWithResult does not exit with exitFailure on failing spec
 items.  If you need this, you have to check the Summary yourself and act
 accordingly.
Summary
Summary of a test run.
Constructors
| Summary | |
| Fields 
 | |
evaluateSummary :: Summary -> IO () Source #
Exit with exitFailure if the given Summary indicates that there was at
 least one failure.
Running a spec
To run a spec hspec performs a sequence of steps:
- Evaluate a Specto a forest ofSpecTrees
- Read config values from the command-line, config files and the process environment
- Execute each spec item of the forest and report results to stdout
- Exit with exitFailureif at least on spec item fails
The four primitives evalSpec, readConfig, runSpecForest and
evaluateResult each perform one of these steps respectively.
hspec is defined in terms of these primitives. Loosely speaking, a definition
for hspec is:
hspec =evalSpecdefaultConfig>=> \ (config, spec) ->getArgs>>=readConfigconfig >>=withArgs[] .runSpecForestspec >>=evaluateResult
Loosely speaking in the sense that this definition of hspec ignores
--rerun-all-on-success.
Using these primitives individually gives you more control over how a spec is
run.  However, if you need support for --rerun-all-on-success then you should
try hard to solve your use case with one of hspec, hspecWith, hspecResult
or hspecWithResult.
runSpecForest :: [SpecTree ()] -> Config -> IO SpecResult Source #
runSpecForest is the most basic primitive to run a spec. hspec is
 defined in terms of runSpecForest:
hspec =evalSpecdefaultConfig>=> \ (config, spec) ->getArgs>>=readConfigconfig >>=withArgs[] . runSpecForest spec >>=evaluateResult
Since: 2.10.0
evaluateResult :: SpecResult -> IO () Source #
Result
Spec Result
data SpecResult Source #
Since: 2.10.0
Instances
| Show SpecResult Source # | |
| Defined in Test.Hspec.Core.Runner.Result Methods showsPrec :: Int -> SpecResult -> ShowS # show :: SpecResult -> String # showList :: [SpecResult] -> ShowS # | |
| Eq SpecResult Source # | |
| Defined in Test.Hspec.Core.Runner.Result | |
specResultItems :: SpecResult -> [ResultItem] Source #
Since: 2.10.0
specResultSuccess :: SpecResult -> Bool Source #
Since: 2.10.0
toSummary :: SpecResult -> Summary Source #
Result Item
data ResultItem Source #
Since: 2.10.0
Instances
| Show ResultItem Source # | |
| Defined in Test.Hspec.Core.Runner.Result Methods showsPrec :: Int -> ResultItem -> ShowS # show :: ResultItem -> String # showList :: [ResultItem] -> ShowS # | |
| Eq ResultItem Source # | |
| Defined in Test.Hspec.Core.Runner.Result | |
resultItemPath :: ResultItem -> Path Source #
Since: 2.10.0
resultItemStatus :: ResultItem -> ResultItemStatus Source #
Since: 2.10.0
resultItemIsFailure :: ResultItem -> Bool Source #
Since: 2.10.0
Result Item Status
data ResultItemStatus Source #
Constructors
| ResultItemSuccess | |
| ResultItemPending | |
| ResultItemFailure | 
Instances
| Show ResultItemStatus Source # | |
| Defined in Test.Hspec.Core.Runner.Result Methods showsPrec :: Int -> ResultItemStatus -> ShowS # show :: ResultItemStatus -> String # showList :: [ResultItemStatus] -> ShowS # | |
| Eq ResultItemStatus Source # | |
| Defined in Test.Hspec.Core.Runner.Result Methods (==) :: ResultItemStatus -> ResultItemStatus -> Bool # (/=) :: ResultItemStatus -> ResultItemStatus -> Bool # | |
Config
Constructors
Constructors
| ColorAuto | |
| ColorNever | |
| ColorAlways | 
data UnicodeMode Source #
Constructors
| UnicodeAuto | |
| UnicodeNever | |
| UnicodeAlways | 
Instances
| Show UnicodeMode Source # | |
| Defined in Test.Hspec.Core.Config.Definition Methods showsPrec :: Int -> UnicodeMode -> ShowS # show :: UnicodeMode -> String # showList :: [UnicodeMode] -> ShowS # | |
| Eq UnicodeMode Source # | |
| Defined in Test.Hspec.Core.Config.Definition | |
type Path = ([String], String) Source #
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: 2.0.0
registerFormatter :: (String, FormatConfig -> IO Format) -> Config -> Config Source #
Deprecated: Use registerFormatter instead.
Make a formatter available for use with --format.
Since: 2.10.5
registerDefaultFormatter :: (String, FormatConfig -> IO Format) -> Config -> Config Source #
Deprecated: Use useFormatter instead.
Make a formatter available for use with --format and use it by default.
Since: 2.10.5
configAddFilter :: (Path -> Bool) -> Config -> Config Source #
Add a filter predicate to config.  If there is already a filter predicate,
 then combine them with ||.
readConfig :: Config -> [String] -> IO Config Source #
readConfig parses config options from several sources and constructs a
 Config value.  It takes options from:
- ~/.hspec(a config file in the user's home directory)
- .hspec(a config file in the current working directory)
- environment variables starting with HSPEC_
- the provided list of command-line options (the second argument to readConfig)
(precedence from low to high)
When parsing fails then readConfig writes an error message to stderr and
 exits with exitFailure.
When --help is provided as a command-line option then readConfig writes
 a help message to stdout and exits with exitSuccess.
A common way to use readConfig is:
getArgs>>= readConfigdefaultConfig
Legacy
runSpec :: Spec -> Config -> IO Summary Source #
Note: runSpec is deprecated. It ignores any modifications applied
 through modifyConfig.  Use evalSpec and runSpecForest instead.