testing-feat-1.1.0.0: Functional Enumeration of Algebraic Types

Safe HaskellNone
LanguageHaskell98

Test.Feat.Enumerate

Contents

Description

Basic combinators for building enumerations most users will want to use the type class based combinators in Test.Feat.Class instead.

Synopsis

Documentation

data Enumerate a Source #

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).

Constructors

Enumerate 

Fields

Instances

Functor Enumerate Source #

Only use fmap with bijective functions (e.g. data constructors)

Methods

fmap :: (a -> b) -> Enumerate a -> Enumerate b #

(<$) :: a -> Enumerate b -> Enumerate a #

Applicative Enumerate Source #

Pure is singleton and <*> corresponds to cartesian product (as with lists)

Methods

pure :: a -> Enumerate a #

(<*>) :: Enumerate (a -> b) -> Enumerate a -> Enumerate b #

liftA2 :: (a -> b -> c) -> Enumerate a -> Enumerate b -> Enumerate c #

(*>) :: Enumerate a -> Enumerate b -> Enumerate b #

(<*) :: Enumerate a -> Enumerate b -> Enumerate a #

Alternative Enumerate Source # 

Methods

empty :: Enumerate a #

(<|>) :: Enumerate a -> Enumerate a -> Enumerate a #

some :: Enumerate a -> Enumerate [a] #

many :: Enumerate a -> Enumerate [a] #

Sized Enumerate Source # 
Semigroup (Enumerate a) Source # 

Methods

(<>) :: Enumerate a -> Enumerate a -> Enumerate a #

sconcat :: NonEmpty (Enumerate a) -> Enumerate a #

stimes :: Integral b => b -> Enumerate a -> Enumerate a #

Monoid (Enumerate a) Source #

The mappend is (disjoint) union

Reversed lists

data RevList a Source #

A data structure that contains a list and the reversals of all initial segments of the list. Intuitively

reversals xs !! n = reverse (take (n+1) (fromRev xs))

Any operation on a RevList typically discards the reversals and constructs new reversals on demand.

Constructors

RevList 

Fields

Instances

Functor RevList Source # 

Methods

fmap :: (a -> b) -> RevList a -> RevList b #

(<$) :: a -> RevList b -> RevList a #

Show a => Show (RevList a) Source # 

Methods

showsPrec :: Int -> RevList a -> ShowS #

show :: RevList a -> String #

showList :: [RevList a] -> ShowS #

Semigroup a => Semigroup (RevList a) Source # 

Methods

(<>) :: RevList a -> RevList a -> RevList a #

sconcat :: NonEmpty (RevList a) -> RevList a #

stimes :: Integral b => b -> RevList a -> RevList a #

(Monoid a, Semigroup a) => Monoid (RevList a) Source #

Padded zip

Methods

mempty :: RevList a #

mappend :: RevList a -> RevList a -> RevList a #

mconcat :: [RevList a] -> RevList a #

toRev :: [a] -> RevList a Source #

Constructs a "Reverse list" variant of a given list. In a sensible Haskell implementation evaluating any inital segment of reversals (toRev xs) uses linear memory in the size of the segment.

Finite ordered sets

data Finite a Source #

Constructors

Finite 

Fields

Instances

Functor Finite Source # 

Methods

fmap :: (a -> b) -> Finite a -> Finite b #

(<$) :: a -> Finite b -> Finite a #

Applicative Finite Source # 

Methods

pure :: a -> Finite a #

(<*>) :: Finite (a -> b) -> Finite a -> Finite b #

liftA2 :: (a -> b -> c) -> Finite a -> Finite b -> Finite c #

(*>) :: Finite a -> Finite b -> Finite b #

(<*) :: Finite a -> Finite b -> Finite a #

Alternative Finite Source # 

Methods

empty :: Finite a #

(<|>) :: Finite a -> Finite a -> Finite a #

some :: Finite a -> Finite [a] #

many :: Finite a -> Finite [a] #

Show a => Show (Finite a) Source # 

Methods

showsPrec :: Int -> Finite a -> ShowS #

show :: Finite a -> String #

showList :: [Finite a] -> ShowS #

Semigroup (Finite a) Source # 

Methods

(<>) :: Finite a -> Finite a -> Finite a #

sconcat :: NonEmpty (Finite a) -> Finite a #

stimes :: Integral b => b -> Finite a -> Finite a #

Monoid (Finite a) Source # 

Methods

mempty :: Finite a #

mappend :: Finite a -> Finite a -> Finite a #

mconcat :: [Finite a] -> Finite a #

fromFinite :: Finite a -> (Index, [a]) Source #

Combinators for building enumerations

singleton :: a -> Enumerate a Source #

The definition of pure for the applicative instance.

pay :: Sized f => forall a. f a -> f a #

Increases the cost/size of all values in the given set.