diff options
Diffstat (limited to 'tests/Main.hs')
-rw-r--r-- | tests/Main.hs | 127 |
1 files changed, 118 insertions, 9 deletions
diff --git a/tests/Main.hs b/tests/Main.hs index ff571b6b..0e18a06b 100644 --- a/tests/Main.hs +++ b/tests/Main.hs | |||
@@ -1,28 +1,35 @@ | |||
1 | {-# LANGUAGE OverloadedStrings #-} | 1 | {-# LANGUAGE StandaloneDeriving #-} |
2 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} | ||
3 | {-# LANGUAGE OverloadedStrings #-} | ||
2 | module Main (main) where | 4 | module Main (main) where |
3 | 5 | ||
4 | import Control.Applicative | 6 | import Control.Applicative |
7 | import Data.ByteString (ByteString) | ||
8 | import qualified Data.ByteString as B | ||
5 | import qualified Data.ByteString.Lazy as Lazy | 9 | import qualified Data.ByteString.Lazy as Lazy |
6 | import Data.IntervalSet | ||
7 | import Data.List as L | 10 | import Data.List as L |
8 | import Data.Ord | 11 | import Data.Ord |
9 | import Data.Maybe | 12 | import Data.Maybe |
10 | import Data.Word | 13 | import Data.Word |
14 | import Data.Serialize as S | ||
11 | import Data.Text as T | 15 | import Data.Text as T |
16 | |||
17 | import Network | ||
12 | import Network.URI | 18 | import Network.URI |
13 | 19 | ||
14 | import Test.Framework (defaultMain) | 20 | import Test.Framework (Test, defaultMain) |
15 | import Test.Framework.Providers.QuickCheck2 (testProperty) | 21 | import Test.Framework.Providers.QuickCheck2 (testProperty) |
16 | import Test.QuickCheck | 22 | import Test.QuickCheck |
17 | 23 | ||
18 | import Data.BEncode | 24 | import Data.BEncode as BE |
19 | import Data.Bitfield as BF | 25 | import Data.Bitfield as BF |
20 | import Data.Torrent | 26 | import Data.Torrent |
21 | import Network.BitTorrent as BT | 27 | import Network.BitTorrent as BT |
22 | 28 | ||
23 | import Debug.Trace | 29 | -- import Debug.Trace |
24 | import Encoding | 30 | |
25 | 31 | ||
32 | data T a = T | ||
26 | 33 | ||
27 | instance Arbitrary URI where | 34 | instance Arbitrary URI where |
28 | arbitrary = pure $ fromJust | 35 | arbitrary = pure $ fromJust |
@@ -90,17 +97,119 @@ instance Arbitrary Torrent where | |||
90 | <*> arbitrary <*> arbitrary <*> arbitrary | 97 | <*> arbitrary <*> arbitrary <*> arbitrary |
91 | <*> arbitrary <*> pure Nothing <*> arbitrary | 98 | <*> arbitrary <*> pure Nothing <*> arbitrary |
92 | 99 | ||
100 | {----------------------------------------------------------------------- | ||
101 | Handshake | ||
102 | -----------------------------------------------------------------------} | ||
103 | |||
104 | instance Arbitrary PeerID where | ||
105 | arbitrary = azureusStyle <$> pure defaultClientID | ||
106 | <*> arbitrary | ||
107 | <*> arbitrary | ||
108 | |||
109 | instance Arbitrary InfoHash where | ||
110 | arbitrary = (hash . B.pack) <$> arbitrary | ||
111 | |||
112 | instance Arbitrary Handshake where | ||
113 | arbitrary = defaultHandshake <$> arbitrary <*> arbitrary | ||
114 | |||
115 | prop_cerealEncoding :: (Serialize a, Eq a) => T a -> [a] -> Bool | ||
116 | prop_cerealEncoding _ msgs = S.decode (S.encode msgs) == Right msgs | ||
117 | |||
118 | {----------------------------------------------------------------------- | ||
119 | Tracker/Scrape | ||
120 | -----------------------------------------------------------------------} | ||
121 | |||
122 | -- | Note that in 6 esample we intensionally do not agree with | ||
123 | -- specification, because taking in account '/' in query parameter | ||
124 | -- seems to be meaningless. (And thats because other clients do not | ||
125 | -- chunk uri by parts) Moreover in practice there should be no | ||
126 | -- difference. (I think so) | ||
127 | -- | ||
128 | test_scrape_url :: [Test] | ||
129 | test_scrape_url = L.zipWith mkTest [1 :: Int ..] (check `L.map` tests) | ||
130 | where | ||
131 | check (iu, ou) = (parseURI iu >>= (`scrapeURL` []) | ||
132 | >>= return . show) == ou | ||
133 | tests = | ||
134 | [ ( "http://example.com/announce" | ||
135 | , Just "http://example.com/scrape") | ||
136 | , ( "http://example.com/x/announce" | ||
137 | , Just "http://example.com/x/scrape") | ||
138 | , ( "http://example.com/announce.php" | ||
139 | , Just "http://example.com/scrape.php") | ||
140 | , ( "http://example.com/a" , Nothing) | ||
141 | , ( "http://example.com/announce?x2%0644" | ||
142 | , Just "http://example.com/scrape?x2%0644") | ||
143 | , ( "http://example.com/announce?x=2/4" | ||
144 | , Just "http://example.com/scrape?x=2/4") | ||
145 | -- , ("http://example.com/announce?x=2/4" , Nothing) -- by specs | ||
146 | , ("http://example.com/x%064announce" , Nothing) | ||
147 | ] | ||
148 | |||
149 | mkTest i = testProperty ("scrape test #" ++ show i) | ||
150 | |||
151 | {----------------------------------------------------------------------- | ||
152 | P2P/message | ||
153 | -----------------------------------------------------------------------} | ||
154 | |||
155 | positive :: Gen Int | ||
156 | positive = fromIntegral <$> (arbitrary :: Gen Word32) | ||
157 | |||
158 | instance Arbitrary ByteString where | ||
159 | arbitrary = B.pack <$> arbitrary | ||
160 | |||
161 | instance Arbitrary BlockIx where | ||
162 | arbitrary = BlockIx <$> positive <*> positive <*> positive | ||
163 | |||
164 | instance Arbitrary Block where | ||
165 | arbitrary = Block <$> positive <*> positive <*> arbitrary | ||
166 | |||
167 | instance Arbitrary Bitfield where | ||
168 | arbitrary = mkBitfield <$> (succ . min 1000 <$> positive) | ||
169 | <*> arbitrary | ||
170 | |||
171 | instance Arbitrary PortNumber where | ||
172 | arbitrary = fromIntegral <$> (arbitrary :: Gen Word16) | ||
173 | |||
174 | instance Arbitrary Message where | ||
175 | arbitrary = oneof | ||
176 | [ pure KeepAlive | ||
177 | , pure Choke | ||
178 | , pure Unchoke | ||
179 | , pure Interested | ||
180 | , pure NotInterested | ||
181 | , Have <$> positive | ||
182 | , Bitfield <$> arbitrary | ||
183 | , Request <$> arbitrary | ||
184 | , Piece <$> arbitrary | ||
185 | , Cancel <$> arbitrary | ||
186 | , Port <$> arbitrary | ||
187 | ] | ||
188 | |||
189 | {----------------------------------------------------------------------- | ||
190 | Main | ||
191 | -----------------------------------------------------------------------} | ||
192 | |||
93 | main :: IO () | 193 | main :: IO () |
94 | main = defaultMain | 194 | main = defaultMain $ |
95 | [ testProperty "completeness range" prop_completenessRange | 195 | [ -- bitfield module |
196 | testProperty "completeness range" prop_completenessRange | ||
96 | , testProperty "rarest in range" prop_rarestInRange | 197 | , testProperty "rarest in range" prop_rarestInRange |
97 | , testProperty "min less that max" prop_minMax | 198 | , testProperty "min less that max" prop_minMax |
98 | , testProperty "difference de morgan" prop_differenceDeMorgan | 199 | , testProperty "difference de morgan" prop_differenceDeMorgan |
99 | 200 | ||
201 | -- torrent module | ||
100 | , testProperty "file info encoding" $ | 202 | , testProperty "file info encoding" $ |
101 | prop_properBEncode (T :: T FileInfo) | 203 | prop_properBEncode (T :: T FileInfo) |
102 | , testProperty "content info encoding" $ | 204 | , testProperty "content info encoding" $ |
103 | prop_properBEncode (T :: T ContentInfo) | 205 | prop_properBEncode (T :: T ContentInfo) |
104 | , testProperty "torrent encoding" $ | 206 | , testProperty "torrent encoding" $ |
105 | prop_properBEncode (T :: T Torrent) | 207 | prop_properBEncode (T :: T Torrent) |
106 | ] | 208 | |
209 | -- handshake module | ||
210 | , testProperty "handshake encoding" $ | ||
211 | prop_cerealEncoding (T :: T Handshake) | ||
212 | , testProperty "message encoding" $ | ||
213 | prop_cerealEncoding (T :: T Message) | ||
214 | |||
215 | ] ++ test_scrape_url | ||