diff options
Diffstat (limited to 'bittorrent/examples')
-rw-r--r-- | bittorrent/examples/Client.hs | 74 | ||||
-rw-r--r-- | bittorrent/examples/FS.hs | 74 | ||||
-rw-r--r-- | bittorrent/examples/MkTorrent.hs | 500 |
3 files changed, 0 insertions, 648 deletions
diff --git a/bittorrent/examples/Client.hs b/bittorrent/examples/Client.hs deleted file mode 100644 index 26711676..00000000 --- a/bittorrent/examples/Client.hs +++ /dev/null | |||
@@ -1,74 +0,0 @@ | |||
1 | {-# LANGUAGE RankNTypes #-} | ||
2 | {-# LANGUAGE CPP #-} | ||
3 | {-# LANGUAGE ExistentialQuantification #-} | ||
4 | {-# LANGUAGE RecordWildCards #-} | ||
5 | module Main (main) where | ||
6 | import Control.Concurrent | ||
7 | import Control.Monad.Trans | ||
8 | import Data.Maybe | ||
9 | import Options.Applicative | ||
10 | import System.Environment | ||
11 | import System.Exit | ||
12 | import System.IO | ||
13 | import Text.Read | ||
14 | |||
15 | import Network.BitTorrent | ||
16 | |||
17 | #if MIN_VERSION_optparse_applicative(0,13,0) | ||
18 | -- maybeReader imported from Options.Applicative.Builder | ||
19 | #elif MIN_VERSION_optparse_applicative(0,11,0) | ||
20 | maybeReader f = eitherReader (maybe (Left ":(") Right . f) | ||
21 | #else | ||
22 | maybeReader f = f | ||
23 | #endif | ||
24 | |||
25 | {----------------------------------------------------------------------- | ||
26 | -- Command line arguments | ||
27 | -----------------------------------------------------------------------} | ||
28 | |||
29 | data TorrentBox = forall s. TorrentSource s => TorrentBox { unTorrentBox :: s } | ||
30 | |||
31 | data Args = Args | ||
32 | { topic :: TorrentBox | ||
33 | , contentDir :: FilePath | ||
34 | } | ||
35 | |||
36 | argsParser :: Parser Args | ||
37 | argsParser = Args <$> (TorrentBox <$> infohashP <|> TorrentBox <$> torrentP) | ||
38 | <*> destDirP | ||
39 | where | ||
40 | infohashP :: Parser InfoHash | ||
41 | infohashP = argument (maybeReader readMaybe) | ||
42 | (metavar "SHA1" <> help "infohash of torrent file") | ||
43 | |||
44 | torrentP :: Parser FilePath | ||
45 | torrentP = argument (maybeReader Just) | ||
46 | ( metavar "FILE" | ||
47 | <> help "A .torrent file" | ||
48 | ) | ||
49 | |||
50 | destDirP :: Parser FilePath | ||
51 | destDirP = argument (maybeReader Just) | ||
52 | ( metavar "DIR" | ||
53 | <> help "Directory to put content" | ||
54 | ) | ||
55 | |||
56 | argsInfo :: ParserInfo Args | ||
57 | argsInfo = info (helper <*> argsParser) | ||
58 | ( fullDesc | ||
59 | <> progDesc "A simple CLI bittorrent client" | ||
60 | <> header "foo" | ||
61 | ) | ||
62 | |||
63 | {----------------------------------------------------------------------- | ||
64 | -- Client | ||
65 | -----------------------------------------------------------------------} | ||
66 | |||
67 | run :: Args -> BitTorrent () | ||
68 | run (Args (TorrentBox t) dir) = do | ||
69 | h <- openHandle dir t | ||
70 | start h | ||
71 | liftIO $ threadDelay 10000000000 | ||
72 | |||
73 | main :: IO () | ||
74 | main = execParser argsInfo >>= simpleClient . run | ||
diff --git a/bittorrent/examples/FS.hs b/bittorrent/examples/FS.hs deleted file mode 100644 index 550d85a7..00000000 --- a/bittorrent/examples/FS.hs +++ /dev/null | |||
@@ -1,74 +0,0 @@ | |||
1 | {-# LANGUAGE RecordWildCards #-} | ||
2 | module Main (main) where | ||
3 | |||
4 | import Control.Arrow | ||
5 | import Data.ByteString.Char8 as BC | ||
6 | import Data.List as L | ||
7 | import Data.Map as M | ||
8 | import Data.Torrent as T | ||
9 | import Data.Torrent.Tree as T | ||
10 | import System.Environment | ||
11 | import System.Fuse | ||
12 | import System.FilePath | ||
13 | import System.Posix.Files | ||
14 | |||
15 | |||
16 | defStat :: FileStat | ||
17 | defStat = FileStat | ||
18 | { statEntryType = Unknown | ||
19 | , statFileMode = ownerReadMode | ||
20 | , statLinkCount = 2 | ||
21 | |||
22 | , statFileOwner = 0 | ||
23 | , statFileGroup = 0 | ||
24 | |||
25 | , statSpecialDeviceID = 0 | ||
26 | |||
27 | , statFileSize = 0 | ||
28 | , statBlocks = 0 | ||
29 | |||
30 | , statAccessTime = 0 | ||
31 | , statModificationTime = 0 | ||
32 | , statStatusChangeTime = 0 | ||
33 | } | ||
34 | |||
35 | dirStat :: FileStat | ||
36 | dirStat = defStat { | ||
37 | statEntryType = Directory | ||
38 | } | ||
39 | |||
40 | type Result a = IO (Either Errno a) | ||
41 | type Result' = IO Errno | ||
42 | |||
43 | fsGetFileStat :: Torrent -> FilePath -> Result FileStat | ||
44 | fsGetFileStat _ path = return $ Right dirStat | ||
45 | |||
46 | fsOpenDirectory :: Torrent -> FilePath -> Result' | ||
47 | fsOpenDirectory _ _ = return eOK | ||
48 | |||
49 | fsReadDirectory :: Torrent -> FilePath -> Result [(FilePath, FileStat)] | ||
50 | fsReadDirectory Torrent {tInfoDict = InfoDict {..}} path | ||
51 | | Just cs <- T.lookupDir (L.tail (splitDirectories path)) tree = | ||
52 | return $ Right $ L.map (BC.unpack *** const defStat) cs | ||
53 | | otherwise = return $ Left eNOENT | ||
54 | where | ||
55 | tree = build $ idLayoutInfo | ||
56 | |||
57 | fsReleaseDirectory :: Torrent -> FilePath -> Result' | ||
58 | fsReleaseDirectory _ _ = return eOK | ||
59 | |||
60 | exfsOps :: Torrent -> FuseOperations () | ||
61 | exfsOps t = defaultFuseOps | ||
62 | { fuseGetFileStat = fsGetFileStat t | ||
63 | |||
64 | , fuseOpenDirectory = fsOpenDirectory t | ||
65 | , fuseReadDirectory = fsReadDirectory t | ||
66 | , fuseReleaseDirectory = fsReleaseDirectory t | ||
67 | } | ||
68 | |||
69 | main :: IO () | ||
70 | main = do | ||
71 | x : xs <- getArgs | ||
72 | t <- fromFile x | ||
73 | withArgs xs $ do | ||
74 | fuseMain (exfsOps t) defaultExceptionHandler \ No newline at end of file | ||
diff --git a/bittorrent/examples/MkTorrent.hs b/bittorrent/examples/MkTorrent.hs deleted file mode 100644 index 88a84893..00000000 --- a/bittorrent/examples/MkTorrent.hs +++ /dev/null | |||
@@ -1,500 +0,0 @@ | |||
1 | {-# LANGUAGE CPP #-} | ||
2 | {-# LANGUAGE OverloadedStrings #-} | ||
3 | {-# LANGUAGE RecordWildCards #-} | ||
4 | {-# LANGUAGE StandaloneDeriving #-} | ||
5 | {-# OPTIONS -fno-warn-orphans #-} | ||
6 | module Main (main) where | ||
7 | |||
8 | import Prelude as P | ||
9 | import Control.Concurrent | ||
10 | import Control.Concurrent.Async.Lifted | ||
11 | import Control.Concurrent.ParallelIO | ||
12 | import Control.Exception | ||
13 | import Control.Lens hiding (argument, (<.>)) | ||
14 | import Control.Monad as M | ||
15 | import Control.Monad.Trans | ||
16 | import Data.Conduit as C | ||
17 | import Data.Conduit.List as C | ||
18 | import Data.List as L | ||
19 | import Data.Maybe as L | ||
20 | import Data.Monoid | ||
21 | import Data.Text as T | ||
22 | import qualified Data.Text.IO as T | ||
23 | import Data.Text.Read as T | ||
24 | import Data.Version | ||
25 | import Network | ||
26 | import Network.URI | ||
27 | import Options.Applicative | ||
28 | import System.Exit | ||
29 | import System.FilePath | ||
30 | import System.Log | ||
31 | import System.Log.Logger | ||
32 | import Text.Read | ||
33 | import Text.PrettyPrint.HughesPJClass hiding ((<>),($$)) | ||
34 | |||
35 | import Paths_bittorrent (version) | ||
36 | import Data.Torrent hiding (Magnet (Magnet)) | ||
37 | import Network.Address | ||
38 | import Network.BitTorrent.DHT.Session hiding (Options, options) | ||
39 | import Network.BitTorrent.DHT as DHT hiding (Options) | ||
40 | import Network.BitTorrent.Exchange.Bitfield as BF | ||
41 | import Network.BitTorrent.Exchange.Connection hiding (Options) | ||
42 | import Network.BitTorrent.Exchange.Message | ||
43 | import Network.BitTorrent.Exchange.Session | ||
44 | import System.Torrent.Storage | ||
45 | |||
46 | #if MIN_VERSION_optparse_applicative(0,13,0) | ||
47 | -- maybeReader imported from Options.Applicative.Builder | ||
48 | #elif MIN_VERSION_optparse_applicative(0,11,0) | ||
49 | maybeReader f = eitherReader (maybe (Left ":(") Right . f) | ||
50 | #else | ||
51 | maybeReader f = f | ||
52 | #endif | ||
53 | |||
54 | |||
55 | {----------------------------------------------------------------------- | ||
56 | -- Dialogs | ||
57 | -----------------------------------------------------------------------} | ||
58 | |||
59 | instance Read URI where | ||
60 | readsPrec _ = f . parseURI | ||
61 | where | ||
62 | f Nothing = [] | ||
63 | f (Just u) = [(u, "")] | ||
64 | |||
65 | question :: Show a => Text -> Maybe a -> IO () | ||
66 | question q defVal = do | ||
67 | T.putStrLn q | ||
68 | case defVal of | ||
69 | Nothing -> return () | ||
70 | Just v -> T.putStrLn $ "[default: " <> T.pack (show v) <> "]" | ||
71 | |||
72 | ask :: Read a => Text -> IO a | ||
73 | ask q = question q (Just True) >> getReply | ||
74 | where | ||
75 | getReply = do | ||
76 | resp <- P.getLine | ||
77 | maybe getReply return $ readMaybe resp | ||
78 | |||
79 | askMaybe :: Read a => Text -> IO (Maybe a) | ||
80 | askMaybe q = question q (Just False) >> getReply | ||
81 | where | ||
82 | getReply = do | ||
83 | resp <- P.getLine | ||
84 | if resp == [] | ||
85 | then return Nothing | ||
86 | else maybe getReply return $ readMaybe resp | ||
87 | |||
88 | askURI :: IO URI | ||
89 | askURI = do | ||
90 | s <- P.getLine | ||
91 | case parseURI s of | ||
92 | Nothing -> T.putStrLn "incorrect URI" >> askURI | ||
93 | Just u -> return u | ||
94 | |||
95 | askFreeform :: IO Text | ||
96 | askFreeform = do | ||
97 | s <- T.getLine | ||
98 | if T.null s | ||
99 | then askFreeform | ||
100 | else return s | ||
101 | |||
102 | askInRange :: Int -> Int -> IO Int | ||
103 | askInRange a b = do | ||
104 | s <- T.getLine | ||
105 | case T.decimal s of | ||
106 | Left msg -> do | ||
107 | P.putStrLn msg | ||
108 | askInRange a b | ||
109 | Right (i, _) | ||
110 | | a <= i && i < b -> return i | ||
111 | | otherwise -> do | ||
112 | T.putStrLn "not in range " | ||
113 | askInRange a b | ||
114 | |||
115 | askChoice :: [(Text, a)] -> IO a | ||
116 | askChoice kvs = do | ||
117 | forM_ (L.zip [1 :: Int ..] $ L.map fst kvs) $ \(i, lbl) -> do | ||
118 | T.putStrLn $ " " <> T.pack (show i) <> ") " <> lbl | ||
119 | T.putStrLn "Your choice?" | ||
120 | n <- askInRange 1 (succ (L.length kvs)) | ||
121 | return $ snd (kvs !! pred n) | ||
122 | |||
123 | {----------------------------------------------------------------------- | ||
124 | -- Helpers | ||
125 | -----------------------------------------------------------------------} | ||
126 | |||
127 | torrentFile :: Parser FilePath | ||
128 | torrentFile = argument (maybeReader Just) | ||
129 | ( metavar "TORRENT_FILE_PATH" | ||
130 | <> help "A .torrent file" | ||
131 | ) | ||
132 | |||
133 | {----------------------------------------------------------------------- | ||
134 | -- Amend command - edit a field of torrent file | ||
135 | -----------------------------------------------------------------------} | ||
136 | |||
137 | data AmendOpts = AmendOpts FilePath | ||
138 | deriving Show | ||
139 | |||
140 | amendInfo :: ParserInfo AmendOpts | ||
141 | amendInfo = info (helper <*> parser) modifier | ||
142 | where | ||
143 | modifier = progDesc "Edit info fields of existing torrent" | ||
144 | parser = AmendOpts <$> torrentFile | ||
145 | |||
146 | type Amend = Torrent -> Torrent | ||
147 | |||
148 | fields :: [(Text, IO Amend)] | ||
149 | fields = [ ("announce", set announce . Just <$> askURI) | ||
150 | , ("comment", set comment . Just <$> askFreeform) | ||
151 | , ("created by", set createdBy . Just <$> askFreeform) | ||
152 | , ("publisher url", set publisherURL . Just <$> askURI) | ||
153 | ] | ||
154 | |||
155 | askAmend :: IO Amend | ||
156 | askAmend = join $ T.putStrLn "Choose a field:" >> askChoice fields | ||
157 | |||
158 | amend :: AmendOpts -> IO () | ||
159 | amend (AmendOpts tpath) = do | ||
160 | t <- fromFile tpath | ||
161 | a <- askAmend | ||
162 | toFile tpath $ a t | ||
163 | |||
164 | {----------------------------------------------------------------------- | ||
165 | -- Check command -- validate content files using torrent file | ||
166 | -----------------------------------------------------------------------} | ||
167 | -- TODO progress bar | ||
168 | |||
169 | data CheckOpts = CheckOpts | ||
170 | { checkTorrentPath :: FilePath -- ^ validation torrent file | ||
171 | , checkContentPath :: FilePath -- ^ root dir for content files | ||
172 | } deriving Show | ||
173 | |||
174 | checkInfo :: ParserInfo CheckOpts | ||
175 | checkInfo = info (helper <*> parser) modifier | ||
176 | where | ||
177 | modifier = progDesc "Validate integrity of torrent data" | ||
178 | <> header "append +RTS -N$NUMBER_OF_CORES -RTS for parallel execution" | ||
179 | parser = CheckOpts | ||
180 | <$> torrentFile | ||
181 | <*> argument (maybeReader Just) | ||
182 | ( metavar "CONTENT_DIR_PATH" | ||
183 | <> value "." | ||
184 | <> help "Content directory or a single file" | ||
185 | ) | ||
186 | |||
187 | validatePiece :: Storage -> PieceInfo -> PieceIx -> IO (Maybe PieceIx) | ||
188 | validatePiece s pinfo pix = do | ||
189 | valid <- verifyPiece s pinfo pix | ||
190 | if valid | ||
191 | then do infoM "check" $ "valid piece " ++ show pix | ||
192 | return (Just pix) | ||
193 | else do infoM "check" $ "invalid piece " ++ show pix | ||
194 | return Nothing | ||
195 | |||
196 | validateStorage :: Storage -> PieceInfo -> IO Bitfield | ||
197 | validateStorage s pinfo = do | ||
198 | infoM "check" "start storage validation" | ||
199 | let total = totalPieces s | ||
200 | pixs <- parallel $ L.map (validatePiece s pinfo) [0 .. total - 1] | ||
201 | infoM "check" "storage validation finished" | ||
202 | return $ fromList total $ L.catMaybes pixs | ||
203 | |||
204 | -- TODO use local thread pool | ||
205 | checkContent :: Storage -> PieceInfo -> IO () | ||
206 | checkContent s pinfo = do | ||
207 | invalids <- BF.complement <$> validateStorage s pinfo | ||
208 | if BF.null invalids | ||
209 | then noticeM "check" "all files are complete and valid" | ||
210 | else do | ||
211 | emergencyM "check" $ "there are some invalid pieces" ++ show invalids | ||
212 | exitFailure | ||
213 | |||
214 | checkTorrent :: CheckOpts -> IO () | ||
215 | checkTorrent CheckOpts {..} = do | ||
216 | infoM "check" "openning torrent file..." | ||
217 | InfoDict {..} <- tInfoDict <$> fromFile checkTorrentPath | ||
218 | let layout = flatLayout checkContentPath idLayoutInfo | ||
219 | infoM "check" "mapping content files..." | ||
220 | withStorage ReadOnly (piPieceLength idPieceInfo) layout $ \ s -> do | ||
221 | infoM "check" "files mapped" | ||
222 | checkContent s idPieceInfo | ||
223 | infoM "check" "unmapping files" | ||
224 | |||
225 | {----------------------------------------------------------------------- | ||
226 | -- Create command | ||
227 | -----------------------------------------------------------------------} | ||
228 | -- TODO progress bar | ||
229 | -- TODO multifile torrents | ||
230 | -- TODO interactive mode | ||
231 | -- TODO non interactive mode | ||
232 | -- TODO --ignore-dot-files | ||
233 | -- TODO --md5 | ||
234 | -- TODO --piece-size | ||
235 | |||
236 | {- | ||
237 | createFlags :: Parser CreateFlags | ||
238 | createFlags = CreateFlags | ||
239 | <$> optional (option | ||
240 | ( long "piece-size" | ||
241 | <> short 's' | ||
242 | <> metavar "SIZE" | ||
243 | <> help "Set size of torrent pieces" | ||
244 | )) | ||
245 | <*> switch | ||
246 | ( long "md5" | ||
247 | <> short '5' | ||
248 | <> help "Include md5 hash of each file" | ||
249 | ) | ||
250 | <*> switch | ||
251 | ( long "ignore-dot-files" | ||
252 | <> short 'd' | ||
253 | <> help "Do not include .* files" | ||
254 | ) | ||
255 | |||
256 | |||
257 | createOpts :: Parser CreateOpts | ||
258 | createOpts = CreateOpts | ||
259 | <$> argument (maybeReader Just) | ||
260 | ( metavar "PATH" | ||
261 | <> help "Content directory or a single file" | ||
262 | ) | ||
263 | <*> optional (argument (maybeReader Just) | ||
264 | ( metavar "FILE" | ||
265 | <> help "Place for the output .torrent file" | ||
266 | )) | ||
267 | <*> createFlags | ||
268 | |||
269 | createInfo :: ParserInfo CreateOpts | ||
270 | createInfo = info (helper <*> createOpts) modifier | ||
271 | where | ||
272 | modifier = progDesc "Make a new .torrent file" | ||
273 | -} | ||
274 | |||
275 | {----------------------------------------------------------------------- | ||
276 | -- Magnet command -- print magnet link for given torrent file | ||
277 | -----------------------------------------------------------------------} | ||
278 | |||
279 | data MagnetOpts = MagnetOpts | ||
280 | { magnetFile :: FilePath -- ^ path to torrent file | ||
281 | , detailed :: Bool -- ^ whether to append additional uri params | ||
282 | } deriving Show | ||
283 | |||
284 | magnetInfo :: ParserInfo MagnetOpts | ||
285 | magnetInfo = info (helper <*> parser) modifier | ||
286 | where | ||
287 | modifier = progDesc "Print magnet link" | ||
288 | parser = MagnetOpts | ||
289 | <$> torrentFile | ||
290 | <*> switch ( long "detailed" ) | ||
291 | |||
292 | magnet :: MagnetOpts -> IO () | ||
293 | magnet MagnetOpts {..} = print . magnetLink =<< fromFile magnetFile | ||
294 | where | ||
295 | magnetLink = if detailed then detailedMagnet else simpleMagnet | ||
296 | |||
297 | {----------------------------------------------------------------------- | ||
298 | -- Show command - print torrent file information | ||
299 | -----------------------------------------------------------------------} | ||
300 | |||
301 | data ShowOpts = ShowOpts | ||
302 | { showPath :: FilePath -- ^ torrent file to inspect; | ||
303 | , infoHashOnly :: Bool -- ^ omit everything except infohash. | ||
304 | } deriving Show | ||
305 | |||
306 | showInfo :: ParserInfo ShowOpts | ||
307 | showInfo = info (helper <*> parser) modifier | ||
308 | where | ||
309 | modifier = progDesc "Print .torrent file metadata" | ||
310 | parser = ShowOpts | ||
311 | <$> torrentFile | ||
312 | <*> switch | ||
313 | ( long "infohash" | ||
314 | <> help "Show only hash of the torrent info part" | ||
315 | ) | ||
316 | |||
317 | showTorrent :: ShowOpts -> Torrent -> ShowS | ||
318 | showTorrent ShowOpts {..} torrent | ||
319 | | infoHashOnly = shows $ idInfoHash (tInfoDict torrent) | ||
320 | | otherwise = shows $ pPrint torrent | ||
321 | |||
322 | putTorrent :: ShowOpts -> IO () | ||
323 | putTorrent opts @ ShowOpts {..} = do | ||
324 | torrent <- fromFile showPath `onException` putStrLn msg | ||
325 | putStrLn $ showTorrent opts torrent [] | ||
326 | where | ||
327 | msg = "Torrent file is either invalid or do not exist" | ||
328 | |||
329 | {----------------------------------------------------------------------- | ||
330 | -- Get command - fetch torrent by infohash | ||
331 | -----------------------------------------------------------------------} | ||
332 | |||
333 | data GetOpts = GetOpts | ||
334 | { topic :: InfoHash | ||
335 | , servPort :: PortNumber | ||
336 | , bootNode :: NodeAddr IPv4 | ||
337 | , buckets :: Int | ||
338 | } deriving Show | ||
339 | |||
340 | #if !MIN_VERSION_network(2,6,3) | ||
341 | instance Read PortNumber where | ||
342 | readsPrec i s = [ (toEnum a, t) | (a, t) <- readsPrec i s] | ||
343 | #endif | ||
344 | |||
345 | paramsParser :: Parser GetOpts | ||
346 | paramsParser = GetOpts | ||
347 | <$> argument (maybeReader readMaybe) | ||
348 | (metavar "SHA1" <> help "infohash of torrent file") | ||
349 | <*> option auto (long "port" <> short 'p' | ||
350 | <> value 7000 <> showDefault | ||
351 | <> metavar "NUM" <> help "port number to bind" | ||
352 | ) | ||
353 | <*> option auto (long "boot" <> short 'b' | ||
354 | <> metavar "NODE" <> help "bootstrap node address" | ||
355 | ) | ||
356 | <*> option auto (long "bucket" <> short 'n' | ||
357 | <> value 2 <> showDefault | ||
358 | <> metavar "NUM" <> help "number of buckets to maintain" | ||
359 | ) | ||
360 | |||
361 | getInfo :: ParserInfo GetOpts | ||
362 | getInfo = info (helper <*> paramsParser) | ||
363 | ( fullDesc | ||
364 | <> progDesc "Get torrent file by infohash" | ||
365 | <> header "get torrent file by infohash" | ||
366 | ) | ||
367 | |||
368 | -- TODO add tNodes, tCreated, etc? | ||
369 | getTorrent :: GetOpts -> IO () | ||
370 | getTorrent GetOpts {..} = do | ||
371 | infoM "get" "searching for peers..." | ||
372 | s <- newSession (\ _ _ _ _ -> return ()) (PeerAddr Nothing Nothing 7000) "/tmp" (Left topic) | ||
373 | dht (def { optBucketCount = buckets }) (NodeAddr "0.0.0.0" servPort) $ do | ||
374 | bootstrap [bootNode] | ||
375 | infodict <- withAsync (DHT.lookup topic $$ connectSink s) | ||
376 | (const (liftIO $ waitMetadata s)) | ||
377 | liftIO $ toFile (show topic <.> torrentExt) $ nullTorrent infodict | ||
378 | infoM "get" "saved torrent file" | ||
379 | |||
380 | {----------------------------------------------------------------------- | ||
381 | -- Command | ||
382 | -----------------------------------------------------------------------} | ||
383 | |||
384 | data Command | ||
385 | = Amend AmendOpts | ||
386 | | Check CheckOpts | ||
387 | -- | Create CreateOpts | ||
388 | | Get GetOpts | ||
389 | | Magnet MagnetOpts | ||
390 | | Show ShowOpts | ||
391 | deriving Show | ||
392 | |||
393 | commandOpts :: Parser Command | ||
394 | commandOpts = subparser $ mconcat | ||
395 | [ command "amend" (Amend <$> amendInfo) | ||
396 | , command "check" (Check <$> checkInfo) | ||
397 | -- , command "create" (Create <$> createInfo) | ||
398 | , command "get" (Get <$> getInfo) | ||
399 | , command "magnet" (Magnet <$> magnetInfo) | ||
400 | , command "show" (Show <$> showInfo) | ||
401 | ] | ||
402 | |||
403 | {----------------------------------------------------------------------- | ||
404 | -- Global Options | ||
405 | -----------------------------------------------------------------------} | ||
406 | |||
407 | data GlobalOpts = GlobalOpts | ||
408 | { verbosity :: Priority | ||
409 | } deriving Show | ||
410 | |||
411 | #if !MIN_VERSION_hslogger(1,2,9) | ||
412 | deriving instance Enum Priority | ||
413 | deriving instance Bounded Priority | ||
414 | #endif | ||
415 | |||
416 | priorities :: [Priority] | ||
417 | priorities = [minBound..maxBound] | ||
418 | |||
419 | defaultPriority :: Priority | ||
420 | defaultPriority = WARNING | ||
421 | |||
422 | verbosityOpts :: Parser Priority | ||
423 | verbosityOpts = verbosityP <|> verboseP <|> quietP | ||
424 | where | ||
425 | verbosityP = option auto | ||
426 | ( long "verbosity" | ||
427 | <> metavar "LEVEL" | ||
428 | <> help ("Set verbosity level\n" | ||
429 | ++ "Possible values are " ++ show priorities) | ||
430 | ) | ||
431 | |||
432 | verboseP = flag defaultPriority INFO | ||
433 | ( long "verbose" | ||
434 | <> short 'v' | ||
435 | <> help "Verbose mode" | ||
436 | ) | ||
437 | |||
438 | quietP = flag defaultPriority CRITICAL | ||
439 | ( long "quiet" | ||
440 | <> short 'q' | ||
441 | <> help "Silent mode" | ||
442 | ) | ||
443 | |||
444 | |||
445 | globalOpts :: Parser GlobalOpts | ||
446 | globalOpts = GlobalOpts <$> verbosityOpts | ||
447 | |||
448 | data Options = Options | ||
449 | { cmdOpts :: Command | ||
450 | , globOpts :: GlobalOpts | ||
451 | } deriving Show | ||
452 | |||
453 | options :: Parser Options | ||
454 | options = Options <$> commandOpts <*> globalOpts | ||
455 | |||
456 | versioner :: String -> Version -> Parser (a -> a) | ||
457 | #if MIN_VERSION_optparse_applicative(0,10,0) | ||
458 | versioner prog ver = nullOption disabled $ mconcat | ||
459 | #else | ||
460 | versioner prog ver = nullOption $ mconcat | ||
461 | #endif | ||
462 | [ long "version" | ||
463 | , help "Show program version and exit" | ||
464 | , value id | ||
465 | , metavar "" | ||
466 | , hidden | ||
467 | , mempty -- reader $ const $ undefined -- Left $ ErrorMsg versionStr | ||
468 | ] | ||
469 | where | ||
470 | versionStr = prog ++ " version " ++ showVersion ver | ||
471 | |||
472 | parserInfo :: ParserInfo Options | ||
473 | parserInfo = info parser modifier | ||
474 | where | ||
475 | parser = helper <*> versioner "mktorrent" version <*> options | ||
476 | modifier = header synopsis <> progDesc description <> fullDesc | ||
477 | synopsis = "Torrent management utility" | ||
478 | description = "" -- TODO | ||
479 | |||
480 | {----------------------------------------------------------------------- | ||
481 | -- Dispatch | ||
482 | -----------------------------------------------------------------------} | ||
483 | |||
484 | run :: Command -> IO () | ||
485 | run (Amend opts) = amend opts | ||
486 | run (Check opts) = checkTorrent opts | ||
487 | --run (Create opts) = createTorrent opts | ||
488 | run (Get opts) = getTorrent opts | ||
489 | run (Magnet opts) = magnet opts | ||
490 | run (Show opts) = putTorrent opts | ||
491 | |||
492 | prepare :: GlobalOpts -> IO () | ||
493 | prepare GlobalOpts {..} = do | ||
494 | updateGlobalLogger rootLoggerName (setLevel verbosity) | ||
495 | |||
496 | main :: IO () | ||
497 | main = do | ||
498 | Options {..} <- execParser parserInfo | ||
499 | prepare globOpts | ||
500 | run cmdOpts | ||