Deprecated --xetex
option - it is no longer needed.
Deprecated `writerXeTeX` and the `--xetex` option. The latex writer now produces a file that can be processed by latex, pdflatex, lualatex, or xelatex, so this option isn't needed. The option is still neded in markdown2pdf, however, which has been modified to take some options that aren't in pandoc.
This commit is contained in:
parent
0590d7e4c2
commit
18306c74fb
6 changed files with 16 additions and 14 deletions
3
README
3
README
|
@ -265,9 +265,6 @@ Options
|
||||||
show in the output, so that the slide show will work even when no
|
show in the output, so that the slide show will work even when no
|
||||||
internet connection is available.
|
internet connection is available.
|
||||||
|
|
||||||
`--xetex`
|
|
||||||
: Create LaTeX outut suitable for processing by XeTeX.
|
|
||||||
|
|
||||||
`--chapters`
|
`--chapters`
|
||||||
: Treat top-level headers as chapters in LaTeX, ConTeXt, and DocBook
|
: Treat top-level headers as chapters in LaTeX, ConTeXt, and DocBook
|
||||||
output.
|
output.
|
||||||
|
|
|
@ -42,9 +42,6 @@ packages are not included in your latex setup, they can be obtained from
|
||||||
\--strict
|
\--strict
|
||||||
: Use strict markdown syntax, with no extensions or variants.
|
: Use strict markdown syntax, with no extensions or variants.
|
||||||
|
|
||||||
\--xetex
|
|
||||||
: Use xelatex instead of pdflatex to create the PDF.
|
|
||||||
|
|
||||||
-N, \--number-sections
|
-N, \--number-sections
|
||||||
: Number section headings in LaTeX output. (Default is not to number them.)
|
: Number section headings in LaTeX output. (Default is not to number them.)
|
||||||
|
|
||||||
|
@ -109,6 +106,9 @@ packages are not included in your latex setup, they can be obtained from
|
||||||
or `s5` directory placed in this directory will override pandoc's
|
or `s5` directory placed in this directory will override pandoc's
|
||||||
normal defaults.
|
normal defaults.
|
||||||
|
|
||||||
|
\--xetex
|
||||||
|
: Use xelatex instead of pdflatex to create the PDF.
|
||||||
|
|
||||||
# SEE ALSO
|
# SEE ALSO
|
||||||
|
|
||||||
`pandoc`(1), `pdflatex`(1)
|
`pandoc`(1), `pdflatex`(1)
|
||||||
|
|
|
@ -493,6 +493,7 @@ data WriterOptions = WriterOptions
|
||||||
, writerAscii :: Bool -- ^ Avoid non-ascii characters
|
, writerAscii :: Bool -- ^ Avoid non-ascii characters
|
||||||
} deriving Show
|
} deriving Show
|
||||||
|
|
||||||
|
{-# DEPRECATED writerXeTeX "writerXeTeX no longer does anything" #-}
|
||||||
-- | Default writer options.
|
-- | Default writer options.
|
||||||
defaultWriterOptions :: WriterOptions
|
defaultWriterOptions :: WriterOptions
|
||||||
defaultWriterOptions =
|
defaultWriterOptions =
|
||||||
|
|
|
@ -111,7 +111,6 @@ pandocToLaTeX options (Pandoc (Meta title authors date) blocks) = do
|
||||||
, ("title", titletext)
|
, ("title", titletext)
|
||||||
, ("date", dateText) ] ++
|
, ("date", dateText) ] ++
|
||||||
[ ("author", a) | a <- authorsText ] ++
|
[ ("author", a) | a <- authorsText ] ++
|
||||||
[ ("xetex", "yes") | writerXeTeX options ] ++
|
|
||||||
[ ("verbatim-in-note", "yes") | stVerbInNote st ] ++
|
[ ("verbatim-in-note", "yes") | stVerbInNote st ] ++
|
||||||
[ ("fancy-enums", "yes") | stEnumerate st ] ++
|
[ ("fancy-enums", "yes") | stEnumerate st ] ++
|
||||||
[ ("tables", "yes") | stTable st ] ++
|
[ ("tables", "yes") | stTable st ] ++
|
||||||
|
|
|
@ -210,9 +210,12 @@ main = bracket
|
||||||
(code, out, _err) <- readProcessWithExitCode "pandoc" ["--help"] ""
|
(code, out, _err) <- readProcessWithExitCode "pandoc" ["--help"] ""
|
||||||
UTF8.putStrLn "markdown2pdf [OPTIONS] [FILES]\nOptions:"
|
UTF8.putStrLn "markdown2pdf [OPTIONS] [FILES]\nOptions:"
|
||||||
UTF8.putStr $ unlines $
|
UTF8.putStr $ unlines $
|
||||||
filter (\l -> any (`isInfixOf` l) goodoptslong) $ lines out
|
filter (\l -> any (`isInfixOf` l) goodoptslong) (lines out)
|
||||||
|
++ [replicate 24 ' ' ++ "--xetex"]
|
||||||
exitWith code
|
exitWith code
|
||||||
|
|
||||||
|
let args' = filter (/= "--xetex") args
|
||||||
|
|
||||||
-- check for executable files
|
-- check for executable files
|
||||||
let latexProgram = if "--xetex" `elem` opts
|
let latexProgram = if "--xetex" `elem` opts
|
||||||
then "xelatex"
|
then "xelatex"
|
||||||
|
@ -224,7 +227,7 @@ main = bracket
|
||||||
|
|
||||||
-- parse arguments
|
-- parse arguments
|
||||||
-- if no input given, use 'stdin'
|
-- if no input given, use 'stdin'
|
||||||
pandocArgs <- parsePandocArgs args
|
pandocArgs <- parsePandocArgs args'
|
||||||
(input, output) <- case pandocArgs of
|
(input, output) <- case pandocArgs of
|
||||||
Nothing -> exit "Could not parse arguments"
|
Nothing -> exit "Could not parse arguments"
|
||||||
Just ([],out) -> do
|
Just ([],out) -> do
|
||||||
|
@ -235,7 +238,7 @@ main = bracket
|
||||||
-- no need because we'll pass all arguments to pandoc
|
-- no need because we'll pass all arguments to pandoc
|
||||||
Just (_ ,out) -> return ([], out)
|
Just (_ ,out) -> return ([], out)
|
||||||
-- run pandoc
|
-- run pandoc
|
||||||
pandocRes <- runPandoc (input ++ args) $ replaceDirectory output tmp
|
pandocRes <- runPandoc (input ++ args') $ replaceDirectory output tmp
|
||||||
case pandocRes of
|
case pandocRes of
|
||||||
Left err -> exit err
|
Left err -> exit err
|
||||||
Right texFile -> do
|
Right texFile -> do
|
||||||
|
|
|
@ -309,7 +309,10 @@ options =
|
||||||
|
|
||||||
, Option "" ["xetex"]
|
, Option "" ["xetex"]
|
||||||
(NoArg
|
(NoArg
|
||||||
(\opt -> return opt { optXeTeX = True }))
|
(\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"
|
"" -- "Format latex for processing by XeTeX"
|
||||||
|
|
||||||
, Option "" ["chapters"]
|
, Option "" ["chapters"]
|
||||||
|
@ -675,7 +678,6 @@ main = do
|
||||||
, optSectionDivs = sectionDivs
|
, optSectionDivs = sectionDivs
|
||||||
, optIncremental = incremental
|
, optIncremental = incremental
|
||||||
, optOffline = offline
|
, optOffline = offline
|
||||||
, optXeTeX = xetex
|
|
||||||
, optSmart = smart
|
, optSmart = smart
|
||||||
, optHtml5 = html5
|
, optHtml5 = html5
|
||||||
, optChapters = chapters
|
, optChapters = chapters
|
||||||
|
@ -786,7 +788,8 @@ main = do
|
||||||
stateIndentedCodeClasses = codeBlockClasses,
|
stateIndentedCodeClasses = codeBlockClasses,
|
||||||
stateApplyMacros = writerName' `notElem` ["latex", "latex+lhs"] }
|
stateApplyMacros = writerName' `notElem` ["latex", "latex+lhs"] }
|
||||||
|
|
||||||
let writerOptions = WriterOptions { writerStandalone = standalone',
|
let writerOptions = defaultWriterOptions
|
||||||
|
{ writerStandalone = standalone',
|
||||||
writerTemplate = if null template
|
writerTemplate = if null template
|
||||||
then defaultTemplate
|
then defaultTemplate
|
||||||
else template,
|
else template,
|
||||||
|
@ -798,7 +801,6 @@ main = do
|
||||||
writerHTMLMathMethod = mathMethod,
|
writerHTMLMathMethod = mathMethod,
|
||||||
writerSlideVariant = slideVariant,
|
writerSlideVariant = slideVariant,
|
||||||
writerIncremental = incremental,
|
writerIncremental = incremental,
|
||||||
writerXeTeX = xetex,
|
|
||||||
writerCiteMethod = citeMethod,
|
writerCiteMethod = citeMethod,
|
||||||
writerBiblioFiles = reffiles,
|
writerBiblioFiles = reffiles,
|
||||||
writerIgnoreNotes = False,
|
writerIgnoreNotes = False,
|
||||||
|
|
Loading…
Reference in a new issue