{-# LANGUAGE CPP                 #-}
{-# LANGUAGE LambdaCase          #-}
{-# LANGUAGE OverloadedStrings   #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE FlexibleContexts    #-}
{- |
   Module      : Text.Pandoc.PDF
   Copyright   : Copyright (C) 2012-2022 John MacFarlane
   License     : GNU GPL, version 2 or above

   Maintainer  : John MacFarlane <jgm@berkeley.edu>
   Stability   : alpha
   Portability : portable

Conversion of LaTeX documents to PDF.
-}
module Text.Pandoc.PDF ( makePDF ) where

import qualified Codec.Picture as JP
import qualified Control.Exception as E
import Control.Monad (when)
import Control.Monad.Trans (MonadIO (..))
import qualified Data.ByteString as BS
import Data.ByteString.Lazy (ByteString)
import qualified Data.ByteString.Lazy as BL
import qualified Data.ByteString.Lazy.Char8 as BC
import Data.Maybe (fromMaybe)
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import Data.Text.Lazy.Encoding (decodeUtf8')
import Text.Printf (printf)
import Data.Char (ord, isAscii, isSpace)
import System.Directory
import System.Environment
import System.Exit (ExitCode (..))
import System.FilePath
import System.IO (stderr, hClose)
import System.IO.Temp (withSystemTempDirectory, withTempDirectory,
                       withTempFile)
import qualified System.IO.Error as IE
import Text.DocLayout (literal)
import Text.Pandoc.Definition
import Text.Pandoc.Error (PandocError (PandocPDFProgramNotFoundError))
import Text.Pandoc.MIME (getMimeType)
import Text.Pandoc.Options (HTMLMathMethod (..), WriterOptions (..))
import Text.Pandoc.Extensions (disableExtension, Extension(Ext_smart))
import Text.Pandoc.Process (pipeProcess)
import System.Process (readProcessWithExitCode)
import Text.Pandoc.Shared (inDirectory, stringify, tshow)
import qualified Text.Pandoc.UTF8 as UTF8
import Text.Pandoc.Walk (walkM)
import Text.Pandoc.Writers.Shared (getField, metaToContext)
import Control.Monad.Catch (MonadMask)
import Data.Digest.Pure.SHA (sha1, showDigest)
#ifdef _WINDOWS
import Data.List (intercalate)
#endif
import Data.List (isPrefixOf, find)
import Text.Pandoc.Class (fillMediaBag, getVerbosity,
                          readFileLazy, readFileStrict, fileExists,
                          report, extractMedia, PandocMonad)
import Text.Pandoc.Logging

#ifdef _WINDOWS
changePathSeparators :: FilePath -> FilePath
changePathSeparators =
  -- We filter out backslashes because an initial `C:\` gets
  -- retained by `splitDirectories`, see #6173:
  intercalate "/" . map (filter (/='\\')) . splitDirectories
#endif

makePDF :: (PandocMonad m, MonadIO m, MonadMask m)
        => String              -- ^ pdf creator (pdflatex, lualatex, xelatex,
                               -- wkhtmltopdf, weasyprint, prince, context,
                               -- pdfroff, pagedjs,
                               -- or path to executable)
        -> [String]            -- ^ arguments to pass to pdf creator
        -> (WriterOptions -> Pandoc -> m Text)  -- ^ writer
        -> WriterOptions       -- ^ options
        -> Pandoc              -- ^ document
        -> m (Either ByteString ByteString)
makePDF :: forall (m :: * -> *).
(PandocMonad m, MonadIO m, MonadMask m) =>
String
-> [String]
-> (WriterOptions -> Pandoc -> m Text)
-> WriterOptions
-> Pandoc
-> m (Either ByteString ByteString)
makePDF String
program [String]
pdfargs WriterOptions -> Pandoc -> m Text
writer WriterOptions
opts Pandoc
doc =
  case String -> String
takeBaseName String
program of
    String
"wkhtmltopdf" -> forall (m :: * -> *).
(PandocMonad m, MonadIO m) =>
String
-> [String]
-> (WriterOptions -> Pandoc -> m Text)
-> WriterOptions
-> Pandoc
-> m (Either ByteString ByteString)
makeWithWkhtmltopdf String
program [String]
pdfargs WriterOptions -> Pandoc -> m Text
writer WriterOptions
opts Pandoc
doc
    String
prog | String
prog forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String
"pagedjs-cli" ,String
"weasyprint", String
"prince"] -> do
      Text
source <- WriterOptions -> Pandoc -> m Text
writer WriterOptions
opts Pandoc
doc
      Verbosity
verbosity <- forall (m :: * -> *). PandocMonad m => m Verbosity
getVerbosity
      forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ Verbosity
-> String -> [String] -> Text -> IO (Either ByteString ByteString)
html2pdf Verbosity
verbosity String
program [String]
pdfargs Text
source
    String
"pdfroff" -> do
      Text
source <- WriterOptions -> Pandoc -> m Text
writer WriterOptions
opts Pandoc
doc
      let args :: [String]
args   = [String
"-ms", String
"-mpdfmark", String
"-mspdf",
                    String
"-e", String
"-t", String
"-k", String
"-KUTF-8", String
"-i"] forall a. [a] -> [a] -> [a]
++ [String]
pdfargs
      forall (m :: * -> *).
(PandocMonad m, MonadIO m) =>
String -> [String] -> Text -> m (Either ByteString ByteString)
generic2pdf String
program [String]
args Text
source
    String
baseProg -> do
      forall (m :: * -> *) a.
(PandocMonad m, MonadMask m, MonadIO m) =>
String -> (String -> m a) -> m a
withTempDir String
"tex2pdf." forall a b. (a -> b) -> a -> b
$ \String
tmpdir' -> do
#ifdef _WINDOWS
        -- note:  we want / even on Windows, for TexLive
        let tmpdir = changePathSeparators tmpdir'
#else
        let tmpdir :: String
tmpdir = String
tmpdir'
#endif
        Pandoc
doc' <- forall (m :: * -> *).
(PandocMonad m, MonadIO m) =>
WriterOptions -> String -> Pandoc -> m Pandoc
handleImages WriterOptions
opts String
tmpdir Pandoc
doc
        Text
source <- WriterOptions -> Pandoc -> m Text
writer WriterOptions
opts{ writerExtensions :: Extensions
writerExtensions = -- disable use of quote
                                  -- ligatures to avoid bad ligatures like ?`
                                  Extension -> Extensions -> Extensions
disableExtension Extension
Ext_smart
                                   (WriterOptions -> Extensions
writerExtensions WriterOptions
opts) } Pandoc
doc'
        case String
baseProg of
          String
"context" -> forall (m :: * -> *).
(PandocMonad m, MonadIO m) =>
String
-> [String] -> String -> Text -> m (Either ByteString ByteString)
context2pdf String
program [String]
pdfargs String
tmpdir Text
source
          String
"tectonic" -> forall (m :: * -> *).
(PandocMonad m, MonadIO m) =>
String
-> [String] -> String -> Text -> m (Either ByteString ByteString)
tectonic2pdf String
program [String]
pdfargs String
tmpdir Text
source
          String
prog | String
prog forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String
"pdflatex", String
"lualatex", String
"xelatex", String
"latexmk"]
              -> forall (m :: * -> *).
(PandocMonad m, MonadIO m) =>
String
-> [String] -> String -> Text -> m (Either ByteString ByteString)
tex2pdf String
program [String]
pdfargs String
tmpdir Text
source
          String
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ String -> ByteString
UTF8.fromStringLazy
                             forall a b. (a -> b) -> a -> b
$ String
"Unknown program " forall a. [a] -> [a] -> [a]
++ String
program

-- latex has trouble with tildes in paths, which
-- you find in Windows temp dir paths with longer
-- user names (see #777)
withTempDir :: (PandocMonad m, MonadMask m, MonadIO m)
            => FilePath -> (FilePath -> m a) -> m a
withTempDir :: forall (m :: * -> *) a.
(PandocMonad m, MonadMask m, MonadIO m) =>
String -> (String -> m a) -> m a
withTempDir String
templ String -> m a
action = do
  String
tmp <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO String
getTemporaryDirectory
  Maybe String
uname <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => IO a -> (e -> IO a) -> IO a
E.catch
    (do (ExitCode
ec, String
sout, String
_) <- String -> [String] -> String -> IO (ExitCode, String, String)
readProcessWithExitCode String
"uname" [String
"-o"] String
""
        if ExitCode
ec forall a. Eq a => a -> a -> Bool
== ExitCode
ExitSuccess
           then forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
isSpace) String
sout
           else forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing)
    (\(SomeException
_  :: E.SomeException) -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing)
  if Char
'~' forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` String
tmp Bool -> Bool -> Bool
|| Maybe String
uname forall a. Eq a => a -> a -> Bool
== forall a. a -> Maybe a
Just String
"Cygwin" -- see #5451
         then forall (m :: * -> *) a.
(MonadMask m, MonadIO m) =>
String -> String -> (String -> m a) -> m a
withTempDirectory String
"." String
templ String -> m a
action
         else forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
String -> (String -> m a) -> m a
withSystemTempDirectory String
templ String -> m a
action

makeWithWkhtmltopdf :: (PandocMonad m, MonadIO m)
                    => String              -- ^ wkhtmltopdf or path
                    -> [String]            -- ^ arguments
                    -> (WriterOptions -> Pandoc -> m Text)  -- ^ writer
                    -> WriterOptions       -- ^ options
                    -> Pandoc              -- ^ document
                    -> m (Either ByteString ByteString)
makeWithWkhtmltopdf :: forall (m :: * -> *).
(PandocMonad m, MonadIO m) =>
String
-> [String]
-> (WriterOptions -> Pandoc -> m Text)
-> WriterOptions
-> Pandoc
-> m (Either ByteString ByteString)
makeWithWkhtmltopdf String
program [String]
pdfargs WriterOptions -> Pandoc -> m Text
writer WriterOptions
opts doc :: Pandoc
doc@(Pandoc Meta
meta [Block]
_) = do
  let mathArgs :: [String]
mathArgs = case WriterOptions -> HTMLMathMethod
writerHTMLMathMethod WriterOptions
opts of
                 -- with MathJax, wait til all math is rendered:
                      MathJax Text
_ -> [String
"--run-script", String
"MathJax.Hub.Register.StartupHook('End Typeset', function() { window.status = 'mathjax_loaded' });",
                                    String
"--window-status", String
"mathjax_loaded"]
                      HTMLMathMethod
_ -> []
  Context Text
meta' <- forall (m :: * -> *) a.
(Monad m, TemplateTarget a) =>
WriterOptions
-> ([Block] -> m (Doc a))
-> ([Inline] -> m (Doc a))
-> Meta
-> m (Context a)
metaToContext WriterOptions
opts
             (forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. HasChars a => a -> Doc a
literal forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Walkable Inline a => a -> Text
stringify)
             (forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. HasChars a => a -> Doc a
literal forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Walkable Inline a => a -> Text
stringify)
             Meta
meta
  let toArgs :: (String, Maybe Text) -> [String]
toArgs (String
f, Maybe Text
mbd) = forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Text
d -> [String
"--" forall a. Semigroup a => a -> a -> a
<> String
f, Text -> String
T.unpack Text
d]) Maybe Text
mbd
  let args :: [String]
args   = [String]
mathArgs forall a. [a] -> [a] -> [a]
++ forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (String, Maybe Text) -> [String]
toArgs
                 [(String
"page-size", forall a b. FromContext a b => Text -> Context a -> Maybe b
getField Text
"papersize" Context Text
meta')
                 ,(String
"title", forall a b. FromContext a b => Text -> Context a -> Maybe b
getField Text
"title" Context Text
meta')
                 ,(String
"margin-bottom", forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a -> a
fromMaybe Text
"1.2in"
                            (forall a b. FromContext a b => Text -> Context a -> Maybe b
getField Text
"margin-bottom" Context Text
meta'))
                 ,(String
"margin-top", forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a -> a
fromMaybe Text
"1.25in"
                            (forall a b. FromContext a b => Text -> Context a -> Maybe b
getField Text
"margin-top" Context Text
meta'))
                 ,(String
"margin-right", forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a -> a
fromMaybe Text
"1.25in"
                            (forall a b. FromContext a b => Text -> Context a -> Maybe b
getField Text
"margin-right" Context Text
meta'))
                 ,(String
"margin-left", forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a -> a
fromMaybe Text
"1.25in"
                            (forall a b. FromContext a b => Text -> Context a -> Maybe b
getField Text
"margin-left" Context Text
meta'))
                 ,(String
"footer-html", forall a b. FromContext a b => Text -> Context a -> Maybe b
getField Text
"footer-html" Context Text
meta')
                 ,(String
"header-html", forall a b. FromContext a b => Text -> Context a -> Maybe b
getField Text
"header-html" Context Text
meta')
                 ] forall a. [a] -> [a] -> [a]
++ (String
"--enable-local-file-access" forall a. a -> [a] -> [a]
: [String]
pdfargs)
                 -- see #6474
  Text
source <- WriterOptions -> Pandoc -> m Text
writer WriterOptions
opts Pandoc
doc
  Verbosity
verbosity <- forall (m :: * -> *). PandocMonad m => m Verbosity
getVerbosity
  forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ Verbosity
-> String -> [String] -> Text -> IO (Either ByteString ByteString)
html2pdf Verbosity
verbosity String
program [String]
args Text
source

handleImages :: (PandocMonad m, MonadIO m)
             => WriterOptions
             -> FilePath      -- ^ temp dir to store images
             -> Pandoc        -- ^ document
             -> m Pandoc
handleImages :: forall (m :: * -> *).
(PandocMonad m, MonadIO m) =>
WriterOptions -> String -> Pandoc -> m Pandoc
handleImages WriterOptions
opts String
tmpdir Pandoc
doc =
  forall (m :: * -> *). PandocMonad m => Pandoc -> m Pandoc
fillMediaBag Pandoc
doc forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
    forall (m :: * -> *).
(PandocMonad m, MonadIO m) =>
String -> Pandoc -> m Pandoc
extractMedia String
tmpdir forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
    forall a b (m :: * -> *).
(Walkable a b, Monad m, Applicative m, Functor m) =>
(a -> m a) -> b -> m b
walkM (forall (m :: * -> *).
(PandocMonad m, MonadIO m) =>
WriterOptions -> String -> Inline -> m Inline
convertImages WriterOptions
opts String
tmpdir)

convertImages :: (PandocMonad m, MonadIO m)
              => WriterOptions -> FilePath -> Inline -> m Inline
convertImages :: forall (m :: * -> *).
(PandocMonad m, MonadIO m) =>
WriterOptions -> String -> Inline -> m Inline
convertImages WriterOptions
opts String
tmpdir (Image Attr
attr [Inline]
ils (Text
src, Text
tit)) = do
  Either Text String
img <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ WriterOptions -> String -> String -> IO (Either Text String)
convertImage WriterOptions
opts String
tmpdir forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack Text
src
  Text
newPath <-
    case Either Text String
img of
      Left Text
e -> do
        forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report forall a b. (a -> b) -> a -> b
$ Text -> Text -> LogMessage
CouldNotConvertImage Text
src Text
e
        forall (m :: * -> *) a. Monad m => a -> m a
return Text
src
      Right String
fp -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
fp
  forall (m :: * -> *) a. Monad m => a -> m a
return (Attr -> [Inline] -> (Text, Text) -> Inline
Image Attr
attr [Inline]
ils (Text
newPath, Text
tit))
convertImages WriterOptions
_ String
_ Inline
x = forall (m :: * -> *) a. Monad m => a -> m a
return Inline
x

-- Convert formats which do not work well in pdf to png
convertImage :: WriterOptions -> FilePath -> FilePath
             -> IO (Either Text FilePath)
convertImage :: WriterOptions -> String -> String -> IO (Either Text String)
convertImage WriterOptions
opts String
tmpdir String
fname = do
  let dpi :: String
dpi = forall a. Show a => a -> String
show forall a b. (a -> b) -> a -> b
$ WriterOptions -> Int
writerDpi WriterOptions
opts
  case Maybe Text
mime of
    Just Text
"image/png" -> forall {a}. IO (Either a String)
doNothing
    Just Text
"image/jpeg" -> forall {a}. IO (Either a String)
doNothing
    Just Text
"application/pdf" -> forall {a}. IO (Either a String)
doNothing
    -- Note: eps is converted by pdflatex using epstopdf.pl
    Just Text
"application/eps" -> forall {a}. IO (Either a String)
doNothing
    Just Text
"image/svg+xml" -> forall e a. Exception e => IO a -> (e -> IO a) -> IO a
E.catch (do
      (ExitCode
exit, ByteString
_) <- Maybe [(String, String)]
-> String -> [String] -> ByteString -> IO (ExitCode, ByteString)
pipeProcess forall a. Maybe a
Nothing String
"rsvg-convert"
                     [String
"-f",String
"pdf",String
"-a",String
"--dpi-x",String
dpi,String
"--dpi-y",String
dpi,
                      String
"-o",String
pdfOut,String
svgIn] ByteString
BL.empty
      if ExitCode
exit forall a. Eq a => a -> a -> Bool
== ExitCode
ExitSuccess
         then forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. b -> Either a b
Right String
pdfOut
         else forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left Text
"conversion from SVG failed")
      (\(SomeException
e :: E.SomeException) -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$
          Text
"check that rsvg-convert is in path.\n" forall a. Semigroup a => a -> a -> a
<>
          forall a. Show a => a -> Text
tshow SomeException
e)
    Maybe Text
_ -> String -> IO (Either String DynamicImage)
JP.readImage String
fname forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
               Left String
e    -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
e
               Right DynamicImage
img ->
                 forall e a. Exception e => IO a -> (e -> IO a) -> IO a
E.catch (forall a b. b -> Either a b
Right String
pngOut forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ String -> DynamicImage -> IO ()
JP.savePngImage String
pngOut DynamicImage
img) forall a b. (a -> b) -> a -> b
$
                     \(SomeException
e :: E.SomeException) -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. a -> Either a b
Left (forall a. Show a => a -> Text
tshow SomeException
e))
  where
    sha :: String
sha = forall t. Digest t -> String
showDigest (ByteString -> Digest SHA1State
sha1 (String -> ByteString
UTF8.fromStringLazy String
fname))
    pngOut :: String
pngOut = String -> String
normalise forall a b. (a -> b) -> a -> b
$ String
tmpdir String -> String -> String
</> String
sha String -> String -> String
<.> String
"png"
    pdfOut :: String
pdfOut = String -> String
normalise forall a b. (a -> b) -> a -> b
$ String
tmpdir String -> String -> String
</> String
sha String -> String -> String
<.> String
"pdf"
    svgIn :: String
svgIn = String -> String
normalise String
fname
    mime :: Maybe Text
mime = String -> Maybe Text
getMimeType String
fname
    doNothing :: IO (Either a String)
doNothing = forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. b -> Either a b
Right String
fname)

tectonic2pdf :: (PandocMonad m, MonadIO m)
             => String                          -- ^ tex program
             -> [String]                        -- ^ Arguments to the latex-engine
             -> FilePath                        -- ^ temp directory for output
             -> Text                            -- ^ tex source
             -> m (Either ByteString ByteString)
tectonic2pdf :: forall (m :: * -> *).
(PandocMonad m, MonadIO m) =>
String
-> [String] -> String -> Text -> m (Either ByteString ByteString)
tectonic2pdf String
program [String]
args String
tmpDir Text
source = do
  (ExitCode
exit, ByteString
log', Maybe ByteString
mbPdf) <- forall (m :: * -> *).
(PandocMonad m, MonadIO m) =>
String
-> [String]
-> String
-> Text
-> m (ExitCode, ByteString, Maybe ByteString)
runTectonic String
program [String]
args String
tmpDir Text
source
  case (ExitCode
exit, Maybe ByteString
mbPdf) of
       (ExitFailure Int
_, Maybe ByteString
_)      -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
extractMsg ByteString
log'
       (ExitCode
ExitSuccess, Maybe ByteString
Nothing)  -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left ByteString
""
       (ExitCode
ExitSuccess, Just ByteString
pdf) -> do
          forall (m :: * -> *). PandocMonad m => ByteString -> m ()
missingCharacterWarnings ByteString
log'
          forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. b -> Either a b
Right ByteString
pdf

tex2pdf :: (PandocMonad m, MonadIO m)
        => String                          -- ^ tex program
        -> [String]                        -- ^ Arguments to the latex-engine
        -> FilePath                        -- ^ temp directory for output
        -> Text                            -- ^ tex source
        -> m (Either ByteString ByteString)
tex2pdf :: forall (m :: * -> *).
(PandocMonad m, MonadIO m) =>
String
-> [String] -> String -> Text -> m (Either ByteString ByteString)
tex2pdf String
program [String]
args String
tmpDir Text
source = do
  let numruns :: Int
numruns | String -> String
takeBaseName String
program forall a. Eq a => a -> a -> Bool
== String
"latexmk"        = Int
1
              | Text
"\\tableofcontents" Text -> Text -> Bool
`T.isInfixOf` Text
source = Int
3  -- to get page numbers
              | Bool
otherwise                                = Int
2  -- 1 run won't give you PDF bookmarks
  (ExitCode
exit, ByteString
log', Maybe ByteString
mbPdf) <- forall (m :: * -> *).
(PandocMonad m, MonadIO m) =>
String
-> [String]
-> Int
-> String
-> Text
-> m (ExitCode, ByteString, Maybe ByteString)
runTeXProgram String
program [String]
args Int
numruns String
tmpDir Text
source
  case (ExitCode
exit, Maybe ByteString
mbPdf) of
       (ExitFailure Int
_, Maybe ByteString
_)      -> do
          let logmsg :: ByteString
logmsg = ByteString -> ByteString
extractMsg ByteString
log'
          let extramsg :: ByteString
extramsg =
                case ByteString
logmsg of
                     ByteString
x | ByteString
"! Package inputenc Error" ByteString -> ByteString -> Bool
`BC.isPrefixOf` ByteString
x
                           Bool -> Bool -> Bool
&& String
program forall a. Eq a => a -> a -> Bool
/= String
"xelatex"
                       -> ByteString
"\nTry running pandoc with --pdf-engine=xelatex."
                     ByteString
_ -> ByteString
""
          forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ ByteString
logmsg forall a. Semigroup a => a -> a -> a
<> ByteString
extramsg
       (ExitCode
ExitSuccess, Maybe ByteString
Nothing)  -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left ByteString
""
       (ExitCode
ExitSuccess, Just ByteString
pdf) -> do
          forall (m :: * -> *). PandocMonad m => ByteString -> m ()
missingCharacterWarnings ByteString
log'
          forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. b -> Either a b
Right ByteString
pdf

missingCharacterWarnings :: PandocMonad m => ByteString -> m ()
missingCharacterWarnings :: forall (m :: * -> *). PandocMonad m => ByteString -> m ()
missingCharacterWarnings ByteString
log' = do
  let ls :: [ByteString]
ls = ByteString -> [ByteString]
BC.lines ByteString
log'
  let isMissingCharacterWarning :: ByteString -> Bool
isMissingCharacterWarning = ByteString -> ByteString -> Bool
BC.isPrefixOf ByteString
"Missing character: "
  let toCodePoint :: Char -> Text
toCodePoint Char
c
        | Char -> Bool
isAscii Char
c   = Char -> Text
T.singleton Char
c
        | Bool
otherwise   = String -> Text
T.pack forall a b. (a -> b) -> a -> b
$ Char
c forall a. a -> [a] -> [a]
: String
" (U+" forall a. [a] -> [a] -> [a]
++ forall r. PrintfType r => String -> r
printf String
"%04X" (Char -> Int
ord Char
c) forall a. [a] -> [a] -> [a]
++ String
")"
  let addCodePoint :: Text -> Text
addCodePoint = (Char -> Text) -> Text -> Text
T.concatMap Char -> Text
toCodePoint
  let warnings :: [Text]
warnings = [ Text -> Text
addCodePoint (ByteString -> Text
utf8ToText (Int64 -> ByteString -> ByteString
BC.drop Int64
19 ByteString
l))
                 | ByteString
l <- [ByteString]
ls
                 , ByteString -> Bool
isMissingCharacterWarning ByteString
l
                 ]
  forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> LogMessage
MissingCharacter) [Text]
warnings

-- parsing output

extractMsg :: ByteString -> ByteString
extractMsg :: ByteString -> ByteString
extractMsg ByteString
log' = do
  let msg' :: [ByteString]
msg'  = forall a. (a -> Bool) -> [a] -> [a]
dropWhile (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString
"!" ByteString -> ByteString -> Bool
`BC.isPrefixOf`)) forall a b. (a -> b) -> a -> b
$ ByteString -> [ByteString]
BC.lines ByteString
log'
  let ([ByteString]
msg'',[ByteString]
rest) = forall a. (a -> Bool) -> [a] -> ([a], [a])
break (ByteString
"l." ByteString -> ByteString -> Bool
`BC.isPrefixOf`) [ByteString]
msg'
  let lineno :: [ByteString]
lineno = forall a. Int -> [a] -> [a]
take Int
1 [ByteString]
rest
  if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ByteString]
msg'
     then ByteString
log'
     else [ByteString] -> ByteString
BC.unlines ([ByteString]
msg'' forall a. [a] -> [a] -> [a]
++ [ByteString]
lineno)

extractConTeXtMsg :: ByteString -> ByteString
extractConTeXtMsg :: ByteString -> ByteString
extractConTeXtMsg ByteString
log' = do
  let msg' :: [ByteString]
msg'  = forall a. Int -> [a] -> [a]
take Int
1 forall a b. (a -> b) -> a -> b
$
              forall a. (a -> Bool) -> [a] -> [a]
dropWhile (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString
"tex error" ByteString -> ByteString -> Bool
`BC.isPrefixOf`)) forall a b. (a -> b) -> a -> b
$ ByteString -> [ByteString]
BC.lines ByteString
log'
  if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ByteString]
msg'
     then ByteString
log'
     else [ByteString] -> ByteString
BC.unlines [ByteString]
msg'

-- running tex programs

runTectonic :: (PandocMonad m, MonadIO m)
            => String -> [String] -> FilePath
              -> Text -> m (ExitCode, ByteString, Maybe ByteString)
runTectonic :: forall (m :: * -> *).
(PandocMonad m, MonadIO m) =>
String
-> [String]
-> String
-> Text
-> m (ExitCode, ByteString, Maybe ByteString)
runTectonic String
program [String]
args' String
tmpDir' Text
source = do
    let getOutDir :: [a] -> [a] -> ([a], Maybe a)
getOutDir [a]
acc (a
a:a
b:[a]
xs) = if a
a forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [a
"-o", a
"--outdir"]
                                    then (forall a. [a] -> [a]
reverse [a]
acc forall a. [a] -> [a] -> [a]
++ [a]
xs, forall a. a -> Maybe a
Just a
b)
                                    else [a] -> [a] -> ([a], Maybe a)
getOutDir (a
bforall a. a -> [a] -> [a]
:a
aforall a. a -> [a] -> [a]
:[a]
acc) [a]
xs
        getOutDir [a]
acc [a]
xs = (forall a. [a] -> [a]
reverse [a]
acc forall a. [a] -> [a] -> [a]
++ [a]
xs, forall a. Maybe a
Nothing)
        ([String]
args, Maybe String
outDir) = forall {a}. (Eq a, IsString a) => [a] -> [a] -> ([a], Maybe a)
getOutDir [] [String]
args'
        tmpDir :: String
tmpDir = forall a. a -> Maybe a -> a
fromMaybe String
tmpDir' Maybe String
outDir
    forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ Bool -> String -> IO ()
createDirectoryIfMissing Bool
True String
tmpDir
    -- run tectonic on stdin so it reads \include commands from $PWD instead of a temp directory
    let sourceBL :: ByteString
sourceBL = ByteString -> ByteString
BL.fromStrict forall a b. (a -> b) -> a -> b
$ Text -> ByteString
UTF8.fromText Text
source
    let programArgs :: [String]
programArgs = [String
"--outdir", String
tmpDir] forall a. [a] -> [a] -> [a]
++ [String]
args forall a. [a] -> [a] -> [a]
++ [String
"-"]
    [(String, String)]
env <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO [(String, String)]
getEnvironment
    Verbosity
verbosity <- forall (m :: * -> *). PandocMonad m => m Verbosity
getVerbosity
    forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Verbosity
verbosity forall a. Ord a => a -> a -> Bool
>= Verbosity
INFO) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$
      Maybe String
-> String -> [String] -> [(String, String)] -> Text -> IO ()
showVerboseInfo (forall a. a -> Maybe a
Just String
tmpDir) String
program [String]
programArgs [(String, String)]
env
         (ByteString -> Text
utf8ToText ByteString
sourceBL)
    (ExitCode
exit, ByteString
out) <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => IO a -> (e -> IO a) -> IO a
E.catch
      (Maybe [(String, String)]
-> String -> [String] -> ByteString -> IO (ExitCode, ByteString)
pipeProcess (forall a. a -> Maybe a
Just [(String, String)]
env) String
program [String]
programArgs ByteString
sourceBL)
      (forall a. String -> IOError -> IO a
handlePDFProgramNotFound String
program)
    forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Verbosity
verbosity forall a. Ord a => a -> a -> Bool
>= Verbosity
INFO) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
      Handle -> Text -> IO ()
UTF8.hPutStrLn Handle
stderr Text
"[makePDF] Running"
      Handle -> ByteString -> IO ()
BL.hPutStr Handle
stderr ByteString
out
      Handle -> Text -> IO ()
UTF8.hPutStr Handle
stderr Text
"\n"
    let pdfFile :: String
pdfFile = String
tmpDir forall a. [a] -> [a] -> [a]
++ String
"/texput.pdf"
    (Maybe ByteString
_, Maybe ByteString
pdf) <- forall (m :: * -> *).
(PandocMonad m, MonadIO m) =>
Maybe String -> String -> m (Maybe ByteString, Maybe ByteString)
getResultingPDF forall a. Maybe a
Nothing String
pdfFile
    forall (m :: * -> *) a. Monad m => a -> m a
return (ExitCode
exit, ByteString
out, Maybe ByteString
pdf)

-- read a pdf that has been written to a temporary directory, and optionally read
-- logs
getResultingPDF :: (PandocMonad m, MonadIO m)
                => Maybe String -> String
                -> m (Maybe ByteString, Maybe ByteString)
getResultingPDF :: forall (m :: * -> *).
(PandocMonad m, MonadIO m) =>
Maybe String -> String -> m (Maybe ByteString, Maybe ByteString)
getResultingPDF Maybe String
logFile String
pdfFile = do
    Bool
pdfExists <- forall (m :: * -> *). PandocMonad m => String -> m Bool
fileExists String
pdfFile
    Maybe ByteString
pdf <- if Bool
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 (forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> ByteString
BL.fromChunks forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. a -> [a] -> [a]
:[])) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap`
                   (forall (m :: * -> *). PandocMonad m => String -> m ByteString
readFileStrict String
pdfFile)
              else forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
    -- Note that some things like Missing character warnings
    -- appear in the log but not on stderr, so we prefer the log:
    Maybe ByteString
log' <- case Maybe String
logFile of
              Just String
logFile' -> do
                Bool
logExists <- forall (m :: * -> *). PandocMonad m => String -> m Bool
fileExists String
logFile'
                if Bool
logExists
                  then forall a. a -> Maybe a
Just forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *). PandocMonad m => String -> m ByteString
readFileLazy String
logFile'
                  else forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
              Maybe String
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
    forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe ByteString
log', Maybe ByteString
pdf)

-- Run a TeX program on an input bytestring and return (exit code,
-- contents of stdout, contents of produced PDF if any).  Rerun
-- a fixed number of times to resolve references.
runTeXProgram :: (PandocMonad m, MonadIO m)
              => String -> [String] -> Int -> FilePath
              -> Text -> m (ExitCode, ByteString, Maybe ByteString)
runTeXProgram :: forall (m :: * -> *).
(PandocMonad m, MonadIO m) =>
String
-> [String]
-> Int
-> String
-> Text
-> m (ExitCode, ByteString, Maybe ByteString)
runTeXProgram String
program [String]
args Int
numRuns String
tmpDir' Text
source = do
    let isOutdirArg :: String -> Bool
isOutdirArg String
x = String
"-outdir=" forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
x Bool -> Bool -> Bool
||
                        String
"-output-directory=" forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
x
    let tmpDir :: String
tmpDir =
          case forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find String -> Bool
isOutdirArg [String]
args of
            Just String
x  -> forall a. Int -> [a] -> [a]
drop Int
1 forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
dropWhile (forall a. Eq a => a -> a -> Bool
/=Char
'=') String
x
            Maybe String
Nothing -> String
tmpDir'
    forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ Bool -> String -> IO ()
createDirectoryIfMissing Bool
True String
tmpDir
    let file :: String
file = String
tmpDir forall a. [a] -> [a] -> [a]
++ String
"/input.tex"  -- note: tmpDir has / path separators
    forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ String -> ByteString -> IO ()
BS.writeFile String
file forall a b. (a -> b) -> a -> b
$ Text -> ByteString
UTF8.fromText Text
source
    let isLatexMk :: Bool
isLatexMk = String -> String
takeBaseName String
program forall a. Eq a => a -> a -> Bool
== String
"latexmk"
        programArgs :: [String]
programArgs | Bool
isLatexMk = [String
"-interaction=batchmode", String
"-halt-on-error", String
"-pdf",
                                   String
"-quiet", String
"-outdir=" forall a. [a] -> [a] -> [a]
++ String
tmpDir] forall a. [a] -> [a] -> [a]
++ [String]
args forall a. [a] -> [a] -> [a]
++ [String
file]
                    | Bool
otherwise = [String
"-halt-on-error", String
"-interaction", String
"nonstopmode",
                                   String
"-output-directory", String
tmpDir] forall a. [a] -> [a] -> [a]
++ [String]
args forall a. [a] -> [a] -> [a]
++ [String
file]
    [(String, String)]
env' <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO [(String, String)]
getEnvironment
    let sep :: String
sep = [Char
searchPathSeparator]
    let texinputs :: String
texinputs = forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String
tmpDir forall a. [a] -> [a] -> [a]
++ String
sep) ((String
tmpDir forall a. [a] -> [a] -> [a]
++ String
sep) forall a. [a] -> [a] -> [a]
++)
          forall a b. (a -> b) -> a -> b
$ forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup String
"TEXINPUTS" [(String, String)]
env'
    let env'' :: [(String, String)]
env'' = (String
"TEXINPUTS", String
texinputs) forall a. a -> [a] -> [a]
:
                (String
"TEXMFOUTPUT", String
tmpDir) forall a. a -> [a] -> [a]
:
                  [(String
k,String
v) | (String
k,String
v) <- [(String, String)]
env'
                         , String
k forall a. Eq a => a -> a -> Bool
/= String
"TEXINPUTS" Bool -> Bool -> Bool
&& String
k forall a. Eq a => a -> a -> Bool
/= String
"TEXMFOUTPUT"]
    Verbosity
verbosity <- forall (m :: * -> *). PandocMonad m => m Verbosity
getVerbosity
    forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Verbosity
verbosity forall a. Ord a => a -> a -> Bool
>= Verbosity
INFO) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$
        String -> IO Text
UTF8.readFile String
file forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
         Maybe String
-> String -> [String] -> [(String, String)] -> Text -> IO ()
showVerboseInfo (forall a. a -> Maybe a
Just String
tmpDir) String
program [String]
programArgs [(String, String)]
env''
    let runTeX :: Int -> m (ExitCode, ByteString, Maybe ByteString)
runTeX Int
runNumber = do
          (ExitCode
exit, ByteString
out) <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => IO a -> (e -> IO a) -> IO a
E.catch
            (Maybe [(String, String)]
-> String -> [String] -> ByteString -> IO (ExitCode, ByteString)
pipeProcess (forall a. a -> Maybe a
Just [(String, String)]
env'') String
program [String]
programArgs ByteString
BL.empty)
            (forall a. String -> IOError -> IO a
handlePDFProgramNotFound String
program)
          forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Verbosity
verbosity forall a. Ord a => a -> a -> Bool
>= Verbosity
INFO) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
            Handle -> Text -> IO ()
UTF8.hPutStrLn Handle
stderr forall a b. (a -> b) -> a -> b
$ Text
"[makePDF] Run #" forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> Text
tshow Int
runNumber
            Handle -> ByteString -> IO ()
BL.hPutStr Handle
stderr ByteString
out
            Handle -> Text -> IO ()
UTF8.hPutStr Handle
stderr Text
"\n"
          if Int
runNumber forall a. Ord a => a -> a -> Bool
< Int
numRuns
             then Int -> m (ExitCode, ByteString, Maybe ByteString)
runTeX (Int
runNumber forall a. Num a => a -> a -> a
+ Int
1)
             else do
               let logFile :: String
logFile = String -> String -> String
replaceExtension String
file String
".log"
               let pdfFile :: String
pdfFile = String -> String -> String
replaceExtension String
file String
".pdf"
               (Maybe ByteString
log', Maybe ByteString
pdf) <- forall (m :: * -> *).
(PandocMonad m, MonadIO m) =>
Maybe String -> String -> m (Maybe ByteString, Maybe ByteString)
getResultingPDF (forall a. a -> Maybe a
Just String
logFile) String
pdfFile
               forall (m :: * -> *) a. Monad m => a -> m a
return (ExitCode
exit, forall a. a -> Maybe a -> a
fromMaybe ByteString
out Maybe ByteString
log', Maybe ByteString
pdf)
    forall {m :: * -> *}.
(MonadIO m, PandocMonad m) =>
Int -> m (ExitCode, ByteString, Maybe ByteString)
runTeX Int
1

generic2pdf :: (PandocMonad m, MonadIO m)
            => String
            -> [String]
            -> Text
            -> m (Either ByteString ByteString)
generic2pdf :: forall (m :: * -> *).
(PandocMonad m, MonadIO m) =>
String -> [String] -> Text -> m (Either ByteString ByteString)
generic2pdf String
program [String]
args Text
source = do
  [(String, String)]
env' <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO [(String, String)]
getEnvironment
  Verbosity
verbosity <- forall (m :: * -> *). PandocMonad m => m Verbosity
getVerbosity
  forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Verbosity
verbosity forall a. Ord a => a -> a -> Bool
>= Verbosity
INFO) forall a b. (a -> b) -> a -> b
$
    forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ Maybe String
-> String -> [String] -> [(String, String)] -> Text -> IO ()
showVerboseInfo forall a. Maybe a
Nothing String
program [String]
args [(String, String)]
env' Text
source
  (ExitCode
exit, ByteString
out) <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => IO a -> (e -> IO a) -> IO a
E.catch
    (Maybe [(String, String)]
-> String -> [String] -> ByteString -> IO (ExitCode, ByteString)
pipeProcess (forall a. a -> Maybe a
Just [(String, String)]
env') String
program [String]
args
                     (ByteString -> ByteString
BL.fromStrict forall a b. (a -> b) -> a -> b
$ Text -> ByteString
UTF8.fromText Text
source))
    (forall a. String -> IOError -> IO a
handlePDFProgramNotFound String
program)
  forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ case ExitCode
exit of
             ExitFailure Int
_ -> forall a b. a -> Either a b
Left ByteString
out
             ExitCode
ExitSuccess   -> forall a b. b -> Either a b
Right ByteString
out


html2pdf  :: Verbosity    -- ^ Verbosity level
          -> String       -- ^ Program (wkhtmltopdf, weasyprint, prince, or path)
          -> [String]     -- ^ Args to program
          -> Text         -- ^ HTML5 source
          -> IO (Either ByteString ByteString)
html2pdf :: Verbosity
-> String -> [String] -> Text -> IO (Either ByteString ByteString)
html2pdf Verbosity
verbosity String
program [String]
args Text
source =
  -- 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.
  forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
String -> String -> (String -> Handle -> m a) -> m a
withTempFile String
"." String
"html2pdf.html" forall a b. (a -> b) -> a -> b
$ \String
file Handle
h1 ->
    forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
String -> String -> (String -> Handle -> m a) -> m a
withTempFile String
"." String
"html2pdf.pdf" forall a b. (a -> b) -> a -> b
$ \String
pdfFile Handle
h2 -> do
      Handle -> IO ()
hClose Handle
h1
      Handle -> IO ()
hClose Handle
h2
      String -> ByteString -> IO ()
BS.writeFile String
file forall a b. (a -> b) -> a -> b
$ Text -> ByteString
UTF8.fromText Text
source
      let pdfFileArgName :: [String]
pdfFileArgName = [String
"-o" | String -> String
takeBaseName String
program forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem`
                                   [String
"pagedjs-cli", String
"prince"]]
      let programArgs :: [String]
programArgs = [String]
args forall a. [a] -> [a] -> [a]
++ [String
file] forall a. [a] -> [a] -> [a]
++ [String]
pdfFileArgName forall a. [a] -> [a] -> [a]
++ [String
pdfFile]
      [(String, String)]
env' <- IO [(String, String)]
getEnvironment
      forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Verbosity
verbosity forall a. Ord a => a -> a -> Bool
>= Verbosity
INFO) forall a b. (a -> b) -> a -> b
$
        String -> IO Text
UTF8.readFile String
file forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
          Maybe String
-> String -> [String] -> [(String, String)] -> Text -> IO ()
showVerboseInfo forall a. Maybe a
Nothing String
program [String]
programArgs [(String, String)]
env'
      (ExitCode
exit, ByteString
out) <- forall e a. Exception e => IO a -> (e -> IO a) -> IO a
E.catch
        (Maybe [(String, String)]
-> String -> [String] -> ByteString -> IO (ExitCode, ByteString)
pipeProcess (forall a. a -> Maybe a
Just [(String, String)]
env') String
program [String]
programArgs ByteString
BL.empty)
        (forall a. String -> IOError -> IO a
handlePDFProgramNotFound String
program)
      forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Verbosity
verbosity forall a. Ord a => a -> a -> Bool
>= Verbosity
INFO) forall a b. (a -> b) -> a -> b
$ do
        Handle -> ByteString -> IO ()
BL.hPutStr Handle
stderr ByteString
out
        Handle -> Text -> IO ()
UTF8.hPutStr Handle
stderr Text
"\n"
      Bool
pdfExists <- String -> IO Bool
doesFileExist String
pdfFile
      Maybe ByteString
mbPdf <- if Bool
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 forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> ByteString
BL.fromChunks forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. a -> [a] -> [a]
:[]) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO ByteString
BS.readFile String
pdfFile
                else forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
      forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ case (ExitCode
exit, Maybe ByteString
mbPdf) of
                 (ExitFailure Int
_, Maybe ByteString
_)      -> forall a b. a -> Either a b
Left ByteString
out
                 (ExitCode
ExitSuccess, Maybe ByteString
Nothing)  -> forall a b. a -> Either a b
Left ByteString
""
                 (ExitCode
ExitSuccess, Just ByteString
pdf) -> forall a b. b -> Either a b
Right ByteString
pdf

context2pdf :: (PandocMonad m, MonadIO m)
            => String       -- ^ "context" or path to it
            -> [String]     -- ^ extra arguments
            -> FilePath     -- ^ temp directory for output
            -> Text         -- ^ ConTeXt source
            -> m (Either ByteString ByteString)
context2pdf :: forall (m :: * -> *).
(PandocMonad m, MonadIO m) =>
String
-> [String] -> String -> Text -> m (Either ByteString ByteString)
context2pdf String
program [String]
pdfargs String
tmpDir Text
source = do
  Verbosity
verbosity <- forall (m :: * -> *). PandocMonad m => m Verbosity
getVerbosity
  forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
inDirectory String
tmpDir forall a b. (a -> b) -> a -> b
$ do
    let file :: String
file = String
"input.tex"
    String -> ByteString -> IO ()
BS.writeFile String
file forall a b. (a -> b) -> a -> b
$ Text -> ByteString
UTF8.fromText Text
source
    let programArgs :: [String]
programArgs = String
"--batchmode" forall a. a -> [a] -> [a]
: [String]
pdfargs forall a. [a] -> [a] -> [a]
++ [String
file]
    [(String, String)]
env' <- IO [(String, String)]
getEnvironment
    forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Verbosity
verbosity forall a. Ord a => a -> a -> Bool
>= Verbosity
INFO) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$
      String -> IO Text
UTF8.readFile String
file forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
        Maybe String
-> String -> [String] -> [(String, String)] -> Text -> IO ()
showVerboseInfo (forall a. a -> Maybe a
Just String
tmpDir) String
program [String]
programArgs [(String, String)]
env'
    (ExitCode
exit, ByteString
out) <- forall e a. Exception e => IO a -> (e -> IO a) -> IO a
E.catch
      (Maybe [(String, String)]
-> String -> [String] -> ByteString -> IO (ExitCode, ByteString)
pipeProcess (forall a. a -> Maybe a
Just [(String, String)]
env') String
program [String]
programArgs ByteString
BL.empty)
      (forall a. String -> IOError -> IO a
handlePDFProgramNotFound String
program)
    forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Verbosity
verbosity forall a. Ord a => a -> a -> Bool
>= Verbosity
INFO) forall a b. (a -> b) -> a -> b
$ do
      Handle -> ByteString -> IO ()
BL.hPutStr Handle
stderr ByteString
out
      Handle -> Text -> IO ()
UTF8.hPutStr Handle
stderr Text
"\n"
    let pdfFile :: String
pdfFile = String -> String -> String
replaceExtension String
file String
".pdf"
    Bool
pdfExists <- String -> IO Bool
doesFileExist String
pdfFile
    Maybe ByteString
mbPdf <- if Bool
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 (forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> ByteString
BL.fromChunks forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. a -> [a] -> [a]
:[])) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` String -> IO ByteString
BS.readFile String
pdfFile
              else forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
    case (ExitCode
exit, Maybe ByteString
mbPdf) of
         (ExitFailure Int
_, Maybe ByteString
_)      -> do
            let logmsg :: ByteString
logmsg = ByteString -> ByteString
extractConTeXtMsg ByteString
out
            forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left ByteString
logmsg
         (ExitCode
ExitSuccess, Maybe ByteString
Nothing)  -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left ByteString
""
         (ExitCode
ExitSuccess, Just ByteString
pdf) -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. b -> Either a b
Right ByteString
pdf


showVerboseInfo :: Maybe FilePath
                -> String
                -> [String]
                -> [(String, String)]
                -> Text
                -> IO ()
showVerboseInfo :: Maybe String
-> String -> [String] -> [(String, String)] -> Text -> IO ()
showVerboseInfo Maybe String
mbTmpDir String
program [String]
programArgs [(String, String)]
env Text
source = do
  case Maybe String
mbTmpDir of
    Just String
tmpDir -> do
      Handle -> Text -> IO ()
UTF8.hPutStrLn Handle
stderr Text
"[makePDF] temp dir:"
      Handle -> Text -> IO ()
UTF8.hPutStrLn Handle
stderr (String -> Text
T.pack String
tmpDir)
    Maybe String
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return ()
  Handle -> Text -> IO ()
UTF8.hPutStrLn Handle
stderr Text
"[makePDF] Command line:"
  Handle -> Text -> IO ()
UTF8.hPutStrLn Handle
stderr forall a b. (a -> b) -> a -> b
$
       String -> Text
T.pack String
program forall a. Semigroup a => a -> a -> a
<> Text
" " forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack ([String] -> String
unwords (forall a b. (a -> b) -> [a] -> [b]
map forall a. Show a => a -> String
show [String]
programArgs))
  Handle -> Text -> IO ()
UTF8.hPutStr Handle
stderr Text
"\n"
  Handle -> Text -> IO ()
UTF8.hPutStrLn Handle
stderr Text
"[makePDF] Relevant environment variables:"
  -- we filter out irrelevant stuff to avoid leaking passwords and keys!
  let isRelevant :: (a, b) -> Bool
isRelevant (a
"PATH",b
_) = Bool
True
      isRelevant (a
"TMPDIR",b
_) = Bool
True
      isRelevant (a
"PWD",b
_) = Bool
True
      isRelevant (a
"LANG",b
_) = Bool
True
      isRelevant (a
"HOME",b
_) = Bool
True
      isRelevant (a
"LUA_PATH",b
_) = Bool
True
      isRelevant (a
"LUA_CPATH",b
_) = Bool
True
      isRelevant (a
"SHELL",b
_) = Bool
True
      isRelevant (a
"TEXINPUTS",b
_) = Bool
True
      isRelevant (a
"TEXMFOUTPUT",b
_) = Bool
True
      isRelevant (a, b)
_ = Bool
False
  forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Handle -> Text -> IO ()
UTF8.hPutStrLn Handle
stderr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> Text
tshow) (forall a. (a -> Bool) -> [a] -> [a]
filter forall {a} {b}. (Eq a, IsString a) => (a, b) -> Bool
isRelevant [(String, String)]
env)
  Handle -> Text -> IO ()
UTF8.hPutStr Handle
stderr Text
"\n"
  Handle -> Text -> IO ()
UTF8.hPutStrLn Handle
stderr Text
"[makePDF] Source:"
  Handle -> Text -> IO ()
UTF8.hPutStrLn Handle
stderr Text
source

handlePDFProgramNotFound :: String -> IE.IOError -> IO a
handlePDFProgramNotFound :: forall a. String -> IOError -> IO a
handlePDFProgramNotFound String
program IOError
e
  | IOError -> Bool
IE.isDoesNotExistError IOError
e =
      forall e a. Exception e => e -> IO a
E.throwIO forall a b. (a -> b) -> a -> b
$ Text -> PandocError
PandocPDFProgramNotFoundError forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
program
  | Bool
otherwise = forall e a. Exception e => e -> IO a
E.throwIO IOError
e

utf8ToText :: ByteString -> Text
utf8ToText :: ByteString -> Text
utf8ToText ByteString
lbs =
  case ByteString -> Either UnicodeException Text
decodeUtf8' ByteString
lbs of
    Left UnicodeException
_  -> String -> Text
T.pack forall a b. (a -> b) -> a -> b
$ ByteString -> String
BC.unpack ByteString
lbs  -- if decoding fails, treat as latin1
    Right Text
t -> Text -> Text
TL.toStrict Text
t