numbering-0.2.1: Combinators for creating bijections from some type to the natural numbers.

Safe HaskellSafe-Infered

Data.Numbering

Contents

Synopsis

Documentation

data Numbering a Source

Invariant:

 For all i in 0 .. nuLength - 1, 
     toInt (fromInt i) == i 

This implies that

 For all a of the form fromInt i (with i in 0 .. nuLength - 1), 
     fromInt (toInt a) = a

The behaviour of fromInt for out-of-bounds indices and that of toInt for elements not occuring in the numbering is undefined.

Thus, assuming the invariant holds, toInt is uniquely determined by fromInt (on valid inputs).

Constructors

UnsafeMkNumbering

"Unsafe" because the invariant isn't checked.

Fields

toInt :: a -> Int
 
fromInt :: Int -> a
 
nuLength :: Int
 

Instances

Eq a => Eq (Numbering a)

Assumes that the invariant holds.

Show a => Show (Numbering a) 

Construction

enumNu :: Enum a => a -> a -> Numbering aSource

enumNu a b creates a numbering of the elements [a .. b] (inclusively).

enumNu' :: Enum a => Int -> Int -> Numbering aSource

enumNu' i j creates a numbering of the elements [toEnum i .. toEnum j] (inclusively).

nuFromSet :: Map Int ignored -> Numbering IntSource

(Uses a Map because Data.Set doesn't expose the necessary index-based API)

nuFromDistinctVector :: (Ord a, Show a, Vector v a) => v a -> Numbering aSource

The distinctness precondition is checked (we have to create a map anyway).

nuFromDistinctVectorGSource

Arguments

:: (Show a, Vector v a) 
=> map

empty equivalent

-> ((a -> Int -> Int -> t) -> a -> Int -> map -> map)

insertWithKey equivalent

-> (a -> map -> Maybe Int)

lookup equivalent

-> v a 
-> Numbering a 

Allows customization of the map type used.

finiteTypeNu :: (Enum a, Bounded a) => Numbering aSource

Numbering of all elements of a finite type.

idNuSource

Arguments

:: Int

The nuLength

-> Numbering Int 

Identity numbering

From a list

nuFromList :: (Ord a, Show a) => [a] -> Numbering aSource

Uniquifies the input first (resulting in an unspecified order).

nuFromUnboxList :: (Ord a, Show a, Unbox a) => [a] -> Numbering aSource

Uniquifies the input first (resulting in an unspecified order).

nuFromIntList :: [Int] -> Numbering IntSource

Uniquifies the input first (resulting in an unspecified order).

Transformation

mapNu :: (a -> b) -> (b -> a) -> Numbering a -> Numbering bSource

In mapNu f g nu, the arguments must satisfy

 For all i in 0 .. nuLength nu - 1, 
     (g . f) a == a
          where
              a = fromInt nu i

reindexNuSource

Arguments

:: Int

New nuLength

-> (Int -> Int)

Old index to new index

-> (Int -> Int)

New index to old index

-> Numbering a 
-> Numbering a 

In reindexNu k f g nu, the arguments must satisfy

 For all i in 0 .. k,
     (g . f) i == i

Note: Decreasing the length with this function will not release any memory retained by the closures in the input numbering (e.g. the vector, for numberings created by nuFromDistinctVector). Use consolidateNu afterwards for that.

consolidateNu :: (Ord a, Show a) => Numbering a -> Numbering aSource

Semantic id (for in-bounds inputs), but backs the numbering with a new vector and map having just the required length (example: consolidateNu (nuTake 1 (nuFromDistinctVector largeVector))).

consolidateUnboxNu :: (Ord a, Show a, Unbox a) => Numbering a -> Numbering aSource

Like consolidateNu, but uses unboxed vectors.

Particular reindexings

nuDrop :: Int -> Numbering a -> Numbering aSource

Identity for nonpositive arg.

Combination

sumNuSource

Arguments

:: (a1 -> a)

Left equivalent

-> (a2 -> a)

Right equivalent

-> ((a1 -> Int) -> (a2 -> Int) -> a -> Int)

either equivalent

-> Numbering a1 
-> Numbering a2 
-> Numbering a 

Creates a numbering for an Either-like type, given numberings for the summand types.

prodNuSource

Arguments

:: (a -> a2)

fst equivalent

-> (a -> a1)

snd equivalent

-> (a2 -> a1 -> a)

(,) equivalent

-> Numbering a2 
-> Numbering a1 
-> Numbering a 

Creates a numbering for an pair-like type, given numberings for the component types.

Destruction

nuToDistinctList :: Numbering a -> [a]Source

= nuElements. Won't actually be distinct if the invariant is broken.

nuToVector :: Vector v a => Numbering a -> v aSource

nuToDistinctVector :: Vector v a => Numbering a -> v aSource

= nuToVector. Won't actually be distinct if the invariant is broken.