test-simple-0.1: 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 :).

Here is 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.

Note, that it was meant for easy integration with exitcode-stdio-1.0 cabal testing. Future versions of this library will probably include other, IO independent, test running functions.

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?

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.