Stability | stable |
---|---|
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- type Format = Event -> IO ()
- 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
- data Event
- type Progress = (Int, Int)
- type Path = ([String], String)
- data Location = Location {}
- newtype Seconds = Seconds Double
- data Item = Item {}
- data Result
- data FailureReason
- monadic :: MonadIO m => (m () -> IO ()) -> (Event -> m ()) -> IO Format
- registerFormatter :: (String, FormatConfig -> IO Format) -> Config -> Config
- useFormatter :: (String, FormatConfig -> IO Format) -> Config -> Config
- liftFormatter :: (String, FormatConfig -> IO Format) -> (String, FormatConfig -> IO Format)
- type SpecWith a = SpecM a ()
- data Config
- modifyConfig :: (Config -> Config) -> SpecWith a
Documentation
data FormatConfig Source #
Since: 2.11.5
FormatConfig | |
|
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.
Location | |
|
Instances
Num Seconds | |
Fractional Seconds | |
Show Seconds | |
PrintfArg Seconds | |
Defined in Test.Hspec.Core.Clock formatArg :: Seconds -> FieldFormatter # parseFormat :: Seconds -> ModifierParser # | |
Eq Seconds | |
Ord Seconds | |
Item | |
|
data FailureReason #
NoReason | |
Reason String | |
ColorizedReason String | |
ExpectedButGot (Maybe String) String String | |
Error (Maybe String) SomeException |
Instances
Show FailureReason | |
Defined in Test.Hspec.Core.Example showsPrec :: Int -> FailureReason -> ShowS # show :: FailureReason -> String # showList :: [FailureReason] -> ShowS # | |
NFData FailureReason | |
Defined in Test.Hspec.Core.Example rnf :: FailureReason -> () # |
Register a formatter
registerFormatter :: (String, FormatConfig -> IO Format) -> Config -> Config Source #
Make a formatter available for use with --format
.
useFormatter :: (String, FormatConfig -> IO Format) -> Config -> Config Source #
Make a formatter available for use with --format
and use it by default.
liftFormatter :: (String, FormatConfig -> IO Format) -> (String, FormatConfig -> IO Format) Source #
Make a formatter compatible with types from Test.Hspec.Core.Format.
Re-exports
modifyConfig :: (Config -> Config) -> SpecWith a #
Since: hspec-core-2.10.0