]> git.rkrishnan.org Git - functorrent.git/blobdiff - src/Main.hs
Make network request return ByteString
[functorrent.git] / src / Main.hs
index 50eb5d1e650da9d48e990db5e487f6e6cb9b7a0a..bc4b8d31013948dbfd35c053c5fb18b3d623b2f2 100644 (file)
@@ -1,19 +1,20 @@
+{-# LANGUAGE OverloadedStrings #-}
 module Main where
 
-import Prelude hiding (length, readFile)
+import Prelude hiding (length, readFile, writeFile)
+import Data.ByteString.Char8 (ByteString, length, readFile, writeFile, length)
+import System.Environment (getArgs)
+import System.Exit (exitSuccess)
+import Text.ParserCombinators.Parsec (ParseError)
 
 import Bencode (decode, BVal(..))
-import Data.ByteString.Char8 as BC (ByteString, pack, length, readFile, length)
-import Data.Functor ((<$>))
-import Metainfo (announce, lengthInBytes, mkMetaInfo, info)
+import Logger (initLogger, logMessage, logStop)
+import Metainfo (announce, lengthInBytes, mkMetaInfo, info, name)
 import Peer (getPeers, getPeerResponse, handShakeMsg)
-import System.Environment (getArgs)
-import System.Exit (exitSuccess)
 import Tracker (connect, prepareRequest)
-import Text.ParserCombinators.Parsec (ParseError)
 
-printError :: ParseError -> IO ()
-printError e = putStrLn $ "parse error: " ++ show e
+logError :: ParseError -> (String -> IO ()) -> IO ()
+logError e logMsg = logMsg $ "parse error: \n" ++ show e
 
 peerId :: String
 peerId = "-HS0001-*-*-20150215"
@@ -32,16 +33,31 @@ parse _ = exit
 main :: IO ()
 main = do
     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 -> putStrLn "parse error"
+            Nothing -> logMsg "parse error"
             Just m -> do
+              logMsg "Input File OK"
+
               let len = lengthInBytes $ info m
                   (Bdict d') = d
-              body <- pack <$> connect (announce m) (prepareRequest d' peerId len)
-              print $ getPeers $ getPeerResponse body
-              print $ length $ handShakeMsg d' peerId
-      Left e -> printError e
-    putStrLn "done"
+
+              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 $ getPeers $ 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