Safe Haskell | None |
---|---|
Language | Haskell98 |
This module contains a (hopefully) manageable subset of the functionality of Feat. The rest resides only in the Test.Feat.* modules.
- test :: Enumerable a => (a -> Bool) -> IO (Result a)
- testOptions :: Enumerable a => Options -> (a -> Bool) -> IO (Result a)
- data Options = Options {}
- defOptions :: Options
- data Enumerate a
- class Typeable * a => Enumerable a where
- datatype :: (Typeable * a, Sized f, Typeable (* -> *) f) => [Shareable f a] -> Shared f a
- c0 :: Sized f => a -> Shareable f a
- c1 :: (Enumerable a, Sized f, Typeable (* -> *) f) => (a -> x) -> Shareable f x
- c2 :: (Enumerable a, Enumerable b, Sized f, Typeable (* -> *) f) => (a -> b -> x) -> Shareable f x
- c3 :: (Enumerable a, Enumerable b, Enumerable c, Sized f, Typeable (* -> *) f) => (a -> b -> c -> x) -> Shareable f x
- c4 :: (Enumerable a, Enumerable b, Enumerable c, Enumerable d, Sized f, Typeable (* -> *) f) => (a -> b -> c -> d -> x) -> Shareable f x
- c5 :: (Enumerable a, Enumerable b, Enumerable c, Enumerable d, Enumerable e, Sized f, Typeable (* -> *) f) => (a -> b -> c -> d -> e -> x) -> Shareable f x
- c6 :: (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 :: (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
- deriveEnumerable :: Name -> Q [Dec]
- optimal :: Enumerable a => Enumerate a
- index :: Enumerable a => Integer -> a
- select :: Enumerable a => Int -> Index -> a
- values :: Enumerable a => [(Integer, [a])]
- uniform :: Enumerable a => Int -> Gen a
Testing driver
test :: Enumerable a => (a -> Bool) -> IO (Result a) Source #
Test with default options (defOptions
).
testOptions :: Enumerable a => Options -> (a -> Bool) -> IO (Result a) Source #
Test with basic options.
Basic options for executing a test. Unlike FlexibleOptions
this type has Show/Read instances.
defOptions :: Options Source #
60 seconds timeout, maximum size of 100, bound of 100000 tests per size
The type class
A functional enumeration of type t
is a partition of
t
into finite numbered sets called Parts. Each parts contains values
of a certain cost (typically the size of the value).
Functor Enumerate Source # | Only use fmap with bijective functions (e.g. data constructors) |
Applicative Enumerate Source # | Pure is |
Alternative Enumerate Source # | |
Sized Enumerate Source # | |
Semigroup (Enumerate a) Source # | |
Monoid (Enumerate a) Source # | |
class Typeable * a => Enumerable a where #
datatype :: (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)
c1 :: (Enumerable a, Sized f, Typeable (* -> *) f) => (a -> x) -> Shareable f x #
Takes a constructor of arity 1
c2 :: (Enumerable a, Enumerable b, Sized f, Typeable (* -> *) f) => (a -> b -> x) -> Shareable f x #
c3 :: (Enumerable a, Enumerable b, Enumerable c, Sized f, Typeable (* -> *) f) => (a -> b -> c -> x) -> Shareable f x #
c4 :: (Enumerable a, Enumerable b, Enumerable c, Enumerable d, Sized f, Typeable (* -> *) f) => (a -> b -> c -> d -> x) -> Shareable f x #
c5 :: (Enumerable a, Enumerable b, Enumerable c, Enumerable d, Enumerable e, Sized f, Typeable (* -> *) f) => (a -> b -> c -> d -> e -> x) -> Shareable f x #
c6 :: (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 :: (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
deriveEnumerable :: Name -> Q [Dec] #
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.