]> git.rkrishnan.org Git - functorrent.git/blobdiff - src/Peer.hs
refactor PeerID and associated functions.
[functorrent.git] / src / Peer.hs
index c7ebca367a2110d7ec97717b46c161a8fa3f814c..52cc03f25829dbf27d9fc5a21237ae9c87e4a1fe 100644 (file)
@@ -2,10 +2,14 @@ module Peer where
 
 import qualified Utils as U
 import qualified Bencode as Benc
+import qualified Tracker as T
 import qualified Data.Map as M
 import qualified Data.ByteString.Char8 as BC
 import qualified Data.ByteString.Base16 as B16
+import qualified Data.ByteString.Lazy as BL
 import qualified Data.List as L
+import qualified Data.Binary as Bin
+import qualified Data.Int as DI
 
 data Peer = Peer { ip :: String
                  , port :: Integer
@@ -24,10 +28,10 @@ getPeers :: PeerResp -> [Peer]
 getPeers = peers
 
 getPeerResponse :: BC.ByteString -> PeerResp
-getPeerResponse body = case (Benc.decode body) of
+getPeerResponse body = case Benc.decode body of
                         Right (Benc.Bdict peerM) ->
                           let (Just (Benc.Bint i)) = M.lookup (Benc.Bstr (BC.pack "lookup")) peerM
-                              (Benc.Bstr peersBS) = peerM M.! (Benc.Bstr (BC.pack "peers"))
+                              (Benc.Bstr peersBS) = peerM M.! Benc.Bstr (BC.pack "peers")
                               pl = map (\peer -> let (ip', port') = BC.splitAt 4 peer
                                                  in Peer { ip = toIPNum ip'
                                                          , port =  toPortNum port'
@@ -39,11 +43,21 @@ getPeerResponse body = case (Benc.decode body) of
                                           , incomplete = Nothing
                                           }
                           where toPortNum = read . ("0x" ++) . BC.unpack . B16.encode
-                                toIPNum = (L.intercalate ".") .
+                                toIPNum = L.intercalate "." .
                                           map (show . toInt . ("0x" ++) . BC.unpack) .
-                                          (U.splitN 2) . B16.encode
+                                          U.splitN 2 . B16.encode
                         _ -> PeerResponse { interval = Nothing
                                           , peers = []
                                           , complete = Nothing
                                           , incomplete = Nothing
                                           }
+
+
+handShakeMsg :: M.Map Benc.BVal Benc.BVal -> String -> BC.ByteString
+handShakeMsg m peer_id = let pstrlen = BC.concat $ BL.toChunks $ Bin.encode (19 :: DI.Int8)
+                             pstr = BC.pack "BitTorrent protocol"
+                             reserved = BC.replicate 8 '\0'
+                             infoH = T.infoHash m
+                             peerID = BC.pack peer_id
+                         in
+                          BC.concat [pstrlen, pstr, reserved, infoH, peerID]