bytestring-trie-0.2.7: An efficient finite map from bytestrings to values.
Copyright2008--2021 wren romano
LicenseBSD-3-Clause
Maintainerwren@cpan.org
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Data.Trie

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 elements of Data.ByteString and then trie on the big-endian bit representation of those elements. For further details on the latter, see

  • Chris Okasaki and Andy Gill, "Fast Mergeable Integer Maps", Workshop on ML, September 1998, pages 77-86, http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.37.5452
  • D.R. Morrison, "PATRICIA -- Practical Algorithm To Retrieve Information Coded In Alphanumeric", Journal of the ACM, 15(4), October 1968, pages 514-534.

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

Instances details
Monad Trie Source #

Since: 0.2.2

Instance details

Defined in Data.Trie.Internal

Methods

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

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

return :: a -> Trie a #

Functor Trie Source # 
Instance details

Defined in Data.Trie.Internal

Methods

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

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

Applicative Trie Source #

Since: 0.2.2

Instance details

Defined in Data.Trie.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.Internal

Methods

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

foldMap :: Monoid m => (a -> m) -> Trie a -> 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.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) #

Eq1 Trie Source #

Since: 0.2.7

Instance details

Defined in Data.Trie.Internal

Methods

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

Ord1 Trie Source #

Warning: This instance suffers unnecessarily from Bug #25.

Since: 0.2.7

Instance details

Defined in Data.Trie.Internal

Methods

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

Read1 Trie Source #

Since: 0.2.7

Instance details

Defined in Data.Trie.Internal

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Trie a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Trie a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Trie a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Trie a] #

Show1 Trie Source #

Warning: This instance suffers Bug #25.

Since: 0.2.7

Instance details

Defined in Data.Trie.Internal

Methods

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

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

IsList (Trie a) Source #

Warning: The toList method of this instance suffers Bug #25.

Since: 0.2.7

Instance details

Defined in Data.Trie.Internal

Associated Types

type Item (Trie a) #

Methods

fromList :: [Item (Trie a)] -> Trie a #

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

toList :: Trie a -> [Item (Trie a)] #

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

Defined in Data.Trie.Internal

Methods

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

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

Ord a => Ord (Trie a) Source #

Warning: This instance suffers unnecessarily from Bug #25.

Since: 0.2.7

Instance details

Defined in Data.Trie.Internal

Methods

compare :: Trie a -> Trie a -> Ordering #

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

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

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

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

max :: Trie a -> Trie a -> Trie a #

min :: Trie a -> Trie a -> Trie a #

Read a => Read (Trie a) Source #

Since: 0.2.7

Instance details

Defined in Data.Trie.Internal

Show a => Show (Trie a) Source #

Warning: This instance suffers Bug #25.

Since: 0.2.2

Instance details

Defined in Data.Trie.Internal

Methods

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

show :: Trie a -> String #

showList :: [Trie a] -> ShowS #

Semigroup a => Semigroup (Trie a) Source #

Since: 0.2.5

Instance details

Defined in Data.Trie.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.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.Internal

Methods

put :: Trie a -> Put #

get :: Get (Trie a) #

putList :: [Trie a] -> Put #

NFData a => NFData (Trie a) Source #

Since: 0.2.7

Instance details

Defined in Data.Trie.Internal

Methods

rnf :: Trie a -> () #

type Item (Trie a) Source # 
Instance details

Defined in Data.Trie.Internal

type Item (Trie a) = (ByteString, a)

Basic functions

empty :: Trie a Source #

\(\mathcal{O}(1)\). Construct the empty trie.

null :: Trie a -> Bool Source #

\(\mathcal{O}(1)\). Is the trie empty?

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

\(\mathcal{O}(1)\). Construct a singleton trie.

size :: Trie a -> Int Source #

\(\mathcal{O}(n)\). Get count of elements in trie.

Conversion functions

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

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

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

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

Warning: This function suffers Bug #25.

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

Convert trie into association list. The list is ordered according to the keys.

Warning: This function suffers Bug #25.

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

Return all keys in the trie, in sorted order.

Warning: This function suffers Bug #25.

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

Return all values in the trie, in key-sorted order.

Note: Prior to version 0.2.7, this function suffered Bug #25; but it no longer does.

Since: 0.2.2

Query functions

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

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

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

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

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

Does a string have a value in the trie?

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

Return the subtrie containing all keys beginning with a prefix.

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

Given a query, find the longest prefix with an associated value in the trie, and return that prefix, it's value, and the remainder of the query.

Since: 0.2.4

minMatch :: Trie a -> ByteString -> Maybe (ByteString, a, ByteString) Source #

Given a query, find the shortest prefix with an associated value in the trie, and return that prefix, it's value, and the remainder of the query.

Since: 0.2.6

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

Given a query, find all prefixes with associated values in the trie, and return their (prefix, value, remainder) triples in order from shortest prefix to longest. This function is a good producer for list fusion.

Since: 0.2.4

Simple modification

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

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

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

Apply a function to the value at a key. If the key is not present, then the trie is returned unaltered.

adjustBy :: (ByteString -> a -> a -> a) -> ByteString -> a -> Trie a -> Trie a Source #

Alter the value associated with a given key. If the key is not present, then the trie is returned unaltered. See alterBy if you are interested in inserting new keys or deleting old keys. Because this function does not need to worry about changing the trie structure, it is somewhat faster than alterBy.

Note: Prior to version 0.2.6 this function was exported from Data.Trie.Internal instead.

Since: 0.2.6

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

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

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

Remove the value stored at a key.

deleteSubmap :: ByteString -> Trie a -> Trie a Source #

Remove all keys beginning with a prefix.

Since: 0.2.6

Combining tries

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

Take the union of 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 #

Take the union of two tries, resolving conflicts by choosing the value from the left trie.

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

Take the union of two tries, resolving conflicts by choosing the value from the right trie.

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

Take the intersection of two tries, using a function to resolve collisions.

Since: 0.2.6

intersectL :: Trie a -> Trie b -> Trie a Source #

Take the intersection of two tries, with values from the left trie.

Since: 0.2.6

intersectR :: Trie a -> Trie b -> Trie b Source #

Take the intersection of two tries, with values from the right trie.

Since: 0.2.6

Mapping functions

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

Keyed version of filterMap.

Warning: This function suffers Bug #25.

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

Apply a function to all values, potentially removing them.

Laws

Expand
Fission
filterMap f ≡ fmap (fromJust . f) . filter (isJust . f)
Fusion
fmap f . filter g ≡ filterMap (\v -> f v <$ guard (g v))
Conservation
filterMap (Just . f) ≡ fmap f
Composition
filterMap f . filterMap g ≡ filterMap (f <=< g)

The fission/fusion laws are essentially the same, they differ only in which direction is more "natural" for use as a rewrite rule. The conservation law is just a special case of fusion, but it's a particularly helpful one to take note of.