bytestring-trie-0.2.6: An efficient finite map from (byte)strings to values.
CopyrightCopyright (c) 2008--2021 wren gayle romano
LicenseBSD3
Maintainerwren@cpan.org
Stabilityprovisional
Portabilityportable (with CPP)
Safe HaskellNone
LanguageHaskell2010

Data.Trie.Internal

Description

Internal definition of the Trie data type and generic functions for manipulating them. Almost everything here is re-exported from Data.Trie, which is the preferred API for users. This module is for developers who need deeper (and potentially fragile) access to the abstract type.

Synopsis

Data types

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

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

Defined in Data.Trie.Internal

Methods

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

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

Show a => Show (Trie a) Source # 
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 # 
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 #

showTrie :: Show a => Trie a -> String Source #

Visualization fuction for debugging.

Functions for ByteStrings

breakMaximalPrefix :: ByteString -> ByteString -> (ByteString, ByteString, ByteString) Source #

Returns the longest shared prefix and the two remaining suffixes for a pair of strings.

   s == (\(pre,s',z') -> pre `append` s') (breakMaximalPrefix s z)
   z == (\(pre,s',z') -> pre `append` z') (breakMaximalPrefix s z)

Basic functions

empty :: Trie a Source #

O(1), Construct the empty trie.

null :: Trie a -> Bool Source #

O(1), Is the trie empty?

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

O(1), Construct a singleton trie.

size :: Trie a -> Int Source #

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

Conversion and folding functions

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

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

foldrWithKey :: (ByteString -> a -> b -> b) -> b -> Trie a -> b Source #

Convert a trie into a list (in key-sorted order) using a function, folding the list as we go.

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

Catamorphism for tries. Unlike most other functions (mapBy, contextualMapBy, foldrWithKey, etc), this function does *not* reconstruct the full ByteString for each value; instead it only returns the suffix since the previous value or branch point.

This function is a direct/literal catamorphism of the implementation datatype, erasing only some bitmasking metadata for the branches. For a more semantic catamorphism, see cata.

Since: 0.2.6

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

Catamorphism for tries. Unlike most other functions (mapBy, contextualMapBy, foldrWithKey, etc), this function does *not* reconstruct the full ByteString for each value; instead it only returns the suffix since the previous value or branch point.

This function is a semantic catamorphism; that is, it tries to express the invariants of the implementation, rather than exposing the literal structure of the implementation. For a more literal catamorphism, see cata_.

Since: 0.2.6

Query functions

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

Generic function to find a value (if it exists) and the subtrie rooted at the prefix. The first function argument is called if and only if a node is exactly reachable by the query; if no node is exactly reachable the default value is used; if the middle of an arc is reached, the second function argument is used.

This function is intended for internal use. For the public-facing version, see lookupBy.

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

Return the subtrie containing all keys beginning with a prefix.

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

Given a query, find the longest prefix with an associated value in the trie, returning the length of that prefix and the associated value.

This function may not have the most useful return type. For a version that returns the prefix itself as well as the remaining string, see match.

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

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

This function may not have the most useful return type. For a version that returns the prefix itself as well as the remaining string, see matches.

Simple modification

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

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

A variant of alterBy which also allows modifying the sub-trie. If the function returns (Just v, t) and lookup S.empty t == Just w, then the w will be overwritten by v.

Type changed in 0.2.6

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.

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

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

Mapping functions

mapBy :: (ByteString -> 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.

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

A variant of fmap which provides access to the subtrie rooted at each value.

contextualMap' :: (a -> Trie a -> b) -> Trie a -> Trie b Source #

A variant of contextualMap which applies the function strictly.

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

A contextual variant of filterMap.

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

A contextual variant of mapBy. Again note that this is expensive since we must reconstruct the keys.

Priority-queue functions

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

Return the lexicographically smallest ByteString and the value it's mapped to; or Nothing for the empty trie. When one entry is a prefix of another, the prefix will be returned.

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

Return the lexicographically largest ByteString and the value it's mapped to; or Nothing for the empty trie. When one entry is a prefix of another, the longer one will be returned.

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

Update the minAssoc and return the old minAssoc.

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

Update the maxAssoc and return the old maxAssoc.