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

Safe HaskellTrustworthy
LanguageHaskell2010

Data.GenericTrie.Internal

Contents

Description

Unstable implementation details

Synopsis

Documentation

class TrieKey k where 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.

Associated Types

type TrieRep k :: * -> * Source #

Type of the representation of tries for this key.

Methods

trieEmpty :: Trie k a Source #

Construct an empty trie

trieNull :: Trie k a -> Bool Source #

Test for an empty trie

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

Lookup element from trie

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

Insert element into trie

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

Delete element from trie

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

Construct a trie holding a single value

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

Apply a function to all values stored in a trie

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

Traverse the values stored in a trie

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

Show the representation of a trie

trieMapMaybeWithKey :: (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.

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

Fold a trie with a function of both key and value.

trieTraverseWithKey :: 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.

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 #

trieEmpty :: TrieRep k ~ TrieRepDefault k => Trie k a Source #

Construct an empty trie

trieSingleton :: (GTrieKey (Rep k), Generic k, TrieRep k ~ TrieRepDefault k) => k -> a -> Trie k a Source #

Construct a trie holding a single value

trieNull :: TrieRep k ~ TrieRepDefault k => Trie k a -> Bool Source #

Test for an empty trie

trieLookup :: (GTrieKey (Rep k), Generic k, TrieRep k ~ TrieRepDefault k) => k -> Trie k a -> Maybe a Source #

Lookup element from trie

trieInsert :: (GTrieKey (Rep k), Generic k, TrieRep k ~ TrieRepDefault k) => k -> a -> Trie k a -> Trie k a Source #

Insert element into trie

trieDelete :: (GTrieKey (Rep k), Generic k, TrieRep k ~ TrieRepDefault k) => k -> Trie k a -> Trie k a Source #

Delete element from trie

trieMap :: (GTrieKey (Rep k), TrieRep k ~ TrieRepDefault k) => (a -> b) -> Trie k a -> Trie k b Source #

Apply a function to all values stored in a trie

trieTraverse :: (GTrieKey (Rep k), TrieRep k ~ TrieRepDefault k, Applicative f) => (a -> f b) -> Trie k a -> f (Trie k b) Source #

Traverse the values stored in a trie

trieShowsPrec :: (Show a, GTrieKeyShow (Rep k), TrieRep k ~ TrieRepDefault k) => Int -> Trie k a -> ShowS Source #

Show the representation of a trie

trieMapMaybeWithKey :: (GTrieKey (Rep k), Generic k, TrieRep k ~ TrieRepDefault 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.

trieFoldWithKey :: (GTrieKey (Rep k), TrieRep k ~ TrieRepDefault k, Generic k) => (k -> a -> r -> r) -> r -> Trie k a -> r Source #

Fold a trie with a function of both key and value.

trieTraverseWithKey :: (GTrieKey (Rep k), TrieRep k ~ TrieRepDefault k, Generic 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.

trieMergeWithKey :: (GTrieKey (Rep k), TrieRep k ~ TrieRepDefault k, Generic k) => (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 #

Instances

TrieKey Bool Source # 

Associated Types

type TrieRep Bool :: * -> * 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 #

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 #

trieShowsPrec :: Show a => Int -> Trie Bool a -> ShowS 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 #

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.

Associated Types

type TrieRep Char :: * -> * 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 #

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 #

trieShowsPrec :: Show a => Int -> Trie Char a -> ShowS 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 #

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.

Associated Types

type TrieRep Int :: * -> * 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 #

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 #

trieShowsPrec :: Show a => Int -> Trie Int a -> ShowS 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 #

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 Integer Source #

Integer tries are implemented with Map.

TrieKey () Source # 

Associated Types

type TrieRep () :: * -> * 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 #

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 #

trieShowsPrec :: Show a => Int -> Trie () a -> ShowS 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 #

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

TrieKey k => TrieKey [k] Source # 

Associated Types

type TrieRep [k] :: * -> * 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 #

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 #

trieShowsPrec :: Show a => Int -> Trie [k] a -> ShowS 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 #

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 k => TrieKey (Maybe k) Source # 

Associated Types

type TrieRep (Maybe k) :: * -> * 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 #

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 #

trieShowsPrec :: Show a => Int -> Trie (Maybe k) a -> ShowS 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 #

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 #

(Show k, 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.

Associated Types

type TrieRep (OrdKey k) :: * -> * 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 #

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 #

trieShowsPrec :: Show a => Int -> Trie (OrdKey k) a -> ShowS 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 #

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 a, TrieKey b) => TrieKey (Either a b) Source # 

Associated Types

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

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Associated Types

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

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Associated Types

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

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Associated Types

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

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Associated Types

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

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

newtype Trie k a Source #

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

Constructors

MkTrie (TrieRep k a) 

Instances

TrieKey k => Functor (Trie k) Source # 

Methods

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

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

TrieKey k => Foldable (Trie k) Source # 

Methods

fold :: Monoid m => Trie k m -> 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 # 

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) #

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

Methods

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

show :: Trie k a -> String #

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

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

Eq k => Eq (OrdKey k) Source # 

Methods

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

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

Ord k => Ord (OrdKey k) Source # 

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 #

Read k => Read (OrdKey k) Source # 
Show k => Show (OrdKey k) Source # 

Methods

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

show :: OrdKey k -> String #

showList :: [OrdKey k] -> ShowS #

(Show k, 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.

Associated Types

type TrieRep (OrdKey k) :: * -> * 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 #

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 #

trieShowsPrec :: Show a => Int -> Trie (OrdKey k) a -> ShowS 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 #

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 #

type TrieRep (OrdKey k) Source # 
type TrieRep (OrdKey k) = Map k

Generic derivation implementation

genericTrieNull :: TrieRep k ~ TrieRepDefault k => Trie k a -> Bool Source #

Generic implementation of trieNull. This is the default implementation.

genericTrieMap :: (GTrieKey (Rep k), TrieRep k ~ TrieRepDefault k) => (a -> b) -> Trie k a -> Trie k b Source #

Generic implementation of trieMap. This is the default implementation.

genericTrieTraverse :: (GTrieKey (Rep k), TrieRep k ~ TrieRepDefault k, Applicative f) => (a -> f b) -> Trie k a -> f (Trie k b) Source #

Generic implementation of trieTraverse. This is the default implementation.

genericTrieShowsPrec :: (Show a, GTrieKeyShow (Rep k), TrieRep k ~ TrieRepDefault k) => Int -> Trie k a -> ShowS Source #

Generic implementation of trieShowsPrec. This is the default implementation.

genericInsert :: (GTrieKey (Rep k), Generic k, TrieRep k ~ TrieRepDefault k) => k -> a -> Trie k a -> Trie k a Source #

Generic implementation of insert. This is the default implementation.

genericLookup :: (GTrieKey (Rep k), Generic k, TrieRep k ~ TrieRepDefault k) => k -> Trie k a -> Maybe a Source #

Generic implementation of lookup. This is the default implementation.

genericDelete :: (GTrieKey (Rep k), Generic k, TrieRep k ~ TrieRepDefault k) => k -> Trie k a -> Trie k a Source #

Generic implementation of delete. This is the default implementation.

genericMapMaybeWithKey :: (GTrieKey (Rep k), Generic k, TrieRep k ~ TrieRepDefault k) => (k -> a -> Maybe b) -> Trie k a -> Trie k b Source #

Generic implementation of mapMaybe. This is the default implementation.

genericSingleton :: (GTrieKey (Rep k), Generic k, TrieRep k ~ TrieRepDefault k) => k -> a -> Trie k a Source #

Generic implementation of singleton. This is the default implementation.

genericEmpty :: TrieRep k ~ TrieRepDefault k => Trie k a Source #

Generic implementation of empty. This is the default implementation.

genericFoldWithKey :: (GTrieKey (Rep k), Generic k, TrieRep k ~ TrieRepDefault k) => (k -> a -> r -> r) -> r -> Trie k a -> r Source #

Generic implementation of foldWithKey. This is the default implementation.

genericTraverseWithKey :: (GTrieKey (Rep k), Generic k, TrieRep k ~ TrieRepDefault k, Applicative f) => (k -> a -> f b) -> Trie k a -> f (Trie k b) Source #

Generic implementation of traverseWithKey. This is the default implementation.

data TrieRepDefault k a Source #

The default implementation of a TrieRep is GTrie wrapped in a Maybe. This wrapping is due to the GTrie being a non-empty trie allowing all the of the "emptiness" to be represented at the top level for any given generically implemented key.

class GTrieKey f where Source #

TrieKey operations on Generic representations used to provide the default implementations of tries.

Methods

gtrieLookup :: f p -> GTrie f a -> Maybe a Source #

gtrieInsert :: f p -> a -> GTrie f a -> GTrie f a Source #

gtrieSingleton :: f p -> a -> GTrie f a Source #

gtrieDelete :: f p -> GTrie f a -> Maybe (GTrie f a) Source #

gtrieMap :: (a -> b) -> GTrie f a -> GTrie f b Source #

gtrieTraverse :: Applicative m => (a -> m b) -> GTrie f a -> m (GTrie f b) Source #

gmapMaybeWithKey :: (f p -> a -> Maybe b) -> GTrie f a -> Maybe (GTrie f b) Source #

gfoldWithKey :: (f p -> a -> r -> r) -> r -> GTrie f a -> r Source #

gtraverseWithKey :: Applicative m => (f p -> a -> m b) -> GTrie f a -> m (GTrie f b) Source #

gmergeWithKey :: (f p -> a -> b -> Maybe c) -> (GTrie f a -> Maybe (GTrie f c)) -> (GTrie f b -> Maybe (GTrie f c)) -> GTrie f a -> GTrie f b -> Maybe (GTrie f c) Source #

Instances

GTrieKey V1 Source #

Tries of types without constructors are represented by a unit.

Methods

gtrieLookup :: V1 p -> GTrie V1 a -> Maybe a Source #

gtrieInsert :: V1 p -> a -> GTrie V1 a -> GTrie V1 a Source #

gtrieSingleton :: V1 p -> a -> GTrie V1 a Source #

gtrieDelete :: V1 p -> GTrie V1 a -> Maybe (GTrie V1 a) Source #

gtrieMap :: (a -> b) -> GTrie V1 a -> GTrie V1 b Source #

gtrieTraverse :: Applicative m => (a -> m b) -> GTrie V1 a -> m (GTrie V1 b) Source #

gmapMaybeWithKey :: (V1 p -> a -> Maybe b) -> GTrie V1 a -> Maybe (GTrie V1 b) Source #

gfoldWithKey :: (V1 p -> a -> r -> r) -> r -> GTrie V1 a -> r Source #

gtraverseWithKey :: Applicative m => (V1 p -> a -> m b) -> GTrie V1 a -> m (GTrie V1 b) Source #

gmergeWithKey :: (V1 p -> a -> b -> Maybe c) -> (GTrie V1 a -> Maybe (GTrie V1 c)) -> (GTrie V1 b -> Maybe (GTrie V1 c)) -> GTrie V1 a -> GTrie V1 b -> Maybe (GTrie V1 c) Source #

GTrieKey U1 Source #

Tries of constructors without fields are represented by a single value.

Methods

gtrieLookup :: U1 p -> GTrie U1 a -> Maybe a Source #

gtrieInsert :: U1 p -> a -> GTrie U1 a -> GTrie U1 a Source #

gtrieSingleton :: U1 p -> a -> GTrie U1 a Source #

gtrieDelete :: U1 p -> GTrie U1 a -> Maybe (GTrie U1 a) Source #

gtrieMap :: (a -> b) -> GTrie U1 a -> GTrie U1 b Source #

gtrieTraverse :: Applicative m => (a -> m b) -> GTrie U1 a -> m (GTrie U1 b) Source #

gmapMaybeWithKey :: (U1 p -> a -> Maybe b) -> GTrie U1 a -> Maybe (GTrie U1 b) Source #

gfoldWithKey :: (U1 p -> a -> r -> r) -> r -> GTrie U1 a -> r Source #

gtraverseWithKey :: Applicative m => (U1 p -> a -> m b) -> GTrie U1 a -> m (GTrie U1 b) Source #

gmergeWithKey :: (U1 p -> a -> b -> Maybe c) -> (GTrie U1 a -> Maybe (GTrie U1 c)) -> (GTrie U1 b -> Maybe (GTrie U1 c)) -> GTrie U1 a -> GTrie U1 b -> Maybe (GTrie U1 c) Source #

TrieKey k => GTrieKey (K1 i k) Source #

Generic fields are represented by tries of the field type.

Methods

gtrieLookup :: K1 i k p -> GTrie (K1 i k) a -> Maybe a Source #

gtrieInsert :: K1 i k p -> a -> GTrie (K1 i k) a -> GTrie (K1 i k) a Source #

gtrieSingleton :: K1 i k p -> a -> GTrie (K1 i k) a Source #

gtrieDelete :: K1 i k p -> GTrie (K1 i k) a -> Maybe (GTrie (K1 i k) a) Source #

gtrieMap :: (a -> b) -> GTrie (K1 i k) a -> GTrie (K1 i k) b Source #

gtrieTraverse :: Applicative m => (a -> m b) -> GTrie (K1 i k) a -> m (GTrie (K1 i k) b) Source #

gmapMaybeWithKey :: (K1 i k p -> a -> Maybe b) -> GTrie (K1 i k) a -> Maybe (GTrie (K1 i k) b) Source #

gfoldWithKey :: (K1 i k p -> a -> r -> r) -> r -> GTrie (K1 i k) a -> r Source #

gtraverseWithKey :: Applicative m => (K1 i k p -> a -> m b) -> GTrie (K1 i k) a -> m (GTrie (K1 i k) b) Source #

gmergeWithKey :: (K1 i k p -> a -> b -> Maybe c) -> (GTrie (K1 i k) a -> Maybe (GTrie (K1 i k) c)) -> (GTrie (K1 i k) b -> Maybe (GTrie (K1 i k) c)) -> GTrie (K1 i k) a -> GTrie (K1 i k) b -> Maybe (GTrie (K1 i k) c) Source #

(GTrieKey f, GTrieKey g) => GTrieKey ((:+:) f g) Source #

Generic sums are represented by up to a pair of sub-tries.

Methods

gtrieLookup :: (f :+: g) p -> GTrie (f :+: g) a -> Maybe a Source #

gtrieInsert :: (f :+: g) p -> a -> GTrie (f :+: g) a -> GTrie (f :+: g) a Source #

gtrieSingleton :: (f :+: g) p -> a -> GTrie (f :+: g) a Source #

gtrieDelete :: (f :+: g) p -> GTrie (f :+: g) a -> Maybe (GTrie (f :+: g) a) Source #

gtrieMap :: (a -> b) -> GTrie (f :+: g) a -> GTrie (f :+: g) b Source #

gtrieTraverse :: Applicative m => (a -> m b) -> GTrie (f :+: g) a -> m (GTrie (f :+: g) b) Source #

gmapMaybeWithKey :: ((f :+: g) p -> a -> Maybe b) -> GTrie (f :+: g) a -> Maybe (GTrie (f :+: g) b) Source #

gfoldWithKey :: ((f :+: g) p -> a -> r -> r) -> r -> GTrie (f :+: g) a -> r Source #

gtraverseWithKey :: Applicative m => ((f :+: g) p -> a -> m b) -> GTrie (f :+: g) a -> m (GTrie (f :+: g) b) Source #

gmergeWithKey :: ((f :+: g) p -> a -> b -> Maybe c) -> (GTrie (f :+: g) a -> Maybe (GTrie (f :+: g) c)) -> (GTrie (f :+: g) b -> Maybe (GTrie (f :+: g) c)) -> GTrie (f :+: g) a -> GTrie (f :+: g) b -> Maybe (GTrie (f :+: g) c) Source #

(GTrieKey f, GTrieKey g) => GTrieKey ((:*:) f g) Source #

Generic products are represented by tries of tries.

Methods

gtrieLookup :: (f :*: g) p -> GTrie (f :*: g) a -> Maybe a Source #

gtrieInsert :: (f :*: g) p -> a -> GTrie (f :*: g) a -> GTrie (f :*: g) a Source #

gtrieSingleton :: (f :*: g) p -> a -> GTrie (f :*: g) a Source #

gtrieDelete :: (f :*: g) p -> GTrie (f :*: g) a -> Maybe (GTrie (f :*: g) a) Source #

gtrieMap :: (a -> b) -> GTrie (f :*: g) a -> GTrie (f :*: g) b Source #

gtrieTraverse :: Applicative m => (a -> m b) -> GTrie (f :*: g) a -> m (GTrie (f :*: g) b) Source #

gmapMaybeWithKey :: ((f :*: g) p -> a -> Maybe b) -> GTrie (f :*: g) a -> Maybe (GTrie (f :*: g) b) Source #

gfoldWithKey :: ((f :*: g) p -> a -> r -> r) -> r -> GTrie (f :*: g) a -> r Source #

gtraverseWithKey :: Applicative m => ((f :*: g) p -> a -> m b) -> GTrie (f :*: g) a -> m (GTrie (f :*: g) b) Source #

gmergeWithKey :: ((f :*: g) p -> a -> b -> Maybe c) -> (GTrie (f :*: g) a -> Maybe (GTrie (f :*: g) c)) -> (GTrie (f :*: g) b -> Maybe (GTrie (f :*: g) c)) -> GTrie (f :*: g) a -> GTrie (f :*: g) b -> Maybe (GTrie (f :*: g) c) Source #

GTrieKey f => GTrieKey (M1 i c f) Source #

Generic metadata is skipped in trie representation and operations.

Methods

gtrieLookup :: M1 i c f p -> GTrie (M1 i c f) a -> Maybe a Source #

gtrieInsert :: M1 i c f p -> a -> GTrie (M1 i c f) a -> GTrie (M1 i c f) a Source #

gtrieSingleton :: M1 i c f p -> a -> GTrie (M1 i c f) a Source #

gtrieDelete :: M1 i c f p -> GTrie (M1 i c f) a -> Maybe (GTrie (M1 i c f) a) Source #

gtrieMap :: (a -> b) -> GTrie (M1 i c f) a -> GTrie (M1 i c f) b Source #

gtrieTraverse :: Applicative m => (a -> m b) -> GTrie (M1 i c f) a -> m (GTrie (M1 i c f) b) Source #

gmapMaybeWithKey :: (M1 i c f p -> a -> Maybe b) -> GTrie (M1 i c f) a -> Maybe (GTrie (M1 i c f) b) Source #

gfoldWithKey :: (M1 i c f p -> a -> r -> r) -> r -> GTrie (M1 i c f) a -> r Source #

gtraverseWithKey :: Applicative m => (M1 i c f p -> a -> m b) -> GTrie (M1 i c f) a -> m (GTrie (M1 i c f) b) Source #

gmergeWithKey :: (M1 i c f p -> a -> b -> Maybe c) -> (GTrie (M1 i c f) a -> Maybe (GTrie (M1 i c f) c)) -> (GTrie (M1 i c f) b -> Maybe (GTrie (M1 i c f) c)) -> GTrie (M1 i c f) a -> GTrie (M1 i c f) b -> Maybe (GTrie (M1 i c f) c) Source #

data family GTrie (f :: * -> *) a Source #

Mapping of generic representation of keys to trie structures.

Instances

GTrieKey f => Functor (GTrie f) Source # 

Methods

fmap :: (a -> b) -> GTrie f a -> GTrie f b #

(<$) :: a -> GTrie f b -> GTrie f a #

(Show a, GTrieKeyShow f) => Show (GTrie f a) Source # 

Methods

showsPrec :: Int -> GTrie f a -> ShowS #

show :: GTrie f a -> String #

showList :: [GTrie f a] -> ShowS #

data GTrie V1 Source # 
data GTrie V1
data GTrie U1 Source # 
data GTrie U1 = UTrie a
data GTrie (K1 i k) Source # 
data GTrie (K1 i k) = KTrie (Trie k a)
data GTrie ((:+:) f g) Source # 
data GTrie ((:+:) f g)
data GTrie ((:*:) f g) Source # 
data GTrie ((:*:) f g) = PTrie (GTrie f (GTrie g a))
data GTrie (M1 i c f) Source # 
data GTrie (M1 i c f) = MTrie (GTrie f a)