Added new Haskell version of markdown2pdf.
Thanks to Paulo Tanimoto for the patch. git-svn-id: https://pandoc.googlecode.com/svn/trunk@1573 788f1e2b-df1e-0410-8736-df70ead52e1b
This commit is contained in:
parent
2d5f718048
commit
cceede4ca2
2 changed files with 27 additions and 15 deletions
11
pandoc.cabal
11
pandoc.cabal
|
@ -232,3 +232,14 @@ Executable hsmarkdown
|
||||||
else
|
else
|
||||||
Buildable: False
|
Buildable: False
|
||||||
|
|
||||||
|
Executable markdown2pdf
|
||||||
|
Hs-Source-Dirs: src
|
||||||
|
Main-Is: markdown2pdf.hs
|
||||||
|
Ghc-Options: -Wall -threaded
|
||||||
|
Ghc-Prof-Options: -auto-all
|
||||||
|
Extensions: CPP, TemplateHaskell
|
||||||
|
if flag(wrappers)
|
||||||
|
Buildable: True
|
||||||
|
else
|
||||||
|
Buildable: False
|
||||||
|
|
||||||
|
|
|
@ -1,6 +1,6 @@
|
||||||
module Main where
|
module Main where
|
||||||
|
|
||||||
import Data.List (isInfixOf, intercalate, intersect)
|
import Data.List (isInfixOf, intercalate, (\\))
|
||||||
import Data.Maybe (isNothing)
|
import Data.Maybe (isNothing)
|
||||||
|
|
||||||
import Control.Monad (when, unless, guard)
|
import Control.Monad (when, unless, guard)
|
||||||
|
@ -153,23 +153,24 @@ main = bracket
|
||||||
paths <- mapM findExecutable execs
|
paths <- mapM findExecutable execs
|
||||||
let miss = map snd $ filter (isNothing . fst) $ zip paths execs
|
let miss = map snd $ filter (isNothing . fst) $ zip paths execs
|
||||||
unless (null miss) $ exit $! "Could not find " ++ intercalate ", " miss
|
unless (null miss) $ exit $! "Could not find " ++ intercalate ", " miss
|
||||||
-- parse arguments
|
|
||||||
args <- getArgs
|
args <- getArgs
|
||||||
let badopts = ["-t","-w","--to","--write","-s","--standalone",
|
-- check for invalid arguments and print help message if needed
|
||||||
"--reference-links","-m","--latexmathml",
|
let goodopts = ["-f","-r","--from","--read","--strict","-N",
|
||||||
"--asciimathml","--mimetex","--jsmath","--gladtex",
|
"-p","--preserve-tabs","--tab-stop","-R","--parse-raw",
|
||||||
"-i","--incremental","--no-wrap", "--sanitize-html",
|
"--toc","--table-of-contents",
|
||||||
"--email-obfuscation","-c","--css","-T","--title-prefix",
|
"--number-sections","-H","--include-in-header",
|
||||||
"-D","--print-default-header","--dump-args",
|
"-B","--include-before-body","-A","--include-after-body",
|
||||||
"--ignore-args","-h","--help","-v","--version"]
|
"-C","--custom-header","-o","--output"]
|
||||||
let badoptsLong = filter (\o -> length o > 2) badopts
|
let goodoptsLong = filter (\op -> length op > 2) goodopts
|
||||||
unless (null (args `intersect` badopts)) $ do
|
let isOpt ('-':_) = True
|
||||||
|
isOpt _ = False
|
||||||
|
unless (null (filter isOpt args \\ goodopts)) $ do
|
||||||
(code, out, _err) <- readProcessWithExitCode "pandoc" ["--help"] ""
|
(code, out, _err) <- readProcessWithExitCode "pandoc" ["--help"] ""
|
||||||
putStrLn "markdown2pdf [OPTIONS] [FILES]"
|
putStrLn "markdown2pdf [OPTIONS] [FILES]\nOptions:"
|
||||||
putStrLn $ unlines $ drop 3 $
|
putStr $ unlines $
|
||||||
filter (\l -> not . any (`isInfixOf` l) $ badoptsLong) $
|
filter (\l -> any (`isInfixOf` l) goodoptsLong) $ lines out
|
||||||
lines out
|
|
||||||
exitWith code
|
exitWith code
|
||||||
|
-- parse arguments
|
||||||
pandocArgs <- parsePandocArgs args
|
pandocArgs <- parsePandocArgs args
|
||||||
(inputs, output) <- case pandocArgs of
|
(inputs, output) <- case pandocArgs of
|
||||||
Nothing -> exit "Could not parse arguments"
|
Nothing -> exit "Could not parse arguments"
|
||||||
|
|
Loading…
Add table
Reference in a new issue