summaryrefslogtreecommitdiff
path: root/tests/Network/BitTorrent/CoreSpec.hs
diff options
context:
space:
mode:
Diffstat (limited to 'tests/Network/BitTorrent/CoreSpec.hs')
-rw-r--r--tests/Network/BitTorrent/CoreSpec.hs308
1 files changed, 301 insertions, 7 deletions
diff --git a/tests/Network/BitTorrent/CoreSpec.hs b/tests/Network/BitTorrent/CoreSpec.hs
index 460c52be..5bf900b2 100644
--- a/tests/Network/BitTorrent/CoreSpec.hs
+++ b/tests/Network/BitTorrent/CoreSpec.hs
@@ -1,11 +1,305 @@
1-- | Re-export modules. 1{-# LANGUAGE FlexibleInstances #-}
2{-# OPTIONS_GHC -fno-warn-orphans #-}
2module Network.BitTorrent.CoreSpec (spec) where 3module Network.BitTorrent.CoreSpec (spec) where
3import Network.BitTorrent.Core.FingerprintSpec as CoreSpec () 4import Control.Applicative
4import Network.BitTorrent.Core.NodeInfoSpec as CoreSpec () 5import Data.BEncode as BE
5import Network.BitTorrent.Core.PeerIdSpec as CoreSpec () 6import Data.ByteString.Lazy as BL
6import Network.BitTorrent.Core.PeerAddrSpec as CoreSpec () 7import Data.IP
8import Data.Serialize as S
9import Data.String
10import Data.Text.Encoding as T
11import Data.Word
12import Network
13import Test.Hspec
14import Test.QuickCheck
15import Test.QuickCheck.Instances ()
7 16
8import Test.Hspec (Spec) 17import Network.BitTorrent.Address
18
19
20instance Arbitrary IPv4 where
21 arbitrary = do
22 a <- choose (0, 255)
23 b <- choose (0, 255)
24 c <- choose (0, 255)
25 d <- choose (0, 255)
26 return $ toIPv4 [a, b, c, d]
27
28instance Arbitrary IPv6 where
29 arbitrary = do
30 a <- choose (0, fromIntegral (maxBound :: Word16))
31 b <- choose (0, fromIntegral (maxBound :: Word16))
32 c <- choose (0, fromIntegral (maxBound :: Word16))
33 d <- choose (0, fromIntegral (maxBound :: Word16))
34 e <- choose (0, fromIntegral (maxBound :: Word16))
35 f <- choose (0, fromIntegral (maxBound :: Word16))
36 g <- choose (0, fromIntegral (maxBound :: Word16))
37 h <- choose (0, fromIntegral (maxBound :: Word16))
38 return $ toIPv6 [a, b, c, d, e, f, g, h]
39
40instance Arbitrary IP where
41 arbitrary = frequency
42 [ (1, IPv4 <$> arbitrary)
43 , (1, IPv6 <$> arbitrary)
44 ]
45
46instance Arbitrary PortNumber where
47 arbitrary = fromIntegral <$> (arbitrary :: Gen Word16)
48
49instance Arbitrary PeerId where
50 arbitrary = oneof
51 [ azureusStyle defaultClientId defaultVersionNumber
52 <$> (T.encodeUtf8 <$> arbitrary)
53 , shadowStyle 'X' defaultVersionNumber
54 <$> (T.encodeUtf8 <$> arbitrary)
55 ]
56
57instance Arbitrary a => Arbitrary (PeerAddr a) where
58 arbitrary = PeerAddr <$> arbitrary <*> arbitrary <*> arbitrary
59
60instance Arbitrary NodeId where
61 arbitrary = fromString <$> vector 20
62
63instance Arbitrary a => Arbitrary (NodeAddr a) where
64 arbitrary = NodeAddr <$> arbitrary <*> arbitrary
65
66instance Arbitrary a => Arbitrary (NodeInfo a) where
67 arbitrary = NodeInfo <$> arbitrary <*> arbitrary
9 68
10spec :: Spec 69spec :: Spec
11spec = return () \ No newline at end of file 70spec = do
71 describe "PeerId" $ do
72 it "properly bencoded" $ do
73 BE.decode "20:01234567890123456789"
74 `shouldBe` Right ("01234567890123456789" :: PeerId)
75
76 describe "PortNumber" $ do
77 it "properly serialized" $ do
78 S.decode "\x1\x2" `shouldBe` Right (258 :: PortNumber)
79 S.encode (258 :: PortNumber) `shouldBe` "\x1\x2"
80
81 it "properly bencoded" $ do
82 BE.decode "i80e" `shouldBe` Right (80 :: PortNumber)
83
84 it "fail if port number is invalid" $ do
85 (BE.decode "i-10e" :: BE.Result PortNumber)
86 `shouldBe`
87 Left "fromBEncode: unable to decode PortNumber: -10"
88
89 (BE.decode "i70000e" :: BE.Result PortNumber)
90 `shouldBe`
91 Left "fromBEncode: unable to decode PortNumber: 70000"
92
93 describe "Peer IPv4" $ do
94 it "properly serialized" $ do
95 S.decode "\x1\x2\x3\x4" `shouldBe` Right (toIPv4 [1, 2, 3, 4])
96 S.encode (toIPv4 [1, 2, 3, 4]) `shouldBe` "\x1\x2\x3\x4"
97
98 it "properly serialized (iso)" $ property $ \ ip -> do
99 S.decode (S.encode ip) `shouldBe` Right (ip :: IPv4)
100
101 it "properly bencoded" $ do
102 BE.decode "11:168.192.0.1" `shouldBe` Right (toIPv4 [168, 192, 0, 1])
103 BE.encode (toIPv4 [168, 192, 0, 1]) `shouldBe` "11:168.192.0.1"
104
105 it "properly bencoded (iso)" $ property $ \ ip ->
106 BE.decode (BL.toStrict (BE.encode ip)) `shouldBe` Right (ip :: IPv4)
107
108 it "fail gracefully on invalid strings" $ do
109 BE.decode "3:1.1" `shouldBe`
110 (Left "fromBEncode: unable to decode IP: 1.1" :: BE.Result IPv4)
111
112 it "fail gracefully on invalid bencode" $ do
113 BE.decode "i10e" `shouldBe`
114 (Left "fromBEncode: unable to decode IP: addr should be a bstring"
115 :: BE.Result IPv4)
116
117 describe "Peer IPv6" $ do
118 it "properly serialized" $ do
119 S.decode "\x1\x2\x3\x4\x5\x6\x7\x8\x9\xa\xb\xc\xd\xe\xf\x10"
120 `shouldBe`
121 Right ("102:304:506:708:90a:b0c:d0e:f10" :: IPv6)
122
123 S.encode ("102:304:506:708:90a:b0c:d0e:f10" :: IPv6)
124 `shouldBe`
125 "\x1\x2\x3\x4\x5\x6\x7\x8\x9\xa\xb\xc\xd\xe\xf\x10"
126
127 it "properly serialized (iso)" $ property $ \ ip ->
128 S.decode (S.encode ip) `shouldBe` Right (ip :: IPv6)
129
130 it "properly bencoded" $ do
131 BE.decode "3:::1" `shouldBe` Right (toIPv6 [0, 0, 0, 0, 0, 0, 0, 1])
132 BE.encode (toIPv6 [0, 0, 0, 0, 0, 0, 0, 1]) `shouldBe`
133 "23:00:00:00:00:00:00:00:01"
134
135 BE.decode "23:00:00:00:00:00:00:00:01"
136 `shouldBe`
137 Right (toIPv6 [0, 0, 0, 0, 0, 0, 0, 1])
138
139 it "properly bencoded iso" $ property $ \ ip ->
140 BE.decode (BL.toStrict (BE.encode ip)) `shouldBe` Right (ip :: IPv4)
141
142 it "fail gracefully on invalid strings" $ do
143 BE.decode "4:g::1" `shouldBe`
144 (Left "fromBEncode: unable to decode IP: g::1" :: BE.Result IPv6)
145
146 it "fail gracefully on invalid bencode" $ do
147 BE.decode "i10e" `shouldBe`
148 (Left "fromBEncode: unable to decode IP: addr should be a bstring"
149 :: BE.Result IPv6)
150
151
152 describe "Peer IP" $ do
153 it "properly serialized IPv6" $ do
154 S.decode "\x1\x2\x3\x4\x5\x6\x7\x8\x9\xa\xb\xc\xd\xe\xf\x10"
155 `shouldBe`
156 Right ("102:304:506:708:90a:b0c:d0e:f10" :: IP)
157
158 S.encode ("102:304:506:708:90a:b0c:d0e:f10" :: IP)
159 `shouldBe`
160 "\x1\x2\x3\x4\x5\x6\x7\x8\x9\xa\xb\xc\xd\xe\xf\x10"
161
162 it "properly serialized (iso) IPv6" $ property $ \ ip ->
163 S.decode (S.encode ip) `shouldBe` Right (ip :: IP)
164
165 it "properly serialized IPv4" $ do
166 S.decode "\x1\x2\x3\x4" `shouldBe` Right (IPv4 $ toIPv4 [1, 2, 3, 4])
167 S.encode (toIPv4 [1, 2, 3, 4]) `shouldBe` "\x1\x2\x3\x4"
168
169 it "properly serialized (iso) IPv4" $ property $ \ ip -> do
170 S.decode (S.encode ip) `shouldBe` Right (ip :: IP)
171
172 it "properly bencoded" $ do
173 BE.decode "11:168.192.0.1" `shouldBe`
174 Right (IPv4 (toIPv4 [168, 192, 0, 1]))
175
176 BE.decode "3:::1" `shouldBe` Right
177 (IPv6 (toIPv6 [0, 0, 0, 0, 0, 0, 0, 1]))
178
179 BE.encode (IPv6 (toIPv6 [0, 0, 0, 0, 0, 0, 0, 1])) `shouldBe`
180 "23:00:00:00:00:00:00:00:01"
181
182 BE.decode "23:00:00:00:00:00:00:00:01"
183 `shouldBe`
184 Right (IPv6 (toIPv6 [0, 0, 0, 0, 0, 0, 0, 1]))
185
186 it "properly bencoded iso" $ property $ \ ip ->
187 BE.decode (BL.toStrict (BE.encode ip)) `shouldBe` Right (ip :: IP)
188
189 it "fail gracefully on invalid strings" $ do
190 BE.decode "4:g::1" `shouldBe`
191 (Left "fromBEncode: unable to decode IP: g::1" :: BE.Result IP)
192
193 it "fail gracefully on invalid bencode" $ do
194 BE.decode "i10e" `shouldBe`
195 (Left "fromBEncode: unable to decode IP: addr should be a bstring"
196 :: BE.Result IP)
197
198 describe "PeerAddr" $ do
199 it "IsString" $ do
200 ("127.0.0.1:80" :: PeerAddr IP)
201 `shouldBe` PeerAddr Nothing "127.0.0.1" 80
202
203 ("127.0.0.1:80" :: PeerAddr IPv4)
204 `shouldBe` PeerAddr Nothing "127.0.0.1" 80
205
206 ("[::1]:80" :: PeerAddr IP)
207 `shouldBe` PeerAddr Nothing "::1" 80
208
209 ("[::1]:80" :: PeerAddr IPv6)
210 `shouldBe` PeerAddr Nothing "::1" 80
211
212 it "properly bencoded (iso)" $ property $ \ addr ->
213 BE.decode (BL.toStrict (BE.encode addr))
214 `shouldBe` Right (addr :: PeerAddr IP)
215
216
217 it "properly bencoded (ipv4)" $ do
218 BE.decode "d2:ip11:168.192.0.1\
219 \7:peer id20:01234567890123456789\
220 \4:porti6881e\
221 \e"
222 `shouldBe`
223 Right (PeerAddr (Just "01234567890123456789")
224 (IPv4 (toIPv4 [168, 192, 0, 1]))
225 6881)
226
227 it "properly bencoded (ipv6)" $ do
228 BE.decode "d2:ip3:::1\
229 \7:peer id20:01234567890123456789\
230 \4:porti6881e\
231 \e"
232 `shouldBe`
233 Right (PeerAddr (Just "01234567890123456789")
234 (IPv6 (toIPv6 [0, 0, 0, 0, 0, 0, 0, 1]))
235 6881)
236
237 it "peer id is optional" $ do
238 BE.decode "d2:ip11:168.192.0.1\
239 \4:porti6881e\
240 \e"
241 `shouldBe`
242 Right (PeerAddr Nothing (IPv4 (toIPv4 [168, 192, 0, 1])) 6881)
243
244 it "has sock addr for both ipv4 and ipv6" $ do
245 show (peerSockAddr "128.0.0.1:80") `shouldBe` "128.0.0.1:80"
246 show (peerSockAddr "[::1]:8080" ) `shouldBe` "[::1]:8080"
247
248 describe "NodeId" $ do
249 it "properly serialized" $ do
250 S.decode "mnopqrstuvwxyz123456"
251 `shouldBe` Right ("mnopqrstuvwxyz123456" :: NodeId)
252
253 S.encode ("mnopqrstuvwxyz123456" :: NodeId)
254 `shouldBe` "mnopqrstuvwxyz123456"
255
256 it "properly serialized (iso)" $ property $ \ nid ->
257 S.decode (S.encode nid) `shouldBe`
258 Right (nid :: NodeId)
259
260 describe "NodeAddr" $ do
261 it "properly serialized" $ do
262 S.decode "\127\0\0\1\1\2" `shouldBe`
263 Right ("127.0.0.1:258" :: NodeAddr IPv4)
264
265 it "properly serialized (iso)" $ property $ \ nid ->
266 S.decode (S.encode nid) `shouldBe`
267 Right (nid :: NodeAddr IPv4)
268
269 describe "NodeInfo" $ do
270 it "properly serialized" $ do
271 S.decode "mnopqrstuvwxyz123456\
272 \\127\0\0\1\1\2" `shouldBe` Right
273 (NodeInfo "mnopqrstuvwxyz123456" "127.0.0.1:258" :: NodeInfo IPv4)
274
275 it "properly serialized (iso)" $ property $ \ nid ->
276 S.decode (S.encode nid) `shouldBe`
277 Right (nid :: NodeInfo IPv4)
278
279 -- see <http://bittorrent.org/beps/bep_0020.html>
280 describe "Fingerprint" $ do
281 it "decode mainline encoded peer id" $ do
282 fingerprint "M4-3-6--xxxxxxxxxxxx" `shouldBe` "Mainline-4.3.6"
283 fingerprint "M4-20-8-xxxxxxxxxxxx" `shouldBe` "Mainline-4.20.8"
284
285 it "decode azureus encoded peer id" $ do
286 fingerprint "-AZ2060-xxxxxxxxxxxx" `shouldBe` "Azureus-2060"
287 fingerprint "-BS0000-xxxxxxxxxxxx" `shouldBe` "BTSlave-0"
288
289 it "decode Shad0w style peer id" $ do
290 fingerprint "S58B-----xxxxxxxxxxx" `shouldBe` "Shadow-5.8.11"
291 fingerprint "T58B-----xxxxxxxxxxx" `shouldBe` "BitTornado-5.8.11"
292
293 it "decode bitcomet style peer id" $ do
294 fingerprint "exbc01xxxxxxxxxxxxxx" `shouldBe` "BitComet-48.49"
295 fingerprint "FUTB01xxxxxxxxxxxxxx" `shouldBe` "BitComet-48.49"
296 fingerprint "exbc01LORDxxxxxxxxxx" `shouldBe` "BitLord-48.49"
297
298 it "decode opera style peer id" $ do
299 fingerprint "OP0123xxxxxxxxxxxxxx" `shouldBe` "Opera-123"
300
301 it "decode ML donkey style peer id" $ do
302 fingerprint "-ML2.7.2-xxxxxxxxxxx" `shouldBe` "MLdonkey-0"
303
304-- TODO XBT, Bits on Wheels, Queen Bee, BitTyrant, TorrenTopia,
305-- BitSpirit, Rufus, G3 Torrent, FlashGet \ No newline at end of file