Safe Haskell | None |
---|---|
Language | Haskell2010 |
This provides a generic, framework-agnostic interface to routing.
If you have a RouteMap
(see Web.Route.Invertible.Common), make a Request
to describe an incoming request, and call lookupRoute
or routeRequest
to find the route.
See RouteRequest
for handling errors or the result.
You can also use requestActionRoute
to produce a Request
from a route endpoint.
Synopsis
- module Web.Route.Invertible.Common
- normRoute :: Route a -> Route a
- type HostString = ByteString
- type PathString = Text
- normalizePath :: [PathString] -> [PathString]
- data Method
- class IsMethod m where
- toMethod :: m -> Method
- fromMethod :: Method -> Maybe m
- data Request = Request {}
- data RouteResult a
- lookupRoute :: Request -> RouteMap a -> RouteResult a
- routeRequest :: Request -> RouteMap a -> Either (Status, ResponseHeaders) a
- requestActionRoute :: RouteAction a b -> a -> Request
- (!:?) :: RouteAction a b -> a -> BoundRoute
- requestBoundRoute :: BoundRoute -> Request
Documentation
module Web.Route.Invertible.Common
normRoute :: Route a -> Route a Source #
By default, route predicates are matched in the order they are specified, so each test is done only if all preceding tests succeed.
However, in most cases routing rules should be tested in a specific order in order to produce sensible errors (e.g., a 405 error that offers available methods should only apply to other routes with the same path).
This re-orders the predicates in a route in order of the constructors in RoutePredicate
(i.e., host, secure, path, method, ...), allowing you to construct your routes in any order but still produce sensible matching behavior.
Alternatively, since there are cases you may watch to match in a different order (e.g., for routePriority
), you can specify your routes in specific order and avoid this function (which would also be more efficient).
Note that there are some "de-normalized" cases that this will not correct, such as having duplicate routeMethod
specifications (in which case all must match, but each is done independently).
Request representation
type HostString = ByteString Source #
The representation for domain names or domain name segments (after splitHost
).
type PathString = Text Source #
A component of a path, such that paths are represented by [
(after splitting on '/').
Paths can be created by PathString
]decodePath
.
normalizePath :: [PathString] -> [PathString] Source #
Remove double- and trailing-slashes (i.e., empty path segments).
Standard HTTP methods. These are defined a number of places already, but the http-types version (which is the only thing we import by default) is too cumbersome.
class IsMethod m where Source #
Any types that represent an HTTP method.
Instances
IsMethod ByteString Source # | |
Defined in Web.Route.Invertible.Method toMethod :: ByteString -> Method Source # fromMethod :: Method -> Maybe ByteString Source # | |
IsMethod Method Source # | |
IsMethod StdMethod Source # | |
IsMethod Method Source # | |
IsMethod Method Source # | |
IsMethod (Either ByteString StdMethod) Source # | |
Defined in Web.Route.Invertible.Method toMethod :: Either ByteString StdMethod -> Method Source # fromMethod :: Method -> Maybe (Either ByteString StdMethod) Source # |
A reduced representation of an HTTP request, sufficient for routing. This lets us both pre-process/parse the request to optimize routing, and be agnostic about the incoming request representation. These can be created with one of the framework-specific layers.
Request | |
|
Forward routing
data RouteResult a Source #
The result of looking up a request in a routing map.
RouteNotFound | No route was found to handle this request: 404 |
AllowedMethods [Method] | No route was found to handle this request, but there are routes for other methods: 405 |
RouteResult a | A route was found to handle this request |
MultipleRoutes | Multiple (conflicting) routes were found to handle this request: 500 |
Instances
Functor RouteResult Source # | |
Defined in Web.Route.Invertible.Result fmap :: (a -> b) -> RouteResult a -> RouteResult b # (<$) :: a -> RouteResult b -> RouteResult a # | |
Eq a => Eq (RouteResult a) Source # | |
Defined in Web.Route.Invertible.Result (==) :: RouteResult a -> RouteResult a -> Bool # (/=) :: RouteResult a -> RouteResult a -> Bool # | |
Show a => Show (RouteResult a) Source # | |
Defined in Web.Route.Invertible.Result showsPrec :: Int -> RouteResult a -> ShowS # show :: RouteResult a -> String # showList :: [RouteResult a] -> ShowS # | |
Semigroup (RouteResult a) Source # | |
Defined in Web.Route.Invertible.Result (<>) :: RouteResult a -> RouteResult a -> RouteResult a # sconcat :: NonEmpty (RouteResult a) -> RouteResult a # stimes :: Integral b => b -> RouteResult a -> RouteResult a # | |
Monoid (RouteResult a) Source # | |
Defined in Web.Route.Invertible.Result mempty :: RouteResult a # mappend :: RouteResult a -> RouteResult a -> RouteResult a # mconcat :: [RouteResult a] -> RouteResult a # |
lookupRoute :: Request -> RouteMap a -> RouteResult a Source #
Lookup a value in a routing table based on a Request
.
This returns the action returned by the route
that can handle this request, wrapped in a RouteResult
in case of error.
routeRequest :: Request -> RouteMap a -> Either (Status, ResponseHeaders) a Source #
Lookup a request in a routing table and transform errors to appropriate HTTP status and headers. It is up to the user to provide an appropriate body (if any).
Reverse routing
requestActionRoute :: RouteAction a b -> a -> Request Source #
Apply requestRoute
to actionRoute
.
(!:?) :: RouteAction a b -> a -> BoundRoute infix 1 Source #
Combine (:?)
and actionRoute
.
requestBoundRoute :: BoundRoute -> Request Source #
Apply requestRoute
on a BoundRoute
.