| Copyright | 2008--2022 wren romano | 
|---|---|
| License | BSD-3-Clause | 
| Maintainer | wren@cpan.org | 
| Stability | experimental | 
| Portability | portable (with CPP) | 
| Safe Haskell | Trustworthy | 
| Language | Haskell2010 | 
Data.Trie.Internal
Description
Synopsis
- data Trie a
- empty :: Trie a
- null :: Trie a -> Bool
- singleton :: ByteString -> a -> Trie a
- size :: Trie a -> Int
- fromList :: [(ByteString, a)] -> Trie a
- toList :: Trie a -> [(ByteString, a)]
- toListBy :: (ByteString -> a -> b) -> Trie a -> [b]
- elems :: Trie a -> [a]
- lookupBy_ :: (a -> Trie a -> b) -> (Trie a -> b) -> b -> ByteString -> Trie a -> b
- submap :: ByteString -> Trie a -> Trie a
- match_ :: Trie a -> ByteString -> Maybe (Int, a)
- matches_ :: Trie a -> ByteString -> [(Int, a)]
- alterBy :: (ByteString -> a -> Maybe a -> Maybe a) -> ByteString -> a -> Trie a -> Trie a
- alterBy_ :: (Maybe a -> Trie a -> (Maybe a, Trie a)) -> ByteString -> Trie a -> Trie a
- adjust :: (a -> a) -> ByteString -> Trie a -> Trie a
- wip_unionWith :: (a -> a -> a) -> Trie a -> Trie a -> Trie a
- mergeBy :: (a -> a -> Maybe a) -> Trie a -> Trie a -> Trie a
- intersectBy :: (a -> b -> Maybe c) -> Trie a -> Trie b -> Trie c
- minAssoc :: Trie a -> Maybe (ByteString, a)
- maxAssoc :: Trie a -> Maybe (ByteString, a)
- updateMinViewBy :: (ByteString -> a -> Maybe a) -> Trie a -> Maybe (ByteString, a, Trie a)
- updateMaxViewBy :: (ByteString -> a -> Maybe a) -> Trie a -> Maybe (ByteString, a, Trie a)
- filter :: (a -> Bool) -> Trie a -> Trie a
- filterMap :: (a -> Maybe b) -> Trie a -> Trie b
- mapBy :: (ByteString -> a -> Maybe b) -> Trie a -> Trie b
- filterA :: Applicative f => (a -> f Bool) -> Trie a -> f (Trie a)
- wither :: Applicative f => (a -> f (Maybe b)) -> Trie a -> f (Trie b)
- contextualMap :: (a -> Trie a -> b) -> Trie a -> Trie b
- contextualMap' :: (a -> Trie a -> b) -> Trie a -> Trie b
- contextualFilterMap :: (a -> Trie a -> Maybe b) -> Trie a -> Trie b
- contextualMapBy :: (ByteString -> a -> Trie a -> Maybe b) -> Trie a -> Trie b
- foldrWithKey :: (ByteString -> a -> b -> b) -> b -> Trie a -> b
- foldrWithKey' :: (ByteString -> a -> b -> b) -> b -> Trie a -> b
- foldlWithKey :: (b -> ByteString -> a -> b) -> b -> Trie a -> b
- foldlWithKey' :: (b -> ByteString -> a -> b) -> b -> Trie a -> b
- cata_ :: (ByteString -> Maybe a -> b -> b) -> (b -> b -> b) -> b -> Trie a -> b
- cata :: (ByteString -> a -> b -> b) -> (ByteString -> [b] -> b) -> b -> Trie a -> b
- traverseWithKey :: Applicative f => (ByteString -> a -> f b) -> Trie a -> f (Trie b)
- showTrie :: Show a => Trie a -> String
- breakMaximalPrefix :: ByteString -> ByteString -> (ByteString, ByteString, ByteString)
Data types
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 # | Since: 0.2.2 | 
| Functor Trie Source # | |
| Applicative Trie Source # | Since: 0.2.2 | 
| Foldable Trie Source # | |
| 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 # elem :: Eq a => a -> Trie a -> Bool # maximum :: Ord a => Trie a -> a # | |
| Traversable Trie Source # | |
| Eq1 Trie Source # | Since: 0.2.7 | 
| Ord1 Trie Source # | Warning: This instance suffers unnecessarily from Bug #25. Since: 0.2.7 | 
| Defined in Data.Trie.Internal | |
| Read1 Trie Source # | Since: 0.2.7 | 
| Defined in Data.Trie.Internal | |
| Show1 Trie Source # | Warning: This instance suffers Bug #25. Since: 0.2.7 | 
| IsList (Trie a) Source # | Warning: The  Since: 0.2.7 | 
| Eq a => Eq (Trie a) Source # | |
| Ord a => Ord (Trie a) Source # | Warning: This instance suffers unnecessarily from Bug #25. Since: 0.2.7 | 
| Read a => Read (Trie a) Source # | Since: 0.2.7 | 
| Show a => Show (Trie a) Source # | Warning: This instance suffers Bug #25. Since: 0.2.2 | 
| Semigroup a => Semigroup (Trie a) Source # | Since: 0.2.5 | 
| Monoid a => Monoid (Trie a) Source # | |
| Binary a => Binary (Trie a) Source # | |
| NFData a => NFData (Trie a) Source # | Since: 0.2.7 | 
| Defined in Data.Trie.Internal | |
| type Item (Trie a) Source # | |
| Defined in Data.Trie.Internal | |
Performance Warning
Many (but not all) functions which need to reconstruct bytestrings suffer from an asymptotic slowdown; see: Bug #25. For clarity, all functions affected by this bug will have a link to this section. This is not a new bug, it has affected all prior versions of this library as well. However, compared to older versions, bytestring-trie-0.2.7 mitigates the severity of the bug, and in certain cases to avoids it entirely.
In particular, this affects the "keyed" variants of functions
 (for folding, traversing, filtering, etc), and anything built
 from them, including toListBy and various instances which use
 it.
Conversely, functions which are unaffected include: those like
 alterBy which merely pass the query back to the user as a
 convenience; those which only need to reconstruct a single
 bytestring (e.g., the priority-queue functions); and
 matches/matches_.
Basic functions
singleton :: ByteString -> a -> Trie a Source #
\(\mathcal{O}(1)\). Construct a singleton trie.
List-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.
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.
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.
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
Arguments
| :: (a -> Trie a -> b) | The query matches a value. | 
| -> (Trie a -> b) | The query doesn't match, but an extension might. | 
| -> b | The query doesn't match, nor does any extension. | 
| -> ByteString | |
| -> Trie a | |
| -> b | 
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.
Note: Type changed in 0.2.7
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.
Since: 0.2.4
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.
Since: 0.2.4
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).
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
wip_unionWith :: (a -> a -> a) -> Trie a -> Trie a -> Trie a Source #
Take the union of two tries, using a function to resolve conflicts. The resulting trie is constructed strictly, but the results of the combining function are evaluated lazily.
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
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.
Note: Prior to version 0.2.7, this function suffered Bug #25; but it no longer does.
Since: 0.2.2
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.
Note: Prior to version 0.2.7, this function suffered Bug #25; but it no longer does.
Since: 0.2.2
updateMinViewBy :: (ByteString -> a -> Maybe a) -> Trie a -> Maybe (ByteString, a, Trie a) Source #
updateMaxViewBy :: (ByteString -> a -> Maybe a) -> Trie a -> Maybe (ByteString, a, Trie a) Source #
Mapping, filtering, folding, and traversing
Filterable
filter :: (a -> Bool) -> Trie a -> Trie a Source #
Retain only those values which satisfy some predicate.
Laws
- Definition
- filterf ≡- filterMap(\v -> v- <$- guard(f v))
- Composition
- filterf .- filterg ≡- filter(- liftA2(- &&) f g)
The definition above is a special case of the fusion law for
 filterMap.  (Also, the name just means definitional-equality;
 it's not the actual implementation used.)
Since: 0.2.7
filterMap :: (a -> Maybe b) -> Trie a -> Trie b Source #
Apply a function to all values, potentially removing them.
Laws
- Fission
- filterMapf ≡- fmap(- fromJust. f) .- filter(- isJust. f)
- Fusion
- fmapf .- filterg ≡- filterMap(\v -> f v- <$- guard(g v))
- Conservation
- filterMap(- Just. f) ≡- fmapf
- Composition
- filterMapf .- filterMapg ≡- 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.
Witherable
filterA :: Applicative f => (a -> f Bool) -> Trie a -> f (Trie a) Source #
An effectful version of filter.
Laws
- Definition
- filterAf ≡- wither(\v -> (v- <$) .- guard- <$>f v)
- Naturality
- filterA(t . f) ≡ t .- filterAf- t
- Purity
- filterA(- pure. f) ≡- pure.- filterf
- Horizontal Composition
- filterAf `under`- filterAg ≡- filterA(underA2 (- &&) f g)
-- Like 'liftA2' for the @(a->)@ monad, but horizontal.
-- The function definition should (hopefully) be straightforward
-- to follow; however, do beware the oddly criss-crossed types
-- for @g@ and @f@.
underA2 :: (Applicative f, Applicative g)
        => (b -> c -> d)
        -> (a -> g b)
        -> (a -> f c)
        -> a -> Compose f g d
underA2 h g f = liftA2 (liftA2 h) (g `under` pure) (pure `under` f)For the definition of under and more details about horizontal
 composition, see the laws section of wither.
Since: 0.2.7
wither :: Applicative f => (a -> f (Maybe b)) -> Trie a -> f (Trie b) Source #
An effectful version of filterMap.
Laws
- Naturality
- wither(t . f) ≡ t .- witherf- t
- Purity
- wither(- pure. f) ≡- pure.- filterMapf
- Conservation
- wither(- fmap- Just. f) ≡- traversef
- Horizontal Composition
- witherf `under`- witherg ≡- wither(wither_Maybe f `under` g)
under :: Functor f
      => (b -> g c)
      -> (a -> f b)
      -> a -> Compose f g c
under g f = Compose . fmap g . f
-- | Variant of wither for Maybe instead of Trie.
wither_Maybe :: Applicative f
             => (a -> f (Maybe b))
             -> Maybe a -> f (Maybe b)
wither_Maybe f = fmap join . traverse fNote that the horizontal composition law is using two different
 applicative functors.  Conversely, a vertical composition law
 would have the form: wither f <=< wither g ≡ ...
Although the horizontal composition law may look baroque, it is
 helpful to compare it to the composition law for traverse
 itself:
traversef `under`traverseg ≡traverse(f `under` g)
Since: 0.2.7
Contextual filtering/mapping functions
contextualMap :: (a -> Trie a -> b) -> Trie a -> Trie b Source #
A variant of fmap which provides access to the subtrie rooted
 at each value.
Since: 0.2.3
contextualMap' :: (a -> Trie a -> b) -> Trie a -> Trie b Source #
A variant of contextualMap which evaluates the function strictly.
Since: 0.2.3
contextualFilterMap :: (a -> Trie a -> Maybe b) -> Trie a -> Trie b Source #
Contextual variant of filterMap.
Since: 0.2.3
contextualMapBy :: (ByteString -> a -> Trie a -> Maybe b) -> Trie a -> Trie b Source #
Contextual variant of mapBy, aka keyed variant of contextualFilterMap.
Warning: This function suffers Bug #25.
Since: 0.2.3
Foldable
foldrWithKey :: (ByteString -> a -> b -> b) -> b -> Trie a -> b Source #
foldrWithKey' :: (ByteString -> a -> b -> b) -> b -> Trie a -> b Source #
foldlWithKey :: (b -> ByteString -> a -> b) -> b -> Trie a -> b Source #
foldlWithKey' :: (b -> ByteString -> a -> b) -> b -> Trie a -> b Source #
Arguments
| :: (ByteString -> Maybe a -> b -> b) | Algebra for arc. | 
| -> (b -> b -> b) | Algebra for binary branch. | 
| -> b | Algebra for empty trie. | 
| -> Trie a | |
| -> b | 
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
Arguments
| :: (ByteString -> a -> b -> b) | Algebra for accepting arcs. | 
| -> (ByteString -> [b] -> b) | Algebra for n-ary branch with prefix. | 
| -> b | Algebra for empty trie. | 
| -> Trie a | |
| -> b | 
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
Traverse
traverseWithKey :: Applicative f => (ByteString -> a -> f b) -> Trie a -> f (Trie b) Source #
Internal utility functions
breakMaximalPrefix :: ByteString -> ByteString -> (ByteString, ByteString, ByteString) Source #
Returns the longest shared prefix and the two remaining suffixes for a pair of strings. This function performs no allocation/copying, it simply returns slices/views of the arguments.
- s ≡ (\(pre,s',z') -> pre - <>s') (- breakMaximalPrefixs z)
- z ≡ (\(pre,s',z') -> pre - <>z') (- breakMaximalPrefixs z)
Since: 0.2.2