Safe Haskell | None |
---|---|
Language | Haskell2010 |
Serv.Wai
Contents
Description
Build an "implementation" of a given Api
-kinded type (e.g.
) which describes all of the logic for your server and then convert
it into a Impl
apiServer
value and then an Application
.
- server :: (Constrain api, Monad m) => Sing api -> Impl m api -> Server m
- data Server m
- mapServer :: Monad m => (forall x. m x -> n x) -> Server m -> Server n
- serverApplication :: Server IO -> Application
- serverApplication' :: Server IO -> (Context -> Response -> Response) -> Application
- serverApplication'' :: Server IO -> (Context -> ServerResult -> Response) -> Application
- type family Impl m api
- type family Constrain a :: Constraint
- type family AllImpl m apis
- type family AllHandlers m hs
- type family ImplHandler m h
- type family ConstrainEndpoint hs :: Constraint
- type family ConstrainHandler h :: Constraint
- type family ConstrainOutputs os :: Constraint
- type family ConstrainRespond r :: Constraint
- type family ConstrainBody b :: Constraint
Implement a Server
A server executing in a given monad. We construct these from Api
descriptions and corresponding Impl
descriptions for said Api
s.
Ultimately, a Server
, or at least a 'Server IO', is destined to be
transformed into a Wai Appliation
, but Server
tracks around more
information useful for interpretation and route finding.
Server transformation
Typically you use server
to construct a value
for
some Server
MM
specific to your application, either a transformer stack or
an abstract monad constrained by mtl
-like typeclasses. If M
is not
IO
then serverApplication
cannot be used to build an
Application
, so instead we must first transform M
using a "run"
function applied to mapServer
.
For instance, if M
is StateT St IO
then
flip evalStateT s0 :: StateT St IO a -> IO a
is a suitable "run" function we could apply
using mapServer
to transform
into Server
M
.Server
IO
mapServer :: Monad m => (forall x. m x -> n x) -> Server m -> Server n Source
Lift an effect transformation on to a Server
Execute it as an Application
serverApplication :: Server IO -> Application Source
Converts a
into a regular Wai Server
IO
Application
value.
serverApplication' :: Server IO -> (Context -> Response -> Response) -> Application Source
Converts a
into a regular Wai Server
IO
Application
value;
parameterized on a "response transformer" which allows a final
modification of the Wai response using information gathered from the
Context
. Useful, e.g., for writing final headers.
serverApplication'' :: Server IO -> (Context -> ServerResult -> Response) -> Application Source
Converts a
into a regular Wai Server
IO
Application
value. The
most general of the serverApplication*
functions, parameterized on
a function interpreting the Context
and ServerResult
as a Wai
Response
. As an invariant, the interpreter will never see an
Application
ServerResult
---those are handled by this function.
Constraints and Implementations
In order to call server
we must ensure that our api ::
type is decorated with the appropriate constraints and that the
Api
type properly matches the Impl
apiApi
. This is achieved by
analyzing the types with type-level functions, e.g. the closed type
families Impl
and Constrain
.
NOTE: Closed type families are rather finnicky as to when they actually evaluate, so the factoring of these type families into smaller pieces is done by some trial an error.
Equations
Impl m Abstract = m (Context -> Application) | |
Impl m (OneOf apis) = HList (AllImpl m apis) | |
Impl m (Endpoint ann hs) = FieldRec (AllHandlers m hs) | |
Impl m (Const s :> api) = Impl m api | |
Impl m (HeaderAs s v :> api) = Impl m api | |
Impl m (Seg s a :> api) = a -> Impl m api | |
Impl m (Header n a :> api) = a -> Impl m api | |
Impl m (Wildcard :> api) = [Text] -> Impl m api |
type family Constrain a :: Constraint Source
Equations
Constrain Abstract = () | |
Constrain (Endpoint ann hs) = ConstrainEndpoint hs | |
Constrain (OneOf `[]`) = () | |
Constrain (OneOf (api : apis)) = (Constrain api, Constrain (OneOf apis)) | |
Constrain (Const s :> api) = Constrain api | |
Constrain (HeaderAs s v :> api) = Constrain api | |
Constrain (Seg s a :> api) = (Constrain api, URIDecode a) | |
Constrain (Header n a :> api) = (Constrain api, HeaderDecode n a) | |
Constrain (Wildcard :> api) = Constrain api |
Detailed constraints and implementations
type family AllHandlers m hs Source
Equations
AllHandlers m `[]` = `[]` | |
AllHandlers m (h : hs) = `(VerbOf h, ImplHandler m h)` : AllHandlers m hs |
type family ImplHandler m h Source
Equations
ImplHandler m (CaptureBody ts a h) = a -> ImplHandler m h | |
ImplHandler m (CaptureHeaders hs h) = FieldRec hs -> ImplHandler m h | |
ImplHandler m (CaptureQuery qs h) = FieldRec qs -> ImplHandler m h | |
ImplHandler m (Method v os) = m (SomeResponse os) |
type family ConstrainEndpoint hs :: Constraint Source
Equations
ConstrainEndpoint `[]` = () | |
ConstrainEndpoint (h : hs) = (ConstrainHandler h, ConstrainEndpoint hs) |
type family ConstrainHandler h :: Constraint Source
Equations
ConstrainHandler (Method verb os) = ConstrainOutputs os | |
ConstrainHandler (CaptureBody ctypes a h) = ConstrainHandler h | |
ConstrainHandler (CaptureHeaders hs h) = (AllHeaderDecodes hs, ConstrainHandler h) | |
ConstrainHandler (CaptureQuery qs h) = (AllQueryDecodes qs, ConstrainHandler h) |
type family ConstrainOutputs os :: Constraint Source
Equations
ConstrainOutputs `[]` = () | |
ConstrainOutputs ((s ::: r) : os) = (ConstrainRespond r, ConstrainOutputs os) |
type family ConstrainRespond r :: Constraint Source
Equations
ConstrainRespond (Respond hs b) = (AllHeaderEncodes hs, ConstrainBody b) |
type family ConstrainBody b :: Constraint Source
Equations
ConstrainBody Empty = () | |
ConstrainBody (HasBody ts a) = AllMimeEncode a ts |