trie-simple-0.4.2: Simple Map-based Trie
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Trie.Map

Synopsis

Type

data TMap c a Source #

Mapping from [c] to a implemented as a trie. This type serves the almost same purpose of Map [c] a, but can be looked up more efficiently.

Instances

Instances details
Eq2 TMap Source # 
Instance details

Defined in Data.Trie.Map.Hidden

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> TMap a c -> TMap b d -> Bool #

Ord2 TMap Source # 
Instance details

Defined in Data.Trie.Map.Hidden

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> TMap a c -> TMap b d -> Ordering #

Show2 TMap Source # 
Instance details

Defined in Data.Trie.Map.Hidden

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> TMap a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [TMap a b] -> ShowS #

Hashable2 TMap Source # 
Instance details

Defined in Data.Trie.Map.Hidden

Methods

liftHashWithSalt2 :: (Int -> a -> Int) -> (Int -> b -> Int) -> Int -> TMap a b -> Int #

Foldable (TMap c) Source # 
Instance details

Defined in Data.Trie.Map.Hidden

Methods

fold :: Monoid m => TMap c m -> m #

foldMap :: Monoid m => (a -> m) -> TMap c a -> m #

foldMap' :: Monoid m => (a -> m) -> TMap c a -> m #

foldr :: (a -> b -> b) -> b -> TMap c a -> b #

foldr' :: (a -> b -> b) -> b -> TMap c a -> b #

foldl :: (b -> a -> b) -> b -> TMap c a -> b #

foldl' :: (b -> a -> b) -> b -> TMap c a -> b #

foldr1 :: (a -> a -> a) -> TMap c a -> a #

foldl1 :: (a -> a -> a) -> TMap c a -> a #

toList :: TMap c a -> [a] #

null :: TMap c a -> Bool #

length :: TMap c a -> Int #

elem :: Eq a => a -> TMap c a -> Bool #

maximum :: Ord a => TMap c a -> a #

minimum :: Ord a => TMap c a -> a #

sum :: Num a => TMap c a -> a #

product :: Num a => TMap c a -> a #

Eq c => Eq1 (TMap c) Source # 
Instance details

Defined in Data.Trie.Map.Hidden

Methods

liftEq :: (a -> b -> Bool) -> TMap c a -> TMap c b -> Bool #

Ord c => Ord1 (TMap c) Source # 
Instance details

Defined in Data.Trie.Map.Hidden

Methods

liftCompare :: (a -> b -> Ordering) -> TMap c a -> TMap c b -> Ordering #

Show c => Show1 (TMap c) Source # 
Instance details

Defined in Data.Trie.Map.Hidden

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> TMap c a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [TMap c a] -> ShowS #

Traversable (TMap c) Source # 
Instance details

Defined in Data.Trie.Map.Hidden

Methods

traverse :: Applicative f => (a -> f b) -> TMap c a -> f (TMap c b) #

sequenceA :: Applicative f => TMap c (f a) -> f (TMap c a) #

mapM :: Monad m => (a -> m b) -> TMap c a -> m (TMap c b) #

sequence :: Monad m => TMap c (m a) -> m (TMap c a) #

Functor (TMap c) Source # 
Instance details

Defined in Data.Trie.Map.Hidden

Methods

fmap :: (a -> b) -> TMap c a -> TMap c b #

(<$) :: a -> TMap c b -> TMap c a #

Hashable c => Hashable1 (TMap c) Source # 
Instance details

Defined in Data.Trie.Map.Hidden

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> TMap c a -> Int #

Eq c => Matchable (TMap c) Source # 
Instance details

Defined in Data.Trie.Map.Hidden

Methods

zipMatch :: TMap c a -> TMap c b -> Maybe (TMap c (a, b)) #

zipMatchWith :: (a -> b -> Maybe c0) -> TMap c a -> TMap c b -> Maybe (TMap c c0) #

Ord c => Align (TMap c) Source # 
Instance details

Defined in Data.Trie.Map.Hidden

Methods

nil :: TMap c a #

Ord c => Semialign (TMap c) Source # 
Instance details

Defined in Data.Trie.Map.Hidden

Methods

align :: TMap c a -> TMap c b -> TMap c (These a b) #

alignWith :: (These a b -> c0) -> TMap c a -> TMap c b -> TMap c c0 #

Ord c => Zip (TMap c) Source # 
Instance details

Defined in Data.Trie.Map.Hidden

Methods

zip :: TMap c a -> TMap c b -> TMap c (a, b) #

zipWith :: (a -> b -> c0) -> TMap c a -> TMap c b -> TMap c c0 #

Ord c => Filterable (TMap c) Source # 
Instance details

Defined in Data.Trie.Map.Hidden

Methods

mapMaybe :: (a -> Maybe b) -> TMap c a -> TMap c b #

catMaybes :: TMap c (Maybe a) -> TMap c a #

filter :: (a -> Bool) -> TMap c a -> TMap c a #

Ord c => Witherable (TMap c) Source # 
Instance details

Defined in Data.Trie.Map.Hidden

Methods

wither :: Applicative f => (a -> f (Maybe b)) -> TMap c a -> f (TMap c b) #

witherM :: Monad m => (a -> m (Maybe b)) -> TMap c a -> m (TMap c b) #

filterA :: Applicative f => (a -> f Bool) -> TMap c a -> f (TMap c a) #

witherMap :: Applicative m => (TMap c b -> r) -> (a -> m (Maybe b)) -> TMap c a -> m r #

FoldableWithIndex [c] (TMap c) Source # 
Instance details

Defined in Data.Trie.Map.Hidden

Methods

ifoldMap :: Monoid m => ([c] -> a -> m) -> TMap c a -> m #

ifoldMap' :: Monoid m => ([c] -> a -> m) -> TMap c a -> m #

ifoldr :: ([c] -> a -> b -> b) -> b -> TMap c a -> b #

ifoldl :: ([c] -> b -> a -> b) -> b -> TMap c a -> b #

ifoldr' :: ([c] -> a -> b -> b) -> b -> TMap c a -> b #

ifoldl' :: ([c] -> b -> a -> b) -> b -> TMap c a -> b #

FunctorWithIndex [c] (TMap c) Source # 
Instance details

Defined in Data.Trie.Map.Hidden

Methods

imap :: ([c] -> a -> b) -> TMap c a -> TMap c b #

TraversableWithIndex [c] (TMap c) Source # 
Instance details

Defined in Data.Trie.Map.Hidden

Methods

itraverse :: Applicative f => ([c] -> a -> f b) -> TMap c a -> f (TMap c b) #

Ord c => FilterableWithIndex [c] (TMap c) Source # 
Instance details

Defined in Data.Trie.Map.Hidden

Methods

imapMaybe :: ([c] -> a -> Maybe b) -> TMap c a -> TMap c b #

ifilter :: ([c] -> a -> Bool) -> TMap c a -> TMap c a #

Ord c => WitherableWithIndex [c] (TMap c) Source # 
Instance details

Defined in Data.Trie.Map.Hidden

Methods

iwither :: Applicative f => ([c] -> a -> f (Maybe b)) -> TMap c a -> f (TMap c b) #

iwitherM :: Monad m => ([c] -> a -> m (Maybe b)) -> TMap c a -> m (TMap c b) #

ifilterA :: Applicative f => ([c] -> a -> f Bool) -> TMap c a -> f (TMap c a) #

(Ord c, Semigroup a) => Monoid (TMap c a) Source #

unionWith-based

Instance details

Defined in Data.Trie.Map.Hidden

Methods

mempty :: TMap c a #

mappend :: TMap c a -> TMap c a -> TMap c a #

mconcat :: [TMap c a] -> TMap c a #

(Ord c, Semigroup a) => Semigroup (TMap c a) Source #

unionWith-based

Instance details

Defined in Data.Trie.Map.Hidden

Methods

(<>) :: TMap c a -> TMap c a -> TMap c a #

sconcat :: NonEmpty (TMap c a) -> TMap c a #

stimes :: Integral b => b -> TMap c a -> TMap c a #

Ord c => IsList (TMap c a) Source # 
Instance details

Defined in Data.Trie.Map.Hidden

Associated Types

type Item (TMap c a) #

Methods

fromList :: [Item (TMap c a)] -> TMap c a #

fromListN :: Int -> [Item (TMap c a)] -> TMap c a #

toList :: TMap c a -> [Item (TMap c a)] #

(Show c, Show a) => Show (TMap c a) Source # 
Instance details

Defined in Data.Trie.Map.Hidden

Methods

showsPrec :: Int -> TMap c a -> ShowS #

show :: TMap c a -> String #

showList :: [TMap c a] -> ShowS #

(NFData c, NFData a) => NFData (TMap c a) Source # 
Instance details

Defined in Data.Trie.Map.Hidden

Methods

rnf :: TMap c a -> () #

(Eq a, Eq c) => Eq (TMap c a) Source # 
Instance details

Defined in Data.Trie.Map.Hidden

Methods

(==) :: TMap c a -> TMap c a -> Bool #

(/=) :: TMap c a -> TMap c a -> Bool #

(Ord a, Ord c) => Ord (TMap c a) Source # 
Instance details

Defined in Data.Trie.Map.Hidden

Methods

compare :: TMap c a -> TMap c a -> Ordering #

(<) :: TMap c a -> TMap c a -> Bool #

(<=) :: TMap c a -> TMap c a -> Bool #

(>) :: TMap c a -> TMap c a -> Bool #

(>=) :: TMap c a -> TMap c a -> Bool #

max :: TMap c a -> TMap c a -> TMap c a #

min :: TMap c a -> TMap c a -> TMap c a #

(Hashable c, Hashable a) => Hashable (TMap c a) Source # 
Instance details

Defined in Data.Trie.Map.Hidden

Methods

hashWithSalt :: Int -> TMap c a -> Int #

hash :: TMap c a -> Int #

type Item (TMap c a) Source # 
Instance details

Defined in Data.Trie.Map.Hidden

type Item (TMap c a) = ([c], a)

Queries

match :: Ord c => [c] -> TMap c a -> (Maybe a, TMap c a) Source #

Perform partial matching against a TMap.

match xs tmap returns two values. The first value is the result of lookup. The second is another TMap for all keys which contain xs as their prefix. The keys of the returned map do not contain the common prefix xs.

Example
>>> let x = 'fromList' [("ham", 1), ("bacon", 2), ("hamburger", 3)]
>>> match "ham" x
(Just 1,fromList [("",1),("burger",3)])

lookup :: Ord c => [c] -> TMap c a -> Maybe a Source #

lookup xs tmap returns Just a if tmap contains mapping from xs to a, and returns Nothing if not.

member :: Ord c => [c] -> TMap c a -> Bool Source #

notMember :: Ord c => [c] -> TMap c a -> Bool Source #

null :: TMap c a -> Bool Source #

Tests if given map is empty.

count :: TMap c a -> Int Source #

Returns number of entries.

Note that this operation takes O(number of nodes), unlike O(1) of size.

keys :: TMap c a -> [[c]] Source #

Returns list of key strings, in ascending order.

elems :: TMap c a -> [a] Source #

Returns list of values, in ascending order by its key.

Construction

empty :: TMap c a Source #

Empty TMap.

just :: a -> TMap c a Source #

TMap which contains only one entry from the empty string to a.

singleton :: [c] -> a -> TMap c a Source #

singleton xs a is a TMap which contains only one entry from xs to a.

Single item modification

insertWith :: Ord c => (a -> a -> a) -> [c] -> a -> TMap c a -> TMap c a Source #

insertWith op xs a tmap inserts an entry of key-value pair (cs,a) to the tmap. If tmap already has an entry with key equals to xs, its value b is replaced with op a b.

insertWith op cs a = 'revise' (maybe a (op a)) cs

insert :: Ord c => [c] -> a -> TMap c a -> TMap c a Source #

Inserts an entry of key and value pair.

Already existing value will be overwritten.

insert = 'insertWith' (const a)

deleteWith :: Ord c => (b -> a -> Maybe a) -> [c] -> b -> TMap c a -> TMap c a Source #

Deletes an entry with given key, conditionally.

deleteWith f xs b looks up an entry with key xs, and if such entry is found, evaluate f b a with its value a. If it returned Nothing, the entry is deleted. Otherwise, if it returned Just a', the value of the entry is replaced with a'.

deleteWith f cs b = 'update' (f b) cs

delete :: Ord c => [c] -> TMap c a -> TMap c a Source #

Deletes an entry with given key.

delete = 'update' (const Nothing)

adjust :: Ord c => (a -> a) -> [c] -> TMap c a -> TMap c a Source #

Apply a function to the entry with given key.

revise :: Ord c => (Maybe a -> a) -> [c] -> TMap c a -> TMap c a Source #

Apply a function f to the entry with the given key. If there is no such entry, insert an entry with value f Nothing.

update :: Ord c => (a -> Maybe a) -> [c] -> TMap c a -> TMap c a Source #

Apply a function f to the entry with given key. If f returns Nothing, that entry is deleted.

alter :: Ord c => (Maybe a -> Maybe a) -> [c] -> TMap c a -> TMap c a Source #

Apply a function f to the entry with given key. This function alter is the most generic version of adjust, revise, update.

  • You can insert new entry by returning Just a from f Nothing.
  • You can delete existing entry by returning Nothing from f (Just a).

This function always evaluates f Nothing in addition to determine operation applied to the given key. If you're not going to use alter on missing keys, consider using update instead.

Combine

union :: Ord c => TMap c a -> TMap c a -> TMap c a Source #

unionWith :: Ord c => (a -> a -> a) -> TMap c a -> TMap c a -> TMap c a Source #

intersection :: Ord c => TMap c a -> TMap c b -> TMap c a Source #

intersectionWith :: Ord c => (a -> b -> Maybe r) -> TMap c a -> TMap c b -> TMap c r Source #

difference :: Ord c => TMap c a -> TMap c b -> TMap c a Source #

differenceWith :: Ord c => (a -> b -> Maybe a) -> TMap c a -> TMap c b -> TMap c a Source #

appendWith :: (Ord c, Semigroup z) => (x -> y -> z) -> TMap c x -> TMap c y -> TMap c z Source #

Creates a new TMap from two TMaps. The keys of the new map are concatenations of one key from the first map and another one from the second map.

Corresponding values for these keys are calculated with the given function of type (x -> y -> z). If two different concatenations yield the same key, the calculated values for these keys are combined with the Semigroup operation <>.

The behavior of appendWith is equivalent to the following implementation.

appendWith :: (Ord c, Semigroup z) => (x -> y -> z) ->
  TMap c x -> TMap c y -> TMap c z
appendWith f x y = fromListWith (flip (<>))
  [ (kx ++ ky, f valx valy)
    | (kx, valx) <- toAscList x
    , (ky, valy) <- toAscList y ]

In other words, a set of colliding key-valur pairs is combined in increasing order of the left key. For example, suppose x, y are TMap with these key-value pairs, and kx1 ++ ky3, kx2 ++ ky2, kx3 ++ ky1 are all equal to the same key kz.

x = fromAscList [ (kx1, x1), (kx2, x2), (kx3, x3) ] -- kx1 < kx2 < kx3
y = fromAscList [ (ky1, y1), (ky2, y2), (ky3, y3) ]

On these maps, appendWith combines the values for these colliding keys in the order of kx*.

lookup kz (appendWith f x y) == Just (f x1 y3 <> f x2 y2 <> f x3 y1)
Example
let x = fromList [("a", 1), ("aa", 2)]     :: TMap Char Int
    y = fromList [("aa", 10), ("aaa", 20)] :: TMap Char Int

appendWith (\a b -> show (a,b)) x y ==
  fromList [ ("aaa", "(1,10)")
           , ("aaaa", "(1,20)" <> "(2,10)")
           , ("aaaaa", "(2,20)") ]

Conversion

toList :: TMap c a -> [([c], a)] Source #

fromList :: Ord c => [([c], a)] -> TMap c a Source #

fromListWith :: Ord c => (a -> a -> a) -> [([c], a)] -> TMap c a Source #

toAscList :: TMap c a -> [([c], a)] Source #

fromAscList :: Eq c => [([c], a)] -> TMap c a Source #

fromAscListWith :: Ord c => (a -> a -> a) -> [([c], a)] -> TMap c a Source #

toMap :: TMap c a -> Map [c] a Source #

fromMap :: Eq c => Map [c] a -> TMap c a Source #

keysTSet :: TMap c a -> TSet c Source #

fromTSet :: ([c] -> a) -> TSet c -> TMap c a Source #

Parsing

toParser Source #

Arguments

:: Alternative f 
=> (c -> f c')

char

-> f eot

eot

-> TMap c a 
-> f ([c'], a) 

toParser_ Source #

Arguments

:: Alternative f 
=> (c -> f c')

char

-> f eot

eot

-> TMap c a 
-> f a 

toParser__ Source #

Arguments

:: Alternative f 
=> (c -> f c')

char

-> f eot

eot

-> TMap c a 
-> f () 

Traversing with keys

traverseWithKey :: Applicative f => ([c] -> a -> f b) -> TMap c a -> f (TMap c b) Source #

Same semantics to following defintion, but have more efficient implementation.

traverseWithKey f = fmap fromAscList .
                    traverse (\(cs,a) -> (,) cs <$> f cs a) .
                    toAscList

mapWithKey :: ([c] -> a -> b) -> TMap c a -> TMap c b Source #

Same semantics to following defintion, but have more efficient implementation.

mapWithKey f = fromAscList .
               map (\(cs,a) -> (cs,  f cs a)) .
               toAscList

foldMapWithKey :: Monoid r => ([c] -> a -> r) -> TMap c a -> r Source #

Same semantics to following defintion, but have more efficient implementation.

foldMapWithKey f = foldMap (uncurry f) . toAscList

foldrWithKey :: ([c] -> a -> r -> r) -> r -> TMap c a -> r Source #

Same semantics to following defintion, but have more efficient implementation.

foldrWithKey f z = foldr (uncurry f) z . toAscList