1{-# LANGUAGE CPP                 #-}
2{-# LANGUAGE LambdaCase          #-}
3{-# LANGUAGE OverloadedStrings   #-}
4{-# LANGUAGE ScopedTypeVariables #-}
5{- |
6   Module      : Text.Pandoc.PDF
7   Copyright   : Copyright (C) 2012-2021 John MacFarlane
8   License     : GNU GPL, version 2 or above
9
10   Maintainer  : John MacFarlane <jgm@berkeley.edu>
11   Stability   : alpha
12   Portability : portable
13
14Conversion of LaTeX documents to PDF.
15-}
16module Text.Pandoc.PDF ( makePDF ) where
17
18import qualified Codec.Picture as JP
19import qualified Control.Exception as E
20import Control.Monad (when)
21import Control.Monad.Trans (MonadIO (..))
22import qualified Data.ByteString as BS
23import Data.ByteString.Lazy (ByteString)
24import qualified Data.ByteString.Lazy as BL
25import qualified Data.ByteString.Lazy.Char8 as BC
26import Data.Maybe (fromMaybe)
27import Data.Text (Text)
28import qualified Data.Text as T
29import qualified Data.Text.Lazy as TL
30import Data.Text.Lazy.Encoding (decodeUtf8')
31import Text.Printf (printf)
32import Data.Char (ord, isAscii, isSpace)
33import System.Directory
34import System.Environment
35import System.Exit (ExitCode (..))
36import System.FilePath
37import System.IO (stderr, hClose)
38import System.IO.Temp (withSystemTempDirectory, withTempDirectory,
39                       withTempFile)
40import qualified System.IO.Error as IE
41import Text.DocLayout (literal)
42import Text.Pandoc.Definition
43import Text.Pandoc.Error (PandocError (PandocPDFProgramNotFoundError))
44import Text.Pandoc.MIME (getMimeType)
45import Text.Pandoc.Options (HTMLMathMethod (..), WriterOptions (..))
46import Text.Pandoc.Extensions (disableExtension, Extension(Ext_smart))
47import Text.Pandoc.Process (pipeProcess)
48import System.Process (readProcessWithExitCode)
49import Text.Pandoc.Shared (inDirectory, stringify, tshow)
50import qualified Text.Pandoc.UTF8 as UTF8
51import Text.Pandoc.Walk (walkM)
52import Text.Pandoc.Writers.Shared (getField, metaToContext)
53#ifdef _WINDOWS
54import Data.List (intercalate)
55#endif
56import Data.List (isPrefixOf, find)
57import Text.Pandoc.Class.PandocIO (PandocIO, extractMedia, runIOorExplode)
58import Text.Pandoc.Class.PandocMonad (fillMediaBag, getCommonState, getVerbosity,
59                                      putCommonState, report, setVerbosity)
60import Text.Pandoc.Logging
61
62#ifdef _WINDOWS
63changePathSeparators :: FilePath -> FilePath
64changePathSeparators =
65  -- We filter out backslashes because an initial `C:\` gets
66  -- retained by `splitDirectories`, see #6173:
67  intercalate "/" . map (filter (/='\\')) . splitDirectories
68#endif
69
70makePDF :: String              -- ^ pdf creator (pdflatex, lualatex, xelatex,
71                               -- wkhtmltopdf, weasyprint, prince, context, pdfroff,
72                               -- or path to executable)
73        -> [String]            -- ^ arguments to pass to pdf creator
74        -> (WriterOptions -> Pandoc -> PandocIO Text)  -- ^ writer
75        -> WriterOptions       -- ^ options
76        -> Pandoc              -- ^ document
77        -> PandocIO (Either ByteString ByteString)
78makePDF program pdfargs writer opts doc =
79  case takeBaseName program of
80    "wkhtmltopdf" -> makeWithWkhtmltopdf program pdfargs writer opts doc
81    prog | prog `elem` ["weasyprint", "prince"] -> do
82      source <- writer opts doc
83      verbosity <- getVerbosity
84      liftIO $ html2pdf verbosity program pdfargs source
85    "pdfroff" -> do
86      source <- writer opts doc
87      let args   = ["-ms", "-mpdfmark", "-mspdf",
88                    "-e", "-t", "-k", "-KUTF-8", "-i"] ++ pdfargs
89      verbosity <- getVerbosity
90      liftIO $ generic2pdf verbosity program args source
91    baseProg -> do
92      commonState <- getCommonState
93      verbosity <- getVerbosity
94      -- latex has trouble with tildes in paths, which
95      -- you find in Windows temp dir paths with longer
96      -- user names (see #777)
97      let withTempDir templ action = do
98            tmp <- getTemporaryDirectory
99            uname <- E.catch
100              (do (ec, sout, _) <- readProcessWithExitCode "uname" ["-o"] ""
101                  if ec == ExitSuccess
102                     then return $ Just $ filter (not . isSpace) sout
103                     else return Nothing)
104              (\(_ :: E.SomeException) -> return Nothing)
105            if '~' `elem` tmp || uname == Just "Cygwin" -- see #5451
106                   then withTempDirectory "." templ action
107                   else withSystemTempDirectory templ action
108      (newCommonState, res) <- liftIO $ withTempDir "tex2pdf." $ \tmpdir' -> do
109#ifdef _WINDOWS
110        -- note:  we want / even on Windows, for TexLive
111        let tmpdir = changePathSeparators tmpdir'
112#else
113        let tmpdir = tmpdir'
114#endif
115        runIOorExplode $ do
116          putCommonState commonState
117          doc' <- handleImages opts tmpdir doc
118          source <- writer opts{ writerExtensions = -- disable use of quote
119                                    -- ligatures to avoid bad ligatures like ?`
120                                    disableExtension Ext_smart
121                                     (writerExtensions opts) } doc'
122          res <- case baseProg of
123            "context" -> context2pdf verbosity program pdfargs tmpdir source
124            "tectonic" -> tectonic2pdf verbosity program pdfargs tmpdir source
125            prog | prog `elem` ["pdflatex", "lualatex", "xelatex", "latexmk"]
126                -> tex2pdf verbosity program pdfargs tmpdir source
127            _ -> return $ Left $ UTF8.fromStringLazy
128                               $ "Unknown program " ++ program
129          cs <- getCommonState
130          return (cs, res)
131      putCommonState newCommonState
132      return res
133
134makeWithWkhtmltopdf :: String              -- ^ wkhtmltopdf or path
135                    -> [String]            -- ^ arguments
136                    -> (WriterOptions -> Pandoc -> PandocIO Text)  -- ^ writer
137                    -> WriterOptions       -- ^ options
138                    -> Pandoc              -- ^ document
139                    -> PandocIO (Either ByteString ByteString)
140makeWithWkhtmltopdf program pdfargs writer opts doc@(Pandoc meta _) = do
141  let mathArgs = case writerHTMLMathMethod opts of
142                 -- with MathJax, wait til all math is rendered:
143                      MathJax _ -> ["--run-script", "MathJax.Hub.Register.StartupHook('End Typeset', function() { window.status = 'mathjax_loaded' });",
144                                    "--window-status", "mathjax_loaded"]
145                      _ -> []
146  meta' <- metaToContext opts
147             (return . literal . stringify)
148             (return . literal . stringify)
149             meta
150  let toArgs (f, mbd) = maybe [] (\d -> ["--" <> f, T.unpack d]) mbd
151  let args   = mathArgs ++ concatMap toArgs
152                 [("page-size", getField "papersize" meta')
153                 ,("title", getField "title" meta')
154                 ,("margin-bottom", Just $ fromMaybe "1.2in"
155                            (getField "margin-bottom" meta'))
156                 ,("margin-top", Just $ fromMaybe "1.25in"
157                            (getField "margin-top" meta'))
158                 ,("margin-right", Just $ fromMaybe "1.25in"
159                            (getField "margin-right" meta'))
160                 ,("margin-left", Just $ fromMaybe "1.25in"
161                            (getField "margin-left" meta'))
162                 ,("footer-html", getField "footer-html" meta')
163                 ,("header-html", getField "header-html" meta')
164                 ] ++ ("--enable-local-file-access" : pdfargs)
165                 -- see #6474
166  source <- writer opts doc
167  verbosity <- getVerbosity
168  liftIO $ html2pdf verbosity program args source
169
170handleImages :: WriterOptions
171             -> FilePath      -- ^ temp dir to store images
172             -> Pandoc        -- ^ document
173             -> PandocIO Pandoc
174handleImages opts tmpdir doc =
175  fillMediaBag doc >>=
176    extractMedia tmpdir >>=
177    walkM (convertImages opts tmpdir)
178
179convertImages :: WriterOptions -> FilePath -> Inline -> PandocIO Inline
180convertImages opts tmpdir (Image attr ils (src, tit)) = do
181  img <- liftIO $ convertImage opts tmpdir $ T.unpack src
182  newPath <-
183    case img of
184      Left e -> do
185        report $ CouldNotConvertImage src e
186        return src
187      Right fp -> return $ T.pack fp
188  return (Image attr ils (newPath, tit))
189convertImages _ _ x = return x
190
191-- Convert formats which do not work well in pdf to png
192convertImage :: WriterOptions -> FilePath -> FilePath
193             -> IO (Either Text FilePath)
194convertImage opts tmpdir fname = do
195  let dpi = show $ writerDpi opts
196  case mime of
197    Just "image/png" -> doNothing
198    Just "image/jpeg" -> doNothing
199    Just "application/pdf" -> doNothing
200    -- Note: eps is converted by pdflatex using epstopdf.pl
201    Just "application/eps" -> doNothing
202    Just "image/svg+xml" -> E.catch (do
203      (exit, _) <- pipeProcess Nothing "rsvg-convert"
204                     ["-f","pdf","-a","--dpi-x",dpi,"--dpi-y",dpi,
205                      "-o",pdfOut,svgIn] BL.empty
206      if exit == ExitSuccess
207         then return $ Right pdfOut
208         else return $ Left "conversion from SVG failed")
209      (\(e :: E.SomeException) -> return $ Left $
210          "check that rsvg-convert is in path.\n" <>
211          tshow e)
212    _ -> JP.readImage fname >>= \case
213               Left e    -> return $ Left $ T.pack e
214               Right img ->
215                 E.catch (Right pngOut <$ JP.savePngImage pngOut img) $
216                     \(e :: E.SomeException) -> return (Left (tshow e))
217  where
218    pngOut = normalise $ replaceDirectory (replaceExtension fname ".png") tmpdir
219    pdfOut = normalise $ replaceDirectory (replaceExtension fname ".pdf") tmpdir
220    svgIn = normalise fname
221    mime = getMimeType fname
222    doNothing = return (Right fname)
223
224tectonic2pdf :: Verbosity                       -- ^ Verbosity level
225             -> String                          -- ^ tex program
226             -> [String]                        -- ^ Arguments to the latex-engine
227             -> FilePath                        -- ^ temp directory for output
228             -> Text                            -- ^ tex source
229             -> PandocIO (Either ByteString ByteString)
230tectonic2pdf verbosity program args tmpDir source = do
231  (exit, log', mbPdf) <- runTectonic verbosity program args tmpDir source
232  case (exit, mbPdf) of
233       (ExitFailure _, _)      -> return $ Left $ extractMsg log'
234       (ExitSuccess, Nothing)  -> return $ Left ""
235       (ExitSuccess, Just pdf) -> do
236          missingCharacterWarnings verbosity log'
237          return $ Right pdf
238
239tex2pdf :: Verbosity                       -- ^ Verbosity level
240        -> String                          -- ^ tex program
241        -> [String]                        -- ^ Arguments to the latex-engine
242        -> FilePath                        -- ^ temp directory for output
243        -> Text                            -- ^ tex source
244        -> PandocIO (Either ByteString ByteString)
245tex2pdf verbosity program args tmpDir source = do
246  let numruns | takeBaseName program == "latexmk"        = 1
247              | "\\tableofcontents" `T.isInfixOf` source = 3  -- to get page numbers
248              | otherwise                                = 2  -- 1 run won't give you PDF bookmarks
249  (exit, log', mbPdf) <- runTeXProgram verbosity program args numruns
250                          tmpDir source
251  case (exit, mbPdf) of
252       (ExitFailure _, _)      -> do
253          let logmsg = extractMsg log'
254          let extramsg =
255                case logmsg of
256                     x | "! Package inputenc Error" `BC.isPrefixOf` x
257                           && program /= "xelatex"
258                       -> "\nTry running pandoc with --pdf-engine=xelatex."
259                     _ -> ""
260          return $ Left $ logmsg <> extramsg
261       (ExitSuccess, Nothing)  -> return $ Left ""
262       (ExitSuccess, Just pdf) -> do
263          missingCharacterWarnings verbosity log'
264          return $ Right pdf
265
266missingCharacterWarnings :: Verbosity -> ByteString -> PandocIO ()
267missingCharacterWarnings verbosity log' = do
268  let ls = BC.lines log'
269  let isMissingCharacterWarning = BC.isPrefixOf "Missing character: "
270  let toCodePoint c
271        | isAscii c   = T.singleton c
272        | otherwise   = T.pack $ c : " (U+" ++ printf "%04X" (ord c) ++ ")"
273  let addCodePoint = T.concatMap toCodePoint
274  let warnings = [ addCodePoint (utf8ToText (BC.drop 19 l))
275                 | l <- ls
276                 , isMissingCharacterWarning l
277                 ]
278  setVerbosity verbosity
279  mapM_ (report . MissingCharacter) warnings
280
281-- parsing output
282
283extractMsg :: ByteString -> ByteString
284extractMsg log' = do
285  let msg'  = dropWhile (not . ("!" `BC.isPrefixOf`)) $ BC.lines log'
286  let (msg'',rest) = break ("l." `BC.isPrefixOf`) msg'
287  let lineno = take 1 rest
288  if null msg'
289     then log'
290     else BC.unlines (msg'' ++ lineno)
291
292extractConTeXtMsg :: ByteString -> ByteString
293extractConTeXtMsg log' = do
294  let msg'  = take 1 $
295              dropWhile (not . ("tex error" `BC.isPrefixOf`)) $ BC.lines log'
296  if null msg'
297     then log'
298     else BC.unlines msg'
299
300-- running tex programs
301
302runTectonic :: Verbosity -> String -> [String] -> FilePath
303              -> Text -> PandocIO (ExitCode, ByteString, Maybe ByteString)
304runTectonic verbosity program args' tmpDir' source = do
305    let getOutDir acc (a:b:xs) = if a `elem` ["-o", "--outdir"]
306                                    then (reverse acc ++ xs, Just b)
307                                    else getOutDir (b:a:acc) xs
308        getOutDir acc xs = (reverse acc ++ xs, Nothing)
309        (args, outDir) = getOutDir [] args'
310        tmpDir = fromMaybe tmpDir' outDir
311    liftIO $ createDirectoryIfMissing True tmpDir
312    -- run tectonic on stdin so it reads \include commands from $PWD instead of a temp directory
313    let sourceBL = BL.fromStrict $ UTF8.fromText source
314    let programArgs = ["--outdir", tmpDir] ++ args ++ ["-"]
315    env <- liftIO getEnvironment
316    when (verbosity >= INFO) $ liftIO $
317      showVerboseInfo (Just tmpDir) program programArgs env
318         (utf8ToText sourceBL)
319    (exit, out) <- liftIO $ E.catch
320      (pipeProcess (Just env) program programArgs sourceBL)
321      (handlePDFProgramNotFound program)
322    when (verbosity >= INFO) $ liftIO $ do
323      UTF8.hPutStrLn stderr "[makePDF] Running"
324      BL.hPutStr stderr out
325      UTF8.hPutStr stderr "\n"
326    let pdfFile = tmpDir ++ "/texput.pdf"
327    (_, pdf) <- getResultingPDF Nothing pdfFile
328    return (exit, out, pdf)
329
330-- read a pdf that has been written to a temporary directory, and optionally read
331-- logs
332getResultingPDF :: Maybe String -> String -> PandocIO (Maybe ByteString, Maybe ByteString)
333getResultingPDF logFile pdfFile = do
334    pdfExists <- liftIO $ doesFileExist pdfFile
335    pdf <- if pdfExists
336              -- We read PDF as a strict bytestring to make sure that the
337              -- temp directory is removed on Windows.
338              -- See https://github.com/jgm/pandoc/issues/1192.
339              then (Just . BL.fromChunks . (:[])) `fmap`
340                   liftIO (BS.readFile pdfFile)
341              else return Nothing
342    -- Note that some things like Missing character warnings
343    -- appear in the log but not on stderr, so we prefer the log:
344    log' <- case logFile of
345              Just logFile' -> do
346                logExists <- liftIO $ doesFileExist logFile'
347                if logExists
348                  then liftIO $ Just <$> BL.readFile logFile'
349                  else return Nothing
350              Nothing -> return Nothing
351    return (log', pdf)
352
353-- Run a TeX program on an input bytestring and return (exit code,
354-- contents of stdout, contents of produced PDF if any).  Rerun
355-- a fixed number of times to resolve references.
356runTeXProgram :: Verbosity -> String -> [String] -> Int -> FilePath
357              -> Text -> PandocIO (ExitCode, ByteString, Maybe ByteString)
358runTeXProgram verbosity program args numRuns tmpDir' source = do
359    let isOutdirArg x = "-outdir=" `isPrefixOf` x ||
360                        "-output-directory=" `isPrefixOf` x
361    let tmpDir =
362          case find isOutdirArg args of
363            Just x  -> drop 1 $ dropWhile (/='=') x
364            Nothing -> tmpDir'
365    liftIO $ createDirectoryIfMissing True tmpDir
366    let file = tmpDir ++ "/input.tex"  -- note: tmpDir has / path separators
367    liftIO $ BS.writeFile file $ UTF8.fromText source
368    let isLatexMk = takeBaseName program == "latexmk"
369        programArgs | isLatexMk = ["-interaction=batchmode", "-halt-on-error", "-pdf",
370                                   "-quiet", "-outdir=" ++ tmpDir] ++ args ++ [file]
371                    | otherwise = ["-halt-on-error", "-interaction", "nonstopmode",
372                                   "-output-directory", tmpDir] ++ args ++ [file]
373    env' <- liftIO getEnvironment
374    let sep = [searchPathSeparator]
375    let texinputs = maybe (tmpDir ++ sep) ((tmpDir ++ sep) ++)
376          $ lookup "TEXINPUTS" env'
377    let env'' = ("TEXINPUTS", texinputs) :
378                ("TEXMFOUTPUT", tmpDir) :
379                  [(k,v) | (k,v) <- env'
380                         , k /= "TEXINPUTS" && k /= "TEXMFOUTPUT"]
381    when (verbosity >= INFO) $ liftIO $
382        UTF8.readFile file >>=
383         showVerboseInfo (Just tmpDir) program programArgs env''
384    let runTeX runNumber = do
385          (exit, out) <- liftIO $ E.catch
386            (pipeProcess (Just env'') program programArgs BL.empty)
387            (handlePDFProgramNotFound program)
388          when (verbosity >= INFO) $ liftIO $ do
389            UTF8.hPutStrLn stderr $ "[makePDF] Run #" <> tshow runNumber
390            BL.hPutStr stderr out
391            UTF8.hPutStr stderr "\n"
392          if runNumber < numRuns
393             then runTeX (runNumber + 1)
394             else do
395               let logFile = replaceExtension file ".log"
396               let pdfFile = replaceExtension file ".pdf"
397               (log', pdf) <- getResultingPDF (Just logFile) pdfFile
398               return (exit, fromMaybe out log', pdf)
399    runTeX 1
400
401generic2pdf :: Verbosity
402            -> String
403            -> [String]
404            -> Text
405            -> IO (Either ByteString ByteString)
406generic2pdf verbosity program args source = do
407  env' <- getEnvironment
408  when (verbosity >= INFO) $
409    showVerboseInfo Nothing program args env' source
410  (exit, out) <- E.catch
411    (pipeProcess (Just env') program args
412                     (BL.fromStrict $ UTF8.fromText source))
413    (handlePDFProgramNotFound program)
414  return $ case exit of
415             ExitFailure _ -> Left out
416             ExitSuccess   -> Right out
417
418
419html2pdf  :: Verbosity    -- ^ Verbosity level
420          -> String       -- ^ Program (wkhtmltopdf, weasyprint, prince, or path)
421          -> [String]     -- ^ Args to program
422          -> Text         -- ^ HTML5 source
423          -> IO (Either ByteString ByteString)
424html2pdf verbosity program args source =
425  -- write HTML to temp file so we don't have to rewrite
426  -- all links in `a`, `img`, `style`, `script`, etc. tags,
427  -- and piping to weasyprint didn't work on Windows either.
428  withTempFile "." "html2pdf.html" $ \file h1 ->
429    withTempFile "." "html2pdf.pdf" $ \pdfFile h2 -> do
430      hClose h1
431      hClose h2
432      BS.writeFile file $ UTF8.fromText source
433      let pdfFileArgName = ["-o" | takeBaseName program == "prince"]
434      let programArgs = args ++ [file] ++ pdfFileArgName ++ [pdfFile]
435      env' <- getEnvironment
436      when (verbosity >= INFO) $
437        UTF8.readFile file >>=
438          showVerboseInfo Nothing program programArgs env'
439      (exit, out) <- E.catch
440        (pipeProcess (Just env') program programArgs BL.empty)
441        (handlePDFProgramNotFound program)
442      when (verbosity >= INFO) $ do
443        BL.hPutStr stderr out
444        UTF8.hPutStr stderr "\n"
445      pdfExists <- doesFileExist pdfFile
446      mbPdf <- if pdfExists
447                -- We read PDF as a strict bytestring to make sure that the
448                -- temp directory is removed on Windows.
449                -- See https://github.com/jgm/pandoc/issues/1192.
450                then Just . BL.fromChunks . (:[]) <$> BS.readFile pdfFile
451                else return Nothing
452      return $ case (exit, mbPdf) of
453                 (ExitFailure _, _)      -> Left out
454                 (ExitSuccess, Nothing)  -> Left ""
455                 (ExitSuccess, Just pdf) -> Right pdf
456
457context2pdf :: Verbosity    -- ^ Verbosity level
458            -> String       -- ^ "context" or path to it
459            -> [String]     -- ^ extra arguments
460            -> FilePath     -- ^ temp directory for output
461            -> Text         -- ^ ConTeXt source
462            -> PandocIO (Either ByteString ByteString)
463context2pdf verbosity program pdfargs tmpDir source =
464  liftIO $ inDirectory tmpDir $ do
465    let file = "input.tex"
466    BS.writeFile file $ UTF8.fromText source
467    let programArgs = "--batchmode" : pdfargs ++ [file]
468    env' <- getEnvironment
469    when (verbosity >= INFO) $
470      UTF8.readFile file >>=
471        showVerboseInfo (Just tmpDir) program programArgs env'
472    (exit, out) <- E.catch
473      (pipeProcess (Just env') program programArgs BL.empty)
474      (handlePDFProgramNotFound program)
475    when (verbosity >= INFO) $ do
476      BL.hPutStr stderr out
477      UTF8.hPutStr stderr "\n"
478    let pdfFile = replaceExtension file ".pdf"
479    pdfExists <- doesFileExist pdfFile
480    mbPdf <- if pdfExists
481              -- We read PDF as a strict bytestring to make sure that the
482              -- temp directory is removed on Windows.
483              -- See https://github.com/jgm/pandoc/issues/1192.
484              then (Just . BL.fromChunks . (:[])) `fmap` BS.readFile pdfFile
485              else return Nothing
486    case (exit, mbPdf) of
487         (ExitFailure _, _)      -> do
488            let logmsg = extractConTeXtMsg out
489            return $ Left logmsg
490         (ExitSuccess, Nothing)  -> return $ Left ""
491         (ExitSuccess, Just pdf) -> return $ Right pdf
492
493
494showVerboseInfo :: Maybe FilePath
495                -> String
496                -> [String]
497                -> [(String, String)]
498                -> Text
499                -> IO ()
500showVerboseInfo mbTmpDir program programArgs env source = do
501  case mbTmpDir of
502    Just tmpDir -> do
503      UTF8.hPutStrLn stderr "[makePDF] temp dir:"
504      UTF8.hPutStrLn stderr (T.pack tmpDir)
505    Nothing -> return ()
506  UTF8.hPutStrLn stderr "[makePDF] Command line:"
507  UTF8.hPutStrLn stderr $
508       T.pack program <> " " <> T.pack (unwords (map show programArgs))
509  UTF8.hPutStr stderr "\n"
510  UTF8.hPutStrLn stderr "[makePDF] Relevant environment variables:"
511  -- we filter out irrelevant stuff to avoid leaking passwords and keys!
512  let isRelevant ("PATH",_) = True
513      isRelevant ("TMPDIR",_) = True
514      isRelevant ("PWD",_) = True
515      isRelevant ("LANG",_) = True
516      isRelevant ("HOME",_) = True
517      isRelevant ("LUA_PATH",_) = True
518      isRelevant ("LUA_CPATH",_) = True
519      isRelevant ("SHELL",_) = True
520      isRelevant ("TEXINPUTS",_) = True
521      isRelevant ("TEXMFOUTPUT",_) = True
522      isRelevant _ = False
523  mapM_ (UTF8.hPutStrLn stderr . tshow) (filter isRelevant env)
524  UTF8.hPutStr stderr "\n"
525  UTF8.hPutStrLn stderr "[makePDF] Source:"
526  UTF8.hPutStrLn stderr source
527
528handlePDFProgramNotFound :: String -> IE.IOError -> IO a
529handlePDFProgramNotFound program e
530  | IE.isDoesNotExistError e =
531      E.throwIO $ PandocPDFProgramNotFoundError $ T.pack program
532  | otherwise = E.throwIO e
533
534utf8ToText :: ByteString -> Text
535utf8ToText lbs =
536  case decodeUtf8' lbs of
537    Left _  -> T.pack $ BC.unpack lbs  -- if decoding fails, treat as latin1
538    Right t -> TL.toStrict t
539