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

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

Does a pandoc conversion based on command-line options.
-}
module Text.Pandoc.App (
            convertWithOpts
          , handleOptInfo
          , Opt(..)
          , OptInfo(..)
          , LineEnding(..)
          , IpynbOutput (..)
          , Filter(..)
          , defaultOpts
          , parseOptions
          , parseOptionsFromArgs
          , options
          , applyFilters
          ) where
import qualified Control.Exception as E
import Control.Monad ( (>=>), when, forM, forM_ )
import Control.Monad.Trans ( MonadIO(..) )
import Control.Monad.Catch ( MonadMask )
import Control.Monad.Except (throwError)
import qualified Data.ByteString.Lazy as BL
import Data.Maybe (fromMaybe, isJust, isNothing)
import qualified Data.Set as Set
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Encoding as TE
import qualified Data.Text.Encoding.Error as TE
import System.Directory (doesDirectoryExist, createDirectory)
import Codec.Archive.Zip (toArchiveOrFail,
                          extractFilesFromArchive, ZipOption(..))
import System.Exit (exitSuccess)
import System.FilePath ( takeBaseName, takeExtension)
import System.IO (nativeNewline, stdout)
import qualified System.IO as IO (Newline (..))
import Text.Pandoc
import Text.Pandoc.Builder (setMeta)
import Text.Pandoc.MediaBag (mediaItems)
import Text.Pandoc.Image (svgToPng)
import Text.Pandoc.App.FormatHeuristics (formatFromFilePaths)
import Text.Pandoc.App.Opt (Opt (..), LineEnding (..), defaultOpts,
                            IpynbOutput (..), OptInfo(..))
import Text.Pandoc.App.CommandLineOptions (parseOptions, parseOptionsFromArgs,
                                           options, handleOptInfo)
import Text.Pandoc.App.Input (InputParameters (..), readInput)
import Text.Pandoc.App.OutputSettings (OutputSettings (..), optToOutputSettings)
import Text.Collate.Lang (Lang (..), parseLang)
import Text.Pandoc.Filter (Filter (JSONFilter, LuaFilter), Environment (..),
                           applyFilters)
import qualified Text.Pandoc.Format as Format
import Text.Pandoc.PDF (makePDF)
import Text.Pandoc.Scripting (ScriptingEngine (..), CustomComponents(..))
import Text.Pandoc.SelfContained (makeSelfContained)
import Text.Pandoc.Shared (eastAsianLineBreakFilter,
         headerShift, filterIpynbOutput, tshow)
import Text.Pandoc.URI (isURI)
import Text.Pandoc.Writers.Shared (lookupMetaString)
import Text.Pandoc.Readers.Markdown (yamlToMeta)
import qualified Text.Pandoc.UTF8 as UTF8
#ifndef _WINDOWS
import System.Posix.IO (stdOutput)
import System.Posix.Terminal (queryTerminal)
#endif

convertWithOpts :: ScriptingEngine -> Opt -> IO ()
convertWithOpts :: ScriptingEngine -> Opt -> IO ()
convertWithOpts ScriptingEngine
scriptingEngine Opt
opts = do
  let outputFile :: FilePath
outputFile = FilePath -> Maybe FilePath -> FilePath
forall a. a -> Maybe a -> a
fromMaybe FilePath
"-" (Opt -> Maybe FilePath
optOutputFile Opt
opts)
  Maybe FilePath
datadir <- case Opt -> Maybe FilePath
optDataDir Opt
opts of
                  Maybe FilePath
Nothing   -> do
                    FilePath
d <- IO FilePath
defaultUserDataDir
                    Bool
exists <- FilePath -> IO Bool
doesDirectoryExist FilePath
d
                    Maybe FilePath -> IO (Maybe FilePath)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe FilePath -> IO (Maybe FilePath))
-> Maybe FilePath -> IO (Maybe FilePath)
forall a b. (a -> b) -> a -> b
$ if Bool
exists
                                then FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just FilePath
d
                                else Maybe FilePath
forall a. Maybe a
Nothing
                  Maybe FilePath
mdatadir  -> Maybe FilePath -> IO (Maybe FilePath)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FilePath
mdatadir

  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Opt -> Bool
optDumpArgs Opt
opts) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    do Handle -> Text -> IO ()
UTF8.hPutStrLn Handle
stdout (FilePath -> Text
T.pack FilePath
outputFile)
       (FilePath -> IO ()) -> [FilePath] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Handle -> Text -> IO ()
UTF8.hPutStrLn Handle
stdout (Text -> IO ()) -> (FilePath -> Text) -> FilePath -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Text
T.pack)
             ([FilePath] -> Maybe [FilePath] -> [FilePath]
forall a. a -> Maybe a -> a
fromMaybe [FilePath
"-"] (Maybe [FilePath] -> [FilePath]) -> Maybe [FilePath] -> [FilePath]
forall a b. (a -> b) -> a -> b
$ Opt -> Maybe [FilePath]
optInputFiles Opt
opts)
       IO ()
forall a. IO a
exitSuccess

#ifdef _WINDOWS
  let istty = True
#else
  Bool
istty <- IO Bool -> IO Bool
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> IO Bool) -> IO Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$ Fd -> IO Bool
queryTerminal Fd
stdOutput
#endif

  Either PandocError (PandocOutput, [LogMessage])
res <- PandocIO (PandocOutput, [LogMessage])
-> IO (Either PandocError (PandocOutput, [LogMessage]))
forall a. PandocIO a -> IO (Either PandocError a)
runIO (PandocIO (PandocOutput, [LogMessage])
 -> IO (Either PandocError (PandocOutput, [LogMessage])))
-> PandocIO (PandocOutput, [LogMessage])
-> IO (Either PandocError (PandocOutput, [LogMessage]))
forall a b. (a -> b) -> a -> b
$ ScriptingEngine
-> Bool
-> Maybe FilePath
-> Opt
-> PandocIO (PandocOutput, [LogMessage])
forall (m :: * -> *).
(PandocMonad m, MonadIO m, MonadMask m) =>
ScriptingEngine
-> Bool -> Maybe FilePath -> Opt -> m (PandocOutput, [LogMessage])
convertWithOpts' ScriptingEngine
scriptingEngine Bool
istty Maybe FilePath
datadir Opt
opts
  case Either PandocError (PandocOutput, [LogMessage])
res of
    Left PandocError
e -> PandocError -> IO ()
forall e a. Exception e => e -> IO a
E.throwIO PandocError
e
    Right (PandocOutput
output, [LogMessage]
reports) -> do
      case Opt -> Maybe FilePath
optLogFile Opt
opts of
           Maybe FilePath
Nothing      -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
           Just FilePath
logfile -> FilePath -> ByteString -> IO ()
BL.writeFile FilePath
logfile ([LogMessage] -> ByteString
encodeLogMessages [LogMessage]
reports)
      let isWarning :: LogMessage -> Bool
isWarning LogMessage
msg = LogMessage -> Verbosity
messageVerbosity LogMessage
msg Verbosity -> Verbosity -> Bool
forall a. Eq a => a -> a -> Bool
== Verbosity
WARNING
      Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Opt -> Bool
optFailIfWarnings Opt
opts Bool -> Bool -> Bool
&& (LogMessage -> Bool) -> [LogMessage] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any LogMessage -> Bool
isWarning [LogMessage]
reports) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
          PandocError -> IO ()
forall e a. Exception e => e -> IO a
E.throwIO PandocError
PandocFailOnWarningError
      let eol :: Newline
eol = case Opt -> LineEnding
optEol Opt
opts of
                     LineEnding
CRLF   -> Newline
IO.CRLF
                     LineEnding
LF     -> Newline
IO.LF
                     LineEnding
Native -> Newline
nativeNewline
      case PandocOutput
output of
        TextOutput Text
t    -> Newline -> FilePath -> Text -> IO ()
writerFn Newline
eol FilePath
outputFile Text
t
        BinaryOutput ByteString
bs -> FilePath -> ByteString -> IO ()
writeFnBinary FilePath
outputFile ByteString
bs
        ZipOutput ByteString
bs
          | FilePath -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (FilePath -> FilePath
takeExtension FilePath
outputFile) -> do
             -- create directory and unzip
             FilePath -> IO ()
createDirectory FilePath
outputFile -- will fail if directory exists
             let zipopts :: [ZipOption]
zipopts = [ZipOption
OptRecursive, FilePath -> ZipOption
OptDestination FilePath
outputFile] [ZipOption] -> [ZipOption] -> [ZipOption]
forall a. [a] -> [a] -> [a]
++
                           [ZipOption
OptVerbose | Opt -> Verbosity
optVerbosity Opt
opts Verbosity -> Verbosity -> Bool
forall a. Eq a => a -> a -> Bool
== Verbosity
INFO]
             case ByteString -> Either FilePath Archive
toArchiveOrFail ByteString
bs of
               Right Archive
archive -> [ZipOption] -> Archive -> IO ()
extractFilesFromArchive [ZipOption]
zipopts Archive
archive
               Left FilePath
e -> PandocError -> IO ()
forall e a. Exception e => e -> IO a
E.throwIO (PandocError -> IO ()) -> PandocError -> IO ()
forall a b. (a -> b) -> a -> b
$ Text -> PandocError
PandocShouldNeverHappenError (Text -> PandocError) -> Text -> PandocError
forall a b. (a -> b) -> a -> b
$ FilePath -> Text
T.pack FilePath
e
          | Bool
otherwise -> FilePath -> ByteString -> IO ()
writeFnBinary FilePath
outputFile ByteString
bs

convertWithOpts' :: (PandocMonad m, MonadIO m, MonadMask m)
                 => ScriptingEngine
                 -> Bool
                 -> Maybe FilePath
                 -> Opt
                 -> m (PandocOutput, [LogMessage])
convertWithOpts' :: forall (m :: * -> *).
(PandocMonad m, MonadIO m, MonadMask m) =>
ScriptingEngine
-> Bool -> Maybe FilePath -> Opt -> m (PandocOutput, [LogMessage])
convertWithOpts' ScriptingEngine
scriptingEngine Bool
istty Maybe FilePath
datadir Opt
opts = do
  Maybe FilePath -> Opt -> m ()
forall (m :: * -> *).
PandocMonad m =>
Maybe FilePath -> Opt -> m ()
configureCommonState Maybe FilePath
datadir Opt
opts
  let outputFile :: FilePath
outputFile = FilePath -> Maybe FilePath -> FilePath
forall a. a -> Maybe a -> a
fromMaybe FilePath
"-" (Opt -> Maybe FilePath
optOutputFile Opt
opts)
  let filters :: [Filter]
filters = Opt -> [Filter]
optFilters Opt
opts
  let sources :: [FilePath]
sources = case Opt -> Maybe [FilePath]
optInputFiles Opt
opts of
                     Just [FilePath]
xs | Bool -> Bool
not (Opt -> Bool
optIgnoreArgs Opt
opts) -> [FilePath]
xs
                     Maybe [FilePath]
_ -> [FilePath
"-"]

  -- assign reader and writer based on options and filenames
  Text
readerName <- case Opt -> Maybe Text
optFrom Opt
opts of
                     Just Text
f  -> Text -> m Text
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
f
                     Maybe Text
Nothing -> case [FilePath] -> Maybe Text
formatFromFilePaths [FilePath]
sources of
                         Just Text
f' -> Text -> m Text
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
f'
                         Maybe Text
Nothing | [FilePath]
sources [FilePath] -> [FilePath] -> Bool
forall a. Eq a => a -> a -> Bool
== [FilePath
"-"] -> Text -> m Text
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"markdown"
                                 | (FilePath -> Bool) -> [FilePath] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Text -> Bool
isURI (Text -> Bool) -> (FilePath -> Text) -> FilePath -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Text
T.pack) [FilePath]
sources -> Text -> m Text
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"html"
                                 | Bool
otherwise -> do
                           LogMessage -> m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> m ()) -> LogMessage -> m ()
forall a b. (a -> b) -> a -> b
$ [Text] -> Text -> LogMessage
CouldNotDeduceFormat
                               ((FilePath -> Text) -> [FilePath] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> Text
T.pack (FilePath -> Text) -> (FilePath -> FilePath) -> FilePath -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath
takeExtension) [FilePath]
sources) Text
"markdown"
                           Text -> m Text
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"markdown"

  flvrd :: FlavoredFormat
flvrd@(Format.FlavoredFormat Text
readerNameBase ExtensionsDiff
_extsDiff) <-
    Text -> m FlavoredFormat
forall (m :: * -> *). PandocMonad m => Text -> m FlavoredFormat
Format.parseFlavoredFormat Text
readerName
  let makeSandboxed :: Reader PandocPure -> Reader m
makeSandboxed Reader PandocPure
pureReader =
        let files :: [FilePath]
files = ([FilePath] -> [FilePath])
-> (FilePath -> [FilePath] -> [FilePath])
-> Maybe FilePath
-> [FilePath]
-> [FilePath]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [FilePath] -> [FilePath]
forall a. a -> a
id (:) (Opt -> Maybe FilePath
optReferenceDoc Opt
opts) ([FilePath] -> [FilePath])
-> ([FilePath] -> [FilePath]) -> [FilePath] -> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                    ([FilePath] -> [FilePath])
-> (FilePath -> [FilePath] -> [FilePath])
-> Maybe FilePath
-> [FilePath]
-> [FilePath]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [FilePath] -> [FilePath]
forall a. a -> a
id (:) (Opt -> Maybe FilePath
optEpubMetadata Opt
opts) ([FilePath] -> [FilePath])
-> ([FilePath] -> [FilePath]) -> [FilePath] -> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                    ([FilePath] -> [FilePath])
-> (FilePath -> [FilePath] -> [FilePath])
-> Maybe FilePath
-> [FilePath]
-> [FilePath]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [FilePath] -> [FilePath]
forall a. a -> a
id (:) (Opt -> Maybe FilePath
optEpubCoverImage Opt
opts) ([FilePath] -> [FilePath])
-> ([FilePath] -> [FilePath]) -> [FilePath] -> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                    ([FilePath] -> [FilePath])
-> (FilePath -> [FilePath] -> [FilePath])
-> Maybe FilePath
-> [FilePath]
-> [FilePath]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [FilePath] -> [FilePath]
forall a. a -> a
id (:) (Opt -> Maybe FilePath
optCSL Opt
opts) ([FilePath] -> [FilePath])
-> ([FilePath] -> [FilePath]) -> [FilePath] -> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                    ([FilePath] -> [FilePath])
-> (FilePath -> [FilePath] -> [FilePath])
-> Maybe FilePath
-> [FilePath]
-> [FilePath]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [FilePath] -> [FilePath]
forall a. a -> a
id (:) (Opt -> Maybe FilePath
optCitationAbbreviations Opt
opts) ([FilePath] -> [FilePath]) -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> a -> b
$
                    Opt -> [FilePath]
optEpubFonts Opt
opts [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++
                    Opt -> [FilePath]
optBibliography Opt
opts
         in  case Reader PandocPure
pureReader of
               TextReader forall a. ToSources a => ReaderOptions -> a -> PandocPure Pandoc
r -> (forall a. ToSources a => ReaderOptions -> a -> m Pandoc)
-> Reader m
forall (m :: * -> *).
(forall a. ToSources a => ReaderOptions -> a -> m Pandoc)
-> Reader m
TextReader ((forall a. ToSources a => ReaderOptions -> a -> m Pandoc)
 -> Reader m)
-> (forall a. ToSources a => ReaderOptions -> a -> m Pandoc)
-> Reader m
forall a b. (a -> b) -> a -> b
$ \ReaderOptions
o a
t -> [FilePath] -> PandocPure Pandoc -> m Pandoc
forall (m :: * -> *) a.
(PandocMonad m, MonadIO m) =>
[FilePath] -> PandocPure a -> m a
sandbox [FilePath]
files (ReaderOptions -> a -> PandocPure Pandoc
forall a. ToSources a => ReaderOptions -> a -> PandocPure Pandoc
r ReaderOptions
o a
t)
               ByteStringReader ReaderOptions -> ByteString -> PandocPure Pandoc
r
                          -> (ReaderOptions -> ByteString -> m Pandoc) -> Reader m
forall (m :: * -> *).
(ReaderOptions -> ByteString -> m Pandoc) -> Reader m
ByteStringReader ((ReaderOptions -> ByteString -> m Pandoc) -> Reader m)
-> (ReaderOptions -> ByteString -> m Pandoc) -> Reader m
forall a b. (a -> b) -> a -> b
$ \ReaderOptions
o ByteString
t -> [FilePath] -> PandocPure Pandoc -> m Pandoc
forall (m :: * -> *) a.
(PandocMonad m, MonadIO m) =>
[FilePath] -> PandocPure a -> m a
sandbox [FilePath]
files (ReaderOptions -> ByteString -> PandocPure Pandoc
r ReaderOptions
o ByteString
t)

  (Reader m
reader, Extensions
readerExts) <-
    if Text
".lua" Text -> Text -> Bool
`T.isSuffixOf` Text
readerNameBase
       then do
            let scriptPath :: FilePath
scriptPath = Text -> FilePath
T.unpack Text
readerNameBase
            CustomComponents m
components <- ScriptingEngine
-> forall (m :: * -> *).
   (PandocMonad m, MonadIO m) =>
   FilePath -> m (CustomComponents m)
engineLoadCustom ScriptingEngine
scriptingEngine FilePath
scriptPath
            Reader m
r <- case CustomComponents m -> Maybe (Reader m)
forall (m :: * -> *). CustomComponents m -> Maybe (Reader m)
customReader CustomComponents m
components of
                   Maybe (Reader m)
Nothing -> PandocError -> m (Reader m)
forall a. PandocError -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> m (Reader m)) -> PandocError -> m (Reader m)
forall a b. (a -> b) -> a -> b
$ Text -> PandocError
PandocAppError (Text -> PandocError) -> Text -> PandocError
forall a b. (a -> b) -> a -> b
$
                               Text
readerName Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" does not contain a custom reader"
                   Just Reader m
r -> Reader m -> m (Reader m)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Reader m
r
            let extsConf :: ExtensionsConfig
extsConf = ExtensionsConfig -> Maybe ExtensionsConfig -> ExtensionsConfig
forall a. a -> Maybe a -> a
fromMaybe ExtensionsConfig
forall a. Monoid a => a
mempty (CustomComponents m -> Maybe ExtensionsConfig
forall (m :: * -> *). CustomComponents m -> Maybe ExtensionsConfig
customExtensions CustomComponents m
components)
            Extensions
rexts <- ExtensionsConfig -> FlavoredFormat -> m Extensions
forall (m :: * -> *).
PandocMonad m =>
ExtensionsConfig -> FlavoredFormat -> m Extensions
Format.applyExtensionsDiff ExtensionsConfig
extsConf FlavoredFormat
flvrd
            (Reader m, Extensions) -> m (Reader m, Extensions)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Reader m
r, Extensions
rexts)
       else if Opt -> Bool
optSandbox Opt
opts
               then case PandocPure (Reader PandocPure, Extensions)
-> Either PandocError (Reader PandocPure, Extensions)
forall a. PandocPure a -> Either PandocError a
runPure (FlavoredFormat -> PandocPure (Reader PandocPure, Extensions)
forall (m :: * -> *).
PandocMonad m =>
FlavoredFormat -> m (Reader m, Extensions)
getReader FlavoredFormat
flvrd) of
                      Left PandocError
e -> PandocError -> m (Reader m, Extensions)
forall a. PandocError -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError PandocError
e
                      Right (Reader PandocPure
r, Extensions
rexts) -> (Reader m, Extensions) -> m (Reader m, Extensions)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Reader PandocPure -> Reader m
forall {m :: * -> *}.
(PandocMonad m, MonadIO m) =>
Reader PandocPure -> Reader m
makeSandboxed Reader PandocPure
r, Extensions
rexts)
               else FlavoredFormat -> m (Reader m, Extensions)
forall (m :: * -> *).
PandocMonad m =>
FlavoredFormat -> m (Reader m, Extensions)
getReader FlavoredFormat
flvrd

  OutputSettings m
outputSettings <- ScriptingEngine -> Opt -> m (OutputSettings m)
forall (m :: * -> *).
(PandocMonad m, MonadIO m) =>
ScriptingEngine -> Opt -> m (OutputSettings m)
optToOutputSettings ScriptingEngine
scriptingEngine Opt
opts
  let format :: Text
format = OutputSettings m -> Text
forall (m :: * -> *). OutputSettings m -> Text
outputFormat OutputSettings m
outputSettings
  let writer :: Writer m
writer = OutputSettings m -> Writer m
forall (m :: * -> *). OutputSettings m -> Writer m
outputWriter OutputSettings m
outputSettings
  let writerOptions :: WriterOptions
writerOptions = OutputSettings m -> WriterOptions
forall (m :: * -> *). OutputSettings m -> WriterOptions
outputWriterOptions OutputSettings m
outputSettings

  -- whether we are targeting PDF.
  let pdfOutput :: Bool
pdfOutput = Maybe FilePath -> Bool
forall a. Maybe a -> Bool
isJust (Maybe FilePath -> Bool) -> Maybe FilePath -> Bool
forall a b. (a -> b) -> a -> b
$ OutputSettings m -> Maybe FilePath
forall (m :: * -> *). OutputSettings m -> Maybe FilePath
outputPdfProgram OutputSettings m
outputSettings
  -- whether standalone output should be produced.
  let bibOutput :: Bool
bibOutput = Text
format Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text
"bibtex", Text
"biblatex", Text
"csljson"]
  let standalone :: Bool
standalone = Maybe (Template Text) -> Bool
forall a. Maybe a -> Bool
isJust (WriterOptions -> Maybe (Template Text)
writerTemplate WriterOptions
writerOptions) Bool -> Bool -> Bool
|| Bool
bibOutput

  --
  -- Sanity checks
  --
  Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool
pdfOutput Bool -> Bool -> Bool
&& Text
readerNameBase Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"latex") (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$
    case Opt -> Maybe [FilePath]
optInputFiles Opt
opts of
      Just (FilePath
inputFile:[FilePath]
_) -> LogMessage -> m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> m ()) -> LogMessage -> m ()
forall a b. (a -> b) -> a -> b
$ Text -> LogMessage
UnusualConversion (Text -> LogMessage) -> Text -> LogMessage
forall a b. (a -> b) -> a -> b
$ FilePath -> Text
T.pack (FilePath -> Text) -> FilePath -> Text
forall a b. (a -> b) -> a -> b
$
        FilePath
"to convert a .tex file to PDF, you get better results by using pdflatex "
          FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath
"(or lualatex or xelatex) directly, try `pdflatex " FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath
inputFile
          FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath
"` instead of `pandoc " FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath
inputFile FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath
" -o " FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath
outputFile FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath
"`."
      Maybe [FilePath]
_ -> () -> m ()
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

  -- We don't want to send output to the terminal if the user
  -- does 'pandoc -t docx input.txt'; though we allow them to
  -- force this with '-o -'.  On posix systems, we detect
  -- when stdout is being piped and allow output to stdout
  -- in that case, but on Windows we can't.
  Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ((Bool
pdfOutput Bool -> Bool -> Bool
|| Bool -> Bool
not (Text -> Bool
isTextFormat Text
format)) Bool -> Bool -> Bool
&&
           Bool
istty Bool -> Bool -> Bool
&& Maybe FilePath -> Bool
forall a. Maybe a -> Bool
isNothing ( Opt -> Maybe FilePath
optOutputFile Opt
opts)) (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$
    PandocError -> m ()
forall a. PandocError -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> m ()) -> PandocError -> m ()
forall a b. (a -> b) -> a -> b
$ Text -> PandocError
PandocAppError (Text -> PandocError) -> Text -> PandocError
forall a b. (a -> b) -> a -> b
$
            Text
"Cannot write " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> (if Bool
pdfOutput then Text
"pdf" else Text
format) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
            Text
" output to terminal.\n" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
            Text
"Specify an output file using the -o option, or " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
            Text
"use '-o -' to force output to stdout."

  Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Text
readerNameBase Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"markdown_github" Bool -> Bool -> Bool
||
        Text
format Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"markdown_github") (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$
    LogMessage -> m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> m ()) -> LogMessage -> m ()
forall a b. (a -> b) -> a -> b
$ Text -> Text -> LogMessage
Deprecated Text
"markdown_github" Text
"Use gfm instead."

  Set Text
abbrevs <- Maybe FilePath -> m (Set Text)
forall (m :: * -> *).
PandocMonad m =>
Maybe FilePath -> m (Set Text)
readAbbreviations (Opt -> Maybe FilePath
optAbbreviations Opt
opts)
  let readerOpts :: ReaderOptions
readerOpts = ReaderOptions
forall a. Default a => a
def{
          readerStandalone :: Bool
readerStandalone = Bool
standalone
        , readerColumns :: Int
readerColumns = Opt -> Int
optColumns Opt
opts
        , readerTabStop :: Int
readerTabStop = Opt -> Int
optTabStop Opt
opts
        , readerIndentedCodeClasses :: [Text]
readerIndentedCodeClasses = Opt -> [Text]
optIndentedCodeClasses Opt
opts
        , readerDefaultImageExtension :: Text
readerDefaultImageExtension = Opt -> Text
optDefaultImageExtension Opt
opts
        , readerTrackChanges :: TrackChanges
readerTrackChanges = Opt -> TrackChanges
optTrackChanges Opt
opts
        , readerAbbreviations :: Set Text
readerAbbreviations = Set Text
abbrevs
        , readerExtensions :: Extensions
readerExtensions = Extensions
readerExts
        , readerStripComments :: Bool
readerStripComments = Opt -> Bool
optStripComments Opt
opts
        }

  Meta
metadataFromFile <- Text -> ReaderOptions -> [FilePath] -> m Meta
forall (m :: * -> *).
PandocMonad m =>
Text -> ReaderOptions -> [FilePath] -> m Meta
getMetadataFromFiles Text
readerNameBase ReaderOptions
readerOpts
                         (Opt -> [FilePath]
optMetadataFiles Opt
opts)

  let transforms :: [Pandoc -> Pandoc]
transforms = (case Opt -> Int
optShiftHeadingLevelBy Opt
opts of
                        Int
0             -> [Pandoc -> Pandoc] -> [Pandoc -> Pandoc]
forall a. a -> a
id
                        Int
x             -> (Int -> Pandoc -> Pandoc
headerShift Int
x (Pandoc -> Pandoc) -> [Pandoc -> Pandoc] -> [Pandoc -> Pandoc]
forall a. a -> [a] -> [a]
:)) ([Pandoc -> Pandoc] -> [Pandoc -> Pandoc])
-> ([Pandoc -> Pandoc] -> [Pandoc -> Pandoc])
-> [Pandoc -> Pandoc]
-> [Pandoc -> Pandoc]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                   (if Extension -> Extensions -> Bool
extensionEnabled Extension
Ext_east_asian_line_breaks
                          Extensions
readerExts Bool -> Bool -> Bool
&&
                       Bool -> Bool
not (Extension -> Extensions -> Bool
extensionEnabled Extension
Ext_east_asian_line_breaks
                            (WriterOptions -> Extensions
writerExtensions WriterOptions
writerOptions) Bool -> Bool -> Bool
&&
                            WriterOptions -> WrapOption
writerWrapText WriterOptions
writerOptions WrapOption -> WrapOption -> Bool
forall a. Eq a => a -> a -> Bool
== WrapOption
WrapPreserve)
                       then (Pandoc -> Pandoc
eastAsianLineBreakFilter (Pandoc -> Pandoc) -> [Pandoc -> Pandoc] -> [Pandoc -> Pandoc]
forall a. a -> [a] -> [a]
:)
                       else [Pandoc -> Pandoc] -> [Pandoc -> Pandoc]
forall a. a -> a
id) ([Pandoc -> Pandoc] -> [Pandoc -> Pandoc])
-> ([Pandoc -> Pandoc] -> [Pandoc -> Pandoc])
-> [Pandoc -> Pandoc]
-> [Pandoc -> Pandoc]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                   (case Opt -> IpynbOutput
optIpynbOutput Opt
opts of
                     IpynbOutput
_ | Text
readerNameBase Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"ipynb" -> [Pandoc -> Pandoc] -> [Pandoc -> Pandoc]
forall a. a -> a
id
                     IpynbOutput
IpynbOutputAll  -> [Pandoc -> Pandoc] -> [Pandoc -> Pandoc]
forall a. a -> a
id
                     IpynbOutput
IpynbOutputNone -> (Maybe Format -> Pandoc -> Pandoc
filterIpynbOutput Maybe Format
forall a. Maybe a
Nothing (Pandoc -> Pandoc) -> [Pandoc -> Pandoc] -> [Pandoc -> Pandoc]
forall a. a -> [a] -> [a]
:)
                     IpynbOutput
IpynbOutputBest -> (Maybe Format -> Pandoc -> Pandoc
filterIpynbOutput (Format -> Maybe Format
forall a. a -> Maybe a
Just (Format -> Maybe Format) -> Format -> Maybe Format
forall a b. (a -> b) -> a -> b
$
                                   if Text -> Bool
htmlFormat Text
format
                                      then Text -> Format
Format Text
"html"
                                      else
                                        case Text
format of
                                          Text
"latex"  -> Text -> Format
Format Text
"latex"
                                          Text
"beamer" -> Text -> Format
Format Text
"latex"
                                          Text
_        -> Text -> Format
Format Text
format) (Pandoc -> Pandoc) -> [Pandoc -> Pandoc] -> [Pandoc -> Pandoc]
forall a. a -> [a] -> [a]
:))
                   ([Pandoc -> Pandoc] -> [Pandoc -> Pandoc])
-> [Pandoc -> Pandoc] -> [Pandoc -> Pandoc]
forall a b. (a -> b) -> a -> b
$ []

  let isPandocCiteproc :: Filter -> Bool
isPandocCiteproc (JSONFilter FilePath
f) = FilePath -> FilePath
takeBaseName FilePath
f FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"pandoc-citeproc"
      isPandocCiteproc Filter
_              = Bool
False

  Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ((Filter -> Bool) -> [Filter] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Filter -> Bool
isPandocCiteproc [Filter]
filters) (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$
    LogMessage -> m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> m ()) -> LogMessage -> m ()
forall a b. (a -> b) -> a -> b
$ Text -> Text -> LogMessage
Deprecated Text
"pandoc-citeproc filter"
             Text
"Use --citeproc instead."

  let cslMetadata :: Meta
cslMetadata =
        (Meta -> Meta)
-> (FilePath -> Meta -> Meta) -> Maybe FilePath -> Meta -> Meta
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Meta -> Meta
forall a. a -> a
id (Text -> FilePath -> Meta -> Meta
forall a b. (HasMeta a, ToMetaValue b) => Text -> b -> a -> a
forall b. ToMetaValue b => Text -> b -> Meta -> Meta
setMeta Text
"csl") (Opt -> Maybe FilePath
optCSL Opt
opts) (Meta -> Meta) -> (Meta -> Meta) -> Meta -> Meta
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
        (case Opt -> [FilePath]
optBibliography Opt
opts of
           [] -> Meta -> Meta
forall a. a -> a
id
           [FilePath]
xs -> Text -> [FilePath] -> Meta -> Meta
forall a b. (HasMeta a, ToMetaValue b) => Text -> b -> a -> a
forall b. ToMetaValue b => Text -> b -> Meta -> Meta
setMeta Text
"bibliography" [FilePath]
xs) (Meta -> Meta) -> (Meta -> Meta) -> Meta -> Meta
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
        (Meta -> Meta)
-> (FilePath -> Meta -> Meta) -> Maybe FilePath -> Meta -> Meta
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Meta -> Meta
forall a. a -> a
id (Text -> FilePath -> Meta -> Meta
forall a b. (HasMeta a, ToMetaValue b) => Text -> b -> a -> a
forall b. ToMetaValue b => Text -> b -> Meta -> Meta
setMeta Text
"citation-abbreviations")
                       (Opt -> Maybe FilePath
optCitationAbbreviations Opt
opts) (Meta -> Meta) -> Meta -> Meta
forall a b. (a -> b) -> a -> b
$ Meta
forall a. Monoid a => a
mempty

  let filterEnv :: Environment
filterEnv = ReaderOptions -> WriterOptions -> Environment
Environment ReaderOptions
readerOpts WriterOptions
writerOptions

  let inputParams :: InputParameters m
inputParams = InputParameters
        { inputReader :: Reader m
inputReader = Reader m
reader
        , inputReaderName :: Text
inputReaderName = Text
readerNameBase
        , inputReaderOptions :: ReaderOptions
inputReaderOptions = ReaderOptions
readerOpts
        , inputSources :: [FilePath]
inputSources = [FilePath]
sources
        , inputFileScope :: Bool
inputFileScope = Opt -> Bool
optFileScope Opt
opts
        , inputSpacesPerTab :: Maybe Int
inputSpacesPerTab = if Opt -> Bool
optPreserveTabs Opt
opts
                              then Maybe Int
forall a. Maybe a
Nothing
                              else Int -> Maybe Int
forall a. a -> Maybe a
Just (Opt -> Int
optTabStop Opt
opts)
        }

  Pandoc
doc <- InputParameters m -> m Pandoc
forall (m :: * -> *).
PandocMonad m =>
InputParameters m -> m Pandoc
readInput InputParameters m
inputParams
          m Pandoc -> (Pandoc -> m Pandoc) -> m Pandoc
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ( Pandoc -> m Pandoc
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Pandoc -> m Pandoc) -> (Pandoc -> Pandoc) -> Pandoc -> m Pandoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Meta -> Meta) -> Pandoc -> Pandoc
adjustMetadata (Meta
metadataFromFile Meta -> Meta -> Meta
forall a. Semigroup a => a -> a -> a
<>)
            (Pandoc -> m Pandoc) -> (Pandoc -> m Pandoc) -> Pandoc -> m Pandoc
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> Pandoc -> m Pandoc
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Pandoc -> m Pandoc) -> (Pandoc -> Pandoc) -> Pandoc -> m Pandoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Meta -> Meta) -> Pandoc -> Pandoc
adjustMetadata (Meta -> Meta -> Meta
forall a. Semigroup a => a -> a -> a
<> Opt -> Meta
optMetadata Opt
opts)
            (Pandoc -> m Pandoc) -> (Pandoc -> m Pandoc) -> Pandoc -> m Pandoc
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> Pandoc -> m Pandoc
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Pandoc -> m Pandoc) -> (Pandoc -> Pandoc) -> Pandoc -> m Pandoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Meta -> Meta) -> Pandoc -> Pandoc
adjustMetadata (Meta -> Meta -> Meta
forall a. Semigroup a => a -> a -> a
<> Meta
cslMetadata)
            (Pandoc -> m Pandoc) -> (Pandoc -> m Pandoc) -> Pandoc -> m Pandoc
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> [Pandoc -> Pandoc] -> Pandoc -> m Pandoc
forall (m :: * -> *).
Monad m =>
[Pandoc -> Pandoc] -> Pandoc -> m Pandoc
applyTransforms [Pandoc -> Pandoc]
transforms
            (Pandoc -> m Pandoc) -> (Pandoc -> m Pandoc) -> Pandoc -> m Pandoc
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> ScriptingEngine
-> Environment -> [Filter] -> [FilePath] -> Pandoc -> m Pandoc
forall (m :: * -> *).
(PandocMonad m, MonadIO m) =>
ScriptingEngine
-> Environment -> [Filter] -> [FilePath] -> Pandoc -> m Pandoc
applyFilters ScriptingEngine
scriptingEngine Environment
filterEnv [Filter]
filters [Text -> FilePath
T.unpack Text
format]
            (Pandoc -> m Pandoc) -> (Pandoc -> m Pandoc) -> Pandoc -> m Pandoc
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (if Bool -> Bool
not (Opt -> Bool
optSandbox Opt
opts) Bool -> Bool -> Bool
&&
                    (Maybe FilePath -> Bool
forall a. Maybe a -> Bool
isJust (Opt -> Maybe FilePath
optExtractMedia Opt
opts)
                     Bool -> Bool -> Bool
|| Text
format Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"docx") -- for fallback pngs
                 then Pandoc -> m Pandoc
forall (m :: * -> *). PandocMonad m => Pandoc -> m Pandoc
fillMediaBag
                 else Pandoc -> m Pandoc
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return)
            (Pandoc -> m Pandoc) -> (Pandoc -> m Pandoc) -> Pandoc -> m Pandoc
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (Pandoc -> m Pandoc)
-> (FilePath -> Pandoc -> m Pandoc)
-> Maybe FilePath
-> Pandoc
-> m Pandoc
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Pandoc -> m Pandoc
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath -> Pandoc -> m Pandoc
forall (m :: * -> *).
(PandocMonad m, MonadIO m) =>
FilePath -> Pandoc -> m Pandoc
extractMedia (Opt -> Maybe FilePath
optExtractMedia Opt
opts)
            )

  Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Text
format Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"docx" Bool -> Bool -> Bool
&& Bool -> Bool
not (Opt -> Bool
optSandbox Opt
opts)) (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Int -> m ()
forall (m :: * -> *). (PandocMonad m, MonadIO m) => Int -> m ()
createPngFallbacks (WriterOptions -> Int
writerDpi WriterOptions
writerOptions)

  PandocOutput
output <- case Writer m
writer of
    ByteStringWriter WriterOptions -> Pandoc -> m ByteString
f
      | Text
format Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"chunkedhtml" -> ByteString -> PandocOutput
ZipOutput (ByteString -> PandocOutput) -> m ByteString -> m PandocOutput
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> WriterOptions -> Pandoc -> m ByteString
f WriterOptions
writerOptions Pandoc
doc
      | Bool
otherwise -> ByteString -> PandocOutput
BinaryOutput (ByteString -> PandocOutput) -> m ByteString -> m PandocOutput
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> WriterOptions -> Pandoc -> m ByteString
f WriterOptions
writerOptions Pandoc
doc
    TextWriter WriterOptions -> Pandoc -> m Text
f -> case OutputSettings m -> Maybe FilePath
forall (m :: * -> *). OutputSettings m -> Maybe FilePath
outputPdfProgram OutputSettings m
outputSettings of
      Just FilePath
pdfProg -> do
              Either ByteString ByteString
res <- FilePath
-> [FilePath]
-> (WriterOptions -> Pandoc -> m Text)
-> WriterOptions
-> Pandoc
-> m (Either ByteString ByteString)
forall (m :: * -> *).
(PandocMonad m, MonadIO m, MonadMask m) =>
FilePath
-> [FilePath]
-> (WriterOptions -> Pandoc -> m Text)
-> WriterOptions
-> Pandoc
-> m (Either ByteString ByteString)
makePDF FilePath
pdfProg (Opt -> [FilePath]
optPdfEngineOpts Opt
opts) WriterOptions -> Pandoc -> m Text
f
                      WriterOptions
writerOptions Pandoc
doc
              case Either ByteString ByteString
res of
                   Right ByteString
pdf -> PandocOutput -> m PandocOutput
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (PandocOutput -> m PandocOutput) -> PandocOutput -> m PandocOutput
forall a b. (a -> b) -> a -> b
$ ByteString -> PandocOutput
BinaryOutput ByteString
pdf
                   Left ByteString
err' -> PandocError -> m PandocOutput
forall a. PandocError -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> m PandocOutput) -> PandocError -> m PandocOutput
forall a b. (a -> b) -> a -> b
$ Text -> PandocError
PandocPDFError (Text -> PandocError) -> Text -> PandocError
forall a b. (a -> b) -> a -> b
$
                                   Text -> Text
TL.toStrict (OnDecodeError -> ByteString -> Text
TE.decodeUtf8With OnDecodeError
TE.lenientDecode ByteString
err')

      Maybe FilePath
Nothing -> do
              let ensureNl :: Text -> Text
ensureNl Text
t
                    | Bool
standalone = Text
t
                    | Text -> Bool
T.null Text
t Bool -> Bool -> Bool
|| HasCallStack => Text -> Char
Text -> Char
T.last Text
t Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'\n' = Text
t Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Char -> Text
T.singleton Char
'\n'
                    | Bool
otherwise = Text
t
              Text
textOutput <- Text -> Text
ensureNl (Text -> Text) -> m Text -> m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> WriterOptions -> Pandoc -> m Text
f WriterOptions
writerOptions Pandoc
doc
              if (Opt -> Bool
optSelfContained Opt
opts Bool -> Bool -> Bool
|| Opt -> Bool
optEmbedResources Opt
opts) Bool -> Bool -> Bool
&& Text -> Bool
htmlFormat Text
format
                 then Text -> PandocOutput
TextOutput (Text -> PandocOutput) -> m Text -> m PandocOutput
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> m Text
forall (m :: * -> *). PandocMonad m => Text -> m Text
makeSelfContained Text
textOutput
                 else PandocOutput -> m PandocOutput
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (PandocOutput -> m PandocOutput) -> PandocOutput -> m PandocOutput
forall a b. (a -> b) -> a -> b
$ Text -> PandocOutput
TextOutput Text
textOutput
  [LogMessage]
reports <- m [LogMessage]
forall (m :: * -> *). PandocMonad m => m [LogMessage]
getLog
  (PandocOutput, [LogMessage]) -> m (PandocOutput, [LogMessage])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (PandocOutput
output, [LogMessage]
reports)

data PandocOutput =
      TextOutput Text
    | BinaryOutput BL.ByteString
    | ZipOutput BL.ByteString
  deriving (Int -> PandocOutput -> FilePath -> FilePath
[PandocOutput] -> FilePath -> FilePath
PandocOutput -> FilePath
(Int -> PandocOutput -> FilePath -> FilePath)
-> (PandocOutput -> FilePath)
-> ([PandocOutput] -> FilePath -> FilePath)
-> Show PandocOutput
forall a.
(Int -> a -> FilePath -> FilePath)
-> (a -> FilePath) -> ([a] -> FilePath -> FilePath) -> Show a
$cshowsPrec :: Int -> PandocOutput -> FilePath -> FilePath
showsPrec :: Int -> PandocOutput -> FilePath -> FilePath
$cshow :: PandocOutput -> FilePath
show :: PandocOutput -> FilePath
$cshowList :: [PandocOutput] -> FilePath -> FilePath
showList :: [PandocOutput] -> FilePath -> FilePath
Show)

type Transform = Pandoc -> Pandoc

-- | Configure the common state
configureCommonState :: PandocMonad m => Maybe FilePath -> Opt -> m ()
configureCommonState :: forall (m :: * -> *).
PandocMonad m =>
Maybe FilePath -> Opt -> m ()
configureCommonState Maybe FilePath
datadir Opt
opts = do
  Maybe FilePath -> m ()
forall (m :: * -> *). PandocMonad m => Maybe FilePath -> m ()
setUserDataDir Maybe FilePath
datadir
  Bool -> m ()
forall (m :: * -> *). PandocMonad m => Bool -> m ()
setTrace (Opt -> Bool
optTrace Opt
opts)
  Verbosity -> m ()
forall (m :: * -> *). PandocMonad m => Verbosity -> m ()
setVerbosity (Opt -> Verbosity
optVerbosity Opt
opts)
  [FilePath] -> m ()
forall (m :: * -> *). PandocMonad m => [FilePath] -> m ()
setResourcePath (Opt -> [FilePath]
optResourcePath Opt
opts)
  [FilePath] -> m ()
forall (m :: * -> *). PandocMonad m => [FilePath] -> m ()
setInputFiles ([FilePath] -> Maybe [FilePath] -> [FilePath]
forall a. a -> Maybe a -> a
fromMaybe [FilePath
"-"] (Opt -> Maybe [FilePath]
optInputFiles Opt
opts))
  Maybe FilePath -> m ()
forall (m :: * -> *). PandocMonad m => Maybe FilePath -> m ()
setOutputFile (Opt -> Maybe FilePath
optOutputFile Opt
opts)
  Bool -> m ()
forall (m :: * -> *). PandocMonad m => Bool -> m ()
setNoCheckCertificate (Opt -> Bool
optNoCheckCertificate Opt
opts)

  ((Text, Text) -> m ()) -> [(Text, Text)] -> m ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ ((Text -> Text -> m ()) -> (Text, Text) -> m ()
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Text -> Text -> m ()
forall (m :: * -> *). PandocMonad m => Text -> Text -> m ()
setRequestHeader) (Opt -> [(Text, Text)]
optRequestHeaders Opt
opts)

  case Text -> Meta -> Text
lookupMetaString Text
"lang" (Opt -> Meta
optMetadata Opt
opts) of
    Text
""      -> Lang -> m ()
forall (m :: * -> *). PandocMonad m => Lang -> m ()
setTranslations (Lang -> m ()) -> Lang -> m ()
forall a b. (a -> b) -> a -> b
$ Text
-> Maybe Text
-> Maybe Text
-> [Text]
-> [(Text, [(Text, Text)])]
-> [Text]
-> Lang
Lang Text
"en" Maybe Text
forall a. Maybe a
Nothing (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"US") [] [] []
    Text
l       -> case Text -> Either FilePath Lang
parseLang Text
l of
                 Left FilePath
_   -> LogMessage -> m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> m ()) -> LogMessage -> m ()
forall a b. (a -> b) -> a -> b
$ Text -> LogMessage
InvalidLang Text
l
                 Right Lang
l' -> Lang -> m ()
forall (m :: * -> *). PandocMonad m => Lang -> m ()
setTranslations Lang
l'

-- | Retrieves the set of abbreviations to be used by pandoc. These currently
-- only affect the Markdown reader.
readAbbreviations :: PandocMonad m => Maybe FilePath -> m (Set.Set Text)
readAbbreviations :: forall (m :: * -> *).
PandocMonad m =>
Maybe FilePath -> m (Set Text)
readAbbreviations Maybe FilePath
mbfilepath =
  [Text] -> Set Text
forall a. Ord a => [a] -> Set a
Set.fromList ([Text] -> Set Text)
-> (ByteString -> [Text]) -> ByteString -> Set Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Bool) -> [Text] -> [Text]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (Text -> Bool) -> Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Bool
T.null) ([Text] -> [Text])
-> (ByteString -> [Text]) -> ByteString -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
T.lines (Text -> [Text]) -> (ByteString -> Text) -> ByteString -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
UTF8.toText (ByteString -> Set Text) -> m ByteString -> m (Set Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
  case Maybe FilePath
mbfilepath of
    Maybe FilePath
Nothing -> FilePath -> m ByteString
forall (m :: * -> *). PandocMonad m => FilePath -> m ByteString
readDataFile FilePath
"abbreviations"
    Just FilePath
f  -> FilePath -> m ByteString
forall (m :: * -> *). PandocMonad m => FilePath -> m ByteString
readFileStrict FilePath
f

createPngFallbacks :: (PandocMonad m, MonadIO m) => Int -> m ()
createPngFallbacks :: forall (m :: * -> *). (PandocMonad m, MonadIO m) => Int -> m ()
createPngFallbacks Int
dpi = do
  -- create fallback pngs for svgs
  [(FilePath, Text, ByteString)]
items <- MediaBag -> [(FilePath, Text, ByteString)]
mediaItems (MediaBag -> [(FilePath, Text, ByteString)])
-> m MediaBag -> m [(FilePath, Text, ByteString)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m MediaBag
forall (m :: * -> *). PandocMonad m => m MediaBag
getMediaBag
  [(FilePath, Text, ByteString)]
-> ((FilePath, Text, ByteString) -> m ()) -> m ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [(FilePath, Text, ByteString)]
items (((FilePath, Text, ByteString) -> m ()) -> m ())
-> ((FilePath, Text, ByteString) -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ \(FilePath
fp, Text
mt, ByteString
bs) ->
    case (Char -> Bool) -> Text -> Text
T.takeWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/=Char
';') Text
mt of
      Text
"image/svg+xml" -> do
        Either Text ByteString
res <- Int -> ByteString -> m (Either Text ByteString)
forall (m :: * -> *).
MonadIO m =>
Int -> ByteString -> m (Either Text ByteString)
svgToPng Int
dpi ByteString
bs
        case Either Text ByteString
res of
          Right ByteString
bs' -> do
            let fp' :: FilePath
fp' = FilePath
fp FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath
".png"
            FilePath -> Maybe Text -> ByteString -> m ()
forall (m :: * -> *).
PandocMonad m =>
FilePath -> Maybe Text -> ByteString -> m ()
insertMedia FilePath
fp' (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"image/png") ByteString
bs'
          Left Text
e -> LogMessage -> m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> m ()) -> LogMessage -> m ()
forall a b. (a -> b) -> a -> b
$ Text -> Text -> LogMessage
CouldNotConvertImage (FilePath -> Text
T.pack FilePath
fp) (Text -> Text
forall a. Show a => a -> Text
tshow Text
e)
      Text
_ -> () -> m ()
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

getMetadataFromFiles :: PandocMonad m
                     => Text -> ReaderOptions -> [FilePath] -> m Meta
getMetadataFromFiles :: forall (m :: * -> *).
PandocMonad m =>
Text -> ReaderOptions -> [FilePath] -> m Meta
getMetadataFromFiles Text
readerFormat ReaderOptions
readerOpts = \case
  []    -> Meta -> m Meta
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Meta
forall a. Monoid a => a
mempty
  [FilePath]
paths -> [Meta] -> Meta
forall a. Monoid a => [a] -> a
mconcat ([Meta] -> Meta) -> m [Meta] -> m Meta
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> do
    -- If format is markdown or commonmark, use the enabled extensions,
    -- otherwise treat metadata as pandoc markdown (see #7926, #6832)
    let readerOptsMeta :: ReaderOptions
readerOptsMeta =
          if Text
readerFormat Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text
"markdown", Text
"commonmark"]
          then ReaderOptions
readerOpts
          else ReaderOptions
readerOpts{ readerExtensions :: Extensions
readerExtensions = Extensions
pandocExtensions }
    [FilePath] -> (FilePath -> m Meta) -> m [Meta]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [FilePath]
paths ((FilePath -> m Meta) -> m [Meta])
-> (FilePath -> m Meta) -> m [Meta]
forall a b. (a -> b) -> a -> b
$ \FilePath
path -> do
      ByteString
raw <- FilePath -> m ByteString
forall (m :: * -> *). PandocMonad m => FilePath -> m ByteString
readMetadataFile FilePath
path
      ReaderOptions -> Maybe FilePath -> ByteString -> m Meta
forall (m :: * -> *).
PandocMonad m =>
ReaderOptions -> Maybe FilePath -> ByteString -> m Meta
yamlToMeta ReaderOptions
readerOptsMeta (FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just FilePath
path) ByteString
raw

htmlFormat :: Text -> Bool
htmlFormat :: Text -> Bool
htmlFormat = (Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text
"html",Text
"html4",Text
"html5",Text
"s5",Text
"slidy",
                      Text
"slideous",Text
"dzslides",Text
"revealjs"])

isTextFormat :: Text -> Bool
isTextFormat :: Text -> Bool
isTextFormat Text
s = Text
s Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [Text
"odt",Text
"docx",Text
"epub2",Text
"epub3",Text
"epub",Text
"pptx"]

adjustMetadata :: (Meta -> Meta) -> Pandoc -> Pandoc
adjustMetadata :: (Meta -> Meta) -> Pandoc -> Pandoc
adjustMetadata Meta -> Meta
f (Pandoc Meta
meta [Block]
bs) = Meta -> [Block] -> Pandoc
Pandoc (Meta -> Meta
f Meta
meta) [Block]
bs

-- Transformations of a Pandoc document post-parsing:

applyTransforms :: Monad m => [Transform] -> Pandoc -> m Pandoc
applyTransforms :: forall (m :: * -> *).
Monad m =>
[Pandoc -> Pandoc] -> Pandoc -> m Pandoc
applyTransforms [Pandoc -> Pandoc]
transforms Pandoc
d = Pandoc -> m Pandoc
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Pandoc -> m Pandoc) -> Pandoc -> m Pandoc
forall a b. (a -> b) -> a -> b
$ ((Pandoc -> Pandoc) -> Pandoc -> Pandoc)
-> Pandoc -> [Pandoc -> Pandoc] -> Pandoc
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (Pandoc -> Pandoc) -> Pandoc -> Pandoc
forall a b. (a -> b) -> a -> b
($) Pandoc
d [Pandoc -> Pandoc]
transforms

writeFnBinary :: FilePath -> BL.ByteString -> IO ()
writeFnBinary :: FilePath -> ByteString -> IO ()
writeFnBinary FilePath
"-" = ByteString -> IO ()
BL.putStr
writeFnBinary FilePath
f   = FilePath -> ByteString -> IO ()
BL.writeFile (FilePath -> FilePath
UTF8.encodePath FilePath
f)

writerFn :: IO.Newline -> FilePath -> Text -> IO ()
writerFn :: Newline -> FilePath -> Text -> IO ()
writerFn Newline
eol FilePath
"-" = Newline -> Text -> IO ()
UTF8.putStrWith Newline
eol
writerFn Newline
eol FilePath
f   = Newline -> FilePath -> Text -> IO ()
UTF8.writeFileWith Newline
eol FilePath
f