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

Safe HaskellSafe-Infered

Data.Generics.Fixplate.Trie

Contents

Description

Generalized tries. "Normal" tries encode finite maps from lists to arbitrary values, where the common prefixes are shared. Here we do the same for trees, generically.

See also

  • Connelly, Morris: A generalization of the trie data structure
  • Ralf Hinze: Generalizing Generalized Tries

This module should be imported qualified.

Synopsis

Documentation

data Trie f v Source

Trie is an efficient(?) implementation of finite maps from (Mu f) to an arbitrary type v.

Construction / deconstruction

empty :: (Functor f, Foldable f, OrdF f) => Trie f aSource

singleton :: (Functor f, Foldable f, OrdF f) => Mu f -> a -> Trie f aSource

fromList :: (Traversable f, OrdF f) => [(Mu f, a)] -> Trie f aSource

TODO: more efficient implementation?

toList :: (Traversable f, OrdF f) => Trie f a -> [(Mu f, a)]Source

bag :: (Functor f, Foldable f, OrdF f) => [Mu f] -> Trie f IntSource

Creates a trie-multiset from a list of trees.

universeBag :: (Functor f, Foldable f, OrdF f) => Mu f -> Trie f IntSource

This is equivalent to

 universeBag == bag . universe

TODO: more efficient implementation?

Lookup

lookup :: (Functor f, Foldable f, OrdF f) => Mu f -> Trie f a -> Maybe aSource

Insertion / deletion

insert :: (Functor f, Foldable f, OrdF f) => Mu f -> a -> Trie f a -> Trie f aSource

insertWith :: (Functor f, Foldable f, OrdF f) => (a -> b) -> (a -> b -> b) -> Mu f -> a -> Trie f b -> Trie f bSource

delete :: (Functor f, Foldable f, OrdF f) => Mu f -> Trie f a -> Trie f aSource

update :: (Functor f, Foldable f, OrdF f) => (a -> Maybe a) -> Mu f -> Trie f a -> Trie f aSource

Set operations

intersection :: (Functor f, Foldable f, OrdF f) => Trie f a -> Trie f b -> Trie f aSource

intersectionWith :: (Functor f, Foldable f, OrdF f) => (a -> b -> c) -> Trie f a -> Trie f b -> Trie f cSource

union :: (Functor f, Foldable f, OrdF f) => Trie f a -> Trie f a -> Trie f aSource

Union is left-biased:

 union == unionWith const

unionWith :: (Functor f, Foldable f, OrdF f) => (a -> a -> a) -> Trie f a -> Trie f a -> Trie f aSource

difference :: (Functor f, Foldable f, OrdF f) => Trie f a -> Trie f b -> Trie f aSource

differenceWith :: (Functor f, Foldable f, OrdF f) => (a -> b -> Maybe a) -> Trie f a -> Trie f b -> Trie f aSource