generic-trie-0.3.2: A map, where the keys may be complex structured data.
Safe HaskellSafe
LanguageHaskell2010

Data.GenericTrie

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

Instances details
TrieKey k => Foldable (Trie k) Source # 
Instance details

Defined in Data.GenericTrie.Internal

Methods

fold :: Monoid m => Trie k m -> m #

foldMap :: Monoid m => (a -> m) -> Trie k a -> m #

foldMap' :: Monoid m => (a -> m) -> Trie k a -> m #

foldr :: (a -> b -> b) -> b -> Trie k a -> b #

foldr' :: (a -> b -> b) -> b -> Trie k a -> b #

foldl :: (b -> a -> b) -> b -> Trie k a -> b #

foldl' :: (b -> a -> b) -> b -> Trie k a -> b #

foldr1 :: (a -> a -> a) -> Trie k a -> a #

foldl1 :: (a -> a -> a) -> Trie k a -> a #

toList :: Trie k a -> [a] #

null :: Trie k a -> Bool #

length :: Trie k a -> Int #

elem :: Eq a => a -> Trie k a -> Bool #

maximum :: Ord a => Trie k a -> a #

minimum :: Ord a => Trie k a -> a #

sum :: Num a => Trie k a -> a #

product :: Num a => Trie k a -> a #

TrieKey k => Traversable (Trie k) Source # 
Instance details

Defined in Data.GenericTrie.Internal

Methods

traverse :: Applicative f => (a -> f b) -> Trie k a -> f (Trie k b) #

sequenceA :: Applicative f => Trie k (f a) -> f (Trie k a) #

mapM :: Monad m => (a -> m b) -> Trie k a -> m (Trie k b) #

sequence :: Monad m => Trie k (m a) -> m (Trie k a) #

TrieKey k => Functor (Trie k) Source # 
Instance details

Defined in Data.GenericTrie.Internal

Methods

fmap :: (a -> b) -> Trie k a -> Trie k b #

(<$) :: a -> Trie k b -> Trie k a #

(TrieKey k, Show k, Show a) => Show (Trie k a) Source # 
Instance details

Defined in Data.GenericTrie.Internal

Methods

showsPrec :: Int -> Trie k a -> ShowS #

show :: Trie k a -> String #

showList :: [Trie k a] -> ShowS #

class TrieKey k Source #

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

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

Instances

Instances details
TrieKey Void Source # 
Instance details

Defined in Data.GenericTrie.Internal

Associated Types

type TrieRep Void :: Type -> Type Source #

Methods

trieEmpty :: Trie Void a Source #

trieNull :: Trie Void a -> Bool Source #

trieLookup :: Void -> Trie Void a -> Maybe a Source #

trieInsert :: Void -> a -> Trie Void a -> Trie Void a Source #

trieDelete :: Void -> Trie Void a -> Trie Void a Source #

trieAlter :: Void -> (Maybe a -> Maybe a) -> Trie Void a -> Trie Void a Source #

trieSingleton :: Void -> a -> Trie Void a Source #

trieMap :: (a -> b) -> Trie Void a -> Trie Void b Source #

trieTraverse :: Applicative f => (a -> f b) -> Trie Void a -> f (Trie Void b) Source #

trieMapMaybeWithKey :: (Void -> a -> Maybe b) -> Trie Void a -> Trie Void b Source #

trieFoldWithKey :: (Void -> a -> r -> r) -> r -> Trie Void a -> r Source #

trieTraverseWithKey :: Applicative f => (Void -> a -> f b) -> Trie Void a -> f (Trie Void b) Source #

trieTraverseMaybeWithKey :: Applicative f => (Void -> a -> f (Maybe b)) -> Trie Void a -> f (Trie Void b) Source #

trieMergeWithKey :: (Void -> a -> b -> Maybe c) -> (Trie Void a -> Trie Void c) -> (Trie Void b -> Trie Void c) -> Trie Void a -> Trie Void b -> Trie Void c Source #

TrieKey Ordering Source # 
Instance details

Defined in Data.GenericTrie.Internal

Associated Types

type TrieRep Ordering :: Type -> Type Source #

TrieKey Integer Source #

Integer tries are implemented with Map.

Instance details

Defined in Data.GenericTrie.Internal

Associated Types

type TrieRep Integer :: Type -> Type Source #

TrieKey Natural Source #

Natural tries are implemented with Map.

Instance details

Defined in Data.GenericTrie.Internal

Associated Types

type TrieRep Natural :: Type -> Type Source #

TrieKey () Source # 
Instance details

Defined in Data.GenericTrie.Internal

Associated Types

type TrieRep () :: Type -> Type Source #

Methods

trieEmpty :: Trie () a Source #

trieNull :: Trie () a -> Bool Source #

trieLookup :: () -> Trie () a -> Maybe a Source #

trieInsert :: () -> a -> Trie () a -> Trie () a Source #

trieDelete :: () -> Trie () a -> Trie () a Source #

trieAlter :: () -> (Maybe a -> Maybe a) -> Trie () a -> Trie () a Source #

trieSingleton :: () -> a -> Trie () a Source #

trieMap :: (a -> b) -> Trie () a -> Trie () b Source #

trieTraverse :: Applicative f => (a -> f b) -> Trie () a -> f (Trie () b) Source #

trieMapMaybeWithKey :: (() -> a -> Maybe b) -> Trie () a -> Trie () b Source #

trieFoldWithKey :: (() -> a -> r -> r) -> r -> Trie () a -> r Source #

trieTraverseWithKey :: Applicative f => (() -> a -> f b) -> Trie () a -> f (Trie () b) Source #

trieTraverseMaybeWithKey :: Applicative f => (() -> a -> f (Maybe b)) -> Trie () a -> f (Trie () b) Source #

trieMergeWithKey :: (() -> a -> b -> Maybe c) -> (Trie () a -> Trie () c) -> (Trie () b -> Trie () c) -> Trie () a -> Trie () b -> Trie () c Source #

TrieKey Bool Source # 
Instance details

Defined in Data.GenericTrie.Internal

Associated Types

type TrieRep Bool :: Type -> Type Source #

Methods

trieEmpty :: Trie Bool a Source #

trieNull :: Trie Bool a -> Bool Source #

trieLookup :: Bool -> Trie Bool a -> Maybe a Source #

trieInsert :: Bool -> a -> Trie Bool a -> Trie Bool a Source #

trieDelete :: Bool -> Trie Bool a -> Trie Bool a Source #

trieAlter :: Bool -> (Maybe a -> Maybe a) -> Trie Bool a -> Trie Bool a Source #

trieSingleton :: Bool -> a -> Trie Bool a Source #

trieMap :: (a -> b) -> Trie Bool a -> Trie Bool b Source #

trieTraverse :: Applicative f => (a -> f b) -> Trie Bool a -> f (Trie Bool b) Source #

trieMapMaybeWithKey :: (Bool -> a -> Maybe b) -> Trie Bool a -> Trie Bool b Source #

trieFoldWithKey :: (Bool -> a -> r -> r) -> r -> Trie Bool a -> r Source #

trieTraverseWithKey :: Applicative f => (Bool -> a -> f b) -> Trie Bool a -> f (Trie Bool b) Source #

trieTraverseMaybeWithKey :: Applicative f => (Bool -> a -> f (Maybe b)) -> Trie Bool a -> f (Trie Bool b) Source #

trieMergeWithKey :: (Bool -> a -> b -> Maybe c) -> (Trie Bool a -> Trie Bool c) -> (Trie Bool b -> Trie Bool c) -> Trie Bool a -> Trie Bool b -> Trie Bool c Source #

TrieKey Char Source #

Char tries are implemented with IntMap.

Instance details

Defined in Data.GenericTrie.Internal

Associated Types

type TrieRep Char :: Type -> Type Source #

Methods

trieEmpty :: Trie Char a Source #

trieNull :: Trie Char a -> Bool Source #

trieLookup :: Char -> Trie Char a -> Maybe a Source #

trieInsert :: Char -> a -> Trie Char a -> Trie Char a Source #

trieDelete :: Char -> Trie Char a -> Trie Char a Source #

trieAlter :: Char -> (Maybe a -> Maybe a) -> Trie Char a -> Trie Char a Source #

trieSingleton :: Char -> a -> Trie Char a Source #

trieMap :: (a -> b) -> Trie Char a -> Trie Char b Source #

trieTraverse :: Applicative f => (a -> f b) -> Trie Char a -> f (Trie Char b) Source #

trieMapMaybeWithKey :: (Char -> a -> Maybe b) -> Trie Char a -> Trie Char b Source #

trieFoldWithKey :: (Char -> a -> r -> r) -> r -> Trie Char a -> r Source #

trieTraverseWithKey :: Applicative f => (Char -> a -> f b) -> Trie Char a -> f (Trie Char b) Source #

trieTraverseMaybeWithKey :: Applicative f => (Char -> a -> f (Maybe b)) -> Trie Char a -> f (Trie Char b) Source #

trieMergeWithKey :: (Char -> a -> b -> Maybe c) -> (Trie Char a -> Trie Char c) -> (Trie Char b -> Trie Char c) -> Trie Char a -> Trie Char b -> Trie Char c Source #

TrieKey Int Source #

Int tries are implemented with IntMap.

Instance details

Defined in Data.GenericTrie.Internal

Associated Types

type TrieRep Int :: Type -> Type Source #

Methods

trieEmpty :: Trie Int a Source #

trieNull :: Trie Int a -> Bool Source #

trieLookup :: Int -> Trie Int a -> Maybe a Source #

trieInsert :: Int -> a -> Trie Int a -> Trie Int a Source #

trieDelete :: Int -> Trie Int a -> Trie Int a Source #

trieAlter :: Int -> (Maybe a -> Maybe a) -> Trie Int a -> Trie Int a Source #

trieSingleton :: Int -> a -> Trie Int a Source #

trieMap :: (a -> b) -> Trie Int a -> Trie Int b Source #

trieTraverse :: Applicative f => (a -> f b) -> Trie Int a -> f (Trie Int b) Source #

trieMapMaybeWithKey :: (Int -> a -> Maybe b) -> Trie Int a -> Trie Int b Source #

trieFoldWithKey :: (Int -> a -> r -> r) -> r -> Trie Int a -> r Source #

trieTraverseWithKey :: Applicative f => (Int -> a -> f b) -> Trie Int a -> f (Trie Int b) Source #

trieTraverseMaybeWithKey :: Applicative f => (Int -> a -> f (Maybe b)) -> Trie Int a -> f (Trie Int b) Source #

trieMergeWithKey :: (Int -> a -> b -> Maybe c) -> (Trie Int a -> Trie Int c) -> (Trie Int b -> Trie Int c) -> Trie Int a -> Trie Int b -> Trie Int c Source #

TrieKey Word Source #

Word tries are implemented with IntMap.

Instance details

Defined in Data.GenericTrie.Internal

Associated Types

type TrieRep Word :: Type -> Type Source #

Methods

trieEmpty :: Trie Word a Source #

trieNull :: Trie Word a -> Bool Source #

trieLookup :: Word -> Trie Word a -> Maybe a Source #

trieInsert :: Word -> a -> Trie Word a -> Trie Word a Source #

trieDelete :: Word -> Trie Word a -> Trie Word a Source #

trieAlter :: Word -> (Maybe a -> Maybe a) -> Trie Word a -> Trie Word a Source #

trieSingleton :: Word -> a -> Trie Word a Source #

trieMap :: (a -> b) -> Trie Word a -> Trie Word b Source #

trieTraverse :: Applicative f => (a -> f b) -> Trie Word a -> f (Trie Word b) Source #

trieMapMaybeWithKey :: (Word -> a -> Maybe b) -> Trie Word a -> Trie Word b Source #

trieFoldWithKey :: (Word -> a -> r -> r) -> r -> Trie Word a -> r Source #

trieTraverseWithKey :: Applicative f => (Word -> a -> f b) -> Trie Word a -> f (Trie Word b) Source #

trieTraverseMaybeWithKey :: Applicative f => (Word -> a -> f (Maybe b)) -> Trie Word a -> f (Trie Word b) Source #

trieMergeWithKey :: (Word -> a -> b -> Maybe c) -> (Trie Word a -> Trie Word c) -> (Trie Word b -> Trie Word c) -> Trie Word a -> Trie Word b -> Trie Word c Source #

Ord k => TrieKey (OrdKey k) Source #

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.

Instance details

Defined in Data.GenericTrie.Internal

Associated Types

type TrieRep (OrdKey k) :: Type -> Type Source #

Methods

trieEmpty :: Trie (OrdKey k) a Source #

trieNull :: Trie (OrdKey k) a -> Bool Source #

trieLookup :: OrdKey k -> Trie (OrdKey k) a -> Maybe a Source #

trieInsert :: OrdKey k -> a -> Trie (OrdKey k) a -> Trie (OrdKey k) a Source #

trieDelete :: OrdKey k -> Trie (OrdKey k) a -> Trie (OrdKey k) a Source #

trieAlter :: OrdKey k -> (Maybe a -> Maybe a) -> Trie (OrdKey k) a -> Trie (OrdKey k) a Source #

trieSingleton :: OrdKey k -> a -> Trie (OrdKey k) a Source #

trieMap :: (a -> b) -> Trie (OrdKey k) a -> Trie (OrdKey k) b Source #

trieTraverse :: Applicative f => (a -> f b) -> Trie (OrdKey k) a -> f (Trie (OrdKey k) b) Source #

trieMapMaybeWithKey :: (OrdKey k -> a -> Maybe b) -> Trie (OrdKey k) a -> Trie (OrdKey k) b Source #

trieFoldWithKey :: (OrdKey k -> a -> r -> r) -> r -> Trie (OrdKey k) a -> r Source #

trieTraverseWithKey :: Applicative f => (OrdKey k -> a -> f b) -> Trie (OrdKey k) a -> f (Trie (OrdKey k) b) Source #

trieTraverseMaybeWithKey :: Applicative f => (OrdKey k -> a -> f (Maybe b)) -> Trie (OrdKey k) a -> f (Trie (OrdKey k) b) Source #

trieMergeWithKey :: (OrdKey k -> a -> b -> Maybe c) -> (Trie (OrdKey k) a -> Trie (OrdKey k) c) -> (Trie (OrdKey k) b -> Trie (OrdKey k) c) -> Trie (OrdKey k) a -> Trie (OrdKey k) b -> Trie (OrdKey k) c Source #

TrieKey k => TrieKey (Maybe k) Source # 
Instance details

Defined in Data.GenericTrie.Internal

Associated Types

type TrieRep (Maybe k) :: Type -> Type Source #

Methods

trieEmpty :: Trie (Maybe k) a Source #

trieNull :: Trie (Maybe k) a -> Bool Source #

trieLookup :: Maybe k -> Trie (Maybe k) a -> Maybe a Source #

trieInsert :: Maybe k -> a -> Trie (Maybe k) a -> Trie (Maybe k) a Source #

trieDelete :: Maybe k -> Trie (Maybe k) a -> Trie (Maybe k) a Source #

trieAlter :: Maybe k -> (Maybe a -> Maybe a) -> Trie (Maybe k) a -> Trie (Maybe k) a Source #

trieSingleton :: Maybe k -> a -> Trie (Maybe k) a Source #

trieMap :: (a -> b) -> Trie (Maybe k) a -> Trie (Maybe k) b Source #

trieTraverse :: Applicative f => (a -> f b) -> Trie (Maybe k) a -> f (Trie (Maybe k) b) Source #

trieMapMaybeWithKey :: (Maybe k -> a -> Maybe b) -> Trie (Maybe k) a -> Trie (Maybe k) b Source #

trieFoldWithKey :: (Maybe k -> a -> r -> r) -> r -> Trie (Maybe k) a -> r Source #

trieTraverseWithKey :: Applicative f => (Maybe k -> a -> f b) -> Trie (Maybe k) a -> f (Trie (Maybe k) b) Source #

trieTraverseMaybeWithKey :: Applicative f => (Maybe k -> a -> f (Maybe b)) -> Trie (Maybe k) a -> f (Trie (Maybe k) b) Source #

trieMergeWithKey :: (Maybe k -> a -> b -> Maybe c) -> (Trie (Maybe k) a -> Trie (Maybe k) c) -> (Trie (Maybe k) b -> Trie (Maybe k) c) -> Trie (Maybe k) a -> Trie (Maybe k) b -> Trie (Maybe k) c Source #

TrieKey k => TrieKey [k] Source # 
Instance details

Defined in Data.GenericTrie.Internal

Associated Types

type TrieRep [k] :: Type -> Type Source #

Methods

trieEmpty :: Trie [k] a Source #

trieNull :: Trie [k] a -> Bool Source #

trieLookup :: [k] -> Trie [k] a -> Maybe a Source #

trieInsert :: [k] -> a -> Trie [k] a -> Trie [k] a Source #

trieDelete :: [k] -> Trie [k] a -> Trie [k] a Source #

trieAlter :: [k] -> (Maybe a -> Maybe a) -> Trie [k] a -> Trie [k] a Source #

trieSingleton :: [k] -> a -> Trie [k] a Source #

trieMap :: (a -> b) -> Trie [k] a -> Trie [k] b Source #

trieTraverse :: Applicative f => (a -> f b) -> Trie [k] a -> f (Trie [k] b) Source #

trieMapMaybeWithKey :: ([k] -> a -> Maybe b) -> Trie [k] a -> Trie [k] b Source #

trieFoldWithKey :: ([k] -> a -> r -> r) -> r -> Trie [k] a -> r Source #

trieTraverseWithKey :: Applicative f => ([k] -> a -> f b) -> Trie [k] a -> f (Trie [k] b) Source #

trieTraverseMaybeWithKey :: Applicative f => ([k] -> a -> f (Maybe b)) -> Trie [k] a -> f (Trie [k] b) Source #

trieMergeWithKey :: ([k] -> a -> b -> Maybe c) -> (Trie [k] a -> Trie [k] c) -> (Trie [k] b -> Trie [k] c) -> Trie [k] a -> Trie [k] b -> Trie [k] c Source #

(TrieKey a, TrieKey b) => TrieKey (Either a b) Source # 
Instance details

Defined in Data.GenericTrie.Internal

Associated Types

type TrieRep (Either a b) :: Type -> Type Source #

Methods

trieEmpty :: Trie (Either a b) a0 Source #

trieNull :: Trie (Either a b) a0 -> Bool Source #

trieLookup :: Either a b -> Trie (Either a b) a0 -> Maybe a0 Source #

trieInsert :: Either a b -> a0 -> Trie (Either a b) a0 -> Trie (Either a b) a0 Source #

trieDelete :: Either a b -> Trie (Either a b) a0 -> Trie (Either a b) a0 Source #

trieAlter :: Either a b -> (Maybe a0 -> Maybe a0) -> Trie (Either a b) a0 -> Trie (Either a b) a0 Source #

trieSingleton :: Either a b -> a0 -> Trie (Either a b) a0 Source #

trieMap :: (a0 -> b0) -> Trie (Either a b) a0 -> Trie (Either a b) b0 Source #

trieTraverse :: Applicative f => (a0 -> f b0) -> Trie (Either a b) a0 -> f (Trie (Either a b) b0) Source #

trieMapMaybeWithKey :: (Either a b -> a0 -> Maybe b0) -> Trie (Either a b) a0 -> Trie (Either a b) b0 Source #

trieFoldWithKey :: (Either a b -> a0 -> r -> r) -> r -> Trie (Either a b) a0 -> r Source #

trieTraverseWithKey :: Applicative f => (Either a b -> a0 -> f b0) -> Trie (Either a b) a0 -> f (Trie (Either a b) b0) Source #

trieTraverseMaybeWithKey :: Applicative f => (Either a b -> a0 -> f (Maybe b0)) -> Trie (Either a b) a0 -> f (Trie (Either a b) b0) Source #

trieMergeWithKey :: (Either a b -> a0 -> b0 -> Maybe c) -> (Trie (Either a b) a0 -> Trie (Either a b) c) -> (Trie (Either a b) b0 -> Trie (Either a b) c) -> Trie (Either a b) a0 -> Trie (Either a b) b0 -> Trie (Either a b) c Source #

(TrieKey a, TrieKey b) => TrieKey (a, b) Source # 
Instance details

Defined in Data.GenericTrie.Internal

Associated Types

type TrieRep (a, b) :: Type -> Type Source #

Methods

trieEmpty :: Trie (a, b) a0 Source #

trieNull :: Trie (a, b) a0 -> Bool Source #

trieLookup :: (a, b) -> Trie (a, b) a0 -> Maybe a0 Source #

trieInsert :: (a, b) -> a0 -> Trie (a, b) a0 -> Trie (a, b) a0 Source #

trieDelete :: (a, b) -> Trie (a, b) a0 -> Trie (a, b) a0 Source #

trieAlter :: (a, b) -> (Maybe a0 -> Maybe a0) -> Trie (a, b) a0 -> Trie (a, b) a0 Source #

trieSingleton :: (a, b) -> a0 -> Trie (a, b) a0 Source #

trieMap :: (a0 -> b0) -> Trie (a, b) a0 -> Trie (a, b) b0 Source #

trieTraverse :: Applicative f => (a0 -> f b0) -> Trie (a, b) a0 -> f (Trie (a, b) b0) Source #

trieMapMaybeWithKey :: ((a, b) -> a0 -> Maybe b0) -> Trie (a, b) a0 -> Trie (a, b) b0 Source #

trieFoldWithKey :: ((a, b) -> a0 -> r -> r) -> r -> Trie (a, b) a0 -> r Source #

trieTraverseWithKey :: Applicative f => ((a, b) -> a0 -> f b0) -> Trie (a, b) a0 -> f (Trie (a, b) b0) Source #

trieTraverseMaybeWithKey :: Applicative f => ((a, b) -> a0 -> f (Maybe b0)) -> Trie (a, b) a0 -> f (Trie (a, b) b0) Source #

trieMergeWithKey :: ((a, b) -> a0 -> b0 -> Maybe c) -> (Trie (a, b) a0 -> Trie (a, b) c) -> (Trie (a, b) b0 -> Trie (a, b) c) -> Trie (a, b) a0 -> Trie (a, b) b0 -> Trie (a, b) c Source #

(TrieKey a, TrieKey b, TrieKey c) => TrieKey (a, b, c) Source # 
Instance details

Defined in Data.GenericTrie.Internal

Associated Types

type TrieRep (a, b, c) :: Type -> Type Source #

Methods

trieEmpty :: Trie (a, b, c) a0 Source #

trieNull :: Trie (a, b, c) a0 -> Bool Source #

trieLookup :: (a, b, c) -> Trie (a, b, c) a0 -> Maybe a0 Source #

trieInsert :: (a, b, c) -> a0 -> Trie (a, b, c) a0 -> Trie (a, b, c) a0 Source #

trieDelete :: (a, b, c) -> Trie (a, b, c) a0 -> Trie (a, b, c) a0 Source #

trieAlter :: (a, b, c) -> (Maybe a0 -> Maybe a0) -> Trie (a, b, c) a0 -> Trie (a, b, c) a0 Source #

trieSingleton :: (a, b, c) -> a0 -> Trie (a, b, c) a0 Source #

trieMap :: (a0 -> b0) -> Trie (a, b, c) a0 -> Trie (a, b, c) b0 Source #

trieTraverse :: Applicative f => (a0 -> f b0) -> Trie (a, b, c) a0 -> f (Trie (a, b, c) b0) Source #

trieMapMaybeWithKey :: ((a, b, c) -> a0 -> Maybe b0) -> Trie (a, b, c) a0 -> Trie (a, b, c) b0 Source #

trieFoldWithKey :: ((a, b, c) -> a0 -> r -> r) -> r -> Trie (a, b, c) a0 -> r Source #

trieTraverseWithKey :: Applicative f => ((a, b, c) -> a0 -> f b0) -> Trie (a, b, c) a0 -> f (Trie (a, b, c) b0) Source #

trieTraverseMaybeWithKey :: Applicative f => ((a, b, c) -> a0 -> f (Maybe b0)) -> Trie (a, b, c) a0 -> f (Trie (a, b, c) b0) Source #

trieMergeWithKey :: ((a, b, c) -> a0 -> b0 -> Maybe c0) -> (Trie (a, b, c) a0 -> Trie (a, b, c) c0) -> (Trie (a, b, c) b0 -> Trie (a, b, c) c0) -> Trie (a, b, c) a0 -> Trie (a, b, c) b0 -> Trie (a, b, c) c0 Source #

(TrieKey a, TrieKey b, TrieKey c, TrieKey d) => TrieKey (a, b, c, d) Source # 
Instance details

Defined in Data.GenericTrie.Internal

Associated Types

type TrieRep (a, b, c, d) :: Type -> Type Source #

Methods

trieEmpty :: Trie (a, b, c, d) a0 Source #

trieNull :: Trie (a, b, c, d) a0 -> Bool Source #

trieLookup :: (a, b, c, d) -> Trie (a, b, c, d) a0 -> Maybe a0 Source #

trieInsert :: (a, b, c, d) -> a0 -> Trie (a, b, c, d) a0 -> Trie (a, b, c, d) a0 Source #

trieDelete :: (a, b, c, d) -> Trie (a, b, c, d) a0 -> Trie (a, b, c, d) a0 Source #

trieAlter :: (a, b, c, d) -> (Maybe a0 -> Maybe a0) -> Trie (a, b, c, d) a0 -> Trie (a, b, c, d) a0 Source #

trieSingleton :: (a, b, c, d) -> a0 -> Trie (a, b, c, d) a0 Source #

trieMap :: (a0 -> b0) -> Trie (a, b, c, d) a0 -> Trie (a, b, c, d) b0 Source #

trieTraverse :: Applicative f => (a0 -> f b0) -> Trie (a, b, c, d) a0 -> f (Trie (a, b, c, d) b0) Source #

trieMapMaybeWithKey :: ((a, b, c, d) -> a0 -> Maybe b0) -> Trie (a, b, c, d) a0 -> Trie (a, b, c, d) b0 Source #

trieFoldWithKey :: ((a, b, c, d) -> a0 -> r -> r) -> r -> Trie (a, b, c, d) a0 -> r Source #

trieTraverseWithKey :: Applicative f => ((a, b, c, d) -> a0 -> f b0) -> Trie (a, b, c, d) a0 -> f (Trie (a, b, c, d) b0) Source #

trieTraverseMaybeWithKey :: Applicative f => ((a, b, c, d) -> a0 -> f (Maybe b0)) -> Trie (a, b, c, d) a0 -> f (Trie (a, b, c, d) b0) Source #

trieMergeWithKey :: ((a, b, c, d) -> a0 -> b0 -> Maybe c0) -> (Trie (a, b, c, d) a0 -> Trie (a, b, c, d) c0) -> (Trie (a, b, c, d) b0 -> Trie (a, b, c, d) c0) -> Trie (a, b, c, d) a0 -> Trie (a, b, c, d) b0 -> Trie (a, b, c, d) c0 Source #

(TrieKey a, TrieKey b, TrieKey c, TrieKey d, TrieKey e) => TrieKey (a, b, c, d, e) Source # 
Instance details

Defined in Data.GenericTrie.Internal

Associated Types

type TrieRep (a, b, c, d, e) :: Type -> Type Source #

Methods

trieEmpty :: Trie (a, b, c, d, e) a0 Source #

trieNull :: Trie (a, b, c, d, e) a0 -> Bool Source #

trieLookup :: (a, b, c, d, e) -> Trie (a, b, c, d, e) a0 -> Maybe a0 Source #

trieInsert :: (a, b, c, d, e) -> a0 -> Trie (a, b, c, d, e) a0 -> Trie (a, b, c, d, e) a0 Source #

trieDelete :: (a, b, c, d, e) -> Trie (a, b, c, d, e) a0 -> Trie (a, b, c, d, e) a0 Source #

trieAlter :: (a, b, c, d, e) -> (Maybe a0 -> Maybe a0) -> Trie (a, b, c, d, e) a0 -> Trie (a, b, c, d, e) a0 Source #

trieSingleton :: (a, b, c, d, e) -> a0 -> Trie (a, b, c, d, e) a0 Source #

trieMap :: (a0 -> b0) -> Trie (a, b, c, d, e) a0 -> Trie (a, b, c, d, e) b0 Source #

trieTraverse :: Applicative f => (a0 -> f b0) -> Trie (a, b, c, d, e) a0 -> f (Trie (a, b, c, d, e) b0) Source #

trieMapMaybeWithKey :: ((a, b, c, d, e) -> a0 -> Maybe b0) -> Trie (a, b, c, d, e) a0 -> Trie (a, b, c, d, e) b0 Source #

trieFoldWithKey :: ((a, b, c, d, e) -> a0 -> r -> r) -> r -> Trie (a, b, c, d, e) a0 -> r Source #

trieTraverseWithKey :: Applicative f => ((a, b, c, d, e) -> a0 -> f b0) -> Trie (a, b, c, d, e) a0 -> f (Trie (a, b, c, d, e) b0) Source #

trieTraverseMaybeWithKey :: Applicative f => ((a, b, c, d, e) -> a0 -> f (Maybe b0)) -> Trie (a, b, c, d, e) a0 -> f (Trie (a, b, c, d, e) b0) Source #

trieMergeWithKey :: ((a, b, c, d, e) -> a0 -> b0 -> Maybe c0) -> (Trie (a, b, c, d, e) a0 -> Trie (a, b, c, d, e) c0) -> (Trie (a, b, c, d, e) b0 -> Trie (a, b, c, d, e) c0) -> Trie (a, b, c, d, e) a0 -> Trie (a, b, c, d, e) b0 -> Trie (a, b, c, d, e) c0 Source #

class TrieKey k => ShowTrieKey k Source #

Instances

Instances details
ShowTrieKey Void Source # 
Instance details

Defined in Data.GenericTrie.Internal

Methods

trieShowsPrec :: Show a => Int -> Trie Void a -> ShowS Source #

ShowTrieKey Ordering Source # 
Instance details

Defined in Data.GenericTrie.Internal

Methods

trieShowsPrec :: Show a => Int -> Trie Ordering a -> ShowS Source #

ShowTrieKey Integer Source # 
Instance details

Defined in Data.GenericTrie.Internal

Methods

trieShowsPrec :: Show a => Int -> Trie Integer a -> ShowS Source #

ShowTrieKey Natural Source # 
Instance details

Defined in Data.GenericTrie.Internal

Methods

trieShowsPrec :: Show a => Int -> Trie Natural a -> ShowS Source #

ShowTrieKey () Source # 
Instance details

Defined in Data.GenericTrie.Internal

Methods

trieShowsPrec :: Show a => Int -> Trie () a -> ShowS Source #

ShowTrieKey Bool Source # 
Instance details

Defined in Data.GenericTrie.Internal

Methods

trieShowsPrec :: Show a => Int -> Trie Bool a -> ShowS Source #

ShowTrieKey Char Source # 
Instance details

Defined in Data.GenericTrie.Internal

Methods

trieShowsPrec :: Show a => Int -> Trie Char a -> ShowS Source #

ShowTrieKey Int Source # 
Instance details

Defined in Data.GenericTrie.Internal

Methods

trieShowsPrec :: Show a => Int -> Trie Int a -> ShowS Source #

ShowTrieKey Word Source # 
Instance details

Defined in Data.GenericTrie.Internal

Methods

trieShowsPrec :: Show a => Int -> Trie Word a -> ShowS Source #

(Show k, Ord k) => ShowTrieKey (OrdKey k) Source # 
Instance details

Defined in Data.GenericTrie.Internal

Methods

trieShowsPrec :: Show a => Int -> Trie (OrdKey k) a -> ShowS Source #

ShowTrieKey k => ShowTrieKey (Maybe k) Source # 
Instance details

Defined in Data.GenericTrie.Internal

Methods

trieShowsPrec :: Show a => Int -> Trie (Maybe k) a -> ShowS Source #

ShowTrieKey k => ShowTrieKey [k] Source # 
Instance details

Defined in Data.GenericTrie.Internal

Methods

trieShowsPrec :: Show a => Int -> Trie [k] a -> ShowS Source #

(ShowTrieKey a, ShowTrieKey b) => ShowTrieKey (Either a b) Source # 
Instance details

Defined in Data.GenericTrie.Internal

Methods

trieShowsPrec :: Show a0 => Int -> Trie (Either a b) a0 -> ShowS Source #

(ShowTrieKey a, ShowTrieKey b) => ShowTrieKey (a, b) Source # 
Instance details

Defined in Data.GenericTrie.Internal

Methods

trieShowsPrec :: Show a0 => Int -> Trie (a, b) a0 -> ShowS Source #

(ShowTrieKey a, ShowTrieKey b, ShowTrieKey c) => ShowTrieKey (a, b, c) Source # 
Instance details

Defined in Data.GenericTrie.Internal

Methods

trieShowsPrec :: Show a0 => Int -> Trie (a, b, c) a0 -> ShowS Source #

(ShowTrieKey a, ShowTrieKey b, ShowTrieKey c, ShowTrieKey d) => ShowTrieKey (a, b, c, d) Source # 
Instance details

Defined in Data.GenericTrie.Internal

Methods

trieShowsPrec :: Show a0 => Int -> Trie (a, b, c, d) a0 -> ShowS Source #

(ShowTrieKey a, ShowTrieKey b, ShowTrieKey c, ShowTrieKey d, ShowTrieKey e) => ShowTrieKey (a, b, c, d, e) Source # 
Instance details

Defined in Data.GenericTrie.Internal

Methods

trieShowsPrec :: Show a0 => Int -> Trie (a, b, c, d, e) a0 -> ShowS Source #

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

traverseMaybeWithKey :: (TrieKey k, Applicative f) => (k -> a -> f (Maybe b)) -> Trie k a -> f (Trie k b) Source #

Perform an action for each value in a trie and keep the elements of the trie that result in a Just 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

Instances

Instances details
Read k => Read (OrdKey k) Source # 
Instance details

Defined in Data.GenericTrie.Internal

Show k => Show (OrdKey k) Source # 
Instance details

Defined in Data.GenericTrie.Internal

Methods

showsPrec :: Int -> OrdKey k -> ShowS #

show :: OrdKey k -> String #

showList :: [OrdKey k] -> ShowS #

(Show k, Ord k) => ShowTrieKey (OrdKey k) Source # 
Instance details

Defined in Data.GenericTrie.Internal

Methods

trieShowsPrec :: Show a => Int -> Trie (OrdKey k) a -> ShowS Source #

Ord k => TrieKey (OrdKey k) Source #

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.

Instance details

Defined in Data.GenericTrie.Internal

Associated Types

type TrieRep (OrdKey k) :: Type -> Type Source #

Methods

trieEmpty :: Trie (OrdKey k) a Source #

trieNull :: Trie (OrdKey k) a -> Bool Source #

trieLookup :: OrdKey k -> Trie (OrdKey k) a -> Maybe a Source #

trieInsert :: OrdKey k -> a -> Trie (OrdKey k) a -> Trie (OrdKey k) a Source #

trieDelete :: OrdKey k -> Trie (OrdKey k) a -> Trie (OrdKey k) a Source #

trieAlter :: OrdKey k -> (Maybe a -> Maybe a) -> Trie (OrdKey k) a -> Trie (OrdKey k) a Source #

trieSingleton :: OrdKey k -> a -> Trie (OrdKey k) a Source #

trieMap :: (a -> b) -> Trie (OrdKey k) a -> Trie (OrdKey k) b Source #

trieTraverse :: Applicative f => (a -> f b) -> Trie (OrdKey k) a -> f (Trie (OrdKey k) b) Source #

trieMapMaybeWithKey :: (OrdKey k -> a -> Maybe b) -> Trie (OrdKey k) a -> Trie (OrdKey k) b Source #

trieFoldWithKey :: (OrdKey k -> a -> r -> r) -> r -> Trie (OrdKey k) a -> r Source #

trieTraverseWithKey :: Applicative f => (OrdKey k -> a -> f b) -> Trie (OrdKey k) a -> f (Trie (OrdKey k) b) Source #

trieTraverseMaybeWithKey :: Applicative f => (OrdKey k -> a -> f (Maybe b)) -> Trie (OrdKey k) a -> f (Trie (OrdKey k) b) Source #

trieMergeWithKey :: (OrdKey k -> a -> b -> Maybe c) -> (Trie (OrdKey k) a -> Trie (OrdKey k) c) -> (Trie (OrdKey k) b -> Trie (OrdKey k) c) -> Trie (OrdKey k) a -> Trie (OrdKey k) b -> Trie (OrdKey k) c Source #

Eq k => Eq (OrdKey k) Source # 
Instance details

Defined in Data.GenericTrie.Internal

Methods

(==) :: OrdKey k -> OrdKey k -> Bool #

(/=) :: OrdKey k -> OrdKey k -> Bool #

Ord k => Ord (OrdKey k) Source # 
Instance details

Defined in Data.GenericTrie.Internal

Methods

compare :: OrdKey k -> OrdKey k -> Ordering #

(<) :: OrdKey k -> OrdKey k -> Bool #

(<=) :: OrdKey k -> OrdKey k -> Bool #

(>) :: OrdKey k -> OrdKey k -> Bool #

(>=) :: OrdKey k -> OrdKey k -> Bool #

max :: OrdKey k -> OrdKey k -> OrdKey k #

min :: OrdKey k -> OrdKey k -> OrdKey k #

type TrieRep (OrdKey k) Source # 
Instance details

Defined in Data.GenericTrie.Internal

type TrieRep (OrdKey k) = Map k