diff options
Diffstat (limited to 'bittorrent/src/Network/BitTorrent/Tracker/Message.hs')
-rw-r--r-- | bittorrent/src/Network/BitTorrent/Tracker/Message.hs | 920 |
1 files changed, 920 insertions, 0 deletions
diff --git a/bittorrent/src/Network/BitTorrent/Tracker/Message.hs b/bittorrent/src/Network/BitTorrent/Tracker/Message.hs new file mode 100644 index 00000000..b9b6a9d3 --- /dev/null +++ b/bittorrent/src/Network/BitTorrent/Tracker/Message.hs | |||
@@ -0,0 +1,920 @@ | |||
1 | -- | | ||
2 | -- Copyright : (c) Sam Truzjan 2013 | ||
3 | -- (c) Daniel Gröber 2013 | ||
4 | -- License : BSD3 | ||
5 | -- Maintainer : pxqr.sta@gmail.com | ||
6 | -- Stability : experimental | ||
7 | -- Portability : portable | ||
8 | -- | ||
9 | -- Every tracker should support announce query. This query is used | ||
10 | -- to discover peers within a swarm and have two-fold effect: | ||
11 | -- | ||
12 | -- * peer doing announce discover other peers using peer list from | ||
13 | -- the response to the announce query. | ||
14 | -- | ||
15 | -- * tracker store peer information and use it in the succeeding | ||
16 | -- requests made by other peers, until the peer info expires. | ||
17 | -- | ||
18 | -- By convention most trackers support another form of request — | ||
19 | -- scrape query — which queries the state of a given torrent (or | ||
20 | -- a list of torrents) that the tracker is managing. | ||
21 | -- | ||
22 | {-# LANGUAGE FlexibleContexts #-} | ||
23 | {-# LANGUAGE FlexibleInstances #-} | ||
24 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} | ||
25 | {-# LANGUAGE TemplateHaskell #-} | ||
26 | {-# LANGUAGE DeriveDataTypeable #-} | ||
27 | {-# LANGUAGE DeriveFunctor #-} | ||
28 | {-# LANGUAGE ScopedTypeVariables #-} | ||
29 | {-# LANGUAGE TypeFamilies #-} | ||
30 | {-# OPTIONS -fno-warn-orphans #-} | ||
31 | module Network.BitTorrent.Tracker.Message | ||
32 | ( -- * Announce | ||
33 | -- ** Query | ||
34 | AnnounceEvent (..) | ||
35 | , AnnounceQuery (..) | ||
36 | , renderAnnounceQuery | ||
37 | , ParamParseFailure | ||
38 | , parseAnnounceQuery | ||
39 | |||
40 | -- ** Info | ||
41 | , PeerList (..) | ||
42 | , getPeerList | ||
43 | , AnnounceInfo(..) | ||
44 | , defaultNumWant | ||
45 | , defaultMaxNumWant | ||
46 | , defaultReannounceInterval | ||
47 | |||
48 | -- * Scrape | ||
49 | -- ** Query | ||
50 | , ScrapeQuery | ||
51 | , renderScrapeQuery | ||
52 | , parseScrapeQuery | ||
53 | |||
54 | -- ** Info | ||
55 | , ScrapeEntry (..) | ||
56 | , ScrapeInfo | ||
57 | |||
58 | -- * HTTP specific | ||
59 | -- ** Routes | ||
60 | , PathPiece | ||
61 | , defaultAnnouncePath | ||
62 | , defaultScrapePath | ||
63 | |||
64 | -- ** Preferences | ||
65 | , AnnouncePrefs (..) | ||
66 | , renderAnnouncePrefs | ||
67 | , parseAnnouncePrefs | ||
68 | |||
69 | -- ** Request | ||
70 | , AnnounceRequest (..) | ||
71 | , parseAnnounceRequest | ||
72 | , renderAnnounceRequest | ||
73 | |||
74 | -- ** Response | ||
75 | , announceType | ||
76 | , scrapeType | ||
77 | , parseFailureStatus | ||
78 | |||
79 | -- ** Extra | ||
80 | , queryToSimpleQuery | ||
81 | |||
82 | -- * UDP specific | ||
83 | -- ** Connection | ||
84 | , ConnectionId | ||
85 | , initialConnectionId | ||
86 | |||
87 | -- ** Messages | ||
88 | , Request (..) | ||
89 | , Response (..) | ||
90 | , responseName | ||
91 | |||
92 | -- ** Transaction | ||
93 | , genTransactionId | ||
94 | , TransactionId | ||
95 | , Transaction (..) | ||
96 | ) | ||
97 | where | ||
98 | |||
99 | import Control.Applicative | ||
100 | import Control.Monad | ||
101 | import Data.BEncode as BE hiding (Result) | ||
102 | import Data.BEncode.BDict as BE | ||
103 | import Data.ByteString as BS | ||
104 | import Data.ByteString.Char8 as BC | ||
105 | import Data.Char as Char | ||
106 | import Data.Convertible | ||
107 | import Data.Default | ||
108 | import Data.Either | ||
109 | import Data.List as L | ||
110 | import Data.Maybe | ||
111 | import Data.Monoid | ||
112 | import Data.Serialize as S hiding (Result) | ||
113 | import Data.String | ||
114 | import Data.Text (Text) | ||
115 | import Data.Text.Encoding | ||
116 | import Data.Typeable | ||
117 | import Data.Word | ||
118 | import Data.IP | ||
119 | import Network | ||
120 | import Network.HTTP.Types.QueryLike | ||
121 | import Network.HTTP.Types.URI hiding (urlEncode) | ||
122 | import Network.HTTP.Types.Status | ||
123 | import Network.Socket hiding (Connected) | ||
124 | import Numeric | ||
125 | import System.Entropy | ||
126 | import Text.Read (readMaybe) | ||
127 | |||
128 | import Data.Torrent | ||
129 | import Network.Address | ||
130 | import Network.BitTorrent.Internal.Progress | ||
131 | |||
132 | {----------------------------------------------------------------------- | ||
133 | -- Events | ||
134 | -----------------------------------------------------------------------} | ||
135 | |||
136 | -- | Events are used to specify which kind of announce query is performed. | ||
137 | data AnnounceEvent | ||
138 | -- | For the first request: when download first begins. | ||
139 | = Started | ||
140 | |||
141 | -- | This peer stopped downloading /and/ uploading the torrent or | ||
142 | -- just shutting down. | ||
143 | | Stopped | ||
144 | |||
145 | -- | This peer completed downloading the torrent. This only happen | ||
146 | -- right after last piece have been verified. No 'Completed' is | ||
147 | -- sent if the file was completed when 'Started'. | ||
148 | | Completed | ||
149 | deriving (Show, Read, Eq, Ord, Enum, Bounded, Typeable) | ||
150 | |||
151 | -- | HTTP tracker protocol compatible encoding. | ||
152 | instance QueryValueLike AnnounceEvent where | ||
153 | toQueryValue e = toQueryValue (Char.toLower x : xs) | ||
154 | where | ||
155 | (x : xs) = show e -- INVARIANT: this is always nonempty list | ||
156 | |||
157 | type EventId = Word32 | ||
158 | |||
159 | -- | UDP tracker encoding event codes. | ||
160 | eventId :: AnnounceEvent -> EventId | ||
161 | eventId Completed = 1 | ||
162 | eventId Started = 2 | ||
163 | eventId Stopped = 3 | ||
164 | |||
165 | -- TODO add Regular event | ||
166 | putEvent :: Putter (Maybe AnnounceEvent) | ||
167 | putEvent Nothing = putWord32be 0 | ||
168 | putEvent (Just e) = putWord32be (eventId e) | ||
169 | |||
170 | getEvent :: S.Get (Maybe AnnounceEvent) | ||
171 | getEvent = do | ||
172 | eid <- getWord32be | ||
173 | case eid of | ||
174 | 0 -> return Nothing | ||
175 | 1 -> return $ Just Completed | ||
176 | 2 -> return $ Just Started | ||
177 | 3 -> return $ Just Stopped | ||
178 | _ -> fail "unknown event id" | ||
179 | |||
180 | {----------------------------------------------------------------------- | ||
181 | Announce query | ||
182 | -----------------------------------------------------------------------} | ||
183 | -- TODO add &ipv6= and &ipv4= params to AnnounceQuery | ||
184 | -- http://www.bittorrent.org/beps/bep_0007.html#announce-parameter | ||
185 | |||
186 | -- | A tracker request is HTTP GET request; used to include metrics | ||
187 | -- from clients that help the tracker keep overall statistics about | ||
188 | -- the torrent. The most important, requests are used by the tracker | ||
189 | -- to keep track lists of active peer for a particular torrent. | ||
190 | -- | ||
191 | data AnnounceQuery = AnnounceQuery | ||
192 | { | ||
193 | -- | Hash of info part of the torrent usually obtained from | ||
194 | -- 'Torrent' or 'Magnet'. | ||
195 | reqInfoHash :: !InfoHash | ||
196 | |||
197 | -- | ID of the peer doing request. | ||
198 | , reqPeerId :: !PeerId | ||
199 | |||
200 | -- | Port to listen to for connections from other | ||
201 | -- peers. Tracker should respond with this port when | ||
202 | -- some /other/ peer request the tracker with the same info hash. | ||
203 | -- Normally, this port is choosed from 'defaultPorts'. | ||
204 | , reqPort :: !PortNumber | ||
205 | |||
206 | -- | Current progress of peer doing request. | ||
207 | , reqProgress :: !Progress | ||
208 | |||
209 | -- | The peer IP. Needed only when client communicated with | ||
210 | -- tracker throught a proxy. | ||
211 | , reqIP :: Maybe HostAddress | ||
212 | |||
213 | -- | Number of peers that the peers wants to receive from. It is | ||
214 | -- optional for trackers to honor this limit. See note for | ||
215 | -- 'defaultNumWant'. | ||
216 | , reqNumWant :: Maybe Int | ||
217 | |||
218 | -- | If not specified, the request is regular periodic | ||
219 | -- request. Regular request should be sent | ||
220 | , reqEvent :: Maybe AnnounceEvent | ||
221 | } deriving (Show, Eq, Typeable) | ||
222 | |||
223 | -- | UDP tracker protocol compatible encoding. | ||
224 | instance Serialize AnnounceQuery where | ||
225 | put AnnounceQuery {..} = do | ||
226 | put reqInfoHash | ||
227 | put reqPeerId | ||
228 | put reqProgress | ||
229 | putEvent reqEvent | ||
230 | putWord32host $ fromMaybe 0 reqIP | ||
231 | putWord32be $ 0 -- TODO what the fuck is "key"? | ||
232 | putWord32be $ fromIntegral $ fromMaybe (-1) reqNumWant | ||
233 | |||
234 | put reqPort | ||
235 | |||
236 | get = do | ||
237 | ih <- get | ||
238 | pid <- get | ||
239 | |||
240 | progress <- get | ||
241 | |||
242 | ev <- getEvent | ||
243 | ip <- getWord32be | ||
244 | -- key <- getWord32be -- TODO | ||
245 | want <- getWord32be | ||
246 | |||
247 | port <- get | ||
248 | |||
249 | return $ AnnounceQuery { | ||
250 | reqInfoHash = ih | ||
251 | , reqPeerId = pid | ||
252 | , reqPort = port | ||
253 | , reqProgress = progress | ||
254 | , reqIP = if ip == 0 then Nothing else Just ip | ||
255 | , reqNumWant = if want == -1 then Nothing | ||
256 | else Just (fromIntegral want) | ||
257 | , reqEvent = ev | ||
258 | } | ||
259 | |||
260 | instance QueryValueLike PortNumber where | ||
261 | toQueryValue = toQueryValue . show . fromEnum | ||
262 | |||
263 | instance QueryValueLike Word32 where | ||
264 | toQueryValue = toQueryValue . show | ||
265 | |||
266 | instance QueryValueLike Int where | ||
267 | toQueryValue = toQueryValue . show | ||
268 | |||
269 | -- | HTTP tracker protocol compatible encoding. | ||
270 | instance QueryLike AnnounceQuery where | ||
271 | toQuery AnnounceQuery {..} = | ||
272 | toQuery reqProgress ++ | ||
273 | [ ("info_hash", toQueryValue reqInfoHash) -- TODO use 'paramName' | ||
274 | , ("peer_id" , toQueryValue reqPeerId) | ||
275 | , ("port" , toQueryValue reqPort) | ||
276 | , ("ip" , toQueryValue reqIP) | ||
277 | , ("numwant" , toQueryValue reqNumWant) | ||
278 | , ("event" , toQueryValue reqEvent) | ||
279 | ] | ||
280 | |||
281 | -- | Filter @param=value@ pairs with the unset value. | ||
282 | queryToSimpleQuery :: Query -> SimpleQuery | ||
283 | queryToSimpleQuery = catMaybes . L.map f | ||
284 | where | ||
285 | f (_, Nothing) = Nothing | ||
286 | f (a, Just b ) = Just (a, b) | ||
287 | |||
288 | -- | Encode announce query to query string. | ||
289 | renderAnnounceQuery :: AnnounceQuery -> SimpleQuery | ||
290 | renderAnnounceQuery = queryToSimpleQuery . toQuery | ||
291 | |||
292 | data QueryParam | ||
293 | -- announce query | ||
294 | = ParamInfoHash | ||
295 | | ParamPeerId | ||
296 | | ParamPort | ||
297 | | ParamUploaded | ||
298 | | ParamLeft | ||
299 | | ParamDownloaded | ||
300 | | ParamIP | ||
301 | | ParamNumWant | ||
302 | | ParamEvent | ||
303 | -- announce query ext | ||
304 | | ParamCompact | ||
305 | | ParamNoPeerId | ||
306 | deriving (Show, Eq, Ord, Enum) | ||
307 | |||
308 | paramName :: QueryParam -> BS.ByteString | ||
309 | paramName ParamInfoHash = "info_hash" | ||
310 | paramName ParamPeerId = "peer_id" | ||
311 | paramName ParamPort = "port" | ||
312 | paramName ParamUploaded = "uploaded" | ||
313 | paramName ParamLeft = "left" | ||
314 | paramName ParamDownloaded = "downloaded" | ||
315 | paramName ParamIP = "ip" | ||
316 | paramName ParamNumWant = "numwant" | ||
317 | paramName ParamEvent = "event" | ||
318 | paramName ParamCompact = "compact" | ||
319 | paramName ParamNoPeerId = "no_peer_id" | ||
320 | {-# INLINE paramName #-} | ||
321 | |||
322 | class FromParam a where | ||
323 | fromParam :: BS.ByteString -> Maybe a | ||
324 | |||
325 | instance FromParam Bool where | ||
326 | fromParam "0" = Just False | ||
327 | fromParam "1" = Just True | ||
328 | fromParam _ = Nothing | ||
329 | |||
330 | instance FromParam InfoHash where | ||
331 | fromParam = either (const Nothing) pure . safeConvert | ||
332 | |||
333 | instance FromParam PeerId where | ||
334 | fromParam = either (const Nothing) pure . safeConvert | ||
335 | |||
336 | instance FromParam Word32 where | ||
337 | fromParam = readMaybe . BC.unpack | ||
338 | |||
339 | instance FromParam Word64 where | ||
340 | fromParam = readMaybe . BC.unpack | ||
341 | |||
342 | instance FromParam Int where | ||
343 | fromParam = readMaybe . BC.unpack | ||
344 | |||
345 | instance FromParam PortNumber where | ||
346 | fromParam bs = fromIntegral <$> (fromParam bs :: Maybe Word32) | ||
347 | |||
348 | instance FromParam AnnounceEvent where | ||
349 | fromParam bs = do | ||
350 | (x, xs) <- BC.uncons bs | ||
351 | readMaybe $ BC.unpack $ BC.cons (Char.toUpper x) xs | ||
352 | |||
353 | -- | 'ParamParseFailure' represent errors can occur while parsing HTTP | ||
354 | -- tracker requests. In case of failure, this can be used to provide | ||
355 | -- more informative 'statusCode' and 'statusMessage' in tracker | ||
356 | -- responses. | ||
357 | -- | ||
358 | data ParamParseFailure | ||
359 | = Missing QueryParam -- ^ param not found in query string; | ||
360 | | Invalid QueryParam BS.ByteString -- ^ param present but not valid. | ||
361 | deriving (Show, Eq) | ||
362 | |||
363 | type ParseResult = Either ParamParseFailure | ||
364 | |||
365 | withError :: ParamParseFailure -> Maybe a -> ParseResult a | ||
366 | withError e = maybe (Left e) Right | ||
367 | |||
368 | reqParam :: FromParam a => QueryParam -> SimpleQuery -> ParseResult a | ||
369 | reqParam param xs = do | ||
370 | val <- withError (Missing param) $ L.lookup (paramName param) xs | ||
371 | withError (Invalid param val) (fromParam val) | ||
372 | |||
373 | optParam :: FromParam a => QueryParam -> SimpleQuery -> ParseResult (Maybe a) | ||
374 | optParam param ps | ||
375 | | Just x <- L.lookup (paramName param) ps | ||
376 | = pure <$> withError (Invalid param x) (fromParam x) | ||
377 | | otherwise = pure Nothing | ||
378 | |||
379 | parseProgress :: SimpleQuery -> ParseResult Progress | ||
380 | parseProgress params = Progress | ||
381 | <$> reqParam ParamDownloaded params | ||
382 | <*> reqParam ParamLeft params | ||
383 | <*> reqParam ParamUploaded params | ||
384 | |||
385 | -- | Parse announce request from a query string. | ||
386 | parseAnnounceQuery :: SimpleQuery -> ParseResult AnnounceQuery | ||
387 | parseAnnounceQuery params = AnnounceQuery | ||
388 | <$> reqParam ParamInfoHash params | ||
389 | <*> reqParam ParamPeerId params | ||
390 | <*> reqParam ParamPort params | ||
391 | <*> parseProgress params | ||
392 | <*> optParam ParamIP params | ||
393 | <*> optParam ParamNumWant params | ||
394 | <*> optParam ParamEvent params | ||
395 | |||
396 | {----------------------------------------------------------------------- | ||
397 | -- Announce Info | ||
398 | -----------------------------------------------------------------------} | ||
399 | -- TODO check if announceinterval/complete/incomplete is positive ints | ||
400 | |||
401 | -- | Tracker can return peer list in either compact(BEP23) or not | ||
402 | -- compact form. | ||
403 | -- | ||
404 | -- For more info see: <http://www.bittorrent.org/beps/bep_0023.html> | ||
405 | -- | ||
406 | data PeerList ip | ||
407 | = PeerList [PeerAddr IP] | ||
408 | | CompactPeerList [PeerAddr ip] | ||
409 | deriving (Show, Eq, Typeable, Functor) | ||
410 | |||
411 | -- | The empty non-compact peer list. | ||
412 | instance Default (PeerList IP) where | ||
413 | def = PeerList [] | ||
414 | {-# INLINE def #-} | ||
415 | |||
416 | getPeerList :: PeerList IP -> [PeerAddr IP] | ||
417 | getPeerList (PeerList xs) = xs | ||
418 | getPeerList (CompactPeerList xs) = xs | ||
419 | |||
420 | instance Serialize a => BEncode (PeerList a) where | ||
421 | toBEncode (PeerList xs) = toBEncode xs | ||
422 | toBEncode (CompactPeerList xs) = toBEncode $ runPut (mapM_ put xs) | ||
423 | |||
424 | fromBEncode (BList l ) = PeerList <$> fromBEncode (BList l) | ||
425 | fromBEncode (BString s ) = CompactPeerList <$> runGet (many get) s | ||
426 | fromBEncode _ = decodingError "PeerList: should be a BString or BList" | ||
427 | |||
428 | -- | The tracker response includes a peer list that helps the client | ||
429 | -- participate in the torrent. The most important is 'respPeer' list | ||
430 | -- used to join the swarm. | ||
431 | -- | ||
432 | data AnnounceInfo = | ||
433 | Failure !Text -- ^ Failure reason in human readable form. | ||
434 | | AnnounceInfo { | ||
435 | -- | Number of peers completed the torrent. (seeders) | ||
436 | respComplete :: !(Maybe Int) | ||
437 | |||
438 | -- | Number of peers downloading the torrent. (leechers) | ||
439 | , respIncomplete :: !(Maybe Int) | ||
440 | |||
441 | -- | Recommended interval to wait between requests, in seconds. | ||
442 | , respInterval :: !Int | ||
443 | |||
444 | -- | Minimal amount of time between requests, in seconds. A | ||
445 | -- peer /should/ make timeout with at least 'respMinInterval' | ||
446 | -- value, otherwise tracker might not respond. If not specified | ||
447 | -- the same applies to 'respInterval'. | ||
448 | , respMinInterval :: !(Maybe Int) | ||
449 | |||
450 | -- | Peers that must be contacted. | ||
451 | , respPeers :: !(PeerList IP) | ||
452 | |||
453 | -- | Human readable warning. | ||
454 | , respWarning :: !(Maybe Text) | ||
455 | } deriving (Show, Eq, Typeable) | ||
456 | |||
457 | -- | Empty peer list with default reannounce interval. | ||
458 | instance Default AnnounceInfo where | ||
459 | def = AnnounceInfo | ||
460 | { respComplete = Nothing | ||
461 | , respIncomplete = Nothing | ||
462 | , respInterval = defaultReannounceInterval | ||
463 | , respMinInterval = Nothing | ||
464 | , respPeers = def | ||
465 | , respWarning = Nothing | ||
466 | } | ||
467 | |||
468 | -- | HTTP tracker protocol compatible encoding. | ||
469 | instance BEncode AnnounceInfo where | ||
470 | toBEncode (Failure t) = toDict $ | ||
471 | "failure reason" .=! t | ||
472 | .: endDict | ||
473 | |||
474 | toBEncode AnnounceInfo {..} = toDict $ | ||
475 | "complete" .=? respComplete | ||
476 | .: "incomplete" .=? respIncomplete | ||
477 | .: "interval" .=! respInterval | ||
478 | .: "min interval" .=? respMinInterval | ||
479 | .: "peers" .=! peers | ||
480 | .: "peers6" .=? peers6 | ||
481 | .: "warning message" .=? respWarning | ||
482 | .: endDict | ||
483 | where | ||
484 | (peers, peers6) = prttn respPeers | ||
485 | |||
486 | prttn :: PeerList IP -> (PeerList IPv4, Maybe (PeerList IPv6)) | ||
487 | prttn (PeerList xs) = (PeerList xs, Nothing) | ||
488 | prttn (CompactPeerList xs) = mk $ partitionEithers $ toEither <$> xs | ||
489 | where | ||
490 | mk (v4s, v6s) | ||
491 | | L.null v6s = (CompactPeerList v4s, Nothing) | ||
492 | | otherwise = (CompactPeerList v4s, Just (CompactPeerList v6s)) | ||
493 | |||
494 | toEither :: PeerAddr IP -> Either (PeerAddr IPv4) (PeerAddr IPv6) | ||
495 | toEither PeerAddr {..} = case peerHost of | ||
496 | IPv4 ipv4 -> Left $ PeerAddr peerId ipv4 peerPort | ||
497 | IPv6 ipv6 -> Right $ PeerAddr peerId ipv6 peerPort | ||
498 | |||
499 | fromBEncode (BDict d) | ||
500 | | Just t <- BE.lookup "failure reason" d = Failure <$> fromBEncode t | ||
501 | | otherwise = (`fromDict` (BDict d)) $ | ||
502 | AnnounceInfo | ||
503 | <$>? "complete" | ||
504 | <*>? "incomplete" | ||
505 | <*>! "interval" | ||
506 | <*>? "min interval" | ||
507 | <*> (uncurry merge =<< (,) <$>! "peers" <*>? "peers6") | ||
508 | <*>? "warning message" | ||
509 | where | ||
510 | merge :: PeerList IPv4 -> Maybe (PeerList IPv6) -> BE.Get (PeerList IP) | ||
511 | merge (PeerList ips) Nothing = pure (PeerList ips) | ||
512 | merge (PeerList _ ) (Just _) | ||
513 | = fail "PeerList: non-compact peer list provided, \ | ||
514 | \but the `peers6' field present" | ||
515 | |||
516 | merge (CompactPeerList ipv4s) Nothing | ||
517 | = pure $ CompactPeerList (fmap IPv4 <$> ipv4s) | ||
518 | |||
519 | merge (CompactPeerList _ ) (Just (PeerList _)) | ||
520 | = fail "PeerList: the `peers6' field value \ | ||
521 | \should contain *compact* peer list" | ||
522 | |||
523 | merge (CompactPeerList ipv4s) (Just (CompactPeerList ipv6s)) | ||
524 | = pure $ CompactPeerList $ | ||
525 | (fmap IPv4 <$> ipv4s) <> (fmap IPv6 <$> ipv6s) | ||
526 | |||
527 | fromBEncode _ = decodingError "Announce info" | ||
528 | |||
529 | -- | UDP tracker protocol compatible encoding. | ||
530 | instance Serialize AnnounceInfo where | ||
531 | put (Failure msg) = put $ encodeUtf8 msg | ||
532 | put AnnounceInfo {..} = do | ||
533 | putWord32be $ fromIntegral respInterval | ||
534 | putWord32be $ fromIntegral $ fromMaybe 0 respIncomplete | ||
535 | putWord32be $ fromIntegral $ fromMaybe 0 respComplete | ||
536 | forM_ (fmap ipv4 <$> getPeerList respPeers) put | ||
537 | |||
538 | get = do | ||
539 | interval <- getWord32be | ||
540 | leechers <- getWord32be | ||
541 | seeders <- getWord32be | ||
542 | peers <- many $ fmap IPv4 <$> get | ||
543 | |||
544 | return $ AnnounceInfo { | ||
545 | respWarning = Nothing | ||
546 | , respInterval = fromIntegral interval | ||
547 | , respMinInterval = Nothing | ||
548 | , respIncomplete = Just $ fromIntegral leechers | ||
549 | , respComplete = Just $ fromIntegral seeders | ||
550 | , respPeers = PeerList peers | ||
551 | } | ||
552 | |||
553 | -- | Decodes announce response from bencoded string, for debugging only. | ||
554 | instance IsString AnnounceInfo where | ||
555 | fromString str = either (error . format) id $ BE.decode (fromString str) | ||
556 | where | ||
557 | format msg = "fromString: unable to decode AnnounceInfo: " ++ msg | ||
558 | |||
559 | -- | Above 25, new peers are highly unlikely to increase download | ||
560 | -- speed. Even 30 peers is /plenty/, the official client version 3 | ||
561 | -- in fact only actively forms new connections if it has less than | ||
562 | -- 30 peers and will refuse connections if it has 55. | ||
563 | -- | ||
564 | -- <https://wiki.theory.org/BitTorrent_Tracker_Protocol#Basic_Tracker_Announce_Request> | ||
565 | -- | ||
566 | defaultNumWant :: Int | ||
567 | defaultNumWant = 50 | ||
568 | |||
569 | -- | Reasonable upper bound of numwant parameter. | ||
570 | defaultMaxNumWant :: Int | ||
571 | defaultMaxNumWant = 200 | ||
572 | |||
573 | -- | Widely used reannounce interval. Note: tracker clients should not | ||
574 | -- use this value! | ||
575 | defaultReannounceInterval :: Int | ||
576 | defaultReannounceInterval = 30 * 60 | ||
577 | |||
578 | {----------------------------------------------------------------------- | ||
579 | Scrape message | ||
580 | -----------------------------------------------------------------------} | ||
581 | |||
582 | -- | Scrape query used to specify a set of torrent to scrape. | ||
583 | -- If list is empty then tracker should return scrape info about each | ||
584 | -- torrent. | ||
585 | type ScrapeQuery = [InfoHash] | ||
586 | |||
587 | -- TODO | ||
588 | -- data ScrapeQuery | ||
589 | -- = ScrapeAll | ||
590 | -- | ScrapeSingle InfoHash | ||
591 | -- | ScrapeMulti (HashSet InfoHash) | ||
592 | -- deriving (Show) | ||
593 | -- | ||
594 | -- data ScrapeInfo | ||
595 | -- = ScrapeAll (HashMap InfoHash ScrapeEntry) | ||
596 | -- | ScrapeSingle InfoHash ScrapeEntry | ||
597 | -- | ScrapeMulti (HashMap InfoHash ScrapeEntry) | ||
598 | -- | ||
599 | |||
600 | scrapeParam :: BS.ByteString | ||
601 | scrapeParam = "info_hash" | ||
602 | |||
603 | isScrapeParam :: BS.ByteString -> Bool | ||
604 | isScrapeParam = (==) scrapeParam | ||
605 | |||
606 | -- | Parse scrape query to query string. | ||
607 | parseScrapeQuery :: SimpleQuery -> ScrapeQuery | ||
608 | parseScrapeQuery | ||
609 | = catMaybes . L.map (fromParam . snd) . L.filter (isScrapeParam . fst) | ||
610 | |||
611 | -- | Render scrape query to query string. | ||
612 | renderScrapeQuery :: ScrapeQuery -> SimpleQuery | ||
613 | renderScrapeQuery = queryToSimpleQuery . L.map mkPair | ||
614 | where | ||
615 | mkPair ih = (scrapeParam, toQueryValue ih) | ||
616 | |||
617 | -- | Overall information about particular torrent. | ||
618 | data ScrapeEntry = ScrapeEntry { | ||
619 | -- | Number of seeders - peers with the entire file. | ||
620 | siComplete :: {-# UNPACK #-} !Int | ||
621 | |||
622 | -- | Total number of times the tracker has registered a completion. | ||
623 | , siDownloaded :: {-# UNPACK #-} !Int | ||
624 | |||
625 | -- | Number of leechers. | ||
626 | , siIncomplete :: {-# UNPACK #-} !Int | ||
627 | |||
628 | -- | Name of the torrent file, as specified by the "name" | ||
629 | -- file in the info section of the .torrent file. | ||
630 | , siName :: !(Maybe Text) | ||
631 | } deriving (Show, Eq, Typeable) | ||
632 | |||
633 | -- | HTTP tracker protocol compatible encoding. | ||
634 | instance BEncode ScrapeEntry where | ||
635 | toBEncode ScrapeEntry {..} = toDict $ | ||
636 | "complete" .=! siComplete | ||
637 | .: "downloaded" .=! siDownloaded | ||
638 | .: "incomplete" .=! siIncomplete | ||
639 | .: "name" .=? siName | ||
640 | .: endDict | ||
641 | |||
642 | fromBEncode = fromDict $ ScrapeEntry | ||
643 | <$>! "complete" | ||
644 | <*>! "downloaded" | ||
645 | <*>! "incomplete" | ||
646 | <*>? "name" | ||
647 | |||
648 | -- | UDP tracker protocol compatible encoding. | ||
649 | instance Serialize ScrapeEntry where | ||
650 | put ScrapeEntry {..} = do | ||
651 | putWord32be $ fromIntegral siComplete | ||
652 | putWord32be $ fromIntegral siDownloaded | ||
653 | putWord32be $ fromIntegral siIncomplete | ||
654 | |||
655 | get = ScrapeEntry | ||
656 | <$> (fromIntegral <$> getWord32be) | ||
657 | <*> (fromIntegral <$> getWord32be) | ||
658 | <*> (fromIntegral <$> getWord32be) | ||
659 | <*> pure Nothing | ||
660 | |||
661 | -- | Scrape info about a set of torrents. | ||
662 | type ScrapeInfo = [(InfoHash, ScrapeEntry)] | ||
663 | |||
664 | {----------------------------------------------------------------------- | ||
665 | -- HTTP specific | ||
666 | -----------------------------------------------------------------------} | ||
667 | |||
668 | -- | Some HTTP trackers allow to choose prefered representation of the | ||
669 | -- 'AnnounceInfo'. It's optional for trackers to honor any of this | ||
670 | -- options. | ||
671 | data AnnouncePrefs = AnnouncePrefs | ||
672 | { -- | If specified, "compact" parameter is used to advise the | ||
673 | -- tracker to send peer id list as: | ||
674 | -- | ||
675 | -- * bencoded list (extCompact = Just False); | ||
676 | -- * or more compact binary string (extCompact = Just True). | ||
677 | -- | ||
678 | -- The later is prefered since compact peer list will reduce the | ||
679 | -- size of tracker responses. Hovewer, if tracker do not support | ||
680 | -- this extension then it can return peer list in either form. | ||
681 | -- | ||
682 | -- For more info see: <http://www.bittorrent.org/beps/bep_0023.html> | ||
683 | -- | ||
684 | extCompact :: !(Maybe Bool) | ||
685 | |||
686 | -- | If specified, "no_peer_id" parameter is used advise tracker | ||
687 | -- to either send or not to send peer id in tracker response. | ||
688 | -- Tracker may not support this extension as well. | ||
689 | -- | ||
690 | -- For more info see: | ||
691 | -- <http://permalink.gmane.org/gmane.network.bit-torrent.general/4030> | ||
692 | -- | ||
693 | , extNoPeerId :: !(Maybe Bool) | ||
694 | } deriving (Show, Eq, Typeable) | ||
695 | |||
696 | instance Default AnnouncePrefs where | ||
697 | def = AnnouncePrefs Nothing Nothing | ||
698 | |||
699 | instance QueryLike AnnouncePrefs where | ||
700 | toQuery AnnouncePrefs {..} = | ||
701 | [ ("compact", toQueryFlag <$> extCompact) -- TODO use 'paramName' | ||
702 | , ("no_peer_id", toQueryFlag <$> extNoPeerId) | ||
703 | ] | ||
704 | where | ||
705 | toQueryFlag False = "0" | ||
706 | toQueryFlag True = "1" | ||
707 | |||
708 | -- | Parse announce query extended part from query string. | ||
709 | parseAnnouncePrefs :: SimpleQuery -> AnnouncePrefs | ||
710 | parseAnnouncePrefs params = either (const def) id $ | ||
711 | AnnouncePrefs | ||
712 | <$> optParam ParamCompact params | ||
713 | <*> optParam ParamNoPeerId params | ||
714 | |||
715 | -- | Render announce preferences to query string. | ||
716 | renderAnnouncePrefs :: AnnouncePrefs -> SimpleQuery | ||
717 | renderAnnouncePrefs = queryToSimpleQuery . toQuery | ||
718 | |||
719 | -- | HTTP tracker request with preferences. | ||
720 | data AnnounceRequest = AnnounceRequest | ||
721 | { announceQuery :: AnnounceQuery -- ^ Request query params. | ||
722 | , announcePrefs :: AnnouncePrefs -- ^ Optional advises to the tracker. | ||
723 | } deriving (Show, Eq, Typeable) | ||
724 | |||
725 | instance QueryLike AnnounceRequest where | ||
726 | toQuery AnnounceRequest{..} = | ||
727 | toQuery announcePrefs <> | ||
728 | toQuery announceQuery | ||
729 | |||
730 | -- | Parse announce request from query string. | ||
731 | parseAnnounceRequest :: SimpleQuery -> ParseResult AnnounceRequest | ||
732 | parseAnnounceRequest params = AnnounceRequest | ||
733 | <$> parseAnnounceQuery params | ||
734 | <*> pure (parseAnnouncePrefs params) | ||
735 | |||
736 | -- | Render announce request to query string. | ||
737 | renderAnnounceRequest :: AnnounceRequest -> SimpleQuery | ||
738 | renderAnnounceRequest = queryToSimpleQuery . toQuery | ||
739 | |||
740 | type PathPiece = BS.ByteString | ||
741 | |||
742 | defaultAnnouncePath :: PathPiece | ||
743 | defaultAnnouncePath = "announce" | ||
744 | |||
745 | defaultScrapePath :: PathPiece | ||
746 | defaultScrapePath = "scrape" | ||
747 | |||
748 | missingOffset :: Int | ||
749 | missingOffset = 101 | ||
750 | |||
751 | invalidOffset :: Int | ||
752 | invalidOffset = 150 | ||
753 | |||
754 | parseFailureCode :: ParamParseFailure -> Int | ||
755 | parseFailureCode (Missing param ) = missingOffset + fromEnum param | ||
756 | parseFailureCode (Invalid param _) = invalidOffset + fromEnum param | ||
757 | |||
758 | parseFailureMessage :: ParamParseFailure -> BS.ByteString | ||
759 | parseFailureMessage e = BS.concat $ case e of | ||
760 | Missing p -> ["Missing parameter: ", paramName p] | ||
761 | Invalid p v -> ["Invalid parameter: ", paramName p, " = ", v] | ||
762 | |||
763 | -- | HTTP response /content type/ for announce info. | ||
764 | announceType :: ByteString | ||
765 | announceType = "text/plain" | ||
766 | |||
767 | -- | HTTP response /content type/ for scrape info. | ||
768 | scrapeType :: ByteString | ||
769 | scrapeType = "text/plain" | ||
770 | |||
771 | -- | Get HTTP response status from a announce params parse failure. | ||
772 | -- | ||
773 | -- For more info see: | ||
774 | -- <https://wiki.theory.org/BitTorrent_Tracker_Protocol#Response_Codes> | ||
775 | -- | ||
776 | parseFailureStatus :: ParamParseFailure -> Status | ||
777 | parseFailureStatus = mkStatus <$> parseFailureCode <*> parseFailureMessage | ||
778 | |||
779 | {----------------------------------------------------------------------- | ||
780 | -- UDP specific message types | ||
781 | -----------------------------------------------------------------------} | ||
782 | |||
783 | genToken :: IO Word64 | ||
784 | genToken = do | ||
785 | bs <- getEntropy 8 | ||
786 | either err return $ runGet getWord64be bs | ||
787 | where | ||
788 | err = error "genToken: impossible happen" | ||
789 | |||
790 | -- | Connection Id is used for entire tracker session. | ||
791 | newtype ConnectionId = ConnectionId Word64 | ||
792 | deriving (Eq, Serialize) | ||
793 | |||
794 | instance Show ConnectionId where | ||
795 | showsPrec _ (ConnectionId cid) = showString "0x" <> showHex cid | ||
796 | |||
797 | initialConnectionId :: ConnectionId | ||
798 | initialConnectionId = ConnectionId 0x41727101980 | ||
799 | |||
800 | -- | Transaction Id is used within a UDP RPC. | ||
801 | newtype TransactionId = TransactionId Word32 | ||
802 | deriving (Eq, Ord, Enum, Bounded, Serialize) | ||
803 | |||
804 | instance Show TransactionId where | ||
805 | showsPrec _ (TransactionId tid) = showString "0x" <> showHex tid | ||
806 | |||
807 | genTransactionId :: IO TransactionId | ||
808 | genTransactionId = (TransactionId . fromIntegral) <$> genToken | ||
809 | |||
810 | data Request | ||
811 | = Connect | ||
812 | | Announce AnnounceQuery | ||
813 | | Scrape ScrapeQuery | ||
814 | deriving Show | ||
815 | |||
816 | data Response | ||
817 | = Connected ConnectionId | ||
818 | | Announced AnnounceInfo | ||
819 | | Scraped [ScrapeEntry] | ||
820 | | Failed Text | ||
821 | deriving Show | ||
822 | |||
823 | responseName :: Response -> String | ||
824 | responseName (Connected _) = "connected" | ||
825 | responseName (Announced _) = "announced" | ||
826 | responseName (Scraped _) = "scraped" | ||
827 | responseName (Failed _) = "failed" | ||
828 | |||
829 | data family Transaction a | ||
830 | data instance Transaction Request = TransactionQ | ||
831 | { connIdQ :: {-# UNPACK #-} !ConnectionId | ||
832 | , transIdQ :: {-# UNPACK #-} !TransactionId | ||
833 | , request :: !Request | ||
834 | } deriving Show | ||
835 | data instance Transaction Response = TransactionR | ||
836 | { transIdR :: {-# UNPACK #-} !TransactionId | ||
837 | , response :: !Response | ||
838 | } deriving Show | ||
839 | |||
840 | -- TODO newtype | ||
841 | newtype MessageId = MessageId Word32 | ||
842 | deriving (Show, Eq, Num, Serialize) | ||
843 | |||
844 | connectId, announceId, scrapeId, errorId :: MessageId | ||
845 | connectId = 0 | ||
846 | announceId = 1 | ||
847 | scrapeId = 2 | ||
848 | errorId = 3 | ||
849 | |||
850 | instance Serialize (Transaction Request) where | ||
851 | put TransactionQ {..} = do | ||
852 | case request of | ||
853 | Connect -> do | ||
854 | put initialConnectionId | ||
855 | put connectId | ||
856 | put transIdQ | ||
857 | |||
858 | Announce ann -> do | ||
859 | put connIdQ | ||
860 | put announceId | ||
861 | put transIdQ | ||
862 | put ann | ||
863 | |||
864 | Scrape hashes -> do | ||
865 | put connIdQ | ||
866 | put scrapeId | ||
867 | put transIdQ | ||
868 | forM_ hashes put | ||
869 | |||
870 | get = do | ||
871 | cid <- get | ||
872 | mid <- get | ||
873 | TransactionQ cid <$> S.get <*> getBody mid | ||
874 | where | ||
875 | getBody :: MessageId -> S.Get Request | ||
876 | getBody msgId | ||
877 | | msgId == connectId = pure Connect | ||
878 | | msgId == announceId = Announce <$> get | ||
879 | | msgId == scrapeId = Scrape <$> many get | ||
880 | | otherwise = fail errMsg | ||
881 | where | ||
882 | errMsg = "unknown request: " ++ show msgId | ||
883 | |||
884 | instance Serialize (Transaction Response) where | ||
885 | put TransactionR {..} = do | ||
886 | case response of | ||
887 | Connected conn -> do | ||
888 | put connectId | ||
889 | put transIdR | ||
890 | put conn | ||
891 | |||
892 | Announced info -> do | ||
893 | put announceId | ||
894 | put transIdR | ||
895 | put info | ||
896 | |||
897 | Scraped infos -> do | ||
898 | put scrapeId | ||
899 | put transIdR | ||
900 | forM_ infos put | ||
901 | |||
902 | Failed info -> do | ||
903 | put errorId | ||
904 | put transIdR | ||
905 | put (encodeUtf8 info) | ||
906 | |||
907 | |||
908 | get = do | ||
909 | mid <- get | ||
910 | TransactionR <$> get <*> getBody mid | ||
911 | where | ||
912 | getBody :: MessageId -> S.Get Response | ||
913 | getBody msgId | ||
914 | | msgId == connectId = Connected <$> get | ||
915 | | msgId == announceId = Announced <$> get | ||
916 | | msgId == scrapeId = Scraped <$> many get | ||
917 | | msgId == errorId = (Failed . decodeUtf8) <$> get | ||
918 | | otherwise = fail msg | ||
919 | where | ||
920 | msg = "unknown response: " ++ show msgId | ||