diff options
Diffstat (limited to 'src/Network/BitTorrent')
-rw-r--r-- | src/Network/BitTorrent/Exchange/Block.hs | 2 | ||||
-rw-r--r-- | src/Network/BitTorrent/Exchange/Message.hs | 180 | ||||
-rw-r--r-- | src/Network/BitTorrent/Exchange/Wire.hs | 4 |
3 files changed, 111 insertions, 75 deletions
diff --git a/src/Network/BitTorrent/Exchange/Block.hs b/src/Network/BitTorrent/Exchange/Block.hs index ca635a75..5ab73b65 100644 --- a/src/Network/BitTorrent/Exchange/Block.hs +++ b/src/Network/BitTorrent/Exchange/Block.hs | |||
@@ -144,7 +144,7 @@ instance Pretty (Block BL.ByteString) where | |||
144 | 144 | ||
145 | -- | Get size of block /payload/ in bytes. | 145 | -- | Get size of block /payload/ in bytes. |
146 | blockSize :: Block BL.ByteString -> BlockSize | 146 | blockSize :: Block BL.ByteString -> BlockSize |
147 | blockSize blk = fromIntegral (BL.length (blkData blk)) | 147 | blockSize = fromIntegral . BL.length . blkData |
148 | {-# INLINE blockSize #-} | 148 | {-# INLINE blockSize #-} |
149 | 149 | ||
150 | -- | Get block index of a block. | 150 | -- | Get block index of a block. |
diff --git a/src/Network/BitTorrent/Exchange/Message.hs b/src/Network/BitTorrent/Exchange/Message.hs index f29dec10..65b05737 100644 --- a/src/Network/BitTorrent/Exchange/Message.hs +++ b/src/Network/BitTorrent/Exchange/Message.hs | |||
@@ -25,11 +25,12 @@ | |||
25 | -- For more infomation see: | 25 | -- For more infomation see: |
26 | -- <https://wiki.theory.org/BitTorrentSpecification#Peer_wire_protocol_.28TCP.29> | 26 | -- <https://wiki.theory.org/BitTorrentSpecification#Peer_wire_protocol_.28TCP.29> |
27 | -- | 27 | -- |
28 | {-# LANGUAGE FlexibleInstances #-} | 28 | {-# LANGUAGE ViewPatterns #-} |
29 | {-# LANGUAGE FlexibleInstances #-} | ||
29 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} | 30 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} |
30 | {-# LANGUAGE DeriveDataTypeable #-} | 31 | {-# LANGUAGE DeriveDataTypeable #-} |
31 | {-# LANGUAGE TemplateHaskell #-} | 32 | {-# LANGUAGE TemplateHaskell #-} |
32 | {-# OPTIONS -fno-warn-orphans #-} | 33 | {-# OPTIONS -fno-warn-orphans #-} |
33 | module Network.BitTorrent.Exchange.Message | 34 | module Network.BitTorrent.Exchange.Message |
34 | ( -- * Capabilities | 35 | ( -- * Capabilities |
35 | Extension (..) | 36 | Extension (..) |
@@ -52,7 +53,8 @@ module Network.BitTorrent.Exchange.Message | |||
52 | 53 | ||
53 | -- ** Core messages | 54 | -- ** Core messages |
54 | , StatusUpdate (..) | 55 | , StatusUpdate (..) |
55 | , RegularMessage (..) | 56 | , Available (..) |
57 | , Transfer (..) | ||
56 | 58 | ||
57 | -- ** Fast extension | 59 | -- ** Fast extension |
58 | , FastMessage (..) | 60 | , FastMessage (..) |
@@ -279,10 +281,12 @@ instance PeerMessage StatusUpdate where | |||
279 | {-# INLINE envelop #-} | 281 | {-# INLINE envelop #-} |
280 | 282 | ||
281 | {----------------------------------------------------------------------- | 283 | {----------------------------------------------------------------------- |
282 | -- Available and transfer messages | 284 | -- Available messages |
283 | -----------------------------------------------------------------------} | 285 | -----------------------------------------------------------------------} |
284 | 286 | ||
285 | data RegularMessage = | 287 | -- | Messages used to inform receiver which pieces of the torrent |
288 | -- sender have. | ||
289 | data Available = | ||
286 | -- | Zero-based index of a piece that has just been successfully | 290 | -- | Zero-based index of a piece that has just been successfully |
287 | -- downloaded and verified via the hash. | 291 | -- downloaded and verified via the hash. |
288 | Have ! PieceIx | 292 | Have ! PieceIx |
@@ -292,11 +296,30 @@ data RegularMessage = | |||
292 | -- are sent. If client have no pieces then bitfield need not to be | 296 | -- are sent. If client have no pieces then bitfield need not to be |
293 | -- sent. | 297 | -- sent. |
294 | | Bitfield !Bitfield | 298 | | Bitfield !Bitfield |
299 | deriving (Show, Eq) | ||
300 | |||
301 | instance Pretty Available where | ||
302 | pretty (Have ix ) = "Have" <+> int ix | ||
303 | pretty (Bitfield _ ) = "Bitfield" | ||
304 | |||
305 | instance PeerMessage Available where | ||
306 | envelop _ = Available | ||
307 | |||
308 | -- | BITFIELD message. | ||
309 | instance PeerMessage Bitfield where | ||
310 | envelop c = envelop c . Bitfield | ||
311 | {-# INLINE envelop #-} | ||
312 | |||
313 | {----------------------------------------------------------------------- | ||
314 | -- Transfer messages | ||
315 | -----------------------------------------------------------------------} | ||
295 | 316 | ||
317 | -- | Messages used to transfer 'Block's. | ||
318 | data Transfer | ||
296 | -- | Request for a particular block. If a client is requested a | 319 | -- | Request for a particular block. If a client is requested a |
297 | -- block that another peer do not have the peer might not answer | 320 | -- block that another peer do not have the peer might not answer |
298 | -- at all. | 321 | -- at all. |
299 | | Request ! BlockIx | 322 | = Request ! BlockIx |
300 | 323 | ||
301 | -- | Response to a request for a block. | 324 | -- | Response to a request for a block. |
302 | | Piece !(Block BL.ByteString) | 325 | | Piece !(Block BL.ByteString) |
@@ -306,33 +329,21 @@ data RegularMessage = | |||
306 | | Cancel !BlockIx | 329 | | Cancel !BlockIx |
307 | deriving (Show, Eq) | 330 | deriving (Show, Eq) |
308 | 331 | ||
309 | -- TODO | 332 | instance Pretty Transfer where |
310 | -- data Availability = Have | Bitfield | ||
311 | -- data Transfer | ||
312 | -- = Request !BlockIx | ||
313 | -- | Piece !(Block BL.ByteString) | ||
314 | -- | Cancel !BlockIx | ||
315 | |||
316 | |||
317 | instance Pretty RegularMessage where | ||
318 | pretty (Have ix ) = "Have" <+> int ix | ||
319 | pretty (Bitfield _ ) = "Bitfield" | ||
320 | pretty (Request ix ) = "Request" <+> pretty ix | 333 | pretty (Request ix ) = "Request" <+> pretty ix |
321 | pretty (Piece blk) = "Piece" <+> pretty blk | 334 | pretty (Piece blk) = "Piece" <+> pretty blk |
322 | pretty (Cancel i ) = "Cancel" <+> pretty i | 335 | pretty (Cancel i ) = "Cancel" <+> pretty i |
323 | 336 | ||
324 | instance PeerMessage RegularMessage where | 337 | instance PeerMessage Transfer where |
325 | envelop _ = Regular | 338 | envelop _ = Transfer |
326 | {-# INLINE envelop #-} | ||
327 | |||
328 | instance PeerMessage Bitfield where | ||
329 | envelop c = envelop c . Bitfield | ||
330 | {-# INLINE envelop #-} | 339 | {-# INLINE envelop #-} |
331 | 340 | ||
341 | -- | REQUEST message. | ||
332 | instance PeerMessage BlockIx where | 342 | instance PeerMessage BlockIx where |
333 | envelop c = envelop c . Request | 343 | envelop c = envelop c . Request |
334 | {-# INLINE envelop #-} | 344 | {-# INLINE envelop #-} |
335 | 345 | ||
346 | -- | PIECE message. | ||
336 | instance PeerMessage (Block BL.ByteString) where | 347 | instance PeerMessage (Block BL.ByteString) where |
337 | envelop c = envelop c . Piece | 348 | envelop c = envelop c . Piece |
338 | {-# INLINE envelop #-} | 349 | {-# INLINE envelop #-} |
@@ -507,8 +518,8 @@ nullExtendedHandshake caps | |||
507 | 518 | ||
508 | type MetadataId = Int | 519 | type MetadataId = Int |
509 | 520 | ||
510 | pieceSize :: Int | 521 | metadataPieceSize :: Int |
511 | pieceSize = 16 * 1024 | 522 | metadataPieceSize = 16 * 1024 |
512 | 523 | ||
513 | data ExtendedMetadata | 524 | data ExtendedMetadata |
514 | = MetadataRequest PieceIx | 525 | = MetadataRequest PieceIx |
@@ -586,11 +597,17 @@ data Message | |||
586 | -- connection between two peers alive, if no /other/ message has | 597 | -- connection between two peers alive, if no /other/ message has |
587 | -- been sent in a given period of time. | 598 | -- been sent in a given period of time. |
588 | = KeepAlive | 599 | = KeepAlive |
589 | | Status !StatusUpdate | 600 | | Status !StatusUpdate -- ^ Messages used to update peer status. |
590 | | Regular !RegularMessage | 601 | | Available !Available -- ^ Messages used to inform availability. |
591 | | Port !PortNumber | 602 | | Transfer !Transfer -- ^ Messages used to transfer 'Block's. |
592 | | Fast !FastMessage | 603 | |
593 | | Extended !ExtendedMessage | 604 | -- | Peer receiving a handshake indicating the remote peer |
605 | -- supports the 'ExtDHT' should send a 'Port' message. Peers that | ||
606 | -- receive this message should attempt to ping the node on the | ||
607 | -- received port and IP address of the remote peer. | ||
608 | | Port !PortNumber | ||
609 | | Fast !FastMessage | ||
610 | | Extended !ExtendedMessage | ||
594 | deriving (Show, Eq) | 611 | deriving (Show, Eq) |
595 | 612 | ||
596 | instance Default Message where | 613 | instance Default Message where |
@@ -601,7 +618,8 @@ instance Default Message where | |||
601 | instance Pretty Message where | 618 | instance Pretty Message where |
602 | pretty (KeepAlive ) = "Keep alive" | 619 | pretty (KeepAlive ) = "Keep alive" |
603 | pretty (Status m) = pretty m | 620 | pretty (Status m) = pretty m |
604 | pretty (Regular m) = pretty m | 621 | pretty (Available m) = pretty m |
622 | pretty (Transfer m) = pretty m | ||
605 | pretty (Port p) = "Port" <+> int (fromEnum p) | 623 | pretty (Port p) = "Port" <+> int (fromEnum p) |
606 | pretty (Fast m) = pretty m | 624 | pretty (Fast m) = pretty m |
607 | pretty (Extended m) = pretty m | 625 | pretty (Extended m) = pretty m |
@@ -610,13 +628,15 @@ instance PeerMessage Message where | |||
610 | envelop _ = id | 628 | envelop _ = id |
611 | {-# INLINE envelop #-} | 629 | {-# INLINE envelop #-} |
612 | 630 | ||
613 | requires KeepAlive = Nothing | 631 | requires KeepAlive = Nothing |
614 | requires (Status _) = Nothing | 632 | requires (Status _) = Nothing |
615 | requires (Regular _) = Nothing | 633 | requires (Available _) = Nothing |
616 | requires (Port _) = Just ExtDHT | 634 | requires (Transfer _) = Nothing |
617 | requires (Fast _) = Just ExtFast | 635 | requires (Port _) = Just ExtDHT |
618 | requires (Extended _) = Just ExtExtended | 636 | requires (Fast _) = Just ExtFast |
637 | requires (Extended _) = Just ExtExtended | ||
619 | 638 | ||
639 | -- | PORT message. | ||
620 | instance PeerMessage PortNumber where | 640 | instance PeerMessage PortNumber where |
621 | envelop _ = Port | 641 | envelop _ = Port |
622 | {-# INLINE envelop #-} | 642 | {-# INLINE envelop #-} |
@@ -647,12 +667,12 @@ instance Serialize Message where | |||
647 | 0x01 -> return $ Status (Choking False) | 667 | 0x01 -> return $ Status (Choking False) |
648 | 0x02 -> return $ Status (Interested True) | 668 | 0x02 -> return $ Status (Interested True) |
649 | 0x03 -> return $ Status (Interested False) | 669 | 0x03 -> return $ Status (Interested False) |
650 | 0x04 -> (Regular . Have) <$> getInt | 670 | 0x04 -> (Available . Have) <$> getInt |
651 | 0x05 -> (Regular . Bitfield . fromBitmap) | 671 | 0x05 -> (Available . Bitfield . fromBitmap) |
652 | <$> S.getByteString (pred len) | 672 | <$> S.getByteString (pred len) |
653 | 0x06 -> (Regular . Request) <$> S.get | 673 | 0x06 -> (Transfer . Request) <$> S.get |
654 | 0x07 -> (Regular . Piece) <$> getBlock (len - 9) | 674 | 0x07 -> (Transfer . Piece) <$> getBlock (len - 9) |
655 | 0x08 -> (Regular . Cancel) <$> S.get | 675 | 0x08 -> (Transfer . Cancel) <$> S.get |
656 | 0x09 -> Port <$> S.get | 676 | 0x09 -> Port <$> S.get |
657 | 0x0D -> (Fast . SuggestPiece) <$> getInt | 677 | 0x0D -> (Fast . SuggestPiece) <$> getInt |
658 | 0x0E -> return $ Fast HaveAll | 678 | 0x0E -> return $ Fast HaveAll |
@@ -671,45 +691,59 @@ instance Serialize Message where | |||
671 | <*> S.getLazyByteString (fromIntegral len) | 691 | <*> S.getLazyByteString (fromIntegral len) |
672 | {-# INLINE getBlock #-} | 692 | {-# INLINE getBlock #-} |
673 | 693 | ||
674 | put KeepAlive = putInt 0 | 694 | put KeepAlive = putInt 0 |
675 | put (Status msg) = putStatus msg | 695 | put (Status msg) = putStatus msg |
676 | put (Regular msg) = putRegular msg | 696 | put (Available msg) = putAvailable msg |
677 | put (Port p ) = putPort p | 697 | put (Transfer msg) = putTransfer msg |
678 | put (Fast msg) = putFast msg | 698 | put (Port p ) = putPort p |
679 | put (Extended m ) = putExtendedMessage m | 699 | put (Fast msg) = putFast msg |
700 | put (Extended m ) = putExtendedMessage m | ||
680 | 701 | ||
681 | statusUpdateId :: StatusUpdate -> MessageId | 702 | statusUpdateId :: StatusUpdate -> MessageId |
682 | statusUpdateId (Choking choking) = fromIntegral (0 + fromEnum choking) | 703 | statusUpdateId (Choking choking) = fromIntegral (0 + fromEnum choking) |
683 | statusUpdateId (Interested choking) = fromIntegral (2 + fromEnum choking) | 704 | statusUpdateId (Interested choking) = fromIntegral (2 + fromEnum choking) |
684 | 705 | ||
685 | putStatus :: Putter StatusUpdate | 706 | putStatus :: Putter StatusUpdate |
686 | putStatus su = putInt 1 >> S.putWord8 (statusUpdateId su) | 707 | putStatus su = do |
687 | 708 | putInt 1 | |
688 | putRegular :: Putter RegularMessage | 709 | putWord8 (statusUpdateId su) |
689 | putRegular (Have i) = putInt 5 >> S.putWord8 0x04 >> putInt i | 710 | |
690 | putRegular (Bitfield bf) = putInt l >> S.putWord8 0x05 >> S.putLazyByteString b | 711 | putAvailable :: Putter Available |
691 | where b = toBitmap bf | 712 | putAvailable (Have i) = do |
692 | l = succ (fromIntegral (BL.length b)) | 713 | putInt 5 |
693 | {-# INLINE l #-} | 714 | putWord8 0x04 |
694 | putRegular (Request blk) = putInt 13 >> S.putWord8 0x06 >> S.put blk | 715 | putInt i |
695 | putRegular (Piece blk) = putInt l >> S.putWord8 0x07 >> putBlock | 716 | putAvailable (Bitfield (toBitmap -> bs)) = do |
696 | where l = 9 + fromIntegral (BL.length (blkData blk)) | 717 | putInt $ 1 + fromIntegral (BL.length bs) |
697 | {-# INLINE l #-} | 718 | putWord8 0x05 |
698 | putBlock = do putInt (blkPiece blk) | 719 | putLazyByteString bs |
699 | putInt (blkOffset blk) | 720 | |
700 | S.putLazyByteString (blkData blk) | 721 | putBlock :: Putter (Block BL.ByteString) |
701 | {-# INLINE putBlock #-} | 722 | putBlock Block {..} = do |
702 | putRegular (Cancel blk) = putInt 13 >> S.putWord8 0x08 >> S.put blk | 723 | putInt blkPiece |
724 | putInt blkOffset | ||
725 | putLazyByteString blkData | ||
726 | |||
727 | putTransfer :: Putter Transfer | ||
728 | putTransfer (Request blk) = putInt 13 >> S.putWord8 0x06 >> S.put blk | ||
729 | putTransfer (Piece blk) = do | ||
730 | putInt (9 + blockSize blk) | ||
731 | putWord8 0x07 | ||
732 | putBlock blk | ||
733 | putTransfer (Cancel blk) = putInt 13 >> S.putWord8 0x08 >> S.put blk | ||
703 | 734 | ||
704 | putPort :: Putter PortNumber | 735 | putPort :: Putter PortNumber |
705 | putPort p = putInt 3 >> S.putWord8 0x09 >> S.put p | 736 | putPort p = do |
737 | putInt 3 | ||
738 | putWord8 0x09 | ||
739 | put p | ||
706 | 740 | ||
707 | putFast :: Putter FastMessage | 741 | putFast :: Putter FastMessage |
708 | putFast HaveAll = putInt 1 >> S.putWord8 0x0E | 742 | putFast HaveAll = putInt 1 >> putWord8 0x0E |
709 | putFast HaveNone = putInt 1 >> S.putWord8 0x0F | 743 | putFast HaveNone = putInt 1 >> putWord8 0x0F |
710 | putFast (SuggestPiece pix) = putInt 5 >> S.putWord8 0x0D >> putInt pix | 744 | putFast (SuggestPiece pix) = putInt 5 >> putWord8 0x0D >> putInt pix |
711 | putFast (RejectRequest i ) = putInt 13 >> S.putWord8 0x10 >> S.put i | 745 | putFast (RejectRequest i ) = putInt 13 >> putWord8 0x10 >> put i |
712 | putFast (AllowedFast i ) = putInt 5 >> S.putWord8 0x11 >> putInt i | 746 | putFast (AllowedFast i ) = putInt 5 >> putWord8 0x11 >> putInt i |
713 | 747 | ||
714 | getExtendedHandshake :: Int -> S.Get ExtendedHandshake | 748 | getExtendedHandshake :: Int -> S.Get ExtendedHandshake |
715 | getExtendedHandshake messageSize = do | 749 | getExtendedHandshake messageSize = do |
diff --git a/src/Network/BitTorrent/Exchange/Wire.hs b/src/Network/BitTorrent/Exchange/Wire.hs index 680da059..8f6e1d58 100644 --- a/src/Network/BitTorrent/Exchange/Wire.hs +++ b/src/Network/BitTorrent/Exchange/Wire.hs | |||
@@ -51,7 +51,9 @@ import Data.Torrent.InfoHash | |||
51 | import Network.BitTorrent.Core | 51 | import Network.BitTorrent.Core |
52 | import Network.BitTorrent.Exchange.Message | 52 | import Network.BitTorrent.Exchange.Message |
53 | 53 | ||
54 | 54 | -- TODO handle port message? | |
55 | -- TODO handle limits? | ||
56 | -- TODO filter not requested PIECE messages | ||
55 | {----------------------------------------------------------------------- | 57 | {----------------------------------------------------------------------- |
56 | -- Exceptions | 58 | -- Exceptions |
57 | -----------------------------------------------------------------------} | 59 | -----------------------------------------------------------------------} |