serv-0.2.0.0: Dependently typed API framework

Safe HaskellNone
LanguageHaskell2010

Serv.Api

Contents

Description

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

Synopsis

API types/kinds

data Api star Source

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

Constructors

Endpoint star [Handler star]

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.

OneOf [Api star]

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

Abstract

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

(Path star) :> (Api star) infixr 5

Qualify an API using a series of Path "segments"

Instances

SingI (Api *) (Abstract *) Source 
SingI [Api *] ts => SingI (Api *) (OneOf * ts) Source 
(SingI (Path *) p, SingI (Api *) k) => SingI (Api *) ((:>) * p k) Source 
(SingI * t, SingI [Handler *] ts) => SingI (Api *) (Endpoint * t ts) Source 
data Sing (Api *) where Source 

data Path star Source

Generalized path segments match against data in the request.

Constructors

Const Symbol

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

HeaderAs HeaderName Symbol

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

Seg Symbol star

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

Header HeaderName star

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

Wildcard

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

Instances

SingI (Path *) (Wildcard *) Source 
SingI Symbol s => SingI (Path *) (Const * s) Source 
(SingI HeaderName n, SingI * t) => SingI (Path *) (Header * n t) Source 
(SingI Symbol n, SingI * t) => SingI (Path *) (Seg * n t) Source 
(SingI HeaderName n, SingI Symbol v) => SingI (Path *) (HeaderAs * n v) Source 
data Sing (Path *) where Source 

data Handler star Source

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

Constructors

Method Verb [(Status, Output star)]

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

CaptureBody [star] star (Handler star)

Augment a Handler to include requirements of a request body.

CaptureHeaders [(HeaderName, star)] (Handler star)

Augment a Handler to include requirements of request header values.

CaptureQuery [(Symbol, star)] (Handler star)

Augment a Handler to include requirements of the request query string

Instances

(SingI Verb v, SingI [(,) Status (Output *)] ts) => SingI (Handler *) (Method * v ts) Source 
(SingI [(,) HeaderName *] ts, SingI (Handler *) k) => SingI (Handler *) (CaptureHeaders * ts k) Source 
(SingI [(,) Symbol *] ts, SingI (Handler *) k) => SingI (Handler *) (CaptureQuery * ts k) Source 
(SingI [*] ts, SingI * a, SingI (Handler *) k) => SingI (Handler *) (CaptureBody * ts a k) Source 
data Sing (Handler *) where Source 

data Output star Source

Describes an output from an API under a given status.

Constructors

Respond [(HeaderName, star)] (Body star) 

Instances

(SingI [(,) HeaderName *] ts, SingI (Body *) b) => SingI (Output *) (Respond * ts b) Source 
data Sing (Output *) where Source 

data Body star Source

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

Constructors

HasBody [star] star

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

Empty

A response with an empty body

Instances

SingI (Body *) (Empty *) Source 
(SingI [*] ts, SingI * a) => SingI (Body *) (HasBody * ts a) Source 
data Sing (Body *) where Source 

Syntax sugar

type (:::) a b = `(a, b)` infixr 6 Source

Extra syntax-sugar for representing type-level pairs.

Singletons

data family Sing a

The singleton kind-indexed data family.

Instances

data Sing Bool where 
data Sing Ordering where 
data Sing * where 
data Sing Nat where 
data Sing Symbol where 
data Sing () where 
data Sing Status where 
data Sing Verb where 
data Sing HeaderName where 
data Sing [a0] where 
data Sing (Maybe a0) where 
data Sing (Api *) where 
data Sing (Path *) where 
data Sing (Handler *) where 
data Sing (Output *) where 
data Sing (Body *) where 
data Sing (TyFun k1 k2 -> *) = SLambda {} 
data Sing (Either a0 b0) where 
data Sing ((,) a0 b0) where 
data Sing ((,,) a0 b0 c0) where 
data Sing ((,,,) a0 b0 c0 d0) where 
data Sing ((,,,,) a0 b0 c0 d0 e0) where 
data Sing ((,,,,,) a0 b0 c0 d0 e0 f0) where 
data Sing ((,,,,,,) a0 b0 c0 d0 e0 f0 g0) where 

Type aliases

Eliminates need for single-quoting the DataKind-lifted types.

Api

type Endpoint ann ms = Endpoint ann ms Source

type OneOf apis = OneOf apis Source

type (:>) a b = a :> b infixr 5 Source

Path

type Const sym = Const sym Source

type HeaderAs ty sym = HeaderAs ty sym Source

type Seg sym ty = Seg sym ty Source

type Header name ty = Header name ty Source

Handler

type Method verb responses = Method verb responses Source

type CaptureBody cTypes ty method = CaptureBody cTypes ty method Source

type CaptureHeaders hdrs method = CaptureHeaders hdrs method Source

type CaptureQuery query method = CaptureQuery query method Source

Output

type Respond hdrs body = Respond hdrs body Source

Body

type HasBody ctypes ty = HasBody ctypes ty Source