Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Warning: This API is experimental.
Synopsis
- data Item a = Item {
- itemRequirement :: String
- itemLocation :: Maybe Location
- itemIsParallelizable :: Maybe Bool
- itemIsFocused :: Bool
- itemAnnotations :: Annotations
- itemExample :: Params -> (ActionWith a -> IO ()) -> ProgressCallback -> IO Result
- data Location = Location {}
- data Params = Params {}
- type ActionWith a = a -> IO ()
- type Progress = (Int, Int)
- type ProgressCallback = Progress -> IO ()
- data Result = Result {}
- data ResultStatus
- data FailureReason
- isFocused :: Item a -> Bool
- pending :: Item a -> Item a
- pendingWith :: String -> Item a -> Item a
- setAnnotation :: Typeable value => value -> Item a -> Item a
- getAnnotation :: Typeable value => Item a -> Maybe value
Types
Item
is used to represent spec items internally. A spec item consists of:
- a textual description of a desired behavior
- an example for that behavior
- additional meta information
Everything that is an instance of the Example
type class can be used as an
example, including QuickCheck properties, Hspec expectations and HUnit
assertions.
Item | |
|
Location
is used to represent source locations.
Location | |
|
type ActionWith a = a -> IO () Source #
An IO
action that expects an argument of type a
type ProgressCallback = Progress -> IO () Source #
The result of running an example
Instances
Show Result Source # | |
Example Result Source # | |
Defined in Test.Hspec.Core.Example evaluateExample :: Result -> Params -> (ActionWith (Arg Result) -> IO ()) -> ProgressCallback -> IO Result Source # | |
Example (a -> Result) Source # | |
Defined in Test.Hspec.Core.Example evaluateExample :: (a -> Result) -> Params -> (ActionWith (Arg (a -> Result)) -> IO ()) -> ProgressCallback -> IO Result Source # | |
type Arg Result Source # | |
Defined in Test.Hspec.Core.Example | |
type Arg (a -> Result) Source # | |
Defined in Test.Hspec.Core.Example |
data ResultStatus Source #
Instances
Exception ResultStatus Source # | |
Defined in Test.Hspec.Core.Example | |
Show ResultStatus Source # | |
Defined in Test.Hspec.Core.Example showsPrec :: Int -> ResultStatus -> ShowS # show :: ResultStatus -> String # showList :: [ResultStatus] -> ShowS # |
data FailureReason Source #
NoReason | |
Reason String | |
ColorizedReason String | |
ExpectedButGot (Maybe String) String String | |
Error (Maybe String) SomeException |
Instances
Show FailureReason Source # | |
Defined in Test.Hspec.Core.Example showsPrec :: Int -> FailureReason -> ShowS # show :: FailureReason -> String # showList :: [FailureReason] -> ShowS # | |
NFData FailureReason Source # | |
Defined in Test.Hspec.Core.Example rnf :: FailureReason -> () # |