servant-checked-exceptions-1.0.0.0: Checked exceptions for Servant APIs.

CopyrightDennis Gosnell 2017
LicenseBSD3
MaintainerDennis Gosnell (cdep.illabout@gmail.com)
Stabilityexperimental
Portabilityunknown
Safe HaskellNone
LanguageHaskell2010

Servant.Checked.Exceptions.Internal.Servant.Server

Contents

Description

This module exports HasServer instances for Throws and Throwing.

Synopsis

Documentation

methodRouter :: forall ctypes a es env. (AllCTRender ctypes (Envelope es a), AllErrStatus es) => Method -> Status -> Proxy ctypes -> Delayed env (Handler (Envelope es a)) -> Router' env (Request -> (RouteResult Response -> IO ResponseReceived) -> IO ResponseReceived) Source #

Orphan instances

HasServer * (ThrowingNonterminal ((:>) * * (Throwing es) ((:>) k k1 api apis))) context => HasServer * ((:>) * * (Throwing es) ((:>) k k1 api apis)) context Source #

When a Throws e comes immediately after a Throwing es, Snoc the e onto the es. Otherwise, if Throws e comes before any other combinator, push it down so it is closer to the Verb.

Associated Types

type ServerT ((* :> *) (Throwing es) ((k :> k1) api apis)) (context :: (* :> *) (Throwing es) ((k :> k1) api apis)) (m :: * -> *) :: * #

Methods

route :: Proxy ((* :> *) (Throwing es) ((k :> k1) api apis)) context -> Context context -> Delayed env (Server ((* :> *) (Throwing es) ((k :> k1) api apis)) context) -> Router env #

HasServer * ((:<|>) ((:>) * * (Throwing es) api1) ((:>) * * (Throwing es) api2)) context => HasServer * ((:>) * * (Throwing es) ((:<|>) api1 api2)) context Source #

When Throwing es comes before :<|>, push Throwing es into each branch of the API.

Associated Types

type ServerT ((* :> *) (Throwing es) (api1 :<|> api2)) (context :: (* :> *) (Throwing es) (api1 :<|> api2)) (m :: * -> *) :: * #

Methods

route :: Proxy ((* :> *) (Throwing es) (api1 :<|> api2)) context -> Context context -> Delayed env (Server ((* :> *) (Throwing es) (api1 :<|> api2)) context) -> Router env #

HasServer * (VerbWithErr k1 k method status ctypes es a) context => HasServer * ((:>) * * (Throwing es) (Verb k1 k method status ctypes a)) context Source #

When Throwing es comes before a Verb, change it into the same Verb but returning an Envelope es.

Associated Types

type ServerT ((* :> *) (Throwing es) (Verb k1 k method status ctypes a)) (context :: (* :> *) (Throwing es) (Verb k1 k method status ctypes a)) (m :: * -> *) :: * #

Methods

route :: Proxy ((* :> *) (Throwing es) (Verb k1 k method status ctypes a)) context -> Context context -> Delayed env (Server ((* :> *) (Throwing es) (Verb k1 k method status ctypes a)) context) -> Router env #

HasServer * (VerbWithErr k1 k method status ctypes ([] *) a) context => HasServer * ((:>) * * NoThrow (Verb k1 k method status ctypes a)) context Source #

When NoThrow comes before a Verb, change it into the same Verb but returning an Envelope '[].

Associated Types

type ServerT ((* :> *) NoThrow (Verb k1 k method status ctypes a)) (context :: (* :> *) NoThrow (Verb k1 k method status ctypes a)) (m :: * -> *) :: * #

Methods

route :: Proxy ((* :> *) NoThrow (Verb k1 k method status ctypes a)) context -> Context context -> Delayed env (Server ((* :> *) NoThrow (Verb k1 k method status ctypes a)) context) -> Router env #

HasServer * ((:>) k * api ((:>) * k1 NoThrow apis)) context => HasServer * ((:>) * * NoThrow ((:>) k k1 api apis)) context Source #

When NoThrow comes before any combinator, push it down so it is closer to the Verb.

Associated Types

type ServerT ((* :> *) NoThrow ((k :> k1) api apis)) (context :: (* :> *) NoThrow ((k :> k1) api apis)) (m :: * -> *) :: * #

Methods

route :: Proxy ((* :> *) NoThrow ((k :> k1) api apis)) context -> Context context -> Delayed env (Server ((* :> *) NoThrow ((k :> k1) api apis)) context) -> Router env #

HasServer * ((:<|>) ((:>) * * NoThrow api1) ((:>) * * NoThrow api2)) context => HasServer * ((:>) * * NoThrow ((:<|>) api1 api2)) context Source #

When NoThrow comes before :<|>, push NoThrow into each branch of the API.

Associated Types

type ServerT ((* :> *) NoThrow (api1 :<|> api2)) (context :: (* :> *) NoThrow (api1 :<|> api2)) (m :: * -> *) :: * #

Methods

route :: Proxy ((* :> *) NoThrow (api1 :<|> api2)) context -> Context context -> Delayed env (Server ((* :> *) NoThrow (api1 :<|> api2)) context) -> Router env #

HasServer * ((:>) * k1 (Throwing ((:) * e ([] *))) api) context => HasServer * ((:>) * k1 (Throws e) api) context Source #

Change a Throws into Throwing.

Associated Types

type ServerT ((* :> k1) (Throws e) api) (context :: (* :> k1) (Throws e) api) (m :: * -> *) :: * #

Methods

route :: Proxy ((* :> k1) (Throws e) api) context -> Context context -> Delayed env (Server ((* :> k1) (Throws e) api) context) -> Router env #

(AllCTRender ctypes (Envelope es a), AllErrStatus * es, KnownNat successStatus, ReflectMethod k1 method) => HasServer * (VerbWithErr k1 * method successStatus ctypes es a) context Source # 

Associated Types

type ServerT (VerbWithErr k1 * method successStatus ctypes es a) (context :: VerbWithErr k1 * method successStatus ctypes es a) (m :: * -> *) :: * #

Methods

route :: Proxy (VerbWithErr k1 * method successStatus ctypes es a) context -> Context context -> Delayed env (Server (VerbWithErr k1 * method successStatus ctypes es a) context) -> Router env #