generic-trie-0.3.0.1: A map, where the keys may be complex structured data.

Safe HaskellSafe
LanguageHaskell2010

Data.GenericTrie

Contents

Description

This module implements an interface for working with maps.

For primitive types, like Int, the library automatically selects an efficient implementation (e.g., an IntMap).

For complex structured types, the library uses an implementation based on tries: this is useful when using large and similar keys where comparing for order may become expensive, and storing the distinct keys would be inefficient.

The OrdKey type allows for maps with complex keys, where the keys are compared based on order, rather than using the trie implementation.

All methods of TrieKey can be derived automatically using a Generic instance.

data Demo = DemoC1 Int | DemoC2 Int Char  deriving Generic

instance TrieKey Demo

Synopsis

Trie interface

data Trie k a Source

A map from keys of type k, to values of type a.

Instances

TrieKey k => Functor (Trie k) 
TrieKey k => Foldable (Trie k) 
TrieKey k => Traversable (Trie k) 
(Show a, TrieKey k) => Show (Trie k a) 

class TrieKey k Source

Types that may be used as the key of a Trie.

For data delcarations, the instance can be automatically derived from a Generic instance.

Instances

TrieKey Bool 
TrieKey Char

Char tries are implemented with IntMap.

TrieKey Int

Int tries are implemented with IntMap.

TrieKey Integer

Integer tries are implemented with Map.

TrieKey () 
TrieKey k => TrieKey [k] 
TrieKey k => TrieKey (Maybe k) 
(Show k, Ord k) => TrieKey (OrdKey k)

OrdKey tries are implemented with Map, this is intended for cases where it is better for some reason to force the use of a Map than to use the generically derived structure.

(TrieKey a, TrieKey b) => TrieKey (Either a b) 
(TrieKey a, TrieKey b) => TrieKey (a, b) 
(TrieKey a, TrieKey b, TrieKey c) => TrieKey (a, b, c) 
(TrieKey a, TrieKey b, TrieKey c, TrieKey d) => TrieKey (a, b, c, d) 
(TrieKey a, TrieKey b, TrieKey c, TrieKey d, TrieKey e) => TrieKey (a, b, c, d, e) 

Construction

empty :: TrieKey k => Trie k a Source

Construct an empty trie

singleton :: TrieKey k => k -> a -> Trie k a Source

Construct a trie holding a single value

fromList :: TrieKey k => [(k, v)] -> Trie k v Source

Construct a trie from a list of key-value pairs

fromListWith :: TrieKey k => (v -> v -> v) -> [(k, v)] -> Trie k v Source

Construct a trie from a list of key-value pairs. The given function is used to combine values at the same key.

fromListWith' :: TrieKey k => (v -> v -> v) -> [(k, v)] -> Trie k v Source

Version of fromListWith which is strict in the result of the combining function.

Updates

alter :: TrieKey k => k -> (Maybe a -> Maybe a) -> Trie k a -> Trie k a Source

Alter the value at the given key location. The parameter function takes the value stored at the given key, if one exists, and should return a value to insert at that location, or Nothing to delete from that location.

insert :: TrieKey k => k -> a -> Trie k a -> Trie k a Source

Insert an element into a trie

insertWith :: TrieKey k => (v -> v -> v) -> k -> v -> Trie k v -> Trie k v Source

Insert a value at the given key. The combining function is used when a value is already stored at that key. The new value is the first argument to the combining function.

insertWith' :: TrieKey k => (v -> v -> v) -> k -> v -> Trie k v -> Trie k v Source

Version of insertWith that is strict in the result of combining two elements.

delete :: TrieKey k => k -> Trie k a -> Trie k a Source

Delete an element from a trie

at :: (Functor f, TrieKey k) => k -> (Maybe a -> f (Maybe a)) -> Trie k a -> f (Trie k a) Source

Lens for the value at a given key

Queries

member :: TrieKey k => k -> Trie k a -> Bool Source

Returns True when the Trie has a value stored at the given key.

notMember :: TrieKey k => k -> Trie k a -> Bool Source

Returns False when the Trie has a value stored at the given key.

null :: TrieKey k => Trie k a -> Bool Source

Test for an empty trie

lookup :: TrieKey k => k -> Trie k a -> Maybe a Source

Lookup an element from a trie

Folding

foldWithKey :: TrieKey k => (k -> a -> r -> r) -> r -> Trie k a -> r Source

Fold a trie with a function of both key and value

fold :: TrieKey k => (a -> r -> r) -> r -> Trie k a -> r Source

Fold a trie with a function of the value

toList :: TrieKey k => Trie k a -> [(k, a)] Source

Transform a trie to an association list.

Traversing

traverseWithKey :: (TrieKey k, Applicative f) => (k -> a -> f b) -> Trie k a -> f (Trie k b) Source

Traverse a trie with a function of both key and value

mapMaybe :: TrieKey k => (a -> Maybe b) -> Trie k a -> Trie k b Source

Map a function over a trie filtering out elements where function returns Nothing

mapMaybeWithKey :: TrieKey k => (k -> a -> Maybe b) -> Trie k a -> Trie k b Source

Apply a function to the values of a trie and keep the elements of the trie that result in a Just value.

filter :: TrieKey k => (a -> Bool) -> Trie k a -> Trie k a Source

Filter the values of a trie with the given predicate.

filterWithKey :: TrieKey k => (k -> a -> Bool) -> Trie k a -> Trie k a Source

Version of filter where the predicate also gets the key.

Combining maps

union :: TrieKey k => Trie k a -> Trie k a -> Trie k a Source

Left-biased union of two tries

unionWith :: TrieKey k => (a -> a -> a) -> Trie k a -> Trie k a -> Trie k a Source

Union of two tries with function used to merge overlapping elements

unionWithKey :: TrieKey k => (k -> a -> a -> a) -> Trie k a -> Trie k a -> Trie k a Source

Union of two tries with function used to merge overlapping elements along with key

intersection :: TrieKey k => Trie k a -> Trie k b -> Trie k a Source

Left-biased intersection of two tries

intersectionWith :: TrieKey k => (a -> b -> c) -> Trie k a -> Trie k b -> Trie k c Source

Intersection of two tries parameterized by a combining function of the values at overlapping keys

intersectionWithKey :: TrieKey k => (k -> a -> b -> c) -> Trie k a -> Trie k b -> Trie k c Source

Intersection of two tries parameterized by a combining function of the key and the values at overlapping keys

difference :: TrieKey k => Trie k a -> Trie k b -> Trie k a Source

Remove the keys of the right trie from the left trie

differenceWith :: TrieKey k => (a -> b -> Maybe a) -> Trie k a -> Trie k b -> Trie k a Source

Parameterized difference using a custom merge function. Return Just to change the value stored in left trie, or Nothing to remove from the left trie.

differenceWithKey :: TrieKey k => (k -> a -> b -> Maybe a) -> Trie k a -> Trie k b -> Trie k a Source

differenceWith where function also has access to the key

Keys using Ord

newtype OrdKey k Source

Tries indexed by OrdKey will be represented as an ordinary Map and the keys will be compared based on the Ord instance for k.

Constructors

OrdKey 

Fields

getOrdKey :: k
 

Instances

Eq k => Eq (OrdKey k) 
Ord k => Ord (OrdKey k) 
Read k => Read (OrdKey k) 
Show k => Show (OrdKey k) 
(Show k, Ord k) => TrieKey (OrdKey k)

OrdKey tries are implemented with Map, this is intended for cases where it is better for some reason to force the use of a Map than to use the generically derived structure.

type TrieRep (OrdKey k) = Map k