diff options
Diffstat (limited to 'tests/Network/BitTorrent')
-rw-r--r-- | tests/Network/BitTorrent/DHT/QuerySpec.hs | 108 |
1 files changed, 108 insertions, 0 deletions
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 #-} | ||
2 | module Network.BitTorrent.DHT.QuerySpec (spec) where | ||
3 | import Control.Applicative | ||
4 | import Control.Exception | ||
5 | import Control.Monad.Reader | ||
6 | import Data.Conduit as C | ||
7 | import Data.Conduit.List as CL | ||
8 | import Data.Default | ||
9 | import Data.List as L | ||
10 | import Test.Hspec | ||
11 | |||
12 | import Network.BitTorrent.Core | ||
13 | import Network.BitTorrent.DHT | ||
14 | import Network.BitTorrent.DHT.Session | ||
15 | import Network.BitTorrent.DHT.Query | ||
16 | |||
17 | import Network.BitTorrent.DHT.TestData | ||
18 | |||
19 | |||
20 | myAddr :: NodeAddr IPv4 | ||
21 | myAddr = "0.0.0.0:8000" | ||
22 | |||
23 | nullLogger :: LogFun | ||
24 | nullLogger _ _ _ _ = return () | ||
25 | |||
26 | --simpleLogger :: LogFun | ||
27 | --simpleLogger _ t _ _ = print t | ||
28 | |||
29 | simpleDHT :: [NodeHandler IPv4] -> DHT IPv4 a -> IO a | ||
30 | simpleDHT hs m = | ||
31 | bracket (startNode hs def myAddr nullLogger) stopNode $ \ node -> | ||
32 | runDHT node m | ||
33 | |||
34 | getBootInfo :: IO (NodeInfo IPv4) | ||
35 | getBootInfo = do | ||
36 | startAddr <- resolveHostName (L.head defaultBootstrapNodes) | ||
37 | simpleDHT [] $ pingQ startAddr | ||
38 | |||
39 | spec :: Spec | ||
40 | spec = 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 | ||