wai-routing-0.13.0: Declarative routing for WAI.

Safe HaskellNone
LanguageHaskell2010

Network.Wai.Routing.Route

Contents

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

Monad (Routes a m) Source # 

Methods

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

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

return :: a -> Routes a m a #

fail :: String -> Routes a m a #

Functor (Routes a m) Source # 

Methods

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

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

Applicative (Routes a m) Source # 

Methods

pure :: a -> Routes a m a #

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

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

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

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

addRoute Source #

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.

get Source #

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.

head Source #

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.

post Source #

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.

put Source #

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.

delete Source #

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.

trace Source #

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.

options Source #

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.

connect Source #

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.

patch Source #

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 (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 Tree a :: * -> * #

Instances

Monoid (Tree a) 

Methods

mempty :: Tree a #

mappend :: Tree a -> Tree a -> Tree a #

mconcat :: [Tree a] -> 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 :: * -> * #

value :: Payload a -> a #