]> git.rkrishnan.org Git - functorrent.git/commitdiff
add a simple message loop to print out received msgs
authorRamakrishnan Muthukrishnan <ram@rkrishnan.org>
Wed, 6 May 2015 09:47:19 +0000 (15:17 +0530)
committerRamakrishnan Muthukrishnan <ram@rkrishnan.org>
Wed, 6 May 2015 09:47:30 +0000 (15:17 +0530)
This is just to study what messages come after the handshake.

src/FuncTorrent.hs
src/FuncTorrent/Peer.hs
src/Main.hs

index 8289da5bae88ce73801cb0edb9d11c407ebf6855..cd6473c96878c79e75025eadde601908bc46775b 100644 (file)
@@ -8,6 +8,7 @@ module FuncTorrent
      decode,
      encode,
      handShake,
+     msgLoop,
      initLogger,
      logMessage,
      logStop,
index 29d57143d814fb780a93f2a06c746667b8a266aa..aeba52fdfe7d6418091d817464ff97558306bde8 100644 (file)
@@ -1,7 +1,8 @@
 {-# LANGUAGE OverloadedStrings #-}
 module FuncTorrent.Peer
     (Peer(..),
-     handShake
+     handShake,
+     msgLoop
     ) where
 
 import Prelude hiding (lookup, concat, replicate, splitAt)
@@ -14,7 +15,7 @@ import Network (connectTo, PortID(..))
 import Data.Binary (Binary(..), decode)
 import Data.Binary.Put (putWord32be, putWord16be, putWord8)
 import Data.Binary.Get (getWord32be, getWord16be, getWord8)
-import Control.Monad (replicateM, liftM)
+import Control.Monad (replicateM, liftM, forever)
 import Control.Applicative ((<$>), liftA3)
 
 type ID = String
@@ -143,3 +144,8 @@ getMsg h = do
 
 -- loop1 :: shake hands with all peers, find out the pieces they have, form PieceData.
 -- recvMsg :: Peer -> Handle -> Msg
+
+msgLoop :: Handle -> IO ()
+msgLoop h = forever $ do
+  msg <- getMsg h
+  putStrLn $ "got a " ++ (show msg)
index 65e2dd7cb194321305b3028e88ee1dbe7e7a71fa..afa0bd329d9f0edaa5f9af6274087193cc741120 100644 (file)
@@ -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 (handShake)
+import FuncTorrent.Peer (handShake, msgLoop)
 import FuncTorrent.Tracker (tracker, peers, mkTrackerResponse)
 
 logError :: ParseError -> (String -> IO ()) -> IO ()
@@ -64,9 +64,9 @@ main = do
                       Right peerResp -> do
                           log $ "Peers List : " ++ (show . peers $ peerResp)
                           let p1 = head (peers peerResp)
-                          msg <- handShake p1 (infoHash m) peerId
-                          log $ "handshake: " ++ (show msg)
-                          return ()
+                          h <- handShake p1 (infoHash m) peerId
+                          log $ "handshake"
+                          msgLoop h
                       Left e -> log $ "Error" ++ unpack e
                 Left e -> logError e log