markdown2pdf.hs: When --toc, run latex an extra time.
Previously --toc was broken. git-svn-id: https://pandoc.googlecode.com/svn/trunk@1780 788f1e2b-df1e-0410-8736-df70ead52e1b
This commit is contained in:
parent
1e0c8e21cf
commit
77396199e7
1 changed files with 4 additions and 2 deletions
|
@ -3,7 +3,7 @@ module Main where
|
|||
import Data.List (isInfixOf, intercalate, isPrefixOf)
|
||||
import Data.Maybe (isNothing)
|
||||
|
||||
import Control.Monad (unless, guard)
|
||||
import Control.Monad (unless, guard, when)
|
||||
import Control.Exception (tryJust, bracket)
|
||||
|
||||
import System.IO (stderr)
|
||||
|
@ -91,7 +91,7 @@ checkLatex txt = (err , bib, ref, unlines $! msgs ++ tips)
|
|||
ref = any (oneOf ["Warning: Reference"
|
||||
,"Warning: Label"
|
||||
,"Warning: There were undefined references"
|
||||
,"--toc", "--table-of-contents"]) msgs
|
||||
]) msgs
|
||||
|
||||
checkPackages :: [String] -> [String]
|
||||
checkPackages = concatMap chks
|
||||
|
@ -201,6 +201,8 @@ main = bracket
|
|||
Left err -> exit err
|
||||
Right texFile -> do
|
||||
-- run pdflatex
|
||||
when ("--toc" `elem` opts || "--table-of-contents" `elem` opts) $
|
||||
runLatex latexProgram texFile >> return () -- toc requires extra run
|
||||
latexRes <- runLatex latexProgram texFile
|
||||
case latexRes of
|
||||
Left err -> exit err
|
||||
|
|
Loading…
Add table
Reference in a new issue