]> git.rkrishnan.org Git - functorrent.git/blobdiff - src/Main.hs
Absolute import everywhere, cleanup
[functorrent.git] / src / Main.hs
index 32dc41a83099fe89bb8442e7a8f5b2554c67b793..50eb5d1e650da9d48e990db5e487f6e6cb9b7a0a 100644 (file)
@@ -1,45 +1,47 @@
 module Main where
 
+import Prelude hiding (length, readFile)
+
+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 Peer (getPeers, getPeerResponse, handShakeMsg)
 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 ()
+import System.Exit (exitSuccess)
+import Tracker (connect, prepareRequest)
+import Text.ParserCombinators.Parsec (ParseError)
+
+printError :: ParseError -> IO ()
 printError e = putStrLn $ "parse error: " ++ show e
 
 peerId :: String
 peerId = "-HS0001-*-*-20150215"
 
-exit :: IO BC.ByteString
+exit :: IO ByteString
 exit = exitSuccess
 
 usage :: IO ()
 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] = readFile a
 parse _ = exit
 
 main :: IO ()
 main = do
     args <- getArgs
     torrentStr <- parse args
-    case Benc.decode torrentStr of
+    case decode torrentStr of
       Right d ->
-          case MInfo.mkMetaInfo d of
+          case mkMetaInfo d of
             Nothing -> putStrLn "parse error"
             Just m -> do
-              let len = MInfo.lengthInBytes (MInfo.info m)
-                  (Benc.Bdict d') = d
-              body <- BC.pack <$> T.connect (MInfo.announce m) (T.prepareRequest d' peerId len)
-              print (P.getPeers (P.getPeerResponse body))
-              print (BC.length (P.handShakeMsg d' peerId))
+              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"