summaryrefslogtreecommitdiff
path: root/bittorrent/tests/Network/BitTorrent/DHT/QuerySpec.hs
diff options
context:
space:
mode:
Diffstat (limited to 'bittorrent/tests/Network/BitTorrent/DHT/QuerySpec.hs')
-rw-r--r--bittorrent/tests/Network/BitTorrent/DHT/QuerySpec.hs105
1 files changed, 0 insertions, 105 deletions
diff --git a/bittorrent/tests/Network/BitTorrent/DHT/QuerySpec.hs b/bittorrent/tests/Network/BitTorrent/DHT/QuerySpec.hs
deleted file mode 100644
index 93f78263..00000000
--- a/bittorrent/tests/Network/BitTorrent/DHT/QuerySpec.hs
+++ /dev/null
@@ -1,105 +0,0 @@
1{-# LANGUAGE RecordWildCards #-}
2module Network.BitTorrent.DHT.QuerySpec (spec) where
3import Control.Applicative
4import Control.Exception
5import Control.Monad.Reader
6import Data.Conduit as C
7import Data.Conduit.List as CL
8import Data.Default
9import Data.List as L
10import Test.Hspec
11
12import Network.BitTorrent.Address
13import Network.BitTorrent.DHT
14import Network.BitTorrent.DHT.Session
15import Network.BitTorrent.DHT.Query
16
17import Network.BitTorrent.DHT.TestData
18
19
20myAddr :: NodeAddr IPv4
21myAddr = "0.0.0.0:0"
22
23nullLogger :: LogFun
24nullLogger _ _ _ _ = return ()
25
26--simpleLogger :: LogFun
27--simpleLogger _ t _ _ = print t
28
29simpleDHT :: [NodeHandler IPv4] -> DHT IPv4 a -> IO a
30simpleDHT hs m =
31 bracket (newNode hs def myAddr nullLogger Nothing) closeNode $ \ node ->
32 runDHT node m
33
34getBootInfo :: IO (NodeInfo IPv4)
35getBootInfo = do
36 startAddr <- resolveHostName (L.head defaultBootstrapNodes)
37 simpleDHT [] $ fmap fst (pingQ startAddr)
38
39spec :: Spec
40spec = parallel $ do
41 describe "environment" $ do
42 describe "test node" $ do
43 it "is alive" $ do
44 _ <- getBootInfo
45 return ()
46
47 describe "handlers" $ do
48 it "" $ pendingWith "need to setup 2 DHT locally"
49
50 describe "basic queries" $ do
51 it "ping" $ do
52 _ <- getBootInfo
53 return ()
54
55 it "findNode" $ do
56 startInfo <- getBootInfo
57 _ <- simpleDHT [] $ do
58 nid <- myNodeIdAccordingTo (read "8.8.8.8:6881")
59 findNodeQ nid startInfo
60 return ()
61
62 it "getPeers" $ do
63 startInfo <- getBootInfo
64 peers <- simpleDHT [] $ do
65 nid <- myNodeIdAccordingTo (read "8.8.8.8:6881")
66
67 -- we should not run getPeers query on boot node, because
68 -- it may not support it
69 Right infos <- findNodeQ nid startInfo
70
71 when (L.null infos) $
72 error "boot node malfunction"
73
74 -- at least one node should reply
75 queryParallel $ do
76 getPeersQ (entryHash (L.head testTorrents)) <$> infos
77
78 peers `shouldSatisfy` (not . L.null)
79
80 it "announce" $ do
81 bootNode <- getBootInfo
82 _ <- simpleDHT [] $ do
83 let ih = entryHash (L.head testTorrents)
84 Right nodes <- findNodeQ ih bootNode
85
86 when (L.null nodes) $
87 error "boot node malfunction"
88
89 queryParallel $ do
90 announceQ ih (nodePort myAddr) <$> nodes
91
92 return ()
93
94 describe "iterative queries" $ do
95 forM_ testTorrents $ \ TestEntry {..} -> do
96 context entryName $ do
97
98 it "get at least 10 unique peers for each infohash" $ do
99 bootNode <- getBootInfo
100 peers <- simpleDHT [] $ do
101 Right startNodes <- findNodeQ entryHash bootNode
102 sourceList [startNodes] $=
103 search entryHash (getPeersQ entryHash) $=
104 CL.concat $$ CL.take 10
105 L.length peers `shouldBe` 10