servant-server-0.5: A family of combinators for defining webservices APIs and serving them

Safe HaskellNone
LanguageHaskell2010

Servant.Server.Internal.RoutingApplication

Synopsis

Documentation

type RoutingApplication Source

Arguments

 = Request

the request, the field pathInfo may be modified by url routing

-> (RouteResult Response -> IO ResponseReceived) 
-> IO ResponseReceived 

data RouteResult a Source

The result of matching against a path in the route tree.

Constructors

Fail ServantErr

Keep trying other paths. The ServantErr should only be 404, 405 or 406.

FailFatal !ServantErr

Don't try other paths.

Route !a 

data Delayed c where Source

A Delayed is a representation of a handler with scheduled delayed checks that can trigger errors.

Why would we want to delay checks?

There are two reasons:

  1. In a straight-forward implementation, the order in which we perform checks will determine the error we generate. This is because once an error occurs, we would abort and not perform any subsequent checks, but rather return the current error.

This is not a necessity: we could continue doing other checks, and choose the preferred error. However, that would in general mean more checking, which leads us to the other reason.

  1. We really want to avoid doing certain checks too early. For example, captures involve parsing, and are much more costly than static route matches. In particular, if several paths contain the "same" capture, we'd like as much as possible to avoid trying the same parse many times. Also tricky is the request body. Again, this involves parsing, but also, WAI makes obtaining the request body a side-effecting operation. We could/can work around this by manually caching the request body, but we'd rather keep the number of times we actually try to decode the request body to an absolute minimum.

We prefer to have the following relative priorities of error codes:

404
405 (bad method)
401 (unauthorized)
415 (unsupported media type)
400 (bad request)
406 (not acceptable)

Therefore, while routing, we delay most checks so that they will ultimately occur in the right order.

A Delayed contains three delayed blocks of tests, and the actual handler:

  1. Delayed captures. These can actually cause 404, and while they're costly, they should be done first among the delayed checks (at least as long as we do not decouple the check order from the error reporting, see above). Delayed captures can provide inputs to the actual handler.
  2. Method check(s). This can cause a 405. On success, it does not provide an input for the handler. Method checks are comparatively cheap.
  3. Body and accept header checks. The request body check can cause both 400 and 415. This provides an input to the handler. The accept header check can be performed as the final computation in this block. It can cause a 406.

Constructors

Delayed :: IO (RouteResult captures) -> IO (RouteResult ()) -> IO (RouteResult auth) -> IO (RouteResult body) -> (captures -> auth -> body -> RouteResult c) -> Delayed c 

Fields

capturesD :: IO (RouteResult captures)
 
methodD :: IO (RouteResult ())
 
authD :: IO (RouteResult auth)
 
bodyD :: IO (RouteResult body)
 
serverD :: captures -> auth -> body -> RouteResult c
 

addCapture :: Delayed (a -> b) -> IO (RouteResult a) -> Delayed b Source

Add a capture to the end of the capture block.

addMethodCheck :: Delayed a -> IO (RouteResult ()) -> Delayed a Source

Add a method check to the end of the method block.

addAuthCheck :: Delayed (a -> b) -> IO (RouteResult a) -> Delayed b Source

Add an auth check to the end of the auth block.

addBodyCheck :: Delayed (a -> b) -> IO (RouteResult a) -> Delayed b Source

Add a body check to the end of the body block.

addAcceptCheck :: Delayed a -> IO (RouteResult ()) -> Delayed a Source

Add an accept header check to the end of the body block. The accept header check should occur after the body check, but this will be the case, because the accept header check is only scheduled by the method combinators.

passToServer :: Delayed (a -> b) -> a -> Delayed b Source

Many combinators extract information that is passed to the handler without the possibility of failure. In such a case, passToServer can be used.

bindRouteResults :: IO (RouteResult a) -> (a -> IO (RouteResult b)) -> IO (RouteResult b) Source

The combination 'IO . RouteResult' is a monad, but we don't explicitly wrap it in a newtype in order to make it an instance. This is the >>= of that monad.

We stop on the first error.

combineRouteResults :: (a -> b -> c) -> IO (RouteResult a) -> IO (RouteResult b) -> IO (RouteResult c) Source

Common special case of bindRouteResults, corresponding to liftM2.

runDelayed :: Delayed a -> IO (RouteResult a) Source

Run a delayed server. Performs all scheduled operations in order, and passes the results from the capture and body blocks on to the actual handler.

This should only be called once per request; otherwise the guarantees about effect and HTTP error ordering break down.

runAction :: Delayed (ExceptT ServantErr IO a) -> (RouteResult Response -> IO r) -> (a -> RouteResult Response) -> IO r Source

Runs a delayed server and the resulting action. Takes a continuation that lets us send a response. Also takes a continuation for how to turn the result of the delayed server into a response.