Copyright | (c) 2015 Athan Clark |
---|---|
License | BSD-style |
Maintainer | athan.clark@gmail.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
This module defines a "builder" monad, which aides in the process of building a trie. It's a monad transformer, so you can use it alongside whichever context you're already working in.
myBuilder :: ( Eq k , Hashable k , MonadIO m ) => PTBuilder String Int m () myBuilder = do insertHere 0 insert ("some" ./ "path" ./ nil) 1 insert ("some" ./ pred "pred-chunk" upperPred ./ nil) 2 prefix ("some") $ do insert ("thing" ./ nil) 3 insert ("else" ./ nil) 4 data <- liftIO (doSomething) insert ("another" ./ "thing" ./ nil) data where uppderPred :: String -> Maybe String uppderPred s | all isUpperCase s = Just s | otherwise = Nothing
Then we can get our trie to perform lookups by executing the monad:
main :: IO () main = do trie <- execPTBuilderT myBuilder print (lookup ["foo", "bar", "baz"] trie)
- newtype PTBuilderT k v m a = PTBuilderT {
- runPTBuilderT :: StateT (RootedPredTrie k v) m a
- execPTBuilderT :: (Monad m, Eq k, Hashable k) => PTBuilderT k v m a -> m (RootedPredTrie k v)
- insert :: (Monad m, Eq k, Hashable k, Singleton (PathChunks k xs) childContent (RootedPredTrie k resultContent), cleanxs ~ CatMaybes xs, ArityTypeListIso childContent cleanxs resultContent) => PathChunks k xs -> childContent -> PTBuilderT k resultContent m ()
- insertHere :: (Monad m, Eq k, Hashable k) => v -> PTBuilderT k v m ()
- prefix :: (Monad m, Eq k, Hashable k, cleanxs ~ CatMaybes xs, ExtrudeSoundly k cleanxs xs childContent resultContent) => PathChunks k xs -> PTBuilderT k childContent m () -> PTBuilderT k resultContent m ()
- only :: k -> PathChunk k Nothing
- pred :: k -> (k -> Maybe r) -> PathChunk k (Just r)
- (./) :: PathChunk k mx -> PathChunks k xs -> PathChunks k (mx : xs)
- nil :: PathChunks k `[]`
- lookup :: (Eq k, Hashable k) => [k] -> RootedPredTrie k a -> Maybe a
- match :: (Hashable k, Eq k) => [k] -> RootedPredTrie k a -> Maybe ([k], a, [k])
- matches :: (Hashable k, Eq k) => [k] -> RootedPredTrie k a -> [([k], a, [k])]
- delete :: (Eq k, Hashable k) => [k] -> RootedPredTrie k a -> RootedPredTrie k a
- data RootedPredTrie k a
- data PathChunks k xs
- data PathChunk k mx
Construction
Builder Monad
newtype PTBuilderT k v m a Source
PTBuilderT | |
|
MonadTrans (PTBuilderT k v) Source | |
(Monad m, Eq k, Hashable k) => MonadWriter (RootedPredTrie k v) (PTBuilderT k v m) Source | |
Monad m => MonadState (RootedPredTrie k v) (PTBuilderT k v m) Source | |
Monad m => Monad (PTBuilderT k v m) Source | |
Functor m => Functor (PTBuilderT k v m) Source | |
Monad m => Applicative (PTBuilderT k v m) Source |
execPTBuilderT :: (Monad m, Eq k, Hashable k) => PTBuilderT k v m a -> m (RootedPredTrie k v) Source
Combinators
insert :: (Monad m, Eq k, Hashable k, Singleton (PathChunks k xs) childContent (RootedPredTrie k resultContent), cleanxs ~ CatMaybes xs, ArityTypeListIso childContent cleanxs resultContent) => PathChunks k xs -> childContent -> PTBuilderT k resultContent m () Source
insertHere :: (Monad m, Eq k, Hashable k) => v -> PTBuilderT k v m () Source
prefix :: (Monad m, Eq k, Hashable k, cleanxs ~ CatMaybes xs, ExtrudeSoundly k cleanxs xs childContent resultContent) => PathChunks k xs -> PTBuilderT k childContent m () -> PTBuilderT k resultContent m () Source
Specifying Paths
pred :: k -> (k -> Maybe r) -> PathChunk k (Just r) Source
Match with a predicate against the url chunk directly.
(./) :: PathChunk k mx -> PathChunks k xs -> PathChunks k (mx : xs) infixr 9 Source
The cons-cell for building a query path.
nil :: PathChunks k `[]` Source
The basis, equivalent to []
Query
lookup :: (Eq k, Hashable k) => [k] -> RootedPredTrie k a -> Maybe a Source
match :: (Hashable k, Eq k) => [k] -> RootedPredTrie k a -> Maybe ([k], a, [k]) Source
matches :: (Hashable k, Eq k) => [k] -> RootedPredTrie k a -> [([k], a, [k])] Source
Delete
delete :: (Eq k, Hashable k) => [k] -> RootedPredTrie k a -> RootedPredTrie k a Source
Types
data RootedPredTrie k a Source
(Hashable k, Eq k) => Trie [] k RootedPredTrie Source | |
Functor (RootedPredTrie k) Source | |
(Show k, Show a) => Show (RootedPredTrie k a) Source | |
(Hashable k, Eq k) => Monoid (RootedPredTrie k a) Source | |
Singleton (PathChunks k ([] (Maybe *))) a (RootedPredTrie k a) Source | |
Extrude (PathChunks k ([] (Maybe *))) (RootedPredTrie k a) (RootedPredTrie k a) Source | |
(Eq k, Hashable k, Typeable * r) => Extend (PathChunk k (Just * r)) (RootedPredTrie k (r -> a)) (RootedPredTrie k a) Source | Existentially quantified case |
(Eq k, Hashable k) => Extend (PathChunk k (Nothing *)) (RootedPredTrie k a) (RootedPredTrie k a) Source | Literal case |
(Monad m, Eq k, Hashable k) => MonadWriter (RootedPredTrie k v) (PTBuilderT k v m) | |
Monad m => MonadState (RootedPredTrie k v) (PTBuilderT k v m) |
data PathChunks k xs Source
Container when defining route paths
(Extrude (PathChunks k xs) trie0 trie1, Extend (PathChunk k x) trie1 trie2) => Extrude (PathChunks k ((:) (Maybe *) x xs)) trie0 trie2 Source | |
(Singleton (PathChunks k xs) new trie0, Extend (PathChunk k x) trie0 trie1) => Singleton (PathChunks k ((:) (Maybe *) x xs)) new trie1 Source | |
Singleton (PathChunks k ([] (Maybe *))) a (RootedPredTrie k a) Source | |
Extrude (PathChunks k ([] (Maybe *))) (RootedPredTrie k a) (RootedPredTrie k a) Source |
Constrained to AttoParsec, Regex-Compat and T.Text
IsString k => IsString (PathChunk k (Nothing *)) Source | Use raw strings instead of prepending |
(Eq k, Hashable k, Typeable * r) => Extend (PathChunk k (Just * r)) (RootedPredTrie k (r -> a)) (RootedPredTrie k a) Source | Existentially quantified case |
(Eq k, Hashable k) => Extend (PathChunk k (Nothing *)) (RootedPredTrie k a) (RootedPredTrie k a) Source | Literal case |