servant-checked-exceptions-1.1.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.API

Description

This module defines the Throws and Throwing types.

Synopsis

Documentation

data Throws (e :: *) Source #

Throws is used in Servant API definitions and signifies that an API will throw the given error.

Here is an example of how to create an API that potentially returns a String as an error, or an Int on success:

>>> import Servant.API (Get, JSON, (:>))
>>> type API = Throws String :> Get '[JSON] Int

Instances

type Client m ((:>) * k1 (Throws e) api) # 
type Client m ((:>) * k1 (Throws e) api) = Client m ((:>) * k1 (Throwing ((:) * e ([] *))) api)
type ServerT * ((:>) * k1 (Throws e) api) m # 
type ServerT * ((:>) * k1 (Throws e) api) m = ServerT * ((:>) * k1 (Throwing ((:) * e ([] *))) api) m

data NoThrow Source #

NoThrow is used to indicate that an API will not throw an error, but that it will still return a response wrapped in a Envelope.

Examples

Create an API using NoThrow:

>>> import Servant.API (Get, JSON, (:>))
>>> type API = NoThrow :> Get '[JSON] Int

A servant-server handler for this type would look like the following:

  apiHandler :: Handler (Envelope '[] Int)
  apiHandler = pureSuccEnvelope 3

Instances

type Client m ((:>) * * NoThrow ((:>) k k1 api apis)) # 
type Client m ((:>) * * NoThrow ((:>) k k1 api apis)) = Client m ((:>) k * api ((:>) * k1 NoThrow apis))
type Client m ((:>) * * NoThrow ((:<|>) api1 api2)) # 
type Client m ((:>) * * NoThrow ((:<|>) api1 api2)) = Client m ((:<|>) ((:>) * * NoThrow api1) ((:>) * * NoThrow api2))
type Client m ((:>) * * NoThrow (Verb k1 * method status ctypes a)) # 
type Client m ((:>) * * NoThrow (Verb k1 * method status ctypes a)) = Client m (Verb k1 * method status ctypes (Envelope ([] *) a))
type ServerT * ((:>) * * NoThrow (Verb k1 k method status ctypes a)) m # 
type ServerT * ((:>) * * NoThrow (Verb k1 k method status ctypes a)) m = ServerT * (VerbWithErr k1 k method status ctypes ([] *) a) m
type ServerT * ((:>) * * NoThrow ((:>) k k1 api apis)) m # 
type ServerT * ((:>) * * NoThrow ((:>) k k1 api apis)) m = ServerT * ((:>) k * api ((:>) * k1 NoThrow apis)) m
type ServerT * ((:>) * * NoThrow ((:<|>) api1 api2)) m # 
type ServerT * ((:>) * * NoThrow ((:<|>) api1 api2)) m = ServerT * ((:<|>) ((:>) * * NoThrow api1) ((:>) * * NoThrow api2)) m

data Throwing (e :: [*]) Source #

This is used internally and should not be used by end-users.

Instances

type Client m ((:>) * * (Throwing es) ((:>) k k1 api apis)) # 
type Client m ((:>) * * (Throwing es) ((:>) k k1 api apis)) = Client m (ThrowingNonterminal ((:>) * * (Throwing es) ((:>) k k1 api apis)))
type Client m ((:>) * * (Throwing es) ((:<|>) api1 api2)) # 
type Client m ((:>) * * (Throwing es) ((:<|>) api1 api2)) = Client m ((:<|>) ((:>) * * (Throwing es) api1) ((:>) * * (Throwing es) api2))
type Client m ((:>) * * (Throwing es) (Verb k1 * method status ctypes a)) # 
type Client m ((:>) * * (Throwing es) (Verb k1 * method status ctypes a)) = Client m (Verb k1 * method status ctypes (Envelope es a))
type ServerT * ((:>) * * (Throwing es) ((:>) k k1 api apis)) m # 
type ServerT * ((:>) * * (Throwing es) ((:>) k k1 api apis)) m = ServerT * (ThrowingNonterminal ((:>) * * (Throwing es) ((:>) k k1 api apis))) m
type ServerT * ((:>) * * (Throwing es) ((:<|>) api1 api2)) m # 
type ServerT * ((:>) * * (Throwing es) ((:<|>) api1 api2)) m = ServerT * ((:<|>) ((:>) * * (Throwing es) api1) ((:>) * * (Throwing es) api2)) m
type ServerT * ((:>) * * (Throwing es) (Verb k1 k method status ctypes a)) m # 
type ServerT * ((:>) * * (Throwing es) (Verb k1 k method status ctypes a)) m = ServerT * (VerbWithErr k1 k method status ctypes es a) m

type family ThrowingNonterminal api where ... Source #

Used by the HasServer and HasClient instances for Throwing es :> api :> apis to detect Throwing es followed immediately by Throws e.

Equations

ThrowingNonterminal (Throwing es :> (Throws e :> api)) = Throwing (Snoc es e) :> api 
ThrowingNonterminal (Throwing es :> (c :> api)) = c :> (Throwing es :> api) 

data VerbWithErr (method :: k1) (successStatusCode :: Nat) (contentTypes :: [*]) (es :: [*]) a Source #

Instances

Generic (VerbWithErr k1 k method successStatusCode contentTypes es a) Source # 

Associated Types

type Rep (VerbWithErr k1 k method successStatusCode contentTypes es a) :: * -> * #

Methods

from :: VerbWithErr k1 k method successStatusCode contentTypes es a -> Rep (VerbWithErr k1 k method successStatusCode contentTypes es a) x #

to :: Rep (VerbWithErr k1 k method successStatusCode contentTypes es a) x -> VerbWithErr k1 k method successStatusCode contentTypes es a #

type ServerT * (VerbWithErr k1 * method successStatus ctypes es a) m # 
type ServerT * (VerbWithErr k1 * method successStatus ctypes es a) m = m (Envelope es a)
type Rep (VerbWithErr k1 k method successStatusCode contentTypes es a) Source # 
type Rep (VerbWithErr k1 k method successStatusCode contentTypes es a) = D1 * (MetaData "VerbWithErr" "Servant.Checked.Exceptions.Internal.Servant.API" "servant-checked-exceptions-1.1.0.0-IByHlf9lS1N9CgOD09jp5h" False) (V1 *)

class ErrStatus e where Source #

Minimal complete definition

toErrStatus

Methods

toErrStatus :: e -> Status Source #

type family AllErrStatus (es :: [k]) :: Constraint where ... Source #

Equations

AllErrStatus '[] = () 
AllErrStatus (a ': as) = (ErrStatus a, AllErrStatus as)