text-trie-0.2.5.0: An efficient finite map from Text to values, based on bytestring-trie.

CopyrightCopyright (c) 2008--2015 wren gayle romano 2019 michael j. klein
LicenseBSD3
Maintainerlambdamichael@gmail.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell98

Data.Trie.Text

Contents

Description

An efficient implementation of finite maps from strings to values. The implementation is based on big-endian patricia trees, like Data.IntMap. We first trie on the Word16 elements of Text and then trie on the big-endian bit representation of those elements. For further details, see

This module aims to provide an austere interface, while being detailed enough for most users. For an extended interface with many additional functions, see Data.Trie.Text.Convenience. For functions that give more detailed (potentially abstraction-breaking) access to the data strucuture, or for experimental functions which aren't quite ready for the public API, see Data.Trie.Text.Internal.

Synopsis

Data type

data Trie a Source #

A map from ByteStrings to a. For all the generic functions, note that tries are strict in the Maybe but not in a.

The Monad instance is strange. If a key k1 is a prefix of other keys, then results from binding the value at k1 will override values from longer keys when they collide. If this is useful for anything, or if there's a more sensible instance, I'd be curious to know.

Instances
Monad Trie Source # 
Instance details

Defined in Data.Trie.Text.Internal

Methods

(>>=) :: Trie a -> (a -> Trie b) -> Trie b #

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

return :: a -> Trie a #

fail :: String -> Trie a #

Functor Trie Source # 
Instance details

Defined in Data.Trie.Text.Internal

Methods

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

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

Applicative Trie Source # 
Instance details

Defined in Data.Trie.Text.Internal

Methods

pure :: a -> Trie a #

(<*>) :: Trie (a -> b) -> Trie a -> Trie b #

liftA2 :: (a -> b -> c) -> Trie a -> Trie b -> Trie c #

(*>) :: Trie a -> Trie b -> Trie b #

(<*) :: Trie a -> Trie b -> Trie a #

Foldable Trie Source # 
Instance details

Defined in Data.Trie.Text.Internal

Methods

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

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

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

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

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

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

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

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

toList :: Trie a -> [a] #

null :: Trie a -> Bool #

length :: Trie a -> Int #

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

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

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

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

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

Traversable Trie Source # 
Instance details

Defined in Data.Trie.Text.Internal

Methods

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

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

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

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

Eq a => Eq (Trie a) Source # 
Instance details

Defined in Data.Trie.Text.Internal

Methods

(==) :: Trie a -> Trie a -> Bool #

(/=) :: Trie a -> Trie a -> Bool #

Show a => Show (Trie a) Source # 
Instance details

Defined in Data.Trie.Text.Internal

Methods

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

show :: Trie a -> String #

showList :: [Trie a] -> ShowS #

Generic a => Generic (Trie a) Source # 
Instance details

Defined in Data.Trie.Text.Internal

Associated Types

type Rep (Trie a) :: Type -> Type #

Methods

from :: Trie a -> Rep (Trie a) x #

to :: Rep (Trie a) x -> Trie a #

Semigroup a => Semigroup (Trie a) Source # 
Instance details

Defined in Data.Trie.Text.Internal

Methods

(<>) :: Trie a -> Trie a -> Trie a #

sconcat :: NonEmpty (Trie a) -> Trie a #

stimes :: Integral b => b -> Trie a -> Trie a #

Monoid a => Monoid (Trie a) Source # 
Instance details

Defined in Data.Trie.Text.Internal

Methods

mempty :: Trie a #

mappend :: Trie a -> Trie a -> Trie a #

mconcat :: [Trie a] -> Trie a #

Binary a => Binary (Trie a) Source # 
Instance details

Defined in Data.Trie.Text.Internal

Methods

put :: Trie a -> Put #

get :: Get (Trie a) #

putList :: [Trie a] -> Put #

Generic1 Trie Source # 
Instance details

Defined in Data.Trie.Text.Internal

Associated Types

type Rep1 Trie :: k -> Type #

Methods

from1 :: Trie a -> Rep1 Trie a #

to1 :: Rep1 Trie a -> Trie a #

type Rep (Trie a) Source # 
Instance details

Defined in Data.Trie.Text.Internal

type Rep (Trie a)
type Rep1 Trie Source # 
Instance details

Defined in Data.Trie.Text.Internal

type Rep1 Trie

Basic functions

empty :: Trie a Source #

O(1), Construct the empty trie.

null :: Trie a -> Bool Source #

O(1), Is the trie empty?

singleton :: Text -> a -> Trie a Source #

O(1), Construct a singleton trie.

size :: Trie a -> Int Source #

O(n), Get count of elements in trie.

Conversion functions

fromList :: [(Text, a)] -> Trie a Source #

Convert association list into a trie. On key conflict, values earlier in the list shadow later ones.

toListBy :: (Text -> a -> b) -> Trie a -> [b] Source #

Convert a trie into a list using a function. Resulting values are in key-sorted order.

toList :: Trie a -> [(Text, a)] Source #

Convert trie into association list. Keys will be in sorted order.

keys :: Trie a -> [Text] Source #

Return all keys in the trie, in sorted order.

elems :: Trie a -> [a] Source #

Return all values in the trie, in sorted order according to the keys.

Query functions

lookupBy :: (Maybe a -> Trie a -> b) -> Text -> Trie a -> b Source #

Generic function to find a value (if it exists) and the subtrie rooted at the prefix.

lookup :: Text -> Trie a -> Maybe a Source #

Return the value associated with a query string if it exists.

member :: Text -> Trie a -> Bool Source #

Does a string have a value in the trie?

submap :: Text -> Trie a -> Trie a Source #

Return the subtrie containing all keys beginning with a prefix.

match :: Trie a -> Text -> Maybe (Text, a, Text) Source #

Given a query, find the longest prefix with an associated value in the trie, returning that prefix, it's value, and the remaining string.

matches :: Trie a -> Text -> [(Text, a, Text)] Source #

Given a query, find all prefixes with associated values in the trie, returning the prefixes, their values, and their remaining strings. This function is a good producer for list fusion.

Single-value modification

alterBy :: (Text -> a -> Maybe a -> Maybe a) -> Text -> a -> Trie a -> Trie a Source #

Generic function to alter a trie by one element with a function to resolve conflicts (or non-conflicts).

insert :: Text -> a -> Trie a -> Trie a Source #

Insert a new key. If the key is already present, overrides the old value

adjust :: (a -> a) -> Text -> Trie a -> Trie a Source #

Apply a function to the value at a key.

delete :: Text -> Trie a -> Trie a Source #

Remove the value stored at a key.

Combining tries

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

Combine two tries, using a function to resolve collisions. This can only define the space of functions between union and symmetric difference but, with those two, all set operations can be defined (albeit inefficiently).

unionL :: Trie a -> Trie a -> Trie a Source #

Combine two tries, resolving conflicts by choosing the value from the left trie.

unionR :: Trie a -> Trie a -> Trie a Source #

Combine two tries, resolving conflicts by choosing the value from the right trie.

Mapping functions

mapBy :: (Text -> a -> Maybe b) -> Trie a -> Trie b Source #

Generic version of fmap. This function is notably more expensive than fmap or filterMap because we have to reconstruct the keys.

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

Apply a function to all values, potentially removing them.