diff options
Diffstat (limited to 'tests/Network/BitTorrent/Tracker')
-rw-r--r-- | tests/Network/BitTorrent/Tracker/RPC/UDPSpec.hs | 53 |
1 files changed, 50 insertions, 3 deletions
diff --git a/tests/Network/BitTorrent/Tracker/RPC/UDPSpec.hs b/tests/Network/BitTorrent/Tracker/RPC/UDPSpec.hs index 4cbaa09d..1a893011 100644 --- a/tests/Network/BitTorrent/Tracker/RPC/UDPSpec.hs +++ b/tests/Network/BitTorrent/Tracker/RPC/UDPSpec.hs | |||
@@ -1,7 +1,54 @@ | |||
1 | {-# LANGUAGE RecordWildCards #-} | ||
1 | module Network.BitTorrent.Tracker.RPC.UDPSpec (spec) where | 2 | module Network.BitTorrent.Tracker.RPC.UDPSpec (spec) where |
3 | |||
4 | import Control.Applicative | ||
5 | import Control.Monad | ||
6 | import Data.Default | ||
7 | import Data.List as L | ||
8 | import Data.Maybe | ||
9 | import Network.URI | ||
2 | import Test.Hspec | 10 | import Test.Hspec |
11 | import Test.QuickCheck | ||
12 | |||
13 | import Network.BitTorrent.Core.PeerAddr | ||
14 | import Network.BitTorrent.Tracker.RPC.Message | ||
15 | import Network.BitTorrent.Tracker.RPC.UDP | ||
16 | import Network.BitTorrent.Tracker.RPC.MessageSpec () | ||
17 | |||
18 | |||
19 | arbitrarySample :: Arbitrary a => IO a | ||
20 | arbitrarySample = L.head <$> sample' arbitrary | ||
21 | |||
22 | trackerURIs :: [URI] | ||
23 | trackerURIs = | ||
24 | [ fromJust $ parseURI "udp://tracker.openbittorrent.com:80/announce" | ||
25 | , fromJust $ parseURI "udp://tracker.publicbt.com:80/announce" | ||
26 | ] | ||
27 | |||
28 | -- relation with query: peer id, numwant | ||
29 | validateInfo :: AnnounceQuery -> AnnounceInfo -> Expectation | ||
30 | validateInfo AnnounceQuery {..} AnnounceInfo {..} = do | ||
31 | respComplete `shouldSatisfy` isJust | ||
32 | respIncomplete `shouldSatisfy` isJust | ||
33 | respMinInterval `shouldSatisfy` isNothing | ||
34 | respWarning `shouldSatisfy` isNothing | ||
35 | peerList `shouldSatisfy` L.all (isNothing . peerID) | ||
36 | fromJust respComplete + fromJust respIncomplete `shouldBe` L.length peerList | ||
37 | where | ||
38 | peerList = getPeerList respPeers | ||
39 | |||
3 | 40 | ||
4 | spec :: Spec | 41 | spec :: Spec |
5 | spec = | 42 | spec = do |
6 | describe "UDP tracker client RPC" $ do | 43 | forM_ trackerURIs $ \ uri -> |
7 | return () \ No newline at end of file | 44 | context (show uri) $ do |
45 | describe "announce" $ do | ||
46 | it "have valid response" $ do | ||
47 | query <- arbitrarySample | ||
48 | connect uri >>= announce query >>= validateInfo query | ||
49 | |||
50 | describe "scrape" $ do | ||
51 | it "have valid response" $ do | ||
52 | xs <- connect uri >>= scrape [def] | ||
53 | return () | ||
54 | -- L.length xs `shouldSatisfy` (>= 1) | ||