diff options
-rw-r--r-- | examples/Client.hs | 2 | ||||
-rw-r--r-- | examples/Server.hs | 4 | ||||
-rw-r--r-- | examples/Shared.hs | 29 | ||||
-rw-r--r-- | src/Remote/KRPC.hs | 75 | ||||
-rw-r--r-- | src/Remote/KRPC/Method.hs | 61 | ||||
-rw-r--r-- | src/Remote/KRPC/Protocol.hs | 6 |
6 files changed, 112 insertions, 65 deletions
diff --git a/examples/Client.hs b/examples/Client.hs index bf486cb5..1d925c7a 100644 --- a/examples/Client.hs +++ b/examples/Client.hs | |||
@@ -10,7 +10,7 @@ addr :: RemoteAddr | |||
10 | addr = (0, 6000) | 10 | addr = (0, 6000) |
11 | 11 | ||
12 | main :: IO () | 12 | main :: IO () |
13 | main = print =<< call addr echoInt . read . head =<< getArgs | 13 | main = print =<< call addr swapM (1, 2) |
14 | 14 | ||
15 | {- | 15 | {- |
16 | forM_ [1..] $ const $ do | 16 | forM_ [1..] $ const $ do |
diff --git a/examples/Server.hs b/examples/Server.hs index 8727c7d9..3760b2ab 100644 --- a/examples/Server.hs +++ b/examples/Server.hs | |||
@@ -1,4 +1,4 @@ | |||
1 | {-# LANGUAGE OverloadedStrings #-} | 1 | {-# LANGUAGE IncoherentInstances #-} |
2 | module Main (main) where | 2 | module Main (main) where |
3 | 3 | ||
4 | import Remote.KRPC | 4 | import Remote.KRPC |
@@ -6,4 +6,4 @@ import Shared | |||
6 | 6 | ||
7 | 7 | ||
8 | main :: IO () | 8 | main :: IO () |
9 | main = server 6000 [echoInt ==> return] | 9 | main = server 6000 [swapM ==> \(a, b) -> return (b, a)] |
diff --git a/examples/Shared.hs b/examples/Shared.hs index efe345ac..49cef490 100644 --- a/examples/Shared.hs +++ b/examples/Shared.hs | |||
@@ -1,6 +1,33 @@ | |||
1 | module Shared (echoInt) where | 1 | {-# LANGUAGE OverloadedStrings #-} |
2 | module Shared (echoInt, swapM) where | ||
2 | 3 | ||
3 | import Remote.KRPC | 4 | import Remote.KRPC |
4 | 5 | ||
5 | echoInt :: Method Int Int | 6 | echoInt :: Method Int Int |
6 | echoInt = idM | 7 | echoInt = idM |
8 | |||
9 | swapM :: Method (Int, Int) (Int, Int) | ||
10 | swapM = method "swap" ["x", "y"] ["b", "a"] | ||
11 | |||
12 | {- | ||
13 | type NodeId = Int | ||
14 | type InfoHashe = Int | ||
15 | type NodeAddr = Int | ||
16 | type Token = Int | ||
17 | type | ||
18 | |||
19 | ping :: Method NodeId NodeId | ||
20 | ping = method "ping" ["id"] ["id"] | ||
21 | |||
22 | find_node :: Method (NodeId, NodeId) (NodeId, NodeAddr) | ||
23 | find_node = method "find_node" ["id", "target"] ["id", "nodes"] | ||
24 | |||
25 | get_peers :: Method (NodeId :*: InfoHash) (NodeId, Token, NodeAddr :|: NodeAddr) | ||
26 | get_peers = method "get_peers" | ||
27 | ("id", "target") | ||
28 | ("id", "token", view ("values" :|: "nodes")) | ||
29 | view :: BEncodable -> Maybe BEncodable | ||
30 | view = undefined | ||
31 | announce_peer :: Method (NodeId, InfoHash, PortNumber, Token) NodeId | ||
32 | announce_peer = undefined | ||
33 | -} \ No newline at end of file | ||
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 | |||
26 | import Control.Monad.Trans.Control | 26 | import Control.Monad.Trans.Control |
27 | import Control.Monad.IO.Class | 27 | import Control.Monad.IO.Class |
28 | import Data.BEncode | 28 | import Data.BEncode |
29 | import Data.ByteString.Char8 as BC | ||
29 | import Data.List as L | 30 | import Data.List as L |
30 | import Data.Map as M | 31 | import Data.Map as M |
31 | import Data.Set as S | 32 | import Data.Set as S |
32 | import Data.Text as T | 33 | import Data.Text as T |
34 | import Data.Text.Encoding as T | ||
33 | import Data.Typeable | 35 | import Data.Typeable |
34 | import Network | 36 | import Network |
35 | 37 | ||
@@ -47,14 +49,25 @@ type RemoteAddr = KRemoteAddr | |||
47 | 49 | ||
48 | 50 | ||
49 | queryCall :: BEncodable param | 51 | queryCall :: BEncodable param |
52 | => Extractable param | ||
50 | => KRemote -> KRemoteAddr | 53 | => KRemote -> KRemoteAddr |
51 | -> Method param result -> param -> IO () | 54 | -> Method param result -> param -> IO () |
52 | queryCall sock addr m arg = sendMessage q addr sock | 55 | queryCall 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 | |||
61 | extractArgs :: [ParamName] -> Map ParamName BEncode -> Result [BEncode] | ||
62 | extractArgs 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 |
57 | getResult :: BEncodable result | 69 | getResult :: BEncodable result |
70 | => Extractable result | ||
58 | => KRemote -> KRemoteAddr | 71 | => KRemote -> KRemoteAddr |
59 | -> Method param result -> IO result | 72 | -> Method param result -> IO result |
60 | getResult sock addr m = do | 73 | getResult 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 | -- |
79 | call :: (MonadBaseControl IO host, MonadIO host) | 86 | call :: (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 |
93 | async :: MonadIO host | 101 | async :: 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 | ||
105 | await :: MonadIO host => Async result -> host result | 114 | await :: MonadIO host => Async result -> host result |
106 | await = liftIO . waitResult | 115 | await = liftIO . waitResult |
116 | {-# INLINE await #-} | ||
117 | |||
107 | 118 | ||
108 | type HandlerBody remote = (BEncode -> remote (Result BEncode), KResponseScheme) | 119 | type HandlerBody remote = KQuery -> remote (Either KError KResponse) |
109 | 120 | ||
110 | type MethodHandler remote = (KQueryScheme, HandlerBody remote) | 121 | type 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 |
120 | m ==> body = (methodQueryScheme m, (newbody, methodRespScheme m)) | 132 | {-# INLINE (==>) #-} |
133 | m ==> 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 | ||
129 | server :: (MonadBaseControl IO remote, MonadIO remote) | 147 | server :: (MonadBaseControl IO remote, MonadIO remote) |
130 | => PortNumber | 148 | => PortNumber |
131 | -> [MethodHandler remote] | 149 | -> [MethodHandler remote] |
132 | -> remote () | 150 | -> remote () |
133 | server servport handlers = do | 151 | server 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 #-} | ||
9 | module Remote.KRPC.Method | 10 | module 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 | ||
20 | import Prelude hiding ((.), id) | 24 | import Prelude hiding ((.), id) |
21 | import Control.Applicative | 25 | import Control.Applicative |
22 | import Control.Category | 26 | import Control.Category |
23 | import Control.Monad | 27 | import Control.Monad |
28 | import Data.BEncode | ||
24 | import Data.ByteString as B | 29 | import Data.ByteString as B |
25 | import Data.List as L | 30 | import Data.List as L |
26 | import Data.Set as S | 31 | import Data.Set as S |
@@ -38,7 +43,7 @@ import Remote.KRPC.Protocol | |||
38 | -- | 43 | -- |
39 | data Method param result = Method { | 44 | data 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 | |||
50 | instance Category Method where | ||
51 | {-# SPECIALIZE instance Category Method #-} | ||
52 | id = idM | ||
53 | {-# INLINE id #-} | ||
54 | |||
55 | (.) = composeM | ||
56 | {-# INLINE (.) #-} | ||
57 | |||
58 | methodQueryScheme :: Method a b -> KQueryScheme | 54 | methodQueryScheme :: Method a b -> KQueryScheme |
59 | methodQueryScheme = KQueryScheme <$> B.intercalate "." . methodName | 55 | methodQueryScheme = 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 | |||
75 | idM = method "id" ["x"] ["y"] | 71 | idM = method "id" ["x"] ["y"] |
76 | {-# INLINE idM #-} | 72 | {-# INLINE idM #-} |
77 | 73 | ||
78 | -- | Pipelining of two or more methods. | 74 | method :: MethodName -> [ParamName] -> [ValName] -> Method param result |
79 | -- | 75 | method = 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 | -- | ||
84 | composeM :: Method b c -> Method a b -> Method a c | ||
85 | composeM g h = Method (methodName g ++ methodName h) | ||
86 | (methodParams h) | ||
87 | (methodVals g) | ||
88 | {-# INLINE composeM #-} | ||
89 | 77 | ||
90 | 78 | ||
91 | method :: MethodName -> [ParamName] -> [ValName] -> Method param result | 79 | |
92 | method name = Method [name] | 80 | class Extractable a where |
93 | {-# INLINE method #-} \ No newline at end of file | 81 | injector :: a -> [BEncode] |
82 | extractor :: [BEncode] -> Result a | ||
83 | |||
84 | instance (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 | {- | ||
93 | instance 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 |
79 | data KError | 79 | data 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 | |||
213 | withRemote :: (MonadBaseControl IO m, MonadIO m) => (KRemote -> m a) -> m a | 213 | withRemote :: (MonadBaseControl IO m, MonadIO m) => (KRemote -> m a) -> m a |
214 | withRemote = bracket (liftIO (socket AF_INET Datagram defaultProtocol)) | 214 | withRemote = bracket (liftIO (socket AF_INET Datagram defaultProtocol)) |
215 | (liftIO . sClose) | 215 | (liftIO . sClose) |
216 | {-# SPECIALIZE withRemote :: (KRemote -> IO a) -> IO a #-} | ||
217 | |||
216 | 218 | ||
217 | maxMsgSize :: Int | 219 | maxMsgSize :: Int |
218 | maxMsgSize = 16 * 1024 | 220 | maxMsgSize = 16 * 1024 |
221 | {-# INLINE maxMsgSize #-} | ||
222 | |||
219 | 223 | ||
220 | -- TODO eliminate toStrict | 224 | -- TODO eliminate toStrict |
221 | sendMessage :: BEncodable msg => msg -> KRemoteAddr -> KRemote -> IO () | 225 | sendMessage :: BEncodable msg => msg -> KRemoteAddr -> KRemote -> IO () |