summaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorSam T <pxqr.sta@gmail.com>2013-05-14 10:43:35 +0400
committerSam T <pxqr.sta@gmail.com>2013-05-14 10:43:35 +0400
commitab6ad1b5a10c46908a2c53a8148f5d202e517c7a (patch)
treeef4b2481491a6306f001b54d88fc2b3237a4e233 /src
parentd0038e9bde22751c9c926796a6c46be62a3cb81b (diff)
+ Add documentation to KRPC module.
Diffstat (limited to 'src')
-rw-r--r--src/Remote/KRPC.hs222
1 files changed, 174 insertions, 48 deletions
diff --git a/src/Remote/KRPC.hs b/src/Remote/KRPC.hs
index ec83b802..0e9838f1 100644
--- a/src/Remote/KRPC.hs
+++ b/src/Remote/KRPC.hs
@@ -5,26 +5,101 @@
5-- Stability : experimental 5-- Stability : experimental
6-- Portability : portable 6-- Portability : portable
7-- 7--
8-- This module provides safe remote procedure call. 8-- This module provides safe remote procedure call. One important
9-- point is exceptions and errors, so be able handle them properly
10-- we need to investigate a bit about how this all works.
11-- Internally, in order to make method invokation KRPC makes the
12-- following steps:
13--
14-- * Caller serialize arguments to bencoded bytestrings;
15--
16-- * Caller send bytestring data over UDP to the callee;
17--
18-- * Callee receive and decode arguments to the method and method
19-- name. If it can't decode then it send 'ProtocolError' back to the
20-- caller;
21--
22-- * Callee search for the @method name@ in the method table.
23-- If it not present in the table then callee send 'MethodUnknown'
24-- back to the caller;
25--
26-- * Callee check if argument names match. If not it send
27-- 'ProtocolError' back;
28--
29-- * Callee make the actuall call to the plain old haskell
30-- function. If the function throw exception then callee send
31-- 'ServerError' back.
32--
33-- * Callee serialize result of the function to bencoded bytestring.
34--
35-- * Callee encode result to bencoded bytestring and send it back
36-- to the caller.
37--
38-- * Caller check if return values names match with the signature
39-- it called in the first step.
40--
41-- * Caller extracts results and finally return results of the
42-- procedure call as ordinary haskell values.
43--
44-- If every other error occurred caller get the 'GenericError'. All
45-- errors returned by callee are throwed as ordinary haskell
46-- exceptions at caller side. Make sure that both callee and caller
47-- uses the same method signatures and everything should be ok: this
48-- KRPC implementation provides some level of safety through
49-- types. Also note that both caller and callee use plain UDP, so
50-- KRPC is unreliable.
51--
52-- Consider one tiny example. From now @caller = client@ and
53-- @callee = server or remote@.
54--
55-- Somewhere we have to define all procedure signatures. Imagine
56-- that this is a library shared between client and server:
57--
58-- > factorialMethod :: Method Int Int
59-- > factorialMethod = method "factorial" ["x"] ["y"]
60--
61-- Otherwise you can define this code in both client and server of
62-- course. But in this case you might get into troubles: you can get
63-- 'MethodUnknown' or 'ProtocolError' if name or type of method
64-- will mismatch after not synced changes in client or server code.
65--
66-- Now let's define our client-side:
67--
68-- > main = withRemote $ \remote -> do
69-- > result <- call remote (0, 6000) factorialMethod 4
70-- > assert (result == 24) $ print "Success!"
71--
72-- It basically open socket with 'withRemote' and make all the other
73-- steps in 'call' as describe above. And finally our server-side:
74--
75-- > factorialImpl :: Int -> Int
76-- > factorialImpl n = product [1..n]
77-- >
78-- > main = runServer [factorialMethod $ return . factorialImpl]
79--
80-- Here we implement method signature from that shared lib and run
81-- server with runServer by passing method table in.
82--
83-- For more examples see @exsamples@ or @tests@ directories.
84--
85-- For protocol details see 'Remote.KRPC.Protocol' module.
9-- 86--
10{-# LANGUAGE OverloadedStrings #-} 87{-# LANGUAGE OverloadedStrings #-}
11{-# LANGUAGE FlexibleContexts, DeriveDataTypeable #-} 88{-# LANGUAGE FlexibleContexts, DeriveDataTypeable #-}
12{-# LANGUAGE ExplicitForAll, KindSignatures #-} 89{-# LANGUAGE ExplicitForAll, KindSignatures #-}
13{-# LANGUAGE ViewPatterns #-} 90{-# LANGUAGE ViewPatterns #-}
14module Remote.KRPC 91module Remote.KRPC
15 ( -- * Common 92 ( -- * Method
16 -- ** Types 93 Method(..)
17 RemoteAddr
18
19 -- ** Method
20 , Method(methodName, methodParams, methodVals)
21 , method, idM 94 , method, idM
22 95
23 -- * Client 96 -- * Client
24 , call, async, await 97 , RemoteAddr
98 , RPCException(..)
99 , call, Async, async, await
25 100
26 -- * Server 101 -- * Server
27 , (==>), server 102 , MethodHandler, (==>), server
28 ) where 103 ) where
29 104
30import Control.Applicative 105import Control.Applicative
@@ -40,47 +115,58 @@ import Network
40 115
41import Remote.KRPC.Protocol 116import Remote.KRPC.Protocol
42 117
43 118-- | Method datatype used to describe name, parameters and return
44-- | The 119-- values of procedure. Client use a method to /invoke/, server
120-- /implements/ the method to make the actual work.
45-- 121--
46-- * argument: type of method parameter 122-- We use the following fantom types to ensure type-safiety:
47-- 123--
48-- * remote: A monad used by server-side. 124-- * param: Type of method parameters. Ordinary Tuple type used
125-- to specify more than one parameter, so for example @Method
126-- (Int, Int) result@ will take two arguments.
49-- 127--
50-- * result: type of return value of the method. 128-- * result: Type of return value of the method. Similarly,
129-- tuple used to specify more than one return value, so for
130-- exsample @Method (Foo, Bar) (Bar, Foo)@ will take two arguments
131-- and return two values.
51-- 132--
52data Method param result = Method { 133data Method param result = Method {
53 -- | Name used in query and 134 -- | Name used in query.
54 methodName :: MethodName 135 methodName :: MethodName
55 136
56 -- | Description of each parameter in /right to left/ order. 137 -- | Name of each parameter in /right to left/ order.
57 , methodParams :: [ParamName] 138 , methodParams :: [ParamName]
58 139
59 -- | Description of each return value in /right to left/ order. 140 -- | Name of each return value in /right to left/ order.
60 , methodVals :: [ValName] 141 , methodVals :: [ValName]
61 } 142 }
62 143
63-- TODO ppMethod 144-- TODO ppMethod
64 145
65-- | Remote identity function. Could be used for echo servers for example. 146-- | Identity procedure signature. Could be used for echo
147-- servers. Implemented as:
66-- 148--
67-- idM = method "id" ["x"] ["y"] return 149-- > idM = method "id" ["x"] ["y"]
68-- 150--
69idM :: Method a a 151idM :: Method a a
70idM = method "id" ["x"] ["y"] 152idM = method "id" ["x"] ["y"]
71{-# INLINE idM #-} 153{-# INLINE idM #-}
72 154
155-- | Makes method signature. Note that order of parameters and return
156-- values are not important as long as corresponding names and types
157-- are match. For exsample this is the equal definitions:
158--
159-- > methodA : Method (Foo, Bar) (Baz, Quux)
160-- > methodA = method "mymethod" ["a", "b"] ["c", "d"]
161--
162-- > methodA : Method (Bar, Foo) (Quux, Baz)
163-- > methodB = method "mymethod" ["b", "a"] ["d", "c"]
164--
73method :: MethodName -> [ParamName] -> [ValName] -> Method param result 165method :: MethodName -> [ParamName] -> [ValName] -> Method param result
74method = Method 166method = Method
75{-# INLINE method #-} 167{-# INLINE method #-}
76 168
77 169
78data RPCException = RPCException KError
79 deriving (Show, Eq, Typeable)
80
81instance Exception RPCException
82type RemoteAddr = KRemoteAddr
83
84extractArgs :: BEncodable arg 170extractArgs :: BEncodable arg
85 => [ParamName] -> Map ParamName BEncode -> Result arg 171 => [ParamName] -> Map ParamName BEncode -> Result arg
86extractArgs as d = fromBEncode =<< 172extractArgs as d = fromBEncode =<<
@@ -101,6 +187,19 @@ injectVals _ _ = error "KRPC.injectVals: impossible"
101{-# INLINE injectVals #-} 187{-# INLINE injectVals #-}
102 188
103 189
190
191-- | Represent any error mentioned by protocol specification that
192-- 'call', 'await' might throw.
193-- For more details see 'Remote.KRPC.Protocol'.
194--
195data RPCException = RPCException KError
196 deriving (Show, Eq, Typeable)
197
198instance Exception RPCException
199
200-- | Address of remote can be called by client.
201type RemoteAddr = KRemoteAddr
202
104queryCall :: BEncodable param 203queryCall :: BEncodable param
105 => KRemote -> KRemoteAddr 204 => KRemote -> KRemoteAddr
106 -> Method param result -> param -> IO () 205 -> Method param result -> param -> IO ()
@@ -108,9 +207,6 @@ queryCall sock addr m arg = sendMessage q addr sock
108 where 207 where
109 q = kquery (methodName m) (injectVals (methodParams m) arg) 208 q = kquery (methodName m) (injectVals (methodParams m) arg)
110 209
111
112
113-- TODO check scheme
114getResult :: BEncodable result 210getResult :: BEncodable result
115 => KRemote -> KRemoteAddr 211 => KRemote -> KRemoteAddr
116 -> Method param result -> IO result 212 -> Method param result -> IO result
@@ -123,53 +219,78 @@ getResult sock addr m = do
123 Right vals -> return vals 219 Right vals -> return vals
124 Left e -> throw (RPCException (ProtocolError (BC.pack e))) 220 Left e -> throw (RPCException (ProtocolError (BC.pack e)))
125 221
126-- TODO async call 222
127-- | Makes remote procedure call. Throws RPCException if server 223-- | Makes remote procedure call. Throws RPCException on any error
128-- returns error or decode error occurred. 224-- occurred.
129--
130call :: (MonadBaseControl IO host, MonadIO host) 225call :: (MonadBaseControl IO host, MonadIO host)
131 => (BEncodable param, BEncodable result) 226 => (BEncodable param, BEncodable result)
132 => RemoteAddr 227 => RemoteAddr -- ^ Address of callee.
133 -> Method param result 228 -> Method param result -- ^ Procedure to call.
134 -> param 229 -> param -- ^ Arguments passed by callee to procedure.
135 -> host result 230 -> host result -- ^ Values returned by callee from the procedure.
136call addr m arg = liftIO $ withRemote $ \sock -> do 231call addr m arg = liftIO $ withRemote $ \sock -> do
137 queryCall sock addr m arg 232 queryCall sock addr m arg
138 getResult sock addr m 233 getResult sock addr m
139 234
140 235
236-- | Asynchonous result typically get from 'async' call. Used to defer
237-- return values transfer.
141newtype Async result = Async { waitResult :: IO result } 238newtype Async result = Async { waitResult :: IO result }
142 239
143-- TODO document errorneous usage 240
241-- | Query procedure call but not wait for its results. This function
242-- returns 'Async' value which is handle to procedure result. Actual
243-- result might be obtained with 'await'. Unable to throw
244-- 'RPCException', this might happen in 'await' if at all.
245--
246-- Note that sending multiple queries at the same time to the one
247-- remote is not recommended. For exsample in the following scenario:
248--
249-- > aa <- async theRemote ....
250-- > ab <- async theRemote ....
251-- > a <- await ab
252-- > b <- await ab
253--
254-- it's likely that the /a/ and /b/ values will be mixed up. So in
255-- order to get correct results you need to make 'await' before the
256-- next 'async'.
257--
144async :: MonadIO host 258async :: MonadIO host
145 => (BEncodable param, BEncodable result) 259 => (BEncodable param, BEncodable result)
146 => RemoteAddr 260 => RemoteAddr -- ^ Address of callee.
147 -> Method param result 261 -> Method param result -- ^ Procedure to call.
148 -> param 262 -> param -- ^ Arguments passed by callee to procedure.
149 -> host (Async result) 263 -> host (Async result) -- ^ Handle to result.
150async addr m arg = do 264async addr m arg = do
151 liftIO $ withRemote $ \sock -> 265 liftIO $ withRemote $ \sock ->
152 queryCall sock addr m arg 266 queryCall sock addr m arg
153 return $ Async $ withRemote $ \sock -> 267 return $ Async $ withRemote $ \sock ->
154 getResult sock addr m 268 getResult sock addr m
155 269
156await :: MonadIO host => Async result -> host result 270-- | Will wait until the callee finished processing of procedure call
271-- and return its results. Throws 'RPCException' on any error
272-- occurred.
273await :: MonadIO host
274 => Async result -- ^ Obtained from the corresponding 'async'.
275 -> host result -- ^ Result values of the procedure call quered
276 -- with 'async'.
157await = liftIO . waitResult 277await = liftIO . waitResult
158{-# INLINE await #-} 278{-# INLINE await #-}
159 279
160 280
161type HandlerBody remote = KQuery -> remote (Either KError KResponse) 281type HandlerBody remote = KQuery -> remote (Either KError KResponse)
162 282
283-- | Procedure signature and implementation binded up.
163type MethodHandler remote = (MethodName, HandlerBody remote) 284type MethodHandler remote = (MethodName, HandlerBody remote)
164 285
165
166-- we can safely erase types in (==>) 286-- we can safely erase types in (==>)
287-- | Assign method implementation to the method signature.
167(==>) :: forall (remote :: * -> *) (param :: *) (result :: *). 288(==>) :: forall (remote :: * -> *) (param :: *) (result :: *).
168 (BEncodable param, BEncodable result) 289 (BEncodable param, BEncodable result)
169 => Monad remote 290 => Monad remote
170 => Method param result 291 => Method param result -- ^ Signature.
171 -> (param -> remote result) 292 -> (param -> remote result) -- ^ Implementation.
172 -> MethodHandler remote 293 -> MethodHandler remote -- ^ Handler used by server.
173{-# INLINE (==>) #-} 294{-# INLINE (==>) #-}
174m ==> body = (methodName m, newbody) 295m ==> body = (methodName m, newbody)
175 where 296 where
@@ -184,9 +305,14 @@ m ==> body = (methodName m, newbody)
184infix 1 ==> 305infix 1 ==>
185 306
186-- TODO: allow forkIO 307-- TODO: allow forkIO
308
309-- | Run RPC server on specified port by using list of handlers.
310-- Server will dispatch procedure specified by callee, but note that
311-- it will not create new thread for each connection.
312--
187server :: (MonadBaseControl IO remote, MonadIO remote) 313server :: (MonadBaseControl IO remote, MonadIO remote)
188 => PortNumber 314 => PortNumber -- ^ Port used to accept incoming connections.
189 -> [MethodHandler remote] 315 -> [MethodHandler remote] -- ^ Method table.
190 -> remote () 316 -> remote ()
191server servport handlers = do 317server servport handlers = do
192 remoteServer servport $ \_ q -> do 318 remoteServer servport $ \_ q -> do