]> git.rkrishnan.org Git - functorrent.git/blob - src/main/Main.hs
print and error and exit if called without arguments
[functorrent.git] / src / main / Main.hs
1 {-# LANGUAGE OverloadedStrings #-}
2 {-
3 Copyright (C) 2015-2016 Ramakrishnan Muthukrishnan <ram@rkrishnan.org>
4
5 This file is part of FuncTorrent.
6
7 FuncTorrent is free software; you can redistribute it and/or modify
8 it under the terms of the GNU General Public License as published by
9 the Free Software Foundation; either version 3 of the License, or
10 (at your option) any later version.
11
12 FuncTorrent is distributed in the hope that it will be useful,
13 but WITHOUT ANY WARRANTY; without even the implied warranty of
14 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15 GNU General Public License for more details.
16
17 You should have received a copy of the GNU General Public License
18 along with FuncTorrent; if not,  see <http://www.gnu.org/licenses/>
19 -}
20
21 module Main where
22
23 import           Prelude hiding (log, length, readFile, getContents)
24
25 import           Control.Concurrent (forkIO, killThread)
26 import           Control.Concurrent.MVar (readMVar)
27 import           Data.ByteString.Char8 (ByteString, getContents, readFile)
28 import qualified FuncTorrent.FileSystem as FS (createMsgChannel, pieceMapFromFile, run)
29 import           FuncTorrent.Logger (initLogger, logMessage, logStop)
30 import           FuncTorrent.Metainfo (Info(..), Metainfo(..), torrentToMetainfo)
31 import           FuncTorrent.Peer (handlePeerMsgs)
32 import           FuncTorrent.PieceManager (initPieceMap)
33 import qualified FuncTorrent.Server as Server
34 import           FuncTorrent.Tracker (runTracker, getConnectedPeers, newTracker)
35 import           Network (PortID (PortNumber))
36 import           System.IO (withFile, IOMode (ReadWriteMode))
37 import           System.Directory (doesFileExist)
38 import           System.Environment (getArgs)
39 import           System.Exit (exitSuccess)
40 import           System.Random (getStdGen, randomRs)
41
42 logError :: String -> (String -> IO ()) -> IO ()
43 logError e logMsg = logMsg $ "parse error: \n" ++ e
44
45 exit :: IO ByteString
46 exit = exitSuccess
47
48 usage :: String
49 usage = "usage: functorrent torrent-file"
50
51 parse :: [String] -> IO ByteString
52 parse [] = getContents
53 parse [a] = do
54   fileExist <- doesFileExist a
55   if fileExist
56     then readFile a
57     else error "file does not exist"
58 parse _ = exit
59
60 -- peer id is exactly 20 bytes long.
61 -- peer id starts with '-', followed by 2 char client id'
62 -- followed by 4 ascii digits for version number, followed by
63 -- a '-'. Rest are random digits to fill the 20 bytes.
64 mkPeerID :: IO String
65 mkPeerID = do
66   stdgen <- getStdGen
67   let digits = randomRs (0, 9) stdgen :: [Integer]
68   return $ "-HS9001-" ++ (concatMap show $ take (20 - 8) digits)
69
70 main :: IO ()
71 main = do
72     args <- getArgs
73     logR <- initLogger
74     peerId <- mkPeerID    
75     let log = logMessage logR
76     case args of
77       [] -> do
78         log usage
79       _  -> do
80         log "Starting up functorrent"
81         log $ "Parsing arguments " ++ concat args
82         torrentStr <- parse args
83         case torrentToMetainfo torrentStr of
84           Left e -> logError e log
85           Right m -> do
86             -- if we had downloaded the file before (partly or completely)
87             -- then we should check the current directory for the existence
88             -- of the file and then update the map of each piece' availability.
89             -- This can be done by reading each piece and verifying the checksum.
90             -- If the checksum does not match, we don't have that piece.
91             let filePath = name (info m) -- really this is just the file name, not file path
92                 fileLen = lengthInBytes (info m)
93                 pieceHash = pieces (info m)
94                 pLen = pieceLength (info m)
95                 infohash = infoHash m
96                 defaultPieceMap = initPieceMap pieceHash fileLen pLen
97             log $ "create FS msg channel"
98             fsMsgChannel <- FS.createMsgChannel
99             log $ "Downloading file : " ++ filePath
100             pieceMap <- FS.pieceMapFromFile filePath fileLen defaultPieceMap
101             log $ "start filesystem manager thread"
102             fsTid <- forkIO $ withFile filePath ReadWriteMode (FS.run pieceMap fsMsgChannel)
103             log $ "starting server"
104             (serverSock, (PortNumber portnum)) <- Server.start
105             log $ "server started on " ++ show portnum
106             log "Trying to fetch peers"
107             _ <- forkIO $ Server.run serverSock peerId m pieceMap fsMsgChannel
108             log $ "Trackers: " ++ head (announceList m)
109             trackerMsgChan <- newTracker
110             _ <- forkIO $ runTracker trackerMsgChan fsMsgChannel infohash portnum peerId (announceList m) fileLen
111             ps <- getConnectedPeers trackerMsgChan
112             log $ "Peers List : " ++ (show ps)
113             let p1 = head ps
114             handlePeerMsgs p1 peerId m pieceMap True fsMsgChannel
115             logStop logR
116             killThread fsTid