[Haskell-cafe] Designing somewhat-type-safe RPC
oleg at okmij.org
oleg at okmij.org
Fri Jan 3 05:14:31 UTC 2014
The remote procedure call is obviously a partial function: first of
all, it may fail because of various network problems. It may also fail
if a client and a server disagree on the types of the arguments and
the results of the function call. For example, the client may think
that "Add" service adds integers while the server takes "Add" to sum
floats. There is nothing in the type system that can enforce the
agreement between distributed entities. So, we are liable to get
serialization/deserialization errors. It is inevitable that the
communication part is a big "Dynamic", and getting data from that
Dynamic may fail because of `type' errors (the data were serialized at
a different type than expected, or the data were corrupted in transit).
With these assumptions, the implementation is straightforward
(enclosed). Both the server and the client operations are typed (but
the middle part, the communication, is necessarily `untyped').
Incidentally, some three years ago I wrote a quite more advanced RPC
library, in OCaml. It didn't use any GADTs and other bleeding stuff
(first, OCaml did not have GADTs at the time; second, I'm minimalist).
It did much more, including semi-automatic request batching and some
fairly complex server programs including conditionals. It already does
more than X protocol and Java RPC. If I added server-side loops, it
would do even more. Alas, I didn't have time to come back to that
project since.
http://okmij.org/ftp/meta-future/meta-future.html
{-# LANGUAGE ExistentialQuantification #-}
module RPC where
import System.IO
import qualified Data.Map as M
-- identifiers of functions to call
type ServiceID = String
-- ------------------------------------------------------------------------
-- Server part
-- For simplicity, we use Read for deserialization and Show for
-- serialization. Binary would've been a better choice for both
-- All functions are supposed to be uncurried.
-- ServerFn essentially packs a function together with the serializer
-- of the result and the deserializer for arguments.
data ServerFn = forall a b. (Read a, Show b) => ServerFn (a->b)
type Services = M.Map ServiceID ServerFn
-- For simplicity, we handle just one request, which we read from
-- the handle. We write the result to stdio. It is easy to generalize:
-- write the result to an output handle and loop.
runServer :: Services -> Handle -> IO ()
runServer services h = do
service_id <- hGetLine h
putStrLn $ service_id
args <- hGetLine h
maybe (fail $ "no such service: " ++ service_id) (handle args) $
M.lookup service_id services
where
handle sargs (ServerFn f) = do
let args = read sargs
print $ f args
-- Sample services
services :: Services
services = M.fromList [
("Ping", ServerFn (\ () -> ())),
("Add", ServerFn (\ (x,y) -> x + y :: Int))
]
-- ------------------------------------------------------------------------
-- Client part
-- Stubs of server fn
-- ClientFn a b represents a function a->b to be executed by a server
data ClientFn a b = ClientFn ServiceID
ping :: ClientFn () ()
ping = ClientFn "Ping"
add :: ClientFn (Int,Int) Int
add = ClientFn "Add"
-- the set of functions is open; more can be added at any time
-- Do the remote function application
rpc :: (Show a, Read b) => Handle -> ClientFn a b -> a -> IO b
rpc h (ClientFn fid) x = do
hPutStrLn h fid
hPutStrLn h (show x)
-- read the result: currently stabbed
result_str <- return "stubbed"
return $ read result_str
-- ------------------------------------------------------------------------
-- Test
comm_file = "/tmp/connection"
main = do
h <- openFile comm_file WriteMode
-- send the request down to h. In this example, the return communication
-- is not implemented
res <- rpc h add (2::Int,3::Int)
-- don't look at the result: it this example, it is undefined
hClose h
h <- openFile comm_file ReadMode
runServer services h
More information about the Haskell-Cafe
mailing list