module Network.MessagePackRpc.Server (
RpcMethod,
RpcMethodType(..),
fun,
serve,
) where
import Control.Applicative
import Control.Concurrent
import Control.DeepSeq
import Control.Exception as E
import Data.Enumerator
import Data.Enumerator.Binary
import Control.Monad
import Control.Monad.IO.Class
import Data.Attoparsec.Enumerator
import qualified Data.ByteString.Lazy as BL
import Data.Maybe
import Data.MessagePack
import Network
import System.IO
import Prelude hiding (catch)
bufferSize :: Integer
bufferSize = 4096
type RpcMethod = [Object] -> IO Object
class RpcMethodType f where
toRpcMethod :: f -> RpcMethod
instance OBJECT o => RpcMethodType (IO o) where
toRpcMethod m = \[] -> toObject <$> m
instance (OBJECT o, RpcMethodType r) => RpcMethodType (o -> r) where
toRpcMethod f = \(x:xs) -> toRpcMethod (f $! fromObject' x) xs
fromObject' :: OBJECT o => Object -> o
fromObject' o =
case tryFromObject o of
Left err -> error $ "argument type error: " ++ err
Right r -> r
fun :: RpcMethodType f => f -> RpcMethod
fun = toRpcMethod
serve :: Int
-> [(String, RpcMethod)]
-> IO ()
serve port methods = withSocketsDo $ do
sock <- listenOn (PortNumber $ fromIntegral port)
forever $ do
(h, host, hostport) <- accept sock
forkIO $
(processRequests h `finally` hClose h) `catches`
[ Handler $ \e ->
case e of
ParseError ["demandInput"] _ -> return ()
_ -> hPutStrLn stderr $ host ++ ":" ++ show hostport ++ ": " ++ show e
, Handler $ \e ->
hPutStrLn stderr $ host ++ ":" ++ show hostport ++ ": " ++ show (e :: SomeException)]
where
processRequests h =
run_ $ enumHandle bufferSize h $$ forever $ processRequest h
processRequest h = do
(rtype, msgid, method, args) <- iterParser get
liftIO $ do
resp <- try $ getResponse rtype method args
case resp of
Left err ->
BL.hPutStr h $ pack (1 :: Int, msgid :: Int, show (err :: SomeException), ())
Right ret ->
BL.hPutStr h $ pack (1 :: Int, msgid :: Int, (), ret)
hFlush h
getResponse rtype method args = do
when (rtype /= (0 :: Int)) $
fail "request type is not 0"
r <- callMethod (method :: String) (args :: [Object])
r `deepseq` return r
callMethod methodName args =
case lookup methodName methods of
Nothing ->
fail $ "method '" ++ methodName ++ "' not found"
Just method ->
method args