]> git.rkrishnan.org Git - functorrent.git/blobdiff - src/Main.hs
Move things around
[functorrent.git] / src / Main.hs
index c23b97ed5baadc7f0390cc5c8246770a72124990..3537e48865c4d08d3a91f9f7908e01bd8554b7be 100644 (file)
@@ -2,16 +2,17 @@
 module Main where
 
 import Prelude hiding (length, readFile, writeFile)
-import Data.ByteString.Char8 (ByteString, length, readFile, writeFile, length)
+import Data.ByteString.Char8 (ByteString, readFile, writeFile, length, unpack)
 import System.Environment (getArgs)
 import System.Exit (exitSuccess)
+import System.Directory (doesFileExist)
 import Text.ParserCombinators.Parsec (ParseError)
 
 import FuncTorrent.Bencode (decode, BVal(..))
 import FuncTorrent.Logger (initLogger, logMessage, logStop)
-import FuncTorrent.Metainfo (announce, lengthInBytes, mkMetaInfo, info, name)
-import FuncTorrent.Peer (getPeers, getPeerResponse, handShakeMsg)
-import FuncTorrent.Tracker (connect, prepareRequest)
+import FuncTorrent.Metainfo (Info(..), Metainfo(..), mkMetaInfo)
+import FuncTorrent.Peer (handShakeMsg)
+import FuncTorrent.Tracker (connect, prepareRequest, peers, mkTrackerResponse)
 
 logError :: ParseError -> (String -> IO ()) -> IO ()
 logError e logMsg = logMsg $ "parse error: \n" ++ show e
@@ -27,7 +28,11 @@ usage = putStrLn "usage: functorrent torrent-file"
 
 parse :: [String] -> IO ByteString
 parse [] = usage >> exit
-parse [a] = readFile a
+parse [a] = do
+  fileExist <- doesFileExist a
+  if fileExist
+    then readFile a
+    else error "file does not exist"
 parse _ = exit
 
 main :: IO ()
@@ -46,18 +51,24 @@ main = do
 
               let len = lengthInBytes $ info m
                   (Bdict d') = d
+                  trackers = announceList m
 
               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
+              response <- connect (head trackers) (prepareRequest d' peerId len)
 
               let hsMsgLen = show $ length $ handShakeMsg d' peerId
               logMsg $ "Hand-shake message length : " ++ hsMsgLen
 
+              -- TODO: Write to ~/.functorrent/caches
+              writeFile (name (info m) ++ ".cache") response
+
+              case decode response of
+                Right trackerInfo ->
+                    case mkTrackerResponse trackerInfo of
+                      Right peerResp ->
+                          logMsg $ "Peers List : " ++ (show . peers $ peerResp)
+                      Left e -> logMsg $ "Error" ++ unpack e
+                Left e -> logError e logMsg
+
       Left e -> logError e logMsg
     logStop logR