License | BSD3 |
---|---|
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
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 correspondingApiHandler
for it. - Get a client for web api.
- Get a mock server and a mock client for web api.
... and possibly more.
- class OrdVersion (Version p) => WebApi p where
- class (SingMethod m, WebApi p, ReqInvariant (FormParam m r) (FileParam m r) (RequestBody m r)) => ApiContract p m r where
- type PathParam m r
- type QueryParam m r
- type FormParam m r
- type FileParam m r
- type HeaderIn m r
- type CookieIn m r
- type ApiOut m r
- type ApiErr m r
- type HeaderOut m r
- type CookieOut m r
- type ContentTypes m r :: [*]
- type RequestBody m r :: [*]
- type family PathParam' m r :: *
- data Request m r
- queryParam :: Request m r -> QueryParam m r
- formParam :: Request m r -> FormParam m r
- fileParam :: Request m r -> FileParam m r
- headerIn :: Request m r -> HeaderIn m r
- cookieIn :: Request m r -> CookieIn m r
- method :: Request m r -> Text
- requestBody :: Request m r -> HListToTuple (StripContents (RequestBody m r))
- pathParam :: Request m r -> PathParam m r
- 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
- 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
- data Response m r
- data ApiError m r = ApiError {}
- data OtherError = OtherError {}
- data Resource m r = Res
- module WebApi.Method
API Contract
class OrdVersion (Version p) => WebApi p Source
Describes a collection of web apis.
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.
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 form params that this end point takes in.
Defaults to ()
.
Type of file params that this end point takes in.
Defaults to ()
.
Type of header params that this end point takes in.
Defaults to ()
.
Type of cookie params that this end point takes in.
Defaults to ()
.
Type of result of this end point when successful.
Defaults to ()
.
Type of result of this end point when a known failure occurs.
Defaults to ()
.
Type of headers of this end point gives out.
Defaults to ()
.
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.
type PathParam' m (Static s) = () Source | |
type PathParam' m ((:/) k k1 p1 p2) = HListToTuple (FilterDynP (ToPieces * ((:/) k k1 p1 p2))) Source |
queryParam :: Request m r -> QueryParam m r Source
Query params of the request.
requestBody :: Request m r -> HListToTuple (StripContents (RequestBody m r)) Source
Body 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
Datatype representing a response from route r
with method m
.
Datatype representing a known failure from route r
with method m
.
data OtherError Source
Datatype representing an unknown failure.
Methods
module WebApi.Method