diff options
Diffstat (limited to 'tests/Network/BitTorrent/Core/PeerAddrSpec.hs')
-rw-r--r-- | tests/Network/BitTorrent/Core/PeerAddrSpec.hs | 202 |
1 files changed, 202 insertions, 0 deletions
diff --git a/tests/Network/BitTorrent/Core/PeerAddrSpec.hs b/tests/Network/BitTorrent/Core/PeerAddrSpec.hs new file mode 100644 index 00000000..e5850998 --- /dev/null +++ b/tests/Network/BitTorrent/Core/PeerAddrSpec.hs | |||
@@ -0,0 +1,202 @@ | |||
1 | {-# LANGUAGE FlexibleInstances #-} | ||
2 | {-# OPTIONS_GHC -fno-warn-orphans #-} | ||
3 | module Network.BitTorrent.Core.PeerAddrSpec (spec) where | ||
4 | import Control.Applicative | ||
5 | import Data.BEncode as BE | ||
6 | import Data.ByteString.Lazy as BL | ||
7 | import Data.IP | ||
8 | import Data.Serialize as S | ||
9 | import Data.Word | ||
10 | import Network | ||
11 | import Test.Hspec | ||
12 | import Test.QuickCheck | ||
13 | |||
14 | import Network.BitTorrent.Core.PeerIdSpec hiding (spec) | ||
15 | import Network.BitTorrent.Core.PeerAddr | ||
16 | |||
17 | instance Arbitrary IPv4 where | ||
18 | arbitrary = do | ||
19 | a <- choose (0, 255) | ||
20 | b <- choose (0, 255) | ||
21 | c <- choose (0, 255) | ||
22 | d <- choose (0, 255) | ||
23 | return $ toIPv4 [a, b, c, d] | ||
24 | |||
25 | instance Arbitrary IPv6 where | ||
26 | arbitrary = do | ||
27 | a <- choose (0, fromIntegral (maxBound :: Word16)) | ||
28 | b <- choose (0, fromIntegral (maxBound :: Word16)) | ||
29 | c <- choose (0, fromIntegral (maxBound :: Word16)) | ||
30 | d <- choose (0, fromIntegral (maxBound :: Word16)) | ||
31 | e <- choose (0, fromIntegral (maxBound :: Word16)) | ||
32 | f <- choose (0, fromIntegral (maxBound :: Word16)) | ||
33 | g <- choose (0, fromIntegral (maxBound :: Word16)) | ||
34 | h <- choose (0, fromIntegral (maxBound :: Word16)) | ||
35 | return $ toIPv6 [a, b, c, d, e, f, g, h] | ||
36 | |||
37 | instance Arbitrary IP where | ||
38 | arbitrary = frequency | ||
39 | [ (1, IPv4 <$> arbitrary) | ||
40 | , (1, IPv6 <$> arbitrary) | ||
41 | ] | ||
42 | |||
43 | instance Arbitrary PortNumber where | ||
44 | arbitrary = fromIntegral <$> (arbitrary :: Gen Word16) | ||
45 | |||
46 | instance Arbitrary a => Arbitrary (PeerAddr a) where | ||
47 | arbitrary = PeerAddr <$> arbitrary <*> arbitrary <*> arbitrary | ||
48 | |||
49 | spec :: Spec | ||
50 | spec = do | ||
51 | describe "PortNumber" $ do | ||
52 | it "properly serialized" $ do | ||
53 | S.decode "\x1\x2" `shouldBe` Right (258 :: PortNumber) | ||
54 | S.encode (258 :: PortNumber) `shouldBe` "\x1\x2" | ||
55 | |||
56 | it "properly bencoded" $ do | ||
57 | BE.decode "i80e" `shouldBe` Right (80 :: PortNumber) | ||
58 | |||
59 | it "fail if port number is invalid" $ do | ||
60 | (BE.decode "i-10e" :: BE.Result PortNumber) | ||
61 | `shouldBe` | ||
62 | Left "fromBEncode: unable to decode PortNumber: -10" | ||
63 | |||
64 | (BE.decode "i70000e" :: BE.Result PortNumber) | ||
65 | `shouldBe` | ||
66 | Left "fromBEncode: unable to decode PortNumber: 70000" | ||
67 | |||
68 | describe "Peer IPv4" $ do | ||
69 | it "properly serialized" $ do | ||
70 | S.decode "\x1\x2\x3\x4" `shouldBe` Right (toIPv4 [1, 2, 3, 4]) | ||
71 | S.encode (toIPv4 [1, 2, 3, 4]) `shouldBe` "\x1\x2\x3\x4" | ||
72 | |||
73 | it "properly serialized (iso)" $ property $ \ ip -> do | ||
74 | S.decode (S.encode ip) `shouldBe` Right (ip :: IPv4) | ||
75 | |||
76 | it "properly bencoded" $ do | ||
77 | BE.decode "11:168.192.0.1" `shouldBe` Right (toIPv4 [168, 192, 0, 1]) | ||
78 | BE.encode (toIPv4 [168, 192, 0, 1]) `shouldBe` "11:168.192.0.1" | ||
79 | |||
80 | it "properly bencoded (iso)" $ property $ \ ip -> | ||
81 | BE.decode (BL.toStrict (BE.encode ip)) `shouldBe` Right (ip :: IPv4) | ||
82 | |||
83 | it "fail gracefully on invalid strings" $ do | ||
84 | BE.decode "3:1.1" `shouldBe` | ||
85 | (Left "fromBEncode: unable to decode IP: 1.1" :: BE.Result IPv4) | ||
86 | |||
87 | it "fail gracefully on invalid bencode" $ do | ||
88 | BE.decode "i10e" `shouldBe` | ||
89 | (Left "fromBEncode: unable to decode IP: addr should be a bstring" | ||
90 | :: BE.Result IPv4) | ||
91 | |||
92 | describe "Peer IPv6" $ do | ||
93 | it "properly serialized" $ do | ||
94 | S.decode "\x1\x2\x3\x4\x5\x6\x7\x8\x9\xa\xb\xc\xd\xe\xf\x10" | ||
95 | `shouldBe` | ||
96 | Right ("102:304:506:708:90a:b0c:d0e:f10" :: IPv6) | ||
97 | |||
98 | S.encode ("102:304:506:708:90a:b0c:d0e:f10" :: IPv6) | ||
99 | `shouldBe` | ||
100 | "\x1\x2\x3\x4\x5\x6\x7\x8\x9\xa\xb\xc\xd\xe\xf\x10" | ||
101 | |||
102 | it "properly serialized iso" $ property $ \ ip -> | ||
103 | S.decode (S.encode ip) `shouldBe` Right (ip :: IPv6) | ||
104 | |||
105 | it "properly bencoded" $ do | ||
106 | BE.decode "3:::1" `shouldBe` Right (toIPv6 [0, 0, 0, 0, 0, 0, 0, 1]) | ||
107 | BE.encode (toIPv6 [0, 0, 0, 0, 0, 0, 0, 1]) `shouldBe` | ||
108 | "23:00:00:00:00:00:00:00:01" | ||
109 | |||
110 | BE.decode "23:00:00:00:00:00:00:00:01" | ||
111 | `shouldBe` | ||
112 | Right (toIPv6 [0, 0, 0, 0, 0, 0, 0, 1]) | ||
113 | |||
114 | it "properly bencoded iso" $ property $ \ ip -> | ||
115 | BE.decode (BL.toStrict (BE.encode ip)) `shouldBe` Right (ip :: IPv4) | ||
116 | |||
117 | it "fail gracefully on invalid strings" $ do | ||
118 | BE.decode "4:g::1" `shouldBe` | ||
119 | (Left "fromBEncode: unable to decode IP: g::1" :: BE.Result IPv6) | ||
120 | |||
121 | it "fail gracefully on invalid bencode" $ do | ||
122 | BE.decode "i10e" `shouldBe` | ||
123 | (Left "fromBEncode: unable to decode IP: addr should be a bstring" | ||
124 | :: BE.Result IPv6) | ||
125 | |||
126 | |||
127 | describe "Peer IP" $ do | ||
128 | it "properly bencoded" $ do | ||
129 | BE.decode "11:168.192.0.1" `shouldBe` | ||
130 | Right (IPv4 (toIPv4 [168, 192, 0, 1])) | ||
131 | |||
132 | BE.decode "3:::1" `shouldBe` Right | ||
133 | (IPv6 (toIPv6 [0, 0, 0, 0, 0, 0, 0, 1])) | ||
134 | |||
135 | BE.encode (IPv6 (toIPv6 [0, 0, 0, 0, 0, 0, 0, 1])) `shouldBe` | ||
136 | "23:00:00:00:00:00:00:00:01" | ||
137 | |||
138 | BE.decode "23:00:00:00:00:00:00:00:01" | ||
139 | `shouldBe` | ||
140 | Right (IPv6 (toIPv6 [0, 0, 0, 0, 0, 0, 0, 1])) | ||
141 | |||
142 | it "properly bencoded iso" $ property $ \ ip -> | ||
143 | BE.decode (BL.toStrict (BE.encode ip)) `shouldBe` Right (ip :: IP) | ||
144 | |||
145 | it "fail gracefully on invalid strings" $ do | ||
146 | BE.decode "4:g::1" `shouldBe` | ||
147 | (Left "fromBEncode: unable to decode IP: g::1" :: BE.Result IP) | ||
148 | |||
149 | it "fail gracefully on invalid bencode" $ do | ||
150 | BE.decode "i10e" `shouldBe` | ||
151 | (Left "fromBEncode: unable to decode IP: addr should be a bstring" | ||
152 | :: BE.Result IP) | ||
153 | |||
154 | describe "PeerAddr" $ do | ||
155 | it "IsString" $ do | ||
156 | ("127.0.0.1:80" :: PeerAddr IP) | ||
157 | `shouldBe` PeerAddr Nothing "127.0.0.1" 80 | ||
158 | |||
159 | ("127.0.0.1:80" :: PeerAddr IPv4) | ||
160 | `shouldBe` PeerAddr Nothing "127.0.0.1" 80 | ||
161 | |||
162 | ("[::1]:80" :: PeerAddr IP) | ||
163 | `shouldBe` PeerAddr Nothing "::1" 80 | ||
164 | |||
165 | ("[::1]:80" :: PeerAddr IPv6) | ||
166 | `shouldBe` PeerAddr Nothing "::1" 80 | ||
167 | |||
168 | it "properly bencoded (iso)" $ property $ \ addr -> | ||
169 | BE.decode (BL.toStrict (BE.encode addr)) | ||
170 | `shouldBe` Right (addr :: PeerAddr IP) | ||
171 | |||
172 | |||
173 | it "properly bencoded (ipv4)" $ do | ||
174 | BE.decode "d7:peer id20:01234567890123456789\ | ||
175 | \2:ip11:168.192.0.1\ | ||
176 | \4:porti6881e\ | ||
177 | \e" | ||
178 | `shouldBe` | ||
179 | Right (PeerAddr (Just "01234567890123456789") | ||
180 | (IPv4 (toIPv4 [168, 192, 0, 1])) | ||
181 | 6881) | ||
182 | |||
183 | it "properly bencoded (ipv6)" $ do | ||
184 | BE.decode "d7:peer id20:01234567890123456789\ | ||
185 | \2:ip3:::1\ | ||
186 | \4:porti6881e\ | ||
187 | \e" | ||
188 | `shouldBe` | ||
189 | Right (PeerAddr (Just "01234567890123456789") | ||
190 | (IPv6 (toIPv6 [0, 0, 0, 0, 0, 0, 0, 1])) | ||
191 | 6881) | ||
192 | |||
193 | it "peer id is optional" $ do | ||
194 | BE.decode "d2:ip11:168.192.0.1\ | ||
195 | \4:porti6881e\ | ||
196 | \e" | ||
197 | `shouldBe` | ||
198 | Right (PeerAddr Nothing (IPv4 (toIPv4 [168, 192, 0, 1])) 6881) | ||
199 | |||
200 | it "has sock addr for both ipv4 and ipv6" $ do | ||
201 | show (peerSockAddr "128.0.0.1:80") `shouldBe` "128.0.0.1:80" | ||
202 | show (peerSockAddr "[::1]:8080" ) `shouldBe` "[::1]:8080" | ||