From 764bf86177ca0e85d3cd61b9b7baf197c411c764 Mon Sep 17 00:00:00 2001 From: Mauro Bieg Date: Sun, 3 Jun 2018 22:59:11 +0200 Subject: Regression: make --pdf-engine work with full paths (#4682) Fixes #4681. --- src/Text/Pandoc/App.hs | 4 +- src/Text/Pandoc/PDF.hs | 111 ++++++++++++++++++++++++++----------------------- 2 files changed, 62 insertions(+), 53 deletions(-) (limited to 'src') diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index a59fd9bbe..ac6afa5f1 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -155,9 +155,9 @@ pdfWriterAndProg mWriter mEngine = do where go Nothing Nothing = Right ("latex", "pdflatex") go (Just writer) Nothing = (writer,) <$> engineForWriter writer - go Nothing (Just engine) = (,engine) <$> writerForEngine engine + go Nothing (Just engine) = (,engine) <$> writerForEngine (takeBaseName engine) go (Just writer) (Just engine) = - case find (== (baseWriterName writer, engine)) engines of + case find (== (baseWriterName writer, takeBaseName engine)) engines of Just _ -> Right (writer, engine) Nothing -> Left $ "pdf-engine " ++ engine ++ " is not compatible with output format " ++ writer diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs index b171d65b0..7fa2cd26c 100644 --- a/src/Text/Pandoc/PDF.hs +++ b/src/Text/Pandoc/PDF.hs @@ -79,13 +79,52 @@ changePathSeparators = intercalate "/" . splitDirectories #endif makePDF :: String -- ^ pdf creator (pdflatex, lualatex, xelatex, - -- wkhtmltopdf, weasyprint, prince, context, pdfroff) + -- wkhtmltopdf, weasyprint, prince, context, pdfroff, + -- or path to executable) -> [String] -- ^ arguments to pass to pdf creator -> (WriterOptions -> Pandoc -> PandocIO Text) -- ^ writer -> WriterOptions -- ^ options -> Pandoc -- ^ document -> PandocIO (Either ByteString ByteString) -makePDF "wkhtmltopdf" pdfargs writer opts doc@(Pandoc meta _) = do +makePDF program pdfargs writer opts doc = do + case takeBaseName program of + "wkhtmltopdf" -> makeWithWkhtmltopdf program pdfargs writer opts doc + prog | prog `elem` ["weasyprint", "prince"] -> do + source <- writer opts doc + verbosity <- getVerbosity + liftIO $ html2pdf verbosity program pdfargs source + "pdfroff" -> do + source <- writer opts doc + let args = ["-ms", "-mpdfmark", "-e", "-t", "-k", "-KUTF-8", "-i", + "--no-toc-relocation"] ++ pdfargs + verbosity <- getVerbosity + liftIO $ ms2pdf verbosity program args source + baseProg -> do + -- With context and latex, we create a temp directory within + -- the working directory, since pdflatex sometimes tries to + -- use tools like epstopdf.pl, which are restricted if run + -- on files outside the working directory. + let withTemp = withTempDirectory "." + commonState <- getCommonState + verbosity <- getVerbosity + liftIO $ withTemp "tex2pdf." $ \tmpdir -> do + source <- runIOorExplode $ do + putCommonState commonState + doc' <- handleImages tmpdir doc + writer opts doc' + case baseProg of + "context" -> context2pdf verbosity program tmpdir source + prog | prog `elem` ["pdflatex", "lualatex", "xelatex"] + -> tex2pdf verbosity program pdfargs tmpdir source + _ -> return $ Left $ UTF8.fromStringLazy $ "Unknown program " ++ program + +makeWithWkhtmltopdf :: String -- ^ wkhtmltopdf or path + -> [String] -- ^ arguments + -> (WriterOptions -> Pandoc -> PandocIO Text) -- ^ writer + -> WriterOptions -- ^ options + -> Pandoc -- ^ document + -> PandocIO (Either ByteString ByteString) +makeWithWkhtmltopdf program pdfargs writer opts doc@(Pandoc meta _) = do let mathArgs = case writerHTMLMathMethod opts of -- with MathJax, wait til all math is rendered: MathJax _ -> ["--run-script", "MathJax.Hub.Register.StartupHook('End Typeset', function() { window.status = 'mathjax_loaded' });", @@ -111,39 +150,7 @@ makePDF "wkhtmltopdf" pdfargs writer opts doc@(Pandoc meta _) = do ] source <- writer opts doc verbosity <- getVerbosity - liftIO $ html2pdf verbosity "wkhtmltopdf" args source -makePDF "weasyprint" pdfargs writer opts doc = do - source <- writer opts doc - verbosity <- getVerbosity - liftIO $ html2pdf verbosity "weasyprint" pdfargs source -makePDF "prince" pdfargs writer opts doc = do - source <- writer opts doc - verbosity <- getVerbosity - liftIO $ html2pdf verbosity "prince" pdfargs source -makePDF "pdfroff" pdfargs writer opts doc = do - source <- writer opts doc - let args = ["-ms", "-mpdfmark", "-e", "-t", "-k", "-KUTF-8", "-i", - "--no-toc-relocation"] ++ pdfargs - verbosity <- getVerbosity - liftIO $ ms2pdf verbosity args source -makePDF program pdfargs writer opts doc = do - -- With context and latex, we create a temp directory within - -- the working directory, since pdflatex sometimes tries to - -- use tools like epstopdf.pl, which are restricted if run - -- on files outside the working directory. - let withTemp = withTempDirectory "." - commonState <- getCommonState - verbosity <- getVerbosity - liftIO $ withTemp "tex2pdf." $ \tmpdir -> do - source <- runIOorExplode $ do - putCommonState commonState - doc' <- handleImages tmpdir doc - writer opts doc' - case takeBaseName program of - "context" -> context2pdf verbosity tmpdir source - prog | prog `elem` ["pdflatex", "lualatex", "xelatex"] - -> tex2pdf' verbosity pdfargs tmpdir program source - _ -> return $ Left $ UTF8.fromStringLazy $ "Unknown program " ++ program + liftIO $ html2pdf verbosity program args source handleImages :: FilePath -- ^ temp dir to store images -> Pandoc -- ^ document @@ -195,13 +202,13 @@ convertImage tmpdir fname = mime = getMimeType fname doNothing = return (Right fname) -tex2pdf' :: Verbosity -- ^ Verbosity level - -> [String] -- ^ Arguments to the latex-engine - -> FilePath -- ^ temp directory for output - -> String -- ^ tex program - -> Text -- ^ tex source - -> IO (Either ByteString ByteString) -tex2pdf' verbosity args tmpDir program source = do +tex2pdf :: Verbosity -- ^ Verbosity level + -> String -- ^ tex program + -> [String] -- ^ Arguments to the latex-engine + -> FilePath -- ^ temp directory for output + -> Text -- ^ tex source + -> IO (Either ByteString ByteString) +tex2pdf verbosity program args tmpDir 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 @@ -328,14 +335,15 @@ runTeXProgram verbosity program args runNumber numRuns tmpDir source = do return (exit, log', pdf) ms2pdf :: Verbosity + -> String -> [String] -> Text -> IO (Either ByteString ByteString) -ms2pdf verbosity args source = do +ms2pdf verbosity program args source = do env' <- getEnvironment when (verbosity >= INFO) $ do putStrLn "[makePDF] Command line:" - putStrLn $ "pdfroff " ++ " " ++ unwords (map show args) + putStrLn $ program ++ " " ++ unwords (map show args) putStr "\n" putStrLn "[makePDF] Environment:" mapM_ print env' @@ -344,11 +352,11 @@ ms2pdf verbosity args source = do putStr $ T.unpack source putStr "\n" (exit, out) <- E.catch - (pipeProcess (Just env') "pdfroff" args + (pipeProcess (Just env') program args (BL.fromStrict $ UTF8.fromText source)) (\(e :: IOError) -> if isDoesNotExistError e then E.throwIO $ - PandocPDFProgramNotFoundError "pdfroff" + PandocPDFProgramNotFoundError program else E.throwIO e) when (verbosity >= INFO) $ do BL.hPutStr stdout out @@ -358,7 +366,7 @@ ms2pdf verbosity args source = do ExitSuccess -> Right out html2pdf :: Verbosity -- ^ Verbosity level - -> String -- ^ Program (wkhtmltopdf, weasyprint or prince) + -> String -- ^ Program (wkhtmltopdf, weasyprint, prince, or path) -> [String] -- ^ Args to program -> Text -- ^ HTML5 source -> IO (Either ByteString ByteString) @@ -369,7 +377,7 @@ html2pdf verbosity program args source = do file <- withTempFile "." "html2pdf.html" $ \fp _ -> return fp pdfFile <- withTempFile "." "html2pdf.pdf" $ \fp _ -> return fp BS.writeFile file $ UTF8.fromText source - let pdfFileArgName = ["-o" | program == "prince"] + let pdfFileArgName = ["-o" | takeBaseName program == "prince"] let programArgs = args ++ [file] ++ pdfFileArgName ++ [pdfFile] env' <- getEnvironment when (verbosity >= INFO) $ do @@ -408,10 +416,11 @@ html2pdf verbosity program args source = do (ExitSuccess, Just pdf) -> Right pdf context2pdf :: Verbosity -- ^ Verbosity level + -> String -- ^ "context" or path to it -> FilePath -- ^ temp directory for output -> Text -- ^ ConTeXt source -> IO (Either ByteString ByteString) -context2pdf verbosity tmpDir source = inDirectory tmpDir $ do +context2pdf verbosity program tmpDir source = inDirectory tmpDir $ do let file = "input.tex" BS.writeFile file $ UTF8.fromText source #ifdef _WINDOWS @@ -426,7 +435,7 @@ context2pdf verbosity tmpDir source = inDirectory tmpDir $ do putStrLn "[makePDF] temp dir:" putStrLn tmpDir' putStrLn "[makePDF] Command line:" - putStrLn $ "context" ++ " " ++ unwords (map show programArgs) + putStrLn $ program ++ " " ++ unwords (map show programArgs) putStr "\n" putStrLn "[makePDF] Environment:" mapM_ print env' @@ -435,7 +444,7 @@ context2pdf verbosity tmpDir source = inDirectory tmpDir $ do BL.readFile file >>= BL.putStr putStr "\n" (exit, out) <- E.catch - (pipeProcess (Just env') "context" programArgs BL.empty) + (pipeProcess (Just env') program programArgs BL.empty) (\(e :: IOError) -> if isDoesNotExistError e then E.throwIO $ PandocPDFProgramNotFoundError "context" -- cgit v1.2.3