pred-trie-0.6.0.1: Predicative tries

Copyright(c) 2015 Athan Clark
LicenseBSD-3
Maintainerathan.clark@gmail.com
Stabilityexperimental
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

Data.Trie.Pred.Base

Contents

Description

A "predicative" trie is a lookup table where you can use predicates as a method to match a query path, where success is also enriched with any auxiliary data. This library allows you to match a path-chunk (if you consider a query to the different levels of the tree as a list) with a Boolean predicate, augmented with existentially quantified data. This lets us use parsers, regular expressions, and other functions that can be turned into the form of:

forall a. p -> Maybe a

However, because the communicated data is existentially quantified, we cannot revisit a definition - we cannot update a predicative node, or change any of its children. The current version of this library forces you to use PredTrie and RootedPredTrie directly (i.e. the data constructors) to build your trie manually.

This isn't the actual code, but it's a general idea for how you could build a trie. We build a "tagged" rose-tree, where each node has either a literal name (and is a singleton of the k type in our lookup path) or a predicate to consider the current node or its children as the target. You could imagine a "step" of the trie structure as something like this:

data PredTrie k a
  = Nil
  | Lit
      { litTag       :: k
      , litResult    :: Maybe a
      , litChildren  :: Maybe (PredTrie k a)
      }
  | forall t. Pred
      { predMatch    :: k -> Maybe t
      , predResult   :: Maybe (t -> a)
      , predChildren :: Maybe (PredTrie k a)
      }

Notice how in the Pred constructor, we first create the t data in predMatch, then consume it in predResult. We make a tree out of steps by recursing over the steps.

This isn't how it's actually represented internally, but serves to help see the representation. If you want to build tries and perform lookups casually, please see the Data.Trie.Pred.Interface module.

Synopsis

Predicated Trie

data PredTrie k a Source #

Constructors

PredTrie 

Fields

Instances

(Hashable k, Eq k) => Trie NonEmpty k PredTrie Source # 

Methods

lookup :: NonEmpty k -> PredTrie k a -> Maybe a #

insert :: NonEmpty k -> a -> PredTrie k a -> PredTrie k a #

delete :: NonEmpty k -> PredTrie k a -> PredTrie k a #

Functor (PredTrie k) Source # 

Methods

fmap :: (a -> b) -> PredTrie k a -> PredTrie k b #

(<$) :: a -> PredTrie k b -> PredTrie k a #

(Show a, Show k) => Show (PredTrie k a) Source # 

Methods

showsPrec :: Int -> PredTrie k a -> ShowS #

show :: PredTrie k a -> String #

showList :: [PredTrie k a] -> ShowS #

(Hashable k, Eq k) => Monoid (PredTrie k a) Source # 

Methods

mempty :: PredTrie k a #

mappend :: PredTrie k a -> PredTrie k a -> PredTrie k a #

mconcat :: [PredTrie k a] -> PredTrie k a #

(Arbitrary k, Arbitrary a, Eq k, Hashable k) => Arbitrary (PredTrie k a) Source # 

Methods

arbitrary :: Gen (PredTrie k a) #

shrink :: PredTrie k a -> [PredTrie k a] #

(NFData k, NFData a) => NFData (PredTrie k a) Source # 

Methods

rnf :: PredTrie k a -> () #

matchPT :: (Hashable k, Eq k) => NonEmpty k -> PredTrie k a -> Maybe (NonEmpty k, a, [k]) Source #

Find the nearest parent node of the requested query, while returning the split of the string that was matched, and what wasn't.

matchesPT :: (Hashable k, Eq k) => NonEmpty k -> PredTrie k a -> [(NonEmpty k, a, [k])] Source #

Rooted Predicative Trie

data RootedPredTrie k a Source #

Constructors

RootedPredTrie 

Fields

Instances

(Hashable k, Eq k) => Trie [] k RootedPredTrie Source # 

Methods

lookup :: [k] -> RootedPredTrie k a -> Maybe a #

insert :: [k] -> a -> RootedPredTrie k a -> RootedPredTrie k a #

delete :: [k] -> RootedPredTrie k a -> RootedPredTrie k a #

Functor (RootedPredTrie k) Source # 

Methods

fmap :: (a -> b) -> RootedPredTrie k a -> RootedPredTrie k b #

(<$) :: a -> RootedPredTrie k b -> RootedPredTrie k a #

(Show k, Show a) => Show (RootedPredTrie k a) Source # 
(Hashable k, Eq k) => Monoid (RootedPredTrie k a) Source # 
(NFData k, NFData a) => NFData (RootedPredTrie k a) Source # 

Methods

rnf :: RootedPredTrie k a -> () #

Singleton (PathChunks k ([] (Maybe *))) a (RootedPredTrie k a) Source # 

Methods

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

Methods

extend :: PathChunk k (Just * r) -> RootedPredTrie k (r -> a) -> RootedPredTrie k a Source #

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

Methods

writer :: (a, RootedPredTrie k v) -> PTBuilderT k v m a #

tell :: RootedPredTrie k v -> PTBuilderT k v m () #

listen :: PTBuilderT k v m a -> PTBuilderT k v m (a, RootedPredTrie k v) #

pass :: PTBuilderT k v m (a, RootedPredTrie k v -> RootedPredTrie k v) -> PTBuilderT k v m a #

Monad m => MonadState (RootedPredTrie k v) (PTBuilderT k v m) # 

Methods

get :: PTBuilderT k v m (RootedPredTrie k v) #

put :: RootedPredTrie k v -> PTBuilderT k v m () #

state :: (RootedPredTrie k v -> (a, RootedPredTrie k v)) -> PTBuilderT k v m a #

matchRPT :: (Hashable k, Eq k) => [k] -> RootedPredTrie k a -> Maybe ([k], a, [k]) Source #

matchesRPT :: (Hashable k, Eq k) => [k] -> RootedPredTrie k a -> [([k], a, [k])] Source #