web-inv-route-0.1: Composable, reversible, efficient web routing based on invertible invariants and bijections

Safe HaskellNone
LanguageHaskell2010

Web.Route.Invertible.Common

Contents

Description

The basic routing API, sufficient for route and routing map construction. There is usually no need to import this module directly as it is re-exported by most other exposed interfaces.

This package supports route construction as follows:

  1. Endpoint specification, which consists of a Route key and action value.

    • Describe the parameters of each endpoint using Route, which is constructed by composing the route* functions (routeHost, routePath, routeMethod, routeQuery, etc.) using Control.Invertible.Monoidal operators. Typically these predicates should be specified in order for sensible routing, but you can also use normRoute to reorder them automatically.
    • Join the route with a target using `RouteAction`. This target action is the value associated with the route key, and is usually an action to produce a response in your preferred framework (but could be anything).
    • The RouteAction should typically be assigned to a top-level variable. While the type of the Route parameter can differ for each route, all action values must have the same result type.
    getThing :: RouteAction Int (IO Response)
    getThing =
      routePath ("thing" *< parameter) >*
      routeMethod GET
      `RouteAction` \thingId -> do
        return Response{..}
    
    postThingValue :: RouteAction (Int, String) (IO Response)
    postThingValue =
      routeSecure True *<
      routePath ("thing" *< parameter >* "value" >*< parameter) >*
      routeMethod POST
      RouteAction \(thingId, attribute) ->
        set thingId attribute =<< getRequestBody
        return Response{..}
    
  2. Route Map specification.

    myRoutes = routes
      [ routeCase getThing
      , routeCase postThingValue
      , ..
      ]
    

You can also add support for new parameter types by creating your own instances of Parameter.

Synopsis

Route construction

data Route a Source

A Monoidal collection of routing predicates. For example:

routeHost ("www" >* "domain.com") *< routePath ("object" *< parameter) :: Route Int

routeHost :: Host h -> Route h Source

Limit a route to matching hosts. By default, routes apply to any hosts not matched by any other routes in the map. When combining (with routes) or normalizing (with normRoute) routes, this has the highest precedence.

routeSecure :: Bool -> Route () Source

Limit a route to only secure (https:) or insecure (http:) protocols. By default, routes apply to both.

routePath :: Path p -> Route p Source

Limit a route to matching paths. By default, routes apply to any paths not matched by any other routes in the map (e.g., 404 handler, though it can be more general to handle a RouteNotFound result directly) that also match all previous predicates.

routeMethod :: IsMethod m => m -> Route () Source

Limit a route to a method. By default, routes apply to all methods not handled by any other routes for the same earlier matching predicates (e.g., within the same path).

routeMethods :: (Eq m, IsMethod m) => [m] -> Route m Source

Limit a route to a list of methods and return that method. Supplying a method not in this list when generating (reverse) routes will result in a run-time error.

routeQuery :: QueryString -> Placeholder QueryString a -> Route a Source

Limit a route to requests with a matching URL query parameter. By default, other routes match only when the given parameter is missing.

routeAccept :: ContentType -> Route () Source

Limit a route to requests with the given "Content-type" header, i.e., POST requests containing a request body of a certain type. Note that this does not relate to the type of the response or the "Accept" header. By default, routes match only requests without bodies or with content-type headers not matched by any other routes.

routeAccepts :: [ContentType] -> Route ContentType Source

Limit a route to a list of methods and return that method. Supplying a method not in this list when generating (reverse) routes will result in a run-time error.

routeCustom :: Typeable a => (Request -> Maybe a) -> (a -> Request -> Request) -> Route a Source

A custom routing predicate that can perform arbitrary tests on the request and reverse routing. The first argument is used in forward routing to check the request, and only passes if it returns Just. The second argument is used in reverse routing to modify the request according to the parameter. By default, routes match all requests -- unlike other predicates, matching a custom rule does not exclude other routes. This should be used sparingly and towards the end of a route as, unlike most other predicates, it only provides O(n) lookups, as these functions must be called for every route candidate (those where all previous predicates match).

routePriority :: Int -> Route () Source

Set the priority of a route. Routes with higher priority take precedence when there is a conflict. By default, routes have priority 0. When combining (with routes) or normalizing (with normRoute) routes, this has the lowest precedence (so that conflicts are handled only after matching all other predicates).

data RouteAction a b infix 1 Source

Specify the action to take for a given route, often used as an infix operator between the route specification and the function used to produce the result (which usually generates the HTTP response, but could be anything).

Constructors

RouteAction infix 1 

Fields

actionRoute :: !(Route a)
 
routeAction :: !(a -> b)
 

Instances

mapActionRoute :: (a <-> b) -> RouteAction a r -> RouteAction b r Source

RouteAction is invariant in its first argument. Apply a bijection to the routing argument, leaving the action alone.

Supporting types

data Host a Source

A hostname matcher. These should typically be constructed using the IsString and Parameterized instances. This matches hostnames in reverse order (from TLD down), but the Monoidal instance and splitHost automatically deal with this for you. Example:

parameter >* "domain" >* "com" :: Host String

matches (or generates) *.domain.com and returns the * component.

Instances

Monoidal Host Source 
MonoidalAlt Host Source 
Functor Host Source 
Parameterized HostString Host Source 
Show (Host a) Source 
IsString (Host ()) Source

Since domain components cannot contain ".", "foo.com" is equivalent to "foo" *< "com" (unlike other Sequences).

data Path a Source

A URL path parser/generator. These should typically be constructed using the IsString and Parameterized instances. Note that the individual components are decoded path segments, so a literal slash in a component (e.g., as produced with fromString) will match "%2F". Example:

"get" *< parameter >*< "value" *< parameter :: Path (String, Int)

matches (or generates) /get/$x/value/$y for any string $x and any int $y and returns those values.

class IsMethod m Source

Any types that represent an HTTP method.

Minimal complete definition

toMethod

type QueryString = ByteString Source

The type of URL query strings, variables, and parameters, after URI decoding but before UTF-8 decoding.

type ContentType = ByteString Source

String representation of content types, e.g., from HTTP "Content-type" headers.

Parser construction

wildcard :: (Parameterized s f, MonoidalAlt f, Parameter s a) => [a] -> f () Source

Ignore an arbitrary sequence of parameters (usually as a tail), always generating the same thing.

Placeholder parameters

class (Eq s, IsString s, Hashable s, Monoid s) => RouteString s Source

Representions of request data that can be used in routing

Minimal complete definition

toString

class (RouteString s, Typeable a) => Parameter s a where Source

A parameter value a that can be parsed from or rendered into string data s. parseParameter must invert renderParameter:

  • parseParameter . renderParameter == Just

Minimal complete definition

Nothing

Methods

parseParameter :: s -> Maybe a Source

Parse string data into a value. Often equivalent (and defaults) to readMaybe.

renderParameter :: a -> s Source

Render a value into a string. Often equivalent (and defaults) to show.

class Parameterized s p | p -> s where Source

Parsers p that operate over string data s, and so can parse placeholder Parameter values.

Methods

parameter :: Parameter s a => p a Source

Create a parser for a parameter of type a.

param :: (Parameterized s p, Parameter s a) => a -> p a Source

Create a placeholder parameter with the type of the argument, which is ignored.

data Placeholder s a Source

A segment of a parser over strings s, which may be a fixed string (usually created through IsString), only accepting a single fixed value, or a dynamic parameter (created through Parameterized), which encapsulates a Parameter type.

Forward routing

type RouteCase = RouteMapT ((->) Dynamics) Source

The type of a route map element created from a single Route. These may be combined into a final RouteMap. (Currently these are in fact the same representation, but this may change.)

routeCase :: RouteAction a b -> RouteCase b Source

Convert a Route and result generator to a single entry in the routing table.

routeNormCase :: RouteAction a b -> RouteCase b Source

Combine routeCase and normRoute. See the description of normRoute for an explaination.

type RouteMap = RouteCase Source

A map for efficiently looking up requests based on a set of individual route specifications.

routes :: [RouteCase a] -> RouteMap a Source

Combine a list of routes to a single map.

fallbackHEADtoGET :: RouteMap a -> RouteMap a Source

Make any handler for a GET method in the map also apply to HEAD requests, provided there is not an existing handler. A number of frameworks can automatically convert your GET responses into HEAD responses, so this is useful (if slightly wasteful) in those cases.