RepLib-0.2.1: Generic programming library with representation typesSource codeContentsIndex
Data.RepLib.Lib
Portabilitynon-portable
Stabilityexperimental
Maintainersweirich@cis.upenn.edu
Contents
Available for all representable types
Derivable classes
Generic operations based on Fold
Types and generators for derivable classes
Description
A library of specializable, type-indexed functions
Synopsis
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
gsum :: a -> Int
class Rep1 ZeroD a => Zero a where
zero :: a
class Rep1 GenerateD a => Generate a where
generate :: Int -> [a]
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
foldRight :: Rep a => (a -> b -> b) -> f a -> b -> b
foldLeft :: Rep a => (b -> a -> b) -> b -> f a -> b
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 {
gsumD :: a -> Int
}
data ZeroD a = ZD {
zeroD :: a
}
data GenerateD a = GenerateD {
generateD :: Int -> [a]
}
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 -> bSource
deepSeq recursively forces the evaluation of its entire argument.
rnf :: Rep a => a -> aSource
rnf forces the evaluation of *datatypes* to their normal forms. However, other types are left alone and not forced.
Derivable classes
class Rep1 GSumD a => GSum a whereSource
Add together all of the Ints in a datastructure
Methods
gsum :: a -> IntSource
show/hide Instances
class Rep1 ZeroD a => Zero a whereSource
Create a zero element of a type
Methods
zero :: aSource
show/hide Instances
class Rep1 GenerateD a => Generate a whereSource
Generate elements of a type up to a certain depth
Methods
generate :: Int -> [a]Source
show/hide Instances
class Rep1 EnumerateD a => Enumerate a whereSource
enumerate the elements of a type, in DFS order.
Methods
enumerate :: [a]Source
class Rep1 ShrinkD a => Shrink a whereSource
Methods
shrink :: a -> [a]Source
show/hide Instances
class Rep1 (LreduceD b) a => Lreduce b a whereSource
Methods
lreduce :: b -> a -> bSource
show/hide Instances
Lreduce b Bool
Lreduce b Char
Lreduce b ()
Lreduce b Int
Lreduce c a => Lreduce c ([] a)
(Lreduce c a, Lreduce c b) => Lreduce c ((,) a b)
class Rep1 (RreduceD b) a => Rreduce b a whereSource
Methods
rreduce :: a -> b -> bSource
show/hide Instances
Rreduce b Bool
Rreduce b Char
Rreduce b ()
Rreduce b Int
Rreduce c a => Rreduce c ([] a)
(Rreduce c a, Rreduce c b) => Rreduce c ((,) a b)
Generic operations based on Fold
class Fold f whereSource
Methods
foldRight :: Rep a => (a -> b -> b) -> f a -> b -> bSource
foldLeft :: Rep a => (b -> a -> b) -> b -> f a -> bSource
show/hide Instances
Fold []
crush :: (Rep a, Fold t) => (a -> a -> a) -> a -> t a -> aSource
gproduct :: (Rep a, Num a, Fold t) => t a -> aSource
gand :: Fold t => t Bool -> BoolSource
gor :: Fold t => t Bool -> BoolSource
flatten :: (Rep a, Fold t) => t a -> [a]Source
count :: (Rep a, Fold t) => t a -> IntSource
comp :: (Rep a, Fold t) => t (a -> a) -> a -> aSource
gconcat :: (Rep a, Fold t) => t [a] -> [a]Source
gall :: (Rep a, Fold t) => (a -> Bool) -> t a -> BoolSource
gany :: (Rep a, Fold t) => (a -> Bool) -> t a -> BoolSource
gelem :: (Rep a, Eq a, Fold t) => a -> t a -> BoolSource
Types and generators for derivable classes
data GSumD a Source
Constructors
GSumD
gsumD :: a -> Int
show/hide Instances
GSum a => Sat (GSumD a)
data ZeroD a Source
Constructors
ZD
zeroD :: a
show/hide Instances
Zero a => Sat (ZeroD a)
data GenerateD a Source
Constructors
GenerateD
generateD :: Int -> [a]
show/hide Instances
data EnumerateD a Source
Constructors
EnumerateD
enumerateD :: [a]
show/hide Instances
data ShrinkD a Source
Constructors
ShrinkD
shrinkD :: a -> [a]
show/hide Instances
Shrink a => Sat (ShrinkD a)
data LreduceD b a Source
Constructors
LreduceD
lreduceD :: b -> a -> b
show/hide Instances
Lreduce b a => Sat (LreduceD b a)
data RreduceD b a Source
Constructors
RreduceD
rreduceD :: a -> b -> b
show/hide Instances
Rreduce b a => Sat (RreduceD b a)
rnfR :: R a -> a -> aSource
deepSeqR :: R a -> a -> b -> bSource
gsumR1 :: R1 GSumD a -> a -> IntSource
zeroR1 :: R1 ZeroD a -> aSource
generateR1 :: R1 GenerateD a -> Int -> [a]Source
enumerateR1 :: R1 EnumerateD a -> [a]Source
lreduceR1 :: R1 (LreduceD b) a -> b -> a -> bSource
rreduceR1 :: R1 (RreduceD b) a -> a -> b -> bSource
Produced by Haddock version 2.4.2