]> git.rkrishnan.org Git - functorrent.git/blobdiff - src/Main.hs
error out if the input string is not a valid filepath
[functorrent.git] / src / Main.hs
index 24bd9a99f88236470f9e17ad5e18267b31194552..d0812656c5498d30166c6b762c8ba6038a15f77c 100644 (file)
@@ -1,41 +1,68 @@
+{-# LANGUAGE OverloadedStrings #-}
 module Main where
 
+import Prelude hiding (length, readFile, writeFile)
+import Data.ByteString.Char8 (ByteString, readFile, writeFile, length)
 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
+import System.Exit (exitSuccess)
+import System.Directory (doesFileExist)
+import Text.ParserCombinators.Parsec (ParseError)
 
-printError :: Parsec.ParseError -> IO ()
-printError e = putStrLn $ "parse error: " ++ show e
+import FuncTorrent.Bencode (decode, BVal(..))
+import FuncTorrent.Logger (initLogger, logMessage, logStop)
+import FuncTorrent.Metainfo (announce, lengthInBytes, mkMetaInfo, info, name)
+import FuncTorrent.Peer (peers, getPeerResponse, handShakeMsg)
+import FuncTorrent.Tracker (connect, prepareRequest)
 
-genPeerId :: String
-genPeerId = "-HS0001-20150215"
+logError :: ParseError -> (String -> IO ()) -> IO ()
+logError e logMsg = logMsg $ "parse error: \n" ++ show e
 
-exit :: IO BC.ByteString
-exit = exitWith ExitSuccess
+peerId :: String
+peerId = "-HS0001-*-*-20150215"
+
+exit :: IO ByteString
+exit = exitSuccess
 
 usage :: IO ()
-usage = putStrLn "usage: deluge torrent-file"
+usage = putStrLn "usage: functorrent torrent-file"
 
-parse :: [String] -> IO (BC.ByteString)
+parse :: [String] -> IO ByteString
 parse [] = usage >> exit
-parse [a] = BC.readFile a
+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)
-                 putStrLn (show (P.getPeers body))
-   Left e -> printError e
-  putStrLn "done"
+    args <- getArgs
+    logR <- initLogger
+    let logMsg = logMessage logR
+    logMsg $ "Parsing input file: " ++ concat args
+    torrentStr <- parse args
+    case decode torrentStr of
+      Right d ->
+          case mkMetaInfo d of
+            Nothing -> logMsg "parse error"
+            Just m -> do
+              logMsg "Input File OK"
+
+              let len = lengthInBytes $ info m
+                  (Bdict d') = d
+
+              logMsg "Trying to fetch peers: "
+              body <- connect (announce m) (prepareRequest d' peerId len)
+
+              -- TODO: Write to ~/.functorrent/caches
+              writeFile (name (info m) ++ ".cache") body
+
+              let peerResponse = show $ peers $ getPeerResponse body
+              logMsg $ "Peers List : " ++ peerResponse
+
+              let hsMsgLen = show $ length $ handShakeMsg d' peerId
+              logMsg $ "Hand-shake message length : " ++ hsMsgLen
+
+      Left e -> logError e logMsg
+    logStop logR