diff options
Diffstat (limited to 'src/Network/BitTorrent')
-rw-r--r-- | src/Network/BitTorrent/Exchange/Extension.hs | 67 | ||||
-rw-r--r-- | src/Network/BitTorrent/Exchange/Message.hs | 225 |
2 files changed, 124 insertions, 168 deletions
diff --git a/src/Network/BitTorrent/Exchange/Extension.hs b/src/Network/BitTorrent/Exchange/Extension.hs index a4d72f96..e81cdb87 100644 --- a/src/Network/BitTorrent/Exchange/Extension.hs +++ b/src/Network/BitTorrent/Exchange/Extension.hs | |||
@@ -12,54 +12,59 @@ | |||
12 | -- | 12 | -- |
13 | module Network.BitTorrent.Exchange.Extension | 13 | module Network.BitTorrent.Exchange.Extension |
14 | ( -- * Capabilities | 14 | ( -- * Capabilities |
15 | Capabilities | 15 | Caps |
16 | , ppCaps, defaultCaps | ||
17 | , enabledCaps | ||
18 | 16 | ||
19 | -- * Extensions | 17 | -- * Extensions |
20 | , Extension(..) | 18 | , Extension(..) |
21 | , defaultExtensions, ppExtension | ||
22 | , encodeExts, decodeExts | ||
23 | ) where | 19 | ) where |
24 | 20 | ||
25 | import Data.Bits | 21 | import Data.Bits |
22 | import Data.Default | ||
23 | import Data.Monoid | ||
26 | import Data.Word | 24 | import Data.Word |
27 | import Text.PrettyPrint | 25 | import Text.PrettyPrint |
26 | import Text.PrettyPrint.Class | ||
28 | 27 | ||
28 | class (Enum a, Bounded a) => Capability a where | ||
29 | capMask :: a -> Word64 | ||
30 | capRequires :: a -> Word64 | ||
29 | 31 | ||
30 | type Capabilities = Word64 | 32 | newtype Caps a = Caps Word64 |
31 | 33 | ||
32 | ppCaps :: Capabilities -> Doc | 34 | instance (Pretty a, Capability a) => Pretty (Caps a) where |
33 | ppCaps = hcat . punctuate ", " . map ppExtension . decodeExts | 35 | pretty = hcat . punctuate ", " . map pretty . toList |
34 | 36 | ||
35 | defaultCaps :: Capabilities | 37 | instance Default (Caps a) where |
36 | defaultCaps = 0 | 38 | def = Caps 0 |
39 | {-# INLINE def #-} | ||
37 | 40 | ||
38 | enabledCaps :: Capabilities -- ^ of the client. | 41 | instance Monoid (Caps a) where |
39 | -> Capabilities -- ^ of the peer. | 42 | mempty = Caps (-1) |
40 | -> Capabilities -- ^ should be considered as enabled. | 43 | {-# INLINE mempty #-} |
41 | enabledCaps = (.&.) | ||
42 | 44 | ||
45 | mappend (Caps a) (Caps b) = Caps (a .&. b) | ||
46 | {-# INLINE mappend #-} | ||
43 | 47 | ||
44 | data Extension = ExtDHT -- ^ BEP 5 | 48 | allowed :: Capability a => a -> Caps a -> Bool |
45 | | ExtFast -- ^ BEP 6 | 49 | allowed = member |
46 | deriving (Show, Eq, Ord, Enum, Bounded) | 50 | fromList :: Capability a => [a] -> Caps a |
51 | fromList = Caps . foldr (.&.) 0 . map capMask | ||
47 | 52 | ||
48 | ppExtension :: Extension -> Doc | 53 | toList :: Capability a => Caps a -> [a] |
49 | ppExtension ExtDHT = "DHT" | 54 | toList (Caps rb) = filter (testMask rb . capMask) [minBound..maxBound] |
50 | ppExtension ExtFast = "Fast Extension" | 55 | where |
56 | testMask bits x = bits .&. x > 0 | ||
51 | 57 | ||
52 | extensionMask :: Extension -> Word64 | ||
53 | extensionMask ExtDHT = 0x01 | ||
54 | extensionMask ExtFast = 0x04 | ||
55 | 58 | ||
56 | defaultExtensions :: [Extension] | 59 | data Extension |
57 | defaultExtensions = [] | 60 | = ExtDHT -- ^ BEP 5 |
61 | | ExtFast -- ^ BEP 6 | ||
62 | deriving (Show, Eq, Ord, Enum, Bounded) | ||
58 | 63 | ||
59 | encodeExts :: [Extension] -> Capabilities | 64 | instance Pretty Extension where |
60 | encodeExts = foldr (.&.) 0 . map extensionMask | 65 | pretty ExtDHT = "DHT" |
66 | pretty ExtFast = "Fast Extension" | ||
61 | 67 | ||
62 | decodeExts :: Capabilities -> [Extension] | 68 | instance Capability Extension where |
63 | decodeExts rb = filter (testMask rb . extensionMask) [minBound..maxBound] | 69 | capMask ExtDHT = 0x01 |
64 | where | 70 | capMask ExtFast = 0x04 |
65 | testMask bits x = bits .&. x > 0 | ||
diff --git a/src/Network/BitTorrent/Exchange/Message.hs b/src/Network/BitTorrent/Exchange/Message.hs index 4d4a97e2..546288b2 100644 --- a/src/Network/BitTorrent/Exchange/Message.hs +++ b/src/Network/BitTorrent/Exchange/Message.hs | |||
@@ -41,21 +41,22 @@ module Network.BitTorrent.Exchange.Message | |||
41 | , defaultReserved | 41 | , defaultReserved |
42 | , handshakeMaxSize | 42 | , handshakeMaxSize |
43 | 43 | ||
44 | -- * Regular messages | 44 | -- * Messages |
45 | , Message(..) | 45 | , Message (..) |
46 | , StatusUpdate (..) | ||
47 | , RegularMessage (..) | ||
48 | , FastMessage (..) | ||
46 | ) where | 49 | ) where |
47 | 50 | ||
48 | import Control.Applicative | 51 | import Control.Applicative |
49 | import Control.Exception | 52 | import Control.Exception |
50 | import Control.Monad | 53 | import Control.Monad |
51 | import Data.Binary as B | ||
52 | import Data.Binary.Get as B | ||
53 | import Data.Binary.Put as B | ||
54 | import Data.ByteString as BS | 54 | import Data.ByteString as BS |
55 | import Data.ByteString.Char8 as BC | 55 | import Data.ByteString.Char8 as BC |
56 | import Data.ByteString.Lazy as BL | 56 | import Data.ByteString.Lazy as BL |
57 | import Data.Default | 57 | import Data.Default |
58 | import Data.Serialize as S | 58 | import Data.Serialize as S |
59 | import Data.Word | ||
59 | import Network | 60 | import Network |
60 | import Network.Socket.ByteString | 61 | import Network.Socket.ByteString |
61 | import Text.PrettyPrint | 62 | import Text.PrettyPrint |
@@ -64,26 +65,9 @@ import Text.PrettyPrint.Class | |||
64 | import Data.Torrent.Bitfield | 65 | import Data.Torrent.Bitfield |
65 | import Data.Torrent.Block | 66 | import Data.Torrent.Block |
66 | import Data.Torrent.InfoHash | 67 | import Data.Torrent.InfoHash |
67 | import Network.BitTorrent.Extension | ||
68 | import Network.BitTorrent.Core.PeerId | 68 | import Network.BitTorrent.Core.PeerId |
69 | import Network.BitTorrent.Core.PeerAddr () | 69 | import Network.BitTorrent.Core.PeerAddr () |
70 | 70 | import Network.BitTorrent.Exchange.Extension | |
71 | |||
72 | getInt :: S.Get Int | ||
73 | getInt = fromIntegral <$> S.getWord32be | ||
74 | {-# INLINE getInt #-} | ||
75 | |||
76 | putInt :: S.Putter Int | ||
77 | putInt = S.putWord32be . fromIntegral | ||
78 | {-# INLINE putInt #-} | ||
79 | |||
80 | getIntB :: B.Get Int | ||
81 | getIntB = fromIntegral <$> B.getWord32be | ||
82 | {-# INLINE getIntB #-} | ||
83 | |||
84 | putIntB :: Int -> B.Put | ||
85 | putIntB = B.putWord32be . fromIntegral | ||
86 | {-# INLINE putIntB #-} | ||
87 | 71 | ||
88 | {----------------------------------------------------------------------- | 72 | {----------------------------------------------------------------------- |
89 | Handshake | 73 | Handshake |
@@ -195,6 +179,9 @@ data StatusUpdate | |||
195 | | NotInterested | 179 | | NotInterested |
196 | deriving (Show, Eq, Ord, Enum, Bounded) | 180 | deriving (Show, Eq, Ord, Enum, Bounded) |
197 | 181 | ||
182 | instance Pretty StatusUpdate where | ||
183 | pretty = text . show | ||
184 | |||
198 | data RegularMessage = | 185 | data RegularMessage = |
199 | -- | Zero-based index of a piece that has just been successfully | 186 | -- | Zero-based index of a piece that has just been successfully |
200 | -- downloaded and verified via the hash. | 187 | -- downloaded and verified via the hash. |
@@ -219,9 +206,12 @@ data RegularMessage = | |||
219 | | Cancel !BlockIx | 206 | | Cancel !BlockIx |
220 | deriving (Show, Eq) | 207 | deriving (Show, Eq) |
221 | 208 | ||
222 | data DHTMessage | 209 | instance Pretty RegularMessage where |
223 | = Port !PortNumber | 210 | pretty (Have ix ) = "Have" <+> int ix |
224 | deriving (Show, Eq) | 211 | pretty (Bitfield _ ) = "Bitfield" |
212 | pretty (Request ix ) = "Request" <+> pretty ix | ||
213 | pretty (Piece blk) = "Piece" <+> pretty blk | ||
214 | pretty (Cancel i ) = "Cancel" <+> pretty i | ||
225 | 215 | ||
226 | -- | BEP6 messages. | 216 | -- | BEP6 messages. |
227 | data FastMessage = | 217 | data FastMessage = |
@@ -247,7 +237,12 @@ data FastMessage = | |||
247 | | AllowedFast !PieceIx | 237 | | AllowedFast !PieceIx |
248 | deriving (Show, Eq) | 238 | deriving (Show, Eq) |
249 | 239 | ||
250 | -- TODO make Network.BitTorrent.Exchange.Session | 240 | instance Pretty FastMessage where |
241 | pretty (HaveAll ) = "Have all" | ||
242 | pretty (HaveNone ) = "Have none" | ||
243 | pretty (SuggestPiece pix) = "Suggest" <+> int pix | ||
244 | pretty (RejectRequest bix) = "Reject" <+> pretty bix | ||
245 | pretty (AllowedFast pix) = "Allowed fast" <+> int pix | ||
251 | 246 | ||
252 | -- | Messages used in communication between peers. | 247 | -- | Messages used in communication between peers. |
253 | -- | 248 | -- |
@@ -262,46 +257,53 @@ data Message | |||
262 | | Regular !RegularMessage | 257 | | Regular !RegularMessage |
263 | 258 | ||
264 | -- extensions | 259 | -- extensions |
265 | | DHT !DHTMessage | 260 | | Port !PortNumber |
266 | | Fast !FastMessage | 261 | | Fast !FastMessage |
267 | deriving (Show, Eq) | 262 | deriving (Show, Eq) |
268 | 263 | ||
269 | instance Default Message where | 264 | instance Default Message where |
270 | def = KeepAlive | 265 | def = KeepAlive |
271 | {-# INLINE def #-} | 266 | {-# INLINE def #-} |
272 | {- | 267 | |
273 | -- | Payload bytes are omitted. | 268 | -- | Payload bytes are omitted. |
274 | instance Pretty Message where | 269 | instance Pretty Message where |
275 | pretty (Bitfield _) = "Bitfield" | 270 | pretty (KeepAlive ) = "Keep alive" |
276 | pretty (Piece blk) = "Piece" <+> pretty blk | 271 | pretty (Status m) = pretty m |
277 | pretty (Cancel i ) = "Cancel" <+> pretty i | 272 | pretty (Regular m) = pretty m |
278 | pretty (SuggestPiece pix) = "Suggest" <+> int pix | 273 | pretty (Port p) = "Port" <+> int (fromEnum p) |
279 | pretty (RejectRequest i ) = "Reject" <+> pretty i | 274 | pretty (Fast m) = pretty m |
280 | pretty msg = text (show msg) | 275 | |
276 | getInt :: S.Get Int | ||
277 | getInt = fromIntegral <$> S.getWord32be | ||
278 | {-# INLINE getInt #-} | ||
279 | |||
280 | putInt :: S.Putter Int | ||
281 | putInt = S.putWord32be . fromIntegral | ||
282 | {-# INLINE putInt #-} | ||
281 | 283 | ||
282 | instance Serialize Message where | 284 | instance Serialize Message where |
283 | get = do | 285 | get = do |
284 | len <- getInt | 286 | len <- getInt |
285 | -- _ <- lookAhead $ ensure len | ||
286 | if len == 0 then return KeepAlive | 287 | if len == 0 then return KeepAlive |
287 | else do | 288 | else do |
288 | mid <- S.getWord8 | 289 | mid <- S.getWord8 |
289 | case mid of | 290 | case mid of |
290 | 0x00 -> return Choke | 291 | 0x00 -> return $ Status Choke |
291 | 0x01 -> return Unchoke | 292 | 0x01 -> return $ Status Unchoke |
292 | 0x02 -> return Interested | 293 | 0x02 -> return $ Status Interested |
293 | 0x03 -> return NotInterested | 294 | 0x03 -> return $ Status NotInterested |
294 | 0x04 -> Have <$> getInt | 295 | 0x04 -> (Regular . Have) <$> getInt |
295 | 0x05 -> (Bitfield . fromBitmap) <$> S.getByteString (pred len) | 296 | 0x05 -> (Regular . Bitfield . fromBitmap) |
296 | 0x06 -> Request <$> S.get | 297 | <$> S.getByteString (pred len) |
297 | 0x07 -> Piece <$> getBlock (len - 9) | 298 | 0x06 -> (Regular . Request) <$> S.get |
298 | 0x08 -> Cancel <$> S.get | 299 | 0x07 -> (Regular . Piece) <$> getBlock (len - 9) |
300 | 0x08 -> (Regular . Cancel) <$> S.get | ||
299 | 0x09 -> Port <$> S.get | 301 | 0x09 -> Port <$> S.get |
300 | 0x0D -> SuggestPiece <$> getInt | 302 | 0x0D -> (Fast . SuggestPiece) <$> getInt |
301 | 0x0E -> return HaveAll | 303 | 0x0E -> return $ Fast HaveAll |
302 | 0x0F -> return HaveNone | 304 | 0x0F -> return $ Fast HaveNone |
303 | 0x10 -> RejectRequest <$> S.get | 305 | 0x10 -> (Fast . RejectRequest) <$> S.get |
304 | 0x11 -> AllowedFast <$> getInt | 306 | 0x11 -> (Fast . AllowedFast) <$> getInt |
305 | _ -> do | 307 | _ -> do |
306 | rm <- S.remaining >>= S.getBytes | 308 | rm <- S.remaining >>= S.getBytes |
307 | fail $ "unknown message ID: " ++ show mid ++ "\n" | 309 | fail $ "unknown message ID: " ++ show mid ++ "\n" |
@@ -309,92 +311,41 @@ instance Serialize Message where | |||
309 | 311 | ||
310 | where | 312 | where |
311 | getBlock :: Int -> S.Get (Block BL.ByteString) | 313 | getBlock :: Int -> S.Get (Block BL.ByteString) |
312 | getBlock len = Block <$> getInt <*> getInt <*> S.getLazyByteString (fromIntegral len) | 314 | getBlock len = Block <$> getInt <*> getInt |
313 | {-# INLINE getBlock #-} | 315 | <*> S.getLazyByteString (fromIntegral len) |
314 | |||
315 | |||
316 | put KeepAlive = putInt 0 | ||
317 | put Choke = putInt 1 >> S.putWord8 0x00 | ||
318 | put Unchoke = putInt 1 >> S.putWord8 0x01 | ||
319 | put Interested = putInt 1 >> S.putWord8 0x02 | ||
320 | put NotInterested = putInt 1 >> S.putWord8 0x03 | ||
321 | put (Have i) = putInt 5 >> S.putWord8 0x04 >> putInt i | ||
322 | put (Bitfield bf) = putInt l >> S.putWord8 0x05 >> S.putLazyByteString b | ||
323 | where b = toBitmap bf | ||
324 | l = succ (fromIntegral (BL.length b)) | ||
325 | {-# INLINE l #-} | ||
326 | put (Request blk) = putInt 13 >> S.putWord8 0x06 >> S.put blk | ||
327 | put (Piece blk) = putInt l >> S.putWord8 0x07 >> putBlock | ||
328 | where l = 9 + fromIntegral (BL.length (blkData blk)) | ||
329 | {-# INLINE l #-} | ||
330 | putBlock = do putInt (blkPiece blk) | ||
331 | putInt (blkOffset blk) | ||
332 | S.putLazyByteString (blkData blk) | ||
333 | {-# INLINE putBlock #-} | ||
334 | |||
335 | put (Cancel blk) = putInt 13 >> S.putWord8 0x08 >> S.put blk | ||
336 | put (Port p ) = putInt 3 >> S.putWord8 0x09 >> S.put p | ||
337 | put HaveAll = putInt 1 >> S.putWord8 0x0E | ||
338 | put HaveNone = putInt 1 >> S.putWord8 0x0F | ||
339 | put (SuggestPiece pix) = putInt 5 >> S.putWord8 0x0D >> putInt pix | ||
340 | put (RejectRequest i ) = putInt 13 >> S.putWord8 0x10 >> S.put i | ||
341 | put (AllowedFast i ) = putInt 5 >> S.putWord8 0x11 >> putInt i | ||
342 | -} | ||
343 | {- | ||
344 | instance Binary Message where | ||
345 | get = do | ||
346 | len <- getIntB | ||
347 | -- _ <- lookAhead $ ensure len | ||
348 | if len == 0 then return KeepAlive | ||
349 | else do | ||
350 | mid <- B.getWord8 | ||
351 | case mid of | ||
352 | 0x00 -> return Choke | ||
353 | 0x01 -> return Unchoke | ||
354 | 0x02 -> return Interested | ||
355 | 0x03 -> return NotInterested | ||
356 | 0x04 -> Have <$> getIntB | ||
357 | 0x05 -> (Bitfield . fromBitmap) <$> B.getByteString (pred len) | ||
358 | 0x06 -> Request <$> B.get | ||
359 | 0x07 -> Piece <$> getBlock (len - 9) | ||
360 | 0x08 -> Cancel <$> B.get | ||
361 | 0x09 -> (Port . fromIntegral) <$> B.getWord16be | ||
362 | 0x0E -> return HaveAll | ||
363 | 0x0F -> return HaveNone | ||
364 | 0x0D -> SuggestPiece <$> getIntB | ||
365 | 0x10 -> RejectRequest <$> B.get | ||
366 | 0x11 -> AllowedFast <$> getIntB | ||
367 | _ -> fail $ "unknown message ID: " ++ show mid | ||
368 | where | ||
369 | getBlock :: Int -> B.Get (Block BL.ByteString) | ||
370 | getBlock len = Block <$> getIntB <*> getIntB | ||
371 | <*> B.getLazyByteString (fromIntegral len) | ||
372 | {-# INLINE getBlock #-} | 316 | {-# INLINE getBlock #-} |
373 | 317 | ||
374 | put KeepAlive = putIntB 0 | 318 | put KeepAlive = putInt 0 |
375 | put Choke = putIntB 1 >> B.putWord8 0x00 | 319 | put (Status msg) = putStatus msg |
376 | put Unchoke = putIntB 1 >> B.putWord8 0x01 | 320 | put (Regular msg) = putRegular msg |
377 | put Interested = putIntB 1 >> B.putWord8 0x02 | 321 | put (Port p ) = putPort p |
378 | put NotInterested = putIntB 1 >> B.putWord8 0x03 | 322 | put (Fast msg) = putFast msg |
379 | put (Have i) = putIntB 5 >> B.putWord8 0x04 >> putIntB i | 323 | |
380 | put (Bitfield bf) = putIntB l >> B.putWord8 0x05 >> B.putLazyByteString b | 324 | putStatus :: Putter StatusUpdate |
381 | where b = toBitmap bf | 325 | putStatus su = putInt 1 >> S.putWord8 (fromIntegral (fromEnum su)) |
382 | l = succ (fromIntegral (BL.length b)) | 326 | |
383 | {-# INLINE l #-} | 327 | putRegular :: Putter RegularMessage |
384 | put (Request blk) = putIntB 13 >> B.putWord8 0x06 >> B.put blk | 328 | putRegular (Have i) = putInt 5 >> S.putWord8 0x04 >> putInt i |
385 | put (Piece blk) = putIntB l >> B.putWord8 0x07 >> putBlock | 329 | putRegular (Bitfield bf) = putInt l >> S.putWord8 0x05 >> S.putLazyByteString b |
386 | where l = 9 + fromIntegral (BL.length (blkData blk)) | 330 | where b = toBitmap bf |
387 | {-# INLINE l #-} | 331 | l = succ (fromIntegral (BL.length b)) |
388 | putBlock = do putIntB (blkPiece blk) | 332 | {-# INLINE l #-} |
389 | putIntB (blkOffset blk) | 333 | putRegular (Request blk) = putInt 13 >> S.putWord8 0x06 >> S.put blk |
390 | B.putLazyByteString (blkData blk) | 334 | putRegular (Piece blk) = putInt l >> S.putWord8 0x07 >> putBlock |
391 | {-# INLINE putBlock #-} | 335 | where l = 9 + fromIntegral (BL.length (blkData blk)) |
392 | 336 | {-# INLINE l #-} | |
393 | put (Cancel blk) = putIntB 13 >> B.putWord8 0x08 >> B.put blk | 337 | putBlock = do putInt (blkPiece blk) |
394 | put (Port p ) = putIntB 3 >> B.putWord8 0x09 >> B.putWord16be (fromIntegral p) | 338 | putInt (blkOffset blk) |
395 | put HaveAll = putIntB 1 >> B.putWord8 0x0E | 339 | S.putLazyByteString (blkData blk) |
396 | put HaveNone = putIntB 1 >> B.putWord8 0x0F | 340 | {-# INLINE putBlock #-} |
397 | put (SuggestPiece pix) = putIntB 5 >> B.putWord8 0x0D >> putIntB pix | 341 | putRegular (Cancel blk) = putInt 13 >> S.putWord8 0x08 >> S.put blk |
398 | put (RejectRequest i ) = putIntB 13 >> B.putWord8 0x10 >> B.put i | 342 | |
399 | put (AllowedFast i ) = putIntB 5 >> B.putWord8 0x11 >> putIntB i | 343 | putPort :: Putter PortNumber |
400 | -} \ No newline at end of file | 344 | putPort p = putInt 3 >> S.putWord8 0x09 >> S.put p |
345 | |||
346 | putFast :: Putter FastMessage | ||
347 | putFast HaveAll = putInt 1 >> S.putWord8 0x0E | ||
348 | putFast HaveNone = putInt 1 >> S.putWord8 0x0F | ||
349 | putFast (SuggestPiece pix) = putInt 5 >> S.putWord8 0x0D >> putInt pix | ||
350 | putFast (RejectRequest i ) = putInt 13 >> S.putWord8 0x10 >> S.put i | ||
351 | putFast (AllowedFast i ) = putInt 5 >> S.putWord8 0x11 >> putInt i | ||