| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Network.Wai.Routing.Route
Contents
- data Routes a m b
- type App m = RoutingReq -> Continue m -> m ResponseReceived
- type Continue m = Response -> m ResponseReceived
- data Meta a = Meta {- routeMethod :: !Method
- routePath :: !ByteString
- routeMeta :: a
 
- prepare :: Monad m => Routes a m b -> Tree (App m)
- route :: Monad m => Tree (App m) -> Request -> Continue m -> m ResponseReceived
- continue :: Monad m => (a -> m Response) -> a -> Continue m -> m ResponseReceived
- addRoute :: Monad m => Method -> ByteString -> (a -> Continue m -> m ResponseReceived) -> Predicate RoutingReq Error a -> Routes b m ()
- attach :: a -> Routes a m ()
- examine :: Routes a m b -> [Meta a]
- get :: Monad m => ByteString -> (a -> Continue m -> m ResponseReceived) -> Predicate RoutingReq Error a -> Routes b m ()
- head :: Monad m => ByteString -> (a -> Continue m -> m ResponseReceived) -> Predicate RoutingReq Error a -> Routes b m ()
- post :: Monad m => ByteString -> (a -> Continue m -> m ResponseReceived) -> Predicate RoutingReq Error a -> Routes b m ()
- put :: Monad m => ByteString -> (a -> Continue m -> m ResponseReceived) -> Predicate RoutingReq Error a -> Routes b m ()
- delete :: Monad m => ByteString -> (a -> Continue m -> m ResponseReceived) -> Predicate RoutingReq Error a -> Routes b m ()
- trace :: Monad m => ByteString -> (a -> Continue m -> m ResponseReceived) -> Predicate RoutingReq Error a -> Routes b m ()
- options :: Monad m => ByteString -> (a -> Continue m -> m ResponseReceived) -> Predicate RoutingReq Error a -> Routes b m ()
- connect :: Monad m => ByteString -> (a -> Continue m -> m ResponseReceived) -> Predicate RoutingReq Error a -> Routes b m ()
- patch :: Monad m => ByteString -> (a -> Continue m -> m ResponseReceived) -> Predicate RoutingReq Error a -> Routes b m ()
- type Renderer = Error -> Maybe (ByteString, ResponseHeaders)
- renderer :: Renderer -> Routes a m ()
- data Tree a :: * -> *
- toList :: Tree a -> [Payload a]
- foldTree :: (Payload a -> b -> b) -> b -> Tree a -> b
- mapTree :: (Payload a -> Payload b) -> Tree a -> Tree b
- data Payload a :: * -> *
- path :: Payload a -> ByteString
- value :: Payload a -> a
Documentation
type App m = RoutingReq -> Continue m -> m ResponseReceived Source
Similar to a WAI Application but for RoutingReq and not specific
 to IO.
type Continue m = Response -> m ResponseReceived Source
The WAI 3.0 application continuation for arbitrary m instead of IO.
Data added to a route via attach is returned in this Meta record.
Constructors
| Meta | |
| Fields 
 | |
prepare :: Monad m => Routes a m b -> Tree (App m) Source
Run the Routes monad and return the handlers per path.
route :: Monad m => Tree (App m) -> Request -> Continue m -> m ResponseReceived Source
Routes requests to handlers based on predicated route declarations.
 Note that route (prepare ...) behaves like a WAI Application generalised to
 arbitrary monads.
continue :: Monad m => (a -> m Response) -> a -> Continue m -> m ResponseReceived Source
Prior to WAI 3.0 applications returned a plain Response. continue
 turns such a function into a corresponding CPS version. For example:
sitemap :: Monad m => Routes a m ()
sitemap = do
    get "/f/:foo" (continue f) $ capture "foo"
    get "/g/:foo" g            $ capture "foo"
f :: Monad m => Int -> m Response
f x = ...
g :: Monad m => Int -> Continue m -> m ResponseReceived
g x k = k $ ...
Arguments
| :: Monad m | |
| => Method | |
| -> ByteString | path | 
| -> (a -> Continue m -> m ResponseReceived) | handler | 
| -> Predicate RoutingReq Error a | |
| -> Routes b m () | 
Add a route for some Method and path (potentially with variable
 captures) and constrained by some Predicate.
A route handler is like a WAI Application but instead of Request
 the first parameter is the result-type of the associated Predicate
 evaluation. I.e. the handler is applied to the predicate's metadata
 value iff the predicate is true.
Arguments
| :: Monad m | |
| => ByteString | path | 
| -> (a -> Continue m -> m ResponseReceived) | handler | 
| -> Predicate RoutingReq Error a | |
| -> Routes b m () | 
Arguments
| :: Monad m | |
| => ByteString | path | 
| -> (a -> Continue m -> m ResponseReceived) | handler | 
| -> Predicate RoutingReq Error a | |
| -> Routes b m () | 
Arguments
| :: Monad m | |
| => ByteString | path | 
| -> (a -> Continue m -> m ResponseReceived) | handler | 
| -> Predicate RoutingReq Error a | |
| -> Routes b m () | 
Arguments
| :: Monad m | |
| => ByteString | path | 
| -> (a -> Continue m -> m ResponseReceived) | handler | 
| -> Predicate RoutingReq Error a | |
| -> Routes b m () | 
Arguments
| :: Monad m | |
| => ByteString | path | 
| -> (a -> Continue m -> m ResponseReceived) | handler | 
| -> Predicate RoutingReq Error a | |
| -> Routes b m () | 
Arguments
| :: Monad m | |
| => ByteString | path | 
| -> (a -> Continue m -> m ResponseReceived) | handler | 
| -> Predicate RoutingReq Error a | |
| -> Routes b m () | 
Arguments
| :: Monad m | |
| => ByteString | path | 
| -> (a -> Continue m -> m ResponseReceived) | handler | 
| -> Predicate RoutingReq Error a | |
| -> Routes b m () | 
Arguments
| :: Monad m | |
| => ByteString | path | 
| -> (a -> Continue m -> m ResponseReceived) | handler | 
| -> Predicate RoutingReq Error a | |
| -> Routes b m () | 
Arguments
| :: Monad m | |
| => ByteString | path | 
| -> (a -> Continue m -> m ResponseReceived) | handler | 
| -> Predicate RoutingReq Error a | |
| -> Routes b m () | 
type Renderer = Error -> Maybe (ByteString, ResponseHeaders) Source
Function to turn an Error value into a ByteString
 to send as the response body and a list of additional response headers.
 Clients can provide their own renderer using renderer.
renderer :: Renderer -> Routes a m () Source
Set a custom render function, i.e. a function to turn Errors into
 ByteStrings.
Re-exports
data Payload a :: * -> *
path :: Payload a -> ByteString