Safe Haskell | None |
---|---|
Language | Haskell2010 |
Serv.Internal.Server.Type
- data NotHere = NotHere
- noOp :: Applicative m => m NotHere
- data a :<|> b = a :<|> b
- data ServerValue
- runServerWai :: Context -> (Response -> IO ResponseReceived) -> Server IO -> IO ResponseReceived
- newtype Server m = Server {
- runServer :: Context -> m ServerValue
- transformServer :: (forall x. m x -> n x) -> Server m -> Server n
- orElse :: Monad m => Server m -> Server m -> Server m
- routingError :: Monad m => RoutingError -> m ServerValue
- data Response headers body where
- emptyResponse :: Status -> Response '[] Empty
- withBody :: a -> Response headers Empty -> Response headers (Body ctypes a)
- withHeader :: Proxy name -> value -> Response headers body -> Response ((name ::: value) ': headers) body
- withQuietHeader :: HeaderEncode name value => Proxy name -> value -> Response headers body -> Response headers body
- resortHeaders :: RecordIso headers headers' => Response headers body -> Response headers' body
- deleteBody :: Response headers body -> Response headers Empty
- class ReflectHeaders headers => WaiResponse headers body where
Documentation
A server implementation which always results in a "Not Found" error. Used to
give semantics to "pathological" servers like 'OneOf '[]
and Endpoint '[]
.
These servers could be statically disallowed but (1) they have a semantic sense as described by this type exactly and (2) to do so would require the creation and management of either larger types or non-empty proofs which would be burdensome to carry about.
Constructors
NotHere |
noOp :: Applicative m => m NotHere Source #
Actual servers are implemented effectfully; this is a no-op server which immediately returns Not Found and applies no effects.
data a :<|> b infixr 5 Source #
Either one thing or the other. In particular, often this is used when we are
describing either one server implementation or the other. Used to give
semantics to 'OneOf
and 'Endpoint
.
Constructors
a :<|> b infixr 5 |
data ServerValue Source #
A return value from a Server
computation.
Constructors
RoutingError RoutingError | Routing errors arise when a routing attempt fails and, depending on the error, either we should recover and backtrack or resolve the entire response with that error. |
WaiResponse Response | If the response is arising from the |
Application Application | If the application demands an "upgrade" or ties into another server
mechanism then routing at that location will return the (opaque)
|
runServerWai :: Context -> (Response -> IO ResponseReceived) -> Server IO -> IO ResponseReceived Source #
transformServer :: (forall x. m x -> n x) -> Server m -> Server n Source #
routingError :: Monad m => RoutingError -> m ServerValue Source #
withBody :: a -> Response headers Empty -> Response headers (Body ctypes a) Source #
Adds a body to a response
withHeader :: Proxy name -> value -> Response headers body -> Response ((name ::: value) ': headers) body Source #
Adds a header to a response
withQuietHeader :: HeaderEncode name value => Proxy name -> value -> Response headers body -> Response headers body Source #
Unlike withHeader
, withQuietHeader
allows you to add headers
not explicitly specified in the api specification.
resortHeaders :: RecordIso headers headers' => Response headers body -> Response headers' body Source #
If a response type is complete defined by its implementation then
applying resorted
to it will future proof it against reorderings
of headers. If the response type is not completely inferrable, however,
then this will require manual annotations of the "pre-sorted" response.
deleteBody :: Response headers body -> Response headers Empty Source #
Used primarily for implementing HEAD
request automatically.
class ReflectHeaders headers => WaiResponse headers body where Source #
Minimal complete definition
Instances
ReflectHeaders HeaderName headers => WaiResponse headers (Empty *) Source # | |
(ReflectHeaders HeaderName headers, ReflectEncoders [*] ctypes a) => WaiResponse headers (Body * ctypes a) Source # | |