aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJohn MacFarlane <fiddlosopher@gmail.com>2012-01-20 21:36:04 -0800
committerJohn MacFarlane <fiddlosopher@gmail.com>2012-01-20 21:36:04 -0800
commitd7b67f48cd1b0b33c8777f9b5bb1b6f5608f308f (patch)
treece653d6ee49f1047f843df8c764134f92ab66708
parent1d615908c2c346c034aa63f572f5f112638d8ff4 (diff)
downloadpandoc-d7b67f48cd1b0b33c8777f9b5bb1b6f5608f308f.tar.gz
PDF: Use string instead of special TeXProgram type.
-rw-r--r--src/Text/Pandoc/PDF.hs22
-rw-r--r--src/pandoc.hs4
2 files changed, 8 insertions, 18 deletions
diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs
index d547835b5..b3d0fcbb8 100644
--- a/src/Text/Pandoc/PDF.hs
+++ b/src/Text/Pandoc/PDF.hs
@@ -28,10 +28,9 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
Conversion of LaTeX documents to PDF.
-}
-module Text.Pandoc.PDF ( TeXProgram(..), tex2pdf ) where
+module Text.Pandoc.PDF ( tex2pdf ) where
import System.IO.Temp
-import Data.Char (toLower)
import Data.ByteString.Lazy (ByteString)
import qualified Data.ByteString.Lazy as B
import qualified Data.ByteString.Lazy.Char8 as BC
@@ -44,14 +43,14 @@ import System.IO (hClose)
import Control.Concurrent (putMVar, takeMVar, newEmptyMVar, forkIO)
import Text.Pandoc.UTF8 as UTF8
-tex2pdf :: TeXProgram
- -> String -- ^ latex source
+tex2pdf :: String -- ^ tex program (pdflatex, lualatex, xelatex)
+ -> String -- ^ latex source
-> IO (Either ByteString ByteString)
tex2pdf program source = withSystemTempDirectory "tex2pdf" $ \tmpdir ->
tex2pdf' tmpdir program source
tex2pdf' :: FilePath -- ^ temp directory for output
- -> TeXProgram
+ -> String -- ^ tex program
-> String -- ^ tex source
-> IO (Either ByteString ByteString)
tex2pdf' tmpDir program source = do
@@ -63,14 +62,6 @@ tex2pdf' tmpDir program source = do
(ExitSuccess, Nothing) -> return $ Left msg
(ExitSuccess, Just pdf) -> return $ Right pdf
-data TeXProgram = PDFLaTeX
- | XeLaTeX
- | LuaLaTeX
- | XeTeX
- | LuaTeX
- | PDFTeX
- deriving (Show, Read)
-
(<>) :: ByteString -> ByteString -> ByteString
(<>) = B.append
@@ -102,16 +93,15 @@ hasUndefinedRefs = or . map parseLine . BC.lines
-- Run a TeX program on an input bytestring and return (exit code,
-- contents of stdout, contents of produced PDF if any). Rerun
-- latex as needed to resolve references, but don't run bibtex/biber.
-runTeXProgram :: TeXProgram -> Int -> FilePath -> String
+runTeXProgram :: String -> Int -> FilePath -> String
-> IO (ExitCode, ByteString, Maybe ByteString)
runTeXProgram program runsLeft tmpDir source = do
- let programName = map toLower (show program)
withTempFile tmpDir "tex2pdf" $ \file h -> do
UTF8.hPutStr h source
hClose h
let programArgs = ["-halt-on-error", "-interaction", "nonstopmode",
"-output-directory", tmpDir, file]
- (exit, out, _err) <- readCommand programName programArgs
+ (exit, out, _err) <- readCommand program programArgs
removeFile file
let pdfFile = replaceDirectory (replaceExtension file ".pdf") tmpDir
pdfExists <- doesFileExist pdfFile
diff --git a/src/pandoc.hs b/src/pandoc.hs
index 506ed703d..a6bae7224 100644
--- a/src/pandoc.hs
+++ b/src/pandoc.hs
@@ -30,7 +30,7 @@ writers.
-}
module Main where
import Text.Pandoc
-import Text.Pandoc.PDF (tex2pdf, TeXProgram(..))
+import Text.Pandoc.PDF (tex2pdf)
import Text.Pandoc.Shared ( tabFilter, ObfuscationMethod (..), readDataFile,
headerShift, findDataFile, normalize )
import Text.Pandoc.SelfContained ( makeSelfContained )
@@ -972,7 +972,7 @@ main = do
| writerName' == "docx" ->
writeDocx referenceDocx writerOptions doc2 >>= writeBinary
| writerName' == "pdf" ->
- do res <- tex2pdf PDFLaTeX $ writeLaTeX writerOptions doc2
+ do res <- tex2pdf "pdflatex" $ writeLaTeX writerOptions doc2
case res of
Right pdf -> writeBinary pdf
Left err' -> B.hPutStr stderr err'