diff options
-rw-r--r-- | bittorrent.cabal | 4 | ||||
-rw-r--r-- | src/Network/BitTorrent/Exchange/Message.hs | 184 | ||||
-rw-r--r-- | src/Network/BitTorrent/Exchange/Message/Extended.hs | 51 |
3 files changed, 167 insertions, 72 deletions
diff --git a/bittorrent.cabal b/bittorrent.cabal index c9005f69..a7441eb8 100644 --- a/bittorrent.cabal +++ b/bittorrent.cabal | |||
@@ -60,9 +60,9 @@ library | |||
60 | -- , Network.BitTorrent.DHT.Session | 60 | -- , Network.BitTorrent.DHT.Session |
61 | -- , Network.BitTorrent.Exchange | 61 | -- , Network.BitTorrent.Exchange |
62 | -- , Network.BitTorrent.Exchange.Assembler | 62 | -- , Network.BitTorrent.Exchange.Assembler |
63 | -- , Network.BitTorrent.Exchange.Message | 63 | , Network.BitTorrent.Exchange.Message |
64 | -- , Network.BitTorrent.Exchange.Session | 64 | -- , Network.BitTorrent.Exchange.Session |
65 | -- , Network.BitTorrent.Exchange.Status | 65 | , Network.BitTorrent.Exchange.Status |
66 | -- , Network.BitTorrent.Exchange.Wire | 66 | -- , Network.BitTorrent.Exchange.Wire |
67 | -- , Network.BitTorrent.Extension | 67 | -- , Network.BitTorrent.Extension |
68 | -- , Network.BitTorrent.Tracker | 68 | -- , Network.BitTorrent.Tracker |
diff --git a/src/Network/BitTorrent/Exchange/Message.hs b/src/Network/BitTorrent/Exchange/Message.hs index 6f649030..0a535517 100644 --- a/src/Network/BitTorrent/Exchange/Message.hs +++ b/src/Network/BitTorrent/Exchange/Message.hs | |||
@@ -25,8 +25,9 @@ | |||
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 TemplateHaskell #-} | 28 | {-# LANGUAGE TemplateHaskell #-} |
29 | {-# OPTIONS -fno-warn-orphans #-} | 29 | {-# LANGUAGE DeriveDataTypeable #-} |
30 | {-# OPTIONS -fno-warn-orphans #-} | ||
30 | module Network.BitTorrent.Exchange.Message | 31 | module Network.BitTorrent.Exchange.Message |
31 | ( -- * Extensions | 32 | ( -- * Extensions |
32 | Extension (..) | 33 | Extension (..) |
@@ -51,24 +52,37 @@ module Network.BitTorrent.Exchange.Message | |||
51 | , Message (..) | 52 | , Message (..) |
52 | , StatusUpdate (..) | 53 | , StatusUpdate (..) |
53 | , RegularMessage (..) | 54 | , RegularMessage (..) |
55 | |||
56 | -- * Fast extension | ||
54 | , FastMessage (..) | 57 | , FastMessage (..) |
58 | |||
59 | -- * Extension protocol | ||
60 | , ExtendedExtension | ||
61 | , ExtendedCaps (..) | ||
62 | , ExtendedHandshake (..) | ||
63 | , ExtendedMessage (..) | ||
55 | ) where | 64 | ) where |
56 | 65 | ||
57 | import Control.Applicative | 66 | import Control.Applicative |
58 | import Control.Exception | 67 | import Control.Exception |
59 | import Control.Monad | 68 | import Control.Monad |
69 | import Data.BEncode as BE | ||
60 | import Data.Bits | 70 | import Data.Bits |
61 | import Data.ByteString as BS | 71 | import Data.ByteString as BS |
62 | import Data.ByteString.Char8 as BC | 72 | import Data.ByteString.Char8 as BC |
63 | import Data.ByteString.Lazy as BL | 73 | import Data.ByteString.Lazy as BL |
64 | import Data.Default | 74 | import Data.Default |
75 | import Data.IntMap as IM | ||
65 | import Data.List as L | 76 | import Data.List as L |
66 | import Data.Monoid | 77 | import Data.Monoid |
67 | import Data.Serialize as S | 78 | import Data.Serialize as S |
79 | import Data.Text as T | ||
80 | import Data.Typeable | ||
68 | import Data.Word | 81 | import Data.Word |
69 | import Network | 82 | import Network |
70 | import Network.Socket.ByteString | 83 | import Network.Socket hiding (KeepAlive) |
71 | import Text.PrettyPrint | 84 | import Network.Socket.ByteString as BS |
85 | import Text.PrettyPrint as PP | ||
72 | import Text.PrettyPrint.Class | 86 | import Text.PrettyPrint.Class |
73 | 87 | ||
74 | import Data.Torrent.Bitfield | 88 | import Data.Torrent.Bitfield |
@@ -85,17 +99,20 @@ import Network.BitTorrent.Core.PeerAddr () | |||
85 | -- information. | 99 | -- information. |
86 | -- | 100 | -- |
87 | data Extension | 101 | data Extension |
88 | = ExtDHT -- ^ BEP 5 | 102 | = ExtDHT -- ^ BEP 5 |
89 | | ExtFast -- ^ BEP 6 | 103 | | ExtFast -- ^ BEP 6 |
104 | | ExtExtended -- ^ BEP 10 | ||
90 | deriving (Show, Eq, Ord, Enum, Bounded) | 105 | deriving (Show, Eq, Ord, Enum, Bounded) |
91 | 106 | ||
92 | instance Pretty Extension where | 107 | instance Pretty Extension where |
93 | pretty ExtDHT = "DHT" | 108 | pretty ExtDHT = "DHT" |
94 | pretty ExtFast = "Fast Extension" | 109 | pretty ExtFast = "Fast Extension" |
110 | pretty ExtExtended = "Extension Protocol" | ||
95 | 111 | ||
96 | capMask :: Extension -> Caps | 112 | capMask :: Extension -> Caps |
97 | capMask ExtDHT = Caps 0x01 | 113 | capMask ExtDHT = Caps 0x01 |
98 | capMask ExtFast = Caps 0x04 | 114 | capMask ExtFast = Caps 0x04 |
115 | capMask ExtExtended = Caps 0x100000 | ||
99 | 116 | ||
100 | {----------------------------------------------------------------------- | 117 | {----------------------------------------------------------------------- |
101 | -- Capabilities | 118 | -- Capabilities |
@@ -208,14 +225,14 @@ sendHandshake sock hs = sendAll sock (S.encode hs) | |||
208 | 225 | ||
209 | recvHandshake :: Socket -> IO Handshake | 226 | recvHandshake :: Socket -> IO Handshake |
210 | recvHandshake sock = do | 227 | recvHandshake sock = do |
211 | header <- recv sock 1 | 228 | header <- BS.recv sock 1 |
212 | unless (BS.length header == 1) $ | 229 | unless (BS.length header == 1) $ |
213 | throw $ userError "Unable to receive handshake header." | 230 | throw $ userError "Unable to receive handshake header." |
214 | 231 | ||
215 | let protocolLen = BS.head header | 232 | let protocolLen = BS.head header |
216 | let restLen = handshakeSize protocolLen - 1 | 233 | let restLen = handshakeSize protocolLen - 1 |
217 | 234 | ||
218 | body <- recv sock restLen | 235 | body <- BS.recv sock restLen |
219 | let resp = BS.cons protocolLen body | 236 | let resp = BS.cons protocolLen body |
220 | either (throwIO . userError) return $ S.decode resp | 237 | either (throwIO . userError) return $ S.decode resp |
221 | 238 | ||
@@ -312,6 +329,101 @@ instance Pretty FastMessage where | |||
312 | pretty (RejectRequest bix) = "Reject" <+> pretty bix | 329 | pretty (RejectRequest bix) = "Reject" <+> pretty bix |
313 | pretty (AllowedFast pix) = "Allowed fast" <+> int pix | 330 | pretty (AllowedFast pix) = "Allowed fast" <+> int pix |
314 | 331 | ||
332 | {----------------------------------------------------------------------- | ||
333 | -- Extended messages | ||
334 | -----------------------------------------------------------------------} | ||
335 | |||
336 | type ExtendedExtension = () | ||
337 | |||
338 | type ExtendedMessageId = Word8 | ||
339 | |||
340 | type ExtendedIdMap = IntMap | ||
341 | |||
342 | -- | The extension IDs must be stored for every peer, becuase every | ||
343 | -- peer may have different IDs for the same extension. | ||
344 | -- | ||
345 | newtype ExtendedCaps = ExtendedCaps | ||
346 | { extendedCaps :: ExtendedIdMap ExtendedExtension | ||
347 | } deriving (Show, Eq) | ||
348 | |||
349 | instance BEncode ExtendedCaps where | ||
350 | fromBEncode = undefined | ||
351 | toBEncode = undefined | ||
352 | |||
353 | -- | This message should be sent immediately after the standard | ||
354 | -- bittorrent handshake to any peer that supports this extension | ||
355 | -- protocol. Extended handshakes can be sent more than once, however | ||
356 | -- an implementation may choose to ignore subsequent handshake | ||
357 | -- messages. | ||
358 | -- | ||
359 | data ExtendedHandshake = ExtendedHandshake | ||
360 | { -- | If this peer has an IPv4 interface, this is the compact | ||
361 | -- representation of that address. | ||
362 | ehsIPv4 :: Maybe HostAddress | ||
363 | |||
364 | -- | If this peer has an IPv6 interface, this is the compact | ||
365 | -- representation of that address. | ||
366 | , ehsIPv6 :: Maybe HostAddress6 | ||
367 | |||
368 | -- | Dictionary of supported extension messages which maps names | ||
369 | -- of extensions to an extended message ID for each extension | ||
370 | -- message. | ||
371 | , ehsCaps :: ExtendedCaps | ||
372 | |||
373 | -- | Local TCP /listen/ port. Allows each side to learn about the | ||
374 | -- TCP port number of the other side. | ||
375 | , ehsPort :: Maybe PortNumber | ||
376 | |||
377 | -- | Request queue the number of outstanding 'Request' messages | ||
378 | -- this client supports without dropping any. | ||
379 | , ehsQueueLength :: Maybe Int | ||
380 | |||
381 | -- | Client name and version. | ||
382 | , ehsVersion :: Maybe Text | ||
383 | |||
384 | -- -- | | ||
385 | -- , yourip :: Maybe (Either HostAddress HostAddress6) | ||
386 | } deriving (Show, Eq, Typeable) | ||
387 | |||
388 | instance BEncode ExtendedHandshake where | ||
389 | toBEncode ExtendedHandshake {..} = toDict $ | ||
390 | "ipv4" .=? ehsIPv4 | ||
391 | .: "ipv6" .=? ehsIPv6 | ||
392 | .: "m" .=! ehsCaps | ||
393 | .: "p" .=? ehsPort | ||
394 | .: "reqq" .=? ehsQueueLength | ||
395 | .: "v" .=? ehsVersion | ||
396 | -- .: "yourip" .=? yourip | ||
397 | .: endDict | ||
398 | |||
399 | fromBEncode = fromDict $ ExtendedHandshake | ||
400 | <$>? "ipv4" | ||
401 | <*>? "ipv6" | ||
402 | <*>! "m" | ||
403 | <*>? "p" | ||
404 | <*>? "reqq" | ||
405 | <*>? "v" | ||
406 | -- <*>? "yourip" | ||
407 | |||
408 | instance Pretty ExtendedHandshake where | ||
409 | pretty = PP.text . show | ||
410 | |||
411 | -- | For more info see <http://www.bittorrent.org/beps/bep_0010.html> | ||
412 | data ExtendedMessage | ||
413 | = EHandshake ExtendedHandshake | ||
414 | | EUnknown ExtendedMessageId BS.ByteString | ||
415 | deriving (Show, Eq) | ||
416 | |||
417 | instance Pretty ExtendedMessage where | ||
418 | pretty (EHandshake ehs) = pretty ehs | ||
419 | pretty (EUnknown mid _) = "Unknown" <+> PP.text (show mid) | ||
420 | |||
421 | {----------------------------------------------------------------------- | ||
422 | -- The message datatype | ||
423 | -----------------------------------------------------------------------} | ||
424 | |||
425 | type MessageId = Word8 | ||
426 | |||
315 | -- | Messages used in communication between peers. | 427 | -- | Messages used in communication between peers. |
316 | -- | 428 | -- |
317 | -- Note: If some extensions are disabled (not present in extension | 429 | -- Note: If some extensions are disabled (not present in extension |
@@ -327,6 +439,7 @@ data Message | |||
327 | -- extensions | 439 | -- extensions |
328 | | Port !PortNumber | 440 | | Port !PortNumber |
329 | | Fast !FastMessage | 441 | | Fast !FastMessage |
442 | | Extended !ExtendedMessage | ||
330 | deriving (Show, Eq) | 443 | deriving (Show, Eq) |
331 | 444 | ||
332 | instance Default Message where | 445 | instance Default Message where |
@@ -340,6 +453,17 @@ instance Pretty Message where | |||
340 | pretty (Regular m) = pretty m | 453 | pretty (Regular m) = pretty m |
341 | pretty (Port p) = "Port" <+> int (fromEnum p) | 454 | pretty (Port p) = "Port" <+> int (fromEnum p) |
342 | pretty (Fast m) = pretty m | 455 | pretty (Fast m) = pretty m |
456 | pretty (Extended m) = pretty m | ||
457 | |||
458 | -- | Can be used to check if this message is allowed to send\/recv in | ||
459 | -- current session. | ||
460 | requires :: Message -> Maybe Extension | ||
461 | requires KeepAlive = Nothing | ||
462 | requires (Status _) = Nothing | ||
463 | requires (Regular _) = Nothing | ||
464 | requires (Port _) = Just ExtDHT | ||
465 | requires (Fast _) = Just ExtFast | ||
466 | requires (Extended _) = Just ExtExtended | ||
343 | 467 | ||
344 | getInt :: S.Get Int | 468 | getInt :: S.Get Int |
345 | getInt = fromIntegral <$> S.getWord32be | 469 | getInt = fromIntegral <$> S.getWord32be |
@@ -372,6 +496,7 @@ instance Serialize Message where | |||
372 | 0x0F -> return $ Fast HaveNone | 496 | 0x0F -> return $ Fast HaveNone |
373 | 0x10 -> (Fast . RejectRequest) <$> S.get | 497 | 0x10 -> (Fast . RejectRequest) <$> S.get |
374 | 0x11 -> (Fast . AllowedFast) <$> getInt | 498 | 0x11 -> (Fast . AllowedFast) <$> getInt |
499 | 0x14 -> Extended <$> getExtendedMessage (pred len) | ||
375 | _ -> do | 500 | _ -> do |
376 | rm <- S.remaining >>= S.getBytes | 501 | rm <- S.remaining >>= S.getBytes |
377 | fail $ "unknown message ID: " ++ show mid ++ "\n" | 502 | fail $ "unknown message ID: " ++ show mid ++ "\n" |
@@ -388,6 +513,7 @@ instance Serialize Message where | |||
388 | put (Regular msg) = putRegular msg | 513 | put (Regular msg) = putRegular msg |
389 | put (Port p ) = putPort p | 514 | put (Port p ) = putPort p |
390 | put (Fast msg) = putFast msg | 515 | put (Fast msg) = putFast msg |
516 | put (Extended m ) = putExtendedMessage m | ||
391 | 517 | ||
392 | putStatus :: Putter StatusUpdate | 518 | putStatus :: Putter StatusUpdate |
393 | putStatus su = putInt 1 >> S.putWord8 (fromIntegral (fromEnum su)) | 519 | putStatus su = putInt 1 >> S.putWord8 (fromIntegral (fromEnum su)) |
@@ -418,10 +544,30 @@ putFast (SuggestPiece pix) = putInt 5 >> S.putWord8 0x0D >> putInt pix | |||
418 | putFast (RejectRequest i ) = putInt 13 >> S.putWord8 0x10 >> S.put i | 544 | putFast (RejectRequest i ) = putInt 13 >> S.putWord8 0x10 >> S.put i |
419 | putFast (AllowedFast i ) = putInt 5 >> S.putWord8 0x11 >> putInt i | 545 | putFast (AllowedFast i ) = putInt 5 >> S.putWord8 0x11 >> putInt i |
420 | 546 | ||
421 | 547 | getExtendedHandshake :: Int -> S.Get ExtendedHandshake | |
422 | requires :: Message -> Maybe Extension | 548 | getExtendedHandshake messageSize = do |
423 | requires KeepAlive = Nothing | 549 | bs <- getByteString messageSize |
424 | requires (Status _) = Nothing | 550 | either fail pure $ BE.decode bs |
425 | requires (Regular _) = Nothing | 551 | |
426 | requires (Port _) = Just ExtDHT | 552 | getExtendedMessage :: Int -> S.Get ExtendedMessage |
427 | requires (Fast _) = Just ExtFast \ No newline at end of file | 553 | getExtendedMessage messageSize = do |
554 | msgId <- getWord8 | ||
555 | let msgBodySize = messageSize - 1 | ||
556 | case msgId of | ||
557 | 0 -> EHandshake <$> getExtendedHandshake msgBodySize | ||
558 | _ -> EUnknown msgId <$> getByteString msgBodySize | ||
559 | |||
560 | extendedMessageId :: MessageId | ||
561 | extendedMessageId = 20 | ||
562 | |||
563 | -- NOTE: in contrast to getExtendedMessage this function put length | ||
564 | -- and message id too! | ||
565 | putExtendedMessage :: ExtendedMessage -> S.Put | ||
566 | putExtendedMessage (EHandshake hs) = do | ||
567 | putExtendedMessage $ EUnknown 0 $ BL.toStrict $ BE.encode hs | ||
568 | |||
569 | putExtendedMessage (EUnknown mid bs) = do | ||
570 | putWord32be $ fromIntegral (4 + 1 + BS.length bs) | ||
571 | putWord8 extendedMessageId | ||
572 | putWord8 mid | ||
573 | putByteString bs | ||
diff --git a/src/Network/BitTorrent/Exchange/Message/Extended.hs b/src/Network/BitTorrent/Exchange/Message/Extended.hs deleted file mode 100644 index 5d26b582..00000000 --- a/src/Network/BitTorrent/Exchange/Message/Extended.hs +++ /dev/null | |||
@@ -1,51 +0,0 @@ | |||
1 | -- | | ||
2 | -- Copyright : (c) Sam Truzjan 2013 | ||
3 | -- License : BSD3 | ||
4 | -- Maintainer : pxqr.sta@gmail.com | ||
5 | -- Stability : experimental | ||
6 | -- Portability : portable | ||
7 | -- | ||
8 | -- For more info see <http://www.bittorrent.org/beps/bep_0010.html> | ||
9 | -- | ||
10 | {-# LANGUAGE DeriveDataTypeable #-} | ||
11 | module Network.BitTorrent.Exchange.Message.Extended | ||
12 | ( | ||
13 | ) where | ||
14 | |||
15 | import Data.BEncode | ||
16 | import Data.IntMap as IM | ||
17 | import Data.Text | ||
18 | import Data.Typeable | ||
19 | import Network | ||
20 | import Network.Socket | ||
21 | |||
22 | import Network.BitTorrent.Core.PeerAddr | ||
23 | |||
24 | |||
25 | type Extension = () | ||
26 | |||
27 | type ExtMap = IntMap Extension | ||
28 | |||
29 | data ExtendedHandshake = H | ||
30 | { extMap :: ExtMap | ||
31 | , port :: Maybe PortNumber | ||
32 | , version :: Maybe Text -- TODO ClientInfo | ||
33 | , yourip :: Maybe SockAddr | ||
34 | -- , ipv6 , ipv4 | ||
35 | |||
36 | -- | The number of outstanding 'Request' messages this | ||
37 | -- client supports without dropping any. | ||
38 | , requestQueueLength :: Maybe Int | ||
39 | } deriving (Show, Typeable) | ||
40 | |||
41 | instance BEncode ExtendedHandshake where | ||
42 | toBEncode H {..} = toDict $ | ||
43 | "p" .=? port | ||
44 | .: endDict | ||
45 | |||
46 | fromBEncode = fromDict $ do | ||
47 | undefined | ||
48 | |||
49 | data ExtendedMessage | ||
50 | = ExtendedHandshake | ||
51 | deriving (Show, Eq) | ||