summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorSam Truzjan <pxqr.sta@gmail.com>2014-02-15 07:20:00 +0400
committerSam Truzjan <pxqr.sta@gmail.com>2014-02-15 07:20:00 +0400
commit406e274759b325b9987634e5f9e1536760b87c8f (patch)
tree62110619826758ff63d2e20632c41313fc65af41
parentee1549c48c72f127622961df2e8e0472fcb77b13 (diff)
Add command line arguments to tiny client
-rw-r--r--examples/Client.hs69
1 files changed, 54 insertions, 15 deletions
diff --git a/examples/Client.hs b/examples/Client.hs
index 320b4269..abf62657 100644
--- a/examples/Client.hs
+++ b/examples/Client.hs
@@ -1,26 +1,65 @@
1{-# LANGUAGE RankNTypes #-}
2{-# LANGUAGE ExistentialQuantification #-}
3{-# LANGUAGE RecordWildCards #-}
1module Main (main) where 4module Main (main) where
2import Control.Concurrent 5import Control.Concurrent
3import Control.Monad.Trans 6import Control.Monad.Trans
7import Options.Applicative
4import System.Environment 8import System.Environment
5import System.Exit 9import System.Exit
6import System.IO 10import System.IO
11import Text.Read
12
7import Network.BitTorrent 13import Network.BitTorrent
8 14
9 15
10parseArgs :: IO FilePath 16{-----------------------------------------------------------------------
11parseArgs = do 17-- Command line arguments
12 args <- getArgs 18-----------------------------------------------------------------------}
13 case args of 19
14 [path] -> return path 20data TorrentBox = forall s. TorrentSource s => TorrentBox { unTorrentBox :: s }
15 _ -> do 21
16 hPutStrLn stderr "Usage: client file.torrent" 22data Args = Args
17 exitFailure 23 { topic :: TorrentBox
24 , contentDir :: FilePath
25 }
26
27argsParser :: Parser Args
28argsParser = Args <$> (TorrentBox <$> infohashP <|> TorrentBox <$> torrentP)
29 <*> destDirP
30 where
31 infohashP :: Parser InfoHash
32 infohashP = argument readMaybe
33 (metavar "SHA1" <> help "infohash of torrent file")
34
35 torrentP :: Parser FilePath
36 torrentP = argument Just
37 ( metavar "FILE"
38 <> help "A .torrent file"
39 )
40
41 destDirP :: Parser FilePath
42 destDirP = argument Just
43 ( metavar "DIR"
44 <> help "Directory to put content"
45 )
46
47argsInfo :: ParserInfo Args
48argsInfo = info (helper <*> argsParser)
49 ( fullDesc
50 <> progDesc "A simple CLI bittorrent client"
51 <> header "foo"
52 )
53
54{-----------------------------------------------------------------------
55-- Client
56-----------------------------------------------------------------------}
57
58run :: Args -> BitTorrent ()
59run (Args (TorrentBox t) dir) = do
60 h <- openHandle dir t
61 start h
62 liftIO $ threadDelay 10000000000
18 63
19main :: IO () 64main :: IO ()
20main = do 65main = execParser argsInfo >>= simpleClient . run
21 path <- parseArgs
22 torrent <- fromFile path
23 simpleClient $ do
24 h <- openTorrent "data" torrent
25 start h
26 liftIO $ threadDelay 10000000000