Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data RouteResult a
- = NotMatched
- | Matched a
- type RoutingApplication = Request -> (RouteResult Response -> IO ResponseReceived) -> IO ResponseReceived
- toApplication :: RoutingApplication -> Application
- fromWaiRequest :: forall m r. (FromParam (QueryParam m r) QueryParam, FromParam (FormParam m r) FormParam, FromParam (FileParam m r) FileParam, FromHeader (HeaderIn m r), FromParam (CookieIn m r) Cookie, ToHListRecTuple (StripContents (RequestBody m r)), PartDecodings (RequestBody m r), SingMethod m) => Request -> PathParam m r -> IO (Validation [ParamErr] (Request m r))
- toWaiResponse :: (ToHeader (HeaderOut m r), ToParam (CookieOut m r) Cookie, Encodings (ContentTypes m r) (ApiOut m r), Encodings (ContentTypes m r) (ApiErr m r)) => Request -> Response m r -> Response
- link :: (ToParam (QueryParam m r) QueryParam, MkPathFormatString r, ToParam (PathParam m r) PathParam) => route m r -> URI -> PathParam m r -> Maybe (QueryParam m r) -> URI
- renderUriPath :: (ToParam path PathParam, MkPathFormatString r) => ByteString -> path -> route m r -> ByteString
- renderPaths :: (ToParam path PathParam, MkPathFormatString r) => path -> route m r -> ByteString
- class ApiContract (ApiInterface p) m r => ApiHandler p m r where
- type family Query t query :: *
- class (MonadCatch (HandlerM p), MonadIO (HandlerM p), WebApi (ApiInterface p)) => WebApiImplementation p where
- type HandlerM p :: * -> *
- type ApiInterface p :: *
- toIO :: p -> HandlerM p a -> IO a
- data ServerSettings = ServerSettings
- serverSettings :: ServerSettings
- data PathSegment
- class MkPathFormatString r where
- mkPathFormatString :: Proxy r -> [PathSegment]
- data ApiException m r = ApiException {
- apiException :: ApiError m r
- handleApiException :: (query ~ `[]`, Monad (HandlerM p)) => p -> ApiException m r -> HandlerM p (Query (Response m r) query)
- handleSomeException :: (query ~ `[]`, Monad (HandlerM p)) => p -> SomeException -> HandlerM p (Query (Response m r) query)
- getCookie :: Request -> Maybe ByteString
- getAccept :: Request -> Maybe ByteString
- hSetCookie :: HeaderName
- getContentType :: ResponseHeaders -> Maybe ByteString
- newtype Tagged s b = Tagged {
- unTagged :: b
- toTagged :: Proxy s -> b -> Tagged s b
Documentation
data RouteResult a Source
type RoutingApplication = Request -> (RouteResult Response -> IO ResponseReceived) -> IO ResponseReceived Source
fromWaiRequest :: forall m r. (FromParam (QueryParam m r) QueryParam, FromParam (FormParam m r) FormParam, FromParam (FileParam m r) FileParam, FromHeader (HeaderIn m r), FromParam (CookieIn m r) Cookie, ToHListRecTuple (StripContents (RequestBody m r)), PartDecodings (RequestBody m r), SingMethod m) => Request -> PathParam m r -> IO (Validation [ParamErr] (Request m r)) Source
toWaiResponse :: (ToHeader (HeaderOut m r), ToParam (CookieOut m r) Cookie, Encodings (ContentTypes m r) (ApiOut m r), Encodings (ContentTypes m r) (ApiErr m r)) => Request -> Response m r -> Response Source
link :: (ToParam (QueryParam m r) QueryParam, MkPathFormatString r, ToParam (PathParam m r) PathParam) => route m r -> URI -> PathParam m r -> Maybe (QueryParam m r) -> URI Source
Generate a type safe URL for a given route type. The URI can be used for setting a base URL if required.
renderUriPath :: (ToParam path PathParam, MkPathFormatString r) => ByteString -> path -> route m r -> ByteString Source
renderPaths :: (ToParam path PathParam, MkPathFormatString r) => path -> route m r -> ByteString Source
class ApiContract (ApiInterface p) m r => ApiHandler p m r where Source
Describes the implementation of a single API end point corresponding to ApiContract (ApiInterface p) m r
handler :: (query ~ `[]`) => Tagged query p -> Request m r -> HandlerM p (Query (Response m r) query) Source
Handler for the API end point which returns a Response
.
TODO : query
type parameter is an experimental one used for trying out dependently typed params.
This parameter will let us refine the ApiOut
to the structure that is requested by the client.
for eg : graph.facebook.com/bgolub?fields=id,name,picture
This feature is not finalized and might get changed / removed. Currently the return type of handler is equivalent to `Response m r`
(ApiContract p m r, Arbitrary (ApiOut m r), Arbitrary (ApiErr m r), Arbitrary (HeaderOut m r), Arbitrary (CookieOut m r), Typeable * m, Typeable * r) => ApiHandler (MockServer p) m r Source |
class (MonadCatch (HandlerM p), MonadIO (HandlerM p), WebApi (ApiInterface p)) => WebApiImplementation p where Source
Binds implementation to interface and provides a pluggable handler monad for the endpoint handler implementation.
Nothing
type HandlerM p :: * -> * Source
Type of the handler Monad
. It should implement MonadCatch
and MonadIO
classes. Defaults to IO
.
type ApiInterface p :: * Source
WebApi p => WebApiImplementation (MockServer p) Source |
serverSettings :: ServerSettings Source
Default server settings.
data PathSegment Source
Type of segments of a Path.
StaticSegment Text | A static segment |
Hole | A dynamic segment |
class MkPathFormatString r where Source
Describe representation of the route.
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.
KnownSymbol s => MkPathFormatString (Static s) Source | |
MkFormatStr (ToPieces * ((:/) k k1 a b)) => MkPathFormatString ((:/) k k a b) Source |
data ApiException m r Source
Type of Exception raised in a handler.
ApiException | |
|
Show (ApiException m r) Source | |
(Typeable * m, Typeable * r) => Exception (ApiException m r) Source |
handleApiException :: (query ~ `[]`, Monad (HandlerM p)) => p -> ApiException m r -> HandlerM p (Query (Response m r) query) Source
handleSomeException :: (query ~ `[]`, Monad (HandlerM p)) => p -> SomeException -> HandlerM p (Query (Response m r) query) Source
getCookie :: Request -> Maybe ByteString Source
getAccept :: Request -> Maybe ByteString Source