summaryrefslogtreecommitdiff
path: root/src/pandoc.hs
diff options
context:
space:
mode:
authorKiwamu Okabe <kiwamu@debian.or.jp>2012-02-28 01:49:16 +0900
committerKiwamu Okabe <kiwamu@debian.or.jp>2012-02-28 01:49:16 +0900
commitb27a86d9758512d85d052a9a46917a54eb3da035 (patch)
tree43171a5211b250025cc85e6994a6a516aad5668f /src/pandoc.hs
parent6ac52ff209b172129452cd464d840b3c73c85c01 (diff)
Imported Upstream version 1.9.1.1
Diffstat (limited to 'src/pandoc.hs')
-rw-r--r--src/pandoc.hs738
1 files changed, 444 insertions, 294 deletions
diff --git a/src/pandoc.hs b/src/pandoc.hs
index 27bc2c25c..3853d360a 100644
--- a/src/pandoc.hs
+++ b/src/pandoc.hs
@@ -1,5 +1,5 @@
{-
-Copyright (C) 2006-2011 John MacFarlane <jgm@berkeley.edu>
+Copyright (C) 2006-2012 John MacFarlane <jgm@berkeley.edu>
This program is free software; you can redistribute it and/or modify
it under the terms of the GNU General Public License as published by
@@ -18,7 +18,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
{- |
Module : Main
- Copyright : Copyright (C) 2006-2011 John MacFarlane
+ Copyright : Copyright (C) 2006-2012 John MacFarlane
License : GNU GPL, version 2 or above
Maintainer : John MacFarlane <jgm@berkeley@edu>
@@ -30,24 +30,26 @@ writers.
-}
module Main where
import Text.Pandoc
-import Text.Pandoc.S5 (s5HeaderIncludes)
+import Text.Pandoc.PDF (tex2pdf)
+import Text.Pandoc.Readers.LaTeX (handleIncludes)
import Text.Pandoc.Shared ( tabFilter, ObfuscationMethod (..), readDataFile,
- headerShift, findDataFile, normalize )
-#ifdef _HIGHLIGHTING
-import Text.Pandoc.Highlighting ( languages )
-#endif
+ headerShift, findDataFile, normalize, err, warn )
+import Text.Pandoc.XML ( toEntities, fromEntities )
+import Text.Pandoc.SelfContained ( makeSelfContained )
+import Text.Pandoc.Highlighting ( languages, Style, tango, pygments,
+ espresso, kate, haddock, monochrome )
import System.Environment ( getArgs, getProgName )
import System.Exit ( exitWith, ExitCode (..) )
import System.FilePath
import System.Console.GetOpt
import Data.Char ( toLower )
import Data.List ( intercalate, isSuffixOf, isPrefixOf )
-import System.Directory ( getAppUserDataDirectory, doesFileExist )
-import System.IO ( stdout, stderr )
+import System.Directory ( getAppUserDataDirectory, doesFileExist, findExecutable )
+import System.IO ( stdout )
import System.IO.Error ( isDoesNotExistError )
import Control.Exception.Extensible ( throwIO )
import qualified Text.Pandoc.UTF8 as UTF8
-import Text.CSL
+import qualified Text.CSL as CSL
import Text.Pandoc.Biblio
import Control.Monad (when, unless, liftM)
import Network.HTTP (simpleHTTP, mkRequest, getResponseBody, RequestMethod(..))
@@ -55,35 +57,34 @@ import Network.URI (parseURI, isURI, URI(..))
import qualified Data.ByteString.Lazy as B
import Data.ByteString.Lazy.UTF8 (toString )
import Codec.Binary.UTF8.String (decodeString, encodeString)
+import Text.CSL.Reference (Reference(..))
copyrightMessage :: String
-copyrightMessage = "\nCopyright (C) 2006-2011 John MacFarlane\n" ++
+copyrightMessage = "\nCopyright (C) 2006-2012 John MacFarlane\n" ++
"Web: http://johnmacfarlane.net/pandoc\n" ++
"This is free software; see the source for copying conditions. There is no\n" ++
"warranty, not even for merchantability or fitness for a particular purpose."
compileInfo :: String
compileInfo =
- "\nCompiled with citeproc support." ++
-#ifdef _HIGHLIGHTING
- "\nCompiled with syntax highlighting support for:\n" ++
- wrapWords 78 languages ++
-#endif
- ""
+ "\nCompiled with citeproc-hs " ++ VERSION_citeproc_hs ++ ", texmath " ++
+ VERSION_texmath ++ ", highlighting-kate " ++ VERSION_highlighting_kate ++
+ ".\nSyntax highlighting is supported for the following languages:\n " ++
+ wrapWords 4 78 languages
-- | Converts a list of strings into a single string with the items printed as
-- comma separated words in lines with a maximum line length.
-wrapWords :: Int -> [String] -> String
-wrapWords c = wrap' c c where
- wrap' _ _ [] = ""
+wrapWords :: Int -> Int -> [String] -> String
+wrapWords indent c = wrap' (c - indent) (c - indent)
+ where wrap' _ _ [] = ""
wrap' cols remaining (x:xs) = if remaining == cols
then x ++ wrap' cols (remaining - length x) xs
else if (length x + 1) > remaining
- then ",\n" ++ x ++ wrap' cols (cols - length x) xs
+ then ",\n" ++ replicate indent ' ' ++ x ++ wrap' cols (cols - length x) xs
else ", " ++ x ++ wrap' cols (remaining - (length x + 2)) xs
-isNonTextOutput :: String -> Bool
-isNonTextOutput = (`elem` ["odt","epub"])
+nonTextFormats :: [String]
+nonTextFormats = ["odt","docx","epub"]
-- | Data structure for command line options.
data Opt = Opt
@@ -101,15 +102,19 @@ data Opt = Opt
, optNumberSections :: Bool -- ^ Number sections in LaTeX
, optSectionDivs :: Bool -- ^ Put sections in div tags in HTML
, optIncremental :: Bool -- ^ Use incremental lists in Slidy/S5
- , optOffline :: Bool -- ^ Make slideshow accessible offline
- , optXeTeX :: Bool -- ^ Format latex for xetex
+ , optSelfContained :: Bool -- ^ Make HTML accessible offline
, optSmart :: Bool -- ^ Use smart typography
+ , optOldDashes :: Bool -- ^ Parse dashes like pandoc <=1.8.2.1
, optHtml5 :: Bool -- ^ Produce HTML5 in HTML
+ , optHighlight :: Bool -- ^ Highlight source code
+ , optHighlightStyle :: Style -- ^ Style to use for highlighted code
, optChapters :: Bool -- ^ Use chapter for top-level sects
, optHTMLMathMethod :: HTMLMathMethod -- ^ Method to print HTML math
, optReferenceODT :: Maybe FilePath -- ^ Path of reference.odt
+ , optReferenceDocx :: Maybe FilePath -- ^ Path of reference.docx
, optEPUBStylesheet :: Maybe String -- ^ EPUB stylesheet
, optEPUBMetadata :: String -- ^ EPUB metadata
+ , optEPUBFonts :: [FilePath] -- ^ EPUB fonts to embed
, optDumpArgs :: Bool -- ^ Output command-line arguments
, optIgnoreArgs :: Bool -- ^ Ignore command-line arguments
, optStrict :: Bool -- ^ Use strict markdown syntax
@@ -124,8 +129,12 @@ data Opt = Opt
, optCiteMethod :: CiteMethod -- ^ Method to output cites
, optBibliography :: [String]
, optCslFile :: FilePath
+ , optAbbrevsFile :: Maybe FilePath
, optListings :: Bool -- ^ Use listings package for code blocks
- , optAscii :: Bool -- ^ Avoid using nonascii characters
+ , optLaTeXEngine :: String -- ^ Program to use for latex -> pdf
+ , optSlideLevel :: Maybe Int -- ^ Header level that creates slides
+ , optSetextHeaders :: Bool -- ^ Use atx headers for markdown level 1-2
+ , optAscii :: Bool -- ^ Use ascii characters only in html
}
-- | Defaults for command-line options.
@@ -145,15 +154,19 @@ defaultOpts = Opt
, optNumberSections = False
, optSectionDivs = False
, optIncremental = False
- , optOffline = False
- , optXeTeX = False
+ , optSelfContained = False
, optSmart = False
+ , optOldDashes = False
, optHtml5 = False
+ , optHighlight = True
+ , optHighlightStyle = pygments
, optChapters = False
, optHTMLMathMethod = PlainMath
, optReferenceODT = Nothing
+ , optReferenceDocx = Nothing
, optEPUBStylesheet = Nothing
, optEPUBMetadata = ""
+ , optEPUBFonts = []
, optDumpArgs = False
, optIgnoreArgs = False
, optStrict = False
@@ -168,7 +181,11 @@ defaultOpts = Opt
, optCiteMethod = Citeproc
, optBibliography = []
, optCslFile = ""
+ , optAbbrevsFile = Nothing
, optListings = False
+ , optLaTeXEngine = "pdflatex"
+ , optSlideLevel = Nothing
+ , optSetextHeaders = True
, optAscii = False
}
@@ -188,50 +205,23 @@ options =
"FORMAT")
""
- , Option "s" ["standalone"]
- (NoArg
- (\opt -> return opt { optStandalone = True }))
- "" -- "Include needed header and footer on output"
-
, Option "o" ["output"]
(ReqArg
(\arg opt -> return opt { optOutputFile = arg })
"FILENAME")
"" -- "Name of output file"
- , Option "p" ["preserve-tabs"]
- (NoArg
- (\opt -> return opt { optPreserveTabs = True }))
- "" -- "Preserve tabs instead of converting to spaces"
-
- , Option "" ["tab-stop"]
+ , Option "" ["data-dir"]
(ReqArg
- (\arg opt ->
- case reads arg of
- [(t,"")] | t > 0 -> return opt { optTabStop = t }
- _ -> do
- UTF8.hPutStrLn stderr $
- "tab-stop must be a number greater than 0"
- exitWith $ ExitFailure 31)
- "NUMBER")
- "" -- "Tab stop (default 4)"
+ (\arg opt -> return opt { optDataDir = Just arg })
+ "DIRECTORY") -- "Directory containing pandoc data files."
+ ""
, Option "" ["strict"]
(NoArg
(\opt -> return opt { optStrict = True } ))
"" -- "Disable markdown syntax extensions"
- , Option "" ["normalize"]
- (NoArg
- (\opt -> return opt { optTransforms =
- normalize : optTransforms opt } ))
- "" -- "Normalize the Pandoc AST"
-
- , Option "" ["reference-links"]
- (NoArg
- (\opt -> return opt { optReferenceLinks = True } ))
- "" -- "Use reference links in parsing HTML"
-
, Option "R" ["parse-raw"]
(NoArg
(\opt -> return opt { optParseRaw = True }))
@@ -242,145 +232,25 @@ options =
(\opt -> return opt { optSmart = True }))
"" -- "Use smart quotes, dashes, and ellipses"
- , Option "5" ["html5"]
- (NoArg
- (\opt -> return opt { optHtml5 = True }))
- "" -- "Produce HTML5 in HTML output"
-
- , Option "m" ["latexmathml", "asciimathml"]
- (OptArg
- (\arg opt ->
- return opt { optHTMLMathMethod = LaTeXMathML arg })
- "URL")
- "" -- "Use LaTeXMathML script in html output"
-
- , Option "" ["mathml"]
- (OptArg
- (\arg opt ->
- return opt { optHTMLMathMethod = MathML arg })
- "URL")
- "" -- "Use mathml for HTML math"
-
- , Option "" ["mimetex"]
- (OptArg
- (\arg opt -> do
- let url' = case arg of
- Just u -> u ++ "?"
- Nothing -> "/cgi-bin/mimetex.cgi?"
- return opt { optHTMLMathMethod = WebTeX url' })
- "URL")
- "" -- "Use mimetex for HTML math"
-
- , Option "" ["webtex"]
- (OptArg
- (\arg opt -> do
- let url' = case arg of
- Just u -> u
- Nothing -> "http://chart.apis.google.com/chart?cht=tx&chl="
- return opt { optHTMLMathMethod = WebTeX url' })
- "URL")
- "" -- "Use web service for HTML math"
-
- , Option "" ["jsmath"]
- (OptArg
- (\arg opt -> return opt { optHTMLMathMethod = JsMath arg})
- "URL")
- "" -- "Use jsMath for HTML math"
-
- , Option "" ["mathjax"]
- (OptArg
- (\arg opt -> do
- let url' = case arg of
- Just u -> u
- Nothing -> "https://d3eoax9i5htok0.cloudfront.net/mathjax/latest/MathJax.js?config=TeX-AMS-MML_HTMLorMML"
- return opt { optHTMLMathMethod = MathJax url'})
- "URL")
- "" -- "Use MathJax for HTML math"
-
- , Option "" ["gladtex"]
- (NoArg
- (\opt -> return opt { optHTMLMathMethod = GladTeX }))
- "" -- "Use gladtex for HTML math"
-
- , Option "i" ["incremental"]
- (NoArg
- (\opt -> return opt { optIncremental = True }))
- "" -- "Make list items display incrementally in Slidy/S5"
-
- , Option "" ["offline"]
- (NoArg
- (\opt -> return opt { optOffline = True,
- optStandalone = True }))
- "" -- "Make slide shows include all the needed js and css"
-
- , Option "" ["xetex"]
+ , Option "" ["old-dashes"]
(NoArg
- (\opt -> do
- UTF8.hPutStrLn stderr $ "pandoc: --xetex is deprecated. "
- ++ "It is no longer needed for use with XeTeX."
- return opt { optXeTeX = True }))
- "" -- "Format latex for processing by XeTeX"
-
- , Option "" ["chapters"]
- (NoArg
- (\opt -> return opt { optChapters = True }))
- "" -- "Use chapter for top-level sections in LaTeX, DocBook"
-
- , Option "N" ["number-sections"]
- (NoArg
- (\opt -> return opt { optNumberSections = True }))
- "" -- "Number sections in LaTeX"
-
- , Option "" ["listings"]
- (NoArg
- (\opt -> return opt { optListings = True }))
- "" -- "Use listings package for LaTeX code blocks"
-
- , Option "" ["section-divs"]
- (NoArg
- (\opt -> return opt { optSectionDivs = True }))
- "" -- "Put sections in div tags in HTML"
-
- , Option "" ["no-wrap"]
- (NoArg
- (\opt -> return opt { optWrapText = False }))
- "" -- "Do not wrap text in output"
+ (\opt -> return opt { optSmart = True
+ , optOldDashes = True }))
+ "" -- "Use smart quotes, dashes, and ellipses"
- , Option "" ["columns"]
+ , Option "" ["base-header-level"]
(ReqArg
(\arg opt ->
case reads arg of
- [(t,"")] | t > 0 -> return opt { optColumns = t }
- _ -> do
- UTF8.hPutStrLn stderr $
- "columns must be a number greater than 0"
- exitWith $ ExitFailure 33)
- "NUMBER")
- "" -- "Length of line in characters"
-
- , Option "" ["ascii"]
- (NoArg
- (\opt -> return opt { optAscii = True }))
- "" -- "Avoid using non-ascii characters in output"
-
- , Option "" ["email-obfuscation"]
- (ReqArg
- (\arg opt -> do
- method <- case arg of
- "references" -> return ReferenceObfuscation
- "javascript" -> return JavascriptObfuscation
- "none" -> return NoObfuscation
- _ -> UTF8.hPutStrLn stderr ("Error: Unknown obfuscation method: " ++ arg) >>
- exitWith (ExitFailure 6)
- return opt { optEmailObfuscation = method })
- "none|javascript|references")
- "" -- "Method for obfuscating email in HTML"
-
- , Option "" ["id-prefix"]
- (ReqArg
- (\arg opt -> return opt { optIdentifierPrefix = arg })
- "STRING")
- "" -- "Prefix to add to automatically generated HTML identifiers"
+ [(t,"")] | t > 0 -> do
+ let oldTransforms = optTransforms opt
+ let shift = t - 1
+ return opt{ optTransforms =
+ headerShift shift : oldTransforms }
+ _ -> err 19
+ "base-header-level must be a number > 0")
+ "NUMBER")
+ "" -- "Headers base level"
, Option "" ["indented-code-classes"]
(ReqArg
@@ -389,26 +259,31 @@ options =
"STRING")
"" -- "Classes (whitespace- or comma-separated) to use for indented code-blocks"
- , Option "" ["toc", "table-of-contents"]
- (NoArg
- (\opt -> return opt { optTableOfContents = True }))
- "" -- "Include table of contents"
+ , Option "" ["normalize"]
+ (NoArg
+ (\opt -> return opt { optTransforms =
+ normalize : optTransforms opt } ))
+ "" -- "Normalize the Pandoc AST"
- , Option "" ["base-header-level"]
+ , Option "p" ["preserve-tabs"]
+ (NoArg
+ (\opt -> return opt { optPreserveTabs = True }))
+ "" -- "Preserve tabs instead of converting to spaces"
+
+ , Option "" ["tab-stop"]
(ReqArg
(\arg opt ->
case reads arg of
- [(t,"")] | t > 0 -> do
- let oldTransforms = optTransforms opt
- let shift = t - 1
- return opt{ optTransforms =
- headerShift shift : oldTransforms }
- _ -> do
- UTF8.hPutStrLn stderr $
- "base-header-level must be a number > 0"
- exitWith $ ExitFailure 19)
+ [(t,"")] | t > 0 -> return opt { optTabStop = t }
+ _ -> err 31
+ "tab-stop must be a number greater than 0")
"NUMBER")
- "" -- "Headers base level"
+ "" -- "Tab stop (default 4)"
+
+ , Option "s" ["standalone"]
+ (NoArg
+ (\opt -> return opt { optStandalone = True }))
+ "" -- "Include needed header and footer on output"
, Option "" ["template"]
(ReqArg
@@ -425,21 +300,62 @@ options =
(k,_:v) -> do
let newvars = optVariables opt ++ [(k,v)]
return opt{ optVariables = newvars }
- _ -> do
- UTF8.hPutStrLn stderr $ "Could not parse `" ++ arg ++ "' as a key/value pair (k=v or k:v)"
- exitWith $ ExitFailure 17)
+ _ -> err 17 $
+ "Could not parse `" ++ arg ++ "' as a key/value pair (k=v or k:v)")
"KEY:VALUE")
"" -- "Use custom template"
- , Option "c" ["css"]
+ , Option "D" ["print-default-template"]
(ReqArg
- (\arg opt -> do
- -- add new link to end, so it is included in proper order
- let newvars = optVariables opt ++ [("css",arg)]
- return opt { optVariables = newvars,
- optStandalone = True })
- "URL")
- "" -- "Link to CSS style sheet"
+ (\arg _ -> do
+ templ <- getDefaultTemplate Nothing arg
+ case templ of
+ Right t -> UTF8.hPutStr stdout t
+ Left e -> error $ show e
+ exitWith ExitSuccess)
+ "FORMAT")
+ "" -- "Print default template for FORMAT"
+
+ , Option "" ["no-wrap"]
+ (NoArg
+ (\opt -> return opt { optWrapText = False }))
+ "" -- "Do not wrap text in output"
+
+ , Option "" ["columns"]
+ (ReqArg
+ (\arg opt ->
+ case reads arg of
+ [(t,"")] | t > 0 -> return opt { optColumns = t }
+ _ -> err 33 $
+ "columns must be a number greater than 0")
+ "NUMBER")
+ "" -- "Length of line in characters"
+
+ , Option "" ["toc", "table-of-contents"]
+ (NoArg
+ (\opt -> return opt { optTableOfContents = True }))
+ "" -- "Include table of contents"
+
+ , Option "" ["no-highlight"]
+ (NoArg
+ (\opt -> return opt { optHighlight = False }))
+ "" -- "Don't highlight source code"
+
+ , Option "" ["highlight-style"]
+ (ReqArg
+ (\arg opt -> do
+ newStyle <- case map toLower arg of
+ "pygments" -> return pygments
+ "tango" -> return tango
+ "espresso" -> return espresso
+ "kate" -> return kate
+ "monochrome" -> return monochrome
+ "haddock" -> return haddock
+ _ -> err 39 $
+ "Unknown style :" ++ arg
+ return opt{ optHighlightStyle = newStyle })
+ "STYLE")
+ "" -- "Style for highlighted code"
, Option "H" ["include-in-header"]
(ReqArg
@@ -474,6 +390,100 @@ options =
"FILENAME")
"" -- "File to include after document body"
+ , Option "" ["self-contained"]
+ (NoArg
+ (\opt -> return opt { optSelfContained = True,
+ optVariables = ("slidy-url","slidy") :
+ optVariables opt,
+ optStandalone = True }))
+ "" -- "Make slide shows include all the needed js and css"
+
+ , Option "" ["offline"]
+ (NoArg
+ (\opt -> do warn $ "--offline is deprecated. Use --self-contained instead."
+ return opt { optSelfContained = True,
+ optStandalone = True }))
+ "" -- "Make slide shows include all the needed js and css"
+ -- deprecated synonym for --self-contained
+
+ , Option "5" ["html5"]
+ (NoArg
+ (\opt -> do
+ warn $ "--html5 is deprecated. "
+ ++ "Use the html5 output format instead."
+ return opt { optHtml5 = True }))
+ "" -- "Produce HTML5 in HTML output"
+
+ , Option "" ["ascii"]
+ (NoArg
+ (\opt -> return opt { optAscii = True }))
+ "" -- "Use ascii characters only in HTML output"
+
+ , Option "" ["reference-links"]
+ (NoArg
+ (\opt -> return opt { optReferenceLinks = True } ))
+ "" -- "Use reference links in parsing HTML"
+
+ , Option "" ["atx-headers"]
+ (NoArg
+ (\opt -> return opt { optSetextHeaders = False } ))
+ "" -- "Use atx-style headers for markdown"
+
+ , Option "" ["chapters"]
+ (NoArg
+ (\opt -> return opt { optChapters = True }))
+ "" -- "Use chapter for top-level sections in LaTeX, DocBook"
+
+ , Option "N" ["number-sections"]
+ (NoArg
+ (\opt -> return opt { optNumberSections = True }))
+ "" -- "Number sections in LaTeX"
+
+ , Option "" ["listings"]
+ (NoArg
+ (\opt -> return opt { optListings = True }))
+ "" -- "Use listings package for LaTeX code blocks"
+
+ , Option "i" ["incremental"]
+ (NoArg
+ (\opt -> return opt { optIncremental = True }))
+ "" -- "Make list items display incrementally in Slidy/S5"
+
+ , Option "" ["slide-level"]
+ (ReqArg
+ (\arg opt -> do
+ case reads arg of
+ [(t,"")] | t >= 1 && t <= 6 ->
+ return opt { optSlideLevel = Just t }
+ _ -> err 39 $
+ "slide level must be a number between 1 and 6")
+ "NUMBER")
+ "" -- "Force header level for slides"
+
+ , Option "" ["section-divs"]
+ (NoArg
+ (\opt -> return opt { optSectionDivs = True }))
+ "" -- "Put sections in div tags in HTML"
+
+ , Option "" ["email-obfuscation"]
+ (ReqArg
+ (\arg opt -> do
+ method <- case arg of
+ "references" -> return ReferenceObfuscation
+ "javascript" -> return JavascriptObfuscation
+ "none" -> return NoObfuscation
+ _ -> err 6
+ ("Unknown obfuscation method: " ++ arg)
+ return opt { optEmailObfuscation = method })
+ "none|javascript|references")
+ "" -- "Method for obfuscating email in HTML"
+
+ , Option "" ["id-prefix"]
+ (ReqArg
+ (\arg opt -> return opt { optIdentifierPrefix = arg })
+ "STRING")
+ "" -- "Prefix to add to automatically generated HTML identifiers"
+
, Option "T" ["title-prefix"]
(ReqArg
(\arg opt -> do
@@ -483,6 +493,16 @@ options =
"STRING")
"" -- "String to prefix to HTML window title"
+ , Option "c" ["css"]
+ (ReqArg
+ (\arg opt -> do
+ -- add new link to end, so it is included in proper order
+ let newvars = optVariables opt ++ [("css",arg)]
+ return opt { optVariables = newvars,
+ optStandalone = True })
+ "URL")
+ "" -- "Link to CSS style sheet"
+
, Option "" ["reference-odt"]
(ReqArg
(\arg opt -> do
@@ -490,6 +510,13 @@ options =
"FILENAME")
"" -- "Path of custom reference.odt"
+ , Option "" ["reference-docx"]
+ (ReqArg
+ (\arg opt -> do
+ return opt { optReferenceDocx = Just arg })
+ "FILENAME")
+ "" -- "Path of custom reference.docx"
+
, Option "" ["epub-stylesheet"]
(ReqArg
(\arg opt -> do
@@ -514,16 +541,22 @@ options =
"FILENAME")
"" -- "Path of epub metadata file"
- , Option "D" ["print-default-template"]
+ , Option "" ["epub-embed-font"]
(ReqArg
- (\arg _ -> do
- templ <- getDefaultTemplate Nothing arg
- case templ of
- Right t -> UTF8.hPutStr stdout t
- Left e -> error $ show e
- exitWith ExitSuccess)
- "FORMAT")
- "" -- "Print default template for FORMAT"
+ (\arg opt -> do
+ return opt{ optEPUBFonts = arg : optEPUBFonts opt })
+ "FILE")
+ "" -- "Directory of fonts to embed"
+
+ , Option "" ["latex-engine"]
+ (ReqArg
+ (\arg opt -> do
+ let b = takeBaseName arg
+ if (b == "pdflatex" || b == "lualatex" || b == "xelatex")
+ then return opt { optLaTeXEngine = arg }
+ else err 45 "latex-engine must be pdflatex, lualatex, or xelatex.")
+ "PROGRAM")
+ "" -- "Name of latex program to use in generating PDF"
, Option "" ["bibliography"]
(ReqArg
@@ -537,6 +570,12 @@ options =
"FILENAME")
""
+ , Option "" ["citation-abbreviations"]
+ (ReqArg
+ (\arg opt -> return opt { optAbbrevsFile = Just arg })
+ "FILENAME")
+ ""
+
, Option "" ["natbib"]
(NoArg
(\opt -> return opt { optCiteMethod = Natbib }))
@@ -547,11 +586,60 @@ options =
(\opt -> return opt { optCiteMethod = Biblatex }))
"" -- "Use biblatex cite commands in LaTeX output"
- , Option "" ["data-dir"]
- (ReqArg
- (\arg opt -> return opt { optDataDir = Just arg })
- "DIRECTORY") -- "Directory containing pandoc data files."
- ""
+ , Option "m" ["latexmathml", "asciimathml"]
+ (OptArg
+ (\arg opt ->
+ return opt { optHTMLMathMethod = LaTeXMathML arg })
+ "URL")
+ "" -- "Use LaTeXMathML script in html output"
+
+ , Option "" ["mathml"]
+ (OptArg
+ (\arg opt ->
+ return opt { optHTMLMathMethod = MathML arg })
+ "URL")
+ "" -- "Use mathml for HTML math"
+
+ , Option "" ["mimetex"]
+ (OptArg
+ (\arg opt -> do
+ let url' = case arg of
+ Just u -> u ++ "?"
+ Nothing -> "/cgi-bin/mimetex.cgi?"
+ return opt { optHTMLMathMethod = WebTeX url' })
+ "URL")
+ "" -- "Use mimetex for HTML math"
+
+ , Option "" ["webtex"]
+ (OptArg
+ (\arg opt -> do
+ let url' = case arg of
+ Just u -> u
+ Nothing -> "http://chart.apis.google.com/chart?cht=tx&chl="
+ return opt { optHTMLMathMethod = WebTeX url' })
+ "URL")
+ "" -- "Use web service for HTML math"
+
+ , Option "" ["jsmath"]
+ (OptArg
+ (\arg opt -> return opt { optHTMLMathMethod = JsMath arg})
+ "URL")
+ "" -- "Use jsMath for HTML math"
+
+ , Option "" ["mathjax"]
+ (OptArg
+ (\arg opt -> do
+ let url' = case arg of
+ Just u -> u
+ Nothing -> "https://d3eoax9i5htok0.cloudfront.net/mathjax/latest/MathJax.js?config=TeX-AMS-MML_HTMLorMML"
+ return opt { optHTMLMathMethod = MathJax url'})
+ "URL")
+ "" -- "Use MathJax for HTML math"
+
+ , Option "" ["gladtex"]
+ (NoArg
+ (\opt -> return opt { optHTMLMathMethod = GladTeX }))
+ "" -- "Use gladtex for HTML math"
, Option "" ["dump-args"]
(NoArg
@@ -579,14 +667,15 @@ options =
UTF8.hPutStr stdout (usageMessage prg options)
exitWith ExitSuccess ))
"" -- "Show help"
+
]
-- Returns usage message
usageMessage :: String -> [OptDescr (Opt -> IO Opt)] -> String
usageMessage programName = usageInfo
(programName ++ " [OPTIONS] [FILES]" ++ "\nInput formats: " ++
- (intercalate ", " $ map fst readers) ++ "\nOutput formats: " ++
- (intercalate ", " $ map fst writers ++ ["odt","epub"]) ++ "\nOptions:")
+ (wrapWords 16 78 $ map fst readers) ++ "\nOutput formats: " ++
+ (wrapWords 16 78 $ map fst writers ++ nonTextFormats) ++ "\nOptions:")
-- Determine default reader based on source file extensions
defaultReaderName :: String -> [FilePath] -> String
@@ -637,8 +726,11 @@ defaultWriterName x =
".texinfo" -> "texinfo"
".db" -> "docbook"
".odt" -> "odt"
+ ".docx" -> "docx"
".epub" -> "epub"
".org" -> "org"
+ ".asciidoc" -> "asciidoc"
+ ".pdf" -> "latex"
['.',y] | y `elem` ['1'..'9'] -> "man"
_ -> "html"
@@ -654,10 +746,8 @@ main = do
else getOpt Permute options rawArgs
unless (null errors) $
- do name <- getProgName
- mapM_ (\e -> UTF8.hPutStr stderr (name ++ ": ") >> UTF8.hPutStr stderr e) errors
- UTF8.hPutStrLn stderr $ "Try " ++ name ++ " --help for more information."
- exitWith $ ExitFailure 2
+ err 2 $ concat $ errors ++
+ ["Try " ++ prg ++ " --help for more information."]
let defaultOpts' = if compatMode
then defaultOpts { optReader = "markdown"
@@ -682,14 +772,19 @@ main = do
, optNumberSections = numberSections
, optSectionDivs = sectionDivs
, optIncremental = incremental
- , optOffline = offline
+ , optSelfContained = selfContained
, optSmart = smart
+ , optOldDashes = oldDashes
, optHtml5 = html5
+ , optHighlight = highlight
+ , optHighlightStyle = highlightStyle
, optChapters = chapters
, optHTMLMathMethod = mathMethod
, optReferenceODT = referenceODT
+ , optReferenceDocx = referenceDocx
, optEPUBStylesheet = epubStylesheet
, optEPUBMetadata = epubMetadata
+ , optEPUBFonts = epubFonts
, optDumpArgs = dumpArgs
, optIgnoreArgs = ignoreArgs
, optStrict = strict
@@ -702,8 +797,12 @@ main = do
, optDataDir = mbDataDir
, optBibliography = reffiles
, optCslFile = cslfile
+ , optAbbrevsFile = cslabbrevs
, optCiteMethod = citeMethod
, optListings = listings
+ , optLaTeXEngine = latexEngine
+ , optSlideLevel = slideLevel
+ , optSetextHeaders = setextHeaders
, optAscii = ascii
} = opts
@@ -726,17 +825,35 @@ main = do
then "html"
else "markdown"
in defaultReaderName fallback sources
- else readerName
+ else readerName
let writerName' = if null writerName
then defaultWriterName outputFile
else writerName
+ let pdfOutput = map toLower (takeExtension outputFile) == ".pdf"
+
+ when pdfOutput $ do
+ -- make sure writer is latex or beamer
+ unless (writerName' == "latex" || writerName' == "beamer" ||
+ writerName' == "latex+lhs") $
+ err 47 $ "cannot produce pdf output with " ++ writerName' ++ " writer"
+ -- check for latex program
+ mbLatex <- findExecutable latexEngine
+ case mbLatex of
+ Nothing -> err 41 $
+ latexEngine ++ " not found. " ++
+ latexEngine ++ " is needed for pdf output."
+ Just _ -> return ()
+
reader <- case (lookup readerName' readers) of
Just r -> return r
- Nothing -> error ("Unknown reader: " ++ readerName')
+ Nothing -> err 7 ("Unknown reader: " ++ readerName')
+
+ let standalone' = standalone || writerName' `elem` nonTextFormats || pdfOutput
templ <- case templatePath of
+ _ | not standalone' -> return ""
Nothing -> do
deftemp <- getDefaultTemplate datadir writerName'
case deftemp of
@@ -756,57 +873,57 @@ main = do
(\_ -> throwIO e)
else throwIO e)
- let standalone' = standalone || isNonTextOutput writerName'
-
- variables' <- case (writerName', standalone', offline) of
- ("s5", True, True) -> do
- inc <- s5HeaderIncludes datadir
- return $ ("s5includes", inc) : variables
- ("slidy", True, True) -> do
- slidyJs <- readDataFile datadir $
- "slidy" </> "slidy.min.js"
- slidyCss <- readDataFile datadir $
- "slidy" </> "slidy.css"
- return $ ("slidy-js", slidyJs) :
- ("slidy-css", slidyCss) : variables
- _ -> return variables
+ let slideVariant = case writerName' of
+ "s5" -> S5Slides
+ "slidy" -> SlidySlides
+ "dzslides" -> DZSlides
+ _ -> NoSlides
- variables'' <- case mathMethod of
+ variables' <- case mathMethod of
LaTeXMathML Nothing -> do
s <- readDataFile datadir $ "data" </> "LaTeXMathML.js"
- return $ ("mathml-script", s) : variables'
+ return $ ("mathml-script", s) : variables
MathML Nothing -> do
s <- readDataFile datadir $ "data"</>"MathMLinHTML.js"
- return $ ("mathml-script", s) : variables'
- _ -> return variables'
+ return $ ("mathml-script", s) : variables
+ _ -> return variables
+
+ variables'' <- case slideVariant of
+ DZSlides -> do
+ dztempl <- readDataFile datadir $ "dzslides" </> "template.html"
+ let dzcore = unlines $ dropWhile (not . isPrefixOf "<!-- {{{{ dzslides core")
+ $ lines dztempl
+ return $ ("dzslides-core", dzcore) : variables'
+ _ -> return variables'
- refs <- mapM (\f -> catch (readBiblioFile f) $ \e -> do
- UTF8.hPutStrLn stderr $ "Error reading bibliography `" ++ f ++ "'"
- UTF8.hPutStrLn stderr $ show e
- exitWith (ExitFailure 23)) reffiles >>= \rs -> return $ concat rs
+ -- unescape reference ids, which may contain XML entities, so
+ -- that we can do lookups with regular string equality
+ let unescapeRefId ref = ref{ refId = fromEntities (refId ref) }
+
+ refs <- mapM (\f -> catch (CSL.readBiblioFile f) $ \e ->
+ err 23 $ "Error reading bibliography `" ++ f ++ "'" ++ "\n" ++ show e)
+ reffiles >>=
+ return . map unescapeRefId . concat
let sourceDir = if null sources
then "."
else takeDirectory (head sources)
- let slideVariant = case writerName' of
- "s5" -> S5Slides
- "slidy" -> SlidySlides
- _ -> NoSlides
-
let startParserState =
defaultParserState { stateParseRaw = parseRaw,
stateTabStop = tabStop,
stateLiterateHaskell = "+lhs" `isSuffixOf` readerName' ||
lhsExtension sources,
stateStandalone = standalone',
- stateCitations = map refId refs,
+ stateCitations = map CSL.refId refs,
stateSmart = smart || writerName' `elem`
- ["latex", "context", "latex+lhs", "man"],
+ ["latex", "context", "latex+lhs", "beamer"],
+ stateOldDashes = oldDashes,
stateColumns = columns,
stateStrict = strict,
stateIndentedCodeClasses = codeBlockClasses,
- stateApplyMacros = writerName' `notElem` ["latex", "latex+lhs"] }
+ stateApplyMacros = writerName' `notElem`
+ ["latex", "latex+lhs", "beamer"] }
let writerOptions = defaultWriterOptions
{ writerStandalone = standalone',
@@ -836,16 +953,20 @@ main = do
writerIdentifierPrefix = idPrefix,
writerSourceDirectory = sourceDir,
writerUserDataDir = datadir,
- writerHtml5 = html5 &&
- "html" `isPrefixOf` writerName',
- writerChapters = chapters,
+ writerHtml5 = html5 ||
+ slideVariant == DZSlides,
+ writerChapters = chapters,
writerListings = listings,
- writerAscii = ascii }
+ writerBeamer = writerName' == "beamer",
+ writerSlideLevel = slideLevel,
+ writerHighlight = highlight,
+ writerHighlightStyle = highlightStyle,
+ writerSetextHeaders = setextHeaders
+ }
- when (isNonTextOutput writerName' && outputFile == "-") $
- do UTF8.hPutStrLn stderr ("Error: Cannot write " ++ writerName ++ " output to stdout.\n" ++
- "Specify an output file using the -o option.")
- exitWith $ ExitFailure 5
+ when (writerName' `elem` nonTextFormats&& outputFile == "-") $
+ err 5 $ "Cannot write " ++ writerName' ++ " output to stdout.\n" ++
+ "Specify an output file using the -o option."
let readSources [] = mapM readSource ["-"]
readSources srcs = mapM readSource srcs
@@ -859,7 +980,14 @@ main = do
let convertTabs = tabFilter (if preserveTabs then 0 else tabStop)
- doc <- fmap (reader startParserState . convertTabs . intercalate "\n") (readSources sources)
+ let handleIncludes' = if readerName' == "latex" || readerName' == "beamer" ||
+ readerName' == "latex+lhs" ||
+ readerName' == "context"
+ then handleIncludes
+ else return
+
+ doc <- (reader startParserState) `fmap` (readSources sources >>=
+ handleIncludes' . convertTabs . intercalate "\n")
let doc0 = foldr ($) doc transforms
@@ -881,19 +1009,41 @@ main = do
replaceDirectory
(replaceExtension cslfile "csl")
csldir
- processBiblio cslfile' refs doc1
+ processBiblio cslfile' cslabbrevs refs doc1
else return doc1
+ let writeBinary :: B.ByteString -> IO ()
+ writeBinary = B.writeFile (encodeString outputFile)
+
+ let writerFn :: FilePath -> String -> IO ()
+ writerFn "-" = UTF8.putStr
+ writerFn f = UTF8.writeFile f
+
case lookup writerName' writers of
- Nothing | writerName' == "epub" ->
- writeEPUB epubStylesheet writerOptions doc2
- >>= B.writeFile (encodeString outputFile)
- Nothing | writerName' == "odt" ->
- writeODT referenceODT writerOptions doc2
- >>= B.writeFile (encodeString outputFile)
- Just r -> writerFn outputFile result
- where writerFn "-" = UTF8.putStr
- writerFn f = UTF8.writeFile f
- result = r writerOptions doc2 ++
- ['\n' | not standalone']
- Nothing -> error $ "Unknown writer: " ++ writerName'
+ Nothing
+ | writerName' == "epub" ->
+ writeEPUB epubStylesheet epubFonts writerOptions doc2
+ >>= writeBinary
+ | writerName' == "odt" ->
+ writeODT referenceODT writerOptions doc2 >>= writeBinary
+ | writerName' == "docx" ->
+ writeDocx referenceDocx writerOptions doc2 >>= writeBinary
+ | otherwise -> err 9 ("Unknown writer: " ++ writerName')
+ Just _
+ | pdfOutput -> do
+ res <- tex2pdf latexEngine $ writeLaTeX writerOptions doc2
+ case res of
+ Right pdf -> writeBinary pdf
+ Left err' -> err 43 $ toString err'
+ Just r
+ | htmlFormat && ascii ->
+ writerFn outputFile =<< selfcontain (toEntities result)
+ | otherwise ->
+ writerFn outputFile =<< selfcontain result
+ where result = r writerOptions doc2 ++ ['\n' | not standalone']
+ htmlFormat = writerName' `elem`
+ ["html","html+lhs","html5","html5+lhs",
+ "s5","slidy","dzslides"]
+ selfcontain = if selfContained && htmlFormat
+ then makeSelfContained datadir
+ else return