]> gitweb.michael.orlitzky.com - dead/lwn-epub.git/commitdiff
Use cmdargs to parse the one command-line argument.
authorMichael Orlitzky <michael@orlitzky.com>
Sun, 24 Jun 2012 15:54:52 +0000 (11:54 -0400)
committerMichael Orlitzky <michael@orlitzky.com>
Sun, 24 Jun 2012 15:54:52 +0000 (11:54 -0400)
lwn-epub.cabal
src/CommandLine.hs [new file with mode: 0644]
src/ExitCodes.hs [new file with mode: 0644]
src/Main.hs

index 755845b5f671bb1dcb2e7261e885974530c838b8..6eb0c4e127c40ef572f063e851cf655ff8147e8f 100644 (file)
@@ -11,6 +11,7 @@ executable lwn-epub
   build-depends:
     base                    == 4.5.*,
     bytestring              == 0.9.*,
+    cmdargs                 == 0.9.*,
     directory               == 1.1.*,
     filepath                == 1.3.*,
     HandsomeSoup            == 0.3.*,
diff --git a/src/CommandLine.hs b/src/CommandLine.hs
new file mode 100644 (file)
index 0000000..d9be034
--- /dev/null
@@ -0,0 +1,81 @@
+{-# LANGUAGE DeriveDataTypeable #-}
+
+module CommandLine (Args(..), apply_args)
+where
+
+-- Get the version from Cabal.
+import Paths_lwn_epub (version)
+import Data.Version (showVersion)
+
+import Data.String.Utils (startswith)
+import System.Console.CmdArgs (
+  CmdArgs,
+  Data,
+  Mode,
+  Typeable,
+  (&=),
+  argPos,
+  cmdArgsApply,
+  cmdArgsMode,
+  details,
+  program,
+  typ,
+  summary
+  )
+
+import System.Console.CmdArgs.Explicit (process)
+import System.Environment (getArgs, withArgs)
+import System.Exit (ExitCode(..), exitWith)
+import System.IO (hPutStrLn, stderr)
+
+import ExitCodes
+
+
+
+data Args =
+  Args { article :: String }
+  deriving   (Show, Data, Typeable)
+
+
+description :: String
+description = "Convert LWN articles to EPUB format."
+
+program_name :: String
+program_name = "lwn_epub"
+
+lwn_epub_summary :: String
+lwn_epub_summary =
+  program_name ++ "-" ++ (showVersion version)
+
+arg_spec :: Mode (CmdArgs Args)
+arg_spec = cmdArgsMode $
+             Args { article = "" &= argPos 0 &= typ "ARTICLE" }
+             &= program program_name
+             &= summary lwn_epub_summary
+             &= details [description]
+
+
+-- Infix notation won't work, the arguments are backwards!
+is_missing_arg_error :: String -> Bool
+is_missing_arg_error s =
+  startswith "Requires at least" s
+
+parse_args :: IO (CmdArgs Args)
+parse_args = do
+  x <- getArgs
+  let y = process arg_spec x
+  case y of
+      Right result -> return result
+      Left err ->
+        if (is_missing_arg_error err) then
+          withArgs ["--help"] parse_args
+        else do
+          hPutStrLn stderr err
+          exitWith (ExitFailure exit_args_parse_failed)
+
+        -- Disregard the error message, show help instead.
+
+apply_args :: IO Args
+apply_args = do
+  x <- parse_args
+  cmdArgsApply x
diff --git a/src/ExitCodes.hs b/src/ExitCodes.hs
new file mode 100644 (file)
index 0000000..11c03f9
--- /dev/null
@@ -0,0 +1,9 @@
+-- |All exit codes that the program can return (excepting
+-- ExitSuccess). There's only one, since the program will try and fail
+-- forever upon errors.
+module ExitCodes
+where
+
+-- |Indicates that the command-line arguments could not be parsed.
+exit_args_parse_failed :: Int
+exit_args_parse_failed = 1
index c6ab443a9620d20f716576eb0c188702f8ad4b5d..8687488f7817281760813cd06cdbc24a06ffb44f 100644 (file)
@@ -1,10 +1,14 @@
-{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE ScopedTypeVariables, RecordWildCards #-}
 module Main
 where
 
 import Data.Maybe (fromJust)
-import Text.XML.HXT.Core -- (SysConfigList, IOStateArrow, XmlTree, readDocument)
+import System.Console.CmdArgs (cmdArgsRun)
 
+import Text.XML.HXT.Core
+
+
+import CommandLine (Args(..), apply_args)
 import Epublishable
 import LWN.ArticlePage
 import LWN.FullPage
@@ -18,19 +22,22 @@ my_read =
 
 main :: IO ()
 main = do
-  let article_html = my_read "test/fixtures/501317-article.html"
-  ioap <- parse article_html
-  let article_page :: ArticlePage = fromJust $ ioap
-  epublish article_page "single_article.epub"
-
-  let page_html = my_read "test/fixtures/500848-page.html"
-  ioap_f <- parse page_html
-  let full_page :: FullPage = fromJust $ ioap_f
-  epublish full_page "full_page.epub"
-
-  let bigpage_html = my_read "test/fixtures/50844-bigpage.html"
-  ioap_bp <- parse bigpage_html
-  let bigpage :: FullPage = fromJust $ ioap_bp
-  epublish bigpage "bigpage.epub"
-
-  putStrLn "Done."
+  Args{..} <- apply_args
+  print article
+
+  -- let article_html = my_read "test/fixtures/501317-article.html"
+  -- ioap <- parse article_html
+  -- let article_page :: ArticlePage = fromJust $ ioap
+  -- epublish article_page "single_article.epub"
+
+  -- let page_html = my_read "test/fixtures/500848-page.html"
+  -- ioap_f <- parse page_html
+  -- let full_page :: FullPage = fromJust $ ioap_f
+  -- epublish full_page "full_page.epub"
+
+  -- let bigpage_html = my_read "test/fixtures/50844-bigpage.html"
+  -- ioap_bp <- parse bigpage_html
+  -- let bigpage :: FullPage = fromJust $ ioap_bp
+  -- epublish bigpage "bigpage.epub"
+
+  -- putStrLn "Done."