collections-0.3.1: Useful standard collections types and related functions.

Portabilityunknown This module provides a basic implementation of the Trie data type.
Stabilityvolatile
Maintainerjeanphilippe.bernardy; google mail.

Data.Trie

Contents

Description

Note: performance is currently rather bad. See the benchmark directory. Please contribute :)

Synopsis

Data type

data Trie s k v Source

A Trie with key elements of type k (keys of type [k]) and values of type v. Note that the type is not opaque: user can pattern match on it and construct and Trie value. This is because there is no non-trivial invariant to preserve.

Constructors

Trie 

Fields

value :: !(Maybe v)
 
children :: !(Map k (Trie s k v))
 

Instances

Typeable3 Trie 
Foldable (Trie s k) 
(Eq k, Eq v) => Eq (Trie s k v) 
(Show k, Show v) => Show (Trie [k] k v) 
Ord k => Monoid (Trie s k v) 
(Ord k, Sequence s k) => Map (Trie s k v) s v 
(Ord k, Foldable s k) => Indexed (Trie s k v) s v 
Sequence s k => Foldable (Trie s k v) (s, v) 
(Ord k, Sequence s k) => Unfoldable (Trie s k v) (s, v) 
(Ord k, Sequence s k) => Collection (Trie s k v) (s, v) 

Operators

(!) :: forall s k v. (Foldable s k, Ord k) => Trie s k v -> s -> vSource

Query

null :: Trie s k v -> BoolSource

Is the trie empty ?

member :: forall s k v. (Foldable s k, Ord k) => s -> Trie s k v -> BoolSource

lookup :: forall s m k v. (Foldable s k, Monad m, Ord k) => s -> Trie s k v -> m vSource

prefixLookup :: forall s k v result. (Ord k, Sequence s k, Sequence result (s, v)) => s -> Trie s k v -> resultSource

prefixLookup k p returns a sequence of all (k',v) pairs, such that k is a prefix of k'. The sequence is sorted by lexicographic order of keys.

Construction

empty :: Ord k => Trie s k vSource

The empty trie.

singleton :: (Ord k, Foldable s k) => s -> v -> Trie s k vSource

The singleton trie.

Insertion

insert :: forall s k v. (Foldable s k, Ord k) => s -> v -> Trie s k v -> Trie s k vSource

insertWith :: forall s k v. (Foldable s k, Ord k) => (v -> v -> v) -> s -> v -> Trie s k v -> Trie s k vSource

Delete/Update

alter :: forall s k v. (Foldable s k, Ord k) => (Maybe v -> Maybe v) -> s -> Trie s k v -> Trie s k vSource

Combine

Union

union :: Ord k => Trie s k v -> Trie s k v -> Trie s k vSource

Combining two tries. The first shadows the second.

unionWith :: Ord k => (v -> v -> v) -> Trie s k v -> Trie s k v -> Trie s k vSource

Combining two tries. If the two define the same key, the specified combining function is used.

Difference

difference :: Ord k => Trie s k v -> Trie s k v -> Trie s k vSource

differenceWith :: Ord k => (v -> v -> Maybe v) -> Trie s k v -> Trie s k v -> Trie s k vSource

Intersection

intersection :: Ord k => Trie s k v -> Trie s k v -> Trie s k vSource

intersectionWith :: Ord k => (v -> v -> v) -> Trie s k v -> Trie s k v -> Trie s k vSource

Combining two tries. If the two tries define the same key, the specified combining function is used.

Traversal

Map

Fold

Conversion

retypeKeys :: Trie s1 k v -> Trie s2 k vSource

fromAscList :: forall s k v. (Sequence s k, Ord k) => [(s, v)] -> Trie s k vSource

fromList :: forall s k v. (Sequence s k, Ord k) => [(s, v)] -> Trie s k vSource

fromListWith :: forall s k v. (Sequence s k, Ord k) => (v -> v -> v) -> [(s, v)] -> Trie s k vSource

toList :: (Sequence s k, Ord k) => Trie s k v -> [(s, v)]Source

Filter

filter :: forall k v s. (Ord k, Sequence s k) => (v -> Bool) -> Trie s k v -> Trie s k vSource

Submap

isSubmapOfBy :: Ord k => (v -> v -> Bool) -> Trie s k v -> Trie s k v -> BoolSource

Primitive accessors

upwards :: Ord k => (Trie s k v -> Trie s k v) -> Trie s k v -> Trie s k vSource

An upwards accumulation on the trie.

downwards :: Ord k => (Trie s k v -> Trie s k v) -> Trie s k v -> Trie s k vSource

A downwards accumulation on the trie.

Derived operations

takeWhile :: Ord k => (Trie s k v -> Bool) -> Trie s k v -> Trie s k vSource

Return the prefix of the trie satisfying f.

takeWhile' :: Ord k => (v -> Bool) -> Trie s k v -> Trie s k vSource

Return the prefix of the trie satisfying f on all values present.

fringe :: Ord k => Trie s k v -> Trie s k vSource

Return the fringe of the trie (the trie composed of only the leaf nodes).

Debugging

toTree :: k -> Trie s k v -> Tree (k, Maybe v)Source