summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--bittorrent.cabal9
-rw-r--r--src/Network/BitTorrent/Tracker/List.hs153
-rw-r--r--tests/Network/BitTorrent/Tracker/ListSpec.hs44
3 files changed, 203 insertions, 3 deletions
diff --git a/bittorrent.cabal b/bittorrent.cabal
index f8e598c1..4b2431ce 100644
--- a/bittorrent.cabal
+++ b/bittorrent.cabal
@@ -74,7 +74,7 @@ library
74-- Network.BitTorrent.Exchange.Session 74-- Network.BitTorrent.Exchange.Session
75 Network.BitTorrent.Exchange.Status 75 Network.BitTorrent.Exchange.Status
76 Network.BitTorrent.Exchange.Wire 76 Network.BitTorrent.Exchange.Wire
77-- Network.BitTorrent.Tracker 77 Network.BitTorrent.Tracker.List
78 Network.BitTorrent.Tracker.Message 78 Network.BitTorrent.Tracker.Message
79 Network.BitTorrent.Tracker.RPC 79 Network.BitTorrent.Tracker.RPC
80 Network.BitTorrent.Tracker.RPC.HTTP 80 Network.BitTorrent.Tracker.RPC.HTTP
@@ -153,12 +153,15 @@ library
153 , wai >= 1.4 && < 2.0 153 , wai >= 1.4 && < 2.0
154 , iproute 154 , iproute
155 155
156 -- RNG/PRNG
157 , entropy >= 0.2
158 , random >= 1.0.0.2
159 , random-shuffle >= 0.0.0.4
160
156 -- System 161 -- System
157 , directory >= 1.2 162 , directory >= 1.2
158 , entropy >= 0.2
159 , filepath >= 1.3 163 , filepath >= 1.3
160 , mmap >= 0.5 164 , mmap >= 0.5
161 , random >= 1.0.0.2
162 165
163 ghc-options: -Wall 166 ghc-options: -Wall
164 ghc-prof-options: 167 ghc-prof-options:
diff --git a/src/Network/BitTorrent/Tracker/List.hs b/src/Network/BitTorrent/Tracker/List.hs
new file mode 100644
index 00000000..b6371f1d
--- /dev/null
+++ b/src/Network/BitTorrent/Tracker/List.hs
@@ -0,0 +1,153 @@
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--
12module Network.BitTorrent.Tracker.List
13 ( -- * Tracker list
14 TrackerList
15
16 -- * Construction
17 , trackerList
18 , shuffleTiers
19
20 -- * Traversals
21 , traverseAll
22 , traverseTiers
23 ) where
24
25import Prelude hiding (mapM, foldr)
26import Control.Applicative
27import Control.Exception
28import Data.List as L (elem, any, filter, null)
29import Data.Foldable
30import Data.Traversable
31import Network.URI
32import System.Random.Shuffle
33
34import Data.Torrent
35import Network.BitTorrent.Tracker.RPC as RPC
36
37{-----------------------------------------------------------------------
38-- Tracker list datatype
39-----------------------------------------------------------------------}
40
41type Tier a = [a]
42
43-- | Tracker list is either a single tracker or list of tiers. All
44-- trackers in each tier must be checked before the client goes on to
45-- the next tier.
46data TrackerList a
47 = Announce a -- ^ torrent file 'announce' field only
48 | TierList [Tier a] -- ^ torrent file 'announce-list' field only
49 deriving (Show, Eq)
50
51instance Functor TrackerList where
52 fmap f (Announce a) = Announce (f a)
53 fmap f (TierList a) = TierList (fmap (fmap f) a)
54
55instance Foldable TrackerList where
56 foldr f z (Announce a ) = f a z
57 foldr f z (TierList xs) = foldr (flip (foldr f)) z xs
58
59instance Traversable TrackerList where
60 traverse f (Announce a ) = Announce <$> f a
61 traverse f (TierList xs) = TierList <$> traverse (traverse f) xs
62
63{-----------------------------------------------------------------------
64-- List extraction
65-----------------------------------------------------------------------}
66-- BEP12 do not expose any restrictions for the content of
67-- 'announce-list' key - there are some /bad/ cases can happen with
68-- poorly designed or even malicious torrent creation software.
69--
70-- Bad case #1: announce-list is present, but empty.
71--
72-- { tAnnounce = Just "http://a.com"
73-- , tAnnounceList = Just [[]]
74-- }
75--
76-- Bad case #2: announce uri do not present in announce list.
77--
78-- { tAnnounce = Just "http://a.com"
79-- , tAnnounceList = Just [["udp://a.com"]]
80-- }
81--
82-- The addBackup function solves both problems by adding announce uri
83-- as backup tier.
84--
85addBackup :: [[URI]] -> URI -> [[URI]]
86addBackup tiers bkp
87 | L.any (L.elem bkp) tiers = tiers
88 | otherwise = tiers ++ [[bkp]]
89
90fixList :: Maybe [[URI]] -> Maybe URI -> Maybe [[URI]]
91fixList mxss mx = do
92 xss <- mxss
93 let xss' = L.filter (not . L.null) xss
94 return $ maybe xss' (addBackup xss') mx
95
96-- | Extract set of trackers from torrent file. The 'tAnnounce' key is
97-- only ignored if the 'tAnnounceList' key is present.
98trackerList :: Torrent -> Maybe (TrackerList URI)
99trackerList Torrent {..} = TierList <$> (tAnnounceList `fixList` tAnnounce)
100 <|> Announce <$> tAnnounce
101
102-- | Shuffle /order of trackers/ in each tier, preserving original
103-- /order of tiers/. This can help to balance the load between the
104-- trackers.
105shuffleTiers :: TrackerList a -> IO (TrackerList a)
106shuffleTiers (Announce a ) = return (Announce a)
107shuffleTiers (TierList xs) = TierList <$> mapM shuffleM xs
108
109{-----------------------------------------------------------------------
110-- Special traversals (suppressed RPC exceptions)
111-----------------------------------------------------------------------}
112
113catchRPC :: IO a -> IO a -> IO a
114catchRPC a b = catch a (f b)
115 where
116 f :: a -> RpcException -> a
117 f = const
118
119throwRPC :: String -> IO a
120throwRPC = throwIO . GenericException
121
122-- | Like 'traverse' but ignore 'RpcExceptions'.
123traverseAll :: (a -> IO a) -> TrackerList a -> IO (TrackerList a)
124traverseAll action = traverse (action $?)
125 where
126 f $? x = catchRPC (f x) (return x)
127
128-- | Like 'traverse' but put working trackers to the head of tiers.
129-- This can help to avoid exceessive requests to not available
130-- trackers at each reannounce.
131traverseTiers :: (a -> IO a) -> TrackerList a -> IO (TrackerList a)
132traverseTiers action (Announce a) = Announce <$> action a
133traverseTiers action (TierList tiers) = TierList <$> goTiers (goTier []) tiers
134 where
135 goTiers _ [] = throwRPC "traverseTiers: no tiers"
136 goTiers f (x : xs) = catchRPC shortcut failback
137 where
138 shortcut = do
139 x' <- f x
140 return (x' : xs)
141
142 failback = do
143 xs' <- goTiers f xs
144 return (x : xs')
145
146 goTier _ [] = throwRPC "traverseTiers: no trackers in tier"
147 goTier failed (a : as) = catchRPC shortcut failback
148 where
149 shortcut = do
150 a' <- action a
151 return (a' : as ++ failed) -- failed trackers at the end
152
153 failback = goTier (a : failed) as
diff --git a/tests/Network/BitTorrent/Tracker/ListSpec.hs b/tests/Network/BitTorrent/Tracker/ListSpec.hs
new file mode 100644
index 00000000..8decd3c9
--- /dev/null
+++ b/tests/Network/BitTorrent/Tracker/ListSpec.hs
@@ -0,0 +1,44 @@
1module Network.BitTorrent.Tracker.ListSpec (spec) where
2import Control.Exception
3import Data.Default
4import Data.Foldable as F
5import Data.List as L
6import Data.Maybe
7import Network.URI
8import Test.Hspec
9
10import Data.Torrent
11import Network.BitTorrent.Tracker.List
12import Network.BitTorrent.Tracker.RPC
13
14
15uris :: [URI]
16uris = fmap (fromJust . parseURI . renderURI) [1..10 :: Int]
17 where
18 renderURI n = "http://" ++ show n ++ ".org"
19
20list :: TrackerList URI
21list = fromJust $ trackerList def { tAnnounceList = Just [uris] }
22
23spec :: Spec
24spec = do
25 describe "TrackerList" $ do
26 it "trackerList is not empty" $ do
27 pending
28
29 it "shuffleTiers (may fail with very small probability)" $ do
30 list' <- shuffleTiers list
31 list' `shouldSatisfy` (/= list)
32
33 it "traverseAll" $ do
34 xs <- traverseAll (\ uri -> if uri == L.last uris
35 then throwIO (GenericException "")
36 else return uri { uriScheme = "udp://" }) list
37 let udps = F.sum $ fmap (fromEnum . ("udp://" ==) . uriScheme) xs
38 udps `shouldBe` pred (L.length uris)
39
40 it "traverseTiers" $ do
41 xs' <- traverseTiers (\ uri -> if uri == L.last uris then return uri
42 else throwIO (GenericException "")) list
43
44 return ()