fixplate-0.1.6: Uniplate-style generic traversals for optionally annotated fixed-point types.

Safe HaskellSafe
LanguageHaskell2010

Data.Generics.Fixplate.Util.Hash.Table

Contents

Description

Hash tables, implemented as a structure similar to Map hash (Map key value)].

What this data structure can also give you is a unique value (a (hash,Int) pair) for each key, even during building the table: It is guaranteed to be unique in the past and future lifetime of a single hashtable (that is, one realization of the world-line), among all the keys appearing in that history.

Set operations (union, intersection) clearly break this principle; this is resolved by declaring these operations to be left-biased, in the sense that they retain the unique values of the left table (so union t1 t2 belongs to to t1's world-line, but not to t2's one).

If a key is first removed then added back again, it will get a new value.

To be Haskell98 compatible (no multi-param type classes), when constructing a new hash table, we have to support the function computing (or just fetching, if it is cached) the hash value. This function is then stored in the data type.

Synopsis

Documentation

data HashTable hash k v Source

data Bucket k v Source

Constructors

Bucket !Int !(Map k (Leaf v)) 

data Leaf v Source

Constructors

Leaf !Int v 

getHashValue :: HashTable hash k v -> k -> hash Source

unHashTable :: HashTable hash k v -> Map hash (Bucket k v) Source

Construction and deconstruction

empty :: (Ord hash, Ord k) => (k -> hash) -> HashTable hash k v Source

singleton :: (Ord hash, Ord k) => (k -> hash) -> k -> v -> HashTable hash k v Source

fromList :: (Ord hash, Ord k) => (k -> hash) -> [(k, v)] -> HashTable hash k v Source

toList :: Ord k => HashTable hash k v -> [(k, v)] Source

Note that the returned list is ordered by hash, not by keys like Map!

null :: (Ord hash, Ord k) => HashTable hash k v -> Bool Source

bag :: (Ord hash, Ord k) => (k -> hash) -> [k] -> HashTable hash k Int Source

Creates a multi-set from a list.

Membership

lookup :: (Ord hash, Ord k) => k -> HashTable hash k v -> Maybe v Source

member :: (Ord hash, Ord k) => k -> HashTable hash k v -> Bool Source

Insertion / deletion

insert :: (Ord hash, Ord k) => k -> v -> HashTable hash k v -> HashTable hash k v Source

insertWith :: (Ord hash, Ord k) => (a -> v) -> (a -> v -> v) -> k -> a -> HashTable hash k v -> HashTable hash k v Source

delete :: (Ord hash, Ord k) => k -> HashTable hash k v -> HashTable hash k v Source

Union

union :: (Ord hash, Ord k) => HashTable hash k a -> HashTable hash k a -> HashTable hash k a Source

union == unionWith const

unionWith :: (Ord hash, Ord k) => (v -> v -> v) -> HashTable hash k v -> HashTable hash k v -> HashTable hash k v Source

This is unsafe in the sense that the two getHash functions (supplied when the hash tables were created) must agree. The same applies for all the set operations.

It is also left-biased in the sense that the unique indices from the left hashtable are retained, while the unique indices from the right hashtable are changed.

unionsWith :: (Ord hash, Ord k) => (v -> v -> v) -> [HashTable hash k v] -> HashTable hash k v Source

This is unsafe both in the above sense and also that it does not accepts the empty list (for the same reason). The result belongs to the world-line of the first table.

unionsWith' :: (Ord hash, Ord k) => (k -> hash) -> (v -> v -> v) -> [HashTable hash k v] -> HashTable hash k v Source

This one accepts the empty list. The empty imput creates a new world-line.

Intersection

intersection :: (Ord hash, Ord k) => HashTable hash k a -> HashTable hash k b -> HashTable hash k a Source

intersection == intersectionWith const

intersectionWith :: (Ord hash, Ord k) => (a -> b -> c) -> HashTable hash k a -> HashTable hash k b -> HashTable hash k c Source

intersectionsWith :: (Ord hash, Ord k) => (v -> v -> v) -> [HashTable hash k v] -> HashTable hash k v Source

intersectionsWith' :: (Ord hash, Ord k) => (k -> hash) -> (v -> v -> v) -> [HashTable hash k v] -> HashTable hash k v Source

Difference

difference :: (Ord hash, Ord k) => HashTable hash k a -> HashTable hash k b -> HashTable hash k a Source

differenceWith :: (Ord hash, Ord k) => (a -> b -> Maybe a) -> HashTable hash k a -> HashTable hash k b -> HashTable hash k a Source

Unique indices

getUniqueIndex :: (Ord hash, Ord k) => (hash -> Int -> a) -> k -> HashTable hash k v -> Maybe a Source

Look up a unique index, in the form of a (hash,Int) pair, for any key. If the user-supplied function is injective, then the result is guaranteed to be uniquely associated to the given key in the past and future history of this table (but of course not unique among different future histories).

keysWith :: Ord k => (k -> hash -> Int -> a) -> HashTable hash k v -> [a] Source

Keys together with their associated unique values

mapWithUniqueIndices :: (Ord hash, Ord k) => (hash -> Int -> a -> b) -> HashTable hash k a -> HashTable hash k b Source