Agda-2.4.2.4: A dependently typed functional programming language and proof assistant

Safe HaskellNone
LanguageHaskell98

Agda.Utils.Trie

Description

Strict tries (based on Data.Map.Strict and Agda.Utils.Maybe.Strict).

Synopsis

Documentation

data Trie k v Source

Finite map from [k] to v.

With the strict Maybe type, Trie is also strict in v.

Instances

(Show k, Show v) => Show (Trie k v) Source 
Null (Trie k v) Source

Empty trie.

empty :: Null a => a Source

singleton :: [k] -> v -> Trie k v Source

Singleton trie.

insert :: Ord k => [k] -> v -> Trie k v -> Trie k v Source

Insert. Overwrites existing value if present.

insert = insertWith ( new old -> new)

insertWith :: Ord k => (v -> v -> v) -> [k] -> v -> Trie k v -> Trie k v Source

Insert with function merging new value with old value.

union :: Ord k => Trie k v -> Trie k v -> Trie k v Source

Left biased union.

union = unionWith ( new old -> new).

unionWith :: Ord k => (v -> v -> v) -> Trie k v -> Trie k v -> Trie k v Source

Pointwise union with merge function for values.

adjust :: Ord k => [k] -> (Maybe v -> Maybe v) -> Trie k v -> Trie k v Source

Adjust value at key, leave subtree intact.

delete :: Ord k => [k] -> Trie k v -> Trie k v Source

Delete value at key, but leave subtree intact.

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

Convert to ascending list.

toAscList :: Ord k => Trie k v -> [([k], v)] Source

Convert to ascending list.

lookupPath :: Ord k => [k] -> Trie k v -> [v] Source

Collect all values along a given path.