diff options
author | Sam T <pxqr.sta@gmail.com> | 2013-06-08 02:00:25 +0400 |
---|---|---|
committer | Sam T <pxqr.sta@gmail.com> | 2013-06-08 02:00:25 +0400 |
commit | a548a0ec725ddc3cd1d3c4407f8e2e7210d44f83 (patch) | |
tree | d492af992467622d593d54b989e9a9ae54f84b01 /src/Network/BitTorrent/Exchange/Protocol.hs | |
parent | 279433f8d80f829b9fad6b7e2e60db4f21dfc3ec (diff) |
~ Rename PeerWire to Exchange.
Diffstat (limited to 'src/Network/BitTorrent/Exchange/Protocol.hs')
-rw-r--r-- | src/Network/BitTorrent/Exchange/Protocol.hs | 387 |
1 files changed, 387 insertions, 0 deletions
diff --git a/src/Network/BitTorrent/Exchange/Protocol.hs b/src/Network/BitTorrent/Exchange/Protocol.hs new file mode 100644 index 00000000..cab54ef5 --- /dev/null +++ b/src/Network/BitTorrent/Exchange/Protocol.hs | |||
@@ -0,0 +1,387 @@ | |||
1 | -- | | ||
2 | -- Copyright : (c) Sam T. 2013 | ||
3 | -- License : MIT | ||
4 | -- Maintainer : pxqr.sta@gmail.com | ||
5 | -- Stability : experimental | ||
6 | -- Portability : portable | ||
7 | -- | ||
8 | -- In order to establish the connection between peers we should send | ||
9 | -- 'Handshake' message. The 'Handshake' is a required message and | ||
10 | -- must be the first message transmitted by the peer to the another | ||
11 | -- peer. | ||
12 | -- | ||
13 | {-# LANGUAGE OverloadedStrings #-} | ||
14 | {-# LANGUAGE RecordWildCards #-} | ||
15 | module Network.BitTorrent.PeerWire.Protocol | ||
16 | ( -- * Inital handshake | ||
17 | Handshake(..), ppHandshake | ||
18 | , handshake , handshakeCaps | ||
19 | |||
20 | -- ** Defaults | ||
21 | , defaultHandshake, defaultBTProtocol, defaultReserved | ||
22 | , handshakeMaxSize | ||
23 | |||
24 | -- * Block | ||
25 | , PieceIx, BlockLIx, PieceLIx | ||
26 | , BlockIx(..), ppBlockIx | ||
27 | , Block(..), ppBlock ,blockSize | ||
28 | , pieceIx, blockIx | ||
29 | , blockRange, ixRange, isPiece | ||
30 | |||
31 | -- ** Defaults | ||
32 | , defaultBlockSize | ||
33 | |||
34 | -- * Regular messages | ||
35 | , Message(..) | ||
36 | , ppMessage | ||
37 | ) where | ||
38 | |||
39 | import Control.Applicative | ||
40 | import Control.Monad | ||
41 | import Control.Exception | ||
42 | import Data.ByteString (ByteString) | ||
43 | import qualified Data.ByteString as B | ||
44 | import qualified Data.ByteString.Char8 as BC | ||
45 | import qualified Data.ByteString.Lazy as Lazy | ||
46 | import Data.Serialize as S | ||
47 | import Data.Int | ||
48 | import Data.Word | ||
49 | import Text.PrettyPrint | ||
50 | |||
51 | import Network | ||
52 | import Network.Socket.ByteString | ||
53 | |||
54 | import Data.Bitfield | ||
55 | import Data.Torrent | ||
56 | import Network.BitTorrent.Extension | ||
57 | import Network.BitTorrent.Peer | ||
58 | |||
59 | |||
60 | |||
61 | {----------------------------------------------------------------------- | ||
62 | Handshake | ||
63 | -----------------------------------------------------------------------} | ||
64 | |||
65 | data Handshake = Handshake { | ||
66 | -- | Identifier of the protocol. | ||
67 | hsProtocol :: ByteString | ||
68 | |||
69 | -- | Reserved bytes used to specify supported BEP's. | ||
70 | , hsReserved :: Capabilities | ||
71 | |||
72 | -- | Info hash of the info part of the metainfo file. that is | ||
73 | -- transmitted in tracker requests. Info hash of the initiator | ||
74 | -- handshake and response handshake should match, otherwise | ||
75 | -- initiator should break the connection. | ||
76 | -- | ||
77 | , hsInfoHash :: InfoHash | ||
78 | |||
79 | -- | Peer id of the initiator. This is usually the same peer id | ||
80 | -- that is transmitted in tracker requests. | ||
81 | -- | ||
82 | , hsPeerID :: PeerID | ||
83 | |||
84 | } deriving (Show, Eq) | ||
85 | |||
86 | instance Serialize Handshake where | ||
87 | put hs = do | ||
88 | putWord8 (fromIntegral (B.length (hsProtocol hs))) | ||
89 | putByteString (hsProtocol hs) | ||
90 | putWord64be (hsReserved hs) | ||
91 | put (hsInfoHash hs) | ||
92 | put (hsPeerID hs) | ||
93 | |||
94 | get = do | ||
95 | len <- getWord8 | ||
96 | Handshake <$> getBytes (fromIntegral len) | ||
97 | <*> getWord64be | ||
98 | <*> get | ||
99 | <*> get | ||
100 | |||
101 | |||
102 | handshakeCaps :: Handshake -> Capabilities | ||
103 | handshakeCaps = hsReserved | ||
104 | |||
105 | -- | Format handshake in human readable form. | ||
106 | ppHandshake :: Handshake -> Doc | ||
107 | ppHandshake Handshake {..} = | ||
108 | text (BC.unpack hsProtocol) <+> ppClientInfo (clientInfo hsPeerID) | ||
109 | |||
110 | -- | Get handshake message size in bytes from the length of protocol string. | ||
111 | handshakeSize :: Word8 -> Int | ||
112 | handshakeSize n = 1 + fromIntegral n + 8 + 20 + 20 | ||
113 | |||
114 | -- | Maximum size of handshake message in bytes. | ||
115 | handshakeMaxSize :: Int | ||
116 | handshakeMaxSize = handshakeSize 255 | ||
117 | |||
118 | -- | Default protocol string "BitTorrent protocol" as is. | ||
119 | defaultBTProtocol :: ByteString | ||
120 | defaultBTProtocol = "BitTorrent protocol" | ||
121 | |||
122 | -- | Default reserved word is 0. | ||
123 | defaultReserved :: Word64 | ||
124 | defaultReserved = 0 | ||
125 | |||
126 | -- | Length of info hash and peer id is unchecked, so it /should/ be equal 20. | ||
127 | defaultHandshake :: InfoHash -> PeerID -> Handshake | ||
128 | defaultHandshake = Handshake defaultBTProtocol defaultReserved | ||
129 | |||
130 | -- | Handshaking with a peer specified by the second argument. | ||
131 | handshake :: Socket -> Handshake -> IO Handshake | ||
132 | handshake sock hs = do | ||
133 | sendAll sock (S.encode hs) | ||
134 | |||
135 | header <- recv sock 1 | ||
136 | when (B.length header == 0) $ | ||
137 | throw $ userError "Unable to receive handshake." | ||
138 | |||
139 | let protocolLen = B.head header | ||
140 | let restLen = handshakeSize protocolLen - 1 | ||
141 | body <- recv sock restLen | ||
142 | let resp = B.cons protocolLen body | ||
143 | |||
144 | case checkIH (S.decode resp) of | ||
145 | Right hs' -> return hs' | ||
146 | Left msg -> throw $ userError msg | ||
147 | where | ||
148 | checkIH (Right hs') | ||
149 | | hsInfoHash hs /= hsInfoHash hs' | ||
150 | = Left "Handshake info hash do not match." | ||
151 | checkIH x = x | ||
152 | |||
153 | {----------------------------------------------------------------------- | ||
154 | Blocks | ||
155 | -----------------------------------------------------------------------} | ||
156 | |||
157 | type BlockLIx = Int | ||
158 | type PieceLIx = Int | ||
159 | |||
160 | |||
161 | data BlockIx = BlockIx { | ||
162 | -- | Zero-based piece index. | ||
163 | ixPiece :: {-# UNPACK #-} !PieceLIx | ||
164 | |||
165 | -- | Zero-based byte offset within the piece. | ||
166 | , ixOffset :: {-# UNPACK #-} !Int | ||
167 | |||
168 | -- | Block size starting from offset. | ||
169 | , ixLength :: {-# UNPACK #-} !Int | ||
170 | } deriving (Show, Eq) | ||
171 | |||
172 | getInt :: Get Int | ||
173 | getInt = fromIntegral <$> getWord32be | ||
174 | {-# INLINE getInt #-} | ||
175 | |||
176 | putInt :: Putter Int | ||
177 | putInt = putWord32be . fromIntegral | ||
178 | {-# INLINE putInt #-} | ||
179 | |||
180 | instance Serialize BlockIx where | ||
181 | {-# SPECIALIZE instance Serialize BlockIx #-} | ||
182 | get = BlockIx <$> getInt <*> getInt <*> getInt | ||
183 | {-# INLINE get #-} | ||
184 | |||
185 | put ix = do putInt (ixPiece ix) | ||
186 | putInt (ixOffset ix) | ||
187 | putInt (ixLength ix) | ||
188 | {-# INLINE put #-} | ||
189 | |||
190 | ppBlockIx :: BlockIx -> Doc | ||
191 | ppBlockIx BlockIx {..} = | ||
192 | "piece = " <> int ixPiece <> "," <+> | ||
193 | "offset = " <> int ixOffset <> "," <+> | ||
194 | "length = " <> int ixLength | ||
195 | |||
196 | data Block = Block { | ||
197 | -- | Zero-based piece index. | ||
198 | blkPiece :: !PieceLIx | ||
199 | |||
200 | -- | Zero-based byte offset within the piece. | ||
201 | , blkOffset :: !Int | ||
202 | |||
203 | -- | Payload. | ||
204 | , blkData :: !ByteString | ||
205 | } deriving (Show, Eq) | ||
206 | |||
207 | ppBlock :: Block -> Doc | ||
208 | ppBlock = ppBlockIx . blockIx | ||
209 | |||
210 | blockSize :: Block -> Int | ||
211 | blockSize blk = B.length (blkData blk) | ||
212 | |||
213 | -- | Widely used semi-official block size. | ||
214 | defaultBlockSize :: Int | ||
215 | defaultBlockSize = 16 * 1024 | ||
216 | |||
217 | |||
218 | isPiece :: Int -> Block -> Bool | ||
219 | isPiece pieceSize (Block i offset bs) = | ||
220 | offset == 0 && B.length bs == pieceSize && i >= 0 | ||
221 | {-# INLINE isPiece #-} | ||
222 | |||
223 | pieceIx :: Int -> Int -> BlockIx | ||
224 | pieceIx i = BlockIx i 0 | ||
225 | {-# INLINE pieceIx #-} | ||
226 | |||
227 | blockIx :: Block -> BlockIx | ||
228 | blockIx = BlockIx <$> blkPiece <*> blkOffset <*> B.length . blkData | ||
229 | |||
230 | blockRange :: (Num a, Integral a) => Int -> Block -> (a, a) | ||
231 | blockRange pieceSize blk = (offset, offset + len) | ||
232 | where | ||
233 | offset = fromIntegral pieceSize * fromIntegral (blkPiece blk) | ||
234 | + fromIntegral (blkOffset blk) | ||
235 | len = fromIntegral (B.length (blkData blk)) | ||
236 | {-# INLINE blockRange #-} | ||
237 | {-# SPECIALIZE blockRange :: Int -> Block -> (Int64, Int64) #-} | ||
238 | |||
239 | ixRange :: (Num a, Integral a) => Int -> BlockIx -> (a, a) | ||
240 | ixRange pieceSize ix = (offset, offset + len) | ||
241 | where | ||
242 | offset = fromIntegral pieceSize * fromIntegral (ixPiece ix) | ||
243 | + fromIntegral (ixOffset ix) | ||
244 | len = fromIntegral (ixLength ix) | ||
245 | {-# INLINE ixRange #-} | ||
246 | {-# SPECIALIZE ixRange :: Int -> BlockIx -> (Int64, Int64) #-} | ||
247 | |||
248 | |||
249 | {----------------------------------------------------------------------- | ||
250 | Handshake | ||
251 | -----------------------------------------------------------------------} | ||
252 | |||
253 | -- | Messages used in communication between peers. | ||
254 | -- | ||
255 | -- Note: If some extensions are disabled (not present in extension | ||
256 | -- mask) and client receive message used by the disabled | ||
257 | -- extension then the client MUST close the connection. | ||
258 | -- | ||
259 | data Message = KeepAlive | ||
260 | | Choke | ||
261 | | Unchoke | ||
262 | | Interested | ||
263 | | NotInterested | ||
264 | |||
265 | -- | Zero-based index of a piece that has just been | ||
266 | -- successfully downloaded and verified via the hash. | ||
267 | | Have !PieceIx | ||
268 | |||
269 | -- | The bitfield message may only be sent immediately | ||
270 | -- after the handshaking sequence is complete, and | ||
271 | -- before any other message are sent. If client have no | ||
272 | -- pieces then bitfield need not to be sent. | ||
273 | | Bitfield !Bitfield | ||
274 | |||
275 | -- | Request for a particular block. If a client is | ||
276 | -- requested a block that another peer do not have the | ||
277 | -- peer might not answer at all. | ||
278 | | Request !BlockIx | ||
279 | |||
280 | -- | Response for a request for a block. | ||
281 | | Piece !Block | ||
282 | |||
283 | -- | Used to cancel block requests. It is typically | ||
284 | -- used during "End Game". | ||
285 | | Cancel !BlockIx | ||
286 | |||
287 | | Port !PortNumber | ||
288 | |||
289 | -- | BEP 6: Then peer have all pieces it might send the | ||
290 | -- 'HaveAll' message instead of 'Bitfield' | ||
291 | -- message. Used to save bandwidth. | ||
292 | | HaveAll | ||
293 | |||
294 | -- | BEP 6: Then peer have no pieces it might send | ||
295 | -- 'HaveNone' message intead of 'Bitfield' | ||
296 | -- message. Used to save bandwidth. | ||
297 | | HaveNone | ||
298 | |||
299 | -- | BEP 6: This is an advisory message meaning "you | ||
300 | -- might like to download this piece." Used to avoid | ||
301 | -- excessive disk seeks and amount of IO. | ||
302 | | SuggestPiece !PieceIx | ||
303 | |||
304 | -- | BEP 6: Notifies a requesting peer that its request | ||
305 | -- will not be satisfied. | ||
306 | | RejectRequest !BlockIx | ||
307 | |||
308 | -- | BEP 6: This is an advisory messsage meaning "if | ||
309 | -- you ask for this piece, I'll give it to you even if | ||
310 | -- you're choked." Used to shorten starting phase. | ||
311 | | AllowedFast !PieceIx | ||
312 | deriving (Show, Eq) | ||
313 | |||
314 | |||
315 | instance Serialize Message where | ||
316 | get = do | ||
317 | len <- getInt | ||
318 | -- _ <- lookAhead $ ensure len | ||
319 | if len == 0 then return KeepAlive | ||
320 | else do | ||
321 | mid <- getWord8 | ||
322 | case mid of | ||
323 | 0x00 -> return Choke | ||
324 | 0x01 -> return Unchoke | ||
325 | 0x02 -> return Interested | ||
326 | 0x03 -> return NotInterested | ||
327 | 0x04 -> Have <$> getInt | ||
328 | 0x05 -> (Bitfield . fromBitmap) <$> getByteString (pred len) | ||
329 | 0x06 -> Request <$> get | ||
330 | 0x07 -> Piece <$> getBlock (len - 9) | ||
331 | 0x08 -> Cancel <$> get | ||
332 | 0x09 -> (Port . fromIntegral) <$> getWord16be | ||
333 | 0x0E -> return HaveAll | ||
334 | 0x0F -> return HaveNone | ||
335 | 0x0D -> SuggestPiece <$> getInt | ||
336 | 0x10 -> RejectRequest <$> get | ||
337 | 0x11 -> AllowedFast <$> getInt | ||
338 | _ -> do | ||
339 | rm <- remaining >>= getBytes | ||
340 | fail $ "unknown message ID: " ++ show mid ++ "\n" | ||
341 | ++ "remaining available bytes: " ++ show rm | ||
342 | |||
343 | where | ||
344 | getBlock :: Int -> Get Block | ||
345 | getBlock len = Block <$> getInt <*> getInt <*> getBytes len | ||
346 | {-# INLINE getBlock #-} | ||
347 | |||
348 | |||
349 | put KeepAlive = putInt 0 | ||
350 | put Choke = putInt 1 >> putWord8 0x00 | ||
351 | put Unchoke = putInt 1 >> putWord8 0x01 | ||
352 | put Interested = putInt 1 >> putWord8 0x02 | ||
353 | put NotInterested = putInt 1 >> putWord8 0x03 | ||
354 | put (Have i) = putInt 5 >> putWord8 0x04 >> putInt i | ||
355 | put (Bitfield bf) = putInt l >> putWord8 0x05 >> putLazyByteString b | ||
356 | where b = toBitmap bf | ||
357 | l = succ (fromIntegral (Lazy.length b)) | ||
358 | {-# INLINE l #-} | ||
359 | put (Request blk) = putInt 13 >> putWord8 0x06 >> put blk | ||
360 | put (Piece blk) = putInt l >> putWord8 0x07 >> putBlock | ||
361 | where l = 9 + B.length (blkData blk) | ||
362 | {-# INLINE l #-} | ||
363 | putBlock = do putInt (blkPiece blk) | ||
364 | putInt (blkOffset blk) | ||
365 | putByteString (blkData blk) | ||
366 | {-# INLINE putBlock #-} | ||
367 | |||
368 | put (Cancel blk) = putInt 13 >> putWord8 0x08 >> put blk | ||
369 | put (Port p ) = putInt 3 >> putWord8 0x09 >> putWord16be (fromIntegral p) | ||
370 | put HaveAll = putInt 1 >> putWord8 0x0E | ||
371 | put HaveNone = putInt 1 >> putWord8 0x0F | ||
372 | put (SuggestPiece pix) = putInt 5 >> putWord8 0x0D >> putInt pix | ||
373 | put (RejectRequest ix) = putInt 13 >> putWord8 0x10 >> put ix | ||
374 | put (AllowedFast ix) = putInt 5 >> putWord8 0x11 >> putInt ix | ||
375 | |||
376 | |||
377 | -- | Format messages in human readable form. Note that output is | ||
378 | -- compact and suitable for logging: only useful information but not | ||
379 | -- payload bytes. | ||
380 | -- | ||
381 | ppMessage :: Message -> Doc | ||
382 | ppMessage (Bitfield _) = "Bitfield" | ||
383 | ppMessage (Piece blk) = "Piece" <+> ppBlock blk | ||
384 | ppMessage (Cancel ix) = "Cancel" <+> ppBlockIx ix | ||
385 | ppMessage (SuggestPiece pix) = "Suggest" <+> int pix | ||
386 | ppMessage (RejectRequest ix) = "Reject" <+> ppBlockIx ix | ||
387 | ppMessage msg = text (show msg) \ No newline at end of file | ||