summaryrefslogtreecommitdiff
path: root/tests/Network/BitTorrent/Exchange/DownloadSpec.hs
diff options
context:
space:
mode:
Diffstat (limited to 'tests/Network/BitTorrent/Exchange/DownloadSpec.hs')
-rw-r--r--tests/Network/BitTorrent/Exchange/DownloadSpec.hs71
1 files changed, 71 insertions, 0 deletions
diff --git a/tests/Network/BitTorrent/Exchange/DownloadSpec.hs b/tests/Network/BitTorrent/Exchange/DownloadSpec.hs
new file mode 100644
index 00000000..a0d40af3
--- /dev/null
+++ b/tests/Network/BitTorrent/Exchange/DownloadSpec.hs
@@ -0,0 +1,71 @@
1{-# LANGUAGE RecordWildCards #-}
2module Network.BitTorrent.Exchange.DownloadSpec (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 as Torrent
11import Network.BitTorrent.Address
12import Network.BitTorrent.Exchange.Download
13import Network.BitTorrent.Exchange.Message
14
15import Config
16import Network.BitTorrent.CoreSpec ()
17
18
19placeholderAddr :: PeerAddr IP
20placeholderAddr = "0.0.0.0:0"
21
22chunkBy :: Int -> BS.ByteString -> [BS.ByteString]
23chunkBy s bs
24 | BS.null bs = []
25 | otherwise = BS.take s bs : chunkBy s (BS.drop s bs)
26
27withUpdates :: Updates s a -> IO a
28withUpdates m = do
29 Torrent {..} <- getTestTorrent
30 let infoDictLen = fromIntegral $ BL.length $ BE.encode tInfoDict
31 --mvar <- newMVar (nullStatus infoDictLen)
32 --runUpdates mvar placeholderAddr m
33 undefined
34
35simulateFetch :: InfoDict -> Updates s (Maybe InfoDict)
36simulateFetch dict = go
37 where
38 blocks = chunkBy metadataPieceSize (BL.toStrict (BE.encode dict))
39 packPiece ix = Torrent.Piece ix (blocks !! ix)
40 ih = idInfoHash dict
41
42 go = do
43 mix <- scheduleBlock undefined undefined
44 case mix of
45 Nothing -> return Nothing
46 Just ix -> do
47 mdict <- pushBlock undefined (packPiece ix)
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