servant-checked-exceptions-2.2.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.Client

Contents

Description

This module only exports HasClient instances for Throws and Throwing.

Orphan instances

(RunClient m, HasClient m (api :> (NoThrow :> apis))) => HasClient m (NoThrow :> (api :> apis)) Source #

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

Instance details

Associated Types

type Client m (NoThrow :> (api :> apis)) :: Type #

Methods

clientWithRoute :: Proxy m -> Proxy (NoThrow :> (api :> apis)) -> Request -> Client m (NoThrow :> (api :> apis)) #

hoistClientMonad :: Proxy m -> Proxy (NoThrow :> (api :> apis)) -> (forall x. mon x -> mon' x) -> Client mon (NoThrow :> (api :> apis)) -> Client mon' (NoThrow :> (api :> apis)) #

(RunClient m, HasClient m (ThrowingNonterminal (Throwing es :> (api :> apis)))) => HasClient m (Throwing es :> (api :> apis)) 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 Client m (Throwing es :> (api :> apis)) :: Type #

Methods

clientWithRoute :: Proxy m -> Proxy (Throwing es :> (api :> apis)) -> Request -> Client m (Throwing es :> (api :> apis)) #

hoistClientMonad :: Proxy m -> Proxy (Throwing es :> (api :> apis)) -> (forall x. mon x -> mon' x) -> Client mon (Throwing es :> (api :> apis)) -> Client mon' (Throwing es :> (api :> apis)) #

(RunClient m, HasClient m ((NoThrow :> api1) :<|> (NoThrow :> api2))) => HasClient m (NoThrow :> (api1 :<|> api2)) Source #

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

Instance details

Associated Types

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

Methods

clientWithRoute :: Proxy m -> Proxy (NoThrow :> (api1 :<|> api2)) -> Request -> Client m (NoThrow :> (api1 :<|> api2)) #

hoistClientMonad :: Proxy m -> Proxy (NoThrow :> (api1 :<|> api2)) -> (forall x. mon x -> mon' x) -> Client mon (NoThrow :> (api1 :<|> api2)) -> Client mon' (NoThrow :> (api1 :<|> api2)) #

(RunClient m, HasClient m ((Throwing es :> api1) :<|> (Throwing es :> api2))) => HasClient m (Throwing es :> (api1 :<|> api2)) Source #

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

Instance details

Associated Types

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

Methods

clientWithRoute :: Proxy m -> Proxy (Throwing es :> (api1 :<|> api2)) -> Request -> Client m (Throwing es :> (api1 :<|> api2)) #

hoistClientMonad :: Proxy m -> Proxy (Throwing es :> (api1 :<|> api2)) -> (forall x. mon x -> mon' x) -> Client mon (Throwing es :> (api1 :<|> api2)) -> Client mon' (Throwing es :> (api1 :<|> api2)) #

(RunClient m, HasClient m (Verb method status ctypes (Envelope ([] :: [Type]) a))) => HasClient m (NoThrow :> Verb method status ctypes a) Source #

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

Instance details

Associated Types

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

Methods

clientWithRoute :: Proxy m -> Proxy (NoThrow :> Verb method status ctypes a) -> Request -> Client m (NoThrow :> Verb method status ctypes a) #

hoistClientMonad :: Proxy m -> Proxy (NoThrow :> Verb method status ctypes a) -> (forall x. mon x -> mon' x) -> Client mon (NoThrow :> Verb method status ctypes a) -> Client mon' (NoThrow :> Verb method status ctypes a) #

HasClient m (Verb method status ctypes (Envelope es a)) => HasClient m (Throwing es :> Verb method status ctypes a) Source #

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

Instance details

Associated Types

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

Methods

clientWithRoute :: Proxy m -> Proxy (Throwing es :> Verb method status ctypes a) -> Request -> Client m (Throwing es :> Verb method status ctypes a) #

hoistClientMonad :: Proxy m -> Proxy (Throwing es :> Verb method status ctypes a) -> (forall x. mon x -> mon' x) -> Client mon (Throwing es :> Verb method status ctypes a) -> Client mon' (Throwing es :> Verb method status ctypes a) #

(RunClient m, HasClient m (Throwing (e ': ([] :: [Type])) :> api)) => HasClient m (Throws e :> api) Source #

Change a Throws into Throwing.

Instance details

Associated Types

type Client m (Throws e :> api) :: Type #

Methods

clientWithRoute :: Proxy m -> Proxy (Throws e :> api) -> Request -> Client m (Throws e :> api) #

hoistClientMonad :: Proxy m -> Proxy (Throws e :> api) -> (forall x. mon x -> mon' x) -> Client mon (Throws e :> api) -> Client mon' (Throws e :> api) #