wai-routes-0.10.3: Typesafe URLs for Wai applications.

Copyright(c) Anupam Jain 2013
LicenseMIT (see the file LICENSE)
Maintainerajnsit@gmail.com
Stabilityexperimental
Portabilitynon-portable (uses ghc extensions)
Safe HaskellNone
LanguageHaskell2010

Wai.Routes

Contents

Description

This package provides typesafe URLs for Wai applications.

Synopsis

Declaring Routes using Template Haskell

parseRoutes :: QuasiQuoter Source #

A quasi-quoter to parse a string into a list of Resources. Checks for overlapping routes, failing if present; use parseRoutesNoCheck to skip the checking. See documentation site for details on syntax.

Parse routes declared in a file

parseRoutesNoCheck :: QuasiQuoter Source #

Same as parseRoutes, but performs no overlap checking.

Same as parseRoutesFile, but performs no overlap checking.

mkRoute :: String -> [ResourceTree String] -> Q [Dec] Source #

Generates all the things needed for efficient routing. Including your application's Route datatype, RenderRoute, ParseRoute, RouteAttrs, and Routable instances. Use this for everything except subsites

mkRouteSub :: String -> String -> [ResourceTree String] -> Q [Dec] Source #

Same as mkRoute, but for subsites

Dispatch

routeDispatch :: Routable master master => master -> Middleware Source #

Generates the application middleware from a Routable master datatype

URL rendering and parsing

showRoute :: RenderRoute master => Route master -> Text Source #

Renders a Route as Text

showRouteQuery :: RenderRoute master => Route master -> [(Text, Text)] -> Text Source #

Render a Route and Query parameters to Text

readRoute :: ParseRoute master => Text -> Maybe (Route master) Source #

Read a route from Text Returns Nothing if Route reading failed. Just route otherwise

showRouteMaster :: RenderRoute master => HandlerM sub master (Route master -> Text) Source #

Get the route rendering function for the master site

showRouteQueryMaster :: RenderRoute master => HandlerM sub master (Route master -> [(Text, Text)] -> Text) Source #

Get the route rendering function for the master site

readRouteMaster :: ParseRoute master => HandlerM sub master (Text -> Maybe (Route master)) Source #

Get the route parsing function for the master site

showRouteSub :: RenderRoute master => HandlerM sub master (Route sub -> Text) Source #

Get the route rendering function for the subsite

showRouteQuerySub :: RenderRoute master => HandlerM sub master (Route sub -> [(Text, Text)] -> Text) Source #

Get the route rendering function for the subsite

readRouteSub :: ParseRoute sub => HandlerM sub master (Text -> Maybe (Route master)) Source #

Get the route parsing function for the subsite

Application Handlers

type Handler sub = forall master. RenderRoute master => HandlerS sub master Source #

A Handler generates an App from the master datatype

type HandlerS sub master = Env sub master -> App sub Source #

Generated Datatypes

class Routable sub master where Source #

A Routable instance can be used in dispatching. An appropriate instance for your site datatype is automatically generated by mkRoute.

Minimal complete definition

dispatcher

Methods

dispatcher :: HandlerS sub master Source #

Used internally. However needs to be exported for TH to work.

class Eq (Route a) => RenderRoute a where Source #

Minimal complete definition

renderRoute

Associated Types

data Route a Source #

The type-safe URLs associated with a site argument.

Methods

renderRoute Source #

Arguments

:: Route a 
-> ([Text], [(Text, Text)])

The path of the URL split on forward slashes, and a list of query parameters with their associated value.

Instances
RenderRoute DefaultMaster Source # 
Instance details

Defined in Routes.DefaultRoute

Associated Types

data Route DefaultMaster :: * Source #

A RenderRoute instance for your site datatype is automatically generated by mkRoute

class RenderRoute a => ParseRoute a where Source #

Minimal complete definition

parseRoute

Methods

parseRoute Source #

Arguments

:: ([Text], [(Text, Text)])

The path of the URL split on forward slashes, and a list of query parameters with their associated value.

-> Maybe (Route a) 
Instances
ParseRoute DefaultMaster Source # 
Instance details

Defined in Routes.DefaultRoute

A ParseRoute instance for your site datatype is automatically generated by mkRoute

class RenderRoute a => RouteAttrs a where Source #

Minimal complete definition

routeAttrs

Instances
RouteAttrs DefaultMaster Source # 
Instance details

Defined in Routes.DefaultRoute

A RouteAttrs instance for your site datatype is automatically generated by mkRoute

Accessing Raw Request Data

data RequestData master Source #

An abstract representation of the request data. You can get the wai request object by using waiReq

Extract the wai Request object from RequestData

Extract the next Application in the stack

runNext :: App master Source #

Run the next application in the stack

Run the next application in the stack

Route Monad makes it easy to compose routes together

type RouteM = F RouterF Source #

data DefaultMaster Source #

Constructors

DefaultMaster 
Instances
Eq DefaultMaster Source # 
Instance details

Defined in Routes.DefaultRoute

Ord DefaultMaster Source # 
Instance details

Defined in Routes.DefaultRoute

Show DefaultMaster Source # 
Instance details

Defined in Routes.DefaultRoute

RouteAttrs DefaultMaster Source # 
Instance details

Defined in Routes.DefaultRoute

ParseRoute DefaultMaster Source # 
Instance details

Defined in Routes.DefaultRoute

RenderRoute DefaultMaster Source # 
Instance details

Defined in Routes.DefaultRoute

Associated Types

data Route DefaultMaster :: * Source #

Eq (Route DefaultMaster) Source # 
Instance details

Defined in Routes.DefaultRoute

Ord (Route DefaultMaster) Source # 
Instance details

Defined in Routes.DefaultRoute

Show (Route DefaultMaster) Source # 
Instance details

Defined in Routes.DefaultRoute

data Route DefaultMaster Source # 
Instance details

Defined in Routes.DefaultRoute

handler :: HandlerS DefaultMaster DefaultMaster -> RouteM () Source #

Add a wai-routes handler

Add a wai-routes handler

catchall :: Application -> RouteM () Source #

Catch all routes and process them with the supplied application. Note: As expected from the name, no request proceeds past a catchall.

Catch all routes with the supplied application

defaultAction :: Application -> RouteM () Source #

Synonym of catchall. Kept for backwards compatibility

A synonym for catchall, kept for backwards compatibility

middleware :: Middleware -> RouteM () Source #

Add a middleware to the application Middleware are ordered so the one declared earlier wraps the ones later

Add another middleware to the app

route :: Routable master master => master -> RouteM () Source #

Add a route to the application. Routes are ordered so the one declared earlier is matched first.

Add another routed middleware to the app

waiApp :: RouteM () -> Application Source #

Convert a RouteM monad into a wai application. Note: We ignore the return type of the monad

Convert a RouteM to a wai Application

toWaiApp :: Monad m => RouteM () -> m Application Source #

Similar to waiApp but returns the app in an arbitrary monad Kept for backwards compatibility

Similar to waiApp, but result is wrapped in a monad. Kept for backwards compatibility

HandlerM Monad makes it easy to build a handler

type HandlerM sub master a = HandlerMI sub master IO a Source #

The HandlerM Monad

runHandlerM :: HandlerM sub master () -> HandlerS sub master Source #

Run HandlerM, resulting in a Handler

Run a HandlerM to get a Handler

mountedAppHandler :: Application -> HandlerS sub master Source #

Convert a full wai application to a Handler A bit like subsites, but at a higher level.

Convert a full wai application to a HandlerS

request :: HandlerM sub master Request Source #

Get the request

Access the request data

isWebsocket :: HandlerM sub master Bool Source #

Is this a websocket request

Is this a websocket request

reqHeader :: Text -> HandlerM sub master (Maybe Text) Source #

Get a particular request header (Case insensitive)

Get a particular request header (case insensitive)

reqHeaders :: HandlerM sub master RequestHeaders Source #

Get all request headers as raw case-insensitive bytestrings

Get all request headers (case insensitive)

maybeRootRoute :: HandlerM sub master (Maybe (Route master)) Source #

Get the current root route

Access the current route for root route

maybeRoute :: HandlerM sub master (Maybe (Route sub)) Source #

Get the current route

Access the current route

routeAttrSet :: RouteAttrs sub => HandlerM sub master (Set Text) Source #

Get the current route attributes

Access the current route attributes as a set

rootRouteAttrSet :: RouteAttrs master => HandlerM sub master (Set Text) Source #

Get the attributes for the current root route

Access the current root route attributes as a set

master :: HandlerM sub master master Source #

Get the master

Access the master datatype

sub :: HandlerM sub master sub Source #

Get the sub

Access the sub datatype

rawBody :: HandlerM sub master ByteString Source #

Get the request body as a bytestring. Consumes the entire body into memory at once. TODO: Implement streaming. Prevent clash with direct use of requestBody

Consume and return the request body as ByteString

textBody :: HandlerM master master Text Source #

Get the request body as a Text. However consumes the entire body at once. TODO: Implement streaming. Prevent clash with direct use of requestBody

Consume and return the request body as Text

jsonBody :: FromJSON a => HandlerM sub master (Either String a) Source #

Parse the body as a JSON object

Consume and return the request body as JSON

header :: HeaderName -> ByteString -> HandlerM sub master () Source #

Add a header to the application response TODO: Differentiate between setting and adding headers

Add a header to the response

status :: Status -> HandlerM sub master () Source #

Set the response status

Set the response status

file :: FilePath -> HandlerM sub master () Source #

Send a file as response

Send a file as response

filepart :: FilePath -> FilePart -> HandlerM sub master () Source #

Send a part of a file as response

Send a part of a file as response

stream :: StreamingBody -> HandlerM sub master () Source #

Stream the response

Stream a response

raw :: ByteString -> HandlerM sub master () Source #

Set the response body

Set the raw response body

rawBuilder :: Builder -> HandlerM sub master () Source #

Set the response body as a builder

Set the raw response body as a ByteString Builder

json :: ToJSON a => a -> HandlerM sub master () Source #

Set the body of the response to the JSON encoding of the given value. Also sets "Content-Type" header to "application/json".

Set the json response body

plain :: Text -> HandlerM sub master () Source #

Set the body of the response to the given Text value. Also sets "Content-Type" header to "text/plain".

Set the plain text response body

html :: Text -> HandlerM sub master () Source #

Set the body of the response to the given Text value. Also sets "Content-Type" header to "text/html".

Set the html response body

css :: Text -> HandlerM sub master () Source #

Set the body of the response to the given Text value. Also sets "Content-Type" header to "text/css".

Set the css response body

javascript :: Text -> HandlerM sub master () Source #

Set the body of the response to the given Text value. Also sets "Content-Type" header to "text/javascript".

Set the javascript response body

asContent :: ByteString -> Text -> HandlerM sub master () Source #

Sets the content-type header to the given Bytestring (look in Routes.ContentTypes for examples) And sets the body of the response to the given Text

Set the contentType and a Text body

next :: HandlerM sub master () Source #

Run the next application

Run the next application in the stack

getParams :: HandlerM sub master [(Text, Text)] Source #

Get all params (query or post, NOT file) Duplicate parameters are preserved

Get all params (query or post, not file)

getParam :: Text -> HandlerM sub master (Maybe Text) Source #

Get a param (query or post, NOT file)

Get a particular param (query or post, not file)

getQueryParams :: HandlerM sub master [(Text, Text)] Source #

Get all Query params

Get all query params

getQueryParam :: Text -> HandlerM sub master (Maybe Text) Source #

Get a particular Query param

Get a particular query param

getPostParams :: HandlerM sub master [(Text, Text)] Source #

Get all Post params

Get all post params

getPostParam :: Text -> HandlerM sub master (Maybe Text) Source #

Get a particular Post param

Get a particular post param

getFileParams :: HandlerM sub master [(Text, FileInfo)] Source #

Get all File params

Get all file params

getFileParam :: Text -> HandlerM sub master (Maybe FileInfo) Source #

Get a particular File param

Get a particular file param

setCookie :: SetCookie -> HandlerM sub master () Source #

Sets a cookie to the response

Add a cookie to the response

getCookie :: Text -> HandlerM sub master (Maybe Text) Source #

Get a particular cookie

Get a cookie from the request

getCookies :: HandlerM sub master CookiesText Source #

Get all cookies

Get all cookies from the request

reqVault :: HandlerM sub master Vault Source #

Access the vault

Access the vault from the request

lookupVault :: Key a -> HandlerM sub master (Maybe a) Source #

Lookup a key in the request vault

updateVault :: (Vault -> Vault) -> HandlerM sub master () Source #

Update the request vault

Bare Handlers

data Env sub master Source #

Constructors

Env 

Fields

currentRoute :: RequestData master -> Maybe (Route master) Source #

Extract the current Route from RequestData