webapi-0.2.1.0: WAI based library for web api

LicenseBSD3
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

WebApi.Contract

Contents

Description

Provides the contract for the web api. The contract consists of WebApi and ApiContract classes. WebApi contains information related to the entire group of endpoints whereas ApiContract is concerned with information related to each end point. Once the contract is written, it can be then used to

  • Write a WebApiImplementation and corresponding ApiHandler for it.
  • Get a client for web api.
  • Get a mock server and a mock client for web api.

... and possibly more.

Synopsis

API Contract

class OrdVersion (Version p) => WebApi p Source

Describes a collection of web apis.

Associated Types

type Version p :: * Source

Version of the web api.

type Apis p :: [*] Source

List of all end points that this web api provides.

class (SingMethod m, WebApi p, ReqInvariant (FormParam m r) (FileParam m r) (RequestBody m r)) => ApiContract p m r Source

Describes a contract for a single API end point.

Associated Types

type PathParam m r Source

Type of path param that this end point takes in. Defaults to PathParam' m r.

type QueryParam m r Source

Type of query param that this end point takes in. Defaults to ().

type FormParam m r Source

Type form params that this end point takes in. Defaults to ().

type FileParam m r Source

Type of file params that this end point takes in. Defaults to ().

type HeaderIn m r Source

Type of header params that this end point takes in. Defaults to ().

type CookieIn m r Source

Type of cookie params that this end point takes in. Defaults to ().

type ApiOut m r Source

Type of result of this end point when successful. Defaults to ().

type ApiErr m r Source

Type of result of this end point when a known failure occurs. Defaults to ().

type HeaderOut m r Source

Type of headers of this end point gives out. Defaults to ().

type CookieOut m r Source

Type of cookies of this end point gives out. Defaults to ().

type ContentTypes m r :: [*] Source

List of Content Types that this end point can serve. Defaults to [JSON].

type RequestBody m r :: [*] Source

List of datatypes this end point expects in the request body.

One can specify request's Content-Type by wrapping the data type using Content. If the element in the list is not wrapped with Content, then application/json is used as the Content-Type.

'[Content [PlainText] <Desired-DataType>] -- This goes as "application/text"
'[<Desired-DataType>]                     -- This goes as "application/json"

Currently, it is only possible to have a single entity in request body. Thus RequestBody can only be a singleton list. This restriction might be lifted in a later version.

If it is [], Content-Type is decided by FormParam m r and FileParam m r. Defaults to []

Request and Response

type family PathParam' m r :: * Source

Type of the path params that a route r has. If a custom routing system is being used, then you will have to give an instance for PathParam' for types being used in routing. Please take a look at the existing instances of PathParam' for reference.

Instances

type PathParam' m (Static s) = () Source 
type PathParam' m ((:/) k k1 p1 p2) Source 

data Request m r Source

Datatype representing a request to route r with method m.

queryParam :: Request m r -> QueryParam m r Source

Query params of the request.

formParam :: Request m r -> FormParam m r Source

Form params of the request.

fileParam :: Request m r -> FileParam m r Source

File params of the request.

headerIn :: Request m r -> HeaderIn m r Source

Header params of the request.

cookieIn :: Request m r -> CookieIn m r Source

Cookie params of the request.

requestBody :: Request m r -> HListToTuple (StripContents (RequestBody m r)) Source

Body of the request

pathParam :: Request m r -> PathParam m r Source

Path params of the request.

pattern Req :: () => (SingMethod m, (~) * (HListToTuple (StripContents (RequestBody m r))) ()) => PathParam m r -> QueryParam m r -> FormParam m r -> FileParam m r -> HeaderIn m r -> CookieIn m r -> Text -> Request m r Source

Exists only for compatability reasons. This will be removed in the next version. Use Request pattern instead

pattern Request :: () => SingMethod m => PathParam m r -> QueryParam m r -> FormParam m r -> FileParam m r -> HeaderIn m r -> CookieIn m r -> HListToTuple (StripContents (RequestBody m r)) -> Request m r Source

Used for constructing Request

data Response m r Source

Datatype representing a response from route r with method m.

Constructors

Success Status (ApiOut m r) (HeaderOut m r) (CookieOut m r) 
Failure (Either (ApiError m r) OtherError) 

data ApiError m r Source

Datatype representing a known failure from route r with method m.

Constructors

ApiError 

Fields

code :: Status
 
err :: ApiErr m r
 
headerOut :: Maybe (HeaderOut m r)
 
cookieOut :: Maybe (CookieOut m r)
 

data OtherError Source

Datatype representing an unknown failure.

Constructors

OtherError 

Methods