diff options
Diffstat (limited to 'examples/MkTorrent.hs')
-rw-r--r-- | examples/MkTorrent.hs | 389 |
1 files changed, 389 insertions, 0 deletions
diff --git a/examples/MkTorrent.hs b/examples/MkTorrent.hs new file mode 100644 index 00000000..ca7f5942 --- /dev/null +++ b/examples/MkTorrent.hs | |||
@@ -0,0 +1,389 @@ | |||
1 | {-# LANGUAGE OverloadedStrings #-} | ||
2 | {-# LANGUAGE RecordWildCards #-} | ||
3 | {-# LANGUAGE StandaloneDeriving #-} | ||
4 | {-# OPTIONS -fno-warn-orphans #-} | ||
5 | module Main (main) where | ||
6 | |||
7 | import Prelude as P | ||
8 | import Control.Exception | ||
9 | import Control.Lens hiding (argument) | ||
10 | import Control.Monad | ||
11 | import Data.List as L | ||
12 | import Data.Monoid | ||
13 | import Data.Text as T | ||
14 | import qualified Data.Text.IO as T | ||
15 | import Data.Text.Read as T | ||
16 | import Data.Version | ||
17 | import Network.URI | ||
18 | import Options.Applicative | ||
19 | import System.Log | ||
20 | import System.Log.Logger | ||
21 | import System.Exit | ||
22 | import Text.Read | ||
23 | import Text.PrettyPrint.Class | ||
24 | |||
25 | import Paths_bittorrent (version) | ||
26 | import Data.Torrent | ||
27 | import Data.Torrent.Magnet hiding (Magnet (Magnet)) | ||
28 | import Data.Torrent.Magnet (Magnet) | ||
29 | |||
30 | --import MkTorrent.Check | ||
31 | --import MkTorrent.Create | ||
32 | |||
33 | {----------------------------------------------------------------------- | ||
34 | -- Dialogs | ||
35 | -----------------------------------------------------------------------} | ||
36 | |||
37 | instance Read URI where | ||
38 | readsPrec _ = f . parseURI | ||
39 | where | ||
40 | f Nothing = [] | ||
41 | f (Just u) = [(u, "")] | ||
42 | |||
43 | question :: Show a => Text -> Maybe a -> IO () | ||
44 | question q def = do | ||
45 | T.putStrLn q | ||
46 | case def of | ||
47 | Nothing -> return () | ||
48 | Just v -> T.putStrLn $ "[default: " <> T.pack (show v) <> "]" | ||
49 | |||
50 | ask :: Read a => Text -> IO a | ||
51 | ask q = question q (Just True) >> getReply | ||
52 | where | ||
53 | getReply = do | ||
54 | resp <- P.getLine | ||
55 | maybe getReply return $ readMaybe resp | ||
56 | |||
57 | askMaybe :: Read a => Text -> IO (Maybe a) | ||
58 | askMaybe q = question q (Just False) >> getReply | ||
59 | where | ||
60 | getReply = do | ||
61 | resp <- P.getLine | ||
62 | if resp == [] | ||
63 | then return Nothing | ||
64 | else maybe getReply return $ readMaybe resp | ||
65 | |||
66 | askURI :: IO URI | ||
67 | askURI = do | ||
68 | str <- P.getLine | ||
69 | case parseURI str of | ||
70 | Nothing -> T.putStrLn "incorrect URI" >> askURI | ||
71 | Just u -> return u | ||
72 | |||
73 | askFreeform :: IO Text | ||
74 | askFreeform = do | ||
75 | str <- T.getLine | ||
76 | if T.null str | ||
77 | then askFreeform | ||
78 | else return str | ||
79 | |||
80 | askInRange :: Int -> Int -> IO Int | ||
81 | askInRange a b = do | ||
82 | str <- T.getLine | ||
83 | case T.decimal str of | ||
84 | Left msg -> do | ||
85 | P.putStrLn msg | ||
86 | askInRange a b | ||
87 | Right (i, _) | ||
88 | | a <= i && i < b -> return i | ||
89 | | otherwise -> do | ||
90 | T.putStrLn "not in range " | ||
91 | askInRange a b | ||
92 | |||
93 | askChoice :: [(Text, a)] -> IO a | ||
94 | askChoice kvs = do | ||
95 | forM_ (L.zip [1 :: Int ..] $ L.map fst kvs) $ \(i, lbl) -> do | ||
96 | T.putStrLn $ " " <> T.pack (show i) <> ") " <> lbl | ||
97 | T.putStrLn "Your choice?" | ||
98 | ix <- askInRange 1 (succ (L.length kvs)) | ||
99 | return $ snd (kvs !! pred ix) | ||
100 | |||
101 | {----------------------------------------------------------------------- | ||
102 | -- Helpers | ||
103 | -----------------------------------------------------------------------} | ||
104 | |||
105 | torrentFile :: Parser FilePath | ||
106 | torrentFile = argument Just | ||
107 | ( metavar "FILE" | ||
108 | <> help "A .torrent file" | ||
109 | ) | ||
110 | |||
111 | {----------------------------------------------------------------------- | ||
112 | -- Amend command | ||
113 | -----------------------------------------------------------------------} | ||
114 | |||
115 | data AmendOpts = AmendOpts FilePath | ||
116 | deriving Show | ||
117 | |||
118 | amendOpts :: Parser AmendOpts | ||
119 | amendOpts = AmendOpts <$> torrentFile | ||
120 | |||
121 | amendInfo :: ParserInfo AmendOpts | ||
122 | amendInfo = info (helper <*> amendOpts) modifier | ||
123 | where | ||
124 | modifier = progDesc "Edit info fields of existing torrent" | ||
125 | |||
126 | type Amend = Torrent -> Torrent | ||
127 | |||
128 | fields :: [(Text, IO Amend)] | ||
129 | fields = [ ("announce", set announce <$> askURI) | ||
130 | , ("comment", set comment . Just <$> askFreeform) | ||
131 | , ("created by", set createdBy . Just <$> askFreeform) | ||
132 | , ("publisher url", set publisherURL . Just <$> askURI) | ||
133 | ] | ||
134 | |||
135 | askAmend :: IO Amend | ||
136 | askAmend = join $ T.putStrLn "Choose a field:" >> askChoice fields | ||
137 | |||
138 | amend :: AmendOpts -> IO Bool | ||
139 | amend (AmendOpts tpath) = do | ||
140 | t <- fromFile tpath | ||
141 | a <- askAmend | ||
142 | toFile tpath $ a t | ||
143 | return True | ||
144 | |||
145 | {----------------------------------------------------------------------- | ||
146 | -- Check command | ||
147 | -----------------------------------------------------------------------} | ||
148 | |||
149 | {- | ||
150 | checkOpts :: Parser CheckOpts | ||
151 | checkOpts = CheckOpts | ||
152 | <$> torrentFile | ||
153 | <*> argument Just | ||
154 | ( metavar "PATH" | ||
155 | <> value "." | ||
156 | <> help "Content directory or a single file" ) | ||
157 | |||
158 | checkInfo :: ParserInfo CheckOpts | ||
159 | checkInfo = info (helper <*> checkOpts) modifier | ||
160 | where | ||
161 | modifier = progDesc "Validate integrity of torrent data" | ||
162 | |||
163 | {----------------------------------------------------------------------- | ||
164 | -- Create command | ||
165 | -----------------------------------------------------------------------} | ||
166 | |||
167 | createFlags :: Parser CreateFlags | ||
168 | createFlags = CreateFlags | ||
169 | <$> optional (option | ||
170 | ( long "piece-size" | ||
171 | <> short 's' | ||
172 | <> metavar "SIZE" | ||
173 | <> help "Set size of torrent pieces" | ||
174 | )) | ||
175 | <*> switch | ||
176 | ( long "md5" | ||
177 | <> short '5' | ||
178 | <> help "Include md5 hash of each file" | ||
179 | ) | ||
180 | <*> switch | ||
181 | ( long "ignore-dot-files" | ||
182 | <> short 'd' | ||
183 | <> help "Do not include .* files" | ||
184 | ) | ||
185 | |||
186 | |||
187 | createOpts :: Parser CreateOpts | ||
188 | createOpts = CreateOpts | ||
189 | <$> argument Just | ||
190 | ( metavar "PATH" | ||
191 | <> help "Content directory or a single file" | ||
192 | ) | ||
193 | <*> optional (argument Just | ||
194 | ( metavar "FILE" | ||
195 | <> help "Place for the output .torrent file" | ||
196 | )) | ||
197 | <*> createFlags | ||
198 | |||
199 | createInfo :: ParserInfo CreateOpts | ||
200 | createInfo = info (helper <*> createOpts) modifier | ||
201 | where | ||
202 | modifier = progDesc "Make a new .torrent file" | ||
203 | -} | ||
204 | |||
205 | {----------------------------------------------------------------------- | ||
206 | -- Magnet command | ||
207 | -----------------------------------------------------------------------} | ||
208 | |||
209 | data MagnetFlags = MagnetFlags | ||
210 | { detailed :: Bool | ||
211 | } deriving Show | ||
212 | |||
213 | data MagnetOpts = MagnetOpts FilePath MagnetFlags | ||
214 | deriving Show | ||
215 | |||
216 | magnetFlags :: Parser MagnetFlags | ||
217 | magnetFlags = MagnetFlags | ||
218 | <$> switch | ||
219 | ( long "detailed" | ||
220 | ) | ||
221 | |||
222 | magnetOpts :: Parser MagnetOpts | ||
223 | magnetOpts = MagnetOpts <$> torrentFile <*> magnetFlags | ||
224 | |||
225 | magnetInfo :: ParserInfo MagnetOpts | ||
226 | magnetInfo = info (helper <*> magnetOpts) modifier | ||
227 | where | ||
228 | modifier = progDesc "Print magnet link" | ||
229 | |||
230 | mkMagnet :: MagnetFlags -> Torrent -> Magnet | ||
231 | mkMagnet MagnetFlags {..} = if detailed then detailedMagnet else simpleMagnet | ||
232 | |||
233 | magnet :: MagnetOpts -> IO Bool | ||
234 | magnet (MagnetOpts tpath flags) = do | ||
235 | print . mkMagnet flags =<< fromFile tpath | ||
236 | return True | ||
237 | |||
238 | {----------------------------------------------------------------------- | ||
239 | -- Show command | ||
240 | -----------------------------------------------------------------------} | ||
241 | |||
242 | data ShowFlags = ShowFlags | ||
243 | { infoHashOnly :: Bool | ||
244 | } deriving Show | ||
245 | |||
246 | data ShowOpts = ShowOpts FilePath ShowFlags | ||
247 | deriving Show | ||
248 | |||
249 | showFlags :: Parser ShowFlags | ||
250 | showFlags = ShowFlags | ||
251 | <$> switch | ||
252 | ( long "infohash" | ||
253 | <> help "Show only hash of the torrent info part" | ||
254 | ) | ||
255 | |||
256 | showOpts :: Parser ShowOpts | ||
257 | showOpts = ShowOpts <$> torrentFile <*> showFlags | ||
258 | |||
259 | showInfo :: ParserInfo ShowOpts | ||
260 | showInfo = info (helper <*> showOpts) modifier | ||
261 | where | ||
262 | modifier = progDesc "Print .torrent file metadata" | ||
263 | |||
264 | showTorrent :: ShowFlags -> Torrent -> ShowS | ||
265 | showTorrent ShowFlags {..} torrent | ||
266 | | infoHashOnly = shows $ idInfoHash (tInfoDict torrent) | ||
267 | | otherwise = shows $ pretty torrent | ||
268 | |||
269 | putTorrent :: ShowOpts -> IO Bool | ||
270 | putTorrent (ShowOpts torrentPath flags) = do | ||
271 | torrent <- fromFile torrentPath `onException` putStrLn help | ||
272 | putStrLn $ showTorrent flags torrent [] | ||
273 | return True | ||
274 | where | ||
275 | help = "Most likely this is not a valid .torrent file" | ||
276 | |||
277 | {----------------------------------------------------------------------- | ||
278 | -- Command | ||
279 | -----------------------------------------------------------------------} | ||
280 | |||
281 | data Command | ||
282 | = Amend AmendOpts | ||
283 | -- | Check CheckOpts | ||
284 | -- | Create CreateOpts | ||
285 | | Magnet MagnetOpts | ||
286 | | Show ShowOpts | ||
287 | deriving Show | ||
288 | |||
289 | commandOpts :: Parser Command | ||
290 | commandOpts = subparser $ mconcat | ||
291 | [ command "amend" (Amend <$> amendInfo) | ||
292 | -- , command "check" (Check <$> checkInfo) | ||
293 | -- , command "create" (Create <$> createInfo) | ||
294 | , command "magnet" (Magnet <$> magnetInfo) | ||
295 | , command "show" (Show <$> showInfo) | ||
296 | ] | ||
297 | |||
298 | {----------------------------------------------------------------------- | ||
299 | -- Global Options | ||
300 | -----------------------------------------------------------------------} | ||
301 | |||
302 | data GlobalOpts = GlobalOpts | ||
303 | { verbosity :: Priority | ||
304 | } deriving Show | ||
305 | |||
306 | deriving instance Enum Priority | ||
307 | deriving instance Bounded Priority | ||
308 | |||
309 | priorities :: [Priority] | ||
310 | priorities = [minBound..maxBound] | ||
311 | |||
312 | defaultPriority :: Priority | ||
313 | defaultPriority = WARNING | ||
314 | |||
315 | verbosityOpts :: Parser Priority | ||
316 | verbosityOpts = verbosityP <|> verboseP <|> quietP | ||
317 | where | ||
318 | verbosityP = option | ||
319 | ( long "verbosity" | ||
320 | <> metavar "LEVEL" | ||
321 | <> help ("Set verbosity level\n" | ||
322 | ++ "Possible values are " ++ show priorities) | ||
323 | ) | ||
324 | |||
325 | verboseP = flag defaultPriority INFO | ||
326 | ( long "verbose" | ||
327 | <> short 'v' | ||
328 | <> help "Verbose mode" | ||
329 | ) | ||
330 | |||
331 | quietP = flag defaultPriority CRITICAL | ||
332 | ( long "quiet" | ||
333 | <> short 'q' | ||
334 | <> help "Silent mode" | ||
335 | ) | ||
336 | |||
337 | |||
338 | globalOpts :: Parser GlobalOpts | ||
339 | globalOpts = GlobalOpts <$> verbosityOpts | ||
340 | |||
341 | data Options = Options | ||
342 | { cmdOpts :: Command | ||
343 | , globOpts :: GlobalOpts | ||
344 | } deriving Show | ||
345 | |||
346 | options :: Parser Options | ||
347 | options = Options <$> commandOpts <*> globalOpts | ||
348 | |||
349 | versioner :: String -> Version -> Parser (a -> a) | ||
350 | versioner prog ver = nullOption $ mconcat | ||
351 | [ long "version" | ||
352 | , help "Show program version and exit" | ||
353 | , value id | ||
354 | , metavar "" | ||
355 | , hidden | ||
356 | , reader $ const $ undefined -- Left $ ErrorMsg versionStr | ||
357 | ] | ||
358 | where | ||
359 | versionStr = prog ++ " version " ++ showVersion ver | ||
360 | |||
361 | parserInfo :: ParserInfo Options | ||
362 | parserInfo = info parser modifier | ||
363 | where | ||
364 | parser = helper <*> versioner "mktorrent" version <*> options | ||
365 | modifier = header synopsis <> progDesc description <> fullDesc | ||
366 | synopsis = "Torrent management utility" | ||
367 | description = "" -- TODO | ||
368 | |||
369 | {----------------------------------------------------------------------- | ||
370 | -- Dispatch | ||
371 | -----------------------------------------------------------------------} | ||
372 | |||
373 | run :: Command -> IO Bool | ||
374 | run (Amend opts) = amend opts | ||
375 | --run (Check opts) = checkTorrent opts | ||
376 | --run (Create opts) = createTorrent opts | ||
377 | run (Magnet opts) = magnet opts | ||
378 | run (Show opts) = putTorrent opts | ||
379 | |||
380 | prepare :: GlobalOpts -> IO () | ||
381 | prepare GlobalOpts {..} = do | ||
382 | updateGlobalLogger rootLoggerName (setLevel verbosity) | ||
383 | |||
384 | main :: IO () | ||
385 | main = do | ||
386 | Options {..} <- execParser parserInfo | ||
387 | prepare globOpts | ||
388 | success <- run cmdOpts | ||
389 | if success then exitSuccess else exitFailure \ No newline at end of file | ||