parent
7407b83ced
commit
ad9e4cde9d
4 changed files with 29 additions and 8 deletions
5
README
5
README
|
@ -655,6 +655,11 @@ Options affecting specific writers
|
|||
The default is `pdflatex`. If the engine is not in your PATH,
|
||||
the full path of the engine may be specified here.
|
||||
|
||||
`--latex-engine-opt=`*STRING*
|
||||
: Use the given string as a command-line argument to the `latex-engine`.
|
||||
If used multiple times, the arguments are provided with spaces between
|
||||
them. Note that no check for duplicate options is done.
|
||||
|
||||
Citation rendering
|
||||
------------------
|
||||
|
||||
|
|
14
pandoc.hs
14
pandoc.hs
|
@ -198,6 +198,7 @@ data Opt = Opt
|
|||
, optCiteMethod :: CiteMethod -- ^ Method to output cites
|
||||
, optListings :: Bool -- ^ Use listings package for code blocks
|
||||
, optLaTeXEngine :: String -- ^ Program to use for latex -> pdf
|
||||
, optLaTeXEngineArgs :: [String] -- ^ Flags to pass to the latex-engine
|
||||
, 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
|
||||
|
@ -259,6 +260,7 @@ defaultOpts = Opt
|
|||
, optCiteMethod = Citeproc
|
||||
, optListings = False
|
||||
, optLaTeXEngine = "pdflatex"
|
||||
, optLaTeXEngineArgs = []
|
||||
, optSlideLevel = Nothing
|
||||
, optSetextHeaders = True
|
||||
, optAscii = False
|
||||
|
@ -734,6 +736,14 @@ options =
|
|||
"PROGRAM")
|
||||
"" -- "Name of latex program to use in generating PDF"
|
||||
|
||||
, Option "" ["latex-engine-opt"]
|
||||
(ReqArg
|
||||
(\arg opt -> do
|
||||
let oldArgs = optLaTeXEngineArgs opt
|
||||
return opt { optLaTeXEngineArgs = arg : oldArgs })
|
||||
"STRING")
|
||||
"" -- "Flags to pass to the LaTeX engine, all instances of this option are accumulated and used"
|
||||
|
||||
, Option "" ["bibliography"]
|
||||
(ReqArg
|
||||
(\arg opt -> return opt{ optMetadata = addMetadata
|
||||
|
@ -1080,6 +1090,7 @@ main = do
|
|||
, optCiteMethod = citeMethod
|
||||
, optListings = listings
|
||||
, optLaTeXEngine = latexEngine
|
||||
, optLaTeXEngineArgs = latexEngineArgs
|
||||
, optSlideLevel = slideLevel
|
||||
, optSetextHeaders = setextHeaders
|
||||
, optAscii = ascii
|
||||
|
@ -1312,7 +1323,8 @@ main = do
|
|||
writerReferenceODT = referenceODT,
|
||||
writerReferenceDocx = referenceDocx,
|
||||
writerMediaBag = media,
|
||||
writerVerbose = verbose
|
||||
writerVerbose = verbose,
|
||||
writerLaTeXArgs = latexEngineArgs
|
||||
}
|
||||
|
||||
|
||||
|
|
|
@ -324,6 +324,7 @@ data WriterOptions = WriterOptions
|
|||
, writerReferenceDocx :: Maybe FilePath -- ^ Path to reference DOCX if specified
|
||||
, writerMediaBag :: MediaBag -- ^ Media collected by docx or epub reader
|
||||
, writerVerbose :: Bool -- ^ Verbose debugging output
|
||||
, writerLaTeXArgs :: [String] -- ^ Flags to pass to latex-engine
|
||||
} deriving Show
|
||||
|
||||
instance Default WriterOptions where
|
||||
|
@ -368,6 +369,7 @@ instance Default WriterOptions where
|
|||
, writerReferenceDocx = Nothing
|
||||
, writerMediaBag = mempty
|
||||
, writerVerbose = False
|
||||
, writerLaTeXArgs = []
|
||||
}
|
||||
|
||||
-- | Returns True if the given extension is enabled.
|
||||
|
|
|
@ -71,7 +71,8 @@ makePDF :: String -- ^ pdf creator (pdflatex, lualatex, xelatex)
|
|||
makePDF program writer opts doc = withTempDir "tex2pdf." $ \tmpdir -> do
|
||||
doc' <- handleImages opts tmpdir doc
|
||||
let source = writer opts doc'
|
||||
tex2pdf' (writerVerbose opts) tmpdir program source
|
||||
args = writerLaTeXArgs opts
|
||||
tex2pdf' (writerVerbose opts) args tmpdir program source
|
||||
|
||||
handleImages :: WriterOptions
|
||||
-> FilePath -- ^ temp dir to store images
|
||||
|
@ -132,15 +133,16 @@ convertImage tmpdir fname =
|
|||
doNothing = return (Right fname)
|
||||
|
||||
tex2pdf' :: Bool -- ^ Verbose output
|
||||
-> [String] -- ^ Arguments to the latex-engine
|
||||
-> FilePath -- ^ temp directory for output
|
||||
-> String -- ^ tex program
|
||||
-> String -- ^ tex source
|
||||
-> IO (Either ByteString ByteString)
|
||||
tex2pdf' verbose tmpDir program source = do
|
||||
tex2pdf' verbose args tmpDir program source = do
|
||||
let numruns = if "\\tableofcontents" `isInfixOf` source
|
||||
then 3 -- to get page numbers
|
||||
else 2 -- 1 run won't give you PDF bookmarks
|
||||
(exit, log', mbPdf) <- runTeXProgram verbose program 1 numruns tmpDir source
|
||||
(exit, log', mbPdf) <- runTeXProgram verbose program args 1 numruns tmpDir source
|
||||
case (exit, mbPdf) of
|
||||
(ExitFailure _, _) -> do
|
||||
let logmsg = extractMsg log'
|
||||
|
@ -173,9 +175,9 @@ extractMsg log' = do
|
|||
-- Run a TeX program on an input bytestring and return (exit code,
|
||||
-- contents of stdout, contents of produced PDF if any). Rerun
|
||||
-- a fixed number of times to resolve references.
|
||||
runTeXProgram :: Bool -> String -> Int -> Int -> FilePath -> String
|
||||
runTeXProgram :: Bool -> String -> [String] -> Int -> Int -> FilePath -> String
|
||||
-> IO (ExitCode, ByteString, Maybe ByteString)
|
||||
runTeXProgram verbose program runNumber numRuns tmpDir source = do
|
||||
runTeXProgram verbose program args runNumber numRuns tmpDir source = do
|
||||
let file = tmpDir </> "input.tex"
|
||||
exists <- doesFileExist file
|
||||
unless exists $ UTF8.writeFile file source
|
||||
|
@ -188,7 +190,7 @@ runTeXProgram verbose program runNumber numRuns tmpDir source = do
|
|||
let file' = file
|
||||
#endif
|
||||
let programArgs = ["-halt-on-error", "-interaction", "nonstopmode",
|
||||
"-output-directory", tmpDir', file']
|
||||
"-output-directory", tmpDir', file'] ++ args
|
||||
env' <- getEnvironment
|
||||
let sep = searchPathSeparator:[]
|
||||
let texinputs = maybe (tmpDir' ++ sep) ((tmpDir' ++ sep) ++)
|
||||
|
@ -212,7 +214,7 @@ runTeXProgram verbose program runNumber numRuns tmpDir source = do
|
|||
B.hPutStr stderr err
|
||||
putStr "\n"
|
||||
if runNumber <= numRuns
|
||||
then runTeXProgram verbose program (runNumber + 1) numRuns tmpDir source
|
||||
then runTeXProgram verbose program args (runNumber + 1) numRuns tmpDir source
|
||||
else do
|
||||
let pdfFile = replaceDirectory (replaceExtension file ".pdf") tmpDir
|
||||
pdfExists <- doesFileExist pdfFile
|
||||
|
|
Loading…
Add table
Reference in a new issue