quickcheck-classes-base-0.6.0.0: QuickCheck common typeclasses from `base`

Safe HaskellNone
LanguageHaskell2010

Test.QuickCheck.Classes.Base.IsList

Description

This module provides property tests for functions that operate on list-like data types. If your data type is fully polymorphic in its element type, is it recommended that you use foldableLaws and traversableLaws from Test.QuickCheck.Classes. However, if your list-like data type is either monomorphic in its element type (like Text or ByteString) or if it requires a typeclass constraint on its element (like Data.Vector.Unboxed), the properties provided here can be helpful for testing that your functions have the expected behavior. All properties in this module require your data type to have an IsList instance.

Synopsis

Documentation

isListLaws :: (IsList a, Show a, Show (Item a), Arbitrary a, Arbitrary (Item a), Eq a) => Proxy a -> Laws Source #

Tests the following properties:

Partial Isomorphism
fromList . toList ≡ id
Length Preservation
fromList xs ≡ fromListN (length xs) xs

Note: This property test is only available when using base-4.7 or newer.

foldrProp Source #

Arguments

:: (IsList c, Item c ~ a, Arbitrary c, Show c, Show a, CoArbitrary a, Function a) 
=> Proxy a

input element type

-> (forall b. (a -> b -> b) -> b -> c -> b)

foldr function

-> Property 

foldlProp Source #

Arguments

:: (IsList c, Item c ~ a, Arbitrary c, Show c, Show a, CoArbitrary a, Function a) 
=> Proxy a

input element type

-> (forall b. (b -> a -> b) -> b -> c -> b)

foldl function

-> Property 

foldlMProp Source #

Arguments

:: (IsList c, Item c ~ a, Arbitrary c, Show c, Show a, CoArbitrary a, Function a) 
=> Proxy a

input element type

-> (forall s b. (b -> a -> ST s b) -> b -> c -> ST s b)

monadic foldl function

-> Property 

mapProp Source #

Arguments

:: (IsList c, IsList d, Eq d, Show d, Show b, Item c ~ a, Item d ~ b, Arbitrary c, Arbitrary b, Show c, Show a, CoArbitrary a, Function a) 
=> Proxy a

input element type

-> Proxy b

output element type

-> ((a -> b) -> c -> d)

map function

-> Property 

imapProp Source #

Arguments

:: (IsList c, IsList d, Eq d, Show d, Show b, Item c ~ a, Item d ~ b, Arbitrary c, Arbitrary b, Show c, Show a, CoArbitrary a, Function a) 
=> Proxy a

input element type

-> Proxy b

output element type

-> ((Int -> a -> b) -> c -> d)

indexed map function

-> Property 

imapMProp Source #

Arguments

:: (IsList c, IsList d, Eq d, Show d, Show b, Item c ~ a, Item d ~ b, Arbitrary c, Arbitrary b, Show c, Show a, CoArbitrary a, Function a) 
=> Proxy a

input element type

-> Proxy b

output element type

-> (forall s. (Int -> a -> ST s b) -> c -> ST s d)

monadic indexed map function

-> Property 

traverseProp Source #

Arguments

:: (IsList c, IsList d, Eq d, Show d, Show b, Item c ~ a, Item d ~ b, Arbitrary c, Arbitrary b, Show c, Show a, CoArbitrary a, Function a) 
=> Proxy a

input element type

-> Proxy b

output element type

-> (forall s. (a -> ST s b) -> c -> ST s d)

traverse function

-> Property 

generateProp Source #

Arguments

:: (Item c ~ a, Eq c, Show c, IsList c, Arbitrary a, Show a) 
=> Proxy a

input element type

-> (Int -> (Int -> a) -> c) 
-> Property 

Property for the generate function, which builds a container of a given length by applying a function to each index.

generateMProp Source #

Arguments

:: (Item c ~ a, Eq c, Show c, IsList c, Arbitrary a, Show a) 
=> Proxy a

input element type

-> (forall s. Int -> (Int -> ST s a) -> ST s c) 
-> Property 

replicateProp Source #

Arguments

:: (Item c ~ a, Eq c, Show c, IsList c, Arbitrary a, Show a) 
=> Proxy a

input element type

-> (Int -> a -> c) 
-> Property 

replicateMProp Source #

Arguments

:: (Item c ~ a, Eq c, Show c, IsList c, Arbitrary a, Show a) 
=> Proxy a

input element type

-> (forall s. Int -> ST s a -> ST s c) 
-> Property 

filterProp Source #

Arguments

:: (IsList c, Item c ~ a, Arbitrary c, Show c, Show a, Eq c, CoArbitrary a, Function a) 
=> Proxy a

element type

-> ((a -> Bool) -> c -> c)

map function

-> Property 

Property for the filter function, which keeps elements for which the predicate holds true.

filterMProp Source #

Arguments

:: (IsList c, Item c ~ a, Arbitrary c, Show c, Show a, Eq c, CoArbitrary a, Function a) 
=> Proxy a

element type

-> (forall s. (a -> ST s Bool) -> c -> ST s c)

traverse function

-> Property 

Property for the filterM function, which keeps elements for which the predicate holds true in an applicative context.

mapMaybeProp Source #

Arguments

:: (IsList c, Item c ~ a, Item d ~ b, Eq d, IsList d, Arbitrary b, Show d, Show b, Arbitrary c, Show c, Show a, Eq c, CoArbitrary a, Function a) 
=> Proxy a

input element type

-> Proxy b

output element type

-> ((a -> Maybe b) -> c -> d)

map function

-> Property 

Property for the mapMaybe function, which keeps elements for which the predicate holds true.

mapMaybeMProp Source #

Arguments

:: (IsList c, IsList d, Eq d, Show d, Show b, Item c ~ a, Item d ~ b, Arbitrary c, Arbitrary b, Show c, Show a, CoArbitrary a, Function a) 
=> Proxy a

input element type

-> Proxy b

output element type

-> (forall s. (a -> ST s (Maybe b)) -> c -> ST s d)

traverse function

-> Property