summaryrefslogtreecommitdiff
path: root/src/Network/Torrent/PeerWire/Handshake.hs
blob: ae65933f668d0a0056c4dd0b132dd0eecf59382c (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
{-# LANGUAGE OverloadedStrings #-}
module Network.Torrent.PeerWire.Handshake
       ( Handshake
       , handshakeMaxSize
       , defaultProtocol, defaultReserved, defaultHandshake
       ) where

import Control.Applicative
import Data.Word
import           Data.ByteString (ByteString)
import qualified Data.ByteString as B
import Data.Serialize
import Data.Torrent.InfoHash
import Network.Torrent.PeerID

-- | In order to establish the connection between peers we should send 'Handshake'
--   message. The 'Handshake' is a required message and must be the first message
--   transmitted by the peer to the another peer.
data Handshake = Handshake {
    hsProtocol    :: ByteString  -- ^ Identifier of the protocol.
  , hsReserved    :: Word64      -- ^ Reserved bytes, rarely used.
  , hsInfoHash    :: InfoHash    -- ^ Hash from the metainfo file.
    -- This /should be/ same hash that is transmitted in tracker requests.
  , hsPeerID      :: PeerID      -- ^ Peer id of the initiator.
    -- This is /usually the same peer id that is transmitted in tracker requests.
  } deriving (Show, Eq)

instance Serialize Handshake where
  put hs = do
    putWord8 (fromIntegral (B.length (hsProtocol hs)))
    putByteString (hsProtocol hs)
    putWord64be   (hsReserved hs)
    put (hsInfoHash hs)
    put (hsPeerID hs)

  get = do
    len  <- getWord8
    Handshake <$> getBytes (fromIntegral len)
              <*> getWord64be
              <*> get
              <*> get

-- | Maximum size of handshake message in bytes.
handshakeMaxSize :: Int
handshakeMaxSize = 1 + 256 + 8 + 20 + 20

-- | Default protocol string "BitTorrent protocol" as is.
defaultProtocol :: ByteString
defaultProtocol = "BitTorrent protocol"

-- | Default reserved word is 0.
defaultReserved :: Word64
defaultReserved = 0

-- | Length of info hash and peer id is unchecked, so it /should/ be equal 20.
defaultHandshake :: InfoHash -> PeerID -> Handshake
defaultHandshake = Handshake defaultProtocol defaultReserved