airship-0.9.1: A Webmachine-inspired HTTP library

Safe HaskellNone
LanguageHaskell2010

Airship.Route

Synopsis

Documentation

data Route Source #

Routes represent chunks of text used to match over URLs. You match hardcoded paths with string literals (and the -XOverloadedStrings extension), named variables with the var combinator, and wildcards with star.

data RoutingSpec m a Source #

Represents a fully-specified set of routes that map paths (represented as Routes) to Resources. RoutingSpecs are declared with do-notation, to wit:

   myRoutes :: RoutingSpec IO ()
   myRoutes = do
     root                                 #> myRootResource
     "blog" </> var "date" </> var "post" #> blogPostResource
     "about"                              #> aboutResource
     "anything" </> star                  #> wildcardResource

Instances

Monad (RoutingSpec m) Source # 

Methods

(>>=) :: RoutingSpec m a -> (a -> RoutingSpec m b) -> RoutingSpec m b #

(>>) :: RoutingSpec m a -> RoutingSpec m b -> RoutingSpec m b #

return :: a -> RoutingSpec m a #

fail :: String -> RoutingSpec m a #

Functor (RoutingSpec m) Source # 

Methods

fmap :: (a -> b) -> RoutingSpec m a -> RoutingSpec m b #

(<$) :: a -> RoutingSpec m b -> RoutingSpec m a #

Applicative (RoutingSpec m) Source # 

Methods

pure :: a -> RoutingSpec m a #

(<*>) :: RoutingSpec m (a -> b) -> RoutingSpec m a -> RoutingSpec m b #

(*>) :: RoutingSpec m a -> RoutingSpec m b -> RoutingSpec m b #

(<*) :: RoutingSpec m a -> RoutingSpec m b -> RoutingSpec m a #

MonadWriter [(ByteString, RouteLeaf m)] (RoutingSpec m) Source # 

Methods

writer :: (a, [(ByteString, RouteLeaf m)]) -> RoutingSpec m a #

tell :: [(ByteString, RouteLeaf m)] -> RoutingSpec m () #

listen :: RoutingSpec m a -> RoutingSpec m (a, [(ByteString, RouteLeaf m)]) #

pass :: RoutingSpec m (a, [(ByteString, RouteLeaf m)] -> [(ByteString, RouteLeaf m)]) -> RoutingSpec m a #

data Trie a :: * -> * #

A map from ByteStrings to a. For all the generic functions, note that tries are strict in the Maybe but not in a.

The Monad instance is strange. If a key k1 is a prefix of other keys, then results from binding the value at k1 will override values from longer keys when they collide. If this is useful for anything, or if there's a more sensible instance, I'd be curious to know.

Instances

Monad Trie 

Methods

(>>=) :: Trie a -> (a -> Trie b) -> Trie b #

(>>) :: Trie a -> Trie b -> Trie b #

return :: a -> Trie a #

fail :: String -> Trie a #

Functor Trie 

Methods

fmap :: (a -> b) -> Trie a -> Trie b #

(<$) :: a -> Trie b -> Trie a #

Applicative Trie 

Methods

pure :: a -> Trie a #

(<*>) :: Trie (a -> b) -> Trie a -> Trie b #

(*>) :: Trie a -> Trie b -> Trie b #

(<*) :: Trie a -> Trie b -> Trie a #

Foldable Trie 

Methods

fold :: Monoid m => Trie m -> m #

foldMap :: Monoid m => (a -> m) -> Trie a -> m #

foldr :: (a -> b -> b) -> b -> Trie a -> b #

foldr' :: (a -> b -> b) -> b -> Trie a -> b #

foldl :: (b -> a -> b) -> b -> Trie a -> b #

foldl' :: (b -> a -> b) -> b -> Trie a -> b #

foldr1 :: (a -> a -> a) -> Trie a -> a #

foldl1 :: (a -> a -> a) -> Trie a -> a #

toList :: Trie a -> [a] #

null :: Trie a -> Bool #

length :: Trie a -> Int #

elem :: Eq a => a -> Trie a -> Bool #

maximum :: Ord a => Trie a -> a #

minimum :: Ord a => Trie a -> a #

sum :: Num a => Trie a -> a #

product :: Num a => Trie a -> a #

Traversable Trie 

Methods

traverse :: Applicative f => (a -> f b) -> Trie a -> f (Trie b) #

sequenceA :: Applicative f => Trie (f a) -> f (Trie a) #

mapM :: Monad m => (a -> m b) -> Trie a -> m (Trie b) #

sequence :: Monad m => Trie (m a) -> m (Trie a) #

Eq a => Eq (Trie a) 

Methods

(==) :: Trie a -> Trie a -> Bool #

(/=) :: Trie a -> Trie a -> Bool #

Show a => Show (Trie a) 

Methods

showsPrec :: Int -> Trie a -> ShowS #

show :: Trie a -> String #

showList :: [Trie a] -> ShowS #

Monoid a => Monoid (Trie a) 

Methods

mempty :: Trie a #

mappend :: Trie a -> Trie a -> Trie a #

mconcat :: [Trie a] -> Trie a #

Binary a => Binary (Trie a) 

Methods

put :: Trie a -> Put #

get :: Get (Trie a) #

putList :: [Trie a] -> Put #

root :: Route Source #

Represents the root resource (/). This should usually be the first path declared in a RoutingSpec.

var :: Text -> Route Source #

Captures a named in a route and adds it to the routingParams hashmap under the provided Text value. For example,

   "blog" </> var "date" </> var "post"

will capture all URLs of the form /blog/$date/$post, and add date and post to the routingParams contained within the resource this route maps to.

star :: Route Source #

Captures a wildcard route. For example,

   "emcees" </> star

will match /emcees, /emcees/biggie, /emcees/earl/vince, and so on and so forth.

(</>) :: Route -> Route -> Route Source #

a </> b separates the path components a and b with a slash. This is actually just a synonym for mappend.

(#>=) :: MonadWriter [(ByteString, RouteLeaf a)] m => Route -> m (Resource a) -> m () Source #

runRouter :: RoutingSpec m a -> Trie (RouteLeaf m) Source #

Turns the list of routes in a RoutingSpec into a Trie for efficient routing