servant-checked-exceptions-2.2.0.1: 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

Description

This module exports HasServer instances for Throws and Throwing.

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 (Throwing '[e] :> api) context => HasServer (Throws e :> api :: Type) context Source #

Change a Throws into Throwing.

Instance details

Associated Types

type ServerT (Throws e :> api) m #

Methods

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

hoistServerWithContext :: Proxy (Throws e :> api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (Throws e :> api) m -> ServerT (Throws e :> api) n #

HasServer (VerbWithErr method status ctypes ('[] :: [Type]) a) context => HasServer (NoThrow :> Verb method status ctypes a :: Type) context Source #

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

Instance details

Associated Types

type ServerT (NoThrow :> Verb method status ctypes a) m #

Methods

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

hoistServerWithContext :: Proxy (NoThrow :> Verb method status ctypes a) -> Proxy context -> (forall x. m x -> n x) -> ServerT (NoThrow :> Verb method status ctypes a) m -> ServerT (NoThrow :> Verb method status ctypes a) n #

HasServer (api :> (NoThrow :> apis)) context => HasServer (NoThrow :> (api :> apis) :: Type) context Source #

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

Instance details

Associated Types

type ServerT (NoThrow :> (api :> apis)) m #

Methods

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

hoistServerWithContext :: Proxy (NoThrow :> (api :> apis)) -> Proxy context -> (forall x. m x -> n x) -> ServerT (NoThrow :> (api :> apis)) m -> ServerT (NoThrow :> (api :> apis)) n #

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

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

Instance details

Associated Types

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

Methods

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

hoistServerWithContext :: Proxy (NoThrow :> (api1 :<|> api2)) -> Proxy context -> (forall x. m x -> n x) -> ServerT (NoThrow :> (api1 :<|> api2)) m -> ServerT (NoThrow :> (api1 :<|> api2)) n #

HasServer (ThrowingNonterminal (Throwing es :> (api :> apis))) context => HasServer (Throwing es :> (api :> apis) :: Type) 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.

Instance details

Associated Types

type ServerT (Throwing es :> (api :> apis)) m #

Methods

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

hoistServerWithContext :: Proxy (Throwing es :> (api :> apis)) -> Proxy context -> (forall x. m x -> n x) -> ServerT (Throwing es :> (api :> apis)) m -> ServerT (Throwing es :> (api :> apis)) n #

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

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

Instance details

Associated Types

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

Methods

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

hoistServerWithContext :: Proxy (Throwing es :> (api1 :<|> api2)) -> Proxy context -> (forall x. m x -> n x) -> ServerT (Throwing es :> (api1 :<|> api2)) m -> ServerT (Throwing es :> (api1 :<|> api2)) n #

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

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

Instance details

Associated Types

type ServerT (Throwing es :> Verb method status ctypes a) m #

Methods

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

hoistServerWithContext :: Proxy (Throwing es :> Verb method status ctypes a) -> Proxy context -> (forall x. m x -> n x) -> ServerT (Throwing es :> Verb method status ctypes a) m -> ServerT (Throwing es :> Verb method status ctypes a) n #

(AllCTRender ctypes (Envelope es a), AllErrStatus es, KnownNat successStatus, ReflectMethod method) => HasServer (VerbWithErr method successStatus ctypes es a :: Type) context Source # 
Instance details

Associated Types

type ServerT (VerbWithErr method successStatus ctypes es a) m #

Methods

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

hoistServerWithContext :: Proxy (VerbWithErr method successStatus ctypes es a) -> Proxy context -> (forall x. m x -> n x) -> ServerT (VerbWithErr method successStatus ctypes es a) m -> ServerT (VerbWithErr method successStatus ctypes es a) n #