Safe Haskell | None |
---|---|
Language | Haskell98 |
Basic combinators for building enumerations most users will want to use the type class based combinators in Test.Feat.Class instead.
- type Index = Integer
- data Enumerate a = Enumerate {}
- parts :: Enumerate a -> [Finite a]
- fromParts :: [Finite a] -> Enumerate a
- data RevList a = RevList {}
- toRev :: [a] -> RevList a
- data Finite a = Finite {}
- fromFinite :: Finite a -> (Index, [a])
- module Data.Monoid
- union :: Enumerate a -> Enumerate a -> Enumerate a
- module Control.Applicative
- cartesian :: Enumerate a -> Enumerate b -> Enumerate (a, b)
- singleton :: a -> Enumerate a
- pay :: Enumerate a -> Enumerate a
- module Data.Typeable
- data Tag = Source String String Int Int
- tag :: Q Exp
- eShare :: Typeable a => Tag -> Enumerate a -> Enumerate a
- noOptim :: Enumerate a -> Enumerate a
- optimise :: Enumerate a -> Enumerate a
- irregular :: Enumerate a -> Enumerate a
Documentation
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).
Reversed lists
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.
toRev :: [a] -> RevList a Source
Constructs a "Reverse list" variant of a given list. In a sensible
Haskell implementation evaluating any inital segment of
uses linear memory in the size of the segment.reversals
(toRev xs)
Finite ordered sets
fromFinite :: Finite a -> (Index, [a]) Source
Combinators for building enumerations
module Data.Monoid
module Control.Applicative
Polymorphic sharing
module Data.Typeable