quickcheck-assertions-0.1.1: HUnit like assertions for QuickCheck

Safe HaskellNone

Test.QuickCheck.Assertions

Description

Module provides convenient functions to do some assertions in QuickCheck properties with pretty printed reasons. For example you can do something like that:

 module Main where

 import Test.Hspec
 import Test.Hspec.QuickCheck
 import Test.QuickCheck.Assertions
 import Test.QuickCheck.Property

 someProp :: Int -> Int -> Result
 someProp a b = (a ?> b)

 someOtherProp :: Double -> Double -> Result
 someOtherProp a b = (a ?== b)

 main = hspec $ describe "failing test" $ do
   prop "must fail" $ someProp
   prop "must fail again" $ someOtherProp

And receive pretty printed fail message when testing:

 failing test
   - must fail FAILED [1]
   - must fail again FAILED [2]

 1) failing test must fail FAILED
 *** Failed! (after 1 test):
 >>>>>>>>>>>>>> the value
 0
 >>>>>>>>>>>>>> should be greater than value
 0
 0
 0


 2) failing test must fail again FAILED
 *** Failed! (after 2 tests and 4 shrinks):
 >>>>>>>>>>>>>> expected
 0.0
 >>>>>>>>>>>>>> but got
 1.0
 0.0
 1.0

Ok, not very well printed, but better than nothing.

Synopsis

Documentation

binAsrtSource

Arguments

:: String

The reason of fail

-> Bool

If True then test pass

-> Result

The result with fail reason

(?==) :: (Eq a, Show a) => a -> a -> ResultSource

Left argument should be equal to right

(==?) :: (Eq a, Show a) => a -> a -> ResultSource

Right argument should be equal to left

(/=?) :: (Eq a, Show a) => a -> a -> ResultSource

Right argument should not equal to left

(?/=) :: (Eq a, Show a) => a -> a -> ResultSource

Left argument should not equal to right

(>?) :: (Show a, Ord a) => a -> a -> ResultSource

Right argument is less then left

(<?) :: (Show a, Ord a) => a -> a -> ResultSource

Right argument is greater than left

(?>) :: (Show a, Ord a) => a -> a -> ResultSource

Left argument is greater than right

(?<) :: (Show a, Ord a) => a -> a -> ResultSource

Left argument is less then right

(>=?) :: (Show a, Ord a) => a -> a -> ResultSource

Right argument is less or equal to left

(<=?) :: (Show a, Ord a) => a -> a -> ResultSource

Right argument is greater or equal to left

(?>=) :: (Show a, Ord a) => a -> a -> ResultSource

Left argument is greater or equal to right

(?<=) :: (Show a, Ord a) => a -> a -> ResultSource

Left argument is less or equal to right

(~==?) :: (AEq a, Show a) => a -> a -> ResultSource

Right value is almost equal to left

(?~==) :: (AEq a, Show a) => a -> a -> ResultSource

Left value is almost equal to right