summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--tests/Network/BitTorrent/DHT/RoutingSpec.hs59
1 files changed, 58 insertions, 1 deletions
diff --git a/tests/Network/BitTorrent/DHT/RoutingSpec.hs b/tests/Network/BitTorrent/DHT/RoutingSpec.hs
index e032e27d..a92fec38 100644
--- a/tests/Network/BitTorrent/DHT/RoutingSpec.hs
+++ b/tests/Network/BitTorrent/DHT/RoutingSpec.hs
@@ -1,12 +1,69 @@
1{-# LANGUAGE ScopedTypeVariables #-}
1module Network.BitTorrent.DHT.RoutingSpec (spec) where 2module Network.BitTorrent.DHT.RoutingSpec (spec) where
3import Control.Applicative
4import Control.Monad.State
2import Data.Default 5import Data.Default
6import Data.List as L
7import Data.Maybe
3import Test.Hspec 8import Test.Hspec
9import Test.QuickCheck
4 10
5import Network.BitTorrent.Core 11import Network.BitTorrent.Core
6import Network.BitTorrent.DHT.Routing as T 12import Network.BitTorrent.DHT.Routing as T
7 13
14import Network.BitTorrent.CoreSpec hiding (spec)
15
16
17type Network ip = [NodeAddr ip]
18
19data Env ip = Env
20 { currentTime :: Timestamp
21 , network :: Network ip
22 } deriving Show
23
24type Simulation ip = State (Env ip)
25
26runSimulation :: Eq ip => Env ip -> Routing ip a -> Maybe a
27runSimulation e m = evalState (runRouting ping closest timestamp m) e
28 where
29 ping addr = gets (L.elem addr . network)
30 closest nid = undefined
31 timestamp = gets currentTime
32
33instance Arbitrary ip => Arbitrary (Env ip) where
34 arbitrary = Env <$> arbitrary <*> arbitrary
35
36instance (Arbitrary ip, Eq ip) => Arbitrary (Table ip) where
37 arbitrary = do
38 thisId <- arbitrary
39 bucketN <- choose (1, 20)
40 let table = nullTable thisId bucketN
41
42-- nodeN <- (`mod` bucketN) <$> arbitrary
43-- nodes <- vector nodeN
44
45 node <- arbitrary
46 mt <- runSimulation <$> arbitrary
47 <*> pure (T.insert node table)
48 --(foldM (flip fillTable) table nodes)
49 return (fromJust mt)
50 where
51 fillTable x t = do
52 t' <- T.insert x t
53 return $ if T.full t' then t else t'
54
8spec :: Spec 55spec :: Spec
9spec = do 56spec = do
10 describe "size" $ do 57 describe "size" $ do
11 it "null table is empty" $ do 58 it "null table is empty" $ do
12 T.size (nullTable def 2 :: Table IPv4) `shouldBe` 0 \ No newline at end of file 59 T.size (nullTable def 2 :: Table IPv4) `shouldBe` 0
60
61 it "the same node never appear in different buckets" $ property $ \ t -> do
62 let xss = T.toList (t :: Table Int)
63 let justOnce x = L.length (L.filter (L.elem x) xss) == 1
64 L.all justOnce (L.concat xss)
65
66 it "insert is idemponent" $ property $ \ (e :: Env Int) n t -> do
67 let t1 = runSimulation e (T.insert n t)
68 let t2 = runSimulation e (T.insert n t >>= T.insert n)
69 t1 `shouldBe` t2 \ No newline at end of file