| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Network.RPC.Curryer.Server
Contents
Synopsis
- traceBytes :: Applicative f => String -> ByteString -> f ()
- msgSerialise :: Serialise a => a -> ByteString
- msgDeserialise :: forall s. Serialise s => ByteString -> Either WineryException s
- data Locking a = Locking (MVar ()) a
- newLock :: a -> IO (Locking a)
- withLock :: Locking a -> (a -> IO b) -> IO b
- lockless :: Locking a -> a
- type Timeout = Word32
- type BinaryMessage = ByteString
- data Envelope = Envelope {}
- type TimeoutMicroseconds = Int
- data MessageType
- type RequestHandlers serverState = [RequestHandler serverState]
- data RequestHandler serverState where
- RequestHandler :: forall a b serverState. (Serialise a, Serialise b) => (ConnectionState serverState -> a -> IO b) -> RequestHandler serverState
- AsyncRequestHandler :: forall a serverState. Serialise a => (ConnectionState serverState -> a -> IO ()) -> RequestHandler serverState
- data ConnectionState a = ConnectionState {}
- sendMessage :: Serialise a => Locking Socket -> a -> IO ()
- newtype UUID = UUID {}
- data ConnectionError
- data TimeoutException = TimeoutException
- type HostAddr = (Word8, Word8, Word8, Word8)
- allHostAddrs :: HostAddr
- localHostAddr :: HostAddr
- msgTypeP :: Parser IO Word8 MessageType
- envelopeP :: Parser IO Word8 Envelope
- encodeEnvelope :: Envelope -> ByteString
- fingerprintP :: Parser IO Word8 Fingerprint
- word64P :: Parser IO Word8 Word64
- word32P :: Parser IO Word8 Word32
- uuidP :: Parser IO Word8 UUID
- type NewConnectionHandler msg = IO (Maybe msg)
- type NewMessageHandler req resp = req -> IO resp
- serve :: RequestHandlers s -> s -> HostAddr -> PortNumber -> Maybe (MVar SockAddr) -> IO Bool
- openEnvelope :: forall s. (Serialise s, Typeable s) => Envelope -> Maybe s
- deserialiseOnly :: forall s. Serialise s => ByteString -> Either WineryException s
- matchEnvelope :: forall a b s. (Serialise a, Serialise b, Typeable b) => Envelope -> (ConnectionState s -> a -> IO b) -> Maybe (ConnectionState s -> a -> IO b, a)
- serverEnvelopeHandler :: Locking Socket -> RequestHandlers s -> s -> Envelope -> IO ()
- type EnvelopeHandler = Envelope -> IO ()
- drainSocketMessages :: Socket -> EnvelopeHandler -> IO ()
- sendEnvelope :: Envelope -> Locking Socket -> IO ()
- fingerprint :: Typeable a => a -> Fingerprint
- fromArray :: Array Word8 -> ByteString
Documentation
traceBytes :: Applicative f => String -> ByteString -> f () Source #
msgSerialise :: Serialise a => a -> ByteString Source #
msgDeserialise :: forall s. Serialise s => ByteString -> Either WineryException s Source #
type BinaryMessage = ByteString Source #
Constructors
| Envelope | |
Fields
| |
Instances
| Show Envelope Source # | |
| Generic Envelope Source # | |
| type Rep Envelope Source # | |
Defined in Network.RPC.Curryer.Server type Rep Envelope = D1 ('MetaData "Envelope" "Network.RPC.Curryer.Server" "curryer-rpc-0.2.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)))) | |
type TimeoutMicroseconds = Int Source #
data MessageType Source #
Internal type used to mark envelope types.
Constructors
| RequestMessage TimeoutMicroseconds | |
| ResponseMessage | |
| TimeoutResponseMessage | |
| ExceptionResponseMessage |
Instances
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 | |
Fields | |
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.
data ConnectionError Source #
Errors from remote calls.
Constructors
| CodecError String | |
| TimeoutError | |
| ExceptionError String |
Instances
data TimeoutException Source #
Constructors
| TimeoutException |
Instances
| Show TimeoutException Source # | |
Defined in Network.RPC.Curryer.Server Methods showsPrec :: Int -> TimeoutException -> ShowS # show :: TimeoutException -> String # showList :: [TimeoutException] -> ShowS # | |
| Exception TimeoutException Source # | |
Defined in Network.RPC.Curryer.Server Methods toException :: TimeoutException -> SomeException # | |
encodeEnvelope :: Envelope -> ByteString Source #
type NewConnectionHandler msg = IO (Maybe msg) 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.
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.
type EnvelopeHandler = Envelope -> IO () Source #
drainSocketMessages :: Socket -> EnvelopeHandler -> IO () Source #
fingerprint :: Typeable a => a -> Fingerprint Source #
Orphan instances
| Generic Fingerprint Source # | |
Associated Types type Rep Fingerprint :: Type -> Type # | |
| Serialise Fingerprint Source # | |
Methods schemaGen :: Proxy Fingerprint -> SchemaGen Schema # toBuilder :: Fingerprint -> Builder # extractor :: Extractor Fingerprint # | |