servant-server-0.15: 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 
Instances
Monad RouteResult Source # 
Instance details

Defined in Servant.Server.Internal.RoutingApplication

Functor RouteResult Source # 
Instance details

Defined in Servant.Server.Internal.RoutingApplication

Methods

fmap :: (a -> b) -> RouteResult a -> RouteResult b #

(<$) :: a -> RouteResult b -> RouteResult a #

Applicative RouteResult Source # 
Instance details

Defined in Servant.Server.Internal.RoutingApplication

Methods

pure :: a -> RouteResult a #

(<*>) :: RouteResult (a -> b) -> RouteResult a -> RouteResult b #

liftA2 :: (a -> b -> c) -> RouteResult a -> RouteResult b -> RouteResult c #

(*>) :: RouteResult a -> RouteResult b -> RouteResult b #

(<*) :: RouteResult a -> RouteResult b -> RouteResult a #

Eq a => Eq (RouteResult a) Source # 
Instance details

Defined in Servant.Server.Internal.RoutingApplication

Read a => Read (RouteResult a) Source # 
Instance details

Defined in Servant.Server.Internal.RoutingApplication

Show a => Show (RouteResult a) Source # 
Instance details

Defined in Servant.Server.Internal.RoutingApplication

newtype RouteResultT m a Source #

Constructors

RouteResultT 

Fields

Instances
MonadTrans RouteResultT Source # 
Instance details

Defined in Servant.Server.Internal.RoutingApplication

Methods

lift :: Monad m => m a -> RouteResultT m a #

MonadTransControl RouteResultT Source # 
Instance details

Defined in Servant.Server.Internal.RoutingApplication

Associated Types

type StT RouteResultT a :: Type #

Methods

liftWith :: Monad m => (Run RouteResultT -> m a) -> RouteResultT m a #

restoreT :: Monad m => m (StT RouteResultT a) -> RouteResultT m a #

MonadBase b m => MonadBase b (RouteResultT m) Source # 
Instance details

Defined in Servant.Server.Internal.RoutingApplication

Methods

liftBase :: b α -> RouteResultT m α #

MonadBaseControl b m => MonadBaseControl b (RouteResultT m) Source # 
Instance details

Defined in Servant.Server.Internal.RoutingApplication

Associated Types

type StM (RouteResultT m) a :: Type #

Methods

liftBaseWith :: (RunInBase (RouteResultT m) b -> b a) -> RouteResultT m a #

restoreM :: StM (RouteResultT m) a -> RouteResultT m a #

Monad m => Monad (RouteResultT m) Source # 
Instance details

Defined in Servant.Server.Internal.RoutingApplication

Methods

(>>=) :: RouteResultT m a -> (a -> RouteResultT m b) -> RouteResultT m b #

(>>) :: RouteResultT m a -> RouteResultT m b -> RouteResultT m b #

return :: a -> RouteResultT m a #

fail :: String -> RouteResultT m a #

Functor m => Functor (RouteResultT m) Source # 
Instance details

Defined in Servant.Server.Internal.RoutingApplication

Methods

fmap :: (a -> b) -> RouteResultT m a -> RouteResultT m b #

(<$) :: a -> RouteResultT m b -> RouteResultT m a #

(Functor m, Monad m) => Applicative (RouteResultT m) Source # 
Instance details

Defined in Servant.Server.Internal.RoutingApplication

Methods

pure :: a -> RouteResultT m a #

(<*>) :: RouteResultT m (a -> b) -> RouteResultT m a -> RouteResultT m b #

liftA2 :: (a -> b -> c) -> RouteResultT m a -> RouteResultT m b -> RouteResultT m c #

(*>) :: RouteResultT m a -> RouteResultT m b -> RouteResultT m b #

(<*) :: RouteResultT m a -> RouteResultT m b -> RouteResultT m a #

MonadIO m => MonadIO (RouteResultT m) Source # 
Instance details

Defined in Servant.Server.Internal.RoutingApplication

Methods

liftIO :: IO a -> RouteResultT m a #

MonadThrow m => MonadThrow (RouteResultT m) Source # 
Instance details

Defined in Servant.Server.Internal.RoutingApplication

Methods

throwM :: Exception e => e -> RouteResultT m a #

type StT RouteResultT a Source # 
Instance details

Defined in Servant.Server.Internal.RoutingApplication

type StM (RouteResultT m) a Source # 
Instance details

Defined in Servant.Server.Internal.RoutingApplication

data Delayed env 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)
406 (not acceptable)
400 (bad request)

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

A Delayed contains many 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. Authentication checks. This can cause 401.
  4. Accept and content type header checks. These checks can cause 415 and 406 errors.
  5. Query parameter checks. They require parsing and can cause 400 if the parsing fails. Query parameter checks provide inputs to the handler
  6. Header Checks. They also require parsing and can cause 400 if parsing fails.
  7. Body check. The request body check can cause 400.

Constructors

Delayed 

Fields

Instances
Functor (Delayed env) Source # 
Instance details

Defined in Servant.Server.Internal.RoutingApplication

Methods

fmap :: (a -> b) -> Delayed env a -> Delayed env b #

(<$) :: a -> Delayed env b -> Delayed env a #

newtype DelayedIO a Source #

Computations used in a Delayed can depend on the incoming Request, may perform 'IO, and result in a 'RouteResult, meaning they can either suceed, fail (with the possibility to recover), or fail fatally.

Instances
Monad DelayedIO Source # 
Instance details

Defined in Servant.Server.Internal.RoutingApplication

Methods

(>>=) :: DelayedIO a -> (a -> DelayedIO b) -> DelayedIO b #

(>>) :: DelayedIO a -> DelayedIO b -> DelayedIO b #

return :: a -> DelayedIO a #

fail :: String -> DelayedIO a #

Functor DelayedIO Source # 
Instance details

Defined in Servant.Server.Internal.RoutingApplication

Methods

fmap :: (a -> b) -> DelayedIO a -> DelayedIO b #

(<$) :: a -> DelayedIO b -> DelayedIO a #

Applicative DelayedIO Source # 
Instance details

Defined in Servant.Server.Internal.RoutingApplication

Methods

pure :: a -> DelayedIO a #

(<*>) :: DelayedIO (a -> b) -> DelayedIO a -> DelayedIO b #

liftA2 :: (a -> b -> c) -> DelayedIO a -> DelayedIO b -> DelayedIO c #

(*>) :: DelayedIO a -> DelayedIO b -> DelayedIO b #

(<*) :: DelayedIO a -> DelayedIO b -> DelayedIO a #

MonadIO DelayedIO Source # 
Instance details

Defined in Servant.Server.Internal.RoutingApplication

Methods

liftIO :: IO a -> DelayedIO a #

MonadThrow DelayedIO Source # 
Instance details

Defined in Servant.Server.Internal.RoutingApplication

Methods

throwM :: Exception e => e -> DelayedIO a #

MonadResource DelayedIO Source # 
Instance details

Defined in Servant.Server.Internal.RoutingApplication

MonadBase IO DelayedIO Source # 
Instance details

Defined in Servant.Server.Internal.RoutingApplication

Methods

liftBase :: IO α -> DelayedIO α #

MonadBaseControl IO DelayedIO Source # 
Instance details

Defined in Servant.Server.Internal.RoutingApplication

Associated Types

type StM DelayedIO a :: Type #

MonadReader Request DelayedIO Source # 
Instance details

Defined in Servant.Server.Internal.RoutingApplication

Methods

ask :: DelayedIO Request #

local :: (Request -> Request) -> DelayedIO a -> DelayedIO a #

reader :: (Request -> a) -> DelayedIO a #

type StM DelayedIO a Source # 
Instance details

Defined in Servant.Server.Internal.RoutingApplication

emptyDelayed :: RouteResult a -> Delayed env a Source #

A Delayed without any stored checks.

delayedFail :: ServantErr -> DelayedIO a Source #

Fail with the option to recover.

delayedFailFatal :: ServantErr -> DelayedIO a Source #

Fail fatally, i.e., without any option to recover.

withRequest :: (Request -> DelayedIO a) -> DelayedIO a Source #

Gain access to the incoming request.

addCapture :: Delayed env (a -> b) -> (captured -> DelayedIO a) -> Delayed (captured, env) b Source #

Add a capture to the end of the capture block.

addParameterCheck :: Delayed env (a -> b) -> DelayedIO a -> Delayed env b Source #

Add a parameter check to the end of the params block

addHeaderCheck :: Delayed env (a -> b) -> DelayedIO a -> Delayed env b Source #

Add a parameter check to the end of the params block

addMethodCheck :: Delayed env a -> DelayedIO () -> Delayed env a Source #

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

addAuthCheck :: Delayed env (a -> b) -> DelayedIO a -> Delayed env b Source #

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

addBodyCheck Source #

Arguments

:: Delayed env (a -> b) 
-> DelayedIO c

content type check

-> (c -> DelayedIO a)

body check

-> Delayed env b 

Add a content type and body checks around parameter checks.

We'll report failed content type check (415), before trying to parse query parameters (400). Which, in turn, happens before request body parsing.

addAcceptCheck :: Delayed env a -> DelayedIO () -> Delayed env a Source #

Add an accept header check before handling parameters. In principle, we'd like to take a bad body (400) response take precedence over a failed accept check (406). BUT to allow streaming the body, we cannot run the body check and then still backtrack. We therefore do the accept check before the body check, when we can still backtrack. There are other solutions to this, but they'd be more complicated (such as delaying the body check further so that it can still be run in a situation where we'd otherwise report 406).

passToServer :: Delayed env (a -> b) -> (Request -> a) -> Delayed env 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.

runDelayed :: Delayed env a -> env -> Request -> ResourceT 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 env (Handler a) -> env -> Request -> (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.