{-# LANGUAGE CPP #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TupleSections #-} {- | Module : Text.Pandoc.App Copyright : Copyright (C) 2006-2022 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane Stability : alpha Portability : portable Does a pandoc conversion based on command-line options. -} module Text.Pandoc.App.OutputSettings ( OutputSettings (..) , optToOutputSettings ) where import qualified Data.Map as M import qualified Data.Text as T import Text.DocTemplates (toVal, Context(..), Val(..)) import qualified Control.Exception as E import Control.Monad import Control.Monad.Except (throwError) import Control.Monad.Trans import Data.Char (toLower) import Data.List (find) import Data.Maybe (fromMaybe) import Skylighting (defaultSyntaxMap) import Skylighting.Parser (addSyntaxDefinition, parseSyntaxDefinition) import System.Directory (getCurrentDirectory) import System.Exit (exitSuccess) import System.FilePath import System.IO (stdout) import Text.Pandoc import Text.Pandoc.App.FormatHeuristics (formatFromFilePaths) import Text.Pandoc.App.Opt (Opt (..)) import Text.Pandoc.App.CommandLineOptions (engines, lookupHighlightStyle, setVariable) import Text.Pandoc.Writers.Custom (writeCustom) import qualified Text.Pandoc.UTF8 as UTF8 readUtf8File :: PandocMonad m => FilePath -> m T.Text readUtf8File = fmap UTF8.toText . readFileStrict -- | Settings specifying how document output should be produced. data OutputSettings m = OutputSettings { outputFormat :: T.Text , outputWriter :: Writer m , outputWriterName :: T.Text , outputWriterOptions :: WriterOptions , outputPdfProgram :: Maybe String } -- | Get output settings from command line options. optToOutputSettings :: (PandocMonad m, MonadIO m) => Opt -> m (OutputSettings m) optToOutputSettings opts = do let outputFile = fromMaybe "-" (optOutputFile opts) when (optDumpArgs opts) . liftIO $ do UTF8.hPutStrLn stdout (T.pack outputFile) mapM_ (UTF8.hPutStrLn stdout . T.pack) (fromMaybe [] $ optInputFiles opts) exitSuccess epubMetadata <- traverse readUtf8File $ optEpubMetadata opts let pdfOutput = map toLower (takeExtension outputFile) == ".pdf" || optTo opts == Just "pdf" (writerName, maybePdfProg) <- if pdfOutput then liftIO $ pdfWriterAndProg (case optTo opts of Just "pdf" -> Nothing x -> x) (optPdfEngine opts) else case optTo opts of Just f -> return (f, Nothing) Nothing | outputFile == "-" -> return ("html", Nothing) | otherwise -> case formatFromFilePaths [outputFile] of Nothing -> do report $ CouldNotDeduceFormat [T.pack $ takeExtension outputFile] "html" return ("html", Nothing) Just f -> return (f, Nothing) let format = if ".lua" `T.isSuffixOf` writerName then writerName else T.toLower $ baseWriterName writerName let makeSandboxed pureWriter = let files = maybe id (:) (optReferenceDoc opts) . maybe id (:) (optEpubMetadata opts) . maybe id (:) (optEpubCoverImage opts) . maybe id (:) (optCSL opts) . maybe id (:) (optCitationAbbreviations opts) $ optEpubFonts opts ++ optBibliography opts in case pureWriter of TextWriter w -> TextWriter $ \o d -> sandbox files (w o d) ByteStringWriter w -> ByteStringWriter $ \o d -> sandbox files (w o d) (writer, writerExts) <- if ".lua" `T.isSuffixOf` format then return (TextWriter (\o d -> writeCustom (T.unpack writerName) o d), mempty) else if optSandbox opts then case runPure (getWriter writerName) of Left e -> throwError e Right (w, wexts) -> return (makeSandboxed w, wexts) else getWriter (T.toLower writerName) let standalone = optStandalone opts || not (isTextFormat format) || pdfOutput let addSyntaxMap existingmap f = do res <- liftIO (parseSyntaxDefinition f) case res of Left errstr -> throwError $ PandocSyntaxMapError $ T.pack errstr Right syn -> return $ addSyntaxDefinition syn existingmap syntaxMap <- foldM addSyntaxMap defaultSyntaxMap (optSyntaxDefinitions opts) hlStyle <- traverse (lookupHighlightStyle . T.unpack) $ optHighlightStyle opts let setVariableM k v = return . setVariable k v let setListVariableM _ [] ctx = return ctx setListVariableM k vs ctx = do let ctxMap = unContext ctx return $ Context $ case M.lookup k ctxMap of Just (ListVal xs) -> M.insert k (ListVal $ xs ++ map toVal vs) ctxMap Just v -> M.insert k (ListVal $ v : map toVal vs) ctxMap Nothing -> M.insert k (toVal vs) ctxMap let getTextContents fp = UTF8.toText . fst <$> fetchItem (T.pack fp) let setFilesVariableM k fps ctx = do xs <- mapM getTextContents fps setListVariableM k xs ctx curdir <- liftIO getCurrentDirectory variables <- return (optVariables opts) >>= setListVariableM "sourcefile" (maybe ["-"] (fmap T.pack) (optInputFiles opts)) >>= setVariableM "outputfile" (T.pack outputFile) >>= setFilesVariableM "include-before" (optIncludeBeforeBody opts) >>= setFilesVariableM "include-after" (optIncludeAfterBody opts) >>= setFilesVariableM "header-includes" (optIncludeInHeader opts) >>= setListVariableM "css" (map T.pack $ optCss opts) >>= maybe return (setVariableM "title-prefix") (optTitlePrefix opts) >>= maybe return (setVariableM "epub-cover-image") (T.pack <$> optEpubCoverImage opts) >>= setVariableM "curdir" (T.pack curdir) >>= (\vars -> if format == "dzslides" then do dztempl <- UTF8.toText <$> readDataFile ("dzslides" "template.html") let dzline = "