Stability | provisional |
---|---|
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- hspec :: Spec -> IO ()
- evalSpec :: Config -> SpecWith a -> IO (Config, [SpecTree a])
- runSpecForest :: [SpecTree ()] -> Config -> IO SpecResult
- evaluateResult :: SpecResult -> IO ()
- data Config = Config {
- configIgnoreConfigFile :: Bool
- configDryRun :: Bool
- configFocusedOnly :: Bool
- configFailOnFocused :: Bool
- configPrintSlowItems :: Maybe Int
- configPrintCpuTime :: Bool
- configFailFast :: 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 :: Maybe Int
- configColorMode :: ColorMode
- configUnicodeMode :: UnicodeMode
- configDiff :: Bool
- configPrettyPrint :: Bool
- configPrettyPrintFunction :: Bool -> String -> String -> (String, String)
- configTimes :: Bool
- configAvailableFormatters :: [(String, FormatConfig -> IO Format)]
- configFormat :: Maybe (FormatConfig -> IO Format)
- configFormatter :: Maybe Formatter
- configHtmlOutput :: Bool
- configConcurrentJobs :: Maybe Int
- data ColorMode
- data UnicodeMode
- type Path = ([String], String)
- defaultConfig :: Config
- configAddFilter :: (Path -> Bool) -> Config -> Config
- readConfig :: Config -> [String] -> IO Config
- data SpecResult
- specResultItems :: SpecResult -> [ResultItem]
- specResultSuccess :: SpecResult -> Bool
- data ResultItem
- resultItemPath :: ResultItem -> Path
- resultItemStatus :: ResultItem -> ResultItemStatus
- resultItemIsFailure :: ResultItem -> Bool
- data ResultItemStatus
- hspecWith :: Config -> Spec -> IO ()
- hspecResult :: Spec -> IO Summary
- hspecWithResult :: Config -> Spec -> IO Summary
- runSpec :: Spec -> Config -> IO Summary
- data Summary = Summary {
- summaryExamples :: !Int
- summaryFailures :: !Int
- toSummary :: SpecResult -> Summary
- isSuccess :: Summary -> Bool
- evaluateSummary :: Summary -> IO ()
Running a spec
To run a spec hspec
performs a sequence of steps:
- Evaluate a
Spec
to a forest ofSpecTree
s - 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
exitFailure
if 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:
hspec =evalSpec
defaultConfig
>=> \ (config, spec) ->getArgs
>>=readConfig
config >>=withArgs
[] .runSpecForest
spec >>=evaluateResult
If you need more control over how a spec is run use these primitives individually.
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.
runSpecForest :: [SpecTree ()] -> Config -> IO SpecResult Source #
runSpecForest
is the most basic primitive to run a spec. hspec
is
defined in terms of runSpecForest
:
hspec =evalSpec
defaultConfig
>=> \ (config, spec) ->getArgs
>>=readConfig
config >>=withArgs
[] . runSpecForest spec >>=evaluateResult
Since: 2.10.0
evaluateResult :: SpecResult -> IO () Source #
Config
data UnicodeMode Source #
Instances
Eq UnicodeMode Source # | |
Defined in Test.Hspec.Core.Config.Definition (==) :: UnicodeMode -> UnicodeMode -> Bool # (/=) :: UnicodeMode -> UnicodeMode -> Bool # | |
Show UnicodeMode Source # | |
Defined in Test.Hspec.Core.Config.Definition showsPrec :: Int -> UnicodeMode -> ShowS # show :: UnicodeMode -> String # showList :: [UnicodeMode] -> ShowS # |
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
Result
Spec Result
data SpecResult Source #
Instances
Eq SpecResult Source # | |
Defined in Test.Hspec.Core.Runner.Result (==) :: SpecResult -> SpecResult -> Bool # (/=) :: SpecResult -> SpecResult -> Bool # | |
Show SpecResult Source # | |
Defined in Test.Hspec.Core.Runner.Result showsPrec :: Int -> SpecResult -> ShowS # show :: SpecResult -> String # showList :: [SpecResult] -> ShowS # |
specResultItems :: SpecResult -> [ResultItem] Source #
specResultSuccess :: SpecResult -> Bool Source #
Result Item
data ResultItem Source #
Instances
Eq ResultItem Source # | |
Defined in Test.Hspec.Core.Runner.Result (==) :: ResultItem -> ResultItem -> Bool # (/=) :: ResultItem -> ResultItem -> Bool # | |
Show ResultItem Source # | |
Defined in Test.Hspec.Core.Runner.Result showsPrec :: Int -> ResultItem -> ShowS # show :: ResultItem -> String # showList :: [ResultItem] -> ShowS # |
resultItemPath :: ResultItem -> Path Source #
resultItemIsFailure :: ResultItem -> Bool Source #
Result Item Status
data ResultItemStatus Source #
Instances
Eq ResultItemStatus Source # | |
Defined in Test.Hspec.Core.Runner.Result (==) :: ResultItemStatus -> ResultItemStatus -> Bool # (/=) :: ResultItemStatus -> ResultItemStatus -> Bool # | |
Show ResultItemStatus Source # | |
Defined in Test.Hspec.Core.Runner.Result showsPrec :: Int -> ResultItemStatus -> ShowS # show :: ResultItemStatus -> String # showList :: [ResultItemStatus] -> ShowS # |
Legacy
The following primitives are deprecated. Use runSpecForest
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.
runSpec :: Spec -> Config -> IO Summary Source #
Note: runSpec
is deprecated. It ignores any modifications applied
through modifyConfig
. Use evalSpec
and runSpecForest
instead.
Summary
Summary of a test run.
Summary | |
|
toSummary :: SpecResult -> Summary Source #
evaluateSummary :: Summary -> IO () Source #
Exit with exitFailure
if the given Summary
indicates that there was at
least one failure.