]> git.rkrishnan.org Git - functorrent.git/blobdiff - src/FuncTorrent/Peer.hs
WIP: peer handshake
[functorrent.git] / src / FuncTorrent / Peer.hs
index b0c546b9b5abae16d8260290ec0054f06b1db55a..798f60acf0712eef0c0644b320c8fe97750cb212 100644 (file)
@@ -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