foundation-0.0.10: Alternative prelude with batteries and no dependencies

LicenseBSD-style
MaintainerFoundation maintainers
Safe HaskellNone
LanguageHaskell2010

Foundation.Check

Contents

Description

An implementation of a test framework and property expression & testing

Synopsis

Documentation

data Gen a Source #

Generator monad

Instances

Monad Gen Source # 

Methods

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

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

return :: a -> Gen a #

fail :: String -> Gen a #

Functor Gen Source # 

Methods

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

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

Applicative Gen Source # 

Methods

pure :: a -> Gen a #

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

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

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

class Arbitrary a where Source #

How to generate an arbitrary value for a

Minimal complete definition

arbitrary

Methods

arbitrary :: Gen a Source #

Instances

Arbitrary Bool Source # 
Arbitrary Char Source # 
Arbitrary Double Source # 
Arbitrary Float Source # 
Arbitrary Int Source # 
Arbitrary Int8 Source # 
Arbitrary Int16 Source # 
Arbitrary Int32 Source # 
Arbitrary Int64 Source # 
Arbitrary Integer Source # 
Arbitrary Word Source # 
Arbitrary Word8 Source # 
Arbitrary Word16 Source # 
Arbitrary Word32 Source # 
Arbitrary Word64 Source # 
Arbitrary Natural Source # 
Arbitrary String Source # 
Arbitrary a => Arbitrary (Maybe a) Source # 

Methods

arbitrary :: Gen (Maybe a) Source #

Arbitrary (CountOf ty) Source # 

Methods

arbitrary :: Gen (CountOf ty) Source #

(Arbitrary l, Arbitrary r) => Arbitrary (Either l r) Source # 

Methods

arbitrary :: Gen (Either l r) Source #

(Arbitrary a, Arbitrary b) => Arbitrary (a, b) Source # 

Methods

arbitrary :: Gen (a, b) Source #

(Arbitrary a, Arbitrary b, Arbitrary c) => Arbitrary (a, b, c) Source # 

Methods

arbitrary :: Gen (a, b, c) Source #

(Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d) => Arbitrary (a, b, c, d) Source # 

Methods

arbitrary :: Gen (a, b, c, d) Source #

(Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e) => Arbitrary (a, b, c, d, e) Source # 

Methods

arbitrary :: Gen (a, b, c, d, e) Source #

(Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e, Arbitrary f) => Arbitrary (a, b, c, d, e, f) Source # 

Methods

arbitrary :: Gen (a, b, c, d, e, f) Source #

frequency :: NonEmpty [(Word, Gen a)] -> Gen a Source #

Call one of the generator weighted

data Test where Source #

different type of tests supported

Constructors

Unit :: String -> IO () -> Test 
Property :: IsProperty prop => String -> prop -> Test 
Group :: String -> [Test] -> Test 
CheckPlan :: String -> Check () -> Test 

testName :: Test -> String Source #

Name of a test

Property

data PropertyCheck Source #

The type of check this test did for a property

data Property Source #

Constructors

Prop 

Fields

class IsProperty p where Source #

Minimal complete definition

property

Methods

property :: p -> Property Source #

(===) :: (Show a, Eq a, Typeable a) => a -> a -> PropertyCheck infix 4 Source #

A property that check for equality of its 2 members.

propertyCompare Source #

Arguments

:: (Show a, Typeable a) 
=> String

name of the function used for comparaison, e.g. (<)

-> (a -> a -> Bool)

function used for value comparaison

-> a

value left of the operator

-> a

value right of the operator

-> PropertyCheck 

A property that check for a specific comparaison of its 2 members.

This is equivalent to === but with compare

propertyAnd :: PropertyCheck -> PropertyCheck -> PropertyCheck Source #

A conjuctive property composed of 2 properties that need to pass

forAll :: (Show a, IsProperty prop) => Gen a -> (a -> prop) -> Property Source #

Running a generator for a specific type under a property

Check Plan

data Check a Source #

Instances

Monad Check Source # 

Methods

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

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

return :: a -> Check a #

fail :: String -> Check a #

Functor Check Source # 

Methods

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

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

Applicative Check Source # 

Methods

pure :: a -> Check a #

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

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

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

MonadState Check Source # 

Associated Types

type State (Check :: * -> *) :: * Source #

Methods

withState :: (State Check -> (a, State Check)) -> Check a Source #

type State Check Source # 

validate :: IsProperty prop => String -> prop -> Check () Source #

pick :: String -> IO a -> Check a Source #

iterateProperty :: CountOf TestResult -> GenParams -> (Word64 -> GenRng) -> Property -> IO (PropertyResult, CountOf TestResult) Source #