Safe Haskell | None |
---|---|
Language | Haskell2010 |
A server (represented by ServerT
) is a sequence
of handlers (represented by HandlersT
), one for each
operation in the corresponding Mu service declaration.
In general, you should declare a server as:
server :: MonadServer m => ServerT w MyService m _ server = Server (h1 :<|>: h2 :<|>: ... :<|>: H0)
where each of h1
, h2
, ... handles each method in
MyService
in the order they were declared.
The _
in the type allows GHC to fill in the boring
and long type you would need to write there otherwise.
Implementation note: exceptions raised in handlers
produce an error to be sent as response to the client.
We recommend you to catch exceptions and return custom
ServerError
s instead.
Synopsis
- type MonadServer m = (MonadError ServerError m, MonadIO m)
- data ServerT (w :: Type -> Type) (s :: Service snm mnm) (m :: Type -> Type) (hs :: [Type]) where
- data HandlersT (w :: Type -> Type) (methods :: [Method mnm]) (m :: Type -> Type) (hs :: [Type]) where
- type ServerErrorIO = ExceptT ServerError IO
- type ServerIO w srv = ServerT w srv ServerErrorIO
- serverError :: MonadError ServerError m => ServerError -> m a
- data ServerError = ServerError ServerErrorCode String
- data ServerErrorCode
- alwaysOk :: MonadIO m => IO a -> m a
Servers and handlers
type MonadServer m = (MonadError ServerError m, MonadIO m) Source #
Constraint for monads that can be used as servers
data ServerT (w :: Type -> Type) (s :: Service snm mnm) (m :: Type -> Type) (hs :: [Type]) where Source #
Definition of a complete server for a service.
data HandlersT (w :: Type -> Type) (methods :: [Method mnm]) (m :: Type -> Type) (hs :: [Type]) where Source #
HandlersT
is a sequence of handlers.
Note that the handlers for your service
must appear in the same order as they
are defined.
In general you can choose any type you want for your handlers, due to the following restrictions:
- Haskell types must be convertible to the
corresponding schema type. In other words,
they must implement
FromSchema
if they are inputs, andToSchema
if they are outputs. - Normal returns are represented by returning the corresponding Haskell type.
- Input streams turn into
Conduit () t m ()
, wheret
is the Haskell type for that schema type. - Output streams turn into an additional argument
of type
Conduit t Void m ()
. This stream should be connected to a source to get the elements.
Simple servers using only IO
type ServerErrorIO = ExceptT ServerError IO Source #
Simplest monad which satisfies MonadServer
.
type ServerIO w srv = ServerT w srv ServerErrorIO Source #
Errors which might be raised
serverError :: MonadError ServerError m => ServerError -> m a Source #
Stop the current handler, returning an error to the client.
data ServerErrorCode Source #
Possible types of errors. Some of these are handled in a special way by different transpoprt layers.
Instances
Eq ServerErrorCode Source # | |
Defined in Mu.Server (==) :: ServerErrorCode -> ServerErrorCode -> Bool # (/=) :: ServerErrorCode -> ServerErrorCode -> Bool # | |
Show ServerErrorCode Source # | |
Defined in Mu.Server showsPrec :: Int -> ServerErrorCode -> ShowS # show :: ServerErrorCode -> String # showList :: [ServerErrorCode] -> ShowS # |