{-# LANGUAGE CPP                 #-}
{-# LANGUAGE LambdaCase          #-}
{-# LANGUAGE OverloadedStrings   #-}
{-# LANGUAGE ScopedTypeVariables #-}
{- |
   Module      : Text.Pandoc.PDF
   Copyright   : Copyright (C) 2012-2021 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)
#ifdef _WINDOWS
import Data.List (intercalate)
#endif
import Data.List (isPrefixOf, find)
import Text.Pandoc.Class.PandocIO (PandocIO, extractMedia, runIOorExplode)
import Text.Pandoc.Class.PandocMonad (fillMediaBag, getCommonState, getVerbosity,
                                      putCommonState, report, setVerbosity)
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 :: String              -- ^ pdf creator (pdflatex, lualatex, xelatex,
                               -- 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 :: String
-> [String]
-> (WriterOptions -> Pandoc -> PandocIO Text)
-> WriterOptions
-> Pandoc
-> PandocIO (Either ByteString ByteString)
makePDF String
program [String]
pdfargs WriterOptions -> Pandoc -> PandocIO Text
writer WriterOptions
opts Pandoc
doc =
  case String -> String
takeBaseName String
program of
    String
"wkhtmltopdf" -> String
-> [String]
-> (WriterOptions -> Pandoc -> PandocIO Text)
-> WriterOptions
-> Pandoc
-> PandocIO (Either ByteString ByteString)
makeWithWkhtmltopdf String
program [String]
pdfargs WriterOptions -> Pandoc -> PandocIO Text
writer WriterOptions
opts Pandoc
doc
    String
prog | String
prog String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String
"weasyprint", String
"prince"] -> do
      Text
source <- WriterOptions -> Pandoc -> PandocIO Text
writer WriterOptions
opts Pandoc
doc
      Verbosity
verbosity <- PandocIO Verbosity
forall (m :: * -> *). PandocMonad m => m Verbosity
getVerbosity
      IO (Either ByteString ByteString)
-> PandocIO (Either ByteString ByteString)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Either ByteString ByteString)
 -> PandocIO (Either ByteString ByteString))
-> IO (Either ByteString ByteString)
-> PandocIO (Either ByteString ByteString)
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 -> PandocIO 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"] [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
pdfargs
      Verbosity
verbosity <- PandocIO Verbosity
forall (m :: * -> *). PandocMonad m => m Verbosity
getVerbosity
      IO (Either ByteString ByteString)
-> PandocIO (Either ByteString ByteString)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Either ByteString ByteString)
 -> PandocIO (Either ByteString ByteString))
-> IO (Either ByteString ByteString)
-> PandocIO (Either ByteString ByteString)
forall a b. (a -> b) -> a -> b
$ Verbosity
-> String -> [String] -> Text -> IO (Either ByteString ByteString)
generic2pdf Verbosity
verbosity String
program [String]
args Text
source
    String
baseProg -> do
      CommonState
commonState <- PandocIO CommonState
forall (m :: * -> *). PandocMonad m => m CommonState
getCommonState
      Verbosity
verbosity <- PandocIO Verbosity
forall (m :: * -> *). PandocMonad m => m Verbosity
getVerbosity
      -- latex has trouble with tildes in paths, which
      -- you find in Windows temp dir paths with longer
      -- user names (see #777)
      let withTempDir :: String -> (String -> IO a) -> IO a
withTempDir String
templ String -> IO a
action = do
            String
tmp <- IO String
getTemporaryDirectory
            Maybe String
uname <- IO (Maybe String)
-> (SomeException -> IO (Maybe String)) -> IO (Maybe String)
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 ExitCode -> ExitCode -> Bool
forall a. Eq a => a -> a -> Bool
== ExitCode
ExitSuccess
                     then Maybe String -> IO (Maybe String)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe String -> IO (Maybe String))
-> Maybe String -> IO (Maybe String)
forall a b. (a -> b) -> a -> b
$ String -> Maybe String
forall a. a -> Maybe a
Just (String -> Maybe String) -> String -> Maybe String
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
isSpace) String
sout
                     else Maybe String -> IO (Maybe String)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe String
forall a. Maybe a
Nothing)
              (\(SomeException
_ :: E.SomeException) -> Maybe String -> IO (Maybe String)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe String
forall a. Maybe a
Nothing)
            if Char
'~' Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` String
tmp Bool -> Bool -> Bool
|| Maybe String
uname Maybe String -> Maybe String -> Bool
forall a. Eq a => a -> a -> Bool
== String -> Maybe String
forall a. a -> Maybe a
Just String
"Cygwin" -- see #5451
                   then String -> String -> (String -> IO a) -> IO a
forall (m :: * -> *) a.
(MonadMask m, MonadIO m) =>
String -> String -> (String -> m a) -> m a
withTempDirectory String
"." String
templ String -> IO a
action
                   else String -> (String -> IO a) -> IO a
forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
String -> (String -> m a) -> m a
withSystemTempDirectory String
templ String -> IO a
action
      (CommonState
newCommonState, Either ByteString ByteString
res) <- IO (CommonState, Either ByteString ByteString)
-> PandocIO (CommonState, Either ByteString ByteString)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (CommonState, Either ByteString ByteString)
 -> PandocIO (CommonState, Either ByteString ByteString))
-> IO (CommonState, Either ByteString ByteString)
-> PandocIO (CommonState, Either ByteString ByteString)
forall a b. (a -> b) -> a -> b
$ String
-> (String -> IO (CommonState, Either ByteString ByteString))
-> IO (CommonState, Either ByteString ByteString)
forall a. String -> (String -> IO a) -> IO a
withTempDir String
"tex2pdf." ((String -> IO (CommonState, Either ByteString ByteString))
 -> IO (CommonState, Either ByteString ByteString))
-> (String -> IO (CommonState, Either ByteString ByteString))
-> IO (CommonState, Either ByteString ByteString)
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
        PandocIO (CommonState, Either ByteString ByteString)
-> IO (CommonState, Either ByteString ByteString)
forall a. PandocIO a -> IO a
runIOorExplode (PandocIO (CommonState, Either ByteString ByteString)
 -> IO (CommonState, Either ByteString ByteString))
-> PandocIO (CommonState, Either ByteString ByteString)
-> IO (CommonState, Either ByteString ByteString)
forall a b. (a -> b) -> a -> b
$ do
          CommonState -> PandocIO ()
forall (m :: * -> *). PandocMonad m => CommonState -> m ()
putCommonState CommonState
commonState
          Pandoc
doc' <- WriterOptions -> String -> Pandoc -> PandocIO Pandoc
handleImages WriterOptions
opts String
tmpdir Pandoc
doc
          Text
source <- WriterOptions -> Pandoc -> PandocIO 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'
          Either ByteString ByteString
res <- case String
baseProg of
            String
"context" -> Verbosity
-> String
-> [String]
-> String
-> Text
-> PandocIO (Either ByteString ByteString)
context2pdf Verbosity
verbosity String
program [String]
pdfargs String
tmpdir Text
source
            String
"tectonic" -> Verbosity
-> String
-> [String]
-> String
-> Text
-> PandocIO (Either ByteString ByteString)
tectonic2pdf Verbosity
verbosity String
program [String]
pdfargs String
tmpdir Text
source
            String
prog | String
prog String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String
"pdflatex", String
"lualatex", String
"xelatex", String
"latexmk"]
                -> Verbosity
-> String
-> [String]
-> String
-> Text
-> PandocIO (Either ByteString ByteString)
tex2pdf Verbosity
verbosity String
program [String]
pdfargs String
tmpdir Text
source
            String
_ -> Either ByteString ByteString
-> PandocIO (Either ByteString ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either ByteString ByteString
 -> PandocIO (Either ByteString ByteString))
-> Either ByteString ByteString
-> PandocIO (Either ByteString ByteString)
forall a b. (a -> b) -> a -> b
$ ByteString -> Either ByteString ByteString
forall a b. a -> Either a b
Left (ByteString -> Either ByteString ByteString)
-> ByteString -> Either ByteString ByteString
forall a b. (a -> b) -> a -> b
$ String -> ByteString
UTF8.fromStringLazy
                               (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
$ String
"Unknown program " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
program
          CommonState
cs <- PandocIO CommonState
forall (m :: * -> *). PandocMonad m => m CommonState
getCommonState
          (CommonState, Either ByteString ByteString)
-> PandocIO (CommonState, Either ByteString ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (CommonState
cs, Either ByteString ByteString
res)
      CommonState -> PandocIO ()
forall (m :: * -> *). PandocMonad m => CommonState -> m ()
putCommonState CommonState
newCommonState
      Either ByteString ByteString
-> PandocIO (Either ByteString ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return Either ByteString ByteString
res

makeWithWkhtmltopdf :: String              -- ^ wkhtmltopdf or path
                    -> [String]            -- ^ arguments
                    -> (WriterOptions -> Pandoc -> PandocIO Text)  -- ^ writer
                    -> WriterOptions       -- ^ options
                    -> Pandoc              -- ^ document
                    -> PandocIO (Either ByteString ByteString)
makeWithWkhtmltopdf :: String
-> [String]
-> (WriterOptions -> Pandoc -> PandocIO Text)
-> WriterOptions
-> Pandoc
-> PandocIO (Either ByteString ByteString)
makeWithWkhtmltopdf String
program [String]
pdfargs WriterOptions -> Pandoc -> PandocIO 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' <- WriterOptions
-> ([Block] -> PandocIO (Doc Text))
-> ([Inline] -> PandocIO (Doc Text))
-> Meta
-> PandocIO (Context Text)
forall (m :: * -> *) a.
(Monad m, TemplateTarget a) =>
WriterOptions
-> ([Block] -> m (Doc a))
-> ([Inline] -> m (Doc a))
-> Meta
-> m (Context a)
metaToContext WriterOptions
opts
             (Doc Text -> PandocIO (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> PandocIO (Doc Text))
-> ([Block] -> Doc Text) -> [Block] -> PandocIO (Doc Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal (Text -> Doc Text) -> ([Block] -> Text) -> [Block] -> Doc Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Block] -> Text
forall a. Walkable Inline a => a -> Text
stringify)
             (Doc Text -> PandocIO (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> PandocIO (Doc Text))
-> ([Inline] -> Doc Text) -> [Inline] -> PandocIO (Doc Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal (Text -> Doc Text) -> ([Inline] -> Text) -> [Inline] -> Doc Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inline] -> Text
forall a. Walkable Inline a => a -> Text
stringify)
             Meta
meta
  let toArgs :: (String, Maybe Text) -> [String]
toArgs (String
f, Maybe Text
mbd) = [String] -> (Text -> [String]) -> Maybe Text -> [String]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Text
d -> [String
"--" String -> String -> 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 [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ ((String, Maybe Text) -> [String])
-> [(String, Maybe Text)] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (String, Maybe Text) -> [String]
toArgs
                 [(String
"page-size", Text -> Context Text -> Maybe Text
forall a b. FromContext a b => Text -> Context a -> Maybe b
getField Text
"papersize" Context Text
meta')
                 ,(String
"title", Text -> Context Text -> Maybe Text
forall a b. FromContext a b => Text -> Context a -> Maybe b
getField Text
"title" Context Text
meta')
                 ,(String
"margin-bottom", Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"1.2in"
                            (Text -> Context Text -> Maybe Text
forall a b. FromContext a b => Text -> Context a -> Maybe b
getField Text
"margin-bottom" Context Text
meta'))
                 ,(String
"margin-top", Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"1.25in"
                            (Text -> Context Text -> Maybe Text
forall a b. FromContext a b => Text -> Context a -> Maybe b
getField Text
"margin-top" Context Text
meta'))
                 ,(String
"margin-right", Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"1.25in"
                            (Text -> Context Text -> Maybe Text
forall a b. FromContext a b => Text -> Context a -> Maybe b
getField Text
"margin-right" Context Text
meta'))
                 ,(String
"margin-left", Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"1.25in"
                            (Text -> Context Text -> Maybe Text
forall a b. FromContext a b => Text -> Context a -> Maybe b
getField Text
"margin-left" Context Text
meta'))
                 ,(String
"footer-html", Text -> Context Text -> Maybe Text
forall a b. FromContext a b => Text -> Context a -> Maybe b
getField Text
"footer-html" Context Text
meta')
                 ,(String
"header-html", Text -> Context Text -> Maybe Text
forall a b. FromContext a b => Text -> Context a -> Maybe b
getField Text
"header-html" Context Text
meta')
                 ] [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ (String
"--enable-local-file-access" String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
pdfargs)
                 -- see #6474
  Text
source <- WriterOptions -> Pandoc -> PandocIO Text
writer WriterOptions
opts Pandoc
doc
  Verbosity
verbosity <- PandocIO Verbosity
forall (m :: * -> *). PandocMonad m => m Verbosity
getVerbosity
  IO (Either ByteString ByteString)
-> PandocIO (Either ByteString ByteString)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Either ByteString ByteString)
 -> PandocIO (Either ByteString ByteString))
-> IO (Either ByteString ByteString)
-> PandocIO (Either ByteString ByteString)
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 :: WriterOptions
             -> FilePath      -- ^ temp dir to store images
             -> Pandoc        -- ^ document
             -> PandocIO Pandoc
handleImages :: WriterOptions -> String -> Pandoc -> PandocIO Pandoc
handleImages WriterOptions
opts String
tmpdir Pandoc
doc =
  Pandoc -> PandocIO Pandoc
forall (m :: * -> *). PandocMonad m => Pandoc -> m Pandoc
fillMediaBag Pandoc
doc PandocIO Pandoc -> (Pandoc -> PandocIO Pandoc) -> PandocIO Pandoc
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
    String -> Pandoc -> PandocIO Pandoc
extractMedia String
tmpdir PandocIO Pandoc -> (Pandoc -> PandocIO Pandoc) -> PandocIO Pandoc
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
    (Inline -> PandocIO Inline) -> Pandoc -> PandocIO Pandoc
forall a b (m :: * -> *).
(Walkable a b, Monad m, Applicative m, Functor m) =>
(a -> m a) -> b -> m b
walkM (WriterOptions -> String -> Inline -> PandocIO Inline
convertImages WriterOptions
opts String
tmpdir)

convertImages :: WriterOptions -> FilePath -> Inline -> PandocIO Inline
convertImages :: WriterOptions -> String -> Inline -> PandocIO Inline
convertImages WriterOptions
opts String
tmpdir (Image Attr
attr [Inline]
ils (Text
src, Text
tit)) = do
  Either Text String
img <- IO (Either Text String) -> PandocIO (Either Text String)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Either Text String) -> PandocIO (Either Text String))
-> IO (Either Text String) -> PandocIO (Either Text String)
forall a b. (a -> b) -> a -> b
$ WriterOptions -> String -> String -> IO (Either Text String)
convertImage WriterOptions
opts String
tmpdir (String -> IO (Either Text String))
-> String -> IO (Either Text String)
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
        LogMessage -> PandocIO ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> PandocIO ()) -> LogMessage -> PandocIO ()
forall a b. (a -> b) -> a -> b
$ Text -> Text -> LogMessage
CouldNotConvertImage Text
src Text
e
        Text -> PandocIO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
src
      Right String
fp -> Text -> PandocIO Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> PandocIO Text) -> Text -> PandocIO Text
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
fp
  Inline -> PandocIO Inline
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 = Inline -> PandocIO Inline
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 = Int -> String
forall a. Show a => a -> String
show (Int -> String) -> Int -> String
forall a b. (a -> b) -> a -> b
$ WriterOptions -> Int
writerDpi WriterOptions
opts
  case Maybe Text
mime of
    Just Text
"image/png" -> IO (Either Text String)
forall a. IO (Either a String)
doNothing
    Just Text
"image/jpeg" -> IO (Either Text String)
forall a. IO (Either a String)
doNothing
    Just Text
"application/pdf" -> IO (Either Text String)
forall a. IO (Either a String)
doNothing
    -- Note: eps is converted by pdflatex using epstopdf.pl
    Just Text
"application/eps" -> IO (Either Text String)
forall a. IO (Either a String)
doNothing
    Just Text
"image/svg+xml" -> IO (Either Text String)
-> (SomeException -> IO (Either Text String))
-> IO (Either Text String)
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 Maybe [(String, String)]
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
fname] ByteString
BL.empty
      if ExitCode
exit ExitCode -> ExitCode -> Bool
forall a. Eq a => a -> a -> Bool
== ExitCode
ExitSuccess
         then Either Text String -> IO (Either Text String)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either Text String -> IO (Either Text String))
-> Either Text String -> IO (Either Text String)
forall a b. (a -> b) -> a -> b
$ String -> Either Text String
forall a b. b -> Either a b
Right String
pdfOut
         else Either Text String -> IO (Either Text String)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either Text String -> IO (Either Text String))
-> Either Text String -> IO (Either Text String)
forall a b. (a -> b) -> a -> b
$ Text -> Either Text String
forall a b. a -> Either a b
Left Text
"conversion from SVG failed")
      (\(SomeException
e :: E.SomeException) -> Either Text String -> IO (Either Text String)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either Text String -> IO (Either Text String))
-> Either Text String -> IO (Either Text String)
forall a b. (a -> b) -> a -> b
$ Text -> Either Text String
forall a b. a -> Either a b
Left (Text -> Either Text String) -> Text -> Either Text String
forall a b. (a -> b) -> a -> b
$
          Text
"check that rsvg-convert is in path.\n" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
          SomeException -> Text
forall a. Show a => a -> Text
tshow SomeException
e)
    Maybe Text
_ -> String -> IO (Either String DynamicImage)
JP.readImage String
fname IO (Either String DynamicImage)
-> (Either String DynamicImage -> IO (Either Text String))
-> IO (Either Text String)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
               Left String
e    -> Either Text String -> IO (Either Text String)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either Text String -> IO (Either Text String))
-> Either Text String -> IO (Either Text String)
forall a b. (a -> b) -> a -> b
$ Text -> Either Text String
forall a b. a -> Either a b
Left (Text -> Either Text String) -> Text -> Either Text String
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
e
               Right DynamicImage
img ->
                 IO (Either Text String)
-> (SomeException -> IO (Either Text String))
-> IO (Either Text String)
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
E.catch (String -> Either Text String
forall a b. b -> Either a b
Right String
pngOut Either Text String -> IO () -> IO (Either Text String)
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ String -> DynamicImage -> IO ()
JP.savePngImage String
pngOut DynamicImage
img) ((SomeException -> IO (Either Text String))
 -> IO (Either Text String))
-> (SomeException -> IO (Either Text String))
-> IO (Either Text String)
forall a b. (a -> b) -> a -> b
$
                     \(SomeException
e :: E.SomeException) -> Either Text String -> IO (Either Text String)
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Either Text String
forall a b. a -> Either a b
Left (SomeException -> Text
forall a. Show a => a -> Text
tshow SomeException
e))
  where
    pngOut :: String
pngOut = String -> String -> String
replaceDirectory (String -> String -> String
replaceExtension String
fname String
".png") String
tmpdir
    pdfOut :: String
pdfOut = String -> String -> String
replaceDirectory (String -> String -> String
replaceExtension String
fname String
".pdf") String
tmpdir
    mime :: Maybe Text
mime = String -> Maybe Text
getMimeType String
fname
    doNothing :: IO (Either a String)
doNothing = Either a String -> IO (Either a String)
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Either a String
forall a b. b -> Either a b
Right String
fname)

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

tex2pdf :: Verbosity                       -- ^ Verbosity level
        -> String                          -- ^ tex program
        -> [String]                        -- ^ Arguments to the latex-engine
        -> FilePath                        -- ^ temp directory for output
        -> Text                            -- ^ tex source
        -> PandocIO (Either ByteString ByteString)
tex2pdf :: Verbosity
-> String
-> [String]
-> String
-> Text
-> PandocIO (Either ByteString ByteString)
tex2pdf Verbosity
verbosity String
program [String]
args String
tmpDir Text
source = do
  let numruns :: Int
numruns | String -> String
takeBaseName String
program String -> String -> Bool
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) <- Verbosity
-> String
-> [String]
-> Int
-> String
-> Text
-> PandocIO (ExitCode, ByteString, Maybe ByteString)
runTeXProgram Verbosity
verbosity 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 String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
"xelatex"
                       -> ByteString
"\nTry running pandoc with --pdf-engine=xelatex."
                     ByteString
_ -> ByteString
""
          Either ByteString ByteString
-> PandocIO (Either ByteString ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either ByteString ByteString
 -> PandocIO (Either ByteString ByteString))
-> Either ByteString ByteString
-> PandocIO (Either ByteString ByteString)
forall a b. (a -> b) -> a -> b
$ ByteString -> Either ByteString ByteString
forall a b. a -> Either a b
Left (ByteString -> Either ByteString ByteString)
-> ByteString -> Either ByteString ByteString
forall a b. (a -> b) -> a -> b
$ ByteString
logmsg ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
extramsg
       (ExitCode
ExitSuccess, Maybe ByteString
Nothing)  -> Either ByteString ByteString
-> PandocIO (Either ByteString ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either ByteString ByteString
 -> PandocIO (Either ByteString ByteString))
-> Either ByteString ByteString
-> PandocIO (Either ByteString ByteString)
forall a b. (a -> b) -> a -> b
$ ByteString -> Either ByteString ByteString
forall a b. a -> Either a b
Left ByteString
""
       (ExitCode
ExitSuccess, Just ByteString
pdf) -> do
          Verbosity -> ByteString -> PandocIO ()
missingCharacterWarnings Verbosity
verbosity ByteString
log'
          Either ByteString ByteString
-> PandocIO (Either ByteString ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either ByteString ByteString
 -> PandocIO (Either ByteString ByteString))
-> Either ByteString ByteString
-> PandocIO (Either ByteString ByteString)
forall a b. (a -> b) -> a -> b
$ ByteString -> Either ByteString ByteString
forall a b. b -> Either a b
Right ByteString
pdf

missingCharacterWarnings :: Verbosity -> ByteString -> PandocIO ()
missingCharacterWarnings :: Verbosity -> ByteString -> PandocIO ()
missingCharacterWarnings Verbosity
verbosity 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 (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Char
c Char -> String -> String
forall a. a -> [a] -> [a]
: String
" (U+" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> Int -> String
forall r. PrintfType r => String -> r
printf String
"%04X" (Char -> Int
ord Char
c) String -> String -> String
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
                 ]
  Verbosity -> PandocIO ()
forall (m :: * -> *). PandocMonad m => Verbosity -> m ()
setVerbosity Verbosity
verbosity
  (Text -> PandocIO ()) -> [Text] -> PandocIO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (LogMessage -> PandocIO ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> PandocIO ())
-> (Text -> LogMessage) -> Text -> PandocIO ()
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'  = (ByteString -> Bool) -> [ByteString] -> [ByteString]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (Bool -> Bool
not (Bool -> Bool) -> (ByteString -> Bool) -> ByteString -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString
"!" ByteString -> ByteString -> Bool
`BC.isPrefixOf`)) ([ByteString] -> [ByteString]) -> [ByteString] -> [ByteString]
forall a b. (a -> b) -> a -> b
$ ByteString -> [ByteString]
BC.lines ByteString
log'
  let ([ByteString]
msg'',[ByteString]
rest) = (ByteString -> Bool)
-> [ByteString] -> ([ByteString], [ByteString])
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (ByteString
"l." ByteString -> ByteString -> Bool
`BC.isPrefixOf`) [ByteString]
msg'
  let lineno :: [ByteString]
lineno = Int -> [ByteString] -> [ByteString]
forall a. Int -> [a] -> [a]
take Int
1 [ByteString]
rest
  if [ByteString] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ByteString]
msg'
     then ByteString
log'
     else [ByteString] -> ByteString
BC.unlines ([ByteString]
msg'' [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString]
lineno)

extractConTeXtMsg :: ByteString -> ByteString
extractConTeXtMsg :: ByteString -> ByteString
extractConTeXtMsg ByteString
log' = do
  let msg' :: [ByteString]
msg'  = Int -> [ByteString] -> [ByteString]
forall a. Int -> [a] -> [a]
take Int
1 ([ByteString] -> [ByteString]) -> [ByteString] -> [ByteString]
forall a b. (a -> b) -> a -> b
$
              (ByteString -> Bool) -> [ByteString] -> [ByteString]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (Bool -> Bool
not (Bool -> Bool) -> (ByteString -> Bool) -> ByteString -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString
"tex error" ByteString -> ByteString -> Bool
`BC.isPrefixOf`)) ([ByteString] -> [ByteString]) -> [ByteString] -> [ByteString]
forall a b. (a -> b) -> a -> b
$ ByteString -> [ByteString]
BC.lines ByteString
log'
  if [ByteString] -> Bool
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 :: Verbosity -> String -> [String] -> FilePath
              -> Text -> PandocIO (ExitCode, ByteString, Maybe ByteString)
runTectonic :: Verbosity
-> String
-> [String]
-> String
-> Text
-> PandocIO (ExitCode, ByteString, Maybe ByteString)
runTectonic Verbosity
verbosity 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 a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [a
"-o", a
"--outdir"]
                                    then ([a] -> [a]
forall a. [a] -> [a]
reverse [a]
acc [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ [a]
xs, a -> Maybe a
forall a. a -> Maybe a
Just a
b)
                                    else [a] -> [a] -> ([a], Maybe a)
getOutDir (a
ba -> [a] -> [a]
forall a. a -> [a] -> [a]
:a
aa -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
acc) [a]
xs
        getOutDir [a]
acc [a]
xs = ([a] -> [a]
forall a. [a] -> [a]
reverse [a]
acc [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ [a]
xs, Maybe a
forall a. Maybe a
Nothing)
        ([String]
args, Maybe String
outDir) = [String] -> [String] -> ([String], Maybe String)
forall a. (Eq a, IsString a) => [a] -> [a] -> ([a], Maybe a)
getOutDir [] [String]
args'
        tmpDir :: String
tmpDir = String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
tmpDir' Maybe String
outDir
    IO () -> PandocIO ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> PandocIO ()) -> IO () -> PandocIO ()
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 (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ Text -> ByteString
UTF8.fromText Text
source
    let programArgs :: [String]
programArgs = [String
"--outdir", String
tmpDir] [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
args [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
"-"]
    [(String, String)]
env <- IO [(String, String)] -> PandocIO [(String, String)]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO [(String, String)]
getEnvironment
    Bool -> PandocIO () -> PandocIO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Verbosity
verbosity Verbosity -> Verbosity -> Bool
forall a. Ord a => a -> a -> Bool
>= Verbosity
INFO) (PandocIO () -> PandocIO ()) -> PandocIO () -> PandocIO ()
forall a b. (a -> b) -> a -> b
$ IO () -> PandocIO ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> PandocIO ()) -> IO () -> PandocIO ()
forall a b. (a -> b) -> a -> b
$
      Maybe String
-> String -> [String] -> [(String, String)] -> Text -> IO ()
showVerboseInfo (String -> Maybe String
forall a. a -> Maybe a
Just String
tmpDir) String
program [String]
programArgs [(String, String)]
env
         (ByteString -> Text
utf8ToText ByteString
sourceBL)
    (ExitCode
exit, ByteString
out) <- IO (ExitCode, ByteString) -> PandocIO (ExitCode, ByteString)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (ExitCode, ByteString) -> PandocIO (ExitCode, ByteString))
-> IO (ExitCode, ByteString) -> PandocIO (ExitCode, ByteString)
forall a b. (a -> b) -> a -> b
$ IO (ExitCode, ByteString)
-> (IOError -> IO (ExitCode, ByteString))
-> IO (ExitCode, ByteString)
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
E.catch
      (Maybe [(String, String)]
-> String -> [String] -> ByteString -> IO (ExitCode, ByteString)
pipeProcess ([(String, String)] -> Maybe [(String, String)]
forall a. a -> Maybe a
Just [(String, String)]
env) String
program [String]
programArgs ByteString
sourceBL)
      (String -> IOError -> IO (ExitCode, ByteString)
forall a. String -> IOError -> IO a
handlePDFProgramNotFound String
program)
    Bool -> PandocIO () -> PandocIO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Verbosity
verbosity Verbosity -> Verbosity -> Bool
forall a. Ord a => a -> a -> Bool
>= Verbosity
INFO) (PandocIO () -> PandocIO ()) -> PandocIO () -> PandocIO ()
forall a b. (a -> b) -> a -> b
$ IO () -> PandocIO ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> PandocIO ()) -> IO () -> PandocIO ()
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 String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"/texput.pdf"
    (Maybe ByteString
_, Maybe ByteString
pdf) <- Maybe String
-> String -> PandocIO (Maybe ByteString, Maybe ByteString)
getResultingPDF Maybe String
forall a. Maybe a
Nothing String
pdfFile
    (ExitCode, ByteString, Maybe ByteString)
-> PandocIO (ExitCode, ByteString, Maybe ByteString)
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 :: Maybe String -> String -> PandocIO (Maybe ByteString, Maybe ByteString)
getResultingPDF :: Maybe String
-> String -> PandocIO (Maybe ByteString, Maybe ByteString)
getResultingPDF Maybe String
logFile String
pdfFile = do
    Bool
pdfExists <- IO Bool -> PandocIO Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> PandocIO Bool) -> IO Bool -> PandocIO Bool
forall a b. (a -> b) -> a -> b
$ String -> IO Bool
doesFileExist 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 (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString)
-> (ByteString -> ByteString) -> ByteString -> Maybe ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> ByteString
BL.fromChunks ([ByteString] -> ByteString)
-> (ByteString -> [ByteString]) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
:[])) (ByteString -> Maybe ByteString)
-> PandocIO ByteString -> PandocIO (Maybe ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap`
                   IO ByteString -> PandocIO ByteString
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (String -> IO ByteString
BS.readFile String
pdfFile)
              else Maybe ByteString -> PandocIO (Maybe ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ByteString
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 <- IO Bool -> PandocIO Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> PandocIO Bool) -> IO Bool -> PandocIO Bool
forall a b. (a -> b) -> a -> b
$ String -> IO Bool
doesFileExist String
logFile'
                if Bool
logExists
                  then IO (Maybe ByteString) -> PandocIO (Maybe ByteString)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe ByteString) -> PandocIO (Maybe ByteString))
-> IO (Maybe ByteString) -> PandocIO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString)
-> IO ByteString -> IO (Maybe ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO ByteString
BL.readFile String
logFile'
                  else Maybe ByteString -> PandocIO (Maybe ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ByteString
forall a. Maybe a
Nothing
              Maybe String
Nothing -> Maybe ByteString -> PandocIO (Maybe ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ByteString
forall a. Maybe a
Nothing
    (Maybe ByteString, Maybe ByteString)
-> PandocIO (Maybe ByteString, Maybe ByteString)
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 :: Verbosity -> String -> [String] -> Int -> FilePath
              -> Text -> PandocIO (ExitCode, ByteString, Maybe ByteString)
runTeXProgram :: Verbosity
-> String
-> [String]
-> Int
-> String
-> Text
-> PandocIO (ExitCode, ByteString, Maybe ByteString)
runTeXProgram Verbosity
verbosity String
program [String]
args Int
numRuns String
tmpDir' Text
source = do
    let isOutdirArg :: String -> Bool
isOutdirArg String
x = String
"-outdir=" String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
x Bool -> Bool -> Bool
||
                        String
"-output-directory=" String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
x
    let tmpDir :: String
tmpDir =
          case (String -> Bool) -> [String] -> Maybe String
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find String -> Bool
isOutdirArg [String]
args of
            Just String
x  -> Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/=Char
'=') String
x
            Maybe String
Nothing -> String
tmpDir'
    IO () -> PandocIO ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> PandocIO ()) -> IO () -> PandocIO ()
forall a b. (a -> b) -> a -> b
$ Bool -> String -> IO ()
createDirectoryIfMissing Bool
True String
tmpDir
    let file :: String
file = String
tmpDir String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"/input.tex"  -- note: tmpDir has / path separators
    IO () -> PandocIO ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> PandocIO ()) -> IO () -> PandocIO ()
forall a b. (a -> b) -> a -> b
$ String -> ByteString -> IO ()
BS.writeFile String
file (ByteString -> IO ()) -> ByteString -> IO ()
forall a b. (a -> b) -> a -> b
$ Text -> ByteString
UTF8.fromText Text
source
    let isLatexMk :: Bool
isLatexMk = String -> String
takeBaseName String
program String -> String -> Bool
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=" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
tmpDir] [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
args [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
file]
                    | Bool
otherwise = [String
"-halt-on-error", String
"-interaction", String
"nonstopmode",
                                   String
"-output-directory", String
tmpDir] [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
args [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
file]
    [(String, String)]
env' <- IO [(String, String)] -> PandocIO [(String, String)]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO [(String, String)]
getEnvironment
    let sep :: String
sep = [Char
searchPathSeparator]
    let texinputs :: String
texinputs = String -> (String -> String) -> Maybe String -> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String
tmpDir String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
sep) ((String
tmpDir String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
sep) String -> String -> String
forall a. [a] -> [a] -> [a]
++)
          (Maybe String -> String) -> Maybe String -> String
forall a b. (a -> b) -> a -> b
$ String -> [(String, String)] -> Maybe String
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) (String, String) -> [(String, String)] -> [(String, String)]
forall a. a -> [a] -> [a]
:
                (String
"TEXMFOUTPUT", String
tmpDir) (String, String) -> [(String, String)] -> [(String, String)]
forall a. a -> [a] -> [a]
:
                  [(String
k,String
v) | (String
k,String
v) <- [(String, String)]
env'
                         , String
k String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
"TEXINPUTS" Bool -> Bool -> Bool
&& String
k String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
"TEXMFOUTPUT"]
    Bool -> PandocIO () -> PandocIO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Verbosity
verbosity Verbosity -> Verbosity -> Bool
forall a. Ord a => a -> a -> Bool
>= Verbosity
INFO) (PandocIO () -> PandocIO ()) -> PandocIO () -> PandocIO ()
forall a b. (a -> b) -> a -> b
$ IO () -> PandocIO ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> PandocIO ()) -> IO () -> PandocIO ()
forall a b. (a -> b) -> a -> b
$
        String -> IO Text
UTF8.readFile String
file IO Text -> (Text -> IO ()) -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
         Maybe String
-> String -> [String] -> [(String, String)] -> Text -> IO ()
showVerboseInfo (String -> Maybe String
forall a. a -> Maybe a
Just String
tmpDir) String
program [String]
programArgs [(String, String)]
env''
    let runTeX :: Int -> PandocIO (ExitCode, ByteString, Maybe ByteString)
runTeX Int
runNumber = do
          (ExitCode
exit, ByteString
out) <- IO (ExitCode, ByteString) -> PandocIO (ExitCode, ByteString)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (ExitCode, ByteString) -> PandocIO (ExitCode, ByteString))
-> IO (ExitCode, ByteString) -> PandocIO (ExitCode, ByteString)
forall a b. (a -> b) -> a -> b
$ IO (ExitCode, ByteString)
-> (IOError -> IO (ExitCode, ByteString))
-> IO (ExitCode, ByteString)
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
E.catch
            (Maybe [(String, String)]
-> String -> [String] -> ByteString -> IO (ExitCode, ByteString)
pipeProcess ([(String, String)] -> Maybe [(String, String)]
forall a. a -> Maybe a
Just [(String, String)]
env'') String
program [String]
programArgs ByteString
BL.empty)
            (String -> IOError -> IO (ExitCode, ByteString)
forall a. String -> IOError -> IO a
handlePDFProgramNotFound String
program)
          Bool -> PandocIO () -> PandocIO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Verbosity
verbosity Verbosity -> Verbosity -> Bool
forall a. Ord a => a -> a -> Bool
>= Verbosity
INFO) (PandocIO () -> PandocIO ()) -> PandocIO () -> PandocIO ()
forall a b. (a -> b) -> a -> b
$ IO () -> PandocIO ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> PandocIO ()) -> IO () -> PandocIO ()
forall a b. (a -> b) -> a -> b
$ do
            Handle -> Text -> IO ()
UTF8.hPutStrLn Handle
stderr (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ Text
"[makePDF] Run #" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text
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 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
numRuns
             then Int -> PandocIO (ExitCode, ByteString, Maybe ByteString)
runTeX (Int
runNumber Int -> Int -> Int
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) <- Maybe String
-> String -> PandocIO (Maybe ByteString, Maybe ByteString)
getResultingPDF (String -> Maybe String
forall a. a -> Maybe a
Just String
logFile) String
pdfFile
               (ExitCode, ByteString, Maybe ByteString)
-> PandocIO (ExitCode, ByteString, Maybe ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (ExitCode
exit, ByteString -> Maybe ByteString -> ByteString
forall a. a -> Maybe a -> a
fromMaybe ByteString
out Maybe ByteString
log', Maybe ByteString
pdf)
    Int -> PandocIO (ExitCode, ByteString, Maybe ByteString)
runTeX Int
1

generic2pdf :: Verbosity
            -> String
            -> [String]
            -> Text
            -> IO (Either ByteString ByteString)
generic2pdf :: Verbosity
-> String -> [String] -> Text -> IO (Either ByteString ByteString)
generic2pdf Verbosity
verbosity String
program [String]
args Text
source = do
  [(String, String)]
env' <- IO [(String, String)]
getEnvironment
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Verbosity
verbosity Verbosity -> Verbosity -> Bool
forall a. Ord a => a -> a -> Bool
>= Verbosity
INFO) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    Maybe String
-> String -> [String] -> [(String, String)] -> Text -> IO ()
showVerboseInfo Maybe String
forall a. Maybe a
Nothing String
program [String]
args [(String, String)]
env' Text
source
  (ExitCode
exit, ByteString
out) <- IO (ExitCode, ByteString)
-> (IOError -> IO (ExitCode, ByteString))
-> IO (ExitCode, ByteString)
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
E.catch
    (Maybe [(String, String)]
-> String -> [String] -> ByteString -> IO (ExitCode, ByteString)
pipeProcess ([(String, String)] -> Maybe [(String, String)]
forall a. a -> Maybe a
Just [(String, String)]
env') String
program [String]
args
                     (ByteString -> ByteString
BL.fromStrict (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ Text -> ByteString
UTF8.fromText Text
source))
    (String -> IOError -> IO (ExitCode, ByteString)
forall a. String -> IOError -> IO a
handlePDFProgramNotFound String
program)
  Either ByteString ByteString -> IO (Either ByteString ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either ByteString ByteString -> IO (Either ByteString ByteString))
-> Either ByteString ByteString
-> IO (Either ByteString ByteString)
forall a b. (a -> b) -> a -> b
$ case ExitCode
exit of
             ExitFailure Int
_ -> ByteString -> Either ByteString ByteString
forall a b. a -> Either a b
Left ByteString
out
             ExitCode
ExitSuccess   -> ByteString -> Either ByteString ByteString
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.
  String
-> String
-> (String -> Handle -> IO (Either ByteString ByteString))
-> IO (Either ByteString ByteString)
forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
String -> String -> (String -> Handle -> m a) -> m a
withTempFile String
"." String
"html2pdf.html" ((String -> Handle -> IO (Either ByteString ByteString))
 -> IO (Either ByteString ByteString))
-> (String -> Handle -> IO (Either ByteString ByteString))
-> IO (Either ByteString ByteString)
forall a b. (a -> b) -> a -> b
$ \String
file Handle
h1 ->
    String
-> String
-> (String -> Handle -> IO (Either ByteString ByteString))
-> IO (Either ByteString ByteString)
forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
String -> String -> (String -> Handle -> m a) -> m a
withTempFile String
"." String
"html2pdf.pdf" ((String -> Handle -> IO (Either ByteString ByteString))
 -> IO (Either ByteString ByteString))
-> (String -> Handle -> IO (Either ByteString ByteString))
-> IO (Either ByteString ByteString)
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 (ByteString -> IO ()) -> ByteString -> IO ()
forall a b. (a -> b) -> a -> b
$ Text -> ByteString
UTF8.fromText Text
source
      let pdfFileArgName :: [String]
pdfFileArgName = [String
"-o" | String -> String
takeBaseName String
program String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"prince"]
      let programArgs :: [String]
programArgs = [String]
args [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
file] [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
pdfFileArgName [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
pdfFile]
      [(String, String)]
env' <- IO [(String, String)]
getEnvironment
      Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Verbosity
verbosity Verbosity -> Verbosity -> Bool
forall a. Ord a => a -> a -> Bool
>= Verbosity
INFO) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
        String -> IO Text
UTF8.readFile String
file IO Text -> (Text -> IO ()) -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
          Maybe String
-> String -> [String] -> [(String, String)] -> Text -> IO ()
showVerboseInfo Maybe String
forall a. Maybe a
Nothing String
program [String]
programArgs [(String, String)]
env'
      (ExitCode
exit, ByteString
out) <- IO (ExitCode, ByteString)
-> (IOError -> IO (ExitCode, ByteString))
-> IO (ExitCode, ByteString)
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
E.catch
        (Maybe [(String, String)]
-> String -> [String] -> ByteString -> IO (ExitCode, ByteString)
pipeProcess ([(String, String)] -> Maybe [(String, String)]
forall a. a -> Maybe a
Just [(String, String)]
env') String
program [String]
programArgs ByteString
BL.empty)
        (String -> IOError -> IO (ExitCode, ByteString)
forall a. String -> IOError -> IO a
handlePDFProgramNotFound String
program)
      Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Verbosity
verbosity Verbosity -> Verbosity -> Bool
forall a. Ord a => a -> a -> Bool
>= Verbosity
INFO) (IO () -> IO ()) -> IO () -> IO ()
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 ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString)
-> (ByteString -> ByteString) -> ByteString -> Maybe ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> ByteString
BL.fromChunks ([ByteString] -> ByteString)
-> (ByteString -> [ByteString]) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
:[]) (ByteString -> Maybe ByteString)
-> IO ByteString -> IO (Maybe ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO ByteString
BS.readFile String
pdfFile
                else Maybe ByteString -> IO (Maybe ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ByteString
forall a. Maybe a
Nothing
      Either ByteString ByteString -> IO (Either ByteString ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either ByteString ByteString -> IO (Either ByteString ByteString))
-> Either ByteString ByteString
-> IO (Either ByteString ByteString)
forall a b. (a -> b) -> a -> b
$ case (ExitCode
exit, Maybe ByteString
mbPdf) of
                 (ExitFailure Int
_, Maybe ByteString
_)      -> ByteString -> Either ByteString ByteString
forall a b. a -> Either a b
Left ByteString
out
                 (ExitCode
ExitSuccess, Maybe ByteString
Nothing)  -> ByteString -> Either ByteString ByteString
forall a b. a -> Either a b
Left ByteString
""
                 (ExitCode
ExitSuccess, Just ByteString
pdf) -> ByteString -> Either ByteString ByteString
forall a b. b -> Either a b
Right ByteString
pdf

context2pdf :: Verbosity    -- ^ Verbosity level
            -> String       -- ^ "context" or path to it
            -> [String]     -- ^ extra arguments
            -> FilePath     -- ^ temp directory for output
            -> Text         -- ^ ConTeXt source
            -> PandocIO (Either ByteString ByteString)
context2pdf :: Verbosity
-> String
-> [String]
-> String
-> Text
-> PandocIO (Either ByteString ByteString)
context2pdf Verbosity
verbosity String
program [String]
pdfargs String
tmpDir Text
source =
  IO (Either ByteString ByteString)
-> PandocIO (Either ByteString ByteString)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Either ByteString ByteString)
 -> PandocIO (Either ByteString ByteString))
-> IO (Either ByteString ByteString)
-> PandocIO (Either ByteString ByteString)
forall a b. (a -> b) -> a -> b
$ String
-> IO (Either ByteString ByteString)
-> IO (Either ByteString ByteString)
forall a. String -> IO a -> IO a
inDirectory String
tmpDir (IO (Either ByteString ByteString)
 -> IO (Either ByteString ByteString))
-> IO (Either ByteString ByteString)
-> IO (Either ByteString ByteString)
forall a b. (a -> b) -> a -> b
$ do
    let file :: String
file = String
"input.tex"
    String -> ByteString -> IO ()
BS.writeFile String
file (ByteString -> IO ()) -> ByteString -> IO ()
forall a b. (a -> b) -> a -> b
$ Text -> ByteString
UTF8.fromText Text
source
    let programArgs :: [String]
programArgs = String
"--batchmode" String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
pdfargs [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
file]
    [(String, String)]
env' <- IO [(String, String)]
getEnvironment
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Verbosity
verbosity Verbosity -> Verbosity -> Bool
forall a. Ord a => a -> a -> Bool
>= Verbosity
INFO) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
      String -> IO Text
UTF8.readFile String
file IO Text -> (Text -> IO ()) -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
        Maybe String
-> String -> [String] -> [(String, String)] -> Text -> IO ()
showVerboseInfo (String -> Maybe String
forall a. a -> Maybe a
Just String
tmpDir) String
program [String]
programArgs [(String, String)]
env'
    (ExitCode
exit, ByteString
out) <- IO (ExitCode, ByteString)
-> (IOError -> IO (ExitCode, ByteString))
-> IO (ExitCode, ByteString)
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
E.catch
      (Maybe [(String, String)]
-> String -> [String] -> ByteString -> IO (ExitCode, ByteString)
pipeProcess ([(String, String)] -> Maybe [(String, String)]
forall a. a -> Maybe a
Just [(String, String)]
env') String
program [String]
programArgs ByteString
BL.empty)
      (String -> IOError -> IO (ExitCode, ByteString)
forall a. String -> IOError -> IO a
handlePDFProgramNotFound String
program)
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Verbosity
verbosity Verbosity -> Verbosity -> Bool
forall a. Ord a => a -> a -> Bool
>= Verbosity
INFO) (IO () -> IO ()) -> IO () -> IO ()
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 (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString)
-> (ByteString -> ByteString) -> ByteString -> Maybe ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> ByteString
BL.fromChunks ([ByteString] -> ByteString)
-> (ByteString -> [ByteString]) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
:[])) (ByteString -> Maybe ByteString)
-> IO ByteString -> IO (Maybe ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` String -> IO ByteString
BS.readFile String
pdfFile
              else Maybe ByteString -> IO (Maybe ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ByteString
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
            Either ByteString ByteString -> IO (Either ByteString ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either ByteString ByteString -> IO (Either ByteString ByteString))
-> Either ByteString ByteString
-> IO (Either ByteString ByteString)
forall a b. (a -> b) -> a -> b
$ ByteString -> Either ByteString ByteString
forall a b. a -> Either a b
Left ByteString
logmsg
         (ExitCode
ExitSuccess, Maybe ByteString
Nothing)  -> Either ByteString ByteString -> IO (Either ByteString ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either ByteString ByteString -> IO (Either ByteString ByteString))
-> Either ByteString ByteString
-> IO (Either ByteString ByteString)
forall a b. (a -> b) -> a -> b
$ ByteString -> Either ByteString ByteString
forall a b. a -> Either a b
Left ByteString
""
         (ExitCode
ExitSuccess, Just ByteString
pdf) -> Either ByteString ByteString -> IO (Either ByteString ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either ByteString ByteString -> IO (Either ByteString ByteString))
-> Either ByteString ByteString
-> IO (Either ByteString ByteString)
forall a b. (a -> b) -> a -> b
$ ByteString -> Either ByteString ByteString
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 -> () -> IO ()
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 (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$
       String -> Text
T.pack String
program Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack ([String] -> String
unwords ((String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map String -> String
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] Environment:"
  ((String, String) -> IO ()) -> [(String, String)] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Handle -> Text -> IO ()
UTF8.hPutStrLn Handle
stderr (Text -> IO ())
-> ((String, String) -> Text) -> (String, String) -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String, String) -> Text
forall a. Show a => a -> Text
tshow) [(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 :: String -> IOError -> IO a
handlePDFProgramNotFound String
program IOError
e
  | IOError -> Bool
IE.isDoesNotExistError IOError
e =
      PandocError -> IO a
forall e a. Exception e => e -> IO a
E.throwIO (PandocError -> IO a) -> PandocError -> IO a
forall a b. (a -> b) -> a -> b
$ Text -> PandocError
PandocPDFProgramNotFoundError (Text -> PandocError) -> Text -> PandocError
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
program
  | Bool
otherwise = IOError -> IO a
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 (String -> Text) -> String -> Text
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