diff options
Diffstat (limited to 'src/Network/BitTorrent/Tracker/RPC/UDP.hs')
-rw-r--r-- | src/Network/BitTorrent/Tracker/RPC/UDP.hs | 76 |
1 files changed, 66 insertions, 10 deletions
diff --git a/src/Network/BitTorrent/Tracker/RPC/UDP.hs b/src/Network/BitTorrent/Tracker/RPC/UDP.hs index a835dc23..bc4f9dd0 100644 --- a/src/Network/BitTorrent/Tracker/RPC/UDP.hs +++ b/src/Network/BitTorrent/Tracker/RPC/UDP.hs | |||
@@ -12,6 +12,7 @@ | |||
12 | {-# LANGUAGE RecordWildCards #-} | 12 | {-# LANGUAGE RecordWildCards #-} |
13 | {-# LANGUAGE FlexibleInstances #-} | 13 | {-# LANGUAGE FlexibleInstances #-} |
14 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} | 14 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} |
15 | {-# LANGUAGE DeriveDataTypeable #-} | ||
15 | {-# LANGUAGE TypeFamilies #-} | 16 | {-# LANGUAGE TypeFamilies #-} |
16 | module Network.BitTorrent.Tracker.RPC.UDP | 17 | module Network.BitTorrent.Tracker.RPC.UDP |
17 | ( -- * Manager | 18 | ( -- * Manager |
@@ -22,6 +23,7 @@ module Network.BitTorrent.Tracker.RPC.UDP | |||
22 | , withManager | 23 | , withManager |
23 | 24 | ||
24 | -- * RPC | 25 | -- * RPC |
26 | , RpcException (..) | ||
25 | , announce | 27 | , announce |
26 | , scrape | 28 | , scrape |
27 | ) where | 29 | ) where |
@@ -41,6 +43,7 @@ import Data.Text as T | |||
41 | import Data.Text.Encoding | 43 | import Data.Text.Encoding |
42 | import Data.Time | 44 | import Data.Time |
43 | import Data.Time.Clock.POSIX | 45 | import Data.Time.Clock.POSIX |
46 | import Data.Typeable | ||
44 | import Data.Word | 47 | import Data.Word |
45 | import Text.Read (readMaybe) | 48 | import Text.Read (readMaybe) |
46 | import Network.Socket hiding (Connected, connect) | 49 | import Network.Socket hiding (Connected, connect) |
@@ -71,7 +74,11 @@ defMaxPacketSize = 98 | |||
71 | 74 | ||
72 | data Options = Options | 75 | data Options = Options |
73 | { optMaxPacketSize :: {-# UNPACK #-} !Int | 76 | { optMaxPacketSize :: {-# UNPACK #-} !Int |
77 | |||
78 | -- | in seconds. | ||
74 | , optMinTimeout :: {-# UNPACK #-} !Int | 79 | , optMinTimeout :: {-# UNPACK #-} !Int |
80 | |||
81 | -- | in seconds. | ||
75 | , optMaxTimeout :: {-# UNPACK #-} !Int | 82 | , optMaxTimeout :: {-# UNPACK #-} !Int |
76 | } deriving (Show, Eq) | 83 | } deriving (Show, Eq) |
77 | 84 | ||
@@ -102,6 +109,47 @@ withManager :: Options -> (Manager -> IO a) -> IO a | |||
102 | withManager opts = bracket (newManager opts) closeManager | 109 | withManager opts = bracket (newManager opts) closeManager |
103 | 110 | ||
104 | {----------------------------------------------------------------------- | 111 | {----------------------------------------------------------------------- |
112 | -- Exceptions | ||
113 | -----------------------------------------------------------------------} | ||
114 | |||
115 | data RpcException | ||
116 | -- | Unable to lookup hostname; | ||
117 | = HostUnknown | ||
118 | |||
119 | -- | Unable to lookup hostname; | ||
120 | | HostLookupFailed | ||
121 | |||
122 | -- | Tracker exists but not responding for specific number of seconds. | ||
123 | | TrackerNotResponding Int | ||
124 | |||
125 | -- | Source\/destination socket address mismatch. | ||
126 | -- | ||
127 | -- WARNING: This is a BUG and will be fixed! | ||
128 | -- | ||
129 | | UnexpectedSource | ||
130 | |||
131 | -- | Source\/destination transaction id mismatch. | ||
132 | -- | ||
133 | -- WARNING: This is a BUG and will be fixed! | ||
134 | -- | ||
135 | | TransactionFailed | ||
136 | |||
137 | -- | Unable to decode tracker response; | ||
138 | | ParserFailure String | ||
139 | |||
140 | -- | Tracker respond with unexpected message type. | ||
141 | | UnexpectedResponse | ||
142 | { expectedMsg :: String | ||
143 | , actualMsg :: String | ||
144 | } | ||
145 | |||
146 | -- | RPC succeed, but tracker respond with error code. | ||
147 | | QueryFailed Text | ||
148 | deriving (Show, Typeable) | ||
149 | |||
150 | instance Exception RpcException | ||
151 | |||
152 | {----------------------------------------------------------------------- | ||
105 | -- Host Addr resolution | 153 | -- Host Addr resolution |
106 | -----------------------------------------------------------------------} | 154 | -----------------------------------------------------------------------} |
107 | 155 | ||
@@ -116,8 +164,8 @@ resolveURI URI { uriAuthority = Just (URIAuth {..}) } = do | |||
116 | let port = fromMaybe 0 (readMaybe (L.drop 1 uriPort) :: Maybe Int) | 164 | let port = fromMaybe 0 (readMaybe (L.drop 1 uriPort) :: Maybe Int) |
117 | case infos of | 165 | case infos of |
118 | AddrInfo {..} : _ -> return $ setPort (fromIntegral port) addrAddress | 166 | AddrInfo {..} : _ -> return $ setPort (fromIntegral port) addrAddress |
119 | _ -> fail "getTrackerAddr: unable to lookup host addr" | 167 | _ -> throwIO HostLookupFailed |
120 | resolveURI _ = fail "getTrackerAddr: hostname unknown" | 168 | resolveURI _ = throwIO HostUnknown |
121 | 169 | ||
122 | -- TODO caching? | 170 | -- TODO caching? |
123 | getTrackerAddr :: Manager -> URI -> IO SockAddr | 171 | getTrackerAddr :: Manager -> URI -> IO SockAddr |
@@ -170,6 +218,12 @@ data Response = Connected ConnectionId | |||
170 | | Failed Text | 218 | | Failed Text |
171 | deriving Show | 219 | deriving Show |
172 | 220 | ||
221 | responseName :: Response -> String | ||
222 | responseName (Connected _) = "connected" | ||
223 | responseName (Announced _) = "announced" | ||
224 | responseName (Scraped _) = "scraped" | ||
225 | responseName (Failed _) = "failed" | ||
226 | |||
173 | data family Transaction a | 227 | data family Transaction a |
174 | data instance Transaction Request = TransactionQ | 228 | data instance Transaction Request = TransactionQ |
175 | { connIdQ :: {-# UNPACK #-} !ConnectionId | 229 | { connIdQ :: {-# UNPACK #-} !ConnectionId |
@@ -297,7 +351,7 @@ call Manager {..} addr arg = do | |||
297 | BS.sendAllTo sock arg addr | 351 | BS.sendAllTo sock arg addr |
298 | (res, addr') <- BS.recvFrom sock (optMaxPacketSize options) | 352 | (res, addr') <- BS.recvFrom sock (optMaxPacketSize options) |
299 | unless (addr' == addr) $ do | 353 | unless (addr' == addr) $ do |
300 | throwIO $ userError "address mismatch" | 354 | throwIO $ UnexpectedSource |
301 | return res | 355 | return res |
302 | 356 | ||
303 | transaction :: Manager -> SockAddr -> Connection -> Request -> IO Response | 357 | transaction :: Manager -> SockAddr -> Connection -> Request -> IO Response |
@@ -308,8 +362,8 @@ transaction m addr conn request = do | |||
308 | case decode res of | 362 | case decode res of |
309 | Right (TransactionR {..}) | 363 | Right (TransactionR {..}) |
310 | | tid == transIdR -> return response | 364 | | tid == transIdR -> return response |
311 | | otherwise -> throwIO $ userError "transaction id mismatch" | 365 | | otherwise -> throwIO $ TransactionFailed |
312 | Left msg -> throwIO $ userError msg | 366 | Left msg -> throwIO $ ParserFailure msg |
313 | 367 | ||
314 | {----------------------------------------------------------------------- | 368 | {----------------------------------------------------------------------- |
315 | -- Connection cache | 369 | -- Connection cache |
@@ -320,8 +374,8 @@ connect m addr conn = do | |||
320 | resp <- transaction m addr conn Connect | 374 | resp <- transaction m addr conn Connect |
321 | case resp of | 375 | case resp of |
322 | Connected cid -> return cid | 376 | Connected cid -> return cid |
323 | Failed msg -> throwIO $ userError $ T.unpack msg | 377 | Failed msg -> throwIO $ QueryFailed msg |
324 | _ -> throwIO $ userError "connect: response type mismatch" | 378 | _ -> throwIO $ UnexpectedResponse "connected" (responseName resp) |
325 | 379 | ||
326 | newConnection :: Manager -> SockAddr -> IO Connection | 380 | newConnection :: Manager -> SockAddr -> IO Connection |
327 | newConnection m addr = do | 381 | newConnection m addr = do |
@@ -358,7 +412,7 @@ retransmission :: Options -> IO a -> IO a | |||
358 | retransmission Options {..} action = go optMinTimeout | 412 | retransmission Options {..} action = go optMinTimeout |
359 | where | 413 | where |
360 | go curTimeout | 414 | go curTimeout |
361 | | curTimeout > optMaxTimeout = throwIO $ userError "tracker down" | 415 | | curTimeout > optMaxTimeout = throwIO $ TrackerNotResponding curTimeout |
362 | | otherwise = do | 416 | | otherwise = do |
363 | r <- timeout curTimeout action | 417 | r <- timeout curTimeout action |
364 | maybe (go (2 * curTimeout)) return r | 418 | maybe (go (2 * curTimeout)) return r |
@@ -370,16 +424,18 @@ queryTracker mgr uri req = do | |||
370 | conn <- getConnection mgr addr | 424 | conn <- getConnection mgr addr |
371 | transaction mgr addr conn req | 425 | transaction mgr addr conn req |
372 | 426 | ||
427 | -- | This function can throw 'RpcException'. | ||
373 | announce :: Manager -> URI -> AnnounceQuery -> IO AnnounceInfo | 428 | announce :: Manager -> URI -> AnnounceQuery -> IO AnnounceInfo |
374 | announce mgr uri q = do | 429 | announce mgr uri q = do |
375 | resp <- queryTracker mgr uri (Announce q) | 430 | resp <- queryTracker mgr uri (Announce q) |
376 | case resp of | 431 | case resp of |
377 | Announced info -> return info | 432 | Announced info -> return info |
378 | _ -> fail "announce: response type mismatch" | 433 | _ -> throwIO $ UnexpectedResponse "announce" (responseName resp) |
379 | 434 | ||
435 | -- | This function can throw 'RpcException'. | ||
380 | scrape :: Manager -> URI -> ScrapeQuery -> IO ScrapeInfo | 436 | scrape :: Manager -> URI -> ScrapeQuery -> IO ScrapeInfo |
381 | scrape mgr uri ihs = do | 437 | scrape mgr uri ihs = do |
382 | resp <- queryTracker mgr uri (Scrape ihs) | 438 | resp <- queryTracker mgr uri (Scrape ihs) |
383 | case resp of | 439 | case resp of |
384 | Scraped info -> return $ L.zip ihs info | 440 | Scraped info -> return $ L.zip ihs info |
385 | _ -> fail "scrape: response type mismatch" | 441 | _ -> throwIO $ UnexpectedResponse "scrape" (responseName resp) |