test-simple-0.1.9: Simple Perl inspired testing

Copyright(c) Boris Sukholitko 2012
LicenseBSD3
Maintainerboriss@gmail.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell98

Test.Simple

Contents

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!
 

Synopsis

Types

data TestSimpleT m a Source #

Test.Simple is implemented as monad transformer.

Instances

MonadTrans TestSimpleT Source # 

Methods

lift :: Monad m => m a -> TestSimpleT m a #

Monad m => Monad (TestSimpleT m) Source # 

Methods

(>>=) :: TestSimpleT m a -> (a -> TestSimpleT m b) -> TestSimpleT m b #

(>>) :: TestSimpleT m a -> TestSimpleT m b -> TestSimpleT m b #

return :: a -> TestSimpleT m a #

fail :: String -> TestSimpleT m a #

Functor m => Functor (TestSimpleT m) Source # 

Methods

fmap :: (a -> b) -> TestSimpleT m a -> TestSimpleT m b #

(<$) :: a -> TestSimpleT m b -> TestSimpleT m a #

Monad m => Applicative (TestSimpleT m) Source # 

Methods

pure :: a -> TestSimpleT m a #

(<*>) :: TestSimpleT m (a -> b) -> TestSimpleT m a -> TestSimpleT m b #

(*>) :: TestSimpleT m a -> TestSimpleT m b -> TestSimpleT m b #

(<*) :: TestSimpleT m a -> TestSimpleT m b -> TestSimpleT m a #

MonadIO m => MonadIO (TestSimpleT m) Source # 

Methods

liftIO :: IO a -> TestSimpleT m a #

Monad m => Alternative (TestSimpleT m) Source # 

Methods

empty :: TestSimpleT m a #

(<|>) :: TestSimpleT m a -> TestSimpleT m a -> TestSimpleT m a #

some :: TestSimpleT m a -> TestSimpleT m [a] #

many :: TestSimpleT m a -> TestSimpleT m [a] #

Monad m => MonadPlus (TestSimpleT m) Source # 

Methods

mzero :: TestSimpleT m a #

mplus :: TestSimpleT m a -> TestSimpleT m a -> TestSimpleT m a #

Testable (TestSimpleT (PropertyM IO) a) Source # 
Testable (TestSimpleT Gen a) Source # 

class Likeable a b where Source #

Is used in like, unlike tests.

Minimal complete definition

isLike

Methods

isLike :: a -> b -> Bool Source #

Returns True if a is like b

Instances

Eq a => Likeable [a] [a] Source # 

Methods

isLike :: [a] -> [a] -> Bool Source #

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 :: (m a -> IO Result) -> m a -> IO () Source #

Run some Testable monad through QuickCheck function. Exit with failure on error.

qcTestSimpleMain :: Testable (m a) => 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

ok :: Monad m => Bool -> TestSimpleT m Bool Source #

Is Bool ok?

isnt :: (Eq a, Show a, Monad m) => a -> a -> TestSimpleT m Bool Source #

Are values different?

is :: (Eq a, Show a, Monad m) => a -> a -> TestSimpleT m Bool Source #

Are values equal?

like :: (Show a, Show b, Likeable a b, Monad m) => a -> b -> TestSimpleT m Bool Source #

Is a like b?

unlike :: (Show a, Show b, Likeable a b, Monad m) => a -> b -> TestSimpleT m Bool Source #

Is a unlike b?

isRight :: (Monad m, Show a) => Either a b -> TestSimpleT m Bool Source #

Is Either right?

Diagnostics

loc :: Q Exp Source #

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.

diagen :: Show a => String -> Gen a -> TestSimpleT Gen a Source #

Generates and logs (through diag) arbitrary value. Also outputs current location.