diff options
author | Sam T <pxqr.sta@gmail.com> | 2013-05-03 11:33:48 +0400 |
---|---|---|
committer | Sam T <pxqr.sta@gmail.com> | 2013-05-03 11:33:48 +0400 |
commit | 2c79ab203d8be419cff936e306722cf47625472b (patch) | |
tree | 13059022f5b5eb833fa4cd53ce8703a497484cef /tests/Encoding.hs | |
parent | 26867c91679ecf0c93ecde1cf4eb142041580f92 (diff) |
+ Add initial tests for bitfields.
Diffstat (limited to 'tests/Encoding.hs')
-rw-r--r-- | tests/Encoding.hs | 86 |
1 files changed, 86 insertions, 0 deletions
diff --git a/tests/Encoding.hs b/tests/Encoding.hs new file mode 100644 index 00000000..bd452975 --- /dev/null +++ b/tests/Encoding.hs | |||
@@ -0,0 +1,86 @@ | |||
1 | {-# LANGUAGE StandaloneDeriving #-} | ||
2 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} | ||
3 | {-# OPTIONS -fno-warn-orphans #-} | ||
4 | module Encoding where | ||
5 | |||
6 | import Control.Applicative | ||
7 | import Data.Word | ||
8 | import Data.ByteString (ByteString) | ||
9 | import qualified Data.ByteString as B | ||
10 | import Data.Serialize | ||
11 | import Test.Framework (Test) | ||
12 | import Test.Framework.Providers.QuickCheck2 (testProperty) | ||
13 | import Test.QuickCheck | ||
14 | |||
15 | import Network.URI | ||
16 | |||
17 | import Data.Torrent | ||
18 | import Network.BitTorrent | ||
19 | |||
20 | |||
21 | positive :: Gen Int | ||
22 | positive = fromIntegral <$> (arbitrary :: Gen Word32) | ||
23 | |||
24 | instance Arbitrary ByteString where | ||
25 | arbitrary = B.pack <$> arbitrary | ||
26 | |||
27 | instance Arbitrary BlockIx where | ||
28 | arbitrary = BlockIx <$> positive <*> positive <*> positive | ||
29 | |||
30 | instance Arbitrary Block where | ||
31 | arbitrary = Block <$> positive <*> positive <*> arbitrary | ||
32 | |||
33 | deriving instance Arbitrary Bitfield | ||
34 | |||
35 | instance Arbitrary Message where | ||
36 | arbitrary = oneof | ||
37 | [ pure KeepAlive | ||
38 | , pure Choke | ||
39 | , pure Unchoke | ||
40 | , pure Interested | ||
41 | , pure NotInterested | ||
42 | , Have <$> positive | ||
43 | , Bitfield <$> arbitrary | ||
44 | , Request <$> arbitrary | ||
45 | , Piece <$> arbitrary | ||
46 | , Cancel <$> arbitrary | ||
47 | , Port <$> choose (0, fromIntegral (maxBound :: Word16)) | ||
48 | ] | ||
49 | |||
50 | instance Arbitrary PeerID where | ||
51 | arbitrary = azureusStyle <$> pure defaultClientID | ||
52 | <*> arbitrary | ||
53 | <*> arbitrary | ||
54 | |||
55 | instance Arbitrary InfoHash where | ||
56 | arbitrary = (hash . B.pack) <$> arbitrary | ||
57 | |||
58 | instance Arbitrary Handshake where | ||
59 | arbitrary = defaultHandshake <$> arbitrary <*> arbitrary | ||
60 | |||
61 | data T a = T | ||
62 | |||
63 | prop_encoding :: (Serialize a, Eq a) => T a -> [a] -> Bool | ||
64 | prop_encoding _ msgs = decode (encode msgs) == Right msgs | ||
65 | |||
66 | -- | Note that in 6 esample we intensionally do not agree with specification, | ||
67 | -- because taking in account '/' in query parameter seems to be meaningless. | ||
68 | -- (And thats because other clients do not chunk uri by parts) | ||
69 | -- Moreover in practice there should be no difference. (I hope) | ||
70 | -- | ||
71 | test_scrape_url :: [Test] | ||
72 | test_scrape_url = zipWith mkTest [1 :: Int ..] (check `map` tests) | ||
73 | where | ||
74 | check (iu, ou) = (parseURI iu >>= (`scrapeURL` []) >>= return . show) == ou | ||
75 | tests = | ||
76 | [ ("http://example.com/announce" , Just "http://example.com/scrape") | ||
77 | , ("http://example.com/x/announce" , Just "http://example.com/x/scrape") | ||
78 | , ("http://example.com/announce.php" , Just "http://example.com/scrape.php") | ||
79 | , ("http://example.com/a" , Nothing) | ||
80 | , ("http://example.com/announce?x2%0644", Just "http://example.com/scrape?x2%0644") | ||
81 | , ("http://example.com/announce?x=2/4" , Just "http://example.com/scrape?x=2/4") | ||
82 | -- , ("http://example.com/announce?x=2/4" , Nothing) -- by specs | ||
83 | , ("http://example.com/x%064announce" , Nothing) | ||
84 | ] | ||
85 | |||
86 | mkTest i = testProperty ("scrape test #" ++ show i) | ||