diff options
author | Sam T <pxqr.sta@gmail.com> | 2013-06-07 23:42:34 +0400 |
---|---|---|
committer | Sam T <pxqr.sta@gmail.com> | 2013-06-07 23:42:34 +0400 |
commit | 757ce3b4fa3de2d6e84307f79184a44b48ec0a29 (patch) | |
tree | 82e93efc5920c5e7a18adf6c126f9e8eec002ae3 /src/Network/BitTorrent/PeerWire/Protocol.hs | |
parent | a30bb766e8f2bea19e5a8f1739354d5f7894df1d (diff) |
~ Rename Message to Protocol.
Diffstat (limited to 'src/Network/BitTorrent/PeerWire/Protocol.hs')
-rw-r--r-- | src/Network/BitTorrent/PeerWire/Protocol.hs | 155 |
1 files changed, 155 insertions, 0 deletions
diff --git a/src/Network/BitTorrent/PeerWire/Protocol.hs b/src/Network/BitTorrent/PeerWire/Protocol.hs new file mode 100644 index 00000000..a4d987e6 --- /dev/null +++ b/src/Network/BitTorrent/PeerWire/Protocol.hs | |||
@@ -0,0 +1,155 @@ | |||
1 | {-# LANGUAGE OverloadedStrings #-} | ||
2 | module Network.BitTorrent.PeerWire.Protocol | ||
3 | ( | ||
4 | -- * Messages | ||
5 | Message(..) | ||
6 | , ppMessage | ||
7 | ) where | ||
8 | |||
9 | import Control.Applicative | ||
10 | import qualified Data.ByteString as B | ||
11 | import qualified Data.ByteString.Lazy as Lazy | ||
12 | import Data.Serialize | ||
13 | import Text.PrettyPrint | ||
14 | import Network | ||
15 | |||
16 | import Network.BitTorrent.PeerWire.Block | ||
17 | import Data.Bitfield | ||
18 | |||
19 | |||
20 | |||
21 | -- | Messages used in communication between peers. | ||
22 | -- | ||
23 | -- Note: If some extensions are disabled (not present in extension | ||
24 | -- mask) and client receive message used by the disabled | ||
25 | -- extension then the client MUST close the connection. | ||
26 | -- | ||
27 | data Message = KeepAlive | ||
28 | | Choke | ||
29 | | Unchoke | ||
30 | | Interested | ||
31 | | NotInterested | ||
32 | |||
33 | -- | Zero-based index of a piece that has just been | ||
34 | -- successfully downloaded and verified via the hash. | ||
35 | | Have !PieceIx | ||
36 | |||
37 | -- | The bitfield message may only be sent immediately | ||
38 | -- after the handshaking sequence is complete, and | ||
39 | -- before any other message are sent. If client have no | ||
40 | -- pieces then bitfield need not to be sent. | ||
41 | | Bitfield !Bitfield | ||
42 | |||
43 | -- | Request for a particular block. If a client is | ||
44 | -- requested a block that another peer do not have the | ||
45 | -- peer might not answer at all. | ||
46 | | Request !BlockIx | ||
47 | |||
48 | -- | Response for a request for a block. | ||
49 | | Piece !Block | ||
50 | |||
51 | -- | Used to cancel block requests. It is typically | ||
52 | -- used during "End Game". | ||
53 | | Cancel !BlockIx | ||
54 | |||
55 | | Port !PortNumber | ||
56 | |||
57 | -- | BEP 6: Then peer have all pieces it might send the | ||
58 | -- 'HaveAll' message instead of 'Bitfield' | ||
59 | -- message. Used to save bandwidth. | ||
60 | | HaveAll | ||
61 | |||
62 | -- | BEP 6: Then peer have no pieces it might send | ||
63 | -- 'HaveNone' message intead of 'Bitfield' | ||
64 | -- message. Used to save bandwidth. | ||
65 | | HaveNone | ||
66 | |||
67 | -- | BEP 6: This is an advisory message meaning "you | ||
68 | -- might like to download this piece." Used to avoid | ||
69 | -- excessive disk seeks and amount of IO. | ||
70 | | SuggestPiece !PieceIx | ||
71 | |||
72 | -- | BEP 6: Notifies a requesting peer that its request | ||
73 | -- will not be satisfied. | ||
74 | | RejectRequest !BlockIx | ||
75 | |||
76 | -- | BEP 6: This is an advisory messsage meaning "if | ||
77 | -- you ask for this piece, I'll give it to you even if | ||
78 | -- you're choked." Used to shorten starting phase. | ||
79 | | AllowedFast !PieceIx | ||
80 | deriving (Show, Eq) | ||
81 | |||
82 | |||
83 | instance Serialize Message where | ||
84 | get = do | ||
85 | len <- getInt | ||
86 | -- _ <- lookAhead $ ensure len | ||
87 | if len == 0 then return KeepAlive | ||
88 | else do | ||
89 | mid <- getWord8 | ||
90 | case mid of | ||
91 | 0x00 -> return Choke | ||
92 | 0x01 -> return Unchoke | ||
93 | 0x02 -> return Interested | ||
94 | 0x03 -> return NotInterested | ||
95 | 0x04 -> Have <$> getInt | ||
96 | 0x05 -> (Bitfield . fromBitmap) <$> getByteString (pred len) | ||
97 | 0x06 -> Request <$> get | ||
98 | 0x07 -> Piece <$> getBlock (len - 9) | ||
99 | 0x08 -> Cancel <$> get | ||
100 | 0x09 -> (Port . fromIntegral) <$> getWord16be | ||
101 | 0x0E -> return HaveAll | ||
102 | 0x0F -> return HaveNone | ||
103 | 0x0D -> SuggestPiece <$> getInt | ||
104 | 0x10 -> RejectRequest <$> get | ||
105 | 0x11 -> AllowedFast <$> getInt | ||
106 | _ -> do | ||
107 | rm <- remaining >>= getBytes | ||
108 | fail $ "unknown message ID: " ++ show mid ++ "\n" | ||
109 | ++ "remaining available bytes: " ++ show rm | ||
110 | |||
111 | where | ||
112 | getBlock :: Int -> Get Block | ||
113 | getBlock len = Block <$> getInt <*> getInt <*> getBytes len | ||
114 | {-# INLINE getBlock #-} | ||
115 | |||
116 | |||
117 | put KeepAlive = putInt 0 | ||
118 | put Choke = putInt 1 >> putWord8 0x00 | ||
119 | put Unchoke = putInt 1 >> putWord8 0x01 | ||
120 | put Interested = putInt 1 >> putWord8 0x02 | ||
121 | put NotInterested = putInt 1 >> putWord8 0x03 | ||
122 | put (Have i) = putInt 5 >> putWord8 0x04 >> putInt i | ||
123 | put (Bitfield bf) = putInt l >> putWord8 0x05 >> putLazyByteString b | ||
124 | where b = toBitmap bf | ||
125 | l = succ (fromIntegral (Lazy.length b)) | ||
126 | {-# INLINE l #-} | ||
127 | put (Request blk) = putInt 13 >> putWord8 0x06 >> put blk | ||
128 | put (Piece blk) = putInt l >> putWord8 0x07 >> putBlock | ||
129 | where l = 9 + B.length (blkData blk) | ||
130 | {-# INLINE l #-} | ||
131 | putBlock = do putInt (blkPiece blk) | ||
132 | putInt (blkOffset blk) | ||
133 | putByteString (blkData blk) | ||
134 | {-# INLINE putBlock #-} | ||
135 | |||
136 | put (Cancel blk) = putInt 13 >> putWord8 0x08 >> put blk | ||
137 | put (Port p ) = putInt 3 >> putWord8 0x09 >> putWord16be (fromIntegral p) | ||
138 | put HaveAll = putInt 1 >> putWord8 0x0E | ||
139 | put HaveNone = putInt 1 >> putWord8 0x0F | ||
140 | put (SuggestPiece pix) = putInt 5 >> putWord8 0x0D >> putInt pix | ||
141 | put (RejectRequest ix) = putInt 13 >> putWord8 0x10 >> put ix | ||
142 | put (AllowedFast ix) = putInt 5 >> putWord8 0x11 >> putInt ix | ||
143 | |||
144 | |||
145 | -- | Format messages in human readable form. Note that output is | ||
146 | -- compact and suitable for logging: only useful information but not | ||
147 | -- payload bytes. | ||
148 | -- | ||
149 | ppMessage :: Message -> Doc | ||
150 | ppMessage (Bitfield _) = "Bitfield" | ||
151 | ppMessage (Piece blk) = "Piece" <+> ppBlock blk | ||
152 | ppMessage (Cancel ix) = "Cancel" <+> ppBlockIx ix | ||
153 | ppMessage (SuggestPiece pix) = "Suggest" <+> int pix | ||
154 | ppMessage (RejectRequest ix) = "Reject" <+> ppBlockIx ix | ||
155 | ppMessage msg = text (show msg) \ No newline at end of file | ||