aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2019-08-31 09:18:21 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2019-08-31 09:18:21 -0700
commit716483e03aca2a9afb6ac777575d8a2f8da878b7 (patch)
treeae28dc8aa82e467472cf537a0ee69eec13172ccc /src/Text/Pandoc
parentfba1296fd1ac6427d19f537c4b8afda9fc60ac75 (diff)
downloadpandoc-716483e03aca2a9afb6ac777575d8a2f8da878b7.tar.gz
html2pdf: ensure temp file is deleted...
even if the pdf program is not found. Closes #5720.
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r--src/Text/Pandoc/PDF.hs69
1 files changed, 35 insertions, 34 deletions
diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs
index 6b5dbfb47..ee2208fd1 100644
--- a/src/Text/Pandoc/PDF.hs
+++ b/src/Text/Pandoc/PDF.hs
@@ -33,7 +33,7 @@ import System.Directory
import System.Environment
import System.Exit (ExitCode (..))
import System.FilePath
-import System.IO (stdout)
+import System.IO (stdout, hClose)
import System.IO.Temp (withSystemTempDirectory, withTempDirectory,
withTempFile)
import System.IO.Error (IOError, isDoesNotExistError)
@@ -418,39 +418,40 @@ html2pdf verbosity program args source = do
-- write HTML to temp file so we don't have to rewrite
-- all links in `a`, `img`, `style`, `script`, etc. tags,
-- and piping to weasyprint didn't work on Windows either.
- file <- withTempFile "." "html2pdf.html" $ \fp _ -> return fp
- pdfFile <- withTempFile "." "html2pdf.pdf" $ \fp _ -> return fp
- BS.writeFile file $ UTF8.fromText source
- let pdfFileArgName = ["-o" | takeBaseName program == "prince"]
- let programArgs = args ++ [file] ++ pdfFileArgName ++ [pdfFile]
- env' <- getEnvironment
- when (verbosity >= INFO) $
- UTF8.readFile file >>=
- showVerboseInfo Nothing program programArgs env'
- (exit, out) <- E.catch
- (pipeProcess (Just env') program programArgs BL.empty)
- (\(e :: IOError) -> if isDoesNotExistError e
- then E.throwIO $
- PandocPDFProgramNotFoundError program
- else E.throwIO e)
- removeFile file
- 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
+ withTempFile "." "html2pdf.html" $ \file h1 ->
+ withTempFile "." "html2pdf.pdf" $ \pdfFile h2 -> do
+ hClose h1
+ hClose h2
+ BS.writeFile file $ UTF8.fromText source
+ let pdfFileArgName = ["-o" | takeBaseName program == "prince"]
+ let programArgs = args ++ [file] ++ pdfFileArgName ++ [pdfFile]
+ env' <- getEnvironment
+ when (verbosity >= INFO) $
+ UTF8.readFile file >>=
+ showVerboseInfo Nothing program programArgs env'
+ (exit, out) <- E.catch
+ (pipeProcess (Just env') program programArgs BL.empty)
+ (\(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 . (:[]) <$>
+ BS.readFile 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
-> String -- ^ "context" or path to it