serv-0.1.0.0: Dependently typed API server framework

Safe HaskellNone
LanguageHaskell2010

Serv.Internal.Api

Description

Types, but really kinds, which represent the structure of an API.

Synopsis

Documentation

data Api star where Source #

Apis describe collections of HTTP endpoints accessible at various segmented Paths.

An Endpoint describes a root API which responds only to requests with empty paths. It matches on HTTP Methods which demand Verbs, HeaderNames, and Bodys.

Endpoint differs from OneOf in that it can only choose between possible methods and automatically provides an OPTIONS response.

Apis consist of many sub-Apis which are attempted sequentially. OneOf choices expresses this sequential search along a set of sub-Api choices.

Raw enables the use of standard Applications within an Api. These cannot be examined further through type analysis, but they are a common use case.

Qualify an API using a series of Path qualifiers.

Constructors

Endpoint :: [Method star] -> Api star 
OneOf :: [Api star] -> Api star 
Raw :: Api star 
(:>) :: Path star -> Api star -> Api star infixr 5 

Instances

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 #

(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 #

type Impl (Api star) (Raw star) m Source # 
type Impl (Api star) (Raw star) m = m Application
type Impl (Api *) (Endpoint * methods) m Source # 
type Impl (Api *) (Endpoint * methods) m = Impl [Method *] methods m
type Impl (Api star) (OneOf star apis) m Source # 
type Impl (Api star) (OneOf star apis) m = Impl [Api star] apis m
type Impl (Api *) ((:>) * (Seg * n v) api) m Source # 
type Impl (Api *) ((:>) * (Seg * n v) api) m = Tagged Symbol n v -> Impl (Api *) api m
type Impl (Api *) ((:>) * (Header * n v) api) m Source # 
type Impl (Api *) ((:>) * (Header * n v) api) m = v -> Impl (Api *) api m
type Impl (Api *) ((:>) * (Cors * p) api) m Source # 
type Impl (Api *) ((:>) * (Cors * p) api) m = Impl (Api *) api m
type Impl (Api star) ((:>) star (HeaderAs star s v) api) m Source # 
type Impl (Api star) ((:>) star (HeaderAs star s v) api) m = Impl (Api star) api m
type Impl (Api star) ((:>) star (Wildcard star) api) m Source # 
type Impl (Api star) ((:>) star (Wildcard star) api) m = [Text] -> Impl (Api star) api m
type Impl (Api star) ((:>) star (Const star s) api) m Source # 
type Impl (Api star) ((:>) star (Const star s) api) m = Impl (Api star) api m

data Method star where Source #

A Method is a single HTTP verb response handled at a given Endpoint. In order to complete a Method's operation it may demand data from the request such as headers or the request body.

A "core" Method definition which describes the Verb it responds to along with a set of response headers and a chance to attach a response Body.

Augment a Method to include requirements of a request body.

Augment a Method to include requirements of request header values.

Constructors

Method :: Verb -> [Pair HeaderName star] -> Body star -> Method star 
CaptureBody :: [star] -> star -> Method star -> Method star 
CaptureHeaders :: [Pair HeaderName star] -> Method star -> Method star 
CaptureQuery :: [Pair Symbol star] -> Method star -> Method star 

Instances

HeadersReturnedBy ([] (Method *)) Source # 
HeadersExpectedOf ([] (Method *)) Source # 
(ReflectVerb verb, VerbsOf [Method star] methods) => VerbsOf [Method star] ((:) (Method star) (Method star verb headers body) methods) Source # 

Methods

verbsOf :: Proxy ((Method star ': Method star verb headers body) methods) methods -> Set Verb 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 #

(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 #

(ReflectHeaderNames [Pair HeaderName *] headers, HeadersReturnedBy rs) => HeadersReturnedBy ((:) (Method *) (Method * verb headers body) rs) Source # 

Methods

headersReturnedBy :: Proxy [Method *] ((Method * ': Method * verb headers body) rs) -> Set HeaderName Source #

HeadersReturnedBy ((:) (Method *) method rs) => HeadersReturnedBy ((:) (Method *) (CaptureBody * ctypes ty method) rs) Source # 

Methods

headersReturnedBy :: Proxy [Method *] ((Method * ': CaptureBody * ctypes ty method) rs) -> Set HeaderName Source #

HeadersReturnedBy ((:) (Method *) method rs) => HeadersReturnedBy ((:) (Method *) (CaptureHeaders * hdrs method) rs) Source # 

Methods

headersReturnedBy :: Proxy [Method *] ((Method * ': CaptureHeaders * hdrs method) rs) -> Set HeaderName Source #

HeadersReturnedBy ((:) (Method *) method rs) => HeadersReturnedBy ((:) (Method *) (CaptureQuery * names method) rs) Source # 

Methods

headersReturnedBy :: Proxy [Method *] ((Method * ': CaptureQuery * names method) rs) -> Set HeaderName Source #

HeadersExpectedOf rs => HeadersExpectedOf ((:) (Method *) (Method * verb headers body) rs) Source # 

Methods

headersExpectedOf :: Proxy [Method *] ((Method * ': Method * verb headers body) rs) -> Set HeaderName Source #

HeadersExpectedOf ((:) (Method *) method rs) => HeadersExpectedOf ((:) (Method *) (CaptureBody * ctypes ty method) rs) Source # 

Methods

headersExpectedOf :: Proxy [Method *] ((Method * ': CaptureBody * ctypes ty method) rs) -> Set HeaderName Source #

(HeadersExpectedOf ((:) (Method *) method rs), ReflectHeaderNames [Pair HeaderName *] hdrs) => HeadersExpectedOf ((:) (Method *) (CaptureHeaders * hdrs method) rs) Source # 

Methods

headersExpectedOf :: Proxy [Method *] ((Method * ': CaptureHeaders * hdrs method) rs) -> Set HeaderName Source #

HeadersExpectedOf ((:) (Method *) method rs) => HeadersExpectedOf ((:) (Method *) (CaptureQuery * names method) rs) Source # 

Methods

headersExpectedOf :: Proxy [Method *] ((Method * ': CaptureQuery * names method) rs) -> Set HeaderName Source #

type Impl (Method *) (CaptureHeaders * headers method) m Source # 
type Impl (Method *) (CaptureHeaders * headers method) m = Rec HeaderName headers -> Impl (Method *) method m
type Impl (Method *) (CaptureQuery * query method) m Source # 
type Impl (Method *) (CaptureQuery * query method) m = Rec Symbol query -> Impl (Method *) method m
type Impl (Method *) (Method * verb headers body) m Source # 
type Impl (Method *) (Method * verb headers body) m = m (Response headers body)
type Impl (Method *) (Method * GET headers body) m Source # 
type Impl (Method *) (Method * GET headers body) m = m (Response headers body)
type Impl (Method *) (CaptureBody * ctypes value method) m Source # 
type Impl (Method *) (CaptureBody * ctypes value method) m = value -> Impl (Method *) method m

data Body star where Source #

Method responses may opt to include a response body or not.

Return a response body by specifying a set of content-types and a value to derive the body from.

A response with an empty body

Constructors

Body :: [star] -> star -> Body star 
Empty :: Body star 

data Path star where Source #

Generalized path segments match against data in the request.

Matches if the request has a non-empty remaining path and the next segment matches exactly

Matches if the request has a given header and its value matches exactly (!)

Matches if the request has a non-empty remaining path. The next segment is "captured", provided to the server implementation.

Always matches, "capturing" the value of a header, or Nothing if the header fails to exist.

Always matches, "captures" the remaining path segments as a list of text values. May just capture the empty list.

Always matches, "captures" the existence of a query flag by returning True if the flag is provided and False otherwise.

Always matches, "capturing" the value of a query parameter.

Constructors

Const :: Symbol -> Path star 
HeaderAs :: HeaderName -> Symbol -> Path star 
Seg :: Symbol -> star -> Path star 
Header :: HeaderName -> star -> Path star 
Wildcard :: Path star 
Flag :: Symbol -> Path star 
QueryParam :: Symbol -> star -> Path star 
Cors :: star -> Path star