]> git.rkrishnan.org Git - functorrent.git/blobdiff - src/main/Main.hs
Tracker is a separate thread now
[functorrent.git] / src / main / Main.hs
index b67b6b282160826689a14fa4b82eb5abf9b9e54f..4dd4c6867a92f06e0a9fdb69086aa791cfd507de 100644 (file)
@@ -4,7 +4,8 @@ module Main where
 import Prelude hiding (log, length, readFile, getContents, replicate, writeFile)
 
 import Control.Concurrent (forkIO)
-import Data.ByteString.Char8 (ByteString, getContents, readFile, writeFile, unpack, replicate)
+import Control.Concurrent.MVar (readMVar)
+import Data.ByteString.Char8 (ByteString, getContents, readFile, writeFile, replicate)
 import Network (PortID (PortNumber))
 import System.Environment (getArgs)
 import System.Exit (exitSuccess)
@@ -15,7 +16,7 @@ import FuncTorrent.Logger (initLogger, logMessage, logStop)
 import FuncTorrent.Metainfo (Info(..), Metainfo(..), torrentToMetainfo)
 import FuncTorrent.Peer (initPieceMap, handlePeerMsgs, pieceMapFromFile)
 import qualified FuncTorrent.Server as Server
-import FuncTorrent.Tracker (peers, getTrackerResponse)
+import FuncTorrent.Tracker (connectedPeers, initialTrackerState, trackerLoop)
 
 logError :: String -> (String -> IO ()) -> IO ()
 logError e logMsg = logMsg $ "parse error: \n" ++ e
@@ -60,7 +61,7 @@ main = do
        -- if we had downloaded the file before (partly or completely)
        -- then we should check the current directory for the existence
        -- of the file and then update the map of each piece' availability.
-       -- This can be donw by reading each piece and verifying the checksum.
+       -- This can be done by reading each piece and verifying the checksum.
        -- If the checksum does not match, we don't have that piece.
        let filePath = name (info m) -- really this is just the file name, not file path
            fileLen = lengthInBytes (info m)
@@ -80,13 +81,13 @@ main = do
        (serverSock, (PortNumber portnum)) <- Server.start
        log $ "server started on " ++ show portnum
        log "Trying to fetch peers"
-       forkIO $ Server.run serverSock peerId m pieceMap
+       _ <- forkIO $ Server.run serverSock peerId m pieceMap
        log $ "Trackers: " ++ head (announceList m)
-       trackerResp <- getTrackerResponse portnum peerId m
-       case  trackerResp of
-        Left e -> log $ "Error" ++ unpack e
-        Right peerList -> do
-          log $ "Peers List : " ++ (show . peers $ peerList)
-          let p1 = head (peers peerList)
-          handlePeerMsgs p1 peerId m pieceMap True
-    logStop logR
+       -- (tstate, errstr) <- runTracker portnum peerId m
+       tstate <- initialTrackerState $ lengthInBytes $ info m
+       _ <- forkIO $ trackerLoop portnum peerId m tstate >> return ()
+       ps <- readMVar (connectedPeers tstate)
+       log $ "Peers List : " ++ (show ps)
+       let p1 = head ps
+       handlePeerMsgs p1 peerId m pieceMap True
+       logStop logR