]> git.rkrishnan.org Git - functorrent.git/blobdiff - src/main/Main.hs
starting with a clean slate
[functorrent.git] / src / main / Main.hs
diff --git a/src/main/Main.hs b/src/main/Main.hs
deleted file mode 100644 (file)
index 71c9841..0000000
+++ /dev/null
@@ -1,112 +0,0 @@
-{-# LANGUAGE OverloadedStrings #-}
-{-
-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/>
--}
-
-module Main where
-
-import           Prelude hiding (log, length, readFile, getContents)
-
-import           Control.Concurrent (forkIO, killThread)
-import           Control.Concurrent.MVar (readMVar)
-import           Data.ByteString.Char8 (ByteString, getContents, readFile)
-import qualified FuncTorrent.FileSystem as FS (createMsgChannel, pieceMapFromFile, run)
-import           FuncTorrent.Logger (initLogger, logMessage, logStop)
-import           FuncTorrent.Metainfo (Info(..), Metainfo(..), torrentToMetainfo)
-import           FuncTorrent.Peer (handlePeerMsgs)
-import           FuncTorrent.PieceManager (initPieceMap)
-import qualified FuncTorrent.Server as Server
-import           FuncTorrent.Tracker (runTracker, getConnectedPeers, newTracker)
-import           Network (PortID (PortNumber))
-import           System.IO (withFile, IOMode (ReadWriteMode))
-import           System.Directory (doesFileExist)
-import           System.Environment (getArgs)
-import           System.Exit (exitSuccess)
-import           System.Random (getStdGen, randomRs)
-
-logError :: String -> (String -> IO ()) -> IO ()
-logError e logMsg = logMsg $ "parse error: \n" ++ e
-
-exit :: IO ByteString
-exit = exitSuccess
-
-usage :: IO ()
-usage = putStrLn "usage: functorrent torrent-file"
-
-parse :: [String] -> IO ByteString
-parse [] = getContents
-parse [a] = do
-  fileExist <- doesFileExist a
-  if fileExist
-    then readFile a
-    else error "file does not exist"
-parse _ = exit
-
--- peer id is exactly 20 bytes long.
--- peer id starts with '-', followed by 2 char client id'
--- followed by 4 ascii digits for version number, followed by
--- a '-'. Rest are random digits to fill the 20 bytes.
-mkPeerID :: IO String
-mkPeerID = do
-  stdgen <- getStdGen
-  let digits = randomRs (0, 9) stdgen :: [Integer]
-  return $ "-HS9001-" ++ (concatMap show $ take (20 - 8) digits)
-
-main :: IO ()
-main = do
-    args <- getArgs
-    logR <- initLogger
-    peerId <- mkPeerID    
-    let log = logMessage logR
-    log "Starting up functorrent"
-    log $ "Parsing arguments " ++ concat args
-    torrentStr <- parse args
-    case torrentToMetainfo torrentStr of
-     Left e -> logError e log
-     Right m -> 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 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)
-           pieceHash = pieces (info m)
-           pLen = pieceLength (info m)
-           infohash = infoHash m
-           defaultPieceMap = initPieceMap pieceHash fileLen pLen
-       log $ "create FS msg channel"
-       fsMsgChannel <- FS.createMsgChannel
-       log $ "Downloading file : " ++ filePath
-       pieceMap <- FS.pieceMapFromFile filePath fileLen defaultPieceMap
-       log $ "start filesystem manager thread"
-       fsTid <- forkIO $ withFile filePath ReadWriteMode (FS.run pieceMap fsMsgChannel)
-       log $ "starting server"
-       (serverSock, (PortNumber portnum)) <- Server.start
-       log $ "server started on " ++ show portnum
-       log "Trying to fetch peers"
-       _ <- forkIO $ Server.run serverSock peerId m pieceMap fsMsgChannel
-       log $ "Trackers: " ++ head (announceList m)
-       trackerMsgChan <- newTracker
-       _ <- forkIO $ runTracker trackerMsgChan fsMsgChannel infohash portnum peerId (announceList m) fileLen
-       ps <- getConnectedPeers trackerMsgChan
-       log $ "Peers List : " ++ (show ps)
-       let p1 = head ps
-       handlePeerMsgs p1 peerId m pieceMap True fsMsgChannel
-       logStop logR
-       killThread fsTid