Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
This module defines the AssertM
monad, which allows you either to run assertions
as ordinary unit tests or to evaluate them as pure functions.
Synopsis
- class Monad m => AssertM m where
- genericAssertFailure__ :: Location -> ColorString -> m a
- genericSubAssert :: Location -> Maybe String -> m a -> m a
- data AssertStackElem = AssertStackElem {}
- data AssertBool a
- = AssertOk a
- | AssertFailed [AssertStackElem]
- boolValue :: AssertBool a -> Bool
- eitherValue :: AssertBool a -> Either String a
- formatStack :: [AssertStackElem] -> String
Documentation
class Monad m => AssertM m where Source #
A typeclass for generic assertions.
genericAssertFailure__ :: Location -> ColorString -> m a Source #
genericSubAssert :: Location -> Maybe String -> m a -> m a Source #
Instances
AssertM IO Source # | |
Defined in Test.Framework.AssertM genericAssertFailure__ :: Location -> ColorString -> IO a Source # genericSubAssert :: Location -> Maybe String -> IO a -> IO a Source # | |
AssertM AssertBool Source # | |
Defined in Test.Framework.AssertM genericAssertFailure__ :: Location -> ColorString -> AssertBool a Source # genericSubAssert :: Location -> Maybe String -> AssertBool a -> AssertBool a Source # |
data AssertStackElem Source #
Stack trace element for generic assertions.
Instances
Eq AssertStackElem Source # | |
Defined in Test.Framework.AssertM (==) :: AssertStackElem -> AssertStackElem -> Bool # (/=) :: AssertStackElem -> AssertStackElem -> Bool # | |
Ord AssertStackElem Source # | |
Defined in Test.Framework.AssertM compare :: AssertStackElem -> AssertStackElem -> Ordering # (<) :: AssertStackElem -> AssertStackElem -> Bool # (<=) :: AssertStackElem -> AssertStackElem -> Bool # (>) :: AssertStackElem -> AssertStackElem -> Bool # (>=) :: AssertStackElem -> AssertStackElem -> Bool # max :: AssertStackElem -> AssertStackElem -> AssertStackElem # min :: AssertStackElem -> AssertStackElem -> AssertStackElem # | |
Read AssertStackElem Source # | |
Defined in Test.Framework.AssertM | |
Show AssertStackElem Source # | |
Defined in Test.Framework.AssertM showsPrec :: Int -> AssertStackElem -> ShowS # show :: AssertStackElem -> String # showList :: [AssertStackElem] -> ShowS # |
data AssertBool a Source #
Type for evaluating a generic assertion as a pure function.
AssertOk a | Assertion passes successfully and yields the given value. |
AssertFailed [AssertStackElem] | Assertion fails with the given stack trace. In the stack trace, the outermost stackframe comes first. |
Instances
eitherValue :: AssertBool a -> Either String a Source #
Evaluates a generic assertion to an Either
value. The result
is Right x
if the assertion passes and yields value x
, otherwise
the result is Left err
, where err
is an error message.
formatStack :: [AssertStackElem] -> String Source #
Formats a stack trace.