summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--bittorrent.cabal1
-rw-r--r--tests/Network/BitTorrent/Exchange/Session/MetadataSpec.hs71
2 files changed, 72 insertions, 0 deletions
diff --git a/bittorrent.cabal b/bittorrent.cabal
index 303e93c6..1562fdac 100644
--- a/bittorrent.cabal
+++ b/bittorrent.cabal
@@ -210,6 +210,7 @@ test-suite spec
210 Network.BitTorrent.Tracker.RPC.UDPSpec 210 Network.BitTorrent.Tracker.RPC.UDPSpec
211 Network.BitTorrent.Tracker.SessionSpec 211 Network.BitTorrent.Tracker.SessionSpec
212 Network.BitTorrent.Exchange.MessageSpec 212 Network.BitTorrent.Exchange.MessageSpec
213 Network.BitTorrent.Exchange.Session.MetadataSpec
213 Network.BitTorrent.Exchange.WireSpec 214 Network.BitTorrent.Exchange.WireSpec
214 System.Torrent.StorageSpec 215 System.Torrent.StorageSpec
215 System.Torrent.FileMapSpec 216 System.Torrent.FileMapSpec
diff --git a/tests/Network/BitTorrent/Exchange/Session/MetadataSpec.hs b/tests/Network/BitTorrent/Exchange/Session/MetadataSpec.hs
new file mode 100644
index 00000000..975ceb5b
--- /dev/null
+++ b/tests/Network/BitTorrent/Exchange/Session/MetadataSpec.hs
@@ -0,0 +1,71 @@
1{-# LANGUAGE RecordWildCards #-}
2module Network.BitTorrent.Exchange.Session.MetadataSpec (spec) where
3import Control.Concurrent
4import Data.ByteString as BS
5import Data.ByteString.Lazy as BL
6import Test.Hspec
7import Test.QuickCheck
8
9import Data.BEncode as BE
10import Data.Torrent
11import Data.Torrent.Piece as P
12import Network.BitTorrent.Core
13import Network.BitTorrent.Exchange.Message
14import Network.BitTorrent.Exchange.Session.Metadata
15
16import Config
17import Network.BitTorrent.CoreSpec ()
18
19
20placeholderAddr :: PeerAddr IP
21placeholderAddr = "0.0.0.0:0"
22
23chunkBy :: Int -> BS.ByteString -> [BS.ByteString]
24chunkBy s bs
25 | BS.null bs = []
26 | otherwise = BS.take s bs : chunkBy s (BS.drop s bs)
27
28withUpdates :: Updates a -> IO a
29withUpdates m = do
30 Torrent {..} <- getTestTorrent
31 let infoDictLen = fromIntegral $ BL.length $ BE.encode tInfoDict
32 mvar <- newMVar (nullStatus infoDictLen)
33 runUpdates mvar placeholderAddr m
34
35simulateFetch :: InfoDict -> Updates (Maybe InfoDict)
36simulateFetch dict = go
37 where
38 blocks = chunkBy metadataPieceSize (BL.toStrict (BE.encode dict))
39 packPiece ix = P.Piece ix (blocks !! ix)
40 ih = idInfoHash dict
41
42 go = do
43 mix <- scheduleBlock
44 case mix of
45 Nothing -> return Nothing
46 Just ix -> do
47 mdict <- pushBlock (packPiece ix) ih
48 maybe go (return . Just) mdict
49
50spec :: Spec
51spec = do
52 describe "scheduleBlock" $ do
53 it "never schedule the same index twice" $ do
54 pending
55
56 describe "resetPending" $ do
57 it "" $ do
58 pending
59
60 describe "cancelPending" $ do
61 it "must not throw an exception if cancel the same piece twice" $ do
62 pending
63
64 describe "pushBlock" $ do
65 it "assemble infodict from chunks" $ do
66 Torrent {..} <- getTestTorrent
67 mdict <- withUpdates $ simulateFetch tInfoDict
68 mdict `shouldBe` Just tInfoDict
69
70 it "must throw an exception if block if not requested" $ do
71 pending \ No newline at end of file