pred-trie-0.6.0.1: Predicative tries

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

Data.Trie.Pred.Interface.Types

Contents

Description

 

Synopsis

Heterogenous Construction

class Singleton chunks a trie | chunks a -> trie where Source #

Creates a string of nodes - a trie with a width of 1.

Minimal complete definition

singleton

Methods

singleton :: chunks -> a -> trie Source #

Instances

(Singleton (PathChunks k xs) new trie0, Extend (PathChunk k x) trie0 trie1) => Singleton (PathChunks k ((:) (Maybe *) x xs)) new trie1 Source # 

Methods

singleton :: PathChunks k ((Maybe * ': x) xs) -> new -> trie1 Source #

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

Methods

singleton :: PathChunks k [Maybe *] -> a -> RootedPredTrie k a Source #

class Extend eitherUrlChunk child result | eitherUrlChunk child -> result where Source #

Turn a list of tries (Rooted) into a node with those children

Minimal complete definition

extend

Methods

extend :: eitherUrlChunk -> child -> result Source #

Instances

(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

class Extrude chunks start result | chunks start -> result where Source #

FoldR Extend start chunks ~ result

Minimal complete definition

extrude

Methods

extrude :: chunks -> start -> result Source #

Instances

(Extrude (PathChunks k xs) trie0 trie1, Extend (PathChunk k x) trie1 trie2) => Extrude (PathChunks k ((:) (Maybe *) x xs)) trie0 trie2 Source # 

Methods

extrude :: PathChunks k ((Maybe * ': x) xs) -> trie0 -> trie2 Source #

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

type ExtrudeSoundly k cleanxs xs c r = (cleanxs ~ CatMaybes xs, ArityTypeListIso c cleanxs r, Extrude (PathChunks k xs) (RootedPredTrie k c) (RootedPredTrie k r)) Source #

A simple proof showing that the list version and function version are interchangable.

type family CatMaybes (xs :: [Maybe *]) :: [*] where ... Source #

Convenience type-level function for removing Nothings from a type list.

Equations

CatMaybes '[] = '[] 
CatMaybes (Nothing ': xs) = CatMaybes xs 
CatMaybes (Just x ': xs) = x ': CatMaybes xs 

Path Construction

only :: k -> PathChunk k Nothing Source #

Match a literal key

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 []

Path Types

data PathChunk k (mx :: Maybe *) Source #

Constrained to AttoParsec, Regex-Compat and T.Text

Instances

IsString k => IsString (PathChunk k (Nothing *)) Source #

Use raw strings instead of prepending l

(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

data PathChunks k (xs :: [Maybe *]) Source #

Container when defining route paths

Instances

(Extrude (PathChunks k xs) trie0 trie1, Extend (PathChunk k x) trie1 trie2) => Extrude (PathChunks k ((:) (Maybe *) x xs)) trie0 trie2 Source # 

Methods

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 # 

Methods

singleton :: PathChunks k ((Maybe * ': x) xs) -> new -> trie1 Source #

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 #