diff options
author | joe <joe@jerkface.net> | 2017-09-15 06:22:10 -0400 |
---|---|---|
committer | joe <joe@jerkface.net> | 2017-09-15 06:22:10 -0400 |
commit | 12cbb3af2413dc28838ed271351dda16df8f7bdb (patch) | |
tree | 2db77a787e18a81a8369a8d73fee369d8826f064 /bittorrent/src/Network/BitTorrent/Tracker | |
parent | 362357c6d08cbd8dffa627a1e80199dcb9ba231f (diff) |
Separating dht-client library from bittorrent package.
Diffstat (limited to 'bittorrent/src/Network/BitTorrent/Tracker')
-rw-r--r-- | bittorrent/src/Network/BitTorrent/Tracker/List.hs | 193 | ||||
-rw-r--r-- | bittorrent/src/Network/BitTorrent/Tracker/Message.hs | 920 | ||||
-rw-r--r-- | bittorrent/src/Network/BitTorrent/Tracker/RPC.hs | 175 | ||||
-rw-r--r-- | bittorrent/src/Network/BitTorrent/Tracker/RPC/HTTP.hs | 191 | ||||
-rw-r--r-- | bittorrent/src/Network/BitTorrent/Tracker/RPC/UDP.hs | 454 | ||||
-rw-r--r-- | bittorrent/src/Network/BitTorrent/Tracker/Session.hs | 306 |
6 files changed, 2239 insertions, 0 deletions
diff --git a/bittorrent/src/Network/BitTorrent/Tracker/List.hs b/bittorrent/src/Network/BitTorrent/Tracker/List.hs new file mode 100644 index 00000000..0eb11641 --- /dev/null +++ b/bittorrent/src/Network/BitTorrent/Tracker/List.hs | |||
@@ -0,0 +1,193 @@ | |||
1 | -- | | ||
2 | -- Copyright : (c) Sam Truzjan 2014 | ||
3 | -- License : BSD | ||
4 | -- Maintainer : pxqr.sta@gmail.com | ||
5 | -- Stability : experimental | ||
6 | -- Portability : portable | ||
7 | -- | ||
8 | -- Multitracker Metadata Extension support. | ||
9 | -- | ||
10 | -- For more info see: <http://www.bittorrent.org/beps/bep_0012.html> | ||
11 | -- | ||
12 | {-# LANGUAGE FlexibleInstances #-} | ||
13 | module Network.BitTorrent.Tracker.List | ||
14 | ( -- * Tracker list | ||
15 | TierEntry | ||
16 | , TrackerList | ||
17 | |||
18 | -- * Construction | ||
19 | , trackerList | ||
20 | , shuffleTiers | ||
21 | , mapWithURI | ||
22 | , Network.BitTorrent.Tracker.List.toList | ||
23 | |||
24 | -- * Traversals | ||
25 | , traverseAll | ||
26 | , traverseTiers | ||
27 | ) where | ||
28 | |||
29 | import Prelude hiding (mapM, foldr) | ||
30 | import Control.Arrow | ||
31 | import Control.Applicative | ||
32 | import Control.Exception | ||
33 | import Data.Default | ||
34 | import Data.List as L (map, elem, any, filter, null) | ||
35 | import Data.Maybe | ||
36 | import Data.Foldable | ||
37 | import Data.Traversable | ||
38 | import Network.URI | ||
39 | import System.Random.Shuffle | ||
40 | |||
41 | import Data.Torrent | ||
42 | import Network.BitTorrent.Tracker.RPC as RPC | ||
43 | |||
44 | {----------------------------------------------------------------------- | ||
45 | -- Tracker list datatype | ||
46 | -----------------------------------------------------------------------} | ||
47 | |||
48 | type TierEntry a = (URI, a) | ||
49 | type Tier a = [TierEntry a] | ||
50 | |||
51 | -- | Tracker list is either a single tracker or list of tiers. All | ||
52 | -- trackers in each tier must be checked before the client goes on to | ||
53 | -- the next tier. | ||
54 | data TrackerList a | ||
55 | = Announce (TierEntry a) -- ^ torrent file 'announce' field only | ||
56 | | TierList [Tier a] -- ^ torrent file 'announce-list' field only | ||
57 | deriving (Show, Eq) | ||
58 | |||
59 | -- | Empty tracker list. Can be used for trackerless torrents. | ||
60 | instance Default (TrackerList a) where | ||
61 | def = TierList [] | ||
62 | |||
63 | instance Functor TrackerList where | ||
64 | fmap f (Announce (uri, a)) = Announce (uri, f a) | ||
65 | fmap f (TierList a) = TierList (fmap (fmap (second f)) a) | ||
66 | |||
67 | instance Foldable TrackerList where | ||
68 | foldr f z (Announce e ) = f (snd e) z | ||
69 | foldr f z (TierList xs) = foldr (flip (foldr (f . snd))) z xs | ||
70 | |||
71 | _traverseEntry f (uri, a) = (,) uri <$> f a | ||
72 | |||
73 | instance Traversable TrackerList where | ||
74 | traverse f (Announce e ) = Announce <$> _traverseEntry f e | ||
75 | traverse f (TierList xs) = | ||
76 | TierList <$> traverse (traverse (_traverseEntry f)) xs | ||
77 | |||
78 | traverseWithURI :: Applicative f | ||
79 | => (TierEntry a -> f b) -> TrackerList a -> f (TrackerList b) | ||
80 | traverseWithURI f (Announce (uri, a)) = (Announce . (,) uri) <$> f (uri, a) | ||
81 | traverseWithURI f (TierList xxs ) = | ||
82 | TierList <$> traverse (traverse (traverseEntry f)) xxs | ||
83 | where | ||
84 | traverseEntry f (uri, a) = (,) uri <$> f (uri, a) | ||
85 | |||
86 | {----------------------------------------------------------------------- | ||
87 | -- List extraction | ||
88 | -----------------------------------------------------------------------} | ||
89 | -- BEP12 do not expose any restrictions for the content of | ||
90 | -- 'announce-list' key - there are some /bad/ cases can happen with | ||
91 | -- poorly designed or even malicious torrent creation software. | ||
92 | -- | ||
93 | -- Bad case #1: announce-list is present, but empty. | ||
94 | -- | ||
95 | -- { tAnnounce = Just "http://a.com" | ||
96 | -- , tAnnounceList = Just [[]] | ||
97 | -- } | ||
98 | -- | ||
99 | -- Bad case #2: announce uri do not present in announce list. | ||
100 | -- | ||
101 | -- { tAnnounce = Just "http://a.com" | ||
102 | -- , tAnnounceList = Just [["udp://a.com"]] | ||
103 | -- } | ||
104 | -- | ||
105 | -- The addBackup function solves both problems by adding announce uri | ||
106 | -- as backup tier. | ||
107 | -- | ||
108 | addBackup :: [[URI]] -> URI -> [[URI]] | ||
109 | addBackup tiers bkp | ||
110 | | L.any (L.elem bkp) tiers = tiers | ||
111 | | otherwise = tiers ++ [[bkp]] | ||
112 | |||
113 | fixList :: Maybe [[URI]] -> Maybe URI -> Maybe [[URI]] | ||
114 | fixList mxss mx = do | ||
115 | xss <- mxss | ||
116 | let xss' = L.filter (not . L.null) xss | ||
117 | return $ maybe xss' (addBackup xss') mx | ||
118 | |||
119 | -- | Extract set of trackers from torrent file. The 'tAnnounce' key is | ||
120 | -- only ignored if the 'tAnnounceList' key is present. | ||
121 | trackerList :: Torrent -> TrackerList () | ||
122 | trackerList Torrent {..} = fromMaybe (TierList []) $ do | ||
123 | (TierList . tierList) <$> (tAnnounceList `fixList` tAnnounce) | ||
124 | <|> (Announce . nullEntry) <$> tAnnounce | ||
125 | where | ||
126 | nullEntry uri = (uri, ()) | ||
127 | tierList = L.map (L.map nullEntry) | ||
128 | |||
129 | -- | Shuffle /order of trackers/ in each tier, preserving original | ||
130 | -- /order of tiers/. This can help to balance the load between the | ||
131 | -- trackers. | ||
132 | shuffleTiers :: TrackerList a -> IO (TrackerList a) | ||
133 | shuffleTiers (Announce a ) = return (Announce a) | ||
134 | shuffleTiers (TierList xs) = TierList <$> mapM shuffleM xs | ||
135 | |||
136 | mapWithURI :: (URI -> a -> b) -> TrackerList a -> TrackerList b | ||
137 | mapWithURI f (Announce (uri, a)) = Announce (uri, f uri a) | ||
138 | mapWithURI f (TierList xs ) = TierList (L.map (L.map mapEntry) xs) | ||
139 | where | ||
140 | mapEntry (uri, a) = (uri, f uri a) | ||
141 | |||
142 | toList :: TrackerList a -> [[TierEntry a]] | ||
143 | toList (Announce e) = [[e]] | ||
144 | toList (TierList xxs) = xxs | ||
145 | |||
146 | {----------------------------------------------------------------------- | ||
147 | -- Special traversals (suppressed RPC exceptions) | ||
148 | -----------------------------------------------------------------------} | ||
149 | |||
150 | catchRPC :: IO a -> IO a -> IO a | ||
151 | catchRPC a b = catch a (f b) | ||
152 | where | ||
153 | f :: a -> RpcException -> a | ||
154 | f = const | ||
155 | |||
156 | throwRPC :: String -> IO a | ||
157 | throwRPC = throwIO . GenericException | ||
158 | |||
159 | -- | Like 'traverse' but ignores 'RpcExceptions'. | ||
160 | traverseAll :: (TierEntry a -> IO a) -> TrackerList a -> IO (TrackerList a) | ||
161 | traverseAll action = traverseWithURI (action $?) | ||
162 | where | ||
163 | f $? x = catchRPC (f x) (return (snd x)) | ||
164 | |||
165 | -- | Like 'traverse' but put working trackers to the head of tiers. | ||
166 | -- This can help to avoid exceessive requests to not available | ||
167 | -- trackers at each reannounce. If no one action succeed then original | ||
168 | -- list is returned. | ||
169 | traverseTiers :: (TierEntry a -> IO a) -> TrackerList a -> IO (TrackerList a) | ||
170 | traverseTiers action ts = catchRPC (goList ts) (return ts) | ||
171 | where | ||
172 | goList tl @ (Announce _ ) = traverseWithURI action tl | ||
173 | goList (TierList tiers) = TierList <$> goTiers (goTier []) tiers | ||
174 | |||
175 | goTiers _ [] = throwRPC "traverseTiers: no tiers" | ||
176 | goTiers f (x : xs) = catchRPC shortcut failback | ||
177 | where | ||
178 | shortcut = do | ||
179 | x' <- f x | ||
180 | return (x' : xs) | ||
181 | |||
182 | failback = do | ||
183 | xs' <- goTiers f xs | ||
184 | return (x : xs') | ||
185 | |||
186 | goTier _ [] = throwRPC "traverseTiers: no trackers in tier" | ||
187 | goTier failed ((uri, a) : as) = catchRPC shortcut failback | ||
188 | where | ||
189 | shortcut = do | ||
190 | a' <- action (uri, a) | ||
191 | return ((uri, a') : as ++ failed) -- failed trackers at the end | ||
192 | |||
193 | failback = goTier ((uri, a) : failed) as | ||
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 | ||
diff --git a/bittorrent/src/Network/BitTorrent/Tracker/RPC.hs b/bittorrent/src/Network/BitTorrent/Tracker/RPC.hs new file mode 100644 index 00000000..45fef05e --- /dev/null +++ b/bittorrent/src/Network/BitTorrent/Tracker/RPC.hs | |||
@@ -0,0 +1,175 @@ | |||
1 | -- | | ||
2 | -- Copyright : (c) Sam Truzjan 2013 | ||
3 | -- License : BSD | ||
4 | -- Maintainer : pxqr.sta@gmail.com | ||
5 | -- Stability : experimental | ||
6 | -- Portability : portable | ||
7 | -- | ||
8 | -- This module provides unified RPC interface to BitTorrent | ||
9 | -- trackers. The tracker is an UDP/HTTP/HTTPS service used to | ||
10 | -- discovery peers for a particular existing torrent and keep | ||
11 | -- statistics about the swarm. This module also provides a way to | ||
12 | -- request scrape info for a particular torrent list. | ||
13 | -- | ||
14 | {-# LANGUAGE DeriveDataTypeable #-} | ||
15 | module Network.BitTorrent.Tracker.RPC | ||
16 | ( PeerInfo (..) | ||
17 | |||
18 | -- * Manager | ||
19 | , Options (..) | ||
20 | , Manager | ||
21 | , newManager | ||
22 | , closeManager | ||
23 | , withManager | ||
24 | |||
25 | -- * RPC | ||
26 | , SAnnounceQuery (..) | ||
27 | , RpcException (..) | ||
28 | , Network.BitTorrent.Tracker.RPC.announce | ||
29 | , scrape | ||
30 | ) where | ||
31 | |||
32 | import Control.Exception | ||
33 | import Data.Default | ||
34 | import Data.Typeable | ||
35 | import Network | ||
36 | import Network.URI | ||
37 | import Network.Socket (HostAddress) | ||
38 | |||
39 | import Data.Torrent | ||
40 | import Network.Address | ||
41 | import Network.BitTorrent.Internal.Progress | ||
42 | import Network.BitTorrent.Tracker.Message | ||
43 | import qualified Network.BitTorrent.Tracker.RPC.HTTP as HTTP | ||
44 | import qualified Network.BitTorrent.Tracker.RPC.UDP as UDP | ||
45 | |||
46 | |||
47 | {----------------------------------------------------------------------- | ||
48 | -- Simplified announce | ||
49 | -----------------------------------------------------------------------} | ||
50 | |||
51 | -- | Info to advertise to trackers. | ||
52 | data PeerInfo = PeerInfo | ||
53 | { peerId :: !PeerId | ||
54 | , peerIP :: !(Maybe HostAddress) | ||
55 | , peerPort :: !PortNumber | ||
56 | } deriving (Show, Eq) | ||
57 | |||
58 | instance Default PeerInfo where | ||
59 | def = PeerInfo def Nothing 6881 | ||
60 | |||
61 | -- | Simplified announce query. | ||
62 | data SAnnounceQuery = SAnnounceQuery | ||
63 | { sInfoHash :: InfoHash | ||
64 | , sProgress :: Progress | ||
65 | , sNumWant :: Maybe Int | ||
66 | , sEvent :: Maybe AnnounceEvent | ||
67 | } | ||
68 | |||
69 | fillAnnounceQuery :: PeerInfo -> SAnnounceQuery -> AnnounceQuery | ||
70 | fillAnnounceQuery PeerInfo{..} SAnnounceQuery {..} = AnnounceQuery | ||
71 | { reqInfoHash = sInfoHash | ||
72 | , reqPeerId = peerId | ||
73 | , reqPort = peerPort | ||
74 | , reqProgress = sProgress | ||
75 | , reqIP = peerIP | ||
76 | , reqNumWant = sNumWant | ||
77 | , reqEvent = sEvent | ||
78 | } | ||
79 | |||
80 | {----------------------------------------------------------------------- | ||
81 | -- RPC manager | ||
82 | -----------------------------------------------------------------------} | ||
83 | |||
84 | -- | Tracker manager settings. | ||
85 | data Options = Options | ||
86 | { -- | HTTP tracker protocol specific options. | ||
87 | optHttpRPC :: !HTTP.Options | ||
88 | |||
89 | -- | UDP tracker protocol specific options. | ||
90 | , optUdpRPC :: !UDP.Options | ||
91 | |||
92 | -- | Whether to use multitracker extension. | ||
93 | , optMultitracker :: !Bool | ||
94 | } | ||
95 | |||
96 | instance Default Options where | ||
97 | def = Options | ||
98 | { optHttpRPC = def | ||
99 | , optUdpRPC = def | ||
100 | , optMultitracker = True | ||
101 | } | ||
102 | |||
103 | -- | Tracker RPC Manager. | ||
104 | data Manager = Manager | ||
105 | { options :: !Options | ||
106 | , peerInfo :: !PeerInfo | ||
107 | , httpMgr :: !HTTP.Manager | ||
108 | , udpMgr :: !UDP.Manager | ||
109 | } | ||
110 | |||
111 | -- | Create a new 'Manager'. You /must/ manually 'closeManager' | ||
112 | -- otherwise resource leakage is possible. Normally, a bittorrent | ||
113 | -- client need a single RPC manager only. | ||
114 | -- | ||
115 | -- This function can throw 'IOException' on invalid 'Options'. | ||
116 | -- | ||
117 | newManager :: Options -> PeerInfo -> IO Manager | ||
118 | newManager opts info = do | ||
119 | h <- HTTP.newManager (optHttpRPC opts) | ||
120 | u <- UDP.newManager (optUdpRPC opts) `onException` HTTP.closeManager h | ||
121 | return $ Manager opts info h u | ||
122 | |||
123 | -- | Close all pending RPCs. Behaviour of currently in-flight RPCs can | ||
124 | -- differ depending on underlying protocol used. No rpc calls should | ||
125 | -- be performed after manager becomes closed. | ||
126 | closeManager :: Manager -> IO () | ||
127 | closeManager Manager {..} = do | ||
128 | UDP.closeManager udpMgr `finally` HTTP.closeManager httpMgr | ||
129 | |||
130 | -- | Normally you need to use 'Control.Monad.Trans.Resource.allocate'. | ||
131 | withManager :: Options -> PeerInfo -> (Manager -> IO a) -> IO a | ||
132 | withManager opts info = bracket (newManager opts info) closeManager | ||
133 | |||
134 | {----------------------------------------------------------------------- | ||
135 | -- Exceptions | ||
136 | -----------------------------------------------------------------------} | ||
137 | -- TODO Catch IO exceptions on rpc calls (?) | ||
138 | |||
139 | data RpcException | ||
140 | = UdpException UDP.RpcException -- ^ UDP RPC driver failure; | ||
141 | | HttpException HTTP.RpcException -- ^ HTTP RPC driver failure; | ||
142 | | UnrecognizedScheme String -- ^ unsupported scheme in announce URI; | ||
143 | | GenericException String -- ^ for furter extensibility. | ||
144 | deriving (Show, Typeable) | ||
145 | |||
146 | instance Exception RpcException | ||
147 | |||
148 | packException :: Exception e => (e -> RpcException) -> IO a -> IO a | ||
149 | packException f m = try m >>= either (throwIO . f) return | ||
150 | {-# INLINE packException #-} | ||
151 | |||
152 | {----------------------------------------------------------------------- | ||
153 | -- RPC calls | ||
154 | -----------------------------------------------------------------------} | ||
155 | |||
156 | dispatch :: URI -> IO a -> IO a -> IO a | ||
157 | dispatch URI {..} http udp | ||
158 | | uriScheme == "http:" || | ||
159 | uriScheme == "https:" = packException HttpException http | ||
160 | | uriScheme == "udp:" = packException UdpException udp | ||
161 | | otherwise = throwIO $ UnrecognizedScheme uriScheme | ||
162 | |||
163 | announce :: Manager -> URI -> SAnnounceQuery -> IO AnnounceInfo | ||
164 | announce Manager {..} uri simpleQuery | ||
165 | = dispatch uri | ||
166 | (HTTP.announce httpMgr uri annQ) | ||
167 | ( UDP.announce udpMgr uri annQ) | ||
168 | where | ||
169 | annQ = fillAnnounceQuery peerInfo simpleQuery | ||
170 | |||
171 | scrape :: Manager -> URI -> ScrapeQuery -> IO ScrapeInfo | ||
172 | scrape Manager {..} uri q | ||
173 | = dispatch uri | ||
174 | (HTTP.scrape httpMgr uri q) | ||
175 | ( UDP.scrape udpMgr uri q) | ||
diff --git a/bittorrent/src/Network/BitTorrent/Tracker/RPC/HTTP.hs b/bittorrent/src/Network/BitTorrent/Tracker/RPC/HTTP.hs new file mode 100644 index 00000000..9b6e056a --- /dev/null +++ b/bittorrent/src/Network/BitTorrent/Tracker/RPC/HTTP.hs | |||
@@ -0,0 +1,191 @@ | |||
1 | -- | | ||
2 | -- Copyright : (c) Sam Truzjan 2013 | ||
3 | -- License : BSD | ||
4 | -- Maintainer : pxqr.sta@gmail.com | ||
5 | -- Stability : provisional | ||
6 | -- Portability : portable | ||
7 | -- | ||
8 | -- This module implement HTTP tracker protocol. | ||
9 | -- | ||
10 | -- For more information see: | ||
11 | -- <https://wiki.theory.org/BitTorrentSpecification#Tracker_HTTP.2FHTTPS_Protocol> | ||
12 | -- | ||
13 | {-# LANGUAGE DeriveDataTypeable #-} | ||
14 | module Network.BitTorrent.Tracker.RPC.HTTP | ||
15 | ( -- * Manager | ||
16 | Options (..) | ||
17 | , Manager | ||
18 | , newManager | ||
19 | , closeManager | ||
20 | , withManager | ||
21 | |||
22 | -- * RPC | ||
23 | , RpcException (..) | ||
24 | , announce | ||
25 | , scrape | ||
26 | , scrapeOne | ||
27 | ) where | ||
28 | |||
29 | import Control.Applicative | ||
30 | import Control.Exception | ||
31 | import Control.Monad | ||
32 | import Control.Monad.Trans.Resource | ||
33 | import Data.BEncode as BE | ||
34 | import Data.ByteString as BS | ||
35 | import Data.ByteString.Char8 as BC | ||
36 | import Data.ByteString.Lazy as BL | ||
37 | import Data.Default | ||
38 | import Data.List as L | ||
39 | import Data.Monoid | ||
40 | import Data.Typeable hiding (Proxy) | ||
41 | import Network.URI | ||
42 | import Network.HTTP.Conduit hiding | ||
43 | (Manager, newManager, closeManager, withManager) | ||
44 | import Network.HTTP.Client (defaultManagerSettings) | ||
45 | import Network.HTTP.Client.Internal (setUri) | ||
46 | import qualified Network.HTTP.Conduit as HTTP | ||
47 | import Network.HTTP.Types.Header (hUserAgent) | ||
48 | import Network.HTTP.Types.URI (SimpleQuery, renderSimpleQuery) | ||
49 | |||
50 | import Data.Torrent (InfoHash) | ||
51 | import Network.Address (libUserAgent) | ||
52 | import Network.BitTorrent.Tracker.Message hiding (Request, Response) | ||
53 | |||
54 | {----------------------------------------------------------------------- | ||
55 | -- Exceptions | ||
56 | -----------------------------------------------------------------------} | ||
57 | |||
58 | data RpcException | ||
59 | = RequestFailed HttpException -- ^ failed HTTP request. | ||
60 | | ParserFailure String -- ^ unable to decode tracker response; | ||
61 | | ScrapelessTracker -- ^ tracker do not support scraping; | ||
62 | | BadScrape -- ^ unable to find info hash in response dict; | ||
63 | deriving (Show, Typeable) | ||
64 | |||
65 | instance Exception RpcException | ||
66 | |||
67 | packHttpException :: IO a -> IO a | ||
68 | packHttpException m = try m >>= either (throwIO . RequestFailed) return | ||
69 | |||
70 | {----------------------------------------------------------------------- | ||
71 | -- Manager | ||
72 | -----------------------------------------------------------------------} | ||
73 | |||
74 | -- | HTTP tracker specific RPC options. | ||
75 | data Options = Options | ||
76 | { -- | Global HTTP announce query preferences. | ||
77 | optAnnouncePrefs :: !AnnouncePrefs | ||
78 | |||
79 | -- | Whether to use HTTP proxy for HTTP tracker requests. | ||
80 | , optHttpProxy :: !(Maybe Proxy) | ||
81 | |||
82 | -- | Value to put in HTTP user agent header. | ||
83 | , optUserAgent :: !BS.ByteString | ||
84 | |||
85 | -- | HTTP manager options. | ||
86 | , optHttpOptions :: !ManagerSettings | ||
87 | } | ||
88 | |||
89 | instance Default Options where | ||
90 | def = Options | ||
91 | { optAnnouncePrefs = def | ||
92 | , optHttpProxy = Nothing | ||
93 | , optUserAgent = BC.pack libUserAgent | ||
94 | , optHttpOptions = defaultManagerSettings | ||
95 | } | ||
96 | |||
97 | -- | HTTP tracker manager. | ||
98 | data Manager = Manager | ||
99 | { options :: !Options | ||
100 | , httpMgr :: !HTTP.Manager | ||
101 | } | ||
102 | |||
103 | -- | | ||
104 | newManager :: Options -> IO Manager | ||
105 | newManager opts = Manager opts <$> HTTP.newManager (optHttpOptions opts) | ||
106 | |||
107 | -- | | ||
108 | closeManager :: Manager -> IO () | ||
109 | closeManager Manager {..} = HTTP.closeManager httpMgr | ||
110 | |||
111 | -- | Normally you need to use 'Control.Monad.Trans.Resource.allocate'. | ||
112 | withManager :: Options -> (Manager -> IO a) -> IO a | ||
113 | withManager opts = bracket (newManager opts) closeManager | ||
114 | |||
115 | {----------------------------------------------------------------------- | ||
116 | -- Queries | ||
117 | -----------------------------------------------------------------------} | ||
118 | |||
119 | fillRequest :: Options -> SimpleQuery -> Request -> Request | ||
120 | fillRequest Options {..} q r = r | ||
121 | { queryString = joinQuery (queryString r) (renderSimpleQuery False q) | ||
122 | , requestHeaders = (hUserAgent, optUserAgent) : requestHeaders r | ||
123 | , proxy = optHttpProxy | ||
124 | } | ||
125 | where | ||
126 | joinQuery a b | ||
127 | | BS.null a = b | ||
128 | | otherwise = a <> "&" <> b | ||
129 | |||
130 | httpTracker :: BEncode a => Manager -> URI -> SimpleQuery -> IO a | ||
131 | httpTracker Manager {..} uri q = packHttpException $ do | ||
132 | request <- fillRequest options q <$> setUri def {- http-client instance for Request -} uri | ||
133 | response <- runResourceT $ httpLbs request httpMgr | ||
134 | case BE.decode $ BL.toStrict $ responseBody response of | ||
135 | Left msg -> throwIO (ParserFailure msg) | ||
136 | Right info -> return info | ||
137 | |||
138 | {----------------------------------------------------------------------- | ||
139 | -- RPC | ||
140 | -----------------------------------------------------------------------} | ||
141 | |||
142 | -- | Send request and receive response from the tracker specified in | ||
143 | -- announce list. | ||
144 | -- | ||
145 | -- This function can throw 'RpcException'. | ||
146 | -- | ||
147 | announce :: Manager -> URI -> AnnounceQuery -> IO AnnounceInfo | ||
148 | announce mgr uri q = httpTracker mgr uri (renderAnnounceRequest uriQ) | ||
149 | where | ||
150 | uriQ = AnnounceRequest | ||
151 | { announceQuery = q | ||
152 | , announcePrefs = optAnnouncePrefs (options mgr) | ||
153 | } | ||
154 | |||
155 | -- | Trying to convert /announce/ URL to /scrape/ URL. If 'scrapeURL' | ||
156 | -- gives 'Nothing' then tracker do not support scraping. | ||
157 | -- | ||
158 | scrapeURL :: URI -> Maybe URI | ||
159 | scrapeURL uri = do | ||
160 | newPath <- replace (BC.pack (uriPath uri)) | ||
161 | return uri { uriPath = BC.unpack newPath } | ||
162 | where | ||
163 | replace p = do | ||
164 | let ps = BC.splitWith (== '/') p | ||
165 | guard (not (L.null ps)) | ||
166 | guard ("announce" `BS.isPrefixOf` L.last ps) | ||
167 | let newSuff = "scrape" <> BS.drop (BS.length "announce") (L.last ps) | ||
168 | return (BS.intercalate "/" (L.init ps ++ [newSuff])) | ||
169 | |||
170 | -- | For each 'InfoHash' of torrents request scrape info from the tracker. | ||
171 | -- However if the info hash list is 'null', the tracker should list | ||
172 | -- all available torrents. | ||
173 | -- | ||
174 | -- This function can throw 'RpcException'. | ||
175 | -- | ||
176 | scrape :: Manager -> URI -> ScrapeQuery -> IO ScrapeInfo | ||
177 | scrape m u q = do | ||
178 | case scrapeURL u of | ||
179 | Nothing -> throwIO ScrapelessTracker | ||
180 | Just uri -> httpTracker m uri (renderScrapeQuery q) | ||
181 | |||
182 | -- | More particular version of 'scrape', just for one torrent. | ||
183 | -- | ||
184 | -- This function can throw 'RpcException'. | ||
185 | -- | ||
186 | scrapeOne :: Manager -> URI -> InfoHash -> IO ScrapeEntry | ||
187 | scrapeOne m uri ih = do | ||
188 | xs <- scrape m uri [ih] | ||
189 | case L.lookup ih xs of | ||
190 | Nothing -> throwIO BadScrape | ||
191 | Just a -> return a | ||
diff --git a/bittorrent/src/Network/BitTorrent/Tracker/RPC/UDP.hs b/bittorrent/src/Network/BitTorrent/Tracker/RPC/UDP.hs new file mode 100644 index 00000000..31b6b870 --- /dev/null +++ b/bittorrent/src/Network/BitTorrent/Tracker/RPC/UDP.hs | |||
@@ -0,0 +1,454 @@ | |||
1 | -- | | ||
2 | -- Copyright : (c) Sam Truzjan 2013-2014 | ||
3 | -- License : BSD3 | ||
4 | -- Maintainer : pxqr.sta@gmail.com | ||
5 | -- Stability : provisional | ||
6 | -- Portability : portable | ||
7 | -- | ||
8 | -- This module implement UDP tracker protocol. | ||
9 | -- | ||
10 | -- For protocol details and uri scheme see: | ||
11 | -- <http://www.bittorrent.org/beps/bep_0015.html>, | ||
12 | -- <https://www.iana.org/assignments/uri-schemes/prov/udp> | ||
13 | -- | ||
14 | {-# LANGUAGE RecordWildCards #-} | ||
15 | {-# LANGUAGE FlexibleInstances #-} | ||
16 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} | ||
17 | {-# LANGUAGE DeriveDataTypeable #-} | ||
18 | module Network.BitTorrent.Tracker.RPC.UDP | ||
19 | ( -- * Manager | ||
20 | Options (..) | ||
21 | , Manager | ||
22 | , newManager | ||
23 | , closeManager | ||
24 | , withManager | ||
25 | |||
26 | -- * RPC | ||
27 | , RpcException (..) | ||
28 | , announce | ||
29 | , scrape | ||
30 | ) where | ||
31 | |||
32 | import Control.Applicative | ||
33 | import Control.Concurrent | ||
34 | import Control.Exception | ||
35 | import Control.Monad | ||
36 | import Data.Default | ||
37 | import Data.IORef | ||
38 | import Data.List as L | ||
39 | import Data.Map as M | ||
40 | import Data.Maybe | ||
41 | import Data.Serialize | ||
42 | import Data.Text as T | ||
43 | import Data.Time | ||
44 | import Data.Time.Clock.POSIX | ||
45 | import Data.Traversable | ||
46 | import Data.Typeable | ||
47 | import Text.Read (readMaybe) | ||
48 | import Network.Socket hiding (Connected, connect, listen) | ||
49 | import Network.Socket.ByteString as BS | ||
50 | import Network.URI | ||
51 | import System.Timeout | ||
52 | |||
53 | import Network.BitTorrent.Tracker.Message | ||
54 | |||
55 | {----------------------------------------------------------------------- | ||
56 | -- Options | ||
57 | -----------------------------------------------------------------------} | ||
58 | |||
59 | -- | 'System.Timeout.timeout' specific. | ||
60 | sec :: Int | ||
61 | sec = 1000000 | ||
62 | |||
63 | -- | See <http://www.bittorrent.org/beps/bep_0015.html#time-outs> | ||
64 | defMinTimeout :: Int | ||
65 | defMinTimeout = 15 | ||
66 | |||
67 | -- | See <http://www.bittorrent.org/beps/bep_0015.html#time-outs> | ||
68 | defMaxTimeout :: Int | ||
69 | defMaxTimeout = 15 * 2 ^ (8 :: Int) | ||
70 | |||
71 | -- | See: <http://www.bittorrent.org/beps/bep_0015.html#time-outs> | ||
72 | defMultiplier :: Int | ||
73 | defMultiplier = 2 | ||
74 | |||
75 | -- TODO why 98? | ||
76 | defMaxPacketSize :: Int | ||
77 | defMaxPacketSize = 98 | ||
78 | |||
79 | -- | Manager configuration. | ||
80 | data Options = Options | ||
81 | { -- | Max size of a /response/ packet. | ||
82 | -- | ||
83 | -- 'optMaxPacketSize' /must/ be a positive value. | ||
84 | -- | ||
85 | optMaxPacketSize :: {-# UNPACK #-} !Int | ||
86 | |||
87 | -- | Starting timeout interval in seconds. If a response is not | ||
88 | -- received after 'optMinTimeout' then 'Manager' repeat RPC with | ||
89 | -- timeout interval multiplied by 'optMultiplier' and so on until | ||
90 | -- timeout interval reach 'optMaxTimeout'. | ||
91 | -- | ||
92 | -- 'optMinTimeout' /must/ be a positive value. | ||
93 | -- | ||
94 | , optMinTimeout :: {-# UNPACK #-} !Int | ||
95 | |||
96 | -- | Final timeout interval in seconds. After 'optMaxTimeout' | ||
97 | -- reached and tracker still not responding both 'announce' and | ||
98 | -- 'scrape' functions will throw 'TimeoutExpired' exception. | ||
99 | -- | ||
100 | -- 'optMaxTimeout' /must/ be greater than 'optMinTimeout'. | ||
101 | -- | ||
102 | , optMaxTimeout :: {-# UNPACK #-} !Int | ||
103 | |||
104 | -- | 'optMultiplier' /must/ be a positive value. | ||
105 | , optMultiplier :: {-# UNPACK #-} !Int | ||
106 | } deriving (Show, Eq) | ||
107 | |||
108 | -- | Options suitable for bittorrent client. | ||
109 | instance Default Options where | ||
110 | def = Options | ||
111 | { optMaxPacketSize = defMaxPacketSize | ||
112 | , optMinTimeout = defMinTimeout | ||
113 | , optMaxTimeout = defMaxTimeout | ||
114 | , optMultiplier = defMultiplier | ||
115 | } | ||
116 | |||
117 | checkOptions :: Options -> IO () | ||
118 | checkOptions Options {..} = do | ||
119 | unless (optMaxPacketSize > 0) $ do | ||
120 | throwIO $ userError "optMaxPacketSize must be positive" | ||
121 | |||
122 | unless (optMinTimeout > 0) $ do | ||
123 | throwIO $ userError "optMinTimeout must be positive" | ||
124 | |||
125 | unless (optMaxTimeout > 0) $ do | ||
126 | throwIO $ userError "optMaxTimeout must be positive" | ||
127 | |||
128 | unless (optMultiplier > 0) $ do | ||
129 | throwIO $ userError "optMultiplier must be positive" | ||
130 | |||
131 | unless (optMaxTimeout > optMinTimeout) $ do | ||
132 | throwIO $ userError "optMaxTimeout must be greater than optMinTimeout" | ||
133 | |||
134 | |||
135 | {----------------------------------------------------------------------- | ||
136 | -- Manager state | ||
137 | -----------------------------------------------------------------------} | ||
138 | |||
139 | type ConnectionCache = Map SockAddr Connection | ||
140 | |||
141 | type PendingResponse = MVar (Either RpcException Response) | ||
142 | type PendingTransactions = Map TransactionId PendingResponse | ||
143 | type PendingQueries = Map SockAddr PendingTransactions | ||
144 | |||
145 | -- | UDP tracker manager. | ||
146 | data Manager = Manager | ||
147 | { options :: !Options | ||
148 | , sock :: !Socket | ||
149 | -- , dnsCache :: !(IORef (Map URI SockAddr)) | ||
150 | , connectionCache :: !(IORef ConnectionCache) | ||
151 | , pendingResps :: !(MVar PendingQueries) | ||
152 | , listenerThread :: !(MVar ThreadId) | ||
153 | } | ||
154 | |||
155 | initManager :: Options -> IO Manager | ||
156 | initManager opts = Manager opts | ||
157 | <$> socket AF_INET Datagram defaultProtocol | ||
158 | <*> newIORef M.empty | ||
159 | <*> newMVar M.empty | ||
160 | <*> newEmptyMVar | ||
161 | |||
162 | unblockAll :: PendingQueries -> IO () | ||
163 | unblockAll m = traverse (traverse unblockCall) m >> return () | ||
164 | where | ||
165 | unblockCall ares = putMVar ares (Left ManagerClosed) | ||
166 | |||
167 | resetState :: Manager -> IO () | ||
168 | resetState Manager {..} = do | ||
169 | writeIORef connectionCache err | ||
170 | m <- swapMVar pendingResps err | ||
171 | unblockAll m | ||
172 | mtid <- tryTakeMVar listenerThread | ||
173 | case mtid of | ||
174 | Nothing -> return () -- thread killed by 'closeManager' | ||
175 | Just _ -> return () -- thread killed by exception from 'listen' | ||
176 | return () | ||
177 | where | ||
178 | err = error "UDP tracker manager closed" | ||
179 | |||
180 | -- | This function will throw 'IOException' on invalid 'Options'. | ||
181 | newManager :: Options -> IO Manager | ||
182 | newManager opts = do | ||
183 | checkOptions opts | ||
184 | mgr <- initManager opts | ||
185 | tid <- forkIO (listen mgr `finally` resetState mgr) | ||
186 | putMVar (listenerThread mgr) tid | ||
187 | return mgr | ||
188 | |||
189 | -- | Unblock all RPCs by throwing 'ManagerClosed' exception. No rpc | ||
190 | -- calls should be performed after manager becomes closed. | ||
191 | closeManager :: Manager -> IO () | ||
192 | closeManager Manager {..} = do | ||
193 | close sock | ||
194 | mtid <- tryTakeMVar listenerThread | ||
195 | case mtid of | ||
196 | Nothing -> return () | ||
197 | Just tid -> killThread tid | ||
198 | |||
199 | -- | Normally you need to use 'Control.Monad.Trans.Resource.allocate'. | ||
200 | withManager :: Options -> (Manager -> IO a) -> IO a | ||
201 | withManager opts = bracket (newManager opts) closeManager | ||
202 | |||
203 | {----------------------------------------------------------------------- | ||
204 | -- Exceptions | ||
205 | -----------------------------------------------------------------------} | ||
206 | |||
207 | data RpcException | ||
208 | -- | Unable to lookup hostname; | ||
209 | = HostUnknown | ||
210 | |||
211 | -- | Unable to lookup hostname; | ||
212 | | HostLookupFailed | ||
213 | |||
214 | -- | Expecting 'udp:', but some other scheme provided. | ||
215 | | UnrecognizedScheme String | ||
216 | |||
217 | -- | Tracker exists but not responding for specific number of seconds. | ||
218 | | TimeoutExpired Int | ||
219 | |||
220 | -- | Tracker responded with unexpected message type. | ||
221 | | UnexpectedResponse | ||
222 | { expectedMsg :: String | ||
223 | , actualMsg :: String | ||
224 | } | ||
225 | |||
226 | -- | RPC succeed, but tracker responded with error code. | ||
227 | | QueryFailed Text | ||
228 | |||
229 | -- | RPC manager closed while waiting for response. | ||
230 | | ManagerClosed | ||
231 | deriving (Eq, Show, Typeable) | ||
232 | |||
233 | instance Exception RpcException | ||
234 | |||
235 | {----------------------------------------------------------------------- | ||
236 | -- Host Addr resolution | ||
237 | -----------------------------------------------------------------------} | ||
238 | |||
239 | setPort :: PortNumber -> SockAddr -> SockAddr | ||
240 | setPort p (SockAddrInet _ h) = SockAddrInet p h | ||
241 | setPort p (SockAddrInet6 _ f h s) = SockAddrInet6 p f h s | ||
242 | setPort _ addr = addr | ||
243 | |||
244 | resolveURI :: URI -> IO SockAddr | ||
245 | resolveURI URI { uriAuthority = Just (URIAuth {..}) } = do | ||
246 | infos <- getAddrInfo Nothing (Just uriRegName) Nothing | ||
247 | let port = fromMaybe 0 (readMaybe (L.drop 1 uriPort) :: Maybe Int) | ||
248 | case infos of | ||
249 | AddrInfo {..} : _ -> return $ setPort (fromIntegral port) addrAddress | ||
250 | _ -> throwIO HostLookupFailed | ||
251 | resolveURI _ = throwIO HostUnknown | ||
252 | |||
253 | -- TODO caching? | ||
254 | getTrackerAddr :: Manager -> URI -> IO SockAddr | ||
255 | getTrackerAddr _ uri | ||
256 | | uriScheme uri == "udp:" = resolveURI uri | ||
257 | | otherwise = throwIO (UnrecognizedScheme (uriScheme uri)) | ||
258 | |||
259 | {----------------------------------------------------------------------- | ||
260 | Connection | ||
261 | -----------------------------------------------------------------------} | ||
262 | |||
263 | connectionLifetime :: NominalDiffTime | ||
264 | connectionLifetime = 60 | ||
265 | |||
266 | data Connection = Connection | ||
267 | { connectionId :: ConnectionId | ||
268 | , connectionTimestamp :: UTCTime | ||
269 | } deriving Show | ||
270 | |||
271 | -- placeholder for the first 'connect' | ||
272 | initialConnection :: Connection | ||
273 | initialConnection = Connection initialConnectionId (posixSecondsToUTCTime 0) | ||
274 | |||
275 | establishedConnection :: ConnectionId -> IO Connection | ||
276 | establishedConnection cid = Connection cid <$> getCurrentTime | ||
277 | |||
278 | isExpired :: Connection -> IO Bool | ||
279 | isExpired Connection {..} = do | ||
280 | currentTime <- getCurrentTime | ||
281 | let timeDiff = diffUTCTime currentTime connectionTimestamp | ||
282 | return $ timeDiff > connectionLifetime | ||
283 | |||
284 | {----------------------------------------------------------------------- | ||
285 | -- Transactions | ||
286 | -----------------------------------------------------------------------} | ||
287 | |||
288 | -- | Sometimes 'genTransactionId' may return already used transaction | ||
289 | -- id. We use a good entropy source but the issue /still/ (with very | ||
290 | -- small probabality) may happen. If the collision happen then this | ||
291 | -- function tries to find nearest unused slot, otherwise pending | ||
292 | -- transactions table is full. | ||
293 | firstUnused :: SockAddr -> TransactionId -> PendingQueries -> TransactionId | ||
294 | firstUnused addr rid m = do | ||
295 | case M.splitLookup rid <$> M.lookup addr m of | ||
296 | Nothing -> rid | ||
297 | Just (_ , Nothing, _ ) -> rid | ||
298 | Just (lt, Just _ , gt) -> | ||
299 | case backwardHole (keys lt) rid <|> forwardHole rid (keys gt) of | ||
300 | Nothing -> error "firstUnused: table is full" -- impossible | ||
301 | Just tid -> tid | ||
302 | where | ||
303 | forwardHole a [] | ||
304 | | a == maxBound = Nothing | ||
305 | | otherwise = Just (succ a) | ||
306 | forwardHole a (b : xs) | ||
307 | | succ a == b = forwardHole b xs | ||
308 | | otherwise = Just (succ a) | ||
309 | |||
310 | backwardHole [] a | ||
311 | | a == minBound = Nothing | ||
312 | | otherwise = Just (pred a) | ||
313 | backwardHole (b : xs) a | ||
314 | | b == pred a = backwardHole xs b | ||
315 | | otherwise = Just (pred a) | ||
316 | |||
317 | register :: SockAddr -> TransactionId -> PendingResponse | ||
318 | -> PendingQueries -> PendingQueries | ||
319 | register addr tid ares = M.alter insertId addr | ||
320 | where | ||
321 | insertId Nothing = Just (M.singleton tid ares) | ||
322 | insertId (Just m) = Just (M.insert tid ares m) | ||
323 | |||
324 | unregister :: SockAddr -> TransactionId | ||
325 | -> PendingQueries -> PendingQueries | ||
326 | unregister addr tid = M.update deleteId addr | ||
327 | where | ||
328 | deleteId m | ||
329 | | M.null m' = Nothing | ||
330 | | otherwise = Just m' | ||
331 | where | ||
332 | m' = M.delete tid m | ||
333 | |||
334 | -- | Generate a new unused transaction id and register as pending. | ||
335 | allocTransaction :: Manager -> SockAddr -> PendingResponse -> IO TransactionId | ||
336 | allocTransaction Manager {..} addr ares = | ||
337 | modifyMVar pendingResps $ \ m -> do | ||
338 | rndId <- genTransactionId | ||
339 | let tid = firstUnused addr rndId m | ||
340 | return (register addr tid ares m, tid) | ||
341 | |||
342 | -- | Wake up blocked thread and return response back. | ||
343 | commitTransaction :: Manager -> SockAddr -> TransactionId -> Response -> IO () | ||
344 | commitTransaction Manager {..} addr tid resp = | ||
345 | modifyMVarMasked_ pendingResps $ \ m -> do | ||
346 | case M.lookup tid =<< M.lookup addr m of | ||
347 | Nothing -> return m -- tracker responded after 'cancelTransaction' fired | ||
348 | Just ares -> do | ||
349 | putMVar ares (Right resp) | ||
350 | return $ unregister addr tid m | ||
351 | |||
352 | -- | Abort transaction forcefully. | ||
353 | cancelTransaction :: Manager -> SockAddr -> TransactionId -> IO () | ||
354 | cancelTransaction Manager {..} addr tid = | ||
355 | modifyMVarMasked_ pendingResps $ \m -> | ||
356 | return $ unregister addr tid m | ||
357 | |||
358 | -- | Handle responses from trackers. | ||
359 | listen :: Manager -> IO () | ||
360 | listen mgr @ Manager {..} = do | ||
361 | forever $ do | ||
362 | (bs, addr) <- BS.recvFrom sock (optMaxPacketSize options) | ||
363 | case decode bs of | ||
364 | Left _ -> return () -- parser failed, ignoring | ||
365 | Right (TransactionR {..}) -> commitTransaction mgr addr transIdR response | ||
366 | |||
367 | -- | Perform RPC transaction. If the action interrupted transaction | ||
368 | -- will be aborted. | ||
369 | transaction :: Manager -> SockAddr -> Connection -> Request -> IO Response | ||
370 | transaction mgr @ Manager {..} addr conn request = do | ||
371 | ares <- newEmptyMVar | ||
372 | tid <- allocTransaction mgr addr ares | ||
373 | performTransaction tid ares | ||
374 | `onException` cancelTransaction mgr addr tid | ||
375 | where | ||
376 | performTransaction tid ares = do | ||
377 | let trans = TransactionQ (connectionId conn) tid request | ||
378 | BS.sendAllTo sock (encode trans) addr | ||
379 | takeMVar ares >>= either throwIO return | ||
380 | |||
381 | {----------------------------------------------------------------------- | ||
382 | -- Connection cache | ||
383 | -----------------------------------------------------------------------} | ||
384 | |||
385 | connect :: Manager -> SockAddr -> Connection -> IO ConnectionId | ||
386 | connect m addr conn = do | ||
387 | resp <- transaction m addr conn Connect | ||
388 | case resp of | ||
389 | Connected cid -> return cid | ||
390 | Failed msg -> throwIO $ QueryFailed msg | ||
391 | _ -> throwIO $ UnexpectedResponse "connected" (responseName resp) | ||
392 | |||
393 | newConnection :: Manager -> SockAddr -> IO Connection | ||
394 | newConnection m addr = do | ||
395 | connId <- connect m addr initialConnection | ||
396 | establishedConnection connId | ||
397 | |||
398 | refreshConnection :: Manager -> SockAddr -> Connection -> IO Connection | ||
399 | refreshConnection mgr addr conn = do | ||
400 | expired <- isExpired conn | ||
401 | if expired | ||
402 | then do | ||
403 | connId <- connect mgr addr conn | ||
404 | establishedConnection connId | ||
405 | else do | ||
406 | return conn | ||
407 | |||
408 | withCache :: Manager -> SockAddr | ||
409 | -> (Maybe Connection -> IO Connection) -> IO Connection | ||
410 | withCache mgr addr action = do | ||
411 | cache <- readIORef (connectionCache mgr) | ||
412 | conn <- action (M.lookup addr cache) | ||
413 | writeIORef (connectionCache mgr) (M.insert addr conn cache) | ||
414 | return conn | ||
415 | |||
416 | getConnection :: Manager -> SockAddr -> IO Connection | ||
417 | getConnection mgr addr = withCache mgr addr $ | ||
418 | maybe (newConnection mgr addr) (refreshConnection mgr addr) | ||
419 | |||
420 | {----------------------------------------------------------------------- | ||
421 | -- RPC | ||
422 | -----------------------------------------------------------------------} | ||
423 | |||
424 | retransmission :: Options -> IO a -> IO a | ||
425 | retransmission Options {..} action = go optMinTimeout | ||
426 | where | ||
427 | go curTimeout | ||
428 | | curTimeout > optMaxTimeout = throwIO $ TimeoutExpired curTimeout | ||
429 | | otherwise = do | ||
430 | r <- timeout (curTimeout * sec) action | ||
431 | maybe (go (optMultiplier * curTimeout)) return r | ||
432 | |||
433 | queryTracker :: Manager -> URI -> Request -> IO Response | ||
434 | queryTracker mgr uri req = do | ||
435 | addr <- getTrackerAddr mgr uri | ||
436 | retransmission (options mgr) $ do | ||
437 | conn <- getConnection mgr addr | ||
438 | transaction mgr addr conn req | ||
439 | |||
440 | -- | This function can throw 'RpcException'. | ||
441 | announce :: Manager -> URI -> AnnounceQuery -> IO AnnounceInfo | ||
442 | announce mgr uri q = do | ||
443 | resp <- queryTracker mgr uri (Announce q) | ||
444 | case resp of | ||
445 | Announced info -> return info | ||
446 | _ -> throwIO $ UnexpectedResponse "announce" (responseName resp) | ||
447 | |||
448 | -- | This function can throw 'RpcException'. | ||
449 | scrape :: Manager -> URI -> ScrapeQuery -> IO ScrapeInfo | ||
450 | scrape mgr uri ihs = do | ||
451 | resp <- queryTracker mgr uri (Scrape ihs) | ||
452 | case resp of | ||
453 | Scraped info -> return $ L.zip ihs info | ||
454 | _ -> throwIO $ UnexpectedResponse "scrape" (responseName resp) | ||
diff --git a/bittorrent/src/Network/BitTorrent/Tracker/Session.hs b/bittorrent/src/Network/BitTorrent/Tracker/Session.hs new file mode 100644 index 00000000..aa4a832f --- /dev/null +++ b/bittorrent/src/Network/BitTorrent/Tracker/Session.hs | |||
@@ -0,0 +1,306 @@ | |||
1 | -- | | ||
2 | -- Copyright : (c) Sam Truzjan 2014 | ||
3 | -- License : BSD | ||
4 | -- Maintainer : pxqr.sta@gmail.com | ||
5 | -- Stability : experimental | ||
6 | -- Portability : portable | ||
7 | -- | ||
8 | -- Multitracker sessions. | ||
9 | -- | ||
10 | {-# LANGUAGE FlexibleInstances #-} | ||
11 | {-# LANGUAGE TypeFamilies #-} | ||
12 | {-# LANGUAGE TypeSynonymInstances #-} | ||
13 | {-# LANGUAGE TemplateHaskell #-} | ||
14 | module Network.BitTorrent.Tracker.Session | ||
15 | ( -- * Session | ||
16 | Session | ||
17 | , Event (..) | ||
18 | , newSession | ||
19 | , closeSession | ||
20 | , withSession | ||
21 | |||
22 | -- * Client send notifications | ||
23 | , notify | ||
24 | , askPeers | ||
25 | |||
26 | -- * Session state | ||
27 | -- ** Status | ||
28 | , Status (..) | ||
29 | , getStatus | ||
30 | |||
31 | -- ** Single tracker sessions | ||
32 | , LastScrape (..) | ||
33 | , TrackerSession | ||
34 | , trackerPeers | ||
35 | , trackerScrape | ||
36 | , getSessionState | ||
37 | |||
38 | -- * Tracker Exchange | ||
39 | -- | BEP28: <http://www.bittorrent.org/beps/bep_0028.html> | ||
40 | , addTracker | ||
41 | , removeTracker | ||
42 | , getTrustedTrackers | ||
43 | ) where | ||
44 | |||
45 | import Control.Applicative | ||
46 | import Control.Exception | ||
47 | import Control.Concurrent | ||
48 | import Control.Concurrent.Chan.Split as CS | ||
49 | import Control.Monad | ||
50 | import Data.Default | ||
51 | import Data.Fixed | ||
52 | import Data.Foldable as F | ||
53 | import Data.IORef | ||
54 | import Data.List as L | ||
55 | import Data.Maybe | ||
56 | import Data.Time | ||
57 | import Data.Traversable | ||
58 | import Network.URI | ||
59 | |||
60 | import Data.Torrent | ||
61 | import Network.Address | ||
62 | import Network.BitTorrent.Internal.Cache | ||
63 | import Network.BitTorrent.Internal.Types | ||
64 | import Network.BitTorrent.Tracker.List as TL | ||
65 | import Network.BitTorrent.Tracker.Message | ||
66 | import Network.BitTorrent.Tracker.RPC as RPC | ||
67 | |||
68 | {----------------------------------------------------------------------- | ||
69 | -- Single tracker session | ||
70 | -----------------------------------------------------------------------} | ||
71 | |||
72 | -- | Status of this client. | ||
73 | data Status | ||
74 | = Running -- ^ This client is announced and listenning for incoming | ||
75 | -- connections. | ||
76 | | Paused -- ^ This client does not expecting incoming connections. | ||
77 | deriving (Show, Eq, Bounded, Enum) | ||
78 | |||
79 | -- | Client starting in the paused state. | ||
80 | instance Default Status where | ||
81 | def = Paused | ||
82 | |||
83 | -- | Tracker session starts with scrape unknown. | ||
84 | instance Default LastScrape where | ||
85 | def = LastScrape Nothing Nothing | ||
86 | |||
87 | data LastScrape = LastScrape | ||
88 | { -- | Count of leechers the tracker aware of. | ||
89 | scrapeLeechers :: Maybe Int | ||
90 | |||
91 | -- | Count of seeders the tracker aware of. | ||
92 | , scrapeSeeders :: Maybe Int | ||
93 | } deriving (Show, Eq) | ||
94 | |||
95 | -- | Single tracker session. | ||
96 | data TrackerSession = TrackerSession | ||
97 | { -- | Used to notify 'Stopped' and 'Completed' events. | ||
98 | statusSent :: !(Maybe Status) | ||
99 | |||
100 | -- | Can be used to retrieve peer set. | ||
101 | , trackerPeers :: Cached [PeerAddr IP] | ||
102 | |||
103 | -- | Can be used to show brief swarm stats in client GUI. | ||
104 | , trackerScrape :: Cached LastScrape | ||
105 | } | ||
106 | |||
107 | -- | Not contacted. | ||
108 | instance Default TrackerSession where | ||
109 | def = TrackerSession Nothing def def | ||
110 | |||
111 | -- | Do we need to notify this /specific/ tracker? | ||
112 | needNotify :: AnnounceEvent -> Maybe Status -> Maybe Bool | ||
113 | needNotify Started Nothing = Just True | ||
114 | needNotify Stopped Nothing = Just False | ||
115 | needNotify Completed Nothing = Just False | ||
116 | needNotify Started (Just Running) = Nothing | ||
117 | needNotify Stopped (Just Running) = Just True | ||
118 | needNotify Completed (Just Running) = Just True | ||
119 | needNotify Started (Just Paused ) = Just True | ||
120 | needNotify Stopped (Just Paused ) = Just False | ||
121 | needNotify Completed (Just Paused ) = Just True | ||
122 | |||
123 | -- | Client status after event announce succeed. | ||
124 | nextStatus :: AnnounceEvent -> Maybe Status | ||
125 | nextStatus Started = Just Running | ||
126 | nextStatus Stopped = Just Paused | ||
127 | nextStatus Completed = Nothing -- must keep previous status | ||
128 | |||
129 | seconds :: Int -> NominalDiffTime | ||
130 | seconds n = realToFrac (toEnum n :: Uni) | ||
131 | |||
132 | cachePeers :: AnnounceInfo -> IO (Cached [PeerAddr IP]) | ||
133 | cachePeers AnnounceInfo {..} = | ||
134 | newCached (seconds respInterval) | ||
135 | (seconds (fromMaybe respInterval respMinInterval)) | ||
136 | (getPeerList respPeers) | ||
137 | |||
138 | cacheScrape :: AnnounceInfo -> IO (Cached LastScrape) | ||
139 | cacheScrape AnnounceInfo {..} = | ||
140 | newCached (seconds respInterval) | ||
141 | (seconds (fromMaybe respInterval respMinInterval)) | ||
142 | LastScrape | ||
143 | { scrapeSeeders = respComplete | ||
144 | , scrapeLeechers = respIncomplete | ||
145 | } | ||
146 | |||
147 | -- | Make announce request to specific tracker returning new state. | ||
148 | notifyTo :: Manager -> Session -> AnnounceEvent | ||
149 | -> TierEntry TrackerSession -> IO TrackerSession | ||
150 | notifyTo mgr s @ Session {..} event (uri, entry @ TrackerSession {..}) = do | ||
151 | let shouldNotify = needNotify event statusSent | ||
152 | mustNotify <- maybe (isExpired trackerPeers) return shouldNotify | ||
153 | if not mustNotify | ||
154 | then return entry | ||
155 | else do | ||
156 | let q = SAnnounceQuery sessionTopic def Nothing (Just event) | ||
157 | res <- RPC.announce mgr uri q | ||
158 | when (statusSent == Nothing) $ do | ||
159 | send sessionEvents (TrackerConfirmed uri) | ||
160 | send sessionEvents (AnnouncedTo uri) | ||
161 | let status' = nextStatus event <|> statusSent | ||
162 | TrackerSession status' <$> cachePeers res <*> cacheScrape res | ||
163 | |||
164 | {----------------------------------------------------------------------- | ||
165 | -- Multitracker Session | ||
166 | -----------------------------------------------------------------------} | ||
167 | |||
168 | -- | Multitracker session. | ||
169 | data Session = Session | ||
170 | { -- | Infohash to announce at each 'announce' request. | ||
171 | sessionTopic :: !InfoHash | ||
172 | |||
173 | -- | Current status of this client is used to filter duplicated | ||
174 | -- notifications, for e.g. we don't want to notify a tracker with | ||
175 | -- ['Stopped', 'Stopped'], the last should be ignored. | ||
176 | , sessionStatus :: !(IORef Status) | ||
177 | |||
178 | -- | A set of single-tracker sessions. Any request to a tracker | ||
179 | -- must take a lock. | ||
180 | , sessionTrackers :: !(MVar (TrackerList TrackerSession)) | ||
181 | |||
182 | , sessionEvents :: !(SendPort (Event Session)) | ||
183 | } | ||
184 | |||
185 | instance EventSource Session where | ||
186 | data Event Session | ||
187 | = TrackerAdded URI | ||
188 | | TrackerConfirmed URI | ||
189 | | TrackerRemoved URI | ||
190 | | AnnouncedTo URI | ||
191 | | SessionClosed | ||
192 | |||
193 | listen Session {..} = CS.listen sessionEvents | ||
194 | |||
195 | |||
196 | -- | Create a new multitracker session in paused state. Tracker list | ||
197 | -- must contant only /trusted/ tracker uris. To start announcing | ||
198 | -- client presence use 'notify'. | ||
199 | newSession :: InfoHash -> TrackerList () -> IO Session | ||
200 | newSession ih origUris = do | ||
201 | urisList <- shuffleTiers origUris | ||
202 | statusRef <- newIORef def | ||
203 | entriesVar <- newMVar (fmap (const def) urisList) | ||
204 | eventStream <- newSendPort | ||
205 | return Session | ||
206 | { sessionTopic = ih | ||
207 | , sessionStatus = statusRef | ||
208 | , sessionTrackers = entriesVar | ||
209 | , sessionEvents = eventStream | ||
210 | } | ||
211 | |||
212 | -- | Release scarce resources associated with the given session. This | ||
213 | -- function block until all trackers tied with this peer notified with | ||
214 | -- 'Stopped' event. | ||
215 | closeSession :: Manager -> Session -> IO () | ||
216 | closeSession m s @ Session {..} = do | ||
217 | notify m s Stopped | ||
218 | send sessionEvents SessionClosed | ||
219 | |||
220 | {----------------------------------------------------------------------- | ||
221 | -- Operations | ||
222 | -----------------------------------------------------------------------} | ||
223 | |||
224 | -- | Normally you need to use 'Control.Monad.Trans.Resource.alloc'. | ||
225 | withSession :: Manager -> InfoHash -> TrackerList () | ||
226 | -> (Session -> IO ()) -> IO () | ||
227 | withSession m ih uris = bracket (newSession ih uris) (closeSession m) | ||
228 | |||
229 | -- | Get last announced status. The only action can alter this status | ||
230 | -- is 'notify'. | ||
231 | getStatus :: Session -> IO Status | ||
232 | getStatus Session {..} = readIORef sessionStatus | ||
233 | |||
234 | getSessionState :: Session -> IO [[TierEntry TrackerSession]] | ||
235 | getSessionState Session {..} = TL.toList <$> readMVar sessionTrackers | ||
236 | |||
237 | -- | Do we need to sent this event to a first working tracker or to | ||
238 | -- the all known good trackers? | ||
239 | allNotify :: AnnounceEvent -> Bool | ||
240 | allNotify Started = False | ||
241 | allNotify Stopped = True | ||
242 | allNotify Completed = True | ||
243 | |||
244 | notifyAll :: Manager -> Session -> AnnounceEvent -> IO () | ||
245 | notifyAll mgr s @ Session {..} event = do | ||
246 | modifyMVar_ sessionTrackers $ | ||
247 | (traversal (notifyTo mgr s event)) | ||
248 | where | ||
249 | traversal | ||
250 | | allNotify event = traverseAll | ||
251 | | otherwise = traverseTiers | ||
252 | |||
253 | -- TODO send notifications to tracker periodically. | ||
254 | -- | | ||
255 | -- | ||
256 | -- This function /may/ block until tracker query proceed. | ||
257 | notify :: Manager -> Session -> AnnounceEvent -> IO () | ||
258 | notify mgr ses event = do | ||
259 | prevStatus <- atomicModifyIORef (sessionStatus ses) $ \ s -> | ||
260 | (fromMaybe s (nextStatus event), s) | ||
261 | when (needNotify event (Just prevStatus) == Just True) $ do | ||
262 | notifyAll mgr ses event | ||
263 | |||
264 | -- TODO run announce if sesion have no peers | ||
265 | -- | The returned list of peers can have duplicates. | ||
266 | -- This function /may/ block. Use async if needed. | ||
267 | askPeers :: Manager -> Session -> IO [PeerAddr IP] | ||
268 | askPeers _mgr ses = do | ||
269 | list <- readMVar (sessionTrackers ses) | ||
270 | L.concat <$> collect (tryTakeData . trackerPeers) list | ||
271 | |||
272 | collect :: (a -> IO (Maybe b)) -> TrackerList a -> IO [b] | ||
273 | collect f lst = (catMaybes . F.toList) <$> traverse f lst | ||
274 | |||
275 | --sourcePeers :: Session -> Source (PeerAddr IP) | ||
276 | --sourcePeers | ||
277 | |||
278 | {----------------------------------------------------------------------- | ||
279 | -- Tracker exchange | ||
280 | -----------------------------------------------------------------------} | ||
281 | |||
282 | -- Trackers discovered through this protocol SHOULD be treated with a | ||
283 | -- certain amount of suspicion. Since the source of a tracker exchange | ||
284 | -- message cannot be trusted, an implementation SHOULD have a lower | ||
285 | -- number of retries before giving up entirely. | ||
286 | |||
287 | addTracker :: Session -> URI -> IO () | ||
288 | addTracker Session {..} uri = do | ||
289 | undefined | ||
290 | send sessionEvents (TrackerAdded uri) | ||
291 | |||
292 | removeTracker :: Manager -> Session -> URI -> IO () | ||
293 | removeTracker m Session {..} uri = do | ||
294 | send sessionEvents (TrackerRemoved uri) | ||
295 | |||
296 | -- Also, as specified under the definitions section, a tracker that | ||
297 | -- has not worked should never be propagated to other peers over the | ||
298 | -- tracker exchange protocol. | ||
299 | |||
300 | -- | Return all known trackers. | ||
301 | getTrackers :: Session -> IO [URI] | ||
302 | getTrackers = undefined | ||
303 | |||
304 | -- | Return trackers from torrent file and | ||
305 | getTrustedTrackers :: Session -> IO [URI] | ||
306 | getTrustedTrackers = undefined | ||