wai-routing-0.9: Declarative routing for WAI.

Safe HaskellNone

Network.Wai.Routing.Route

Synopsis

Documentation

data Routes a m b Source

The Routes monad is used to add routing declarations via addRoute or one of get, post, etc.

Instances

type App m = RoutingReq -> Continue m -> m ResponseReceivedSource

Similar to a WAI Application but for RoutingReq and not specific to IO.

type Continue m = Response -> m ResponseReceivedSource

The WAI 3.0 application continuation for arbitrary m instead of IO.

data Meta a Source

Data added to a route via attach is returned in this Meta record.

Constructors

Meta 

prepare :: Monad m => Routes a m b -> [(ByteString, App m)]Source

Run the Routes monad and return the handlers per path.

route :: Monad m => [(ByteString, App m)] -> Request -> Continue m -> m ResponseReceivedSource

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 ResponseReceivedSource

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 $ ...

addRouteSource

Arguments

:: Monad m 
=> Method 
-> ByteString

path

-> (a -> Continue m -> m ResponseReceived)

handler

-> Predicate RoutingReq Error a

Predicate

-> 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.

attach :: a -> Routes a m ()Source

Add some metadata to the last route.

examine :: Routes a m b -> [Meta a]Source

Get back all attached metadata.

getSource

Arguments

:: Monad m 
=> ByteString

path

-> (a -> Continue m -> m ResponseReceived)

handler

-> Predicate RoutingReq Error a

Predicate

-> Routes b m () 

Specialisation of addRoute for a specific HTTP Method.

headSource

Arguments

:: Monad m 
=> ByteString

path

-> (a -> Continue m -> m ResponseReceived)

handler

-> Predicate RoutingReq Error a

Predicate

-> Routes b m () 

Specialisation of addRoute for a specific HTTP Method.

postSource

Arguments

:: Monad m 
=> ByteString

path

-> (a -> Continue m -> m ResponseReceived)

handler

-> Predicate RoutingReq Error a

Predicate

-> Routes b m () 

Specialisation of addRoute for a specific HTTP Method.

putSource

Arguments

:: Monad m 
=> ByteString

path

-> (a -> Continue m -> m ResponseReceived)

handler

-> Predicate RoutingReq Error a

Predicate

-> Routes b m () 

Specialisation of addRoute for a specific HTTP Method.

deleteSource

Arguments

:: Monad m 
=> ByteString

path

-> (a -> Continue m -> m ResponseReceived)

handler

-> Predicate RoutingReq Error a

Predicate

-> Routes b m () 

Specialisation of addRoute for a specific HTTP Method.

traceSource

Arguments

:: Monad m 
=> ByteString

path

-> (a -> Continue m -> m ResponseReceived)

handler

-> Predicate RoutingReq Error a

Predicate

-> Routes b m () 

Specialisation of addRoute for a specific HTTP Method.

optionsSource

Arguments

:: Monad m 
=> ByteString

path

-> (a -> Continue m -> m ResponseReceived)

handler

-> Predicate RoutingReq Error a

Predicate

-> Routes b m () 

Specialisation of addRoute for a specific HTTP Method.

connectSource

Arguments

:: Monad m 
=> ByteString

path

-> (a -> Continue m -> m ResponseReceived)

handler

-> Predicate RoutingReq Error a

Predicate

-> Routes b m () 

Specialisation of addRoute for a specific HTTP Method.

patchSource

Arguments

:: Monad m 
=> ByteString

path

-> (a -> Continue m -> m ResponseReceived)

handler

-> Predicate RoutingReq Error a

Predicate

-> Routes b m () 

Specialisation of addRoute for a specific HTTP Method.

type Renderer = Error -> Maybe ByteStringSource

Function to turn an Error value into a ByteString. 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.