mu-rpc-0.3.0.0: Protocol-independent declaration of services and servers.
Safe HaskellNone
LanguageHaskell2010

Mu.Server

Description

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 can declare a server by naming each of the methods with their handlers:

server :: MonadServer m => ServerT MyService m _
server = singleService ( method @"m1" h1
                       , method @"m2" h2
                       , ... )

or by position:

server :: MonadServer m => ServerT MyService m _
server = Server (h1 :<|>: h2 :<|>: ... :<|>: H0)

where each of h1, h2, ... handles each method in MyService in the order they were declared.

In both cases, 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 ServerErrors instead.

Synopsis

Servers and handlers

type MonadServer m = (MonadError ServerError m, MonadIO m) Source #

Constraint for monads that can be used as servers

type ServiceChain snm = Mappings snm Type Source #

Defines a mapping between outcome of a service, and its representation as Haskell type.

noContext :: b -> a -> b Source #

To declare that the function doesn't use its context.

Definitions by name

singleService :: (ToNamedList p nl, ToHandlers chn () methods m hs nl, MappingRight chn sname ~ ()) => p -> ServerT chn ('Package pname '['Service sname sanns methods]) m '[hs] Source #

Defines a server for a package with a single service. Intended to be used with a tuple of methods:

singleService (method @"m1" h1, method @"m2" h2)

method :: forall n p. p -> Named n (() -> p) Source #

Declares the handler for a method in the service. Intended to be used with TypeApplications:

method @"myMethod" myHandler

resolver :: (ToNamedList p nl, ToServices chn ss m hs nl) => p -> ServerT chn ('Package pname ss) m hs Source #

Combines the implementation of several GraphQL objects, which means a whole Mu service for a GraphQL server. Intented to be used with a tuple of objects:

resolver (object @"o1" ..., object @"o2" ...)

object :: forall sname p nl chn ms m hs. (ToNamedList p nl, ToHandlers chn (MappingRight chn sname) ms m hs nl) => p -> Named sname (HandlersT chn (MappingRight chn sname) ms m hs) Source #

Defines the implementation of a single GraphQL object, which translates as a single Mu service. Intended to be used with TypeApplications and a tuple of fields:

object @"myObject" (field @"f1" h1, fielf @"f2" h2)

Note: for the root objects in GraphQL (query, mutation, subscription) use method instead of object.

field :: forall n h. h -> Named n h Source #

Declares the handler for a field in an object. Intended to be used with TypeApplications:

field @"myField" myHandler

data NamedList (hs :: [(Symbol, *)]) where Source #

Heterogeneous list in which each element is tagged with a type-level name.

Constructors

N0 :: NamedList '[] 
(:|:) :: Named n h -> NamedList hs -> NamedList ('(n, h) ': hs) infixr 4 

Definitions by position

type SingleServerT = ServerT '[] Source #

A server for a single service, like most RPC ones.

pattern Server :: MappingRight chn sname ~ () => HandlersT chn () methods m hs -> ServerT chn ('Package pname '['Service sname sanns methods]) m '[hs] Source #

data ServerT (chn :: ServiceChain snm) (s :: Package snm mnm anm) (m :: Type -> Type) (hs :: [[Type]]) where Source #

Definition of a complete server for a set of services, with possible references between them.

Constructors

Services :: ServicesT chn s m hs -> ServerT chn ('Package pname s) m hs 

data ServicesT (chn :: ServiceChain snm) (s :: [Service snm mnm anm]) (m :: Type -> Type) (hs :: [[Type]]) where Source #

Definition of a complete server for a service.

Constructors

S0 :: ServicesT chn '[] m '[] 
(:<&>:) :: HandlersT chn (MappingRight chn sname) methods m hs -> ServicesT chn rest m hss -> ServicesT chn ('Service sname anns methods ': rest) m (hs ': hss) infixr 3 

data HandlersT (chn :: ServiceChain snm) (inh :: *) (methods :: [Method snm mnm anm]) (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, and ToSchema if they are outputs.
  • Normal returns are represented by returning the corresponding Haskell type.
  • Input streams turn into Conduit () t m (), where t 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.

Constructors

H0 :: HandlersT chn inh '[] m '[] 
(:<||>:) :: Handles chn args ret m h => (inh -> h) -> HandlersT chn inh ms m hs -> HandlersT chn inh ('Method name anns args ret ': ms) m (h ': hs) infixr 4 

Bundled Patterns

pattern (:<|>:) :: Handles chn args ret m h => h -> HandlersT chn () ms m hs -> HandlersT chn () ('Method name anns args ret ': ms) m (h ': hs) infixr 4 

Simple servers using only IO

type ServerErrorIO = ExceptT ServerError IO Source #

Simplest monad which satisfies MonadServer.

type ServerIO srv = ServerT '[] srv ServerErrorIO Source #

Simple ServerT which uses only IO and errors, and whose service has no back-references.

Errors which might be raised

serverError :: MonadError ServerError m => ServerError -> m a Source #

Stop the current handler, returning an error to the client.

data ServerError Source #

Errors raised in a handler.

data ServerErrorCode Source #

Possible types of errors. Some of these are handled in a special way by different transpoprt layers.

Instances

Instances details
Eq ServerErrorCode Source # 
Instance details

Defined in Mu.Server

Show ServerErrorCode Source # 
Instance details

Defined in Mu.Server

Useful when you do not want to deal with errors

alwaysOk :: MonadIO m => IO a -> m a Source #

Wrapper for handlers which do not use errors. Remember that any exception raised in IO is propagated to the client.

For internal use

class Handles (chn :: ServiceChain snm) (args :: [Argument snm anm]) (ret :: Return snm) (m :: Type -> Type) (h :: Type) Source #

Defines a relation for handling.

Instances

Instances details
(MonadError ServerError m, handler ~ m ()) => Handles (chn :: ServiceChain snm) ('[] :: [Argument snm anm]) ('RetNothing :: Return snm) m handler Source # 
Instance details

Defined in Mu.Server

(MonadError ServerError m, ToRef chn ref v, handler ~ (ConduitT v Void m () -> m ())) => Handles (chn :: ServiceChain serviceName) ('[] :: [Argument serviceName anm]) ('RetStream ref :: Return serviceName) m handler Source # 
Instance details

Defined in Mu.Server

(MonadError ServerError m, ToRef chn ref v, handler ~ m v) => Handles (chn :: ServiceChain serviceName) ('[] :: [Argument serviceName anm]) ('RetSingle ref :: Return serviceName) m handler Source # 
Instance details

Defined in Mu.Server

(MonadError ServerError m, ToRef chn eref e, ToRef chn vref v, handler ~ m (Either e v)) => Handles (chn :: ServiceChain serviceName) ('[] :: [Argument serviceName anm]) ('RetThrows eref vref :: Return serviceName) m handler Source # 
Instance details

Defined in Mu.Server

(MonadError ServerError m, FromRef chn ref t, Handles chn args ret m h, handler ~ (ConduitT () t m () -> h)) => Handles (chn :: ServiceChain serviceName) ('ArgStream aname anns ref ': args :: [Argument serviceName anm]) (ret :: Return serviceName) m handler Source # 
Instance details

Defined in Mu.Server

(FromRef chn ref t, Handles chn args ret m h, handler ~ (t -> h)) => Handles (chn :: ServiceChain serviceName) ('ArgSingle aname anns ref ': args :: [Argument serviceName anm]) (ret :: Return serviceName) m handler Source # 
Instance details

Defined in Mu.Server

class FromRef (chn :: ServiceChain snm) (ref :: TypeRef snm) (t :: Type) Source #

Defines whether a given type t can be obtained from the TypeRef ref.

Instances

Instances details
(FromRef chn ref t, Maybe t ~ s) => FromRef (chn :: ServiceChain serviceName) ('OptionalRef ref :: TypeRef serviceName) s Source # 
Instance details

Defined in Mu.Server

(FromRef chn ref t, [t] ~ s) => FromRef (chn :: ServiceChain serviceName) ('ListRef ref :: TypeRef serviceName) s Source # 
Instance details

Defined in Mu.Server

MappingRight chn ref ~ t => FromRef (chn :: Mappings serviceName Type) ('ObjectRef ref :: TypeRef serviceName) t Source # 
Instance details

Defined in Mu.Server

t ~ s => FromRef (chn :: ServiceChain snm) ('PrimitiveRef t :: TypeRef snm) s Source # 
Instance details

Defined in Mu.Server

t ~ s => FromRef (chn :: ServiceChain snm) ('RegistryRef subject t last :: TypeRef snm) s Source # 
Instance details

Defined in Mu.Server

FromSchema sch sty t => FromRef (chn :: ServiceChain snm) ('SchemaRef sch sty :: TypeRef snm) t Source # 
Instance details

Defined in Mu.Server

class ToRef (chn :: ServiceChain snm) (ref :: TypeRef snm) (t :: Type) Source #

Defines whether a given type t can be turned into the TypeRef ref.

Instances

Instances details
(ToRef chn ref t, Maybe t ~ s) => ToRef (chn :: ServiceChain serviceName) ('OptionalRef ref :: TypeRef serviceName) s Source # 
Instance details

Defined in Mu.Server

(ToRef chn ref t, [t] ~ s) => ToRef (chn :: ServiceChain serviceName) ('ListRef ref :: TypeRef serviceName) s Source # 
Instance details

Defined in Mu.Server

MappingRight chn ref ~ t => ToRef (chn :: Mappings serviceName Type) ('ObjectRef ref :: TypeRef serviceName) t Source # 
Instance details

Defined in Mu.Server

t ~ s => ToRef (chn :: ServiceChain snm) ('PrimitiveRef t :: TypeRef snm) s Source # 
Instance details

Defined in Mu.Server

t ~ s => ToRef (chn :: ServiceChain snm) ('RegistryRef subject t last :: TypeRef snm) s Source # 
Instance details

Defined in Mu.Server

ToSchema sch sty t => ToRef (chn :: ServiceChain snm) ('SchemaRef sch sty :: TypeRef snm) t Source # 
Instance details

Defined in Mu.Server