summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--bittorrent.cabal1
-rw-r--r--tests/Network/BitTorrent/DHT/QuerySpec.hs108
2 files changed, 109 insertions, 0 deletions
diff --git a/bittorrent.cabal b/bittorrent.cabal
index 22edb008..2db94105 100644
--- a/bittorrent.cabal
+++ b/bittorrent.cabal
@@ -196,6 +196,7 @@ test-suite spec
196 Network.BitTorrent.DHTSpec 196 Network.BitTorrent.DHTSpec
197 Network.BitTorrent.DHT.TestData 197 Network.BitTorrent.DHT.TestData
198 Network.BitTorrent.DHT.MessageSpec 198 Network.BitTorrent.DHT.MessageSpec
199 Network.BitTorrent.DHT.QuerySpec
199 Network.BitTorrent.DHT.RoutingSpec 200 Network.BitTorrent.DHT.RoutingSpec
200 Network.BitTorrent.DHT.SessionSpec 201 Network.BitTorrent.DHT.SessionSpec
201 Network.BitTorrent.DHT.TokenSpec 202 Network.BitTorrent.DHT.TokenSpec
diff --git a/tests/Network/BitTorrent/DHT/QuerySpec.hs b/tests/Network/BitTorrent/DHT/QuerySpec.hs
new file mode 100644
index 00000000..1bca477f
--- /dev/null
+++ b/tests/Network/BitTorrent/DHT/QuerySpec.hs
@@ -0,0 +1,108 @@
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.Core
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:8000"
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 (startNode hs def myAddr nullLogger) stopNode $ \ node ->
32 runDHT node m
33
34getBootInfo :: IO (NodeInfo IPv4)
35getBootInfo = do
36 startAddr <- resolveHostName (L.head defaultBootstrapNodes)
37 simpleDHT [] $ pingQ startAddr
38
39spec :: Spec
40spec = 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 <- asks thisNodeId
59 findNodeQ nid startInfo
60 return ()
61
62 it "getPeers" $ do
63 startInfo <- getBootInfo
64 peers <- simpleDHT [] $ do
65 nid <- asks thisNodeId
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 nid <- asks thisNodeId
84 Right nodes <- findNodeQ nid bootNode
85
86 when (L.null nodes) $
87 error "boot node malfunction"
88
89 let ih = entryHash (L.head testTorrents)
90 let port = nodePort myAddr
91 queryParallel $ do
92 announceQ ih port <$> nodes
93
94 return ()
95
96 describe "iterative queries" $ do
97 forM_ testTorrents $ \ TestEntry {..} -> do
98 context entryName $ do
99
100 it "get at least 10 unique peers for each infohash" $ do
101 bootNode <- getBootInfo
102 peers <- simpleDHT [] $ do
103 nid <- asks thisNodeId
104 Right startNodes <- findNodeQ nid bootNode
105 sourceList [startNodes] $=
106 search entryHash (getPeersQ entryHash) $=
107 CL.concat $$ CL.take 10
108 L.length peers `shouldBe` 10 \ No newline at end of file