summaryrefslogtreecommitdiff
path: root/src/Network/BitTorrent/Tracker/Message.hs
diff options
context:
space:
mode:
authorSam Truzjan <pxqr.sta@gmail.com>2013-11-21 21:41:06 +0400
committerSam Truzjan <pxqr.sta@gmail.com>2013-11-21 21:41:06 +0400
commit08d1d4674ef38542e5db24fc398efefbc7bb35af (patch)
tree238538aef942f292961b14fbf686f8f1c886ff09 /src/Network/BitTorrent/Tracker/Message.hs
parentff8eaf451d8c7c420a327c477b16bcc136fc3181 (diff)
Rename protocol module
Diffstat (limited to 'src/Network/BitTorrent/Tracker/Message.hs')
-rw-r--r--src/Network/BitTorrent/Tracker/Message.hs406
1 files changed, 406 insertions, 0 deletions
diff --git a/src/Network/BitTorrent/Tracker/Message.hs b/src/Network/BitTorrent/Tracker/Message.hs
new file mode 100644
index 00000000..8f4c9228
--- /dev/null
+++ b/src/Network/BitTorrent/Tracker/Message.hs
@@ -0,0 +1,406 @@
1-- |
2-- Copyright : (c) Sam Truzjan 2013
3-- License : BSD3
4-- Maintainer : pxqr.sta@gmail.com
5-- Stability : experimental
6-- Portability : portable
7--
8-- Every tracker should support announce query. This query is used
9-- to discover peers within swarm and have two-fold effect:
10--
11-- * peer doing announce discover other peers using peer list from
12-- the response to the announce query.
13--
14-- * tracker store peer information and use it in the succeeding
15-- requests made by other peers, until the peer info expires.
16--
17-- By convention most trackers support another form of request --
18-- scrape query -- which queries the state of a given torrent (or
19-- a list of torrents) that the tracker is managing.
20--
21{-# LANGUAGE FlexibleInstances #-}
22{-# LANGUAGE GeneralizedNewtypeDeriving #-}
23{-# LANGUAGE TemplateHaskell #-}
24{-# LANGUAGE DeriveDataTypeable #-}
25{-# OPTIONS -fno-warn-orphans #-}
26module Network.BitTorrent.Tracker.Protocol
27 ( -- * Announce
28 Event(..)
29 , AnnounceQuery(..)
30 , AnnounceInfo(..)
31
32 -- ** Defaults
33 , defaultNumWant
34 , defaultPorts
35
36 -- * Scrape
37 , ScrapeQuery
38 , ScrapeInfo(..)
39 , Scrape
40
41 -- * TODO
42 , Tracker(..)
43 , scrapeOne
44 )
45 where
46
47import Control.Applicative
48import Control.Exception
49import Control.Monad
50import Data.Aeson (ToJSON, FromJSON)
51import Data.Aeson.TH
52import Data.BEncode as BE
53import Data.BEncode.BDict as BE
54import Data.Char as Char
55import Data.List as L
56import Data.Map as M
57import Data.Maybe
58import Data.Monoid
59import Data.Serialize as S hiding (Result)
60import Data.Text (Text)
61import Data.Text.Encoding
62import Data.Typeable
63import Data.URLEncoded as URL
64import Data.Word
65import Network
66import Network.URI
67import Network.Socket
68
69import Data.Torrent.InfoHash
70import Data.Torrent.Progress
71import Network.BitTorrent.Core.PeerId
72import Network.BitTorrent.Core.PeerAddr
73
74{-----------------------------------------------------------------------
75 Announce messages
76-----------------------------------------------------------------------}
77
78-- | Events used to specify which kind of tracker request is performed.
79data Event = Started
80 -- ^ For the first request: when a peer join the swarm.
81 | Stopped
82 -- ^ Sent when the peer is shutting down.
83 | Completed
84 -- ^ To be sent when the peer completes a download.
85 deriving (Show, Read, Eq, Ord, Enum, Bounded, Typeable)
86
87$(deriveJSON (L.map toLower . L.dropWhile isLower) ''Event)
88
89-- | A tracker request is HTTP GET request; used to include metrics
90-- from clients that help the tracker keep overall statistics about
91-- the torrent. The most important, requests are used by the tracker
92-- to keep track lists of active peer for a particular torrent.
93--
94data AnnounceQuery = AnnounceQuery {
95 reqInfoHash :: !InfoHash
96 -- ^ Hash of info part of the torrent usually obtained from
97 -- 'Torrent'.
98
99 , reqPeerId :: !PeerId
100 -- ^ ID of the peer doing request.
101
102 , reqPort :: !PortNumber
103 -- ^ Port to listen to for connections from other
104 -- peers. Normally, tracker should respond with this port when
105 -- some peer request the tracker with the same info hash.
106
107 , reqProgress :: !Progress
108 -- ^ Current progress of peer doing request.
109
110 , reqIP :: Maybe HostAddress
111 -- ^ The peer IP. Needed only when client communicated with
112 -- tracker throught a proxy.
113
114 , reqNumWant :: Maybe Int
115 -- ^ Number of peers that the peers wants to receive from. See
116 -- note for 'defaultNumWant'.
117
118 , reqEvent :: Maybe Event
119 -- ^ If not specified, the request is regular periodic request.
120 } deriving (Show, Typeable)
121
122$(deriveJSON (L.map toLower . L.dropWhile isLower) ''AnnounceQuery)
123
124newtype PeerList = PeerList { getPeerList :: [PeerAddr] }
125 deriving (Show, Eq, ToJSON, FromJSON, Typeable)
126
127-- | The tracker response includes a peer list that helps the client
128-- participate in the torrent. The most important is 'respPeer' list
129-- used to join the swarm.
130--
131data AnnounceInfo =
132 Failure !Text -- ^ Failure reason in human readable form.
133 | AnnounceInfo {
134 -- | Number of peers completed the torrent. (seeders)
135 respComplete :: !(Maybe Int)
136
137 -- | Number of peers downloading the torrent. (leechers)
138 , respIncomplete :: !(Maybe Int)
139
140 -- | Recommended interval to wait between requests.
141 , respInterval :: !Int
142
143 -- | Minimal amount of time between requests. A peer /should/
144 -- make timeout with at least 'respMinInterval' value,
145 -- otherwise tracker might not respond. If not specified the
146 -- same applies to 'respInterval'.
147 , respMinInterval :: !(Maybe Int)
148
149 -- | Peers that must be contacted.
150 , respPeers :: !PeerList
151
152 -- | Human readable warning.
153 , respWarning :: !(Maybe Text)
154 } deriving (Show, Typeable)
155
156$(deriveJSON (L.map toLower . L.dropWhile isLower) ''AnnounceInfo)
157
158-- | Ports typically reserved for bittorrent P2P listener.
159defaultPorts :: [PortNumber]
160defaultPorts = [6881..6889]
161
162-- | Above 25, new peers are highly unlikely to increase download
163-- speed. Even 30 peers is /plenty/, the official client version 3
164-- in fact only actively forms new connections if it has less than
165-- 30 peers and will refuse connections if it has 55.
166--
167-- So the default value is set to 50 because usually 30-50% of peers
168-- are not responding.
169--
170defaultNumWant :: Int
171defaultNumWant = 50
172
173{-----------------------------------------------------------------------
174 Bencode announce encoding
175-----------------------------------------------------------------------}
176
177instance BEncode PeerList where
178 toBEncode (PeerList xs) = toBEncode xs
179 fromBEncode (BList l ) = PeerList <$> fromBEncode (BList l)
180 fromBEncode (BString s ) = PeerList <$> runGet getCompactPeerList s
181 fromBEncode _ = decodingError "Peer list"
182
183-- | HTTP tracker protocol compatible encoding.
184instance BEncode AnnounceInfo where
185 toBEncode (Failure t) = toDict $
186 "failure reason" .=! t
187 .: endDict
188
189 toBEncode AnnounceInfo {..} = toDict $
190 "complete" .=? respComplete
191 .: "incomplete" .=? respIncomplete
192 .: "interval" .=! respInterval
193 .: "min interval" .=? respMinInterval
194 .: "peers" .=! respPeers
195 .: "warning message" .=? respWarning
196 .: endDict
197
198 fromBEncode (BDict d)
199 | Just t <- BE.lookup "failure reason" d = Failure <$> fromBEncode t
200 | otherwise = (`fromDict` (BDict d)) $ do
201 AnnounceInfo
202 <$>? "complete"
203 <*>? "incomplete"
204 <*>! "interval"
205 <*>? "min interval"
206 <*>! "peers"
207 <*>? "warning message"
208 fromBEncode _ = decodingError "Announce info"
209
210instance URLShow PortNumber where
211 urlShow = urlShow . fromEnum
212
213instance URLShow Word32 where
214 urlShow = show
215
216instance URLShow Event where
217 urlShow e = urlShow (Char.toLower x : xs)
218 where
219 -- INVARIANT: this is always nonempty list
220 (x : xs) = show e
221
222instance URLShow Word64 where
223 urlShow = show
224
225instance URLEncode Progress where
226 urlEncode Progress {..} = mconcat
227 [ s "uploaded" %= _uploaded
228 , s "left" %= _left
229 , s "downloaded" %= _downloaded
230 ]
231 where s :: String -> String; s = id; {-# INLINE s #-}
232
233-- | HTTP tracker protocol compatible encoding.
234instance URLEncode AnnounceQuery where
235 urlEncode AnnounceQuery {..} = mconcat
236 [ s "peer_id" %= reqPeerId
237 , s "port" %= reqPort
238 , urlEncode reqProgress
239
240
241 , s "ip" %=? reqIP
242 , s "numwant" %=? reqNumWant
243 , s "event" %=? reqEvent
244 ]
245 where s :: String -> String; s = id; {-# INLINE s #-}
246
247{-----------------------------------------------------------------------
248 Binary announce encoding
249-----------------------------------------------------------------------}
250
251type EventId = Word32
252
253eventId :: Event -> EventId
254eventId Completed = 1
255eventId Started = 2
256eventId Stopped = 3
257
258-- TODO add Regular event
259putEvent :: Putter (Maybe Event)
260putEvent Nothing = putWord32be 0
261putEvent (Just e) = putWord32be (eventId e)
262
263getEvent :: S.Get (Maybe Event)
264getEvent = do
265 eid <- getWord32be
266 case eid of
267 0 -> return Nothing
268 1 -> return $ Just Completed
269 2 -> return $ Just Started
270 3 -> return $ Just Stopped
271 _ -> fail "unknown event id"
272
273-- | UDP tracker protocol compatible encoding.
274instance Serialize AnnounceQuery where
275 put AnnounceQuery {..} = do
276 put reqInfoHash
277 put reqPeerId
278 put reqProgress
279 putEvent reqEvent
280 putWord32be $ fromMaybe 0 reqIP
281 putWord32be $ 0 -- TODO what the fuck is "key"?
282 putWord32be $ fromIntegral $ fromMaybe (-1) reqNumWant
283
284 put reqPort
285
286 get = do
287 ih <- get
288 pid <- get
289
290 progress <- get
291
292 ev <- getEvent
293 ip <- getWord32be
294-- key <- getWord32be -- TODO
295 want <- getWord32be
296
297 port <- get
298
299 return $ AnnounceQuery {
300 reqInfoHash = ih
301 , reqPeerId = pid
302 , reqPort = port
303 , reqProgress = progress
304 , reqIP = if ip == 0 then Nothing else Just ip
305 , reqNumWant = if want == -1 then Nothing else Just (fromIntegral want)
306 , reqEvent = ev
307 }
308
309-- | UDP tracker protocol compatible encoding.
310instance Serialize AnnounceInfo where
311 put (Failure msg) = put $ encodeUtf8 msg
312 put AnnounceInfo {..} = do
313 putWord32be $ fromIntegral respInterval
314 putWord32be $ fromIntegral $ fromMaybe 0 respIncomplete
315 putWord32be $ fromIntegral $ fromMaybe 0 respComplete
316 forM_ (getPeerList respPeers) put
317
318 get = do
319 interval <- getWord32be
320 leechers <- getWord32be
321 seeders <- getWord32be
322 peers <- many get
323
324 return $ AnnounceInfo {
325 respWarning = Nothing
326 , respInterval = fromIntegral interval
327 , respMinInterval = Nothing
328 , respIncomplete = Just $ fromIntegral leechers
329 , respComplete = Just $ fromIntegral seeders
330 , respPeers = PeerList peers
331 }
332
333{-----------------------------------------------------------------------
334 Scrape messages
335-----------------------------------------------------------------------}
336
337type ScrapeQuery = [InfoHash]
338
339-- | Overall information about particular torrent.
340data ScrapeInfo = ScrapeInfo {
341 -- | Number of seeders - peers with the entire file.
342 siComplete :: {-# UNPACK #-} !Int
343
344 -- | Total number of times the tracker has registered a completion.
345 , siDownloaded :: {-# UNPACK #-} !Int
346
347 -- | Number of leechers.
348 , siIncomplete :: {-# UNPACK #-} !Int
349
350 -- | Name of the torrent file, as specified by the "name"
351 -- file in the info section of the .torrent file.
352 , siName :: !(Maybe Text)
353 } deriving (Show, Eq, Typeable)
354
355$(deriveJSON (L.map toLower . L.dropWhile isLower) ''ScrapeInfo)
356
357-- TODO hash map
358-- | Scrape info about a set of torrents.
359type Scrape = Map InfoHash ScrapeInfo
360
361-- | HTTP tracker protocol compatible encoding.
362instance BEncode ScrapeInfo where
363 toBEncode ScrapeInfo {..} = toDict $
364 "complete" .=! siComplete
365 .: "downloaded" .=! siDownloaded
366 .: "incomplete" .=! siIncomplete
367 .: "name" .=? siName
368 .: endDict
369
370 fromBEncode = fromDict $ do
371 ScrapeInfo <$>! "complete"
372 <*>! "downloaded"
373 <*>! "incomplete"
374 <*>? "name"
375
376-- | UDP tracker protocol complatble encoding.
377instance Serialize ScrapeInfo where
378 put ScrapeInfo {..} = do
379 putWord32be $ fromIntegral siComplete
380 putWord32be $ fromIntegral siDownloaded
381 putWord32be $ fromIntegral siIncomplete
382
383 get = do
384 seeders <- getWord32be
385 downTimes <- getWord32be
386 leechers <- getWord32be
387
388 return $ ScrapeInfo {
389 siComplete = fromIntegral seeders
390 , siDownloaded = fromIntegral downTimes
391 , siIncomplete = fromIntegral leechers
392 , siName = Nothing
393 }
394
395-- | Set of tracker RPCs.
396class Tracker s where
397 connect :: URI -> IO s
398 announce :: s -> AnnounceQuery -> IO AnnounceInfo
399 scrape :: s -> ScrapeQuery -> IO Scrape
400
401-- | More particular version of 'scrape', just for one torrent.
402--
403scrapeOne :: Tracker t => t -> InfoHash -> IO ScrapeInfo
404scrapeOne uri ih = scrape uri [ih] >>= maybe err return . M.lookup ih
405 where
406 err = throwIO $ userError "unable to find info hash in response dict"