]> git.rkrishnan.org Git - functorrent.git/blobdiff - src/Main.hs
remove a few reduntant stuff
[functorrent.git] / src / Main.hs
index b0f594a2f883b897027c9d63572b6233e60c9062..3aa65874efa581464d016899bcfcaf60356ae591 100644 (file)
@@ -1,41 +1,59 @@
+{-# LANGUAGE OverloadedStrings #-}
 module Main where
 
+import Prelude hiding (log, length, readFile, getContents)
+import Data.ByteString.Char8 (ByteString, getContents, readFile, unpack)
 import System.Environment (getArgs)
-import System.Exit
-import qualified Data.ByteString.Char8 as BC
-import qualified Bencode as Benc
-import qualified Metainfo as MInfo
-import qualified Tracker as T
-import qualified Text.ParserCombinators.Parsec as Parsec
-import qualified Peer as P
-import Data.Functor
-
-printError :: Parsec.ParseError -> IO ()
-printError e = putStrLn $ "parse error: " ++ show e
-
-genPeerId :: String
-genPeerId = "-HS0001-20150215"
-
-exit :: IO BC.ByteString
+import System.Exit (exitSuccess)
+import System.Directory (doesFileExist)
+
+import FuncTorrent.Logger (initLogger, logMessage, logStop)
+import FuncTorrent.Metainfo (Info(..), Metainfo(..), torrentToMetainfo)
+import FuncTorrent.Peer (handlePeerMsgs)
+import FuncTorrent.Tracker (peers, getTrackerResponse)
+
+logError :: String -> (String -> IO ()) -> IO ()
+logError e logMsg = logMsg $ "parse error: \n" ++ e
+
+peerId :: String
+peerId = "-HS0001-*-*-20150215"
+
+exit :: IO ByteString
 exit = exitSuccess
 
 usage :: IO ()
 usage = putStrLn "usage: functorrent torrent-file"
 
-parse :: [String] -> IO BC.ByteString
-parse [] = usage >> exit
-parse [a] = BC.readFile a
+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
 
 main :: IO ()
 main = do
-  args <- getArgs
-  torrentStr <- parse args
-  case Benc.decode torrentStr of
-   Right d -> case MInfo.mkMetaInfo d of
-               Nothing -> putStrLn "parse error"
-               Just m -> do
-                 body <- BC.pack <$> T.connect (MInfo.announce m) (T.prepareRequest d genPeerId)
-                 print (P.getPeers (P.getPeerResponse body))
-   Left e -> printError e
-  putStrLn "done"
+    args <- getArgs
+    logR <- initLogger
+    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
+       log "Input File OK"
+       log $ "Downloading file : " ++ name (info m)
+       log "Trying to fetch peers"
+
+       log $ "Trackers: " ++ head (announceList m)
+       trackerResp <- getTrackerResponse m peerId
+       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 m peerId
+    logStop logR