-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Fast, Haskell RPC -- -- Haskell-to-Haskell RPC using Winery serialization. @package curryer-rpc @version 0.3.3 module Network.RPC.Curryer.StreamlyAdditions acceptorOnAddr :: MonadIO m => [(SocketOption, Int)] -> Maybe (MVar SockAddr) -> Unfold m ((Word8, Word8, Word8, Word8), PortNumber) Socket acceptor :: MonadIO m => Maybe (MVar SockAddr) -> Unfold m (Int, SockSpec, SockAddr) Socket listenTuples :: MonadIO m => Maybe (MVar SockAddr) -> Unfold m (Int, SockSpec, SockAddr) (Socket, SockAddr) initListener :: Int -> SockSpec -> SockAddr -> IO Socket module Network.RPC.Curryer.Server 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 -> Locking 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 :: !Fingerprint -> !MessageType -> !UUID -> !BinaryMessage -> Envelope [envFingerprint] :: Envelope -> !Fingerprint [envMessageType] :: Envelope -> !MessageType [envMsgId] :: Envelope -> !UUID [envPayload] :: Envelope -> !BinaryMessage type TimeoutMicroseconds = Int -- | Internal type used to mark envelope types. data MessageType RequestMessage :: TimeoutMicroseconds -> MessageType ResponseMessage :: MessageType TimeoutResponseMessage :: MessageType ExceptionResponseMessage :: MessageType -- | A list of RequestHandlers. type RequestHandlers serverState = [RequestHandler serverState] -- | Data types for server-side request handlers, in synchronous (client -- waits for return value) and asynchronous (client does not wait for -- return value) forms. data RequestHandler serverState -- | create a request handler with a response [RequestHandler] :: forall a b serverState. (Serialise a, Serialise b) => (ConnectionState serverState -> a -> IO b) -> RequestHandler serverState -- | create an asynchronous request handler where the client does not -- expect nor await a response [AsyncRequestHandler] :: forall a serverState. Serialise a => (ConnectionState serverState -> a -> IO ()) -> RequestHandler serverState -- | Server state sent in via serve and passed to -- RequestHandlers. data ConnectionState a ConnectionState :: a -> Locking Socket -> ConnectionState a [connectionServerState] :: ConnectionState a -> a [connectionSocket] :: ConnectionState a -> Locking Socket -- | 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. sendMessage :: Serialise a => Locking Socket -> a -> IO () newtype UUID UUID :: UUID -> UUID [_unUUID] :: UUID -> UUID -- | Errors from remote calls. data ConnectionError CodecError :: String -> ConnectionError TimeoutError :: ConnectionError ExceptionError :: String -> ConnectionError data TimeoutException TimeoutException :: TimeoutException type HostAddr = (Word8, Word8, Word8, Word8) type BParser a = Parser Word8 IO a allHostAddrs :: HostAddr localHostAddr :: HostAddr msgTypeP :: BParser MessageType envelopeP :: BParser Envelope encodeEnvelope :: Envelope -> ByteString fingerprintP :: BParser Fingerprint word64P :: BParser Word64 word32P :: BParser Word32 uuidP :: BParser UUID type NewConnectionHandler msg = IO (Maybe msg) type NewMessageHandler req resp = req -> IO resp -- | 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. 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) -- | Called by serve to process incoming envelope requests. Never -- returns, so use async to spin it off on another thread. 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 instance Codec.Winery.Class.Serialise Network.RPC.Curryer.Server.MessageType instance GHC.Show.Show Network.RPC.Curryer.Server.MessageType instance GHC.Generics.Generic Network.RPC.Curryer.Server.MessageType instance Data.Hashable.Class.Hashable Network.RPC.Curryer.Server.UUID instance Data.Binary.Class.Binary Network.RPC.Curryer.Server.UUID instance GHC.Classes.Eq Network.RPC.Curryer.Server.UUID instance GHC.Show.Show Network.RPC.Curryer.Server.UUID instance GHC.Show.Show Network.RPC.Curryer.Server.Envelope instance GHC.Generics.Generic Network.RPC.Curryer.Server.Envelope instance Codec.Winery.Class.Serialise Network.RPC.Curryer.Server.ConnectionError instance GHC.Classes.Eq Network.RPC.Curryer.Server.ConnectionError instance GHC.Show.Show Network.RPC.Curryer.Server.ConnectionError instance GHC.Generics.Generic Network.RPC.Curryer.Server.ConnectionError instance GHC.Show.Show Network.RPC.Curryer.Server.TimeoutException instance Codec.Winery.Class.Serialise GHC.Fingerprint.Type.Fingerprint instance GHC.Exception.Type.Exception Network.RPC.Curryer.Server.TimeoutException instance Codec.Winery.Class.Serialise Network.RPC.Curryer.Server.UUID module Network.RPC.Curryer.Client type SyncMap = Map UUID (MVar (Either ConnectionError BinaryMessage), UTCTime) -- | Represents a remote connection to server. data Connection Connection :: Locking Socket -> Async () -> SyncMap -> Connection [_conn_sockLock] :: Connection -> Locking Socket [_conn_asyncThread] :: Connection -> Async () [_conn_syncmap] :: Connection -> SyncMap -- | Function handlers run on the client, triggered by the server- useful -- for asynchronous callbacks. data ClientAsyncRequestHandler [ClientAsyncRequestHandler] :: forall a. Serialise a => (a -> IO ()) -> ClientAsyncRequestHandler type ClientAsyncRequestHandlers = [ClientAsyncRequestHandler] -- | Connects to a remote server with specific async callbacks registered. connect :: ClientAsyncRequestHandlers -> HostAddr -> PortNumber -> IO Connection -- | Close the connection and release all connection resources. close :: Connection -> IO () -- | async thread for handling client-side incoming messages- dispatch to -- proper waiting thread or asynchronous notifications handler clientAsync :: Socket -> SyncMap -> ClientAsyncRequestHandlers -> IO () consumeResponse :: UUID -> Map UUID (MVar a, b) -> a -> IO () -- | handles envelope responses from server- timeout from ths server is -- ignored, but perhaps that's proper for trusted servers- the server -- expects the client to process all async requests clientEnvelopeHandler :: ClientAsyncRequestHandlers -> Locking Socket -> SyncMap -> Envelope -> IO () -- | Basic remote function call via data type and return value. call :: (Serialise request, Serialise response) => Connection -> request -> IO (Either ConnectionError response) -- | Send a request to the remote server and returns a response but with -- the possibility of a timeout after n microseconds. callTimeout :: (Serialise request, Serialise response) => Maybe Int -> Connection -> request -> IO (Either ConnectionError response) -- | Call a remote function but do not expect a response from the server. asyncCall :: Serialise request => Connection -> request -> IO (Either ConnectionError ())