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