X-Git-Url: https://git.rkrishnan.org/?a=blobdiff_plain;f=src%2FFuncTorrent%2FTracker.hs;h=157880842cc23951f909dda0e7a489d57bdd1c5f;hb=5b18521efb136dfa7d0676f195a2cdf38744d660;hp=64a2ce9d3e8c96a5a29c5176bd770be0ba05bb52;hpb=eac229d7b955396099b2123554ffd1f18142a85c;p=functorrent.git diff --git a/src/FuncTorrent/Tracker.hs b/src/FuncTorrent/Tracker.hs index 64a2ce9..1578808 100644 --- a/src/FuncTorrent/Tracker.hs +++ b/src/FuncTorrent/Tracker.hs @@ -1,29 +1,69 @@ {-# LANGUAGE OverloadedStrings #-} module FuncTorrent.Tracker - (TState(..), - initialTrackerState, - trackerLoop - ) where + (runTracker + , getConnectedPeers + , newTracker + ) where -import Control.Concurrent.MVar (newEmptyMVar, newMVar) +import Control.Concurrent(forkIO) +import Control.Concurrent.Chan (Chan, newChan, readChan, writeChan) +import Control.Concurrent.MVar (newEmptyMVar, putMVar, readMVar) +import Control.Monad.State (StateT, liftIO, get, runStateT) +import Control.Monad (forever) +import Data.ByteString.Char8 (ByteString) import Data.List (isPrefixOf) +import Network (PortNumber) -import FuncTorrent.Tracker.Http(trackerLoop) -import FuncTorrent.Tracker.Types(TState(..), TrackerEventState(..), TrackerProtocol(..)) +import FuncTorrent.Tracker.Http (trackerLoop) +import FuncTorrent.Tracker.Types (TState(..), TrackerEventState(..), TrackerProtocol(..), TrackerMsg(..)) +import qualified FuncTorrent.FileSystem as FS (MsgChannel) +import FuncTorrent.Peer (Peer) -initialTrackerState :: Integer -> IO TState -initialTrackerState sz = do +type MsgChannel = Chan TrackerMsg + +newTracker :: IO MsgChannel +newTracker = newChan + +runTracker :: MsgChannel -> FS.MsgChannel -> ByteString -> PortNumber + -> String -> [String] -> Integer -> IO () +runTracker msgChannel fsChan infohash port peerId announceList sz = do ps <- newEmptyMVar - up <- newMVar 0 - down <- newMVar 0 - return $ TState { currentState = None - , connectedPeers = ps - , uploaded = up - , downloaded = down - , left = sz } + let initialTState = TState { currentState = None + , connectedPeers = ps + , left = sz } + turl = head announceList + case (getTrackerType turl) of + Http -> do + _ <- forkIO $ trackerLoop turl port peerId infohash fsChan initialTState + runStateT (msgHandler msgChannel) initialTState + return () + _ -> do + error "Tracker Protocol unimplemented" getTrackerType :: String -> TrackerProtocol getTrackerType url | isPrefixOf "http://" url = Http | isPrefixOf "udp://" url = Udp | otherwise = UnknownProtocol + +msgHandler :: MsgChannel -> StateT TState IO () +msgHandler c = forever $ do + st <- get + peers <- liftIO $ readMVar (connectedPeers st) + msg <- liftIO recvMsg + liftIO $ sendResponse msg peers + where + recvMsg = readChan c + sendResponse msg peers = + case msg of + GetConnectedPeersMsg var -> do + putMVar var peers + _ -> do + putStrLn "Unhandled Tracker Msg" + +getConnectedPeers :: MsgChannel -> IO [Peer] +getConnectedPeers c = do + v <- newEmptyMVar + writeChan c (GetConnectedPeersMsg v) + ps <- readMVar v + return ps