serv-0.1.0.0: Dependently typed API server framework

Safe HaskellNone
LanguageHaskell2010

Serv.Internal.Server

Synopsis

Documentation

class Handling spec where Source #

The the core type function responsible for interpreting an Api into a functioning Server. It defines a function handle defined over all forms of Api types which consumes a parallel type defined by the associated type family Impl. If api :: Api then Impl api m is an "implementation" of the Api's server logic executing in the m monad. Then, applying handle to a value of Impl api results in a Server which can be executed as a Application.

Minimal complete definition

handle

Associated Types

type Impl spec (m :: * -> *) Source #

Methods

handle :: Monad m => Proxy spec -> Impl spec m -> Server m Source #

Instances

Handling [k] ([] k) Source # 

Associated Types

type Impl ([] k) (spec :: [] k) (m :: * -> *) :: * Source #

Methods

handle :: Monad m => Proxy [k] spec -> Impl [k] spec m -> Server m Source #

Handling (Api star) (Raw star) Source # 

Associated Types

type Impl (Raw star) (spec :: Raw star) (m :: * -> *) :: * Source #

Methods

handle :: Monad m => Proxy (Raw star) spec -> Impl (Raw star) spec m -> Server m Source #

(VerbsOf [Method *] methods, HeadersReturnedBy methods, HeadersExpectedOf methods, Handling [Method *] methods) => Handling (Api *) (Endpoint * methods) Source # 

Associated Types

type Impl (Endpoint * methods) (spec :: Endpoint * methods) (m :: * -> *) :: * Source #

Methods

handle :: Monad m => Proxy (Endpoint * methods) spec -> Impl (Endpoint * methods) spec m -> Server m Source #

Handling [Api star] apis => Handling (Api star) (OneOf star apis) Source # 

Associated Types

type Impl (OneOf star apis) (spec :: OneOf star apis) (m :: * -> *) :: * Source #

Methods

handle :: Monad m => Proxy (OneOf star apis) spec -> Impl (OneOf star apis) spec m -> Server m Source #

(Handling a x, Handling [a] xs) => Handling [a] ((:) a x xs) Source # 

Associated Types

type Impl ((:) a x xs) (spec :: (:) a x xs) (m :: * -> *) :: * Source #

Methods

handle :: Monad m => Proxy ((a ': x) xs) spec -> Impl ((a ': x) xs) spec m -> Server m Source #

Handling (Method *) method => Handling (Method *) (CaptureHeaders * headers method) Source # 

Associated Types

type Impl (CaptureHeaders * headers method) (spec :: CaptureHeaders * headers method) (m :: * -> *) :: * Source #

Methods

handle :: Monad m => Proxy (CaptureHeaders * headers method) spec -> Impl (CaptureHeaders * headers method) spec m -> Server m Source #

Handling (Method *) method => Handling (Method *) (CaptureQuery * query method) Source # 

Associated Types

type Impl (CaptureQuery * query method) (spec :: CaptureQuery * query method) (m :: * -> *) :: * Source #

Methods

handle :: Monad m => Proxy (CaptureQuery * query method) spec -> Impl (CaptureQuery * query method) spec m -> Server m Source #

(URIDecode v, Handling (Api *) api) => Handling (Api *) ((:>) * (Seg * n v) api) Source # 

Associated Types

type Impl ((:>) * (Seg * n v) api) (spec :: (:>) * (Seg * n v) api) (m :: * -> *) :: * Source #

Methods

handle :: Monad m => Proxy ((* :> Seg * n v) api) spec -> Impl ((* :> Seg * n v) api) spec m -> Server m Source #

(HeaderDecode n v, Handling (Api *) api) => Handling (Api *) ((:>) * (Header * n v) api) Source # 

Associated Types

type Impl ((:>) * (Header * n v) api) (spec :: (:>) * (Header * n v) api) (m :: * -> *) :: * Source #

Methods

handle :: Monad m => Proxy ((* :> Header * n v) api) spec -> Impl ((* :> Header * n v) api) spec m -> Server m Source #

(Handling (Api *) api, CorsPolicy p) => Handling (Api *) ((:>) * (Cors * p) api) Source # 

Associated Types

type Impl ((:>) * (Cors * p) api) (spec :: (:>) * (Cors * p) api) (m :: * -> *) :: * Source #

Methods

handle :: Monad m => Proxy ((* :> Cors * p) api) spec -> Impl ((* :> Cors * p) api) spec m -> Server m Source #

(ReflectName n, KnownSymbol v, Handling (Api star) api) => Handling (Api star) ((:>) star (HeaderAs star n v) api) Source # 

Associated Types

type Impl ((:>) star (HeaderAs star n v) api) (spec :: (:>) star (HeaderAs star n v) api) (m :: * -> *) :: * Source #

Methods

handle :: Monad m => Proxy ((star :> HeaderAs star n v) api) spec -> Impl ((star :> HeaderAs star n v) api) spec m -> Server m Source #

Handling (Api star) api => Handling (Api star) ((:>) star (Wildcard star) api) Source # 

Associated Types

type Impl ((:>) star (Wildcard star) api) (spec :: (:>) star (Wildcard star) api) (m :: * -> *) :: * Source #

Methods

handle :: Monad m => Proxy ((star :> Wildcard star) api) spec -> Impl ((star :> Wildcard star) api) spec m -> Server m Source #

(KnownSymbol s, Handling (Api star) api) => Handling (Api star) ((:>) star (Const star s) api) Source # 

Associated Types

type Impl ((:>) star (Const star s) api) (spec :: (:>) star (Const star s) api) (m :: * -> *) :: * Source #

Methods

handle :: Monad m => Proxy ((star :> Const star s) api) spec -> Impl ((star :> Const star s) api) spec m -> Server m Source #

(ReflectVerb verb, WaiResponse headers body) => Handling (Method *) (Method * verb headers body) Source # 

Associated Types

type Impl (Method * verb headers body) (spec :: Method * verb headers body) (m :: * -> *) :: * Source #

Methods

handle :: Monad m => Proxy (Method * verb headers body) spec -> Impl (Method * verb headers body) spec m -> Server m Source #

WaiResponse headers body => Handling (Method *) (Method * GET headers body) Source #

GET is special-cased to handle HEAD semantics which cannot be specified otherwise.

Associated Types

type Impl (Method * GET headers body) (spec :: Method * GET headers body) (m :: * -> *) :: * Source #

Methods

handle :: Monad m => Proxy (Method * GET headers body) spec -> Impl (Method * GET headers body) spec m -> Server m Source #

Handling (Method *) method => Handling (Method *) (CaptureBody * ctypes value method) Source # 

Associated Types

type Impl (CaptureBody * ctypes value method) (spec :: CaptureBody * ctypes value method) (m :: * -> *) :: * Source #

Methods

handle :: Monad m => Proxy (CaptureBody * ctypes value method) spec -> Impl (CaptureBody * ctypes value method) spec m -> Server m Source #

encodeBody :: WaiResponse hdrs body => Context -> Response hdrs body -> ServerValue Source #

verbMatch :: Set Verb -> Method -> Bool Source #

Is the request method in the set of verbs?