quickpull-0.2.0.0: Generate Main module with QuickCheck tests

Safe HaskellSafe-Inferred

Quickpull.Laws

Description

Functions to build TestTree that test properties of typeclasses, such as the functor laws, monad laws, and monoid laws. These functions are rough; for example, they do not shrink on failure, they are monomorphic, and they do not show the counterexamples of failing functions. But they are sufficient to help verify the lawfulness of your types.

Synopsis

Documentation

monadSource

Arguments

:: (Eq b, Show b, Monad m) 
=> Gen (m Int)

Generates a computation in the monad.

-> Gen (Int -> m Int)

Generates a function that, when applied to an Int, returns a computation in the monad.

-> Gen (m Int -> b)

Generates a function that runs a computation in the monad.

-> TestTree 

Tests the monad laws:

Left identity:

 return a >>= f == f a

Right identity:

 m >>= return == m

Associativity:

 (m >>= f) >>= g == m >>= (\x -> f x >>= g)

functorSource

Arguments

:: (Eq b, Show b, Functor f) 
=> Gen (f Int)

Generates a computation in the functor.

-> Gen (f Int -> b)

Generates a computation that unwraps the functor.

-> TestTree 

Tests the functor laws:

 fmap id == id
 fmap (f . g) == fmap f . fmap g

applicativeSource

Arguments

:: (Eq b, Show b, Applicative f) 
=> Gen (f Int)

Generates a computation in the Applicative.

-> Gen (f (Int -> Int))

Generates a function in the Applicative.

-> Gen (f Int -> b)

Generates an unwrapping function.

-> TestTree 

Tests the Applicative laws:

  • identity:
 pure id <*> v == v
  • composition:
 pure (.) <*> u <*> v <*> w == u <*> (v <*> w)
  • homomorphism:
 pure f <*> pure x = pure (f x)
  • interchange:
 u <*> pure y = pure ($ y) <*> u

monoidSource

Arguments

:: (Eq b, Show b, Monoid a) 
=> Gen a

Generates monoid values

-> Gen (a -> b)

Generates unwrappers

-> TestTree 

Tests the monoid laws:

 mappend mempty x = x
 mappend x mempty = x
 mappend x (mappend y z) = mappend (mappend x y) z
 mconcat = foldr mappend mempty

associativeSource

Arguments

:: (Eq b, Show b) 
=> Gen (a -> a -> a)

Generates an associative operation

-> Gen (a -> b)

Generates unwrappers

-> Gen a

Generates values

-> Gen Property 

Tests whether a particular operation is associative, that is:

 a `f` (b `f` c) == (a `f` b) `f` c

commutativeSource

Arguments

:: (Eq b, Show b) 
=> Gen (a -> a -> a)

Generates a commutative operation

-> Gen (a -> b)

Generates unwrappers

-> Gen a

Generates values

-> Gen Property 

Tests whether a particular operation is commutative, that is:

 a `f` b == b `f` a

leftIdentitySource

Arguments

:: (Eq b, Show b) 
=> Gen (a -> a -> a)

Generates the operation to test

-> Gen (a -> b)

Generates unwrappers

-> Gen a

Generates identity values

-> Gen a

Generates right-hand side values

-> Gen Property 

Tests whether a particular value is the left identity, that is:

 z `f` a == a

rightIdentitySource

Arguments

:: (Eq b, Show b) 
=> Gen (a -> a -> a)

Generates the operation to test

-> Gen (a -> b)

Generates unwrappers

-> Gen a

Generates identity values

-> Gen a

Generates left-hand side values

-> Gen Property 

Tests whether a particular value is the right identity, that is:

 a `f` z == a