testing-feat-1.1.1.1: Functional Enumeration of Algebraic Types
Safe HaskellNone
LanguageHaskell2010

Test.Feat

Description

This module contains a (hopefully) manageable subset of the functionality of Feat. The rest resides only in the Test.Feat.* modules.

Synopsis

Testing driver

test :: Enumerable a => (a -> Bool) -> IO [a] Source #

Test with default options (defOptions). Returns a list of counterexamples

testOptions :: Enumerable a => Options -> (a -> Bool) -> IO [a] Source #

Test with basic options. Returns a list of counterexamples.

data Options Source #

Basic options for executing a test. Unlike FlexibleOptions this type has Show/Read instances.

Constructors

Options 

Fields

Instances

Instances details
Read Options Source # 
Instance details

Defined in Test.Feat.Driver

Show Options Source # 
Instance details

Defined in Test.Feat.Driver

defOptions :: Options Source #

60 seconds timeout, maximum size of 100, bound of 100000 tests per size

The type class

data Enumerate a Source #

A functional enumeration of type t is a partition of t into finite numbered sets. Each part contains values of a certain cost (typically the size of the value).

Instances

Instances details
Functor Enumerate Source #

Only use fmap with bijective functions (e.g. data constructors)

Instance details

Defined in Test.Feat.Enumerate

Methods

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

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

Applicative Enumerate Source #

Pure is singleton and <*> corresponds to cartesian product (as with lists)

Instance details

Defined in Test.Feat.Enumerate

Methods

pure :: a -> Enumerate a #

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

liftA2 :: (a -> b -> c) -> Enumerate a -> Enumerate b -> Enumerate c #

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

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

Alternative Enumerate Source # 
Instance details

Defined in Test.Feat.Enumerate

Methods

empty :: Enumerate a #

(<|>) :: Enumerate a -> Enumerate a -> Enumerate a #

some :: Enumerate a -> Enumerate [a] #

many :: Enumerate a -> Enumerate [a] #

Sized Enumerate Source # 
Instance details

Defined in Test.Feat.Enumerate

Semigroup (Enumerate a) Source # 
Instance details

Defined in Test.Feat.Enumerate

Methods

(<>) :: Enumerate a -> Enumerate a -> Enumerate a #

sconcat :: NonEmpty (Enumerate a) -> Enumerate a #

stimes :: Integral b => b -> Enumerate a -> Enumerate a #

Monoid (Enumerate a) Source #

The mappend is (disjoint) union

Instance details

Defined in Test.Feat.Enumerate

class Typeable a => Enumerable a where #

Methods

enumerate :: forall (f :: Type -> Type). (Typeable f, Sized f) => Shared f a #

Instances

Instances details
Enumerable Bool 
Instance details

Defined in Control.Enumerable

Methods

enumerate :: forall (f :: Type -> Type). (Typeable f, Sized f) => Shared f Bool #

Enumerable Char

ASCII characters

Instance details

Defined in Control.Enumerable

Methods

enumerate :: forall (f :: Type -> Type). (Typeable f, Sized f) => Shared f Char #

Enumerable Double

Not a proper injection

Instance details

Defined in Control.Enumerable

Methods

enumerate :: forall (f :: Type -> Type). (Typeable f, Sized f) => Shared f Double #

Enumerable Float

Not a proper injection

Instance details

Defined in Control.Enumerable

Methods

enumerate :: forall (f :: Type -> Type). (Typeable f, Sized f) => Shared f Float #

Enumerable Int 
Instance details

Defined in Control.Enumerable

Methods

enumerate :: forall (f :: Type -> Type). (Typeable f, Sized f) => Shared f Int #

Enumerable Int8 
Instance details

Defined in Control.Enumerable

Methods

enumerate :: forall (f :: Type -> Type). (Typeable f, Sized f) => Shared f Int8 #

Enumerable Int16 
Instance details

Defined in Control.Enumerable

Methods

enumerate :: forall (f :: Type -> Type). (Typeable f, Sized f) => Shared f Int16 #

Enumerable Int32 
Instance details

Defined in Control.Enumerable

Methods

enumerate :: forall (f :: Type -> Type). (Typeable f, Sized f) => Shared f Int32 #

Enumerable Int64 
Instance details

Defined in Control.Enumerable

Methods

enumerate :: forall (f :: Type -> Type). (Typeable f, Sized f) => Shared f Int64 #

Enumerable Integer 
Instance details

Defined in Control.Enumerable

Methods

enumerate :: forall (f :: Type -> Type). (Typeable f, Sized f) => Shared f Integer #

Enumerable Ordering 
Instance details

Defined in Control.Enumerable

Methods

enumerate :: forall (f :: Type -> Type). (Typeable f, Sized f) => Shared f Ordering #

Enumerable Word 
Instance details

Defined in Control.Enumerable

Methods

enumerate :: forall (f :: Type -> Type). (Typeable f, Sized f) => Shared f Word #

Enumerable Word8 
Instance details

Defined in Control.Enumerable

Methods

enumerate :: forall (f :: Type -> Type). (Typeable f, Sized f) => Shared f Word8 #

Enumerable Word16 
Instance details

Defined in Control.Enumerable

Methods

enumerate :: forall (f :: Type -> Type). (Typeable f, Sized f) => Shared f Word16 #

Enumerable Word32 
Instance details

Defined in Control.Enumerable

Methods

enumerate :: forall (f :: Type -> Type). (Typeable f, Sized f) => Shared f Word32 #

Enumerable Word64 
Instance details

Defined in Control.Enumerable

Methods

enumerate :: forall (f :: Type -> Type). (Typeable f, Sized f) => Shared f Word64 #

Enumerable ()

The unit constructor is free

Instance details

Defined in Control.Enumerable

Methods

enumerate :: forall (f :: Type -> Type). (Typeable f, Sized f) => Shared f () #

Enumerable Unicode 
Instance details

Defined in Control.Enumerable

Methods

enumerate :: forall (f :: Type -> Type). (Typeable f, Sized f) => Shared f Unicode #

Enumerable Printable 
Instance details

Defined in Control.Enumerable

Methods

enumerate :: forall (f :: Type -> Type). (Typeable f, Sized f) => Shared f Printable #

Enumerable a => Enumerable [a] 
Instance details

Defined in Control.Enumerable

Methods

enumerate :: forall (f :: Type -> Type). (Typeable f, Sized f) => Shared f [a] #

Enumerable a => Enumerable (Maybe a) 
Instance details

Defined in Control.Enumerable

Methods

enumerate :: forall (f :: Type -> Type). (Typeable f, Sized f) => Shared f (Maybe a) #

Infinite a => Enumerable (Ratio a) 
Instance details

Defined in Control.Enumerable

Methods

enumerate :: forall (f :: Type -> Type). (Typeable f, Sized f) => Shared f (Ratio a) #

Infinite integer => Enumerable (Nat integer) 
Instance details

Defined in Control.Enumerable

Methods

enumerate :: forall (f :: Type -> Type). (Typeable f, Sized f) => Shared f (Nat integer) #

Enumerable a => Enumerable (NonEmpty a) 
Instance details

Defined in Control.Enumerable

Methods

enumerate :: forall (f :: Type -> Type). (Typeable f, Sized f) => Shared f (NonEmpty a) #

(CoEnumerable a, Enumerable b) => Enumerable (a -> b) 
Instance details

Defined in Control.Enumerable

Methods

enumerate :: forall (f :: Type -> Type). (Typeable f, Sized f) => Shared f (a -> b) #

(Enumerable a, Enumerable b) => Enumerable (Either a b) 
Instance details

Defined in Control.Enumerable

Methods

enumerate :: forall (f :: Type -> Type). (Typeable f, Sized f) => Shared f (Either a b) #

(Enumerable a, Enumerable b) => Enumerable (a, b) 
Instance details

Defined in Control.Enumerable

Methods

enumerate :: forall (f :: Type -> Type). (Typeable f, Sized f) => Shared f (a, b) #

(Enumerable a, Enumerable b, Enumerable c) => Enumerable (a, b, c) 
Instance details

Defined in Control.Enumerable

Methods

enumerate :: forall (f :: Type -> Type). (Typeable f, Sized f) => Shared f (a, b, c) #

(Enumerable a, Enumerable b, Enumerable c, Enumerable d) => Enumerable (a, b, c, d) 
Instance details

Defined in Control.Enumerable

Methods

enumerate :: forall (f :: Type -> Type). (Typeable f, Sized f) => Shared f (a, b, c, d) #

(Enumerable a, Enumerable b, Enumerable c, Enumerable d, Enumerable e) => Enumerable (a, b, c, d, e) 
Instance details

Defined in Control.Enumerable

Methods

enumerate :: forall (f :: Type -> Type). (Typeable f, Sized f) => Shared f (a, b, c, d, e) #

datatype :: forall a (f :: Type -> Type). (Typeable a, Sized f, Typeable f) => [Shareable f a] -> Shared f a #

Builds an enumeration of a data type from a list of constructors (see c0-c7)

c0 :: forall (f :: Type -> Type) a. Sized f => a -> Shareable f a #

Takes a constructor with arity 0 (a pure value)

c1 :: forall a (f :: Type -> Type) x. (Enumerable a, Sized f, Typeable f) => (a -> x) -> Shareable f x #

Takes a constructor of arity 1

c2 :: forall a b (f :: Type -> Type) x. (Enumerable a, Enumerable b, Sized f, Typeable f) => (a -> b -> x) -> Shareable f x #

c3 :: forall a b c (f :: Type -> Type) x. (Enumerable a, Enumerable b, Enumerable c, Sized f, Typeable f) => (a -> b -> c -> x) -> Shareable f x #

c4 :: forall a b c d (f :: Type -> Type) x. (Enumerable a, Enumerable b, Enumerable c, Enumerable d, Sized f, Typeable f) => (a -> b -> c -> d -> x) -> Shareable f x #

c5 :: forall a b c d e (f :: Type -> Type) x. (Enumerable a, Enumerable b, Enumerable c, Enumerable d, Enumerable e, Sized f, Typeable f) => (a -> b -> c -> d -> e -> x) -> Shareable f x #

c6 :: forall a b c d e g (f :: Type -> Type) x. (Enumerable a, Enumerable b, Enumerable c, Enumerable d, Enumerable e, Enumerable g, Sized f, Typeable f) => (a -> b -> c -> d -> e -> g -> x) -> Shareable f x #

c7 :: forall a b c d e g h (f :: Type -> Type) x. (Enumerable a, Enumerable b, Enumerable c, Enumerable d, Enumerable e, Enumerable g, Enumerable h, Sized f, Typeable f) => (a -> b -> c -> d -> e -> g -> h -> x) -> Shareable f x #

Automatic derivation

Accessing data

optimal :: Enumerable a => Enumerate a Source #

Memoised enumeration. Note that all cardinalities are kept in memory until your program terminates.

index :: Enumerable a => Integer -> a Source #

Index into an enumeration. Mainly used for party tricks (give it a really large number), since usually you want to distinguish values by size.

select :: Enumerable a => Int -> Index -> a Source #

A more fine grained version of index that takes a size and an index into the values of that size. select p i is only defined for i within bounds (meaning i < fst (values !! p)).

values :: Enumerable a => [(Integer, [a])] Source #

All values of the enumeration by increasing cost (which is the number of constructors for most types). Also contains the length of each list.

uniform :: Enumerable a => Int -> Gen a Source #

Compatibility with QuickCheck. Distribution is uniform generator over values bounded by the given size. Typical use: sized uniform.