servant-snap-0.9.0: A family of combinators for defining webservices APIs and serving them

Safe HaskellNone
LanguageHaskell2010

Servant.Server.Internal.RoutingApplication

Synopsis

Documentation

type RoutingApplication m Source #

Arguments

 = Request

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

-> (RouteResult Response -> m Response) 
-> m Response 

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 

runAction :: MonadSnap m => Delayed m env (m a) -> env -> Request -> (RouteResult Response -> m r) -> (a -> RouteResult Response) -> m r Source #

data Delayed m env c where Source #

Constructors

Delayed 

Fields

Instances
Functor (Delayed m env) Source # 
Instance details

Defined in Servant.Server.Internal.RoutingApplication

Methods

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

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

newtype DelayedM m a Source #

Constructors

DelayedM 

Fields

Instances
MonadTrans DelayedM Source # 
Instance details

Defined in Servant.Server.Internal.RoutingApplication

Methods

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

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

Defined in Servant.Server.Internal.RoutingApplication

Methods

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

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

return :: a -> DelayedM m a #

fail :: String -> DelayedM m a #

Monad m => Functor (DelayedM m) Source # 
Instance details

Defined in Servant.Server.Internal.RoutingApplication

Methods

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

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

Monad m => Applicative (DelayedM m) Source # 
Instance details

Defined in Servant.Server.Internal.RoutingApplication

Methods

pure :: a -> DelayedM m a #

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

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

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

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

(Monad m, MonadSnap m) => Alternative (DelayedM m) Source # 
Instance details

Defined in Servant.Server.Internal.RoutingApplication

Methods

empty :: DelayedM m a #

(<|>) :: DelayedM m a -> DelayedM m a -> DelayedM m a #

some :: DelayedM m a -> DelayedM m [a] #

many :: DelayedM m a -> DelayedM m [a] #

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

Defined in Servant.Server.Internal.RoutingApplication

Methods

liftIO :: IO a -> DelayedM m a #

emptyDelayed :: Monad m => Proxy (m :: * -> *) -> RouteResult a -> Delayed m env a Source #

A Delayed without any stored checks.

delayedFail :: Monad m => ServantErr -> DelayedM m a Source #

Fail with the option to recover.

delayedFailFatal :: Monad m => ServantErr -> DelayedM m a Source #

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

withRequest :: (Request -> DelayedM m a) -> DelayedM m a Source #

Gain access to the incoming request.

addCapture :: forall env a b captured m. Monad m => Delayed m env (a -> b) -> (captured -> DelayedM m a) -> Delayed m (captured, env) b Source #

Add a capture to the end of the capture block.

addParameterCheck :: Monad m => Delayed m env (a -> b) -> DelayedM m a -> Delayed m env b Source #

Add a parameter check to the end of the params block

addHeaderCheck :: Monad m => Delayed m env (a -> b) -> DelayedM m a -> Delayed m env b Source #

Add a header check to the end of the headers block

addMethodCheck :: Monad m => Delayed m env a -> DelayedM m () -> Delayed m env a Source #

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

addAuthCheck :: Monad m => Delayed m env (a -> b) -> DelayedM m a -> Delayed m env b Source #

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

addBodyCheck Source #

Arguments

:: Monad m 
=> Delayed m env (a -> b) 
-> DelayedM m c

content type check

-> (c -> DelayedM m a)

body check

-> Delayed m 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 :: Monad m => Delayed m env a -> DelayedM m () -> Delayed m 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 m env (a -> b) -> (Request -> a) -> Delayed m 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 :: Monad m => Delayed m env a -> env -> Request -> m (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.