Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Test.HUnit.Lang
Contents
Synopsis
- type Assertion = IO ()
- assertFailure :: HasCallStack => String -> IO a
- assertEqual :: HasCallStack => (Eq a, Show a) => String -> a -> a -> Assertion
- data Result
- performTestCase :: Assertion -> IO Result
- data HUnitFailure = HUnitFailure (Maybe SrcLoc) FailureReason
- data FailureReason
- formatFailureReason :: FailureReason -> String
Documentation
type Assertion = IO () Source #
When an assertion is evaluated, it will output a message if and only if the assertion fails.
Test cases are composed of a sequence of one or more assertions.
Arguments
:: HasCallStack | |
=> String | A message that is displayed with the assertion failure |
-> IO a |
Unconditionally signals that a failure has occurred.
Arguments
:: HasCallStack | |
=> (Eq a, Show a) | |
=> String | The message prefix |
-> a | The expected value |
-> a | The actual value |
-> Assertion |
Asserts that the specified actual value is equal to the expected value. The output message will contain the prefix, the expected value, and the actual value.
If the prefix is the empty string (i.e., ""
), then the prefix is omitted
and only the expected and actual values are output.
Performs a single test case.
Internals
Note: This is not part of the public API! It is exposed so that you can tinker with the internals of HUnit, but do not expect it to be stable!
data HUnitFailure Source #
Constructors
HUnitFailure (Maybe SrcLoc) FailureReason |
Instances
Eq HUnitFailure Source # | |
Defined in Test.HUnit.Lang | |
Show HUnitFailure Source # | |
Defined in Test.HUnit.Lang Methods showsPrec :: Int -> HUnitFailure -> ShowS # show :: HUnitFailure -> String # showList :: [HUnitFailure] -> ShowS # | |
Exception HUnitFailure Source # | |
Defined in Test.HUnit.Lang Methods toException :: HUnitFailure -> SomeException # fromException :: SomeException -> Maybe HUnitFailure # displayException :: HUnitFailure -> String # |
data FailureReason Source #
Instances
Eq FailureReason Source # | |
Defined in Test.HUnit.Lang Methods (==) :: FailureReason -> FailureReason -> Bool # (/=) :: FailureReason -> FailureReason -> Bool # | |
Show FailureReason Source # | |
Defined in Test.HUnit.Lang Methods showsPrec :: Int -> FailureReason -> ShowS # show :: FailureReason -> String # showList :: [FailureReason] -> ShowS # |