2017-03-04 13:03:41 +01:00
|
|
|
{-# LANGUAGE CPP #-}
|
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
{-# LANGUAGE ScopedTypeVariables #-}
|
2012-01-20 18:57:16 -08:00
|
|
|
{-
|
2018-01-05 20:19:47 +01:00
|
|
|
Copyright (C) 2012-2018 John MacFarlane <jgm@berkeley.edu>
|
2012-01-20 18:57:16 -08:00
|
|
|
|
|
|
|
This program is free software; you can redistribute it and/or modify
|
|
|
|
it under the terms of the GNU General Public License as published by
|
|
|
|
the Free Software Foundation; either version 2 of the License, or
|
|
|
|
(at your option) any later version.
|
|
|
|
|
|
|
|
This program is distributed in the hope that it will be useful,
|
|
|
|
but WITHOUT ANY WARRANTY; without even the implied warranty of
|
|
|
|
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
|
|
|
GNU General Public License for more details.
|
|
|
|
|
|
|
|
You should have received a copy of the GNU General Public License
|
|
|
|
along with this program; if not, write to the Free Software
|
|
|
|
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
|
|
|
-}
|
|
|
|
|
|
|
|
{- |
|
|
|
|
Module : Text.Pandoc.PDF
|
2018-01-05 20:19:47 +01:00
|
|
|
Copyright : Copyright (C) 2012-2018 John MacFarlane
|
2012-01-20 18:57:16 -08:00
|
|
|
License : GNU GPL, version 2 or above
|
|
|
|
|
|
|
|
Maintainer : John MacFarlane <jgm@berkeley.edu>
|
|
|
|
Stability : alpha
|
|
|
|
Portability : portable
|
|
|
|
|
|
|
|
Conversion of LaTeX documents to PDF.
|
|
|
|
-}
|
2013-07-20 12:14:43 -07:00
|
|
|
module Text.Pandoc.PDF ( makePDF ) where
|
2012-01-20 18:57:16 -08:00
|
|
|
|
2017-03-04 13:03:41 +01:00
|
|
|
import qualified Codec.Picture as JP
|
|
|
|
import qualified Control.Exception as E
|
2017-05-07 20:57:16 +02:00
|
|
|
import Control.Monad (unless, when)
|
2017-03-04 13:03:41 +01:00
|
|
|
import Control.Monad.Trans (MonadIO (..))
|
|
|
|
import qualified Data.ByteString as BS
|
2012-01-20 18:57:16 -08:00
|
|
|
import Data.ByteString.Lazy (ByteString)
|
2017-03-04 13:03:41 +01:00
|
|
|
import qualified Data.ByteString.Lazy as BL
|
2012-01-20 18:57:16 -08:00
|
|
|
import qualified Data.ByteString.Lazy.Char8 as BC
|
2017-03-04 13:03:41 +01:00
|
|
|
import Data.Maybe (fromMaybe)
|
2016-08-30 13:43:50 -04:00
|
|
|
import Data.Monoid ((<>))
|
2017-10-27 20:28:29 -07:00
|
|
|
import Data.Text (Text)
|
|
|
|
import qualified Data.Text as T
|
|
|
|
import qualified Data.Text.IO as TextIO
|
2017-03-04 13:03:41 +01:00
|
|
|
import System.Directory
|
|
|
|
import System.Environment
|
2012-01-20 19:04:08 -08:00
|
|
|
import System.Exit (ExitCode (..))
|
2012-01-20 18:57:16 -08:00
|
|
|
import System.FilePath
|
2016-12-09 15:59:03 +01:00
|
|
|
import System.IO (stdout)
|
2017-03-04 13:03:41 +01:00
|
|
|
import System.IO.Temp (withTempDirectory, withTempFile)
|
2017-08-16 10:13:16 -07:00
|
|
|
#if MIN_VERSION_base(4,8,3)
|
2017-08-15 21:17:20 -07:00
|
|
|
import System.IO.Error (IOError, isDoesNotExistError)
|
2017-08-16 10:13:16 -07:00
|
|
|
#else
|
|
|
|
import System.IO.Error (isDoesNotExistError)
|
|
|
|
#endif
|
2013-07-20 12:14:43 -07:00
|
|
|
import Text.Pandoc.Definition
|
2017-10-27 20:28:29 -07:00
|
|
|
import Text.Pandoc.Error (PandocError (PandocPDFProgramNotFoundError))
|
2017-05-07 20:57:16 +02:00
|
|
|
import Text.Pandoc.MIME (getMimeType)
|
2017-03-04 13:03:41 +01:00
|
|
|
import Text.Pandoc.Options (HTMLMathMethod (..), WriterOptions (..))
|
2013-08-08 15:15:20 -07:00
|
|
|
import Text.Pandoc.Process (pipeProcess)
|
2017-03-04 13:03:41 +01:00
|
|
|
import Text.Pandoc.Shared (inDirectory, stringify, withTempDir)
|
|
|
|
import qualified Text.Pandoc.UTF8 as UTF8
|
|
|
|
import Text.Pandoc.Walk (walkM)
|
|
|
|
import Text.Pandoc.Writers.Shared (getField, metaToJSON)
|
2014-03-10 11:16:09 -07:00
|
|
|
#ifdef _WINDOWS
|
|
|
|
import Data.List (intercalate)
|
|
|
|
#endif
|
2017-10-27 20:28:29 -07:00
|
|
|
import Text.Pandoc.Class (PandocIO, extractMedia, fillMediaBag, getCommonState,
|
|
|
|
getVerbosity, putCommonState, report, runIO,
|
|
|
|
runIOorExplode, setVerbosity)
|
2017-02-24 14:29:56 +01:00
|
|
|
import Text.Pandoc.Logging
|
2012-01-20 18:57:16 -08:00
|
|
|
|
2014-03-10 11:16:09 -07:00
|
|
|
#ifdef _WINDOWS
|
|
|
|
changePathSeparators :: FilePath -> FilePath
|
|
|
|
changePathSeparators = intercalate "/" . splitDirectories
|
2013-04-26 20:33:15 -07:00
|
|
|
#endif
|
|
|
|
|
2017-09-12 05:18:42 +02:00
|
|
|
makePDF :: String -- ^ pdf creator (pdflatex, lualatex, xelatex,
|
|
|
|
-- wkhtmltopdf, weasyprint, prince, context, pdfroff)
|
2017-10-26 11:11:04 -07:00
|
|
|
-> [String] -- ^ arguments to pass to pdf creator
|
2017-06-10 23:39:49 +02:00
|
|
|
-> (WriterOptions -> Pandoc -> PandocIO Text) -- ^ writer
|
2013-07-20 12:14:43 -07:00
|
|
|
-> WriterOptions -- ^ options
|
|
|
|
-> Pandoc -- ^ document
|
2017-05-20 22:42:30 +02:00
|
|
|
-> PandocIO (Either ByteString ByteString)
|
2017-10-26 11:11:04 -07:00
|
|
|
makePDF "wkhtmltopdf" pdfargs writer opts doc@(Pandoc meta _) = do
|
2015-12-21 22:13:44 -08:00
|
|
|
let mathArgs = case writerHTMLMathMethod opts of
|
|
|
|
-- with MathJax, wait til all math is rendered:
|
2015-12-21 17:22:12 -08:00
|
|
|
MathJax _ -> ["--run-script", "MathJax.Hub.Register.StartupHook('End Typeset', function() { window.status = 'mathjax_loaded' });",
|
|
|
|
"--window-status", "mathjax_loaded"]
|
|
|
|
_ -> []
|
2015-12-21 22:13:44 -08:00
|
|
|
meta' <- metaToJSON opts (return . stringify) (return . stringify) meta
|
2015-12-21 23:47:03 -08:00
|
|
|
let toArgs (f, mbd) = maybe [] (\d -> ['-':'-':f, d]) mbd
|
2017-10-26 11:11:04 -07:00
|
|
|
let args = pdfargs ++ mathArgs ++ concatMap toArgs
|
2015-12-21 23:47:03 -08:00
|
|
|
[("page-size", getField "papersize" meta')
|
|
|
|
,("title", getField "title" meta')
|
|
|
|
,("margin-bottom", fromMaybe (Just "1.2in")
|
|
|
|
(getField "margin-bottom" meta'))
|
|
|
|
,("margin-top", fromMaybe (Just "1.25in")
|
|
|
|
(getField "margin-top" meta'))
|
|
|
|
,("margin-right", fromMaybe (Just "1.25in")
|
|
|
|
(getField "margin-right" meta'))
|
|
|
|
,("margin-left", fromMaybe (Just "1.25in")
|
|
|
|
(getField "margin-left" meta'))
|
|
|
|
]
|
2017-05-20 22:42:30 +02:00
|
|
|
source <- writer opts doc
|
2017-09-30 17:17:04 -05:00
|
|
|
verbosity <- getVerbosity
|
2017-09-12 05:18:42 +02:00
|
|
|
liftIO $ html2pdf verbosity "wkhtmltopdf" args source
|
2017-10-26 11:11:04 -07:00
|
|
|
makePDF "weasyprint" pdfargs writer opts doc = do
|
2017-09-12 05:18:42 +02:00
|
|
|
source <- writer opts doc
|
2017-09-30 17:17:04 -05:00
|
|
|
verbosity <- getVerbosity
|
2017-10-26 11:11:04 -07:00
|
|
|
liftIO $ html2pdf verbosity "weasyprint" pdfargs source
|
|
|
|
makePDF "prince" pdfargs writer opts doc = do
|
2017-09-12 05:18:42 +02:00
|
|
|
source <- writer opts doc
|
2017-09-30 17:17:04 -05:00
|
|
|
verbosity <- getVerbosity
|
2017-10-26 11:11:04 -07:00
|
|
|
liftIO $ html2pdf verbosity "prince" pdfargs source
|
|
|
|
makePDF "pdfroff" pdfargs writer opts doc = do
|
2017-05-20 22:42:30 +02:00
|
|
|
source <- writer opts doc
|
2017-03-26 20:00:40 +02:00
|
|
|
let args = ["-ms", "-mpdfmark", "-e", "-t", "-k", "-KUTF-8", "-i",
|
2017-10-26 11:11:04 -07:00
|
|
|
"--no-toc-relocation"] ++ pdfargs
|
2017-09-30 17:17:04 -05:00
|
|
|
verbosity <- getVerbosity
|
2017-05-20 22:42:30 +02:00
|
|
|
liftIO $ ms2pdf verbosity args source
|
2017-10-26 11:11:04 -07:00
|
|
|
makePDF program pdfargs writer opts doc = do
|
2017-02-25 21:46:41 +01:00
|
|
|
let withTemp = if takeBaseName program == "context"
|
|
|
|
then withTempDirectory "."
|
|
|
|
else withTempDir
|
2017-09-30 17:17:04 -05:00
|
|
|
commonState <- getCommonState
|
|
|
|
verbosity <- getVerbosity
|
2017-02-25 21:46:41 +01:00
|
|
|
liftIO $ withTemp "tex2pdf." $ \tmpdir -> do
|
2017-02-23 15:06:49 +01:00
|
|
|
source <- runIOorExplode $ do
|
2017-09-30 17:17:04 -05:00
|
|
|
putCommonState commonState
|
|
|
|
doc' <- handleImages tmpdir doc
|
2017-02-23 15:06:49 +01:00
|
|
|
writer opts doc'
|
2017-01-15 21:30:20 +01:00
|
|
|
case takeBaseName program of
|
2017-01-23 00:06:04 +01:00
|
|
|
"context" -> context2pdf verbosity tmpdir source
|
2017-01-15 21:30:20 +01:00
|
|
|
prog | prog `elem` ["pdflatex", "lualatex", "xelatex"]
|
2017-10-26 11:11:04 -07:00
|
|
|
-> tex2pdf' verbosity pdfargs tmpdir program source
|
2017-01-15 21:30:20 +01:00
|
|
|
_ -> return $ Left $ UTF8.fromStringLazy $ "Unknown program " ++ program
|
2012-01-20 18:57:16 -08:00
|
|
|
|
2017-09-30 17:17:04 -05:00
|
|
|
handleImages :: FilePath -- ^ temp dir to store images
|
2013-07-20 12:14:43 -07:00
|
|
|
-> Pandoc -- ^ document
|
2017-09-30 17:17:04 -05:00
|
|
|
-> PandocIO Pandoc
|
|
|
|
handleImages tmpdir doc =
|
|
|
|
fillMediaBag doc >>=
|
|
|
|
extractMedia tmpdir >>=
|
|
|
|
walkM (convertImages tmpdir)
|
2013-07-20 12:14:43 -07:00
|
|
|
|
2017-09-30 17:17:04 -05:00
|
|
|
convertImages :: FilePath -> Inline -> PandocIO Inline
|
|
|
|
convertImages tmpdir (Image attr ils (src, tit)) = do
|
|
|
|
img <- liftIO $ convertImage tmpdir src
|
2014-08-12 15:09:43 +01:00
|
|
|
newPath <-
|
|
|
|
case img of
|
2017-02-24 14:29:56 +01:00
|
|
|
Left e -> do
|
2017-09-30 17:17:04 -05:00
|
|
|
report $ CouldNotConvertImage src e
|
2017-02-24 14:29:56 +01:00
|
|
|
return src
|
2014-08-30 18:45:58 -07:00
|
|
|
Right fp -> return fp
|
2015-04-02 21:04:43 -07:00
|
|
|
return (Image attr ils (newPath, tit))
|
2017-09-30 17:17:04 -05:00
|
|
|
convertImages _ x = return x
|
2014-08-12 15:09:43 +01:00
|
|
|
|
|
|
|
-- Convert formats which do not work well in pdf to png
|
2014-08-30 18:45:58 -07:00
|
|
|
convertImage :: FilePath -> FilePath -> IO (Either String FilePath)
|
2014-08-12 15:09:43 +01:00
|
|
|
convertImage tmpdir fname =
|
|
|
|
case mime of
|
|
|
|
Just "image/png" -> doNothing
|
|
|
|
Just "image/jpeg" -> doNothing
|
|
|
|
Just "application/pdf" -> doNothing
|
2017-08-09 12:13:49 -07:00
|
|
|
Just "image/svg+xml" -> E.catch (do
|
|
|
|
(exit, _) <- pipeProcess Nothing "rsvg-convert"
|
|
|
|
["-f","pdf","-a","-o",pdfOut,fname] BL.empty
|
|
|
|
if exit == ExitSuccess
|
|
|
|
then return $ Right pdfOut
|
|
|
|
else return $ Left "conversion from SVG failed")
|
|
|
|
(\(e :: E.SomeException) -> return $ Left $
|
|
|
|
"check that rsvg2pdf is in path.\n" ++
|
|
|
|
show e)
|
2014-08-30 18:45:58 -07:00
|
|
|
_ -> JP.readImage fname >>= \res ->
|
|
|
|
case res of
|
2017-02-24 14:29:56 +01:00
|
|
|
Left e -> return $ Left e
|
2014-08-30 18:45:58 -07:00
|
|
|
Right img ->
|
2017-08-09 12:13:49 -07:00
|
|
|
E.catch (Right pngOut <$ JP.savePngImage pngOut img) $
|
2014-08-30 18:45:58 -07:00
|
|
|
\(e :: E.SomeException) -> return (Left (show e))
|
2014-08-12 15:09:43 +01:00
|
|
|
where
|
2017-08-09 12:13:49 -07:00
|
|
|
pngOut = replaceDirectory (replaceExtension fname ".png") tmpdir
|
|
|
|
pdfOut = replaceDirectory (replaceExtension fname ".pdf") tmpdir
|
2014-08-12 15:09:43 +01:00
|
|
|
mime = getMimeType fname
|
2014-08-30 18:45:58 -07:00
|
|
|
doNothing = return (Right fname)
|
2014-08-12 15:09:43 +01:00
|
|
|
|
2017-01-22 12:19:46 +01:00
|
|
|
tex2pdf' :: Verbosity -- ^ Verbosity level
|
2015-03-04 15:25:56 +05:30
|
|
|
-> [String] -- ^ Arguments to the latex-engine
|
2014-12-26 11:19:55 -07:00
|
|
|
-> FilePath -- ^ temp directory for output
|
2012-01-20 21:36:04 -08:00
|
|
|
-> String -- ^ tex program
|
2017-06-10 23:39:49 +02:00
|
|
|
-> Text -- ^ tex source
|
2012-01-20 19:11:35 -08:00
|
|
|
-> IO (Either ByteString ByteString)
|
2017-01-22 12:19:46 +01:00
|
|
|
tex2pdf' verbosity args tmpDir program source = do
|
2017-06-10 23:39:49 +02:00
|
|
|
let numruns = if "\\tableofcontents" `T.isInfixOf` source
|
2012-03-19 09:25:33 -07:00
|
|
|
then 3 -- to get page numbers
|
|
|
|
else 2 -- 1 run won't give you PDF bookmarks
|
2017-08-15 21:17:20 -07:00
|
|
|
(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)
|
2012-01-20 18:57:16 -08:00
|
|
|
case (exit, mbPdf) of
|
2013-08-11 16:16:24 -07:00
|
|
|
(ExitFailure _, _) -> do
|
|
|
|
let logmsg = extractMsg log'
|
|
|
|
let extramsg =
|
|
|
|
case logmsg of
|
2015-11-22 07:42:11 -08:00
|
|
|
x | "! Package inputenc Error" `BC.isPrefixOf` x
|
|
|
|
&& program /= "xelatex"
|
2017-09-12 05:18:42 +02:00
|
|
|
-> "\nTry running pandoc with --pdf-engine=xelatex."
|
2013-08-11 16:16:24 -07:00
|
|
|
_ -> ""
|
2014-03-19 11:09:36 -07:00
|
|
|
return $ Left $ logmsg <> extramsg
|
|
|
|
(ExitSuccess, Nothing) -> return $ Left ""
|
2017-06-18 11:17:00 +02:00
|
|
|
(ExitSuccess, Just pdf) -> do
|
|
|
|
missingCharacterWarnings verbosity log'
|
|
|
|
return $ Right pdf
|
|
|
|
|
|
|
|
missingCharacterWarnings :: Verbosity -> ByteString -> IO ()
|
|
|
|
missingCharacterWarnings verbosity log' = do
|
|
|
|
let ls = BC.lines log'
|
|
|
|
let isMissingCharacterWarning = BC.isPrefixOf "Missing character: "
|
|
|
|
let warnings = [ UTF8.toStringLazy (BC.drop 19 l)
|
|
|
|
| l <- ls
|
|
|
|
, isMissingCharacterWarning l
|
|
|
|
]
|
|
|
|
runIO $ do
|
|
|
|
setVerbosity verbosity
|
|
|
|
mapM_ (report . MissingCharacter) warnings
|
|
|
|
return ()
|
2012-01-20 18:57:16 -08:00
|
|
|
|
|
|
|
-- parsing output
|
|
|
|
|
|
|
|
extractMsg :: ByteString -> ByteString
|
2012-01-20 19:04:08 -08:00
|
|
|
extractMsg log' = do
|
|
|
|
let msg' = dropWhile (not . ("!" `BC.isPrefixOf`)) $ BC.lines log'
|
2012-01-20 18:57:16 -08:00
|
|
|
let (msg'',rest) = break ("l." `BC.isPrefixOf`) msg'
|
|
|
|
let lineno = take 1 rest
|
2012-01-21 14:18:36 -08:00
|
|
|
if null msg'
|
|
|
|
then log'
|
|
|
|
else BC.unlines (msg'' ++ lineno)
|
2012-01-20 18:57:16 -08:00
|
|
|
|
2015-10-20 08:15:12 -07:00
|
|
|
extractConTeXtMsg :: ByteString -> ByteString
|
|
|
|
extractConTeXtMsg log' = do
|
|
|
|
let msg' = take 1 $
|
|
|
|
dropWhile (not . ("tex error" `BC.isPrefixOf`)) $ BC.lines log'
|
|
|
|
if null msg'
|
|
|
|
then log'
|
|
|
|
else BC.unlines msg'
|
|
|
|
|
2012-01-20 18:57:16 -08:00
|
|
|
-- running tex programs
|
|
|
|
|
|
|
|
-- Run a TeX program on an input bytestring and return (exit code,
|
|
|
|
-- contents of stdout, contents of produced PDF if any). Rerun
|
2012-02-06 12:12:23 -08:00
|
|
|
-- a fixed number of times to resolve references.
|
2017-01-22 12:19:46 +01:00
|
|
|
runTeXProgram :: Verbosity -> String -> [String] -> Int -> Int -> FilePath
|
2017-06-10 23:39:49 +02:00
|
|
|
-> Text -> IO (ExitCode, ByteString, Maybe ByteString)
|
2017-01-22 12:19:46 +01:00
|
|
|
runTeXProgram verbosity program args runNumber numRuns tmpDir source = do
|
2014-03-10 16:23:57 -07:00
|
|
|
let file = tmpDir </> "input.tex"
|
2012-02-06 12:12:23 -08:00
|
|
|
exists <- doesFileExist file
|
2017-06-10 23:39:49 +02:00
|
|
|
unless exists $ BS.writeFile file $ UTF8.fromText source
|
2014-02-23 20:35:07 -08:00
|
|
|
#ifdef _WINDOWS
|
2014-03-10 16:23:57 -07:00
|
|
|
-- note: we want / even on Windows, for TexLive
|
|
|
|
let tmpDir' = changePathSeparators tmpDir
|
|
|
|
let file' = changePathSeparators file
|
2014-02-23 20:35:07 -08:00
|
|
|
#else
|
2014-03-10 16:23:57 -07:00
|
|
|
let tmpDir' = tmpDir
|
|
|
|
let file' = file
|
2014-02-23 20:35:07 -08:00
|
|
|
#endif
|
2014-03-10 16:23:57 -07:00
|
|
|
let programArgs = ["-halt-on-error", "-interaction", "nonstopmode",
|
2015-07-08 17:37:54 -07:00
|
|
|
"-output-directory", tmpDir'] ++ args ++ [file']
|
2014-03-10 16:23:57 -07:00
|
|
|
env' <- getEnvironment
|
2015-11-22 07:42:11 -08:00
|
|
|
let sep = [searchPathSeparator]
|
2014-03-10 16:23:57 -07:00
|
|
|
let texinputs = maybe (tmpDir' ++ sep) ((tmpDir' ++ sep) ++)
|
2013-07-18 21:51:23 -07:00
|
|
|
$ lookup "TEXINPUTS" env'
|
|
|
|
let env'' = ("TEXINPUTS", texinputs) :
|
|
|
|
[(k,v) | (k,v) <- env', k /= "TEXINPUTS"]
|
2017-01-22 12:19:46 +01:00
|
|
|
when (verbosity >= INFO && runNumber == 1) $ do
|
2015-11-22 07:42:11 -08:00
|
|
|
putStrLn "[makePDF] temp dir:"
|
2015-05-20 15:43:42 -07:00
|
|
|
putStrLn tmpDir'
|
2015-11-22 07:42:11 -08:00
|
|
|
putStrLn "[makePDF] Command line:"
|
2014-12-26 11:19:55 -07:00
|
|
|
putStrLn $ program ++ " " ++ unwords (map show programArgs)
|
|
|
|
putStr "\n"
|
2015-11-22 07:42:11 -08:00
|
|
|
putStrLn "[makePDF] Environment:"
|
2014-12-26 11:19:55 -07:00
|
|
|
mapM_ print env''
|
|
|
|
putStr "\n"
|
|
|
|
putStrLn $ "[makePDF] Contents of " ++ file' ++ ":"
|
2017-06-18 11:17:00 +02:00
|
|
|
BL.readFile file' >>= BL.putStr
|
2014-12-26 11:19:55 -07:00
|
|
|
putStr "\n"
|
2016-12-09 15:59:03 +01:00
|
|
|
(exit, out) <- pipeProcess (Just env'') program programArgs BL.empty
|
2017-01-22 12:19:46 +01:00
|
|
|
when (verbosity >= INFO) $ do
|
2014-12-26 11:19:55 -07:00
|
|
|
putStrLn $ "[makePDF] Run #" ++ show runNumber
|
2017-06-18 11:17:00 +02:00
|
|
|
BL.hPutStr stdout out
|
2014-12-26 11:19:55 -07:00
|
|
|
putStr "\n"
|
|
|
|
if runNumber <= numRuns
|
2017-01-22 12:19:46 +01:00
|
|
|
then runTeXProgram verbosity program args (runNumber + 1) numRuns tmpDir source
|
2012-02-06 12:12:23 -08:00
|
|
|
else do
|
|
|
|
let pdfFile = replaceDirectory (replaceExtension file ".pdf") tmpDir
|
|
|
|
pdfExists <- doesFileExist pdfFile
|
|
|
|
pdf <- if pdfExists
|
2014-04-05 19:57:42 -07:00
|
|
|
-- 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.
|
2017-06-18 11:17:00 +02:00
|
|
|
then (Just . BL.fromChunks . (:[])) `fmap` BS.readFile pdfFile
|
2012-02-06 12:12:23 -08:00
|
|
|
else return Nothing
|
2017-06-18 11:17:00 +02:00
|
|
|
-- Note that some things like Missing character warnings
|
|
|
|
-- appear in the log but not on stderr, so we prefer the log:
|
|
|
|
let logFile = replaceExtension file ".log"
|
|
|
|
logExists <- doesFileExist logFile
|
|
|
|
log' <- if logExists
|
|
|
|
then BL.readFile logFile
|
|
|
|
else return out
|
|
|
|
return (exit, log', pdf)
|
2012-01-20 18:57:16 -08:00
|
|
|
|
2017-03-23 21:24:01 +01:00
|
|
|
ms2pdf :: Verbosity
|
|
|
|
-> [String]
|
2017-06-10 23:39:49 +02:00
|
|
|
-> Text
|
2017-03-23 21:24:01 +01:00
|
|
|
-> IO (Either ByteString ByteString)
|
|
|
|
ms2pdf verbosity args source = do
|
|
|
|
env' <- getEnvironment
|
|
|
|
when (verbosity >= INFO) $ do
|
|
|
|
putStrLn "[makePDF] Command line:"
|
|
|
|
putStrLn $ "pdfroff " ++ " " ++ unwords (map show args)
|
|
|
|
putStr "\n"
|
|
|
|
putStrLn "[makePDF] Environment:"
|
|
|
|
mapM_ print env'
|
|
|
|
putStr "\n"
|
2017-10-27 21:29:22 -07:00
|
|
|
putStrLn "[makePDF] Contents:\n"
|
2017-06-10 23:39:49 +02:00
|
|
|
putStr $ T.unpack source
|
2017-03-23 21:24:01 +01:00
|
|
|
putStr "\n"
|
2017-08-15 21:17:20 -07:00
|
|
|
(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)
|
2017-03-23 21:24:01 +01:00
|
|
|
when (verbosity >= INFO) $ do
|
2017-06-18 11:17:00 +02:00
|
|
|
BL.hPutStr stdout out
|
2017-03-23 21:24:01 +01:00
|
|
|
putStr "\n"
|
|
|
|
return $ case exit of
|
|
|
|
ExitFailure _ -> Left out
|
|
|
|
ExitSuccess -> Right out
|
|
|
|
|
2017-01-22 12:19:46 +01:00
|
|
|
html2pdf :: Verbosity -- ^ Verbosity level
|
2017-09-12 05:18:42 +02:00
|
|
|
-> String -- ^ Program (wkhtmltopdf, weasyprint or prince)
|
|
|
|
-> [String] -- ^ Args to program
|
2017-06-10 23:39:49 +02:00
|
|
|
-> Text -- ^ HTML5 source
|
2015-12-21 22:13:44 -08:00
|
|
|
-> IO (Either ByteString ByteString)
|
2017-09-12 05:18:42 +02:00
|
|
|
html2pdf verbosity program args source = do
|
2015-12-21 22:13:44 -08:00
|
|
|
pdfFile <- withTempFile "." "html2pdf.pdf" $ \fp _ -> return fp
|
2017-10-27 21:29:22 -07:00
|
|
|
let pdfFileArgName = ["-o" | program == "prince"]
|
2017-09-12 05:18:42 +02:00
|
|
|
let programArgs = args ++ ["-"] ++ pdfFileArgName ++ [pdfFile]
|
2015-12-21 17:22:12 -08:00
|
|
|
env' <- getEnvironment
|
2017-01-22 12:19:46 +01:00
|
|
|
when (verbosity >= INFO) $ do
|
2015-12-21 17:22:12 -08:00
|
|
|
putStrLn "[makePDF] Command line:"
|
2017-09-12 05:18:42 +02:00
|
|
|
putStrLn $ program ++ " " ++ unwords (map show programArgs)
|
2015-12-21 17:22:12 -08:00
|
|
|
putStr "\n"
|
|
|
|
putStrLn "[makePDF] Environment:"
|
|
|
|
mapM_ print env'
|
|
|
|
putStr "\n"
|
2017-10-27 21:29:22 -07:00
|
|
|
putStrLn "[makePDF] Contents of intermediate HTML:"
|
2017-09-12 05:18:42 +02:00
|
|
|
TextIO.putStr source
|
2015-12-21 17:22:12 -08:00
|
|
|
putStr "\n"
|
2017-08-15 21:17:20 -07:00
|
|
|
(exit, out) <- E.catch
|
2017-09-12 05:18:42 +02:00
|
|
|
(pipeProcess (Just env') program programArgs $ BL.fromStrict $ UTF8.fromText source)
|
2017-08-15 21:17:20 -07:00
|
|
|
(\(e :: IOError) -> if isDoesNotExistError e
|
|
|
|
then E.throwIO $
|
2017-09-12 05:18:42 +02:00
|
|
|
PandocPDFProgramNotFoundError program
|
2017-08-15 21:17:20 -07:00
|
|
|
else E.throwIO e)
|
2017-01-22 12:19:46 +01:00
|
|
|
when (verbosity >= INFO) $ do
|
2017-06-18 11:17:00 +02:00
|
|
|
BL.hPutStr stdout out
|
2015-12-21 17:22:12 -08:00
|
|
|
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
|
2017-06-18 11:17:00 +02:00
|
|
|
res <- (Just . BL.fromChunks . (:[])) `fmap` BS.readFile pdfFile
|
2015-12-21 17:22:12 -08:00
|
|
|
removeFile pdfFile
|
|
|
|
return res
|
|
|
|
else return Nothing
|
|
|
|
return $ case (exit, mbPdf) of
|
2016-12-09 15:59:03 +01:00
|
|
|
(ExitFailure _, _) -> Left out
|
2015-12-21 17:22:12 -08:00
|
|
|
(ExitSuccess, Nothing) -> Left ""
|
|
|
|
(ExitSuccess, Just pdf) -> Right pdf
|
|
|
|
|
2017-01-22 12:19:46 +01:00
|
|
|
context2pdf :: Verbosity -- ^ Verbosity level
|
2015-10-20 08:15:12 -07:00
|
|
|
-> FilePath -- ^ temp directory for output
|
2017-06-10 23:39:49 +02:00
|
|
|
-> Text -- ^ ConTeXt source
|
2015-10-20 08:15:12 -07:00
|
|
|
-> IO (Either ByteString ByteString)
|
2017-01-22 12:19:46 +01:00
|
|
|
context2pdf verbosity tmpDir source = inDirectory tmpDir $ do
|
2015-10-20 08:15:12 -07:00
|
|
|
let file = "input.tex"
|
2017-06-10 23:39:49 +02:00
|
|
|
BS.writeFile file $ UTF8.fromText source
|
2015-10-20 08:15:12 -07:00
|
|
|
#ifdef _WINDOWS
|
|
|
|
-- note: we want / even on Windows, for TexLive
|
|
|
|
let tmpDir' = changePathSeparators tmpDir
|
|
|
|
#else
|
|
|
|
let tmpDir' = tmpDir
|
|
|
|
#endif
|
2015-11-22 07:42:11 -08:00
|
|
|
let programArgs = "--batchmode" : [file]
|
2015-10-20 08:15:12 -07:00
|
|
|
env' <- getEnvironment
|
2017-01-22 12:19:46 +01:00
|
|
|
when (verbosity >= INFO) $ do
|
2015-11-22 07:42:11 -08:00
|
|
|
putStrLn "[makePDF] temp dir:"
|
2015-10-20 08:15:12 -07:00
|
|
|
putStrLn tmpDir'
|
2015-11-22 07:42:11 -08:00
|
|
|
putStrLn "[makePDF] Command line:"
|
2015-10-20 08:15:12 -07:00
|
|
|
putStrLn $ "context" ++ " " ++ unwords (map show programArgs)
|
|
|
|
putStr "\n"
|
2015-11-22 07:42:11 -08:00
|
|
|
putStrLn "[makePDF] Environment:"
|
2017-02-24 14:34:58 +01:00
|
|
|
mapM_ print env'
|
2015-10-20 08:15:12 -07:00
|
|
|
putStr "\n"
|
|
|
|
putStrLn $ "[makePDF] Contents of " ++ file ++ ":"
|
2017-06-18 11:17:00 +02:00
|
|
|
BL.readFile file >>= BL.putStr
|
2015-10-20 08:15:12 -07:00
|
|
|
putStr "\n"
|
2017-08-15 21:17:20 -07:00
|
|
|
(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)
|
2017-01-22 12:19:46 +01:00
|
|
|
when (verbosity >= INFO) $ do
|
2017-06-18 11:17:00 +02:00
|
|
|
BL.hPutStr stdout out
|
2015-10-20 08:15:12 -07:00
|
|
|
putStr "\n"
|
|
|
|
let pdfFile = replaceExtension file ".pdf"
|
|
|
|
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.
|
2017-06-18 11:17:00 +02:00
|
|
|
then (Just . BL.fromChunks . (:[])) `fmap` BS.readFile pdfFile
|
2015-10-20 08:15:12 -07:00
|
|
|
else return Nothing
|
|
|
|
case (exit, mbPdf) of
|
|
|
|
(ExitFailure _, _) -> do
|
2016-12-09 15:59:03 +01:00
|
|
|
let logmsg = extractConTeXtMsg out
|
2015-10-20 08:15:12 -07:00
|
|
|
return $ Left logmsg
|
|
|
|
(ExitSuccess, Nothing) -> return $ Left ""
|
|
|
|
(ExitSuccess, Just pdf) -> return $ Right pdf
|