Skip to content

Commit

Permalink
Remove initial check for pdf creating program.
Browse files Browse the repository at this point in the history
Instead, just try running it and raise the exception if it
isn't found at that point.

This improves things for users of Cygwin on Windows, where
the executable won't be found by `findExecutable` unless
`.exe` is added.

The same exception is raised as before, but at a later
point.

Closes #3819.
  • Loading branch information
jgm committed Aug 16, 2017
1 parent 97fe6c3 commit f8b6a22
Show file tree
Hide file tree
Showing 2 changed files with 27 additions and 9 deletions.
4 changes: 0 additions & 4 deletions src/Text/Pandoc/App.hs
Original file line number Diff line number Diff line change
Expand Up @@ -485,10 +485,6 @@ convertWithOpts opts = do
| html5Output -> "wkhtmltopdf"
| msOutput -> "pdfroff"
| otherwise -> optLaTeXEngine opts
-- check for pdf creating program
mbPdfProg <- liftIO $ findExecutable pdfprog
when (isNothing mbPdfProg) $ liftIO $ E.throwIO $
PandocPDFProgramNotFoundError pdfprog

res <- makePDF pdfprog f writerOptions verbosity media doc
case res of
Expand Down
32 changes: 27 additions & 5 deletions src/Text/Pandoc/PDF.hs
Original file line number Diff line number Diff line change
Expand Up @@ -50,7 +50,9 @@ import System.Exit (ExitCode (..))
import System.FilePath
import System.IO (stdout)
import System.IO.Temp (withTempDirectory, withTempFile)
import System.IO.Error (IOError, isDoesNotExistError)
import Text.Pandoc.Definition
import Text.Pandoc.Error (PandocError(PandocPDFProgramNotFoundError))
import Text.Pandoc.MediaBag
import Text.Pandoc.MIME (getMimeType)
import Text.Pandoc.Options (HTMLMathMethod (..), WriterOptions (..))
Expand Down Expand Up @@ -193,7 +195,12 @@ tex2pdf' verbosity args tmpDir program source = do
let numruns = if "\\tableofcontents" `T.isInfixOf` source
then 3 -- to get page numbers
else 2 -- 1 run won't give you PDF bookmarks
(exit, log', mbPdf) <- runTeXProgram verbosity program args 1 numruns tmpDir source
(exit, log', mbPdf) <- E.catch
(runTeXProgram verbosity program args 1 numruns tmpDir source)
(\(e :: IOError) -> if isDoesNotExistError e
then E.throwIO $
PandocPDFProgramNotFoundError program
else E.throwIO e)
case (exit, mbPdf) of
(ExitFailure _, _) -> do
let logmsg = extractMsg log'
Expand Down Expand Up @@ -321,8 +328,13 @@ ms2pdf verbosity args source = do
putStrLn $ "[makePDF] Contents:\n"
putStr $ T.unpack source
putStr "\n"
(exit, out) <- pipeProcess (Just env') "pdfroff" args
(BL.fromStrict $ UTF8.fromText source)
(exit, out) <- E.catch
(pipeProcess (Just env') "pdfroff" args
(BL.fromStrict $ UTF8.fromText source))
(\(e :: IOError) -> if isDoesNotExistError e
then E.throwIO $
PandocPDFProgramNotFoundError "pdfroff"
else E.throwIO e)
when (verbosity >= INFO) $ do
BL.hPutStr stdout out
putStr "\n"
Expand Down Expand Up @@ -350,7 +362,12 @@ html2pdf verbosity args source = do
putStrLn $ "[makePDF] Contents of " ++ file ++ ":"
BL.readFile file >>= BL.putStr
putStr "\n"
(exit, out) <- pipeProcess (Just env') "wkhtmltopdf" programArgs BL.empty
(exit, out) <- E.catch
(pipeProcess (Just env') "wkhtmltopdf" programArgs BL.empty)
(\(e :: IOError) -> if isDoesNotExistError e
then E.throwIO $
PandocPDFProgramNotFoundError "wkhtml2pdf"
else E.throwIO e)
removeFile file
when (verbosity >= INFO) $ do
BL.hPutStr stdout out
Expand Down Expand Up @@ -397,7 +414,12 @@ context2pdf verbosity tmpDir source = inDirectory tmpDir $ do
putStrLn $ "[makePDF] Contents of " ++ file ++ ":"
BL.readFile file >>= BL.putStr
putStr "\n"
(exit, out) <- pipeProcess (Just env') "context" programArgs BL.empty
(exit, out) <- E.catch
(pipeProcess (Just env') "context" programArgs BL.empty)
(\(e :: IOError) -> if isDoesNotExistError e
then E.throwIO $
PandocPDFProgramNotFoundError "context"
else E.throwIO e)
when (verbosity >= INFO) $ do
BL.hPutStr stdout out
putStr "\n"
Expand Down

0 comments on commit f8b6a22

Please sign in to comment.