hails-0.11.1.3: Multi-app web platform framework

Safe HaskellTrustworthy
LanguageHaskell98

Hails.Web.Router

Contents

Description

Conceptually, a route is function that, given an HTTP request, may return an action (something that would return a response for the client if run). Routes can be concatenated--where each route is evaluated until one matches--and nested. Routes are expressed through the Routeable type class. runRoute transforms an instance of Routeable to a function from Request to a monadic action (in the ResourceT monad) that returns a Maybe Response. The return type was chosen to be monadic so routing decisions can depend on side-effects (e.g. a random number or counter for A/B testing, IP geolocation lookup etc').

Synopsis

Example

The most basic Routeable types are Application and Response. Reaching either of these types marks a termination in the routing lookup. This module exposes a monadic type Route which makes it easy to create routing logic in a DSL-like fashion.

Routes are concatenated using the >> operator (or using do-notation). In the end, any Routeable, including a Route is converted to an Application and passed to the server using mkRouter:

  mainAction :: Application
  mainAction req = ...

  signinForm :: Application
  signinForm req = ...

  login :: Application
  login req = ...

  updateProfile :: Application
  updateProfile req = ...

  main :: IO ()
  main = runSettings defaultSettings $ mkRouter $ do
    routeTop mainAction
    routeName "sessions" $ do
      routeMethod GET signinForm
      routeMethod POST login
    routeMethod PUT $ routePattern "users/:id" updateProfile
    routeAll $ responseLBS status404 [] "Are you in the right place?"

class Routeable r where Source

Routeable types can be converted into a route function using runRoute. If the route is matched it returns a Response, otherwise Nothing.

In general, Routeables are data-dependant (on the Request), but don't have to be. For example, Application is an instance of Routeable that always returns a Response:

  instance Routeable Application where
    runRoute app req = app req >>= return . Just

Methods

runRoute :: r -> RouteHandler Source

Run a route

mkRouter :: Routeable r => r -> Application Source

Converts any Routeable into an Application that can be passed directly to a WAI server.

Route Monad

type Route = RouteM () Source

Synonym for RouteM, the common case where the data parameter is '()'.

data RouteM a Source

The RouteM type is a basic instance of Routeable that simply holds the routing function and an arbitrary additional data parameter. In most cases this paramter is simply '()', hence we have a synonym for RouteM '()' called Route. The power is derived from the instances of Monad and Monoid, which allow the simple construction of complex routing rules using either lists (Monoid) or do-notation. Moreover, because of it's simple type, any Routeable can be used as a Route (using routeAll or by applying it to runRoute), making it possible to leverage the monadic or monoid syntax for any Routeable.

Commonly, route functions that construct a Route only inspect the Request and other parameters. For example, routeHost looks at the hostname:

  routeHost :: Routeable r => S.ByteString -> r -> Route
  routeHost host route = Route func ()
    where func req = if host == serverName req
                       then runRoute route req
                       else return Nothing

However, because the result of a route is in the ResourceT monad, routes have all the power of an Application and can make state-dependant decisions. For example, it is trivial to implement a route that succeeds for every other request (perhaps for A/B testing):

  routeEveryOther :: (Routeable r1, Routeable r2)
                  => MVar Int -> r1 -> r2 -> Route
  routeEveryOther counter r1 r2 = Route func ()
    where func req = do
            i liftIO . modifyMVar $ i -
                    let i' = i+1
                    in return (i', i')
            if i mod 2 == 0
              then runRoute r1 req
              else runRoute r2 req

Constructors

Route RouteHandler a 

Common Routes

routeAll :: Routeable r => r -> Route Source

A route that always matches (useful for converting a Routeable into a Route).

routeHost :: Routeable r => ByteString -> r -> Route Source

Matches on the hostname from the Request. The route only successeds on exact matches.

routeTop :: Routeable r => r -> Route Source

Matches if the path is empty. Note that this route checks that pathInfo is empty, so it works as expected when nested under namespaces or other routes that pop the pathInfo list.

routeMethod :: Routeable r => StdMethod -> r -> Route Source

Matches on the HTTP request method (e.g. GET, POST, PUT)

routePattern :: Routeable r => ByteString -> r -> Route Source

Routes the given URL pattern. Patterns can include directories as well as variable patterns (prefixed with :) to be added to queryString (see routeVar)

  • /posts/:id
  • /posts/:id/new
  • /:date/posts/:category/new

routeName :: Routeable r => ByteString -> r -> Route Source

Matches if the first directory in the path matches the given ByteString

routeVar :: Routeable r => ByteString -> r -> Route Source

Always matches if there is at least one directory in pathInfo but and adds a parameter to queryString where the key is the supplied variable name and the value is the directory consumed from the path.