aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJohn MacFarlane <fiddlosopher@gmail.com>2012-01-20 21:22:51 -0800
committerJohn MacFarlane <fiddlosopher@gmail.com>2012-01-20 21:22:51 -0800
commit1d615908c2c346c034aa63f572f5f112638d8ff4 (patch)
tree1ce3dc4984020a3a7dac69ed032450a4dc7c9f7e
parentb4a6c023431fcb313f04afa4c0d222c977c6d27c (diff)
downloadpandoc-1d615908c2c346c034aa63f572f5f112638d8ff4.tar.gz
Removed markdown2pdf and documentation.
-rw-r--r--MakeManPage.hs10
-rw-r--r--README62
-rw-r--r--Setup.hs23
-rw-r--r--man/man1/markdown2pdf.1.md120
-rw-r--r--pandoc.cabal29
-rw-r--r--src/markdown2pdf.hs269
-rw-r--r--windows/make-windows-installer.bat1
7 files changed, 27 insertions, 487 deletions
diff --git a/MakeManPage.hs b/MakeManPage.hs
index 06a31934c..ca9307c3e 100644
--- a/MakeManPage.hs
+++ b/MakeManPage.hs
@@ -24,16 +24,6 @@ main = do
meta manBlocks
makeManPage verbose ("man" </> "man5" </> "pandoc_markdown.5")
meta syntaxBlocks
- let markdown2pdfpage = "man" </> "man1" </> "markdown2pdf.1"
- modDeps <- modifiedDependencies markdown2pdfpage [markdown2pdfpage <.> "md"]
- unless (null modDeps) $ do
- mpdfContents <- liftM toString $ B.readFile $ markdown2pdfpage <.> "md"
- templ <- liftM toString $ B.readFile $ "templates" </> "default.man"
- let doc = readMarkdown defaultParserState{ stateStandalone = True }
- mpdfContents
- writeManPage markdown2pdfpage templ doc
- when verbose $
- putStrLn $ "Created " ++ markdown2pdfpage
makeManPage :: Bool -> FilePath -> Meta -> [Block] -> IO ()
makeManPage verbose page meta blocks = do
diff --git a/README b/README
index 0bf77ca54..89a5d3412 100644
--- a/README
+++ b/README
@@ -17,7 +17,8 @@ and [LaTeX]; and it can write plain text, [markdown], [reStructuredText],
[XHTML], [HTML 5], [LaTeX], [LaTeX beamer], [ConTeXt], [RTF], [DocBook XML],
[OpenDocument XML], [ODT], [Word docx], [GNU Texinfo], [MediaWiki markup], [EPUB],
[Textile], [groff man] pages, [Emacs Org-Mode], [AsciiDoc], and [Slidy],
-[DZSlides], or [S5] HTML slide shows.
+[DZSlides], or [S5] HTML slide shows. It can also produce [PDF] output
+on systems where LaTeX is installed.
Pandoc's enhanced version of markdown includes syntax for footnotes,
tables, flexible ordered lists, definition lists, delimited code blocks,
@@ -34,14 +35,15 @@ representation of the document, and a set of writers, which convert
this native representation into a target format. Thus, adding an input
or output format requires only adding a reader or writer.
-Using Pandoc
-------------
+Using `pandoc`
+--------------
If no *input-file* is specified, input is read from *stdin*.
Otherwise, the *input-files* are concatenated (with a blank
line between each) and used as input. Output goes to *stdout* by
default (though output to *stdout* is disabled for the `odt`, `docx`,
-and `epub` output formats). For output to a file, use the `-o` option:
+`pdf`, and `epub` output formats). For output to a file, use the
+`-o` option:
pandoc -o output.html input.txt
@@ -89,36 +91,15 @@ should pipe input and output through `iconv`:
iconv -t utf-8 input.txt | pandoc | iconv -f utf-8
-Wrappers
-========
-
`markdown2pdf`
--------------
-The standard Pandoc installation includes `markdown2pdf`, a wrapper
-around `pandoc` and `pdflatex` that produces PDFs directly from markdown
-sources. The default behavior of `markdown2pdf` is to create a file with
-the same base name as the first argument and the extension `pdf`; thus,
-for example,
-
- markdown2pdf sample.txt endnotes.txt
-
-will produce `sample.pdf`. An output file
-name can be specified explicitly using the `-o` option:
-
- markdown2pdf -o book.pdf chap1 chap2
-
-If no input file is specified, input will be taken from *stdin*.
-All of `pandoc`'s options will work with `markdown2pdf` as well.
-
-`markdown2pdf` assumes that `pdflatex` is in the path. It also
-assumes that the following LaTeX packages are available:
-`unicode`, `fancyhdr` (if you have verbatim text in footnotes),
-`graphicx` (if you use images), `array` (if you use tables),
-and `ulem` (if you use strikeout text). If they are not already
-included in your LaTeX distribution, you can get them from
-[CTAN]. A full [TeX Live] or [MacTeX] distribution will have all of
-these packages.
+Earlier versions of pandoc came with a program, `markdown2pdf`,
+that used pandoc and pdflatex to produce a PDF. This is no
+longer needed, since `pandoc` now has a `pdf` output format.
+Note that whereas `markdown2pdf` would create an ouput file
+based on the input file name, `pandoc` requires that you specify
+the output filename explicitly.
`hsmarkdown`
------------
@@ -158,12 +139,12 @@ Options
(DocBook XML), `opendocument` (OpenDocument XML), `odt` (OpenOffice text
document), `docx` (Word docx), `epub` (EPUB book), `asciidoc` (AsciiDoc),
`slidy` (Slidy HTML and javascript slide show), `dzslides` (HTML5 +
- javascript slide show), `s5` (S5 HTML and javascript slide show), or
- `rtf` (rich text format). Note that `odt` and `epub` output will not be
- directed to *stdout*; an output filename must be specified using the
- `-o/--output` option. If `+lhs` is appended to `markdown`, `rst`, `latex`,
- `html`, or `html5`, the output will be rendered as literate Haskell source:
- see [Literate Haskell support](#literate-haskell-support), below.
+ javascript slide show), `s5` (S5 HTML and javascript slide show),
+ `rtf` (rich text format), or `pdf` (PDF). Note that `odt` and `epub` output
+ will not be directed to *stdout*; an output filename must be specified
+ using the `-o/--output` option. If `+lhs` is appended to `markdown`, `rst`,
+ `latex`, `html`, or `html5`, the output will be rendered as literate Haskell
+ source: see [Literate Haskell support](#literate-haskell-support), below.
`-s`, `--standalone`
: Produce output with an appropriate header and footer (e.g. a
@@ -172,7 +153,7 @@ Options
`-o` *FILE*, `--output=`*FILE*
: Write output to *FILE* instead of *stdout*. If *FILE* is
`-`, output will go to *stdout*. (Exception: if the output
- format is `odt`, `docx`, or `epub`, output to stdout is disabled.)
+ format is `odt`, `docx`, `pdf`, or `epub`, output to stdout is disabled.)
`-p`, `--preserve-tabs`
: Preserve tabs instead of converting them to spaces (the default).
@@ -1937,8 +1918,8 @@ Producing slide shows with Pandoc
You can use Pandoc to produce an HTML + javascript slide presentation
that can be viewed via a web browser. There are three ways to do this,
using [S5], [DZSlides], or [Slidy]. You can also produce a PDF slide
-show using [LaTeX beamer]: just pass the `--beamer` option to
-`markdown2pdf`.
+show using [LaTeX beamer]: just use the `--beamer` option with `pdf`
+output.
Here's the markdown source for a simple slide show, `eating.txt`:
@@ -2094,3 +2075,4 @@ Christopher Sawicki, Kelsey Hightower.
[DZSlides]: http://paulrouget.com/dzslides/
[ISO 8601 format]: http://www.w3.org/TR/NOTE-datetime
[Word docx]: http://www.microsoft.com/interop/openup/openxml/default.aspx
+[PDF]: http://www.adobe.com/pdf/ \ No newline at end of file
diff --git a/Setup.hs b/Setup.hs
index 8b3c173a8..2ee9e29a9 100644
--- a/Setup.hs
+++ b/Setup.hs
@@ -25,14 +25,11 @@ main = do
defaultMainWithHooks $ simpleUserHooks {
runTests = runTestSuite
, postBuild = makeManPages
- , postCopy = \ _ flags pkg lbi -> do
+ , postCopy = \ _ flags pkg lbi ->
installManpages pkg lbi (fromFlag $ copyVerbosity flags)
(fromFlag $ copyDest flags)
- installScripts pkg lbi (fromFlag $ copyVerbosity flags)
- (fromFlag $ copyDest flags)
- , postInst = \ _ flags pkg lbi -> do
+ , postInst = \ _ flags pkg lbi ->
installManpages pkg lbi (fromFlag $ installVerbosity flags) NoCopyDest
- installScripts pkg lbi (fromFlag $ installVerbosity flags) NoCopyDest
}
exitWith ExitSuccess
@@ -53,9 +50,7 @@ makeManPages :: Args -> BuildFlags -> PackageDescription -> LocalBuildInfo -> IO
makeManPages _ flags _ lbi = do
ds1 <- modifiedDependencies (manDir </> "man1" </> "pandoc.1")
["README", manDir </> "man1" </> "pandoc.1.template"]
- ds2 <- modifiedDependencies (manDir </> "man1" </> "markdown2pdf.1")
- [manDir </> "man1" </> "markdown2pdf.1.md"]
- ds3 <- modifiedDependencies (manDir </> "man5" </> "pandoc_markdown.5")
+ ds2 <- modifiedDependencies (manDir </> "man5" </> "pandoc_markdown.5")
["README", manDir </> "man5" </> "pandoc_markdown.5.template"]
let distPref = fromFlag (buildDistPref flags)
@@ -71,7 +66,7 @@ makeManPages _ flags _ lbi = do
then args
else args ++ ["--verbose"]
-- Don't run MakeManPage.hs unless we have to
- unless (null ds1 && null ds2 && null ds3) $ do
+ unless (null ds1 && null ds2) $ do
rawSystem "runghc" args' >>= exitWith
-- format arguments to runghc that we wish to pass to ghc
@@ -83,21 +78,11 @@ makeGhcArgs = map ("--ghc-arg="++)
manpages :: [FilePath]
manpages = ["man1" </> "pandoc.1"
- ,"man1" </> "markdown2pdf.1"
,"man5" </> "pandoc_markdown.5"]
manDir :: FilePath
manDir = "man"
-installScripts :: PackageDescription -> LocalBuildInfo
- -> Verbosity -> CopyDest -> IO ()
-installScripts pkg lbi verbosity copy =
- copyFiles verbosity (bindir (absoluteInstallDirs pkg lbi copy))
- (zip (repeat ".") (wrappers \\ exes))
- where exes = map exeName $ filter isBuildable $ executables pkg
- isBuildable = buildable . buildInfo
- wrappers = ["markdown2pdf"]
-
installManpages :: PackageDescription -> LocalBuildInfo
-> Verbosity -> CopyDest -> IO ()
installManpages pkg lbi verbosity copy =
diff --git a/man/man1/markdown2pdf.1.md b/man/man1/markdown2pdf.1.md
deleted file mode 100644
index 8b8da6880..000000000
--- a/man/man1/markdown2pdf.1.md
+++ /dev/null
@@ -1,120 +0,0 @@
-% MARKDOWN2PDF(1) Pandoc User Manuals
-% John MacFarlane, Paulo Tanimoto, and Recai Oktas
-% January 29, 2011
-
-# NAME
-
-markdown2pdf - converts markdown-formatted text to PDF, using pdflatex
-
-# SYNOPSIS
-
-markdown2pdf [*options*] [*input-file*]...
-
-# DESCRIPTION
-
-`markdown2pdf` converts *input-file* (or text from standard
-input) from markdown-formatted plain text to PDF, using `pandoc`
-and `pdflatex`. If no output filename is specified (using the `-o`
-option), the name of the output file is derived from the input file;
-thus, for example, if the input file is *hello.txt*, the output file
-will be *hello.pdf*. If the input is read from STDIN and no output
-filename is specified, the output file will be named *stdin.pdf*. If
-multiple input files are specified, they will be concatenated before
-conversion, and the name of the output file will be derived from the
-first input file.
-
-Input is assumed to be in the UTF-8 character encoding. If your
-local character encoding is not UTF-8, you should pipe input
-through `iconv`:
-
- iconv -t utf-8 input.txt | markdown2pdf
-
-`markdown2pdf` assumes that the `unicode`, `array`, `fancyvrb`,
-`graphicx`, and `ulem` packages are in latex's search path. If these
-packages are not included in your latex setup, they can be obtained from
-<http://ctan.org>.
-
-# OPTIONS
-
--o *FILE*, \--output=*FILE*
-: Write output to *FILE*.
-
-\--strict
-: Use strict markdown syntax, with no extensions or variants.
-
--N, \--number-sections
-: Number section headings in LaTeX output. (Default is not to number them.)
-
-\--listings
-: Use listings package for LaTeX code blocks
-
-\--template=*FILE*
-: Use *FILE* as a custom template for the generated document. Implies
- `-s`. See the section TEMPLATES in `pandoc`(1) for information about
- template syntax. Use `pandoc -D latex` to print the default LaTeX
- template.
-
--V KEY=VAL, \--variable=*KEY:VAL*
-: Set the template variable KEY to the value VAL when rendering the
- document in standalone mode. Use this to set the font size when
- using the default LaTeX template: `-V fontsize=12pt`.
-
--H *FILE*, \--include-in-header=*FILE*
-: Include (LaTeX) contents of *FILE* at the end of the header. Implies
- `-s`.
-
--B *FILE*, \--include-before-body=*FILE*
-: Include (LaTeX) contents of *FILE* at the beginning of the document body.
-
--A *FILE*, \--include-after-body=*FILE*
-: Include (LaTeX) contents of *FILE* at the end of the document body.
-
-\--bibliography=*FILE*
-: Specify bibliography database to be used in resolving
- citations. The database type will be determined from the
- extension of *FILE*, which may be `.xml` (MODS format),
- `.bib` (BibTeX format), or `.json` (citeproc JSON).
-
-\--csl=*FILE*
-: Specify [CSL] style to be used in formatting citations and
- the bibliography. If *FILE* is not found, pandoc will look
- for it in
-
- $HOME/.csl
-
- in unix and
-
- C:\Documents And Settings\USERNAME\Application Data\csl
-
- in Windows. If the `--csl` option is not specified, pandoc
- will use a default style: either `default.csl` in the
- user data directory (see `--data-dir`), or, if that is
- not present, the Chicago author-date style.
-
-\--data-dir*=DIRECTORY*
-: Specify the user data directory to search for pandoc data files.
- If this option is not specified, the default user data directory
- will be used:
-
- $HOME/.pandoc
-
- in unix and
-
- C:\Documents And Settings\USERNAME\Application Data\pandoc
-
- in Windows. A `reference.odt`, `epub.css`, `templates` directory,
- or `s5` directory placed in this directory will override pandoc's
- normal defaults.
-
-\--xetex
-: Use xelatex instead of pdflatex to create the PDF.
-
-\--luatex
-: Use lualatex instead of pdflatex to create the PDF.
-
-# SEE ALSO
-
-`pandoc`(1), `pdflatex`(1)
-
-[CSL]: CitationStyles.org
-
diff --git a/pandoc.cabal b/pandoc.cabal
index 8dd133192..d9d18fe28 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -84,14 +84,11 @@ Data-Files:
-- documentation
README, INSTALL, COPYRIGHT, BUGS, changelog
Extra-Source-Files:
- -- sources for man pages
- man/man1/markdown2pdf.1.md,
-- code to create pandoc.1 man page
MakeManPage.hs,
man/man1/pandoc.1.template,
man/man5/pandoc_markdown.5.template,
-- generated man pages (produced post-build)
- man/man1/markdown2pdf.1,
man/man1/pandoc.1,
man/man5/pandoc_markdown.5,
-- benchmarks
@@ -174,31 +171,21 @@ Extra-Source-Files:
tests/lhs-test.nohl.html+lhs,
tests/lhs-test.fragment.html+lhs
Extra-Tmp-Files: man/man1/pandoc.1,
- man/man1/markdown2pdf.1,
man/man5/pandoc_markdown.5
Source-repository head
type: git
location: git://github.com/jgm/pandoc.git
-Flag threaded
- Description: Compile markdown2pdf with -threaded option.
- Default: True
Flag executable
Description: Build the pandoc executable.
Default: True
Flag library
Description: Build the pandoc library.
Default: True
-Flag wrappers
- Description: Build the wrappers (markdown2pdf).
- Default: True
Flag tests
Description: Build test-pandoc.
Default: False
-Flag benchmarks
- Description: Build benchmark-pandoc.
- Default: False
Library
-- Note: the following material must be in both Library and Executable stanzas.
@@ -334,21 +321,7 @@ Executable pandoc
-- END DUPLICATED SECTION
Main-Is: pandoc.hs
- if flag(executable) || flag(wrappers)
- Buildable: True
- else
- Buildable: False
-
-Executable markdown2pdf
- Hs-Source-Dirs: src
- Main-Is: markdown2pdf.hs
- if flag(threaded)
- Ghc-Options: -Wall -threaded
- else
- Ghc-Options: -Wall
- Ghc-Prof-Options: -auto-all -rtsopts
- Extensions: CPP
- if flag(wrappers)
+ if flag(executable)
Buildable: True
else
Buildable: False
diff --git a/src/markdown2pdf.hs b/src/markdown2pdf.hs
deleted file mode 100644
index 255ba0717..000000000
--- a/src/markdown2pdf.hs
+++ /dev/null
@@ -1,269 +0,0 @@
-module Main where
-
-import Data.List (isInfixOf, intercalate, isPrefixOf)
-import Data.Maybe (isNothing)
-import qualified Data.ByteString as BS
-import Codec.Binary.UTF8.String (decodeString, encodeString)
-import Data.ByteString.UTF8 (toString)
-import Control.Monad (unless, guard, liftM, when)
-import Control.Concurrent (putMVar, takeMVar, newEmptyMVar, forkIO)
-import Control.Exception (tryJust, bracket, evaluate)
-import Control.Monad.Trans (liftIO)
-import System.IO.Error (isAlreadyExistsError)
-
-import System.IO
-import System.IO.Error (isDoesNotExistError)
-import System.Environment ( getArgs, getProgName )
-import qualified Text.Pandoc.UTF8 as UTF8
-import System.Exit (ExitCode (..), exitWith)
-import System.FilePath
-import System.Directory
-import System.Process
-
--- A variant of 'readProcessWithExitCode' that does not
--- cause an error if the output is not UTF-8. (Copied
--- with slight variants from 'System.Process'.)
-readProcessWithExitCode'
- :: FilePath -- ^ command to run
- -> [String] -- ^ any arguments
- -> String -- ^ standard input
- -> IO (ExitCode,String,String) -- ^ exitcode, stdout, stderr
-readProcessWithExitCode' cmd args input = do
- (Just inh, Just outh, Just errh, pid) <-
- createProcess (proc cmd args){ std_in = CreatePipe,
- std_out = CreatePipe,
- std_err = CreatePipe }
-
- outMVar <- newEmptyMVar
-
- -- fork off a thread to start consuming stdout
- out <- liftM toString $ BS.hGetContents outh
- _ <- forkIO $ evaluate (length out) >> putMVar outMVar ()
-
- -- fork off a thread to start consuming stderr
- err <- liftM toString $ BS.hGetContents errh
- _ <- forkIO $ evaluate (length err) >> putMVar outMVar ()
-
- -- now write and flush any input
- when (not (null input)) $ do hPutStr inh input; hFlush inh
- hClose inh -- done with stdin
-
- -- wait on the output
- takeMVar outMVar
- takeMVar outMVar
- hClose outh
-
- -- wait on the process
- ex <- waitForProcess pid
-
- return (ex, out, err)
-
-run :: FilePath -> [String] -> IO (Either String String)
-run file opts = do
- (code, out, err) <- readProcessWithExitCode' (encodeString file)
- (map encodeString opts) ""
- let msg = out ++ err
- case code of
- ExitFailure _ -> return $ Left $! msg
- ExitSuccess -> return $ Right $! msg
-
-parsePandocArgs :: [String] -> IO (Maybe ([String], String))
-parsePandocArgs args = do
- result <- run "pandoc" $ ["--dump-args"] ++ args
- return $ either error (parse . map trim . lines) result
- where parse [] = Nothing
- parse ("-":[]) = Just ([], "stdin") -- no output or input
- parse ("-":x:xs) = Just (x:xs, dropExtension x) -- no output
- parse ( x :xs) = Just (xs, dropExtension x) -- at least output
- --trim = reverse . dropWhile isSpace . reverse . dropWhile isSpace
- trim = takeWhile (/='\r') . dropWhile (=='\r')
-
-runPandoc :: String -> [String] -> FilePath -> IO (Either String FilePath)
-runPandoc outputFormat inputsAndArgs output = do
- let texFile = addExtension output "tex"
- result <- run "pandoc" $
- ["-s", "--no-wrap", "-r", "markdown", "-w", outputFormat]
- ++ inputsAndArgs ++ ["-o", texFile]
- return $ either Left (const $ Right texFile) result
-
-runLatexRaw :: String -> FilePath -> IO (Either (Either String String) FilePath)
-runLatexRaw latexProgram file = do
- -- we ignore the ExitCode because pdflatex always fails the first time
- run latexProgram ["-halt-on-error", "-interaction", "nonstopmode",
- "-output-directory", takeDirectory file, dropExtension file] >> return ()
- let pdfFile = replaceExtension file "pdf"
- let logFile = replaceExtension file "log"
- txt <- tryJust (guard . isDoesNotExistError)
- (liftM toString $ BS.readFile logFile)
- let checks = checkLatex $ either (const "") id txt
- case checks of
- -- err , bib , ref , msg
- (True , _ , _ , msg) -> return $ Left $ Left msg -- failure
- (False, True , _ , msg) -> runBibtex file >>
- (return $ Left $ Right msg) -- citations
- (False, _ , True, msg) -> return $ Left $ Right msg -- references
- (False, False, False, _ ) -> return $ Right pdfFile -- success
-
-runLatex :: String -> FilePath -> IO (Either String FilePath)
-runLatex latexProgram file = step 3
- where
- step n = do
- result <- runLatexRaw latexProgram file
- case result of
- Left (Left err) -> return $ Left err
- Left (Right _) | n > 1 -> step (n-1 :: Int)
- Right _ | n > 2 -> step (n-1 :: Int)
- Left (Right msg) -> return $ Left msg
- Right pdfFile -> return $ Right pdfFile
-
-checkLatex :: String -> (Bool, Bool, Bool, String)
-checkLatex "" = (True, False, False, "Could not read log file")
-checkLatex txt = (err , bib, ref, unlines $! msgs ++ tips)
- where
- xs `oneOf` x = any (flip isInfixOf x) xs
- msgs = dropWhile (not . errorline) $ lines txt
- errorline ('!':_) = True
- errorline _ = False
- tips = checkPackages msgs
- err = any (oneOf ["!", "LaTeX Error:", "Latex Error:"]) msgs
- bib = any (oneOf ["Warning: Citation"
- ,"Warning: There were undefined citations"]) msgs
- ref = any (oneOf ["Warning: Reference"
- ,"Warning: Label"
- ,"Warning: There were undefined references"
- ]) msgs
-
-checkPackages :: [String] -> [String]
-checkPackages = concatMap chks
- where -- for each message, search 'pks' for matches and give a hint
- chks x = concatMap (chk x) pks
- chk x (k,v) = if sub k `isInfixOf` x then tip k v else []
- sub k = "`" ++ k ++ ".sty' not found"
- tip k v = ["Please install the '" ++ k ++
- "' package from CTAN:", " " ++ v]
- pks = [("ucs"
- ,"http://www.ctan.org/tex-archive/macros/latex/contrib/unicode/")
- ,("ulem"
- ,"http://www.ctan.org/tex-archive/macros/latex/contrib/misc/")
- ,("graphicx"
- ,"http://www.ctan.org/tex-archive/macros/latex/required/graphics/")
- ,("fancyhdr"
- ,"http://www.ctan.org/tex-archive/macros/latex/contrib/fancyhdr/")
- ,("array"
- ,"http://www.ctan.org/tex-archive/macros/latex/required/tools/")]
-
-runBibtex :: FilePath -> IO (Either String FilePath)
-runBibtex file = do
- let auxFile = replaceExtension file "aux"
- result <- run "bibtex" [auxFile]
- return $ either Left (const $ Right auxFile) result
-
-exit :: String -> IO a
-exit x = do
- progName <- getProgName
- UTF8.hPutStrLn stderr $ progName ++ ": " ++ x
- exitWith $ ExitFailure 1
-
-saveStdin :: FilePath -> IO (Either String FilePath)
-saveStdin file = do
- text <- liftM toString $ BS.getContents
- UTF8.writeFile file text
- fileExist <- doesFileExist (encodeString file)
- case fileExist of
- False -> return $ Left $! "Could not create " ++ file
- True -> return $ Right file
-
-saveOutput :: FilePath -> FilePath -> IO ()
-saveOutput input output = do
- copyFile (encodeString input) (encodeString output)
- UTF8.hPutStrLn stderr $! "Created " ++ output
-
--- | Perform a function in a temporary directory and clean up.
-withTempDir :: FilePath -> (FilePath -> IO a) -> IO a
-withTempDir baseName = bracket (createTempDir 0 baseName) removeDirectoryRecursive
-
--- | Create a temporary directory with a unique name.
-createTempDir :: Integer -> FilePath -> IO FilePath
-createTempDir num baseName = do
- sysTempDir <- getTemporaryDirectory
- let dirName = sysTempDir </> baseName <.> show num
- liftIO $ catch (createDirectory dirName >> return dirName) $
- \e -> if isAlreadyExistsError e
- then createTempDir (num + 1) baseName
- else ioError e
-
-main :: IO ()
-main = withTempDir "pandoc"
- -- run computation
- $ \tmp -> do
- args <- liftM (map decodeString) getArgs
- -- check for invalid arguments and print help message if needed
- let goodopts = ["-f","-r","-N", "-p","-R","-H","-B","-A", "-C","-o","-V"]
- let goodoptslong = ["--from","--read","--strict",
- "--preserve-tabs","--tab-stop","--parse-raw",
- "--toc","--table-of-contents", "--xetex", "--luatex",
- "--number-sections","--include-in-header",
- "--include-before-body","--include-after-body",
- "--custom-header","--output",
- "--template", "--variable",
- "--no-highlight", "--highlight-style",
- "--citation-abbreviations", "--old-dashes",
- "--csl", "--bibliography", "--data-dir", "--listings",
- "--beamer"]
- let isOpt ('-':_) = True
- isOpt _ = False
- let opts = filter isOpt args
- -- note that a long option can come in this form: --opt=val
- let isGoodopt x = x `elem` (goodopts ++ goodoptslong) ||
- any (\o -> (o ++ "=") `isPrefixOf` x) goodoptslong
- let markdown2pdfOpts = ["--xetex","--luatex", "--beamer"]
- unless (all isGoodopt opts) $ do
- (code, out, _err) <- readProcessWithExitCode "pandoc" ["--help"] ""
- UTF8.putStrLn "markdown2pdf [OPTIONS] [FILES]\nOptions:"
- UTF8.putStr $ unlines $
- filter (\l -> any (`isInfixOf` l) goodoptslong) (lines out)
- ++ map (replicate 24 ' ' ++) markdown2pdfOpts
- exitWith code
-
- let args' = filter (`notElem` markdown2pdfOpts) args
-
- -- check for executable files
- let latexProgram = if "--xetex" `elem` opts
- then "xelatex"
- else if "--luatex" `elem` opts
- then "lualatex"
- else "pdflatex"
- let outputFormat = if "--beamer" `elem` opts
- then "beamer"
- else "latex"
- let execs = ["pandoc", latexProgram, "bibtex"]
- paths <- mapM findExecutable execs
- let miss = map snd $ filter (isNothing . fst) $ zip paths execs
- unless (null miss) $ exit $! "Could not find " ++ intercalate ", " miss
-
- -- parse arguments
- -- if no input given, use 'stdin'
- pandocArgs <- parsePandocArgs args'
- (input, output) <- case pandocArgs of
- Nothing -> exit "Could not parse arguments"
- Just ([],out) -> do
- stdinFile <- saveStdin (replaceDirectory (takeBaseName out) tmp)
- case stdinFile of
- Left err -> exit err
- Right f -> return ([f], out)
- -- no need because we'll pass all arguments to pandoc
- Just (_ ,out) -> return ([], out)
- -- run pandoc
- pandocRes <- runPandoc outputFormat (input ++ args') $ replaceDirectory output tmp
- case pandocRes of
- Left err -> exit err
- Right texFile -> do
- -- run pdflatex
- latexRes <- runLatex latexProgram texFile
- case latexRes of
- Left err -> exit err
- Right pdfFile -> do
- -- save the output
- saveOutput pdfFile $
- replaceDirectory pdfFile (takeDirectory output)
-
diff --git a/windows/make-windows-installer.bat b/windows/make-windows-installer.bat
index 341dfd948..2ea2998fa 100644
--- a/windows/make-windows-installer.bat
+++ b/windows/make-windows-installer.bat
@@ -6,7 +6,6 @@ cabal-dev install --flags="executable wrappers -library highlighting" --datasubd
rem note: we use -f-library in building pandoc, because
rem if the library is built, the data file paths will not be relocatable!
strip cabal-dev\bin\pandoc.exe
-strip cabal-dev\bin\markdown2pdf.exe
cabal-dev\bin\pandoc.exe -s --template templates\html.template -S README -o README.html
copy COPYING COPYING.txt
copy COPYRIGHT COPYRIGHT.txt