diff options
Diffstat (limited to 'src/Network/Torrent/PeerWire/Handshake.hs')
-rw-r--r-- | src/Network/Torrent/PeerWire/Handshake.hs | 77 |
1 files changed, 0 insertions, 77 deletions
diff --git a/src/Network/Torrent/PeerWire/Handshake.hs b/src/Network/Torrent/PeerWire/Handshake.hs deleted file mode 100644 index 733d5785..00000000 --- a/src/Network/Torrent/PeerWire/Handshake.hs +++ /dev/null | |||
@@ -1,77 +0,0 @@ | |||
1 | -- | | ||
2 | -- Copyright : (c) Sam T. 2013 | ||
3 | -- License : MIT | ||
4 | -- Maintainer : pxqr.sta@gmail.com | ||
5 | -- Stability : experimental | ||
6 | -- Portability : portable | ||
7 | -- | ||
8 | {-# LANGUAGE OverloadedStrings #-} | ||
9 | module Network.Torrent.PeerWire.Handshake | ||
10 | ( Handshake | ||
11 | , handshakeMaxSize | ||
12 | , defaultBTProtocol, defaultReserved, defaultHandshake | ||
13 | , handshake | ||
14 | ) where | ||
15 | |||
16 | import Control.Applicative | ||
17 | import Data.Word | ||
18 | import Data.ByteString (ByteString) | ||
19 | import qualified Data.ByteString as B | ||
20 | import Data.Serialize as S | ||
21 | import Data.Torrent.InfoHash | ||
22 | import Network | ||
23 | import Network.Socket.ByteString | ||
24 | import Network.Torrent.PeerID | ||
25 | |||
26 | -- | In order to establish the connection between peers we should send 'Handshake' | ||
27 | -- message. The 'Handshake' is a required message and must be the first message | ||
28 | -- transmitted by the peer to the another peer. | ||
29 | data Handshake = Handshake { | ||
30 | hsProtocol :: ByteString -- ^ Identifier of the protocol. | ||
31 | , hsReserved :: Word64 -- ^ Reserved bytes, rarely used. | ||
32 | , hsInfoHash :: InfoHash -- ^ Hash from the metainfo file. | ||
33 | -- This /should be/ same hash that is transmitted in tracker requests. | ||
34 | , hsPeerID :: PeerID -- ^ Peer id of the initiator. | ||
35 | -- This is /usually the same peer id that is transmitted in tracker requests. | ||
36 | } deriving (Show, Eq) | ||
37 | |||
38 | instance Serialize Handshake where | ||
39 | put hs = do | ||
40 | putWord8 (fromIntegral (B.length (hsProtocol hs))) | ||
41 | putByteString (hsProtocol hs) | ||
42 | putWord64be (hsReserved hs) | ||
43 | put (hsInfoHash hs) | ||
44 | put (hsPeerID hs) | ||
45 | |||
46 | get = do | ||
47 | len <- getWord8 | ||
48 | Handshake <$> getBytes (fromIntegral len) | ||
49 | <*> getWord64be | ||
50 | <*> get | ||
51 | <*> get | ||
52 | |||
53 | -- | Maximum size of handshake message in bytes. | ||
54 | handshakeMaxSize :: Int | ||
55 | handshakeMaxSize = 1 + 256 + 8 + 20 + 20 | ||
56 | |||
57 | -- | Default protocol string "BitTorrent protocol" as is. | ||
58 | defaultBTProtocol :: ByteString | ||
59 | defaultBTProtocol = "BitTorrent protocol" | ||
60 | |||
61 | -- | Default reserved word is 0. | ||
62 | defaultReserved :: Word64 | ||
63 | defaultReserved = 0 | ||
64 | |||
65 | -- | Length of info hash and peer id is unchecked, so it /should/ be equal 20. | ||
66 | defaultHandshake :: InfoHash -> PeerID -> Handshake | ||
67 | defaultHandshake = Handshake defaultBTProtocol defaultReserved | ||
68 | |||
69 | |||
70 | -- TODO check if hash the same | ||
71 | -- | Handshaking with a peer specified by the second argument. | ||
72 | -- | ||
73 | handshake :: Socket -> Handshake -> IO (Either String Handshake) | ||
74 | handshake sock hs = do | ||
75 | sendAll sock (S.encode hs) | ||
76 | r <- recv sock handshakeMaxSize | ||
77 | return (S.decode r) | ||