curryer-rpc-0.3.2: Fast, Haskell RPC
Safe HaskellSafe-Inferred
LanguageHaskell2010

Network.RPC.Curryer.Server

Synopsis

Documentation

msgSerialise :: Serialise a => a -> ByteString Source #

msgDeserialise :: forall s. Serialise s => ByteString -> Either WineryException s Source #

data Locking a Source #

Constructors

Locking (MVar ()) a 

newLock :: a -> IO (Locking a) Source #

withLock :: Locking a -> (a -> IO b) -> IO b Source #

data Envelope Source #

Instances

Instances details
Generic Envelope Source # 
Instance details

Defined in Network.RPC.Curryer.Server

Associated Types

type Rep Envelope :: Type -> Type #

Methods

from :: Envelope -> Rep Envelope x #

to :: Rep Envelope x -> Envelope #

Show Envelope Source # 
Instance details

Defined in Network.RPC.Curryer.Server

type Rep Envelope Source # 
Instance details

Defined in Network.RPC.Curryer.Server

type Rep Envelope = D1 ('MetaData "Envelope" "Network.RPC.Curryer.Server" "curryer-rpc-0.3.2-inplace" 'False) (C1 ('MetaCons "Envelope" 'PrefixI 'True) ((S1 ('MetaSel ('Just "envFingerprint") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Fingerprint) :*: S1 ('MetaSel ('Just "envMessageType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MessageType)) :*: (S1 ('MetaSel ('Just "envMsgId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UUID) :*: S1 ('MetaSel ('Just "envPayload") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BinaryMessage))))

data MessageType Source #

Internal type used to mark envelope types.

Instances

Instances details
Generic MessageType Source # 
Instance details

Defined in Network.RPC.Curryer.Server

Associated Types

type Rep MessageType :: Type -> Type #

Show MessageType Source # 
Instance details

Defined in Network.RPC.Curryer.Server

Serialise MessageType Source # 
Instance details

Defined in Network.RPC.Curryer.Server

Methods

schemaGen :: Proxy MessageType -> SchemaGen Schema

toBuilder :: MessageType -> Builder

extractor :: Extractor MessageType

decodeCurrent :: Decoder MessageType

bundleSerialise :: BundleSerialise MessageType

type Rep MessageType Source # 
Instance details

Defined in Network.RPC.Curryer.Server

type Rep MessageType = D1 ('MetaData "MessageType" "Network.RPC.Curryer.Server" "curryer-rpc-0.3.2-inplace" 'False) ((C1 ('MetaCons "RequestMessage" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TimeoutMicroseconds)) :+: C1 ('MetaCons "ResponseMessage" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TimeoutResponseMessage" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExceptionResponseMessage" 'PrefixI 'False) (U1 :: Type -> Type)))

type RequestHandlers serverState = [RequestHandler serverState] Source #

A list of RequestHandlers.

data RequestHandler serverState where Source #

Data types for server-side request handlers, in synchronous (client waits for return value) and asynchronous (client does not wait for return value) forms.

Constructors

RequestHandler :: forall a b serverState. (Serialise a, Serialise b) => (ConnectionState serverState -> a -> IO b) -> RequestHandler serverState

create a request handler with a response

AsyncRequestHandler :: forall a serverState. Serialise a => (ConnectionState serverState -> a -> IO ()) -> RequestHandler serverState

create an asynchronous request handler where the client does not expect nor await a response

data ConnectionState a Source #

Server state sent in via serve and passed to RequestHandlers.

Constructors

ConnectionState 

sendMessage :: Serialise a => Locking Socket -> a -> IO () Source #

Used by server-side request handlers to send additional messages to the client. This is useful for sending asynchronous responses to the client outside of the normal request-response flow. The locking socket can be found in the ConnectionState when a request handler is called.

newtype UUID Source #

Constructors

UUID 

Fields

Instances

Instances details
Show UUID Source # 
Instance details

Defined in Network.RPC.Curryer.Server

Methods

showsPrec :: Int -> UUID -> ShowS #

show :: UUID -> String #

showList :: [UUID] -> ShowS #

Binary UUID Source # 
Instance details

Defined in Network.RPC.Curryer.Server

Methods

put :: UUID -> Put #

get :: Get UUID #

putList :: [UUID] -> Put #

Eq UUID Source # 
Instance details

Defined in Network.RPC.Curryer.Server

Methods

(==) :: UUID -> UUID -> Bool #

(/=) :: UUID -> UUID -> Bool #

Hashable UUID Source # 
Instance details

Defined in Network.RPC.Curryer.Server

Methods

hashWithSalt :: Int -> UUID -> Int

hash :: UUID -> Int

Serialise UUID Source # 
Instance details

Defined in Network.RPC.Curryer.Server

Methods

schemaGen :: Proxy UUID -> SchemaGen Schema

toBuilder :: UUID -> Builder

extractor :: Extractor UUID

decodeCurrent :: Decoder UUID

bundleSerialise :: BundleSerialise UUID

data ConnectionError Source #

Errors from remote calls.

Instances

Instances details
Generic ConnectionError Source # 
Instance details

Defined in Network.RPC.Curryer.Server

Associated Types

type Rep ConnectionError :: Type -> Type #

Show ConnectionError Source # 
Instance details

Defined in Network.RPC.Curryer.Server

Eq ConnectionError Source # 
Instance details

Defined in Network.RPC.Curryer.Server

Serialise ConnectionError Source # 
Instance details

Defined in Network.RPC.Curryer.Server

Methods

schemaGen :: Proxy ConnectionError -> SchemaGen Schema

toBuilder :: ConnectionError -> Builder

extractor :: Extractor ConnectionError

decodeCurrent :: Decoder ConnectionError

bundleSerialise :: BundleSerialise ConnectionError

type Rep ConnectionError Source # 
Instance details

Defined in Network.RPC.Curryer.Server

type Rep ConnectionError = D1 ('MetaData "ConnectionError" "Network.RPC.Curryer.Server" "curryer-rpc-0.3.2-inplace" 'False) (C1 ('MetaCons "CodecError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: (C1 ('MetaCons "TimeoutError" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExceptionError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))

type BParser a = Parser Word8 IO a Source #

type NewMessageHandler req resp = req -> IO resp Source #

serve :: RequestHandlers s -> s -> HostAddr -> PortNumber -> Maybe (MVar SockAddr) -> IO Bool Source #

Listen for new connections and handle requests which are passed the server state s. The MVar SockAddr can be be optionally used to know when the server is ready for processing requests.

openEnvelope :: forall s. (Serialise s, Typeable s) => Envelope -> Maybe s Source #

deserialiseOnly :: forall s. Serialise s => ByteString -> Either WineryException s Source #

matchEnvelope :: forall a b s. (Serialise a, Serialise b, Typeable b) => Envelope -> (ConnectionState s -> a -> IO b) -> Maybe (ConnectionState s -> a -> IO b, a) Source #

serverEnvelopeHandler :: Locking Socket -> RequestHandlers s -> s -> Envelope -> IO () Source #

Called by serve to process incoming envelope requests. Never returns, so use async to spin it off on another thread.

sendEnvelope :: Envelope -> Locking Socket -> IO () Source #

Orphan instances

Serialise Fingerprint Source # 
Instance details

Methods

schemaGen :: Proxy Fingerprint -> SchemaGen Schema

toBuilder :: Fingerprint -> Builder

extractor :: Extractor Fingerprint

decodeCurrent :: Decoder Fingerprint

bundleSerialise :: BundleSerialise Fingerprint