summaryrefslogtreecommitdiff
path: root/tests/Network/BitTorrent/DHT/TokenSpec.hs
diff options
context:
space:
mode:
Diffstat (limited to 'tests/Network/BitTorrent/DHT/TokenSpec.hs')
-rw-r--r--tests/Network/BitTorrent/DHT/TokenSpec.hs32
1 files changed, 30 insertions, 2 deletions
diff --git a/tests/Network/BitTorrent/DHT/TokenSpec.hs b/tests/Network/BitTorrent/DHT/TokenSpec.hs
index 90ff0f03..6353a24c 100644
--- a/tests/Network/BitTorrent/DHT/TokenSpec.hs
+++ b/tests/Network/BitTorrent/DHT/TokenSpec.hs
@@ -1,14 +1,42 @@
1{-# LANGUAGE ScopedTypeVariables #-}
1{-# OPTIONS_GHC -fno-warn-orphans #-} 2{-# OPTIONS_GHC -fno-warn-orphans #-}
2module Network.BitTorrent.DHT.TokenSpec (spec) where 3module Network.BitTorrent.DHT.TokenSpec (spec) where
3import Control.Applicative 4import Control.Applicative
5import Data.List as L
4import Data.String 6import Data.String
5import Test.Hspec 7import Test.Hspec
6import Test.QuickCheck 8import Test.QuickCheck
7import Network.BitTorrent.DHT.Token 9
10import Network.BitTorrent.Core
11import Network.BitTorrent.CoreSpec ()
12import Network.BitTorrent.DHT.Token as T
8 13
9 14
10instance Arbitrary Token where 15instance Arbitrary Token where
11 arbitrary = fromString <$> arbitrary 16 arbitrary = fromString <$> arbitrary
12 17
18instance Arbitrary TokenMap where
19 arbitrary = tokens <$> arbitrary
20
21repeatN :: Int -> (a -> a) -> (a -> a)
22repeatN n f = L.foldr (.) id $ L.replicate n f
23
13spec :: Spec 24spec :: Spec
14spec = return () \ No newline at end of file 25spec = do
26 describe "Token" $ do
27 return ()
28
29 describe "TokenMap" $ do
30 it "is keeping any granted token in current session" $
31 property $ \ (addr :: NodeAddr IPv4) m ->
32 T.member addr (T.lookup addr m) m
33
34 it "is keeping any granted token in next session" $
35 property $ \ (addr :: NodeAddr IPv4) m ->
36 T.member addr (T.lookup addr m) (T.update m)
37
38 -- can fail with some small probability
39 it "is rejecting any outdated tokens" $
40 property $ \ (addr :: NodeAddr IPv4) m k -> not $
41 let n = min 100 (abs k + 2) in
42 T.member addr (T.lookup addr m) (repeatN n T.update m) \ No newline at end of file