summaryrefslogtreecommitdiff
path: root/src/Network
diff options
context:
space:
mode:
Diffstat (limited to 'src/Network')
-rw-r--r--src/Network/KRPC.hs8
-rw-r--r--src/Network/KRPC/Message.hs47
2 files changed, 27 insertions, 28 deletions
diff --git a/src/Network/KRPC.hs b/src/Network/KRPC.hs
index 8e158f48..2c3a1b48 100644
--- a/src/Network/KRPC.hs
+++ b/src/Network/KRPC.hs
@@ -208,7 +208,7 @@ call :: forall req resp host.
208 (MonadBaseControl IO host, MonadIO host, KRPC req resp) 208 (MonadBaseControl IO host, MonadIO host, KRPC req resp)
209 => SockAddr -> req -> host resp 209 => SockAddr -> req -> host resp
210call addr arg = liftIO $ withRemote $ \sock -> do 210call addr arg = liftIO $ withRemote $ \sock -> do
211 sendMessage (KQuery name (toBEncode arg)) addr sock 211 sendMessage (KQuery (toBEncode arg) name undefined) addr sock
212 getResult sock 212 getResult sock
213 where 213 where
214 Method name = method :: Method req resp 214 Method name = method :: Method req resp
@@ -231,12 +231,12 @@ handler body = (name, newbody)
231 Method name = method :: Method req resp 231 Method name = method :: Method req resp
232 232
233 {-# INLINE newbody #-} 233 {-# INLINE newbody #-}
234 newbody addr q = 234 newbody addr KQuery {..} =
235 case fromBEncode (queryArgs q) of 235 case fromBEncode queryArgs of
236 Left e -> return (Left (ProtocolError (BC.pack e))) 236 Left e -> return (Left (ProtocolError (BC.pack e)))
237 Right a -> do 237 Right a -> do
238 r <- body addr a 238 r <- body addr a
239 return (Right (KResponse (toBEncode r))) 239 return (Right (KResponse (toBEncode r) queryId))
240 240
241sockAddrFamily :: SockAddr -> Family 241sockAddrFamily :: SockAddr -> Family
242sockAddrFamily (SockAddrInet _ _ ) = AF_INET 242sockAddrFamily (SockAddrInet _ _ ) = AF_INET
diff --git a/src/Network/KRPC/Message.hs b/src/Network/KRPC/Message.hs
index 854b733c..1a004c64 100644
--- a/src/Network/KRPC/Message.hs
+++ b/src/Network/KRPC/Message.hs
@@ -100,6 +100,8 @@ serverError = ServerError . BC.pack . show
100 100
101type MethodName = ByteString 101type MethodName = ByteString
102 102
103type TransactionId = ByteString
104
103-- | Query used to signal that caller want to make procedure call to 105-- | Query used to signal that caller want to make procedure call to
104-- callee and pass arguments in. Therefore query may be only sent from 106-- callee and pass arguments in. Therefore query may be only sent from
105-- client to server but not in the opposite direction. 107-- client to server but not in the opposite direction.
@@ -109,27 +111,24 @@ type MethodName = ByteString
109-- > { "y" : "q", "q" : "<method_name>", "a" : [<arg1>, <arg2>, ...] } 111-- > { "y" : "q", "q" : "<method_name>", "a" : [<arg1>, <arg2>, ...] }
110-- 112--
111data KQuery = KQuery 113data KQuery = KQuery
112 { queryMethod :: !MethodName 114 { queryArgs :: !BValue
113 , queryArgs :: !BValue 115 , queryMethod :: !MethodName
116 , queryId :: !TransactionId
114 } deriving (Show, Read, Eq, Ord, Typeable) 117 } deriving (Show, Read, Eq, Ord, Typeable)
115 118
116instance BEncode KQuery where 119instance BEncode KQuery where
117 {-# SPECIALIZE instance BEncode KQuery #-} 120 toBEncode KQuery {..} = toDict $
118 {-# INLINE toBEncode #-} 121 "a" .=! queryArgs
119 toBEncode (KQuery m args) = toDict $ 122 .: "q" .=! queryMethod
120 "a" .=! args 123 .: "t" .=! queryId
121 .: "q" .=! m
122 .: "y" .=! ("q" :: ByteString) 124 .: "y" .=! ("q" :: ByteString)
123 .: endDict 125 .: endDict
126 {-# INLINE toBEncode #-}
124 127
128 fromBEncode = fromDict $ do
129 lookAhead $ match "y" (BString "q")
130 KQuery <$>! "a" <*>! "q" <*>! "t"
125 {-# INLINE fromBEncode #-} 131 {-# INLINE fromBEncode #-}
126 fromBEncode bv @ (BDict d)
127 | BE.lookup "y" d == Just (BString "q") = (`fromDict` bv) $ do
128 a <- field (req "a")
129 q <- field (req "q")
130 return $! KQuery q a
131
132 fromBEncode _ = decodingError "KQuery"
133 132
134-- | KResponse used to signal that callee successufully process a 133-- | KResponse used to signal that callee successufully process a
135-- procedure call and to return values from procedure. KResponse should 134-- procedure call and to return values from procedure. KResponse should
@@ -140,20 +139,20 @@ instance BEncode KQuery where
140-- 139--
141-- > { "y" : "r", "r" : [<val1>, <val2>, ...] } 140-- > { "y" : "r", "r" : [<val1>, <val2>, ...] }
142-- 141--
143newtype KResponse = KResponse 142data KResponse = KResponse
144 { respVals :: BValue 143 { respVals :: BValue
144 , respId :: TransactionId
145 } deriving (Show, Read, Eq, Ord, Typeable) 145 } deriving (Show, Read, Eq, Ord, Typeable)
146 146
147instance BEncode KResponse where 147instance BEncode KResponse where
148 {-# INLINE toBEncode #-} 148 toBEncode KResponse {..} = toDict $
149 toBEncode (KResponse vals) = toDict $ 149 "r" .=! respVals
150 "r" .=! vals 150 .: "t" .=! respId
151 .: "y" .=! ("r" :: ByteString) 151 .: "y" .=! ("r" :: ByteString)
152 .: endDict 152 .: endDict
153 {-# INLINE toBEncode #-}
153 154
154 {-# INLINE fromBEncode #-} 155 fromBEncode = fromDict $ do
155 fromBEncode bv @ (BDict d) 156 lookAhead $ match "y" (BString "r")
156 | BE.lookup "y" d == Just (BString "r") = (`fromDict` bv) $ do 157 KResponse <$>! "r" <*>! "t"
157 KResponse <$>! "r" 158 {-# INLINE fromBEncode #-} \ No newline at end of file
158
159 fromBEncode _ = decodingError "KDict"