]> git.rkrishnan.org Git - functorrent.git/blobdiff - src/FuncTorrent/Tracker.hs
refactor: remove peerid from Peer datatype
[functorrent.git] / src / FuncTorrent / Tracker.hs
index 3644781b4adfa47d5b523824daece3a698c02907..8090feb99ea868eb328dc1811332b550984e277c 100644 (file)
@@ -1,56 +1,94 @@
+{-
+ - Copyright (C) 2015-2016 Ramakrishnan Muthukrishnan <ram@rkrishnan.org>
+ -
+ - This file is part of FuncTorrent.
+ -
+ - FuncTorrent is free software; you can redistribute it and/or modify
+ - it under the terms of the GNU General Public License as published by
+ - the Free Software Foundation; either version 3 of the License, or
+ - (at your option) any later version.
+ -
+ - FuncTorrent is distributed in the hope that it will be useful,
+ - but WITHOUT ANY WARRANTY; without even the implied warranty of
+ - MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ - GNU General Public License for more details.
+ -
+ - You should have received a copy of the GNU General Public License
+ - along with FuncTorrent; if not,  see <http://www.gnu.org/licenses/>
+ -}
+
+{-# LANGUAGE OverloadedStrings #-}
 module FuncTorrent.Tracker
-    (connect,
-     infoHash,
-     prepareRequest,
-     urlEncodeHash
-    ) where
-
-import Prelude hiding (lookup)
-import Crypto.Hash.SHA1 (hash)
-import Data.ByteString.Char8 (ByteString,  unpack)
-import Data.Char (chr)
-import Data.List (intercalate)
-import Data.Maybe (fromJust)
-import Data.Map ((!))
-import Network.HTTP (simpleHTTP, defaultGETRequest_, getResponseBody)
-import Network.HTTP.Base (urlEncode)
-import Network.URI (parseURI)
-import qualified Data.ByteString.Base16 as B16 (encode)
-
-import FuncTorrent.Bencode (InfoDict, encode)
-import FuncTorrent.Utils (splitN)
-
-type Url = String
-
--- | urlEncodeHash
---
--- >>> urlEncodeHash $ pack "123456789abcdef123456789abcdef123456789a"
--- "%124Vx%9a%bc%de%f1%23Eg%89%ab%cd%ef%124Vx%9a"
-urlEncodeHash :: ByteString -> String
-urlEncodeHash bs = concatMap (encode' . unpack) (splitN 2 bs)
-  where encode' b@[c1, c2] = let c =  chr (read ("0x" ++ b))
-                            in escape c c1 c2
-        encode' _ = ""
-        escape i c1 c2 | i `elem` nonSpecialChars = [i]
-                       | otherwise = "%" ++ [c1] ++ [c2]
-
-        nonSpecialChars = ['A'..'Z'] ++ ['a'..'z'] ++ ['0'..'9'] ++ "-_.~"
-
-infoHash :: InfoDict -> ByteString
-infoHash m = hash . encode $ (m ! "info")
-
-prepareRequest :: InfoDict -> String -> Integer -> String
-prepareRequest d peer_id len =
-  let p = [("info_hash", urlEncodeHash ((B16.encode . infoHash) d)),
-           ("peer_id", urlEncode peer_id),
-           ("port", "6881"),
-           ("uploaded", "0"),
-           ("downloaded", "0"),
-           ("left", show len),
-           ("compact", "1"),
-           ("event", "started")]
-  in intercalate "&" [f ++ "=" ++ s | (f,s) <- p]
-
-connect :: Url -> String -> IO ByteString
-connect baseurl qstr = simpleHTTP (defaultGETRequest_ url) >>= getResponseBody
-    where url = fromJust . parseURI $ (baseurl ++ "?" ++ qstr)
+       (runTracker
+       , getConnectedPeers
+       , newTracker
+       ) where
+
+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, pack, unpack)
+import Data.List (isPrefixOf)
+import Network (PortNumber)
+
+import qualified FuncTorrent.Tracker.Http as HT (trackerLoop)
+import qualified FuncTorrent.Tracker.Udp as UT (trackerLoop)
+import FuncTorrent.Tracker.Types (TState(..), TrackerEventState(..), TrackerProtocol(..), TrackerMsg(..))
+import FuncTorrent.Utils (Port, toPort, getHostname)
+import qualified FuncTorrent.FileSystem as FS (MsgChannel)
+import FuncTorrent.PeerMsgs (Peer)
+
+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
+  let initialTState = TState { currentState = None
+                             , connectedPeers = ps
+                             , left = sz }
+      turl = head announceList
+      host = getHostname turl
+  case getTrackerType turl of
+    Http -> do
+      _ <- forkIO $ HT.trackerLoop turl port peerId infohash fsChan initialTState
+      runStateT (msgHandler msgChannel) initialTState
+      return ()
+    Udp -> do
+      _ <- forkIO $ UT.trackerLoop turl (fromIntegral port) peerId infohash fsChan initialTState
+      runStateT (msgHandler msgChannel) initialTState
+      return ()
+    _ ->
+      error "Tracker Protocol unimplemented"
+
+getTrackerType :: String -> TrackerProtocol
+getTrackerType url | "http://" `isPrefixOf` url = Http
+                   | "udp://" `isPrefixOf` 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 ->
+            putMVar var peers
+          _ ->
+            putStrLn "Unhandled Tracker Msg"
+
+getConnectedPeers :: MsgChannel -> IO [Peer]
+getConnectedPeers c = do
+  v <- newEmptyMVar
+  writeChan c (GetConnectedPeersMsg v)
+  readMVar v