aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2018-04-09 09:49:09 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2018-04-09 09:49:09 -0700
commit72878adc63f6a1e5178734aab499c3cd10df6016 (patch)
tree425649765eb1aedd0a54941a1833c230103d4d7c /src/Text/Pandoc
parent52803e2960c3520f8b2159f9076cb454c03988f8 (diff)
downloadpandoc-72878adc63f6a1e5178734aab499c3cd10df6016.tar.gz
PDF: Use withTempDir in html2pdf.
This is intended to help with #4524, a problem on Windows where using weasyprint led to a blank PDF.
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r--src/Text/Pandoc/PDF.hs77
1 files changed, 39 insertions, 38 deletions
diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs
index d73126f44..bb575d13f 100644
--- a/src/Text/Pandoc/PDF.hs
+++ b/src/Text/Pandoc/PDF.hs
@@ -51,7 +51,7 @@ import System.Environment
import System.Exit (ExitCode (..))
import System.FilePath
import System.IO (stdout)
-import System.IO.Temp (withTempDirectory, withTempFile)
+import System.IO.Temp (withTempDirectory)
#if MIN_VERSION_base(4,8,3)
import System.IO.Error (IOError, isDoesNotExistError)
#else
@@ -368,43 +368,44 @@ html2pdf verbosity program args htmlSource = do
baseTag = TagOpen "base"
[("href", T.pack cwd <> T.singleton pathSeparator)] : [TagText "\n"]
source = renderTags $ hd ++ baseTag ++ tl
- pdfFile <- withTempFile "." "html2pdf.pdf" $ \fp _ -> return fp
- let pdfFileArgName = ["-o" | program == "prince"]
- let programArgs = args ++ ["-"] ++ pdfFileArgName ++ [pdfFile]
- env' <- getEnvironment
- when (verbosity >= INFO) $ do
- putStrLn "[makePDF] Command line:"
- putStrLn $ program ++ " " ++ unwords (map show programArgs)
- putStr "\n"
- putStrLn "[makePDF] Environment:"
- mapM_ print env'
- putStr "\n"
- putStrLn "[makePDF] Contents of intermediate HTML:"
- TextIO.putStr source
- putStr "\n"
- (exit, out) <- E.catch
- (pipeProcess (Just env') program programArgs $ BL.fromStrict $ UTF8.fromText source)
- (\(e :: IOError) -> if isDoesNotExistError e
- then E.throwIO $
- PandocPDFProgramNotFoundError program
- else E.throwIO e)
- when (verbosity >= INFO) $ do
- BL.hPutStr stdout out
- putStr "\n"
- pdfExists <- doesFileExist pdfFile
- mbPdf <- if pdfExists
- -- 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 do
- res <- (Just . BL.fromChunks . (:[])) `fmap` BS.readFile pdfFile
- removeFile pdfFile
- return res
- else return Nothing
- return $ case (exit, mbPdf) of
- (ExitFailure _, _) -> Left out
- (ExitSuccess, Nothing) -> Left ""
- (ExitSuccess, Just pdf) -> Right pdf
+ withTempDir "html2pdf.pdf" $ \tmpdir -> do
+ let pdfFile = tmpdir </> "out.pdf"
+ let pdfFileArgName = ["-o" | program == "prince"]
+ let programArgs = args ++ ["-"] ++ pdfFileArgName ++ [pdfFile]
+ env' <- getEnvironment
+ when (verbosity >= INFO) $ do
+ putStrLn "[makePDF] Command line:"
+ putStrLn $ program ++ " " ++ unwords (map show programArgs)
+ putStr "\n"
+ putStrLn "[makePDF] Environment:"
+ mapM_ print env'
+ putStr "\n"
+ putStrLn "[makePDF] Contents of intermediate HTML:"
+ TextIO.putStr source
+ putStr "\n"
+ (exit, out) <- E.catch
+ (pipeProcess (Just env') program programArgs $ BL.fromStrict $ UTF8.fromText source)
+ (\(e :: IOError) -> if isDoesNotExistError e
+ then E.throwIO $
+ PandocPDFProgramNotFoundError program
+ else E.throwIO e)
+ when (verbosity >= INFO) $ do
+ BL.hPutStr stdout out
+ putStr "\n"
+ pdfExists <- doesFileExist pdfFile
+ mbPdf <- if pdfExists
+ -- 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 do
+ res <- (Just . BL.fromChunks . (:[])) `fmap` BS.readFile pdfFile
+ removeFile pdfFile
+ return res
+ else return Nothing
+ return $ case (exit, mbPdf) of
+ (ExitFailure _, _) -> Left out
+ (ExitSuccess, Nothing) -> Left ""
+ (ExitSuccess, Just pdf) -> Right pdf
context2pdf :: Verbosity -- ^ Verbosity level
-> FilePath -- ^ temp directory for output