| Copyright | (c) Boris Sukholitko 2012 |
|---|---|
| License | BSD3 |
| Maintainer | boriss@gmail.com |
| Stability | experimental |
| Safe Haskell | None |
| Language | Haskell98 |
Test.Simple
Description
Test.Simple is yet another testing library for Haskell. It has testing primitives familiar to recovering Perl programmers :).
Having MonadPlus instance allows to cut tests early e.g using guard function.
Being monad transformer it includes integration with QuickCheck by declaring Testable instance
on TestSimpleT Gen a.
Test.Simple also has the ability to run in pure context (see runTestSimple function).
Here is an example suitable for cabal test-suite integration. Note that TemplateHaskell usage is optional and is needed for test failure locations only.
{-# LANGUAGE TemplateHaskell #-}
import Test.Simple
import Control.Monad
main :: IO ()
main = testSimpleMain $ do
plan 7
ok True
is 1 1
isnt "a" "b"
like "abcd" "bc"
unlike "a" "b"
diag "Successful so far, failures follow ..."
$loc >> ok False -- location will be recorded
is "a" "b" >>= guard
diag "I am not being called" -- not reached because of the guard: MonadPlus FTW!
- data TestSimpleT m a
- class Likeable a b where
- testSimpleMain :: MonadIO m => TestSimpleT m a -> m ()
- runTestSimple :: Monad m => TestSimpleT m a -> m (Bool, [String])
- qcTestSimpleWith :: (Testable (m a), Monad m) => (m a -> IO Result) -> m a -> IO ()
- qcTestSimpleMain :: (Testable (m a), Monad m) => m a -> IO ()
- plan :: Monad m => Int -> TestSimpleT m ()
- ok :: Monad m => Bool -> TestSimpleT m Bool
- isnt :: (Eq a, Show a, Monad m) => a -> a -> TestSimpleT m Bool
- is :: (Eq a, Show a, Monad m) => a -> a -> TestSimpleT m Bool
- like :: (Show a, Show b, Likeable a b, Monad m) => a -> b -> TestSimpleT m Bool
- unlike :: (Show a, Show b, Likeable a b, Monad m) => a -> b -> TestSimpleT m Bool
- isRight :: (Monad m, Show a) => Either a b -> TestSimpleT m Bool
- loc :: Q Exp
- diag :: Monad m => String -> TestSimpleT m ()
- diagen :: Show a => String -> Gen a -> TestSimpleT Gen a
Types
data TestSimpleT m a Source
Test.Simple is implemented as monad transformer.
Instances
| MonadTrans TestSimpleT | |
| (Monad m, Functor m) => Alternative (TestSimpleT m) | |
| Monad m => Monad (TestSimpleT m) | |
| Functor m => Functor (TestSimpleT m) | |
| Monad m => MonadPlus (TestSimpleT m) | |
| (Monad m, Functor m) => Applicative (TestSimpleT m) | |
| MonadIO m => MonadIO (TestSimpleT m) | |
| Testable (TestSimpleT (PropertyM IO) a) | |
| Testable (TestSimpleT Gen a) |
Main
testSimpleMain :: MonadIO m => TestSimpleT m a -> m () Source
Runs TestSimpleT transformer in IO. Outputs results in TAP format.
Exits with error on test failure.
runTestSimple :: Monad m => TestSimpleT m a -> m (Bool, [String]) Source
Runs TestSimpleT transformer. Returns whether the tests where successful and resulting
output.
qcTestSimpleWith :: (Testable (m a), Monad m) => (m a -> IO Result) -> m a -> IO () Source
Run some Testable monad through QuickCheck function. Exit with failure on error.
qcTestSimpleMain :: (Testable (m a), Monad m) => m a -> IO () Source
Run some Testable monad through QuickCheck. Exit with failure on error.
Equivalent to qcTestSimpleWith quickCheckResult
Plan
plan :: Monad m => Int -> TestSimpleT m () Source
Sets expected number of tests. Running more or less tests is considered failure. Note, that plans are composable, e.g:
(plan 1 >> ok True) >> (plan 1 >> ok True)
will expect 2 tests.
Test functions
unlike :: (Show a, Show b, Likeable a b, Monad m) => a -> b -> TestSimpleT m Bool Source
Is a unlike b?
Diagnostics
Records current location to output in case of failures. Necessary caveat: failing later without updating location produces the last location recorded.
diag :: Monad m => String -> TestSimpleT m () Source
Outputs diagnostics message.