RepLib-0.2.2: Generic programming library with representation types

Portabilitynon-portable
Stabilityexperimental
Maintainersweirich@cis.upenn.edu

Data.RepLib.Lib

Contents

Description

A library of specializable, type-indexed functions

Synopsis

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

Instances

GSum Bool 
GSum Char 
GSum Double 
GSum Float 
GSum Int 
GSum Integer 
GSum () 
GSum a => GSum [a] 
(GSum a, GSum b) => GSum (a, b) 

class Rep1 ZeroD a => Zero a whereSource

Create a zero element of a type

Methods

zero :: aSource

Instances

Zero Bool 
Zero Char 
Zero Double 
Zero Float 
Zero Int 
Zero Integer 
Zero () 
Zero IOError 
Zero a => Zero [a] 
(Zero a, Zero b) => Zero (a -> b) 
(Zero a, Zero b) => Zero (a, b) 

class Rep1 GenerateD a => Generate a whereSource

Generate elements of a type up to a certain depth

Methods

generate :: Int -> [a]Source

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

Instances

Shrink Char 
Shrink Int 
Shrink () 
Shrink a => Shrink [a] 
(Shrink a, Shrink b) => Shrink (a, b) 

class Rep1 (LreduceD b) a => Lreduce b a whereSource

Methods

lreduce :: b -> a -> bSource

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

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

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 

Fields

gsumD :: a -> Int
 

Instances

GSum a => Sat (GSumD a) 

data ZeroD a Source

Constructors

ZD 

Fields

zeroD :: a
 

Instances

Zero a => Sat (ZeroD a) 

data GenerateD a Source

Constructors

GenerateD 

Fields

generateD :: Int -> [a]
 

Instances

data EnumerateD a Source

Constructors

EnumerateD 

Fields

enumerateD :: [a]
 

Instances

data ShrinkD a Source

Constructors

ShrinkD 

Fields

shrinkD :: a -> [a]
 

Instances

Shrink a => Sat (ShrinkD a) 

data LreduceD b a Source

Constructors

LreduceD 

Fields

lreduceD :: b -> a -> b
 

Instances

Lreduce b a => Sat (LreduceD b a) 

data RreduceD b a Source

Constructors

RreduceD 

Fields

rreduceD :: a -> b -> b
 

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

lreduceR1 :: R1 (LreduceD b) a -> b -> a -> bSource

rreduceR1 :: R1 (RreduceD b) a -> a -> b -> bSource