simple-enumeration-0.2: Finite or countably infinite sequences of values.

CopyrightBrent Yorgey
Maintainerbyorgey@gmail.com
Safe HaskellNone
LanguageHaskell2010

Data.Enumeration

Contents

Description

An enumeration is a finite or countably infinite sequence of values, that is, enumerations are isomorphic to lists. However, enumerations are represented a functions from index to value, so they support efficient indexing and can be constructed for very large finite sets. A few examples are shown below.

>>> enumerate . takeE 15 $ listOf nat
[[],[0],[0,0],[1],[0,0,0],[1,0],[2],[0,1],[1,0,0],[2,0],[3],[0,0,0,0],[1,1],[2,0,0],[3,0]]
>>> select (listOf nat) 986235087203970702008108646
[11987363624969,1854392,1613,15,0,2,0]
data Tree = L | B Tree Tree deriving Show

treesUpTo :: Int -> Enumeration Tree
treesUpTo 0 = singleton L
treesUpTo n = singleton L <|> B <$> t' <*> t'
  where t' = treesUpTo (n-1)

trees :: Enumeration Tree
trees = infinite $ singleton L <|> B <$> trees <*> trees
>>> card (treesUpTo 1)
Finite 2
>>> card (treesUpTo 10)
Finite 14378219780015246281818710879551167697596193767663736497089725524386087657390556152293078723153293423353330879856663164406809615688082297859526620035327291442156498380795040822304677
>>> select (treesUpTo 5) 12345
B (B L (B (B (B L L) L) (B L L))) (B (B (B L L) L) (B L L))
>>> card trees
Infinite
>>> select trees 12345
B (B (B (B L (B L L)) L) (B L (B (B L L) L))) (B (B L (B L L)) (B (B L L) (B L (B L L))))

For invertible enumerations, i.e. bijections between some set of values and natural numbers (or finite prefix thereof), see Data.Enumeration.Invertible.

Synopsis

Enumerations

data Enumeration a Source #

An enumeration of a finite or countably infinite set of values. An enumeration is represented as a function from the natural numbers (for infinite enumerations) or a finite prefix of the natural numbers (for finite ones) to values. Enumerations can thus easily be constructed for very large sets, and support efficient indexing and random sampling.

Enumeration is an instance of the following type classes:

  • Functor (you can map a function over every element of an enumeration)
  • Applicative (representing Cartesian product of enumerations; see (><))
  • Alternative (representing disjoint union of enumerations; see (<+>))

Enumeration is not a Monad, since there is no way to implement join that works for any combination of finite and infinite enumerations (but see interleave).

Instances
Functor Enumeration Source # 
Instance details

Defined in Data.Enumeration

Methods

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

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

Applicative Enumeration Source #

The Applicative instance for Enumeration works similarly to the instance for lists: pure = singleton, and f <*> x takes the Cartesian product of f and x (see (><)) and applies each paired function and argument.

Instance details

Defined in Data.Enumeration

Methods

pure :: a -> Enumeration a #

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

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

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

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

Alternative Enumeration Source #

The Alternative instance for Enumeration represents the sum monoidal structure on enumerations: empty is the empty enumeration, and (<|>) = (<+>) is disjoint union.

Instance details

Defined in Data.Enumeration

mkEnumeration :: Cardinality -> (Index -> a) -> Enumeration a Source #

Create an enumeration primitively out of a cardinality and an index function.

Using enumerations

data Cardinality Source #

The cardinality of a countable set: either a specific finite natural number, or countably infinite.

Constructors

Finite !Integer 
Infinite 
Instances
Eq Cardinality Source # 
Instance details

Defined in Data.Enumeration

Num Cardinality Source #

Cardinality has a Num instance for convenience, so we can use numeric literals as finite cardinalities, and add, subtract, and multiply cardinalities. Note that:

  • subtraction is saturating (i.e. 3 - 5 = 0)
  • infinity - infinity is treated as zero
  • zero is treated as a "very strong" annihilator for multiplication: even infinity * zero = zero.
Instance details

Defined in Data.Enumeration

Ord Cardinality Source # 
Instance details

Defined in Data.Enumeration

Show Cardinality Source # 
Instance details

Defined in Data.Enumeration

card :: Enumeration a -> Cardinality Source #

Get the cardinality of an enumeration.

type Index = Integer Source #

An index into an enumeration.

select :: Enumeration a -> Index -> a Source #

Select the value at a particular index of an enumeration. Precondition: the index must be strictly less than the cardinality. For infinite sets, every possible value must occur at some finite index.

isFinite :: Enumeration a -> Bool Source #

Test whether an enumeration is finite.

>>> isFinite (finiteList [1,2,3])
True
>>> isFinite nat
False

enumerate :: Enumeration a -> [a] Source #

List the elements of an enumeration in order. Inverse of finiteList.

Primitive enumerations

unit :: Enumeration () Source #

The unit enumeration, with a single value of ().

>>> card unit
Finite 1
>>> enumerate unit
[()]

singleton :: a -> Enumeration a Source #

An enumeration of a single given element.

>>> card (singleton 17)
Finite 1
>>> enumerate (singleton 17)
[17]

always :: a -> Enumeration a Source #

A constant infinite enumeration.

>>> card (always 17)
Infinite
>>> enumerate . takeE 10 $ always 17
[17,17,17,17,17,17,17,17,17,17]

finite :: Integer -> Enumeration Integer Source #

A finite prefix of the natural numbers.

>>> card (finite 5)
Finite 5
>>> card (finite 1234567890987654321)
Finite 1234567890987654321
>>> enumerate (finite 5)
[0,1,2,3,4]
>>> enumerate (finite 0)
[]

finiteList :: [a] -> Enumeration a Source #

Construct an enumeration from the elements of a finite list. To turn an enumeration back into a list, use enumerate.

>>> enumerate (finiteList [2,3,8,1])
[2,3,8,1]
>>> select (finiteList [2,3,8,1]) 2
8

finiteList does not work on infinite lists: inspecting the cardinality of the resulting enumeration (something many of the enumeration combinators need to do) will hang trying to compute the length of the infinite list. To make an infinite enumeration, use something like f <$> nat where f is a function to compute the value at any given index.

finiteList uses (!!) internally, so you probably want to avoid using it on long lists. It would be possible to make a version with better indexing performance by allocating a vector internally, but I am too lazy to do it. If you have a good use case let me know (better yet, submit a pull request).

boundedEnum :: forall a. (Enum a, Bounded a) => Enumeration a Source #

Enumerate all the values of a bounded Enum instance.

>>> enumerate (boundedEnum @Bool)
[False,True]
>>> select (boundedEnum @Char) 97
'a'
>>> card (boundedEnum @Int)
Finite 18446744073709551616
>>> select (boundedEnum @Int) 0
-9223372036854775808

nat :: Enumeration Integer Source #

The natural numbers, 0, 1, 2, ....

>>> enumerate . takeE 10 $ nat
[0,1,2,3,4,5,6,7,8,9]

int :: Enumeration Integer Source #

All integers in the order 0, 1, -1, 2, -2, 3, -3, ....

cw :: Enumeration Rational Source #

The positive rational numbers, enumerated according to the Calkin-Wilf sequence.

>>> enumerate . takeE 10 $ cw
[1 % 1,1 % 2,2 % 1,1 % 3,3 % 2,2 % 3,3 % 1,1 % 4,4 % 3,3 % 5]

rat :: Enumeration Rational Source #

An enumeration of all rational numbers: 0 first, then each rational in the Calkin-Wilf sequence followed by its negative.

>>> enumerate . takeE 10 $ rat
[0 % 1,1 % 1,(-1) % 1,1 % 2,(-1) % 2,2 % 1,(-2) % 1,1 % 3,(-1) % 3,3 % 2]

Enumeration combinators

takeE :: Integer -> Enumeration a -> Enumeration a Source #

Take a finite prefix from the beginning of an enumeration. takeE k e always yields the empty enumeration for \(k \leq 0\), and results in e whenever k is greater than or equal to the cardinality of the enumeration. Otherwise takeE k e has cardinality k and matches e from 0 to k-1.

>>> enumerate $ takeE 3 (boundedEnum @Int)
[-9223372036854775808,-9223372036854775807,-9223372036854775806]
>>> enumerate $ takeE 2 (finiteList [1..5])
[1,2]
>>> enumerate $ takeE 0 (finiteList [1..5])
[]
>>> enumerate $ takeE 7 (finiteList [1..5])
[1,2,3,4,5]

dropE :: Integer -> Enumeration a -> Enumeration a Source #

Drop some elements from the beginning of an enumeration. dropE k e yields e unchanged if \(k \leq 0\), and results in the empty enumeration whenever k is greater than or equal to the cardinality of e.

>>> enumerate $ dropE 2 (finiteList [1..5])
[3,4,5]
>>> enumerate $ dropE 0 (finiteList [1..5])
[1,2,3,4,5]
>>> enumerate $ dropE 7 (finiteList [1..5])
[]

infinite :: Enumeration a -> Enumeration a Source #

Explicitly mark an enumeration as having an infinite cardinality, ignoring the previous cardinality. It is sometimes necessary to use this as a "hint" when constructing a recursive enumeration whose cardinality would otherwise consist of an infinite sum of finite cardinalities.

For example, consider the following definitions:

data Tree = L | B Tree Tree deriving Show

treesBad :: Enumeration Tree
treesBad = singleton L <|> B <$> treesBad <*> treesBad

trees :: Enumeration Tree
trees = infinite $ singleton L <|> B <$> trees <*> trees

Trying to use treesBad at all will simply hang, since trying to compute its cardinality leads to infinite recursion.

>>> select treesBad 5
^CInterrupted.

However, using infinite, as in the definition of trees, provides the needed laziness:

>>> card trees
Infinite
>>> enumerate . takeE 3 $ trees
[L,B L L,B L (B L L)]
>>> select trees 87239862967296
B (B (B (B (B L L) (B (B (B L L) L) L)) (B L (B L (B L L)))) (B (B (B L (B L (B L L))) (B (B L L) (B L L))) (B (B L (B L (B L L))) L))) (B (B L (B (B (B L (B L L)) (B L L)) L)) (B (B (B L (B L L)) L) L))

zipE :: Enumeration a -> Enumeration b -> Enumeration (a, b) Source #

Zip two enumerations in parallel, producing the pair of elements at each index. The resulting enumeration is truncated to the cardinality of the smaller of the two arguments.

>>> enumerate $ zipE nat (boundedEnum @Bool)
[(0,False),(1,True)]

zipWithE :: (a -> b -> c) -> Enumeration a -> Enumeration b -> Enumeration c Source #

Zip two enumerations in parallel, applying the given function to the pair of elements at each index to produce a new element. The resulting enumeration is truncated to the cardinality of the smaller of the two arguments.

>>> enumerate $ zipWithE replicate (finiteList [1..10]) (dropE 35 (boundedEnum @Char))
["#","$$","%%%","&&&&","'''''","((((((",")))))))","********","+++++++++",",,,,,,,,,,"]

(<+>) :: Enumeration a -> Enumeration a -> Enumeration a Source #

Sum, i.e. disjoint union, of two enumerations. If both are finite, all the values of the first will be enumerated before the values of the second. If only one is finite, the values from the finite enumeration will be listed first. If both are infinite, a fair (alternating) interleaving is used, so that every value ends up at a finite index in the result.

Note that the (<+>) operator is a synonym for (<|>) from the Alternative instance for Enumeration, which should be used in preference to (<+>). (<+>) is provided as a separate standalone operator to make it easier to document.

>>> enumerate . takeE 10 $ singleton 17 <|> nat
[17,0,1,2,3,4,5,6,7,8]
>>> enumerate . takeE 10 $ nat <|> singleton 17
[17,0,1,2,3,4,5,6,7,8]
>>> enumerate . takeE 10 $ nat <|> (negate <$> nat)
[0,0,1,-1,2,-2,3,-3,4,-4]

Note that this is not associative in a strict sense. In particular, it may fail to be associative when mixing finite and infinite enumerations:

>>> enumerate . takeE 10 $ nat <|> (singleton 17 <|> nat)
[0,17,1,0,2,1,3,2,4,3]
>>> enumerate . takeE 10 $ (nat <|> singleton 17) <|> nat
[17,0,0,1,1,2,2,3,3,4]

However, it is associative in several weaker senses:

  • If all the enumerations are finite
  • If all the enumerations are infinite
  • If enumerations are considered equivalent up to reordering (they are not, but considering them so may be acceptable in some applications).

(><) :: Enumeration a -> Enumeration b -> Enumeration (a, b) Source #

Cartesian product of enumerations. If both are finite, uses a simple lexicographic ordering. If only one is finite, the resulting enumeration is still in lexicographic order, with the infinite enumeration as the most significant component. For two infinite enumerations, uses a fair diagonal interleaving.

>>> enumerate $ finiteList [1..3] >< finiteList "abcd"
[(1,'a'),(1,'b'),(1,'c'),(1,'d'),(2,'a'),(2,'b'),(2,'c'),(2,'d'),(3,'a'),(3,'b'),(3,'c'),(3,'d')]
>>> enumerate . takeE 10 $ finiteList "abc" >< nat
[('a',0),('b',0),('c',0),('a',1),('b',1),('c',1),('a',2),('b',2),('c',2),('a',3)]
>>> enumerate . takeE 10 $ nat >< finiteList "abc"
[(0,'a'),(0,'b'),(0,'c'),(1,'a'),(1,'b'),(1,'c'),(2,'a'),(2,'b'),(2,'c'),(3,'a')]
>>> enumerate . takeE 10 $ nat >< nat
[(0,0),(0,1),(1,0),(0,2),(1,1),(2,0),(0,3),(1,2),(2,1),(3,0)]

Like (<+>), this operation is also not associative (not even up to reassociating tuples).

interleave :: Enumeration (Enumeration a) -> Enumeration a Source #

Fairly interleave a set of infinite enumerations.

For a finite set of infinite enumerations, a round-robin interleaving is used. That is, if we think of an enumeration of enumerations as a 2D matrix read off row-by-row, this corresponds to taking the transpose of a matrix with finitely many infinite rows, turning it into one with infinitely many finite rows. For an infinite set of infinite enumerations, i.e. an infinite 2D matrix, the resulting enumeration reads off the matrix by diagonals.

>>> enumerate . takeE 15 $ interleave (finiteList [nat, negate <$> nat, (*10) <$> nat])
[0,0,0,1,-1,10,2,-2,20,3,-3,30,4,-4,40]
>>> enumerate . takeE 15 $ interleave (always nat)
[0,0,1,0,1,2,0,1,2,3,0,1,2,3,4]

This function is similar to join in a hypothetical Monad instance for Enumeration, but it only works when the inner enumerations are all infinite.

To interleave a finite enumeration of enumerations, some of which may be finite, you can use asum . enumerate. If you want to interleave an infinite enumeration of finite enumerations, you are out of luck.

maybeOf :: Enumeration a -> Enumeration (Maybe a) Source #

Enumerate all possible values of type `Maybe a`, where the values of type a are taken from the given enumeration.

>>> enumerate $ maybeOf (finiteList [1,2,3])
[Nothing,Just 1,Just 2,Just 3]

eitherOf :: Enumeration a -> Enumeration b -> Enumeration (Either a b) Source #

Enumerae all possible values of type Either a b with inner values taken from the given enumerations.

>>> enumerate . takeE 6 $ eitherOf nat nat
[Left 0,Right 0,Left 1,Right 1,Left 2,Right 2]

listOf :: Enumeration a -> Enumeration [a] Source #

Enumerate all possible finite lists containing values from the given enumeration.

>>> enumerate . takeE 15 $ listOf nat
[[],[0],[0,0],[1],[0,0,0],[1,0],[2],[0,1],[1,0,0],[2,0],[3],[0,0,0,0],[1,1],[2,0,0],[3,0]]

finiteSubsetOf :: Enumeration a -> Enumeration [a] Source #

Enumerate all possible finite subsets of values from the given enumeration.

>>> enumerate $ finiteSubsetOf (finite 3)
[[],[0],[1],[0,1],[2],[0,2],[1,2],[0,1,2]]

finiteEnumerationOf :: Int -> Enumeration a -> Enumeration (Enumeration a) Source #

finiteEnumerationOf n a creates an enumeration of all sequences of exactly n items taken from the enumeration a.

Utilities

diagonal :: Integer -> (Integer, Integer) Source #

One half of the isomorphism between \(\mathbb{N}\) and \(\mathbb{N} \times \mathbb{N}\) which enumerates by diagonals: turn a particular natural number index into its position in the 2D grid. That is, given this numbering of a 2D grid:

  0 1 3 6 ...
  2 4 7
  5 8
  9
  

diagonal maps \(0 \mapsto (0,0), 1 \mapsto (0,1), 2 \mapsto (1,0) \dots\)