test-simple-0.1.3: Simple Perl inspired testing

Stabilityexperimental
Maintainerboriss@gmail.com
Safe HaskellNone

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.

class Likeable a b whereSource

Is used in like, unlike tests.

Methods

isLike :: a -> b -> BoolSource

Returns True if a is like b

Instances

Eq a => Likeable [a] [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.

qcTestSimpleMain :: (Testable (m a), Monad m) => m a -> IO ()Source

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

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 BoolSource

Is Bool ok?

isnt :: (Eq a, Show a, Monad m) => a -> a -> TestSimpleT m BoolSource

Are values different?

is :: (Eq a, Show a, Monad m) => a -> a -> TestSimpleT m BoolSource

Are values equal?

like :: (Show a, Show b, Likeable a b, Monad m) => a -> b -> TestSimpleT m BoolSource

Is a like b?

unlike :: (Show a, Show b, Likeable a b, Monad m) => a -> b -> TestSimpleT m BoolSource

Is a unlike b?

isRight :: (Monad m, Show a) => Either a b -> TestSimpleT m BoolSource

Is Either right?

Diagnostics

loc :: Q ExpSource

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.