microspec-0.1.0.0: Tiny QuickCheck test library with minimal dependencies

Safe HaskellSafe
LanguageHaskell2010

Test.Microspec

Contents

Description

Tests can be structured as nested it / describe statements

E.g.

microspec $ do
   describe "plus" $ do
      it "adds positive numbers" $ do
         it "does 1 + 1" $
            1 + 1 == 2
         it "does 2 + 2" $
            2 + 2 == 4
      it "is commutative" $
         \x y -> x + y == y + (x :: Int)

...which will return, nicely in green instead of bold:

  plus
    adds positive numbers
      does 1 + 1
      does 2 + 2
    is commutative
  

Synopsis

Specification

microspec :: Microspec () -> IO () Source #

Run your spec. Put this at the top level, e.g.:

main = microspec $ do
   describe "plus 1" $
      3 + 1 == 4

describe :: MTestable t => String -> t -> Microspec () Source #

Describe a test, e.g.:

describe "reverse 'foo' is 'oof'" $
   reverse "foo" === "oof"

it :: MTestable t => String -> t -> Microspec () Source #

An alias for describe. Usually used inside a describe block:

 describe "replicate" $ do
    it "doubles with 2" $
       replicate 2 'x' === "xx"
    it "creates a list of the right size" $
       \(Positive n) -> length (replicate n 'x') == n

pending :: Pending Source #

Describe a test as unwritten, e.g.:

describe "meaning of life" $ pending

prop :: Testable prop => prop -> Property Source #

Make a test case from a QuickCheck function. Alias for property.

Note that you don't need to use this to create a test, e.g.:

describe "reverse preserves length" $
   \l -> length (reverse l) == length l

data Microspec a Source #

A series of tests, to run with microspec

Instances

Monad Microspec Source # 

Methods

(>>=) :: Microspec a -> (a -> Microspec b) -> Microspec b #

(>>) :: Microspec a -> Microspec b -> Microspec b #

return :: a -> Microspec a #

fail :: String -> Microspec a #

Functor Microspec Source # 

Methods

fmap :: (a -> b) -> Microspec a -> Microspec b #

(<$) :: a -> Microspec b -> Microspec a #

Applicative Microspec Source # 

Methods

pure :: a -> Microspec a #

(<*>) :: Microspec (a -> b) -> Microspec a -> Microspec b #

(*>) :: Microspec a -> Microspec b -> Microspec b #

(<*) :: Microspec a -> Microspec b -> Microspec a #

MTestable (Microspec ()) Source # 

Methods

describe :: String -> Microspec () -> Microspec () Source #

class MTestable t where Source #

Something which can be tested

Note both Bools and Properties can be tested, but only Properties show the values that weren't equal

For both unit tests and property tests, if you want to see the outputs of failed tests use ===. If you just want to test for equality, use ==.

For example, the outputs of running:

  microspec $ do
     describe "baddies" $ do
        it "isn't 1 =="  $ 0 == (1 :: Int)
        it "isn't 1 ===" $ 0 === (1 :: Int)
        it "isn't always 1 =="  $ x -> x == (1 :: Int)
        it "isn't always 1 ===" $ x -> x === (1 :: Int)
  

are:

  isn't 1 == - *** Failed! Falsifiable (after 1 test)
  isn't 1 === - *** Failed! Falsifiable (after 1 test):  | 0 /= 1
  isn't always 1 == - *** Failed! Falsifiable (after 1 test):  | 0
  isn't always 1 === - *** Failed! Falsifiable (after 1 test):  | 0 | 0 /= 1
  

Minimal complete definition

describe

Methods

describe :: String -> t -> Microspec () Source #

Describe a test, e.g.:

describe "reverse 'foo' is 'oof'" $
   reverse "foo" === "oof"

Instances

MTestable Bool Source # 

Methods

describe :: String -> Bool -> Microspec () Source #

MTestable Property Source # 
MTestable (Microspec ()) Source # 

Methods

describe :: String -> Microspec () -> Microspec () Source #

(Arbitrary a, Show a, Testable prop) => MTestable (a -> prop) Source # 

Methods

describe :: String -> (a -> prop) -> Microspec () Source #

Configuration

data MArgs Source #

Tweak how tests are run, with microspecWith.

Constructors

MArgs 

Fields

defaultMArgs :: MArgs Source #

Default arguments. Calling "microspec" is the same as calling "microspecWith defaultMArgs".

Compatibility

shouldBe :: (Eq x, Show x) => x -> x -> Property Source #

Hspec compatibility. Equivalent to using ===