aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/PDF.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/PDF.hs')
-rw-r--r--src/Text/Pandoc/PDF.hs135
1 files changed, 88 insertions, 47 deletions
diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs
index 3227fd0bd..bd55c565f 100644
--- a/src/Text/Pandoc/PDF.hs
+++ b/src/Text/Pandoc/PDF.hs
@@ -1,6 +1,6 @@
{-# LANGUAGE OverloadedStrings, CPP #-}
{-
-Copyright (C) 2012 John MacFarlane <jgm@berkeley.edu>
+Copyright (C) 2012-2014 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
@@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
{- |
Module : Text.Pandoc.PDF
- Copyright : Copyright (C) 2012 John MacFarlane
+ Copyright : Copyright (C) 2012-2014 John MacFarlane
License : GNU GPL, version 2 or above
Maintainer : John MacFarlane <jgm@berkeley.edu>
@@ -28,22 +28,32 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
Conversion of LaTeX documents to PDF.
-}
-module Text.Pandoc.PDF ( tex2pdf ) where
+module Text.Pandoc.PDF ( makePDF ) where
import System.IO.Temp
import Data.ByteString.Lazy (ByteString)
import qualified Data.ByteString.Lazy as B
import qualified Data.ByteString.Lazy.Char8 as BC
+import qualified Data.ByteString as BS
import System.Exit (ExitCode (..))
import System.FilePath
import System.Directory
-import System.Process
-import Control.Exception (evaluate)
-import System.IO (hClose)
-import Control.Concurrent (putMVar, takeMVar, newEmptyMVar, forkIO)
-import Text.Pandoc.UTF8 as UTF8
+import Data.Digest.Pure.SHA (showDigest, sha1)
+import System.Environment
import Control.Monad (unless)
import Data.List (isInfixOf)
+import Data.Maybe (fromMaybe)
+import qualified Text.Pandoc.UTF8 as UTF8
+import Text.Pandoc.Definition
+import Text.Pandoc.Walk (walkM)
+import Text.Pandoc.Shared (fetchItem, warn)
+import Text.Pandoc.Options (WriterOptions(..))
+import Text.Pandoc.MIME (extensionFromMimeType)
+import Text.Pandoc.Process (pipeProcess)
+import qualified Data.ByteString.Lazy as BL
+#ifdef _WINDOWS
+import Data.List (intercalate)
+#endif
withTempDir :: String -> (FilePath -> IO a) -> IO a
withTempDir =
@@ -53,12 +63,50 @@ withTempDir =
withSystemTempDirectory
#endif
-tex2pdf :: String -- ^ tex program (pdflatex, lualatex, xelatex)
- -> String -- ^ latex source
+#ifdef _WINDOWS
+changePathSeparators :: FilePath -> FilePath
+changePathSeparators = intercalate "/" . splitDirectories
+#endif
+
+makePDF :: String -- ^ pdf creator (pdflatex, lualatex, xelatex)
+ -> (WriterOptions -> Pandoc -> String) -- ^ writer
+ -> WriterOptions -- ^ options
+ -> Pandoc -- ^ document
-> IO (Either ByteString ByteString)
-tex2pdf program source = withTempDir "tex2pdf." $ \tmpdir ->
+makePDF program writer opts doc = withTempDir "tex2pdf." $ \tmpdir -> do
+ doc' <- handleImages (writerSourceURL opts) tmpdir doc
+ let source = writer opts doc'
tex2pdf' tmpdir program source
+handleImages :: Maybe String -- ^ source base URL
+ -> FilePath -- ^ temp dir to store images
+ -> Pandoc -- ^ document
+ -> IO Pandoc
+handleImages baseURL tmpdir = walkM (handleImage' baseURL tmpdir)
+
+handleImage' :: Maybe String
+ -> FilePath
+ -> Inline
+ -> IO Inline
+handleImage' baseURL tmpdir (Image ils (src,tit)) = do
+ exists <- doesFileExist src
+ if exists
+ then return $ Image ils (src,tit)
+ else do
+ res <- fetchItem baseURL src
+ case res of
+ Right (contents, Just mime) -> do
+ let ext = fromMaybe (takeExtension src) $
+ extensionFromMimeType mime
+ let basename = showDigest $ sha1 $ BL.fromChunks [contents]
+ let fname = tmpdir </> basename <.> ext
+ BS.writeFile fname contents
+ return $ Image ils (fname,tit)
+ _ -> do
+ warn $ "Could not find image `" ++ src ++ "', skipping..."
+ return $ Image ils (src,tit)
+handleImage' _ _ x = return x
+
tex2pdf' :: FilePath -- ^ temp directory for output
-> String -- ^ tex program
-> String -- ^ tex source
@@ -68,11 +116,16 @@ tex2pdf' tmpDir program source = do
then 3 -- to get page numbers
else 2 -- 1 run won't give you PDF bookmarks
(exit, log', mbPdf) <- runTeXProgram program numruns tmpDir source
- let msg = "Error producing PDF from TeX source."
case (exit, mbPdf) of
- (ExitFailure _, _) -> return $ Left $
- msg <> "\n" <> extractMsg log'
- (ExitSuccess, Nothing) -> return $ Left msg
+ (ExitFailure _, _) -> do
+ let logmsg = extractMsg log'
+ let extramsg =
+ case logmsg of
+ x | "! Package inputenc Error" `BC.isPrefixOf` x ->
+ "\nTry running pandoc with --latex-engine=xelatex."
+ _ -> ""
+ return $ Left $ logmsg <> extramsg
+ (ExitSuccess, Nothing) -> return $ Left ""
(ExitSuccess, Just pdf) -> return $ Right pdf
(<>) :: ByteString -> ByteString -> ByteString
@@ -100,45 +153,33 @@ runTeXProgram program runsLeft tmpDir source = do
let file = tmpDir </> "input.tex"
exists <- doesFileExist file
unless exists $ UTF8.writeFile file source
+#ifdef _WINDOWS
+ -- note: we want / even on Windows, for TexLive
+ let tmpDir' = changePathSeparators tmpDir
+ let file' = changePathSeparators file
+#else
+ let tmpDir' = tmpDir
+ let file' = file
+#endif
let programArgs = ["-halt-on-error", "-interaction", "nonstopmode",
- "-output-directory", tmpDir, file]
- (exit, out, err) <- readCommand program programArgs
+ "-output-directory", tmpDir', file']
+ env' <- getEnvironment
+ let sep = searchPathSeparator:[]
+ let texinputs = maybe (tmpDir' ++ sep) ((tmpDir' ++ sep) ++)
+ $ lookup "TEXINPUTS" env'
+ let env'' = ("TEXINPUTS", texinputs) :
+ [(k,v) | (k,v) <- env', k /= "TEXINPUTS"]
+ (exit, out, err) <- pipeProcess (Just env'') program programArgs BL.empty
if runsLeft > 1
then runTeXProgram program (runsLeft - 1) tmpDir source
else do
let pdfFile = replaceDirectory (replaceExtension file ".pdf") tmpDir
pdfExists <- doesFileExist pdfFile
pdf <- if pdfExists
- then Just `fmap` B.readFile pdfFile
+ -- We read PDF as a strict bytestring to make sure that the
+ -- temp directory is removed on Windows.
+ -- See https://github.com/jgm/pandoc/issues/1192.
+ then (Just . B.fromChunks . (:[])) `fmap` BS.readFile pdfFile
else return Nothing
return (exit, out <> err, pdf)
--- utility functions
-
--- Run a command and return exitcode, contents of stdout, and
--- contents of stderr. (Based on
--- 'readProcessWithExitCode' from 'System.Process'.)
-readCommand :: FilePath -- ^ command to run
- -> [String] -- ^ any arguments
- -> IO (ExitCode,ByteString,ByteString) -- ^ exit, stdout, stderr
-readCommand cmd args = do
- (Just inh, Just outh, Just errh, pid) <-
- createProcess (proc cmd args){ std_in = CreatePipe,
- std_out = CreatePipe,
- std_err = CreatePipe }
- outMVar <- newEmptyMVar
- -- fork off a thread to start consuming stdout
- out <- B.hGetContents outh
- _ <- forkIO $ evaluate (B.length out) >> putMVar outMVar ()
- -- fork off a thread to start consuming stderr
- err <- B.hGetContents errh
- _ <- forkIO $ evaluate (B.length err) >> putMVar outMVar ()
- -- now write and flush any input
- hClose inh -- done with stdin
- -- wait on the output
- takeMVar outMVar
- takeMVar outMVar
- hClose outh
- -- wait on the process
- ex <- waitForProcess pid
- return (ex, out, err)