Z-MessagePack-0.3.0.0: MessagePack
Copyright(c) Dong Han 2019
LicenseBSD
Maintainerwinterland1989@gmail.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Z.IO.RPC.MessagePack

Description

This module provides MessagePack-RPC implementation.

-- server
import Z.IO.RPC.MessagePack
import Z.IO.Network
import Z.IO
import qualified Z.Data.Text as T

serveRPC (startTCPServer defaultTCPServerConfig) . simpleRouter $
 [ ("foo", CallHandler $ \ (req :: Int) -> do
     return (req + 1))
 , ("bar", NotifyHandler $ \ (req :: T.Text) -> do
     printStd (req <> "world"))
 ]

-- client
import Z.IO.RPC.MessagePack
import Z.IO.Network
import Z.IO
import qualified Z.Data.Text as T

withResource (initTCPClient defaultTCPClientConfig) $ \ uvs -> do
    c <- rpcClient uvs
    call @Int @Int c "foo" 1
    call @T.Text @T.Text c "bar" "hello"
Synopsis

Documentation

rpcClient :: (Input dev, Output dev) => dev -> IO Client Source #

Open a RPC client from input/output device.

rpcClient' Source #

Arguments

:: (Input i, Output o) 
=> i 
-> o 
-> Int

recv buffer size

-> Int

send buffer size

-> IO Client 

Open a RPC client with more control.

call :: (MessagePack req, MessagePack res) => Client -> Text -> req -> IO res Source #

Send a single RPC call and get result.

notify :: MessagePack req => Client -> Text -> req -> IO () Source #

Send a single notification RPC call without getting result.

callPipeline :: HasCallStack => MessagePack req => Client -> Text -> req -> IO PipelineId Source #

Make a call inside a pipeline, which will be sent in batch when execPipeline.

 ...
 fooId <- callPipeline client "foo" $ ...
 barId <- callPipeline client "bar" $ ...
 notifyPipeline client "qux" $ ...

 r <- execPipeline client

 fooResult <- fetchPipeline fooId r
 barResult <- fetchPipeline barId r

notifyPipeline :: HasCallStack => MessagePack req => Client -> Text -> req -> IO () Source #

Make a notify inside a pipeline, which will be sent in batch when execPipeline.

Notify calls doesn't affect execution's result.

data RPCException Source #

Exception thrown when remote endpoint return errors.

execPipeline :: HasCallStack => Client -> IO PipelineResult Source #

Sent request in batch and get result in a map identified by PipelineId.

fetchPipeline :: HasCallStack => MessagePack res => PipelineId -> PipelineResult -> IO res Source #

Use the PipelineId returned when callPipeline to fetch call's result.

type ServerLoop = (UVStream -> IO ()) -> IO () Source #

data ServerHandler where Source #

Constructors

CallHandler :: (MessagePack req, MessagePack res) => (req -> IO res) -> ServerHandler 
NotifyHandler :: MessagePack req => (req -> IO ()) -> ServerHandler 

simpleRouter :: [(Text, ServerHandler)] -> ServerService Source #

Simple router using FlatMap, lookup name in O(log(N)).

import Z.IO.PRC.MessagePack
import Z.IO.Network
import Z.IO

serveRPC (startTCPServer defaultTCPServerConfig) . simpleRouter $
 [ ("foo", CallHandler $ \ req -> do
     ... )
 , ("bar", CallHandler $ \ req -> do
     ... )
 ]

serveRPC :: ServerLoop -> ServerService -> IO () Source #

Serve a RPC service.

serveRPC' Source #

Arguments

:: ServerLoop 
-> Int

recv buffer size

-> Int

send buffer size

-> ServerService 
-> IO () 

Serve a RPC service with more control.