License | BSD |
---|---|
Maintainer | sweirich@cis.upenn.edu |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Generics.RepLib.Lib
Contents
Description
A library of type-indexed functions
- subtrees :: forall a. Rep a => a -> [a]
- deepSeq :: Rep a => a -> b -> b
- rnf :: Rep a => a -> a
- class Rep1 GSumD a => GSum a where
- class Rep1 ZeroD a => Zero a where
- zero :: a
- class Rep1 GenerateD a => Generate a where
- class Rep1 EnumerateD a => Enumerate a where
- enumerate :: [a]
- class Rep1 ShrinkD a => Shrink a where
- shrink :: a -> [a]
- class Rep1 (LreduceD b) a => Lreduce b a where
- lreduce :: b -> a -> b
- class Rep1 (RreduceD b) a => Rreduce b a where
- rreduce :: a -> b -> b
- class Fold f where
- crush :: (Rep a, Fold t) => (a -> a -> a) -> a -> t a -> a
- gproduct :: (Rep a, Num a, Fold t) => t a -> a
- gand :: Fold t => t Bool -> Bool
- gor :: Fold t => t Bool -> Bool
- flatten :: (Rep a, Fold t) => t a -> [a]
- count :: (Rep a, Fold t) => t a -> Int
- comp :: (Rep a, Fold t) => t (a -> a) -> a -> a
- gconcat :: (Rep a, Fold t) => t [a] -> [a]
- gall :: (Rep a, Fold t) => (a -> Bool) -> t a -> Bool
- gany :: (Rep a, Fold t) => (a -> Bool) -> t a -> Bool
- gelem :: (Rep a, Eq a, Fold t) => a -> t a -> Bool
- data GSumD a = GSumD {}
- data ZeroD a = ZD {
- zeroD :: a
- data GenerateD a = GenerateD {}
- data EnumerateD a = EnumerateD {
- enumerateD :: [a]
- data ShrinkD a = ShrinkD {
- shrinkD :: a -> [a]
- data LreduceD b a = LreduceD {
- lreduceD :: b -> a -> b
- data RreduceD b a = RreduceD {
- rreduceD :: a -> b -> b
- rnfR :: R a -> a -> a
- deepSeqR :: R a -> a -> b -> b
- gsumR1 :: R1 GSumD a -> a -> Int
- zeroR1 :: R1 ZeroD a -> a
- generateR1 :: R1 GenerateD a -> Int -> [a]
- enumerateR1 :: R1 EnumerateD a -> [a]
- lreduceR1 :: R1 (LreduceD b) a -> b -> a -> b
- rreduceR1 :: R1 (RreduceD b) a -> a -> b -> b
Available for all representable types
subtrees :: forall a. Rep a => a -> [a] Source
Produce all children of a datastructure with the same type. Note that subtrees is available for all representable types. For those that are not recursive datatypes, subtrees will always return the empty list. But, these trivial instances are convenient to have for the Shrink operation below.
deepSeq :: Rep a => a -> b -> b Source
Recursively force the evaluation of the first
argument. For example,
deepSeq ( x , y ) z where
x = ...
y = ...
will evaluate both x
and y
then return z
Force the evaluation of *datatypes* to their normal forms. Other types are left alone and not forced.
Specializable type-indexed functions
class Rep1 GSumD a => GSum a where Source
Add together all of the Int
s in a datastructure
For example:
gsum ( 1 , True, ("a", Maybe 3, []) , Nothing)
4
Minimal complete definition
Nothing
class Rep1 ZeroD a => Zero a where Source
Create a zero element of a type
( zero :: ((Int, Maybe Int), Float))
((0, Nothing), 0.0)
Minimal complete definition
Nothing
Instances
Zero Bool Source | |
Zero Char Source | |
Zero Double Source | |
Zero Float Source | |
Zero Int Source | |
Zero Integer Source | |
Zero () Source | |
Zero IOError Source | |
Zero a => Zero [a] Source | |
Rep a => Zero (Set a) Source | |
(Zero a, Zero b) => Zero (a -> b) Source | |
(Zero a, Zero b) => Zero (a, b) Source | |
(Rep k, Rep a) => Zero (Map k a) Source |
class Rep1 GenerateD a => Generate a where Source
Generate elements of a type up to a certain depth
Minimal complete definition
Nothing
Instances
Generate Char Source | |
Generate Double Source | |
Generate Float Source | |
Generate Int Source | |
Generate Integer Source | |
Generate () Source | |
Generate a => Generate [a] Source | |
(Ord a, Generate a) => Generate (Set a) Source | |
(Generate a, Generate b) => Generate (a, b) Source | |
(Ord k, Generate k, Generate a) => Generate (Map k a) Source |
class Rep1 EnumerateD a => Enumerate a where Source
enumerate the elements of a type, in DFS order.
Minimal complete definition
Nothing
Instances
Enumerate Bool Source | |
Enumerate Char Source | |
Enumerate Double Source | |
Enumerate Float Source | |
Enumerate Int Source | |
Enumerate Integer Source | |
Enumerate () Source | |
Enumerate a => Enumerate [a] Source | |
(Ord a, Enumerate a) => Enumerate (Set a) Source | |
(Enumerate a, Enumerate b) => Enumerate (a, b) Source | |
(Ord k, Enumerate k, Enumerate a) => Enumerate (Map k a) Source |
class Rep1 ShrinkD a => Shrink a where Source
Given an element, return smaller elements of the same type for example, to automatically find small counterexamples when testing
Minimal complete definition
Nothing
class Rep1 (LreduceD b) a => Lreduce b a where Source
A general version of fold left, use for Fold class below
Minimal complete definition
Nothing
class Rep1 (RreduceD b) a => Rreduce b a where Source
A general version of fold right, use for Fold class below
Minimal complete definition
Nothing
Generic operations based on Fold
All of the functions below are defined using instances of the following class
crush :: (Rep a, Fold t) => (a -> a -> a) -> a -> t a -> a Source
Fold a bindary operation left over a datastructure
comp :: (Rep a, Fold t) => t (a -> a) -> a -> a Source
Compose all functions in the datastructure together
gconcat :: (Rep a, Fold t) => t [a] -> [a] Source
Concatenate all lists in the datastructure together
Auxiliary types and generators for derivable classes
data EnumerateD a Source
Constructors
EnumerateD | |
Fields
|
Instances
Enumerate a => Sat (EnumerateD a) Source |
generateR1 :: R1 GenerateD a -> Int -> [a] Source
enumerateR1 :: R1 EnumerateD a -> [a] Source