summaryrefslogtreecommitdiff
path: root/src/Remote
diff options
context:
space:
mode:
Diffstat (limited to 'src/Remote')
-rw-r--r--src/Remote/KRPC.hs75
-rw-r--r--src/Remote/KRPC/Method.hs61
-rw-r--r--src/Remote/KRPC/Protocol.hs6
3 files changed, 81 insertions, 61 deletions
diff --git a/src/Remote/KRPC.hs b/src/Remote/KRPC.hs
index 22dbf3aa..719b9a25 100644
--- a/src/Remote/KRPC.hs
+++ b/src/Remote/KRPC.hs
@@ -26,10 +26,12 @@ import Control.Monad
26import Control.Monad.Trans.Control 26import Control.Monad.Trans.Control
27import Control.Monad.IO.Class 27import Control.Monad.IO.Class
28import Data.BEncode 28import Data.BEncode
29import Data.ByteString.Char8 as BC
29import Data.List as L 30import Data.List as L
30import Data.Map as M 31import Data.Map as M
31import Data.Set as S 32import Data.Set as S
32import Data.Text as T 33import Data.Text as T
34import Data.Text.Encoding as T
33import Data.Typeable 35import Data.Typeable
34import Network 36import Network
35 37
@@ -47,14 +49,25 @@ type RemoteAddr = KRemoteAddr
47 49
48 50
49queryCall :: BEncodable param 51queryCall :: BEncodable param
52 => Extractable param
50 => KRemote -> KRemoteAddr 53 => KRemote -> KRemoteAddr
51 -> Method param result -> param -> IO () 54 -> Method param result -> param -> IO ()
52queryCall sock addr m arg = sendMessage q addr sock 55queryCall sock addr m arg = sendMessage q addr sock
53 where 56 where
54 q = kquery (L.head (methodName m)) [(L.head (methodParams m), toBEncode arg)] 57 q = kquery (methodName m) (mkVals (methodParams m) (injector arg))
58 mkVals = L.zip
59
60
61extractArgs :: [ParamName] -> Map ParamName BEncode -> Result [BEncode]
62extractArgs as d = mapM f as
63 where
64 f x | Just y <- M.lookup x d = return y
65 | otherwise = Left ("not found key " ++ BC.unpack x)
66{-# INLINE extractArgs #-}
55 67
56-- TODO check scheme 68-- TODO check scheme
57getResult :: BEncodable result 69getResult :: BEncodable result
70 => Extractable result
58 => KRemote -> KRemoteAddr 71 => KRemote -> KRemoteAddr
59 -> Method param result -> IO result 72 -> Method param result -> IO result
60getResult sock addr m = do 73getResult sock addr m = do
@@ -62,15 +75,9 @@ getResult sock addr m = do
62 case resp of 75 case resp of
63 Left e -> throw (RPCException e) 76 Left e -> throw (RPCException e)
64 Right (respVals -> dict) -> do 77 Right (respVals -> dict) -> do
65 let valName = L.head (methodVals m) 78 case extractArgs (methodVals m) dict >>= extractor of
66 case M.lookup valName dict of 79 Right vals -> return vals
67 Just val | Right res <- fromBEncode val -> return res 80 Left e -> throw (RPCException (ProtocolError (T.pack e)))
68 Nothing -> throw (RPCException (ProtocolError msg))
69 where
70 msg = T.concat
71 [ "Unable to find return value: ", T.pack (show valName), "\n"
72 , "in response: ", T.pack (show dict)
73 ]
74 81
75-- TODO async call 82-- TODO async call
76-- | Makes remote procedure call. Throws RPCException if server 83-- | Makes remote procedure call. Throws RPCException if server
@@ -78,6 +85,7 @@ getResult sock addr m = do
78-- 85--
79call :: (MonadBaseControl IO host, MonadIO host) 86call :: (MonadBaseControl IO host, MonadIO host)
80 => (BEncodable param, BEncodable result) 87 => (BEncodable param, BEncodable result)
88 => (Extractable param, Extractable result)
81 => RemoteAddr 89 => RemoteAddr
82 -> Method param result 90 -> Method param result
83 -> param 91 -> param
@@ -92,6 +100,7 @@ newtype Async result = Async { waitResult :: IO result }
92-- TODO document errorneous usage 100-- TODO document errorneous usage
93async :: MonadIO host 101async :: MonadIO host
94 => (BEncodable param, BEncodable result) 102 => (BEncodable param, BEncodable result)
103 => (Extractable param, Extractable result)
95 => RemoteAddr 104 => RemoteAddr
96 -> Method param result 105 -> Method param result
97 -> param 106 -> param
@@ -104,52 +113,50 @@ async addr m arg = do
104 113
105await :: MonadIO host => Async result -> host result 114await :: MonadIO host => Async result -> host result
106await = liftIO . waitResult 115await = liftIO . waitResult
116{-# INLINE await #-}
117
107 118
108type HandlerBody remote = (BEncode -> remote (Result BEncode), KResponseScheme) 119type HandlerBody remote = KQuery -> remote (Either KError KResponse)
109 120
110type MethodHandler remote = (KQueryScheme, HandlerBody remote) 121type MethodHandler remote = (MethodName, HandlerBody remote)
111 122
112 123
113-- we can safely erase types in (==>) 124-- we can safely erase types in (==>)
114(==>) :: forall (remote :: * -> *) (param :: *) (result :: *). 125(==>) :: forall (remote :: * -> *) (param :: *) (result :: *).
115 (BEncodable param, BEncodable result) 126 (BEncodable param, BEncodable result)
127 => (Extractable param, Extractable result)
116 => Monad remote 128 => Monad remote
117 => Method param result 129 => Method param result
118 -> (param -> remote result) 130 -> (param -> remote result)
119 -> MethodHandler remote 131 -> MethodHandler remote
120m ==> body = (methodQueryScheme m, (newbody, methodRespScheme m)) 132{-# INLINE (==>) #-}
133m ==> body = (methodName m, newbody)
121 where 134 where
122 newbody x = case fromBEncode x of 135 {-# INLINE newbody #-}
123 Right a -> liftM (Right . toBEncode) (body a) 136 newbody q =
124 Left e -> return (Left e) 137 case extractArgs (methodParams m) (queryArgs q) >>= extractor of
138 Left e -> return (Left (ProtocolError (T.pack e)))
139 Right a -> do
140 r <- body a
141 return (Right (kresponse (mkVals (methodVals m) (injector r))))
125 142
143 mkVals :: [ValName] -> [BEncode] -> [(ValName, BEncode)]
144 mkVals = L.zip
126 145
127-- TODO: allow forkIO 146-- TODO: allow forkIO
128-- TODO: allow overloading
129server :: (MonadBaseControl IO remote, MonadIO remote) 147server :: (MonadBaseControl IO remote, MonadIO remote)
130 => PortNumber 148 => PortNumber
131 -> [MethodHandler remote] 149 -> [MethodHandler remote]
132 -> remote () 150 -> remote ()
133server servport handlers = do 151server servport handlers = do
134 remoteServer servport $ \_ q -> do 152 remoteServer servport $ \_ q -> do
135 case dispatch (scheme q) of 153 case dispatch (queryMethod q) of
136 Nothing -> return (Left (MethodUnknown "method")) 154 Nothing -> return $ Left $ MethodUnknown (decodeUtf8 (queryMethod q))
137 Just (m, rsc) -> do 155 Just m -> invoke m q
138 let arg = snd (L.head (M.toList (queryArgs q)))
139
140 res <- invoke m arg
141 let valName = L.head (S.toList (rscVals rsc))
142 return $ bimap (ProtocolError . T.pack)
143 (kresponse . return . (,) valName) res
144 where 156 where
145 handlerMap = M.fromList handlers 157 handlerMap = M.fromList handlers
146 158 dispatch s = M.lookup s handlerMap
147-- dispatch :: KQueryScheme -> MethodHandler remote 159 invoke m q = m q
148 dispatch s | Just m <- M.lookup s handlerMap = return m
149 | otherwise = Nothing
150
151-- invoke :: MethodHandler remote -> BEncode -> remote BEncode
152 invoke m args = m args
153 160
154 bimap f _ (Left x) = Left (f x) 161 bimap f _ (Left x) = Left (f x)
155 bimap _ g (Right x) = Right (g x) \ No newline at end of file 162 bimap _ g (Right x) = Right (g x) \ No newline at end of file
diff --git a/src/Remote/KRPC/Method.hs b/src/Remote/KRPC/Method.hs
index 420ceacf..8aa6ddc9 100644
--- a/src/Remote/KRPC/Method.hs
+++ b/src/Remote/KRPC/Method.hs
@@ -6,6 +6,7 @@
6-- Portability : portable 6-- Portability : portable
7-- 7--
8{-# LANGUAGE OverloadedStrings #-} 8{-# LANGUAGE OverloadedStrings #-}
9{-# LANGUAGE FlexibleInstances, UndecidableInstances #-}
9module Remote.KRPC.Method 10module Remote.KRPC.Method
10 ( Method(methodName, methodParams, methodVals) 11 ( Method(methodName, methodParams, methodVals)
11 , methodQueryScheme, methodRespScheme 12 , methodQueryScheme, methodRespScheme
@@ -14,13 +15,17 @@ module Remote.KRPC.Method
14 , method 15 , method
15 16
16 -- * Predefined methods 17 -- * Predefined methods
17 , idM, composeM 18 , idM
19
20 -- * Internal
21 , Extractable(..)
18 ) where 22 ) where
19 23
20import Prelude hiding ((.), id) 24import Prelude hiding ((.), id)
21import Control.Applicative 25import Control.Applicative
22import Control.Category 26import Control.Category
23import Control.Monad 27import Control.Monad
28import Data.BEncode
24import Data.ByteString as B 29import Data.ByteString as B
25import Data.List as L 30import Data.List as L
26import Data.Set as S 31import Data.Set as S
@@ -38,7 +43,7 @@ import Remote.KRPC.Protocol
38-- 43--
39data Method param result = Method { 44data Method param result = Method {
40 -- | Name used in query and 45 -- | Name used in query and
41 methodName :: [MethodName] 46 methodName :: MethodName
42 47
43 -- | Description of each parameter in /right to left/ order. 48 -- | Description of each parameter in /right to left/ order.
44 , methodParams :: [ParamName] 49 , methodParams :: [ParamName]
@@ -46,17 +51,8 @@ data Method param result = Method {
46 -- | Description of each return value in /right to left/ order. 51 -- | Description of each return value in /right to left/ order.
47 , methodVals :: [ValName] 52 , methodVals :: [ValName]
48 } 53 }
49
50instance Category Method where
51 {-# SPECIALIZE instance Category Method #-}
52 id = idM
53 {-# INLINE id #-}
54
55 (.) = composeM
56 {-# INLINE (.) #-}
57
58methodQueryScheme :: Method a b -> KQueryScheme 54methodQueryScheme :: Method a b -> KQueryScheme
59methodQueryScheme = KQueryScheme <$> B.intercalate "." . methodName 55methodQueryScheme = KQueryScheme <$> methodName
60 <*> S.fromList . methodParams 56 <*> S.fromList . methodParams
61{-# INLINE methodQueryScheme #-} 57{-# INLINE methodQueryScheme #-}
62 58
@@ -75,19 +71,32 @@ idM :: Method a a
75idM = method "id" ["x"] ["y"] 71idM = method "id" ["x"] ["y"]
76{-# INLINE idM #-} 72{-# INLINE idM #-}
77 73
78-- | Pipelining of two or more methods. 74method :: MethodName -> [ParamName] -> [ValName] -> Method param result
79-- 75method = Method
80-- NOTE: composed methods will work only with this implementation of 76{-# INLINE method #-}
81-- KRPC, so both server and client should use this implementation,
82-- otherwise you more likely get the 'ProtocolError'.
83--
84composeM :: Method b c -> Method a b -> Method a c
85composeM g h = Method (methodName g ++ methodName h)
86 (methodParams h)
87 (methodVals g)
88{-# INLINE composeM #-}
89 77
90 78
91method :: MethodName -> [ParamName] -> [ValName] -> Method param result 79
92method name = Method [name] 80class Extractable a where
93{-# INLINE method #-} \ No newline at end of file 81 injector :: a -> [BEncode]
82 extractor :: [BEncode] -> Result a
83
84instance (BEncodable a, BEncodable b) => Extractable (a, b) where
85 {- SPECIALIZE instance (BEncodable a, BEncodable b) => Extractable (a, b) -}
86 injector (a, b) = [toBEncode a, toBEncode b]
87 {-# INLINE injector #-}
88
89 extractor [a, b] = (,) <$> fromBEncode a <*> fromBEncode b
90 extractor _ = decodingError "unable to match pair"
91 {-# INLINE extractor #-}
92{-
93instance BEncodable a => Extractable a where
94 {-# SPECIALIZE instance BEncodable a => Extractable a #-}
95
96 injector x = [toBEncode x]
97 {-# INLINE injector #-}
98
99 extractor [x] = fromBEncode x
100 extractor _ = decodingError "unable to match single value"
101 {-# INLINE extractor #-}
102-} \ No newline at end of file
diff --git a/src/Remote/KRPC/Protocol.hs b/src/Remote/KRPC/Protocol.hs
index 625aba25..98674c51 100644
--- a/src/Remote/KRPC/Protocol.hs
+++ b/src/Remote/KRPC/Protocol.hs
@@ -74,7 +74,7 @@ class KMessage message scheme | message -> scheme where
74 validate = (==) . scheme 74 validate = (==) . scheme
75 {-# INLINE validate #-} 75 {-# INLINE validate #-}
76 76
77 77-- TODO Text -> ByteString
78-- TODO document that it is and how transferred 78-- TODO document that it is and how transferred
79data KError 79data KError
80 -- | Some error doesn't fit in any other category. 80 -- | Some error doesn't fit in any other category.
@@ -213,9 +213,13 @@ type KRemote = Socket
213withRemote :: (MonadBaseControl IO m, MonadIO m) => (KRemote -> m a) -> m a 213withRemote :: (MonadBaseControl IO m, MonadIO m) => (KRemote -> m a) -> m a
214withRemote = bracket (liftIO (socket AF_INET Datagram defaultProtocol)) 214withRemote = bracket (liftIO (socket AF_INET Datagram defaultProtocol))
215 (liftIO . sClose) 215 (liftIO . sClose)
216{-# SPECIALIZE withRemote :: (KRemote -> IO a) -> IO a #-}
217
216 218
217maxMsgSize :: Int 219maxMsgSize :: Int
218maxMsgSize = 16 * 1024 220maxMsgSize = 16 * 1024
221{-# INLINE maxMsgSize #-}
222
219 223
220-- TODO eliminate toStrict 224-- TODO eliminate toStrict
221sendMessage :: BEncodable msg => msg -> KRemoteAddr -> KRemote -> IO () 225sendMessage :: BEncodable msg => msg -> KRemoteAddr -> KRemote -> IO ()