RepLib-0.5.4: Generic programming library with representation types

LicenseBSD
Maintainersweirich@cis.upenn.edu
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Generics.RepLib.Lib

Contents

Description

A library of 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 -> 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

rnf :: Rep a => a -> a Source #

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 Ints in a datastructure For example: gsum ( 1 , True, ("a", Maybe 3, []) , Nothing) 4

Methods

gsum :: a -> Int Source #

Instances

GSum Bool Source # 

Methods

gsum :: Bool -> Int Source #

GSum Char Source # 

Methods

gsum :: Char -> Int Source #

GSum Double Source # 

Methods

gsum :: Double -> Int Source #

GSum Float Source # 

Methods

gsum :: Float -> Int Source #

GSum Int Source # 

Methods

gsum :: Int -> Int Source #

GSum Integer Source # 

Methods

gsum :: Integer -> Int Source #

GSum () Source # 

Methods

gsum :: () -> Int Source #

GSum a => GSum [a] Source # 

Methods

gsum :: [a] -> Int Source #

GSum a => GSum (Set a) Source # 

Methods

gsum :: Set a -> Int Source #

(GSum a, GSum b) => GSum (a, b) Source # 

Methods

gsum :: (a, b) -> Int Source #

(Rep k, GSum a) => GSum (Map k a) Source # 

Methods

gsum :: Map k a -> Int Source #

class Rep1 ZeroD a => Zero a where Source #

Create a zero element of a type ( zero :: ((Int, Maybe Int), Float)) ((0, Nothing), 0.0)

Methods

zero :: a Source #

Instances

Zero Bool Source # 

Methods

zero :: Bool Source #

Zero Char Source # 

Methods

zero :: Char Source #

Zero Double Source # 

Methods

zero :: Double Source #

Zero Float Source # 

Methods

zero :: Float Source #

Zero Int Source # 

Methods

zero :: Int Source #

Zero Integer Source # 

Methods

zero :: Integer Source #

Zero () Source # 

Methods

zero :: () Source #

Zero IOError Source # 

Methods

zero :: IOError Source #

Zero a => Zero [a] Source # 

Methods

zero :: [a] Source #

Rep a => Zero (Set a) Source # 

Methods

zero :: Set a Source #

(Zero a, Zero b) => Zero (a -> b) Source # 

Methods

zero :: a -> b Source #

(Zero a, Zero b) => Zero (a, b) Source # 

Methods

zero :: (a, b) Source #

(Rep k, Rep a) => Zero (Map k a) Source # 

Methods

zero :: Map k a Source #

class Rep1 GenerateD a => Generate a where Source #

Generate elements of a type up to a certain depth

Methods

generate :: Int -> [a] Source #

Instances

Generate Char Source # 

Methods

generate :: Int -> [Char] Source #

Generate Double Source # 

Methods

generate :: Int -> [Double] Source #

Generate Float Source # 

Methods

generate :: Int -> [Float] Source #

Generate Int Source # 

Methods

generate :: Int -> [Int] Source #

Generate Integer Source # 

Methods

generate :: Int -> [Integer] Source #

Generate () Source # 

Methods

generate :: Int -> [()] Source #

Generate a => Generate [a] Source # 

Methods

generate :: Int -> [[a]] Source #

(Ord a, Generate a) => Generate (Set a) Source # 

Methods

generate :: Int -> [Set a] Source #

(Generate a, Generate b) => Generate (a, b) Source # 

Methods

generate :: Int -> [(a, b)] Source #

(Ord k, Generate k, Generate a) => Generate (Map k a) Source # 

Methods

generate :: Int -> [Map k a] Source #

class Rep1 EnumerateD a => Enumerate a where Source #

enumerate the elements of a type, in DFS order.

Methods

enumerate :: [a] Source #

Instances

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

Methods

shrink :: a -> [a] Source #

Instances

Shrink Char Source # 

Methods

shrink :: Char -> [Char] Source #

Shrink Int Source # 

Methods

shrink :: Int -> [Int] Source #

Shrink () Source # 

Methods

shrink :: () -> [()] Source #

Shrink a => Shrink [a] Source # 

Methods

shrink :: [a] -> [[a]] Source #

(Ord a, Shrink a) => Shrink (Set a) Source # 

Methods

shrink :: Set a -> [Set a] Source #

(Shrink a, Shrink b) => Shrink (a, b) Source # 

Methods

shrink :: (a, b) -> [(a, b)] Source #

(Ord k, Shrink k, Shrink a) => Shrink (Map k a) Source # 

Methods

shrink :: Map k a -> [Map k a] Source #

class Rep1 (LreduceD b) a => Lreduce b a where Source #

A general version of fold left, use for Fold class below

Methods

lreduce :: b -> a -> b Source #

Instances

Lreduce b Bool Source # 

Methods

lreduce :: b -> Bool -> b Source #

Lreduce b Char Source # 

Methods

lreduce :: b -> Char -> b Source #

Lreduce b () Source # 

Methods

lreduce :: b -> () -> b Source #

Lreduce b Int Source # 

Methods

lreduce :: b -> Int -> b Source #

(Ord a, Lreduce b a) => Lreduce b (Set a) Source # 

Methods

lreduce :: b -> Set a -> b Source #

Lreduce c a => Lreduce c [a] Source # 

Methods

lreduce :: c -> [a] -> c Source #

(Lreduce c a, Lreduce c b) => Lreduce c (a, b) Source # 

Methods

lreduce :: c -> (a, b) -> c Source #

class Rep1 (RreduceD b) a => Rreduce b a where Source #

A general version of fold right, use for Fold class below

Methods

rreduce :: a -> b -> b Source #

Instances

Rreduce b Bool Source # 

Methods

rreduce :: Bool -> b -> b Source #

Rreduce b Char Source # 

Methods

rreduce :: Char -> b -> b Source #

Rreduce b () Source # 

Methods

rreduce :: () -> b -> b Source #

Rreduce b Int Source # 

Methods

rreduce :: Int -> b -> b Source #

(Ord a, Rreduce b a) => Rreduce b (Set a) Source # 

Methods

rreduce :: Set a -> b -> b Source #

Rreduce c a => Rreduce c [a] Source # 

Methods

rreduce :: [a] -> c -> c Source #

(Rreduce c a, Rreduce c b) => Rreduce c (a, b) Source # 

Methods

rreduce :: (a, b) -> c -> c Source #

Generic operations based on Fold

class Fold f where Source #

All of the functions below are defined using instances of the following class

Minimal complete definition

foldRight, foldLeft

Methods

foldRight :: Rep a => (a -> b -> b) -> f a -> b -> b Source #

foldLeft :: Rep a => (b -> a -> b) -> b -> f a -> b Source #

Instances

Fold [] Source # 

Methods

foldRight :: Rep a => (a -> b -> b) -> [a] -> b -> b Source #

foldLeft :: Rep a => (b -> a -> b) -> b -> [a] -> b Source #

Fold Set Source # 

Methods

foldRight :: Rep a => (a -> b -> b) -> Set a -> b -> b Source #

foldLeft :: Rep a => (b -> a -> b) -> b -> Set a -> b Source #

Fold (Map k) Source # 

Methods

foldRight :: Rep a => (a -> b -> b) -> Map k a -> b -> b Source #

foldLeft :: Rep a => (b -> a -> b) -> b -> Map k a -> b Source #

crush :: (Rep a, Fold t) => (a -> a -> a) -> a -> t a -> a Source #

Fold a bindary operation left over a datastructure

gproduct :: (Rep a, Num a, Fold t) => t a -> a Source #

Multiply all elements together

gand :: Fold t => t Bool -> Bool Source #

Ensure all booleans are true

gor :: Fold t => t Bool -> Bool Source #

Ensure at least one boolean is true

flatten :: (Rep a, Fold t) => t a -> [a] Source #

Convert to list

count :: (Rep a, Fold t) => t a -> Int Source #

Count number of as that appear in the argument

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

gall :: (Rep a, Fold t) => (a -> Bool) -> t a -> Bool Source #

Ensure property holds of all data

gany :: (Rep a, Fold t) => (a -> Bool) -> t a -> Bool Source #

Ensure property holds of some element

gelem :: (Rep a, Eq a, Fold t) => a -> t a -> Bool Source #

Is an element stored in a datastructure

Auxiliary types and generators for derivable classes

data GSumD a Source #

Constructors

GSumD 

Fields

Instances

GSum a => Sat (GSumD a) Source # 

Methods

dict :: GSumD a Source #

data ZeroD a Source #

Constructors

ZD 

Fields

Instances

Zero a => Sat (ZeroD a) Source # 

Methods

dict :: ZeroD a Source #

data GenerateD a Source #

Constructors

GenerateD 

Fields

Instances

data EnumerateD a Source #

Constructors

EnumerateD 

Fields

Instances

data ShrinkD a Source #

Constructors

ShrinkD 

Fields

Instances

Shrink a => Sat (ShrinkD a) Source # 

Methods

dict :: ShrinkD a Source #

data LreduceD b a Source #

Constructors

LreduceD 

Fields

Instances

Lreduce b a => Sat (LreduceD b a) Source # 

Methods

dict :: LreduceD b a Source #

data RreduceD b a Source #

Constructors

RreduceD 

Fields

Instances

Rreduce b a => Sat (RreduceD b a) Source # 

Methods

dict :: RreduceD b a Source #

rnfR :: R a -> a -> a Source #

deepSeqR :: R a -> a -> b -> b Source #

gsumR1 :: R1 GSumD a -> a -> Int Source #

zeroR1 :: R1 ZeroD a -> a Source #

lreduceR1 :: R1 (LreduceD b) a -> b -> a -> b Source #

rreduceR1 :: R1 (RreduceD b) a -> a -> b -> b Source #