Stability | provisional |
---|---|
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- hspec :: Spec -> IO ()
- runSpec :: Spec -> Config -> IO Summary
- data Config = Config {
- configIgnoreConfigFile :: Bool
- configDryRun :: Bool
- configFocusedOnly :: Bool
- configFailOnFocused :: Bool
- configPrintSlowItems :: Maybe Int
- configPrintCpuTime :: Bool
- configFastFail :: Bool
- configRandomize :: Bool
- configFailureReport :: Maybe FilePath
- configRerun :: Bool
- configRerunAllOnSuccess :: Bool
- configFilterPredicate :: Maybe (Path -> Bool)
- configSkipPredicate :: Maybe (Path -> Bool)
- configQuickCheckSeed :: Maybe Integer
- configQuickCheckMaxSuccess :: Maybe Int
- configQuickCheckMaxDiscardRatio :: Maybe Int
- configQuickCheckMaxSize :: Maybe Int
- configQuickCheckMaxShrinks :: Maybe Int
- configSmallCheckDepth :: Int
- configColorMode :: ColorMode
- configDiff :: Bool
- configTimes :: Bool
- configFormat :: Maybe (FormatConfig -> IO Format)
- configFormatter :: Maybe Formatter
- configHtmlOutput :: Bool
- configConcurrentJobs :: Maybe Int
- data ColorMode
- type Path = ([String], String)
- defaultConfig :: Config
- configAddFilter :: (Path -> Bool) -> Config -> Config
- readConfig :: Config -> [String] -> IO Config
- data Summary = Summary {}
- isSuccess :: Summary -> Bool
- evaluateSummary :: Summary -> IO ()
- hspecWith :: Config -> Spec -> IO ()
- hspecResult :: Spec -> IO Summary
- hspecWithResult :: Config -> Spec -> IO Summary
Running a spec
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 desired. Use runSpec
if you need more control over these
aspects.
runSpec :: Spec -> Config -> IO Summary Source #
runSpec
is the most basic primitive to run a spec. hspec
is defined in
terms of runSpec
:
hspec spec =getArgs
>>=readConfig
defaultConfig
>>=withArgs
[] . runSpec spec >>=evaluateSummary
Config
Config | |
|
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.
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)- the environment variable
HSPEC_OPTIONS
- 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
Summary
Summary of a test run.
evaluateSummary :: Summary -> IO () Source #
Exit with exitFailure
if the given Summary
indicates that there was at
least one failure.
Legacy
The following primitives are deprecated. Use runSpec
instead.
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.