| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Data.RadixTree
Synopsis
- data RadixTree a
- data RadixNode a = RadixNode !Text !(RadixTree a)
- data CompressedRadixTree a
- fromFoldable_ :: Foldable f => f Text -> RadixTree ()
- fromFoldable :: Foldable f => f (Text, a) -> RadixTree a
- compressBy :: Text -> RadixTree a -> Maybe (CompressedRadixTree a)
- class RadixParsing radixtree where
- parse_ :: (RadixParsing r, CharParsing m) => r a -> m Text
- lookup_ :: RadixParsing r => r a -> Text -> Maybe Text
- search :: (Monad m, CharParsing m, RadixParsing radixtree) => radixtree a -> m [Text]
Documentation
A radixtree. Construct with 'fromFoldable_, and use with parse.
Constructors
| RadixAccept | Can terminate a parser successfully, returning the  | 
| RadixSkip !(Vector (RadixNode a)) | possible subtrees beyond this point | 
Instances
| RadixParsing RadixTree Source # | |
| Eq a => Eq (RadixTree a) Source # | |
| Data a => Data (RadixTree a) Source # | |
| Defined in Data.RadixTree Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RadixTree a -> c (RadixTree a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RadixTree a) # toConstr :: RadixTree a -> Constr # dataTypeOf :: RadixTree a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RadixTree a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RadixTree a)) # gmapT :: (forall b. Data b => b -> b) -> RadixTree a -> RadixTree a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RadixTree a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RadixTree a -> r # gmapQ :: (forall d. Data d => d -> u) -> RadixTree a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RadixTree a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RadixTree a -> m (RadixTree a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RadixTree a -> m (RadixTree a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RadixTree a -> m (RadixTree a) # | |
| Show a => Show (RadixTree a) Source # | |
| NFData a => NFData (RadixTree a) Source # | |
| Defined in Data.RadixTree | |
A node in a radixtree. To advance from here a parser must parse the Text
 (i.e., the prefix) value at this node.
Instances
| Eq a => Eq (RadixNode a) Source # | |
| Data a => Data (RadixNode a) Source # | |
| Defined in Data.RadixTree Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RadixNode a -> c (RadixNode a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RadixNode a) # toConstr :: RadixNode a -> Constr # dataTypeOf :: RadixNode a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RadixNode a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RadixNode a)) # gmapT :: (forall b. Data b => b -> b) -> RadixNode a -> RadixNode a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RadixNode a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RadixNode a -> r # gmapQ :: (forall d. Data d => d -> u) -> RadixNode a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RadixNode a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RadixNode a -> m (RadixNode a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RadixNode a -> m (RadixNode a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RadixNode a -> m (RadixNode a) # | |
| Show a => Show (RadixNode a) Source # | |
| NFData a => NFData (RadixNode a) Source # | |
| Defined in Data.RadixTree | |
data CompressedRadixTree a Source #
A normal RadixTree stores a new Text at every node. In contrast, a
 CompressedRadixTree takes a single corpus Text which is indexed into by
 nodes. This can save a lot of memory (e.g., using the radix trees from the
 parsing benchmarks in this package, the CompressedRadixTree version is
 254032 bytes, whereas the ordinary RadixTree is a rotund 709904 bytes) at
 no runtime cost.
Instances
| RadixParsing CompressedRadixTree Source # | |
| Defined in Data.RadixTree Methods keys :: CompressedRadixTree a -> [(Text, a)] Source # parse :: CharParsing m => (Text -> a -> r) -> CompressedRadixTree a -> m r Source # lookup :: CompressedRadixTree a -> Text -> Maybe (Text, a) Source # | |
| NFData a => NFData (CompressedRadixTree a) Source # | |
| Defined in Data.RadixTree Methods rnf :: CompressedRadixTree a -> () # | |
Construction
fromFoldable_ :: Foldable f => f Text -> RadixTree () Source #
- Slow*. Same as fromFoldable, but you do not need to supply pairs of text and values; they will default to().
compressBy :: Text -> RadixTree a -> Maybe (CompressedRadixTree a) Source #
Compress a RadixTree given a corpus. All values in the tree must be
 findable within the corpus, though the corpus does not have to necessarily be
 the direct source of the tree
Parsing with radix trees
class RadixParsing radixtree where Source #
Methods
keys :: radixtree a -> [(Text, a)] Source #
parse :: CharParsing m => (Text -> a -> r) -> radixtree a -> m r Source #
Instances
| RadixParsing CompressedRadixTree Source # | |
| Defined in Data.RadixTree Methods keys :: CompressedRadixTree a -> [(Text, a)] Source # parse :: CharParsing m => (Text -> a -> r) -> CompressedRadixTree a -> m r Source # lookup :: CompressedRadixTree a -> Text -> Maybe (Text, a) Source # | |
| RadixParsing RadixTree Source # | |
parse_ :: (RadixParsing r, CharParsing m) => r a -> m Text Source #
search :: (Monad m, CharParsing m, RadixParsing radixtree) => radixtree a -> m [Text] Source #
Find all occurences of the terms in a RadixTree from this point on. This
 will consume the entire remaining input. Can lazily produce results (but this
 depends on your parser).