From 418bd42df85b93016e50ba48042804e8f51341b5 Mon Sep 17 00:00:00 2001 From: Albert Krewinkel Date: Sat, 3 Nov 2018 07:33:04 +0100 Subject: App: extract output settings into module --- src/Text/Pandoc/App/OutputSettings.hs | 317 ++++++++++++++++++++++++++++++++++ 1 file changed, 317 insertions(+) create mode 100644 src/Text/Pandoc/App/OutputSettings.hs (limited to 'src/Text/Pandoc/App/OutputSettings.hs') diff --git a/src/Text/Pandoc/App/OutputSettings.hs b/src/Text/Pandoc/App/OutputSettings.hs new file mode 100644 index 000000000..a7d5bee1b --- /dev/null +++ b/src/Text/Pandoc/App/OutputSettings.hs @@ -0,0 +1,317 @@ +{-# LANGUAGE CPP #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE NoImplicitPrelude #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TupleSections #-} +{- +Copyright (C) 2006-2018 John MacFarlane + +This program is free software; you can redistribute it and/or modify +it under the terms of the GNU General Public License as published by +the Free Software Foundation; either version 2 of the License, or +(at your option) any later version. + +This program is distributed in the hope that it will be useful, +but WITHOUT ANY WARRANTY; without even the implied warranty of +MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +GNU General Public License for more details. + +You should have received a copy of the GNU General Public License +along with this program; if not, write to the Free Software +Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA +-} + +{- | + Module : Text.Pandoc.App + Copyright : Copyright (C) 2006-2018 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 Prelude +import qualified Control.Exception as E +import Control.Monad +import Control.Monad.Except (catchError, throwError) +import Control.Monad.Trans +import Data.Char (toLower) +import Data.List (find, isPrefixOf, isSuffixOf) +import Data.Maybe (fromMaybe) +import Skylighting (defaultSyntaxMap) +import Skylighting.Parser (addSyntaxDefinition, parseSyntaxDefinition) +import System.Exit (exitSuccess) +import System.FilePath +import System.IO (stdout) +import Text.Pandoc +import Text.Pandoc.App.CommandLineOptions (Opt (..), engines) +import Text.Pandoc.BCP47 (Lang (..), parseBCP47) +import qualified Text.Pandoc.UTF8 as UTF8 + +-- | Settings specifying how document output should be produced. +data OutputSettings = OutputSettings + { outputFormat :: String + , outputWriter :: Writer PandocIO + , outputWriterName :: String + , outputWriterOptions :: WriterOptions + , outputPdfProgram :: Maybe String + } + +readUtf8File :: PandocMonad m => FilePath -> m String +readUtf8File = fmap UTF8.toString . readFileStrict + +-- | Get output settings from command line options. +optToOutputSettings :: Opt -> PandocIO OutputSettings +optToOutputSettings opts = do + let outputFile = fromMaybe "-" (optOutputFile opts) + + when (optDumpArgs opts) . liftIO $ do + UTF8.hPutStrLn stdout outputFile + mapM_ (UTF8.hPutStrLn stdout) (optInputFiles opts) + exitSuccess + + epubMetadata <- case optEpubMetadata opts of + Nothing -> return Nothing + Just fp -> Just <$> readUtf8File fp + + let nonPdfWriterName Nothing = defaultWriterName outputFile + nonPdfWriterName (Just x) = x + + let pdfOutput = map toLower (takeExtension outputFile) == ".pdf" + (writerName, maybePdfProg) <- + if pdfOutput + then liftIO $ pdfWriterAndProg (optWriter opts) (optPdfEngine opts) + else return (nonPdfWriterName $ optWriter opts, Nothing) + + let format = map toLower $ baseWriterName + $ takeFileName writerName -- in case path to lua script + + -- disabling the custom writer for now + (writer, writerExts) <- + if ".lua" `isSuffixOf` format + then return (TextWriter + (\o d -> writeCustom writerName o d) + :: Writer PandocIO, mempty) + else case getWriter (map toLower writerName) of + Left e -> throwError $ PandocAppError $ + if format == "pdf" + then e ++ "\n" ++ pdfIsNoWriterErrorMsg + else e + Right (w, es) -> return (w :: Writer PandocIO, es) + + + let standalone = optStandalone opts || not (isTextFormat format) || pdfOutput + + let addStringAsVariable varname s vars = return $ (varname, s) : vars + + let addSyntaxMap existingmap f = do + res <- liftIO (parseSyntaxDefinition f) + case res of + Left errstr -> throwError $ PandocSyntaxMapError errstr + Right syn -> return $ addSyntaxDefinition syn existingmap + + syntaxMap <- foldM addSyntaxMap defaultSyntaxMap + (optSyntaxDefinitions opts) + + -- note: this reverses the list constructed in option parsing, + -- which in turn was reversed from the command-line order, + -- so we end up with the correct order in the variable list: + let withList _ [] vars = return vars + withList f (x:xs) vars = f x vars >>= withList f xs + + let addContentsAsVariable varname fp vars = do + s <- UTF8.toString <$> readFileStrict fp + return $ (varname, s) : vars + + variables <- + withList (addStringAsVariable "sourcefile") + (reverse $ optInputFiles opts) + (("outputfile", fromMaybe "-" (optOutputFile opts)) + : optVariables opts) + -- we reverse this list because, unlike + -- the other option lists here, it is + -- not reversed when parsed from CLI arguments. + -- See withList, above. + >>= + withList (addContentsAsVariable "include-before") + (optIncludeBeforeBody opts) + >>= + withList (addContentsAsVariable "include-after") + (optIncludeAfterBody opts) + >>= + withList (addContentsAsVariable "header-includes") + (optIncludeInHeader opts) + >>= + withList (addStringAsVariable "css") (optCss opts) + >>= + maybe return (addStringAsVariable "title-prefix") + (optTitlePrefix opts) + >>= + maybe return (addStringAsVariable "epub-cover-image") + (optEpubCoverImage opts) + >>= + (\vars -> if format == "dzslides" + then do + dztempl <- UTF8.toString <$> readDataFile + ("dzslides" "template.html") + let dzline = "