webapi-0.3: WAI based library for web api

LicenseBSD3
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

WebApi.Router

Contents

Description

 

Synopsis

Route types

data Static s Source

Datatype representing a static path piece.

Instances

(KnownSymbol piece, ApiHandler s m (Static piece), ToHeader (HeaderOut m (Static piece)), ToParam Cookie (CookieOut m (Static piece)), FromParam QueryParam (QueryParam m (Static piece)), FromParam FormParam (FormParam m (Static piece)), FromParam FileParam (FileParam m (Static piece)), FromHeader (HeaderIn m (Static piece)), FromParam Cookie (CookieIn m (Static piece)), Encodings (ContentTypes m (Static piece)) (ApiOut m (Static piece)), Encodings (ContentTypes m (Static piece)) (ApiErr m (Static piece)), (~) * (PathParam m (Static piece)) (), ParamErrToApiErr (ApiErr m (Static piece)), ToHListRecTuple (StripContents (RequestBody m (Static piece))), PartDecodings (RequestBody m (Static piece)), Typeable * m, Typeable * (Static piece), WebApiServer s) => Router * s (Static piece) ((,) * [*] m pp) Source 
KnownSymbol s => MkPathFormatString (Static s) Source 
type PathParam' m (Static s) = () Source 

type Root = Static "" Source

data p1 :/ p2 infixr 5 Source

Datatype representing a route.

Instances

(KnownSymbol rpiece, (~) [*] paths ((:++) * pp ((:) * (DynamicPiece lpiece) ((:) * (StaticPiece rpiece) ([] *)))), (~) [*] paths ((:++) * ((:++) * pp ((:) * (DynamicPiece lpiece) ([] *))) ((:) * (StaticPiece rpiece) ([] *))), (~) * route (FromPieces paths), ApiHandler s m route, (~) * (PathParam m route) (HListToTuple (FilterDynP paths)), FromParam QueryParam (QueryParam m route), FromParam FormParam (FormParam m route), FromParam FileParam (FileParam m route), FromParam Cookie (CookieIn m route), FromHeader (HeaderIn m route), Encodings (ContentTypes m route) (ApiErr m route), Encodings (ContentTypes m route) (ApiOut m route), ToHeader (HeaderOut m route), ToParam Cookie (CookieOut m route), DecodeParam lpiece, ParamErrToApiErr (ApiErr m route), ToHListRecTuple (StripContents (RequestBody m route)), PartDecodings (RequestBody m route), Typeable * m, Typeable * route, WebApiServer s) => Router * s ((:/) * Symbol lpiece rpiece) ((,) * [*] m pp) Source 
(KnownSymbol lpiece, KnownSymbol rpiece, (~) [*] paths ((:++) * pp ((:) * (StaticPiece lpiece) ((:) * (StaticPiece rpiece) ([] *)))), (~) [*] paths ((:++) * ((:++) * pp ((:) * (StaticPiece lpiece) ([] *))) ((:) * (StaticPiece rpiece) ([] *))), (~) * route (FromPieces paths), ApiHandler s m route, (~) * (PathParam m route) (HListToTuple (FilterDynP paths)), FromParam QueryParam (QueryParam m route), FromParam FormParam (FormParam m route), FromParam FileParam (FileParam m route), FromParam Cookie (CookieIn m route), FromHeader (HeaderIn m route), Encodings (ContentTypes m route) (ApiErr m route), Encodings (ContentTypes m route) (ApiOut m route), ToHeader (HeaderOut m route), ToParam Cookie (CookieOut m route), ParamErrToApiErr (ApiErr m route), ToHListRecTuple (StripContents (RequestBody m route)), PartDecodings (RequestBody m route), Typeable * m, Typeable * route, WebApiServer s) => Router * s ((:/) Symbol Symbol lpiece rpiece) ((,) * [*] m pp) Source 
(Router * s (MarkDyn rest) ((,) * [*] m ((:++) * pp ((:) * (StaticPiece piece) ([] *)))), KnownSymbol piece) => Router * s ((:/) Symbol * piece rest) ((,) * [*] m pp) Source 
(Router * s (MarkDyn rest) ((,) * [*] m ((:++) * pp ((:) * (DynamicPiece piece) ([] *)))), DecodeParam piece) => Router * s ((:/) * * piece rest) ((,) * [*] m pp) Source 
MkFormatStr (ToPieces * ((:/) k k1 a b)) => MkPathFormatString ((:/) k k a b) Source 
type PathParam' m ((:/) k k1 p1 p2) = HListToTuple (FilterDynP (ToPieces * ((:/) k k1 p1 p2))) Source 

Default routing implementation

data Route ms r Source

Datatype representing a endpoint.

Instances

Router * s (Route ([] *) r) pr Source 
(SingMethod m, Router * s r ((,) * [*] m ([] *)), Router * s (Route ms r) pr) => Router * s (Route ((:) * m ms) r) pr Source 

class Router server r pr where Source

Class to do the default routing.

Methods

route :: (iface ~ ApiInterface server) => Proxy r -> server -> ParsedRoute pr -> RoutingApplication Source

Instances

((~) * route (FromPieces ((:++) * pp ((:) * (DynamicPiece t) ([] *)))), ApiHandler s m route, (~) * (PathParam m route) (HListToTuple (FilterDynP ((:++) * pp ((:) * (DynamicPiece t) ([] *))))), FromParam QueryParam (QueryParam m route), FromParam FormParam (FormParam m route), FromParam FileParam (FileParam m route), FromParam Cookie (CookieIn m route), FromHeader (HeaderIn m route), Encodings (ContentTypes m route) (ApiErr m route), Encodings (ContentTypes m route) (ApiOut m route), ToHeader (HeaderOut m route), ToParam Cookie (CookieOut m route), DecodeParam t, ParamErrToApiErr (ApiErr m route), ToHListRecTuple (StripContents (RequestBody m route)), PartDecodings (RequestBody m route), Typeable * m, Typeable * route, WebApiServer s) => Router * s (DynamicPiece t) ((,) * [*] m pp) Source 
(KnownSymbol piece, ApiHandler s m (Static piece), ToHeader (HeaderOut m (Static piece)), ToParam Cookie (CookieOut m (Static piece)), FromParam QueryParam (QueryParam m (Static piece)), FromParam FormParam (FormParam m (Static piece)), FromParam FileParam (FileParam m (Static piece)), FromHeader (HeaderIn m (Static piece)), FromParam Cookie (CookieIn m (Static piece)), Encodings (ContentTypes m (Static piece)) (ApiOut m (Static piece)), Encodings (ContentTypes m (Static piece)) (ApiErr m (Static piece)), (~) * (PathParam m (Static piece)) (), ParamErrToApiErr (ApiErr m (Static piece)), ToHListRecTuple (StripContents (RequestBody m (Static piece))), PartDecodings (RequestBody m (Static piece)), Typeable * m, Typeable * (Static piece), WebApiServer s) => Router * s (Static piece) ((,) * [*] m pp) Source 
Router * s (Route ([] *) r) pr Source 
(SingMethod m, Router * s r ((,) * [*] m ([] *)), Router * s (Route ms r) pr) => Router * s (Route ((:) * m ms) r) pr Source 
(KnownSymbol rpiece, (~) [*] paths ((:++) * pp ((:) * (DynamicPiece lpiece) ((:) * (StaticPiece rpiece) ([] *)))), (~) [*] paths ((:++) * ((:++) * pp ((:) * (DynamicPiece lpiece) ([] *))) ((:) * (StaticPiece rpiece) ([] *))), (~) * route (FromPieces paths), ApiHandler s m route, (~) * (PathParam m route) (HListToTuple (FilterDynP paths)), FromParam QueryParam (QueryParam m route), FromParam FormParam (FormParam m route), FromParam FileParam (FileParam m route), FromParam Cookie (CookieIn m route), FromHeader (HeaderIn m route), Encodings (ContentTypes m route) (ApiErr m route), Encodings (ContentTypes m route) (ApiOut m route), ToHeader (HeaderOut m route), ToParam Cookie (CookieOut m route), DecodeParam lpiece, ParamErrToApiErr (ApiErr m route), ToHListRecTuple (StripContents (RequestBody m route)), PartDecodings (RequestBody m route), Typeable * m, Typeable * route, WebApiServer s) => Router * s ((:/) * Symbol lpiece rpiece) ((,) * [*] m pp) Source 
(KnownSymbol lpiece, KnownSymbol rpiece, (~) [*] paths ((:++) * pp ((:) * (StaticPiece lpiece) ((:) * (StaticPiece rpiece) ([] *)))), (~) [*] paths ((:++) * ((:++) * pp ((:) * (StaticPiece lpiece) ([] *))) ((:) * (StaticPiece rpiece) ([] *))), (~) * route (FromPieces paths), ApiHandler s m route, (~) * (PathParam m route) (HListToTuple (FilterDynP paths)), FromParam QueryParam (QueryParam m route), FromParam FormParam (FormParam m route), FromParam FileParam (FileParam m route), FromParam Cookie (CookieIn m route), FromHeader (HeaderIn m route), Encodings (ContentTypes m route) (ApiErr m route), Encodings (ContentTypes m route) (ApiOut m route), ToHeader (HeaderOut m route), ToParam Cookie (CookieOut m route), ParamErrToApiErr (ApiErr m route), ToHListRecTuple (StripContents (RequestBody m route)), PartDecodings (RequestBody m route), Typeable * m, Typeable * route, WebApiServer s) => Router * s ((:/) Symbol Symbol lpiece rpiece) ((,) * [*] m pp) Source 
(Router * s (MarkDyn rest) ((,) * [*] m ((:++) * pp ((:) * (StaticPiece piece) ([] *)))), KnownSymbol piece) => Router * s ((:/) Symbol * piece rest) ((,) * [*] m pp) Source 
(Router * s (MarkDyn rest) ((,) * [*] m ((:++) * pp ((:) * (DynamicPiece piece) ([] *)))), DecodeParam piece) => Router * s ((:/) * * piece rest) ((,) * [*] m pp) Source 
Router [k] s ([] k) pr Source 
(Router * s route pr, Router [*] s routes pr) => Router [*] s ((:) * route routes) pr Source 

router :: (iface ~ ApiInterface server, Router server apis `(CUSTOM "", `[]`)`) => Proxy apis -> server -> RoutingApplication Source

type family ToPieces r :: [*] Source

Convert the path into a flat hierarchy.

Equations

ToPieces (Static s) = `[StaticPiece s]` 
ToPieces ((p1 :: Symbol) :/ (p2 :: Symbol)) = `[StaticPiece p1, StaticPiece p2]` 
ToPieces ((p1 :: *) :/ (p2 :: Symbol)) = `[DynamicPiece p1, StaticPiece p2]` 
ToPieces ((p1 :: Symbol) :/ (p2 :/ p3)) = StaticPiece p1 : ToPieces (p2 :/ p3) 
ToPieces ((p1 :: *) :/ (p2 :/ p3)) = DynamicPiece p1 : ToPieces (p2 :/ p3) 
ToPieces ((p1 :: *) :/ (p2 :: *)) = `[DynamicPiece p1, DynamicPiece p2]` 
ToPieces ((p1 :: Symbol) :/ (p2 :: *)) = `[StaticPiece p1, DynamicPiece p2]` 

type family FromPieces pps :: * Source

Equations

FromPieces `[StaticPiece s]` = Static s 
FromPieces `[StaticPiece p1, StaticPiece p2]` = p1 :/ p2 
FromPieces `[DynamicPiece p1, DynamicPiece p2]` = p1 :/ p2 
FromPieces `[StaticPiece p1, DynamicPiece p2]` = p1 :/ p2 
FromPieces `[DynamicPiece p1, StaticPiece p2]` = p1 :/ p2 
FromPieces (StaticPiece p1 : (StaticPiece p2 : pps)) = p1 :/ FromPieces (StaticPiece p2 : pps) 
FromPieces (DynamicPiece p1 : (DynamicPiece p2 : pps)) = p1 :/ FromPieces (DynamicPiece p2 : pps) 
FromPieces (StaticPiece p1 : (DynamicPiece p2 : pps)) = p1 :/ FromPieces (DynamicPiece p2 : pps) 
FromPieces (DynamicPiece p1 : (StaticPiece p2 : pps)) = p1 :/ FromPieces (StaticPiece p2 : pps) 

Custom routing

data PathSegment Source

Type of segments of a Path.

Constructors

StaticSegment Text

A static segment

Hole

A dynamic segment

class MkPathFormatString r where Source

Describe representation of the route.

Methods

mkPathFormatString :: Proxy r -> [PathSegment] Source

Given a route, this function should produce the [PathSegment] of that route. This gives the flexibility to hook in a different routing system into the application.

Instances

KnownSymbol s => MkPathFormatString (Static s) Source 
MkFormatStr (ToPieces * ((:/) k k1 a b)) => MkPathFormatString ((:/) k k a b) Source 

apiHandler :: forall query p m r. (query ~ `[]`, MonadCatch (HandlerM p), ApiHandler p m r, Typeable m, Typeable r) => Tagged query p -> Request m r -> HandlerM p (Query (Response m r) query) Source

This function is used to call local handler without incurring the cost of network round trip and se/deserialisation of Request and Response.

Internal

type family FilterDynP ps :: [*] Source

Equations

FilterDynP (DynamicPiece p1 : p2) = p1 : FilterDynP p2 
FilterDynP (p1 : p2) = FilterDynP p2 
FilterDynP `[]` = `[]` 

data DynamicPiece t Source

Instances

((~) * route (FromPieces ((:++) * pp ((:) * (DynamicPiece t) ([] *)))), ApiHandler s m route, (~) * (PathParam m route) (HListToTuple (FilterDynP ((:++) * pp ((:) * (DynamicPiece t) ([] *))))), FromParam QueryParam (QueryParam m route), FromParam FormParam (FormParam m route), FromParam FileParam (FileParam m route), FromParam Cookie (CookieIn m route), FromHeader (HeaderIn m route), Encodings (ContentTypes m route) (ApiErr m route), Encodings (ContentTypes m route) (ApiOut m route), ToHeader (HeaderOut m route), ToParam Cookie (CookieOut m route), DecodeParam t, ParamErrToApiErr (ApiErr m route), ToHListRecTuple (StripContents (RequestBody m route)), PartDecodings (RequestBody m route), Typeable * m, Typeable * route, WebApiServer s) => Router * s (DynamicPiece t) ((,) * [*] m pp) Source 

data ParsedRoute :: (*, [*]) -> * where Source

Constructors

Nil :: Proxy method -> ParsedRoute `(method, `[]`)` 
ConsStaticPiece :: Proxy (p :: Symbol) -> ParsedRoute `(method, ps)` -> ParsedRoute `(method, StaticPiece p : ps)` 
ConsDynamicPiece :: !t -> ParsedRoute `(method, ps)` -> ParsedRoute `(method, DynamicPiece t : ps)` 

data PieceType :: * -> * where Source

Constructors

SPiece :: Proxy (p :: Symbol) -> PieceType (StaticPiece p) 
DPiece :: !val -> PieceType (DynamicPiece val) 

snocParsedRoute :: ParsedRoute `(method, ps)` -> PieceType pt -> ParsedRoute `(method, ps :++ `[pt]`)` Source

symTxt :: KnownSymbol sym => proxy sym -> Text Source