From b236b7f5a4b065e7b61bdd5966431dc51f450b41 Mon Sep 17 00:00:00 2001
From: Ramakrishnan Muthukrishnan <ram@rkrishnan.org>
Date: Fri, 1 May 2015 15:50:21 +0530
Subject: [PATCH] WIP: peer handshake

---
 src/FuncTorrent.hs         |  2 +-
 src/FuncTorrent/Peer.hs    | 65 ++++++++++++++++++++++++++++----------
 src/FuncTorrent/Tracker.hs |  2 +-
 src/Main.hs                | 13 ++++----
 4 files changed, 58 insertions(+), 24 deletions(-)

diff --git a/src/FuncTorrent.hs b/src/FuncTorrent.hs
index e17b024..8289da5 100644
--- a/src/FuncTorrent.hs
+++ b/src/FuncTorrent.hs
@@ -7,7 +7,7 @@ module FuncTorrent
      tracker,
      decode,
      encode,
-     handShakeMsg,
+     handShake,
      initLogger,
      logMessage,
      logStop,
diff --git a/src/FuncTorrent/Peer.hs b/src/FuncTorrent/Peer.hs
index b0c546b..798f60a 100644
--- a/src/FuncTorrent/Peer.hs
+++ b/src/FuncTorrent/Peer.hs
@@ -1,26 +1,59 @@
 {-# LANGUAGE OverloadedStrings #-}
 module FuncTorrent.Peer
     (Peer(..),
-     handShakeMsg
+     handShake
     ) where
 
 import Prelude hiding (lookup, concat, replicate, splitAt)
 
-import Data.ByteString.Char8 (ByteString, pack, concat, replicate)
-import Data.ByteString.Lazy (toChunks)
-import Data.Int (Int8)
-import qualified Data.Binary as Bin (encode)
+import System.IO
+import Data.ByteString (ByteString, unpack, concat, hGet, hPut, singleton)
+import Data.ByteString.Char8 (replicate, pack)
+import Network (connectTo, PortID(..))
 
-import FuncTorrent.Metainfo (Metainfo(..))
+type ID = String
+type IP = String
+type Port = Integer
 
--- | Peer is a IP address, port tuple
-data Peer = Peer String Integer
-            deriving (Show, Eq)
+data PeerState = PeerState { am_choking :: Bool
+                           , am_interested :: Bool
+                           , peer_choking :: Bool
+                           , peer_interested :: Bool }
 
-handShakeMsg :: Metainfo -> String -> ByteString
-handShakeMsg m peer_id = concat [pstrlen, pstr, reserved, infoH, peerID]
-    where pstrlen = concat $ toChunks $ Bin.encode (19 :: Int8)
-          pstr = pack "BitTorrent protocol"
-          reserved = replicate 8 '\0'
-          infoH = infoHash m
-          peerID = pack peer_id
+-- | Peer is a PeerID, IP address, port tuple
+data Peer = Peer ID IP Port
+          deriving (Show, Eq)
+
+data Msg = HandShakeMsg ByteString ID
+         | KeepAliveMsg
+         | ChokeMsg
+         | UnChokeMsg
+         | InterestedMsg
+         | NotInterestedMsg
+         | HaveMsg Integer
+         | BitFieldMsg Integer
+         | RequestMsg Integer Integer Integer
+         | PieceMsg Integer Integer Integer
+         | CancelMsg Integer Integer Integer
+         | PortMsg Port
+         deriving (Show)
+
+genHandShakeMsg :: ByteString -> String -> ByteString
+genHandShakeMsg infoHash peer_id = concat [pstrlen, pstr, reserved, infoHash, peerID]
+  where pstrlen = singleton 19
+        pstr = pack "BitTorrent protocol"
+        reserved = replicate 8 '\0'
+        peerID = pack peer_id
+
+handShake :: Peer -> ByteString -> String -> IO ByteString
+handShake (Peer _ ip port) infoHash peerid = do
+  let hs = genHandShakeMsg infoHash peerid
+  handle <- connectTo ip (PortNumber (fromIntegral port))
+  hSetBuffering handle LineBuffering
+  hPut handle hs
+  rlenBS <- hGet handle 1
+  let rlen = fromIntegral $ (unpack rlenBS) !! 0
+  hGet handle rlen
+
+-- sendMsg :: Peer -> Handle -> PeerMsg -> IO ()
+-- recvMsg :: Peer -> Handle -> Msg
diff --git a/src/FuncTorrent/Tracker.hs b/src/FuncTorrent/Tracker.hs
index 57c8f9d..b816650 100644
--- a/src/FuncTorrent/Tracker.hs
+++ b/src/FuncTorrent/Tracker.hs
@@ -62,7 +62,7 @@ mkTrackerResponse resp =
                  splitN 2 . B16.encode
 
       makePeer :: ByteString -> Peer
-      makePeer peer = Peer (toIP ip') (toPort port')
+      makePeer peer = Peer "" (toIP ip') (toPort port')
           where (ip', port') = splitAt 4 peer
 
 -- | Connect to a tracker and get peer info
diff --git a/src/Main.hs b/src/Main.hs
index 9cb5908..fa79ac3 100644
--- a/src/Main.hs
+++ b/src/Main.hs
@@ -2,7 +2,7 @@
 module Main where
 
 import Prelude hiding (log, length, readFile, writeFile)
-import Data.ByteString.Char8 (ByteString, readFile, writeFile, length, unpack)
+import Data.ByteString.Char8 (ByteString, readFile, writeFile, unpack)
 import System.Environment (getArgs)
 import System.Exit (exitSuccess)
 import System.Directory (doesFileExist)
@@ -11,7 +11,7 @@ import Text.ParserCombinators.Parsec (ParseError)
 import FuncTorrent.Bencode (decode)
 import FuncTorrent.Logger (initLogger, logMessage, logStop)
 import FuncTorrent.Metainfo (Info(..), Metainfo(..), mkMetaInfo)
-import FuncTorrent.Peer (handShakeMsg)
+import FuncTorrent.Peer (Peer(..), handShake)
 import FuncTorrent.Tracker (tracker, peers, mkTrackerResponse)
 
 logError :: ParseError -> (String -> IO ()) -> IO ()
@@ -55,17 +55,18 @@ main = do
               log $ "Trackers: " ++ head (announceList m)
               response <- tracker m peerId
 
-              let hsMsgLen = show $ length $ handShakeMsg m peerId
-              log $ "Hand-shake message length : " ++ hsMsgLen
-
               -- TODO: Write to ~/.functorrent/caches
               writeFile (name (info m) ++ ".cache") response
 
               case decode response of
                 Right trackerInfo ->
                     case mkTrackerResponse trackerInfo of
-                      Right peerResp ->
+                      Right peerResp -> do
                           log $ "Peers List : " ++ (show . peers $ peerResp)
+                          let p1 = head (peers peerResp)
+                          msg <- handShake (Peer "" "95.188.88.59" 27000) (infoHash m) peerId
+                          log $ "handshake: " ++ (show msg)
+                          return ()
                       Left e -> log $ "Error" ++ unpack e
                 Left e -> logError e log
 
-- 
2.45.2