nested-routes-6.0.0: Declarative, compositional Wai responses

Safe HaskellNone
LanguageHaskell2010

Web.Routes.Nested.Types.UrlChunks

Contents

Synopsis

Path Combinators

o_ :: UrlChunks ([] (Maybe *)) Source

origin_ :: UrlChunks `[]` Source

The Origin chunk - the equivalent to []

literal_ :: Text -> EitherUrlChunk Nothing Source

Match against a Literal chunk

p_ :: (Text, Parser r) -> EitherUrlChunk (Just * r) Source

parse_ :: (Text, Parser r) -> EitherUrlChunk (Just r) Source

Match against a Parsed chunk, with attoparsec.

r_ :: (Text, Regex) -> EitherUrlChunk (Just * [String]) Source

regex_ :: (Text, Regex) -> EitherUrlChunk (Just [String]) Source

Match against a Regular expression chunk, with regex-compat.

pred_ :: (Text, Text -> Maybe r) -> EitherUrlChunk (Just r) Source

Match with a predicate against the url chunk directly.

(</>) :: EitherUrlChunk mx -> UrlChunks xs -> UrlChunks (mx : xs) infixr 9 Source

Prefix a routable path by more predicative lookup data.

Path Types

data EitherUrlChunk x where Source

Constrained to AttoParsec, Regex-Compat and T.Text

Constructors

(:=) :: Text -> EitherUrlChunk Nothing 
(:~) :: (Text, Text -> Maybe r) -> EitherUrlChunk (Just r) 

Instances

(~) (Maybe *) x (Nothing *) => IsString (EitherUrlChunk x) Source

Use raw strings instead of prepending l

Extend (EitherUrlChunk (Just * r)) (RootedPredTrie Text (r -> a)) (RootedPredTrie Text a) Source

Existentially quantified case

Extend (EitherUrlChunk (Nothing *)) (RootedPredTrie Text a) (RootedPredTrie Text a) Source

Literal case

data UrlChunks xs where Source

Container when defining route paths

Constructors

Cons :: EitherUrlChunk mx -> UrlChunks xs -> UrlChunks (mx : xs) 
Root :: UrlChunks `[]` 

Instances

(Extrude (UrlChunks xs) trie0 trie1, Extend (EitherUrlChunk x) trie1 trie2) => Extrude (UrlChunks ((:) (Maybe *) x xs)) trie0 trie2 Source 
(Singleton (UrlChunks xs) a trie0, Extend (EitherUrlChunk x) trie0 trie1) => Singleton (UrlChunks ((:) (Maybe *) x xs)) a trie1 Source 
Singleton (UrlChunks ([] (Maybe *))) a (RootedPredTrie Text a) Source 
Extrude (UrlChunks ([] (Maybe *))) (RootedPredTrie Text a) (RootedPredTrie Text a) Source