diff options
Diffstat (limited to 'src')
-rw-r--r-- | src/Text/Pandoc/App.hs | 16 | ||||
-rw-r--r-- | src/Text/Pandoc/App/CommandLineOptions.hs | 38 | ||||
-rw-r--r-- | src/Text/Pandoc/App/Opt.hs | 245 | ||||
-rw-r--r-- | src/Text/Pandoc/App/OutputSettings.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Filter.hs | 21 | ||||
-rw-r--r-- | src/Text/Pandoc/Logging.hs | 9 | ||||
-rw-r--r-- | src/Text/Pandoc/Options.hs | 98 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Math.hs | 6 |
8 files changed, 390 insertions, 45 deletions
diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index f3d342ebf..0f379419c 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -46,7 +46,8 @@ import System.IO (nativeNewline, stdout) import qualified System.IO as IO (Newline (..)) import Text.Pandoc import Text.Pandoc.App.FormatHeuristics (formatFromFilePaths) -import Text.Pandoc.App.Opt (Opt (..), LineEnding (..), defaultOpts) +import Text.Pandoc.App.Opt (Opt (..), LineEnding (..), defaultOpts, + IpynbOutput (..) ) import Text.Pandoc.App.CommandLineOptions (parseOptions, options) import Text.Pandoc.App.OutputSettings (OutputSettings (..), optToOutputSettings) import Text.Pandoc.BCP47 (Lang (..), parseBCP47) @@ -227,7 +228,7 @@ convertWithOpts opts = do } metadataFromFile <- - case optMetadataFile opts of + case optMetadataFiles opts of [] -> return mempty paths -> mapM readFileLazy paths >>= mapM (yamlToMeta readerOpts) >>= return . (foldr1 (<>)) @@ -250,17 +251,16 @@ convertWithOpts opts = do then (eastAsianLineBreakFilter :) else id) . (case optIpynbOutput opts of - "all" -> id - "none" -> (filterIpynbOutput Nothing :) - "best" -> (filterIpynbOutput (Just $ + IpynbOutputAll -> id + IpynbOutputNone -> (filterIpynbOutput Nothing :) + IpynbOutputBest -> (filterIpynbOutput (Just $ if htmlFormat format then Format "html" else case format of "latex" -> Format "latex" "beamer" -> Format "latex" - _ -> Format format) :) - _ -> id) -- should not happen + _ -> Format format) :)) $ [] let sourceToDoc :: [FilePath] -> PandocIO Pandoc @@ -297,7 +297,7 @@ convertWithOpts opts = do ByteStringWriter f -> f writerOptions doc >>= writeFnBinary outputFile TextWriter f -> case outputPdfProgram outputSettings of Just pdfProg -> do - res <- makePDF pdfProg (optPdfEngineArgs opts) f + res <- makePDF pdfProg (optPdfEngineOpts opts) f writerOptions doc case res of Right pdf -> writeFnBinary outputFile pdf diff --git a/src/Text/Pandoc/App/CommandLineOptions.hs b/src/Text/Pandoc/App/CommandLineOptions.hs index d22ca3f86..9d2ec695f 100644 --- a/src/Text/Pandoc/App/CommandLineOptions.hs +++ b/src/Text/Pandoc/App/CommandLineOptions.hs @@ -42,7 +42,7 @@ import System.FilePath import System.IO (stdout) import Text.Pandoc import Text.Pandoc.Builder (setMeta) -import Text.Pandoc.App.Opt (Opt (..), LineEnding (..)) +import Text.Pandoc.App.Opt (Opt (..), LineEnding (..), IpynbOutput (..)) import Text.Pandoc.Filter (Filter (..)) import Text.Pandoc.Highlighting (highlightingStyles) import Text.Pandoc.Writers.Math (defaultMathJaxURL, defaultKaTeXURL) @@ -64,7 +64,6 @@ import qualified Data.Text as T import Data.Text (Text) import Text.DocTemplates (ToContext(toVal), Context(..)) import qualified Text.Pandoc.UTF8 as UTF8 -import qualified Data.YAML.Aeson as YA import qualified Data.YAML as Y parseOptions :: [OptDescr (Opt -> IO Opt)] -> Opt -> IO Opt @@ -156,8 +155,8 @@ options = , Option "" ["metadata-file"] (ReqArg - (\arg opt -> return opt{ optMetadataFile = - normalizePath arg : optMetadataFile opt }) + (\arg opt -> return opt{ optMetadataFiles = + normalizePath arg : optMetadataFiles opt }) "FILE") "" @@ -175,15 +174,14 @@ options = Just dd -> [fp, dd </> "defaults" </> fp] fp' <- fromMaybe fp <$> findFile fps inp <- readFileLazy fp' - let defaults = YA.encode1 opt - case YA.decode1 (defaults <> inp) of + case Y.decode1 inp of Right (newopts :: Opt) -> return newopts Left (errpos, errmsg) -> throwError $ PandocParseError $ - "Error parsing " ++ fp' ++ - " (line " ++ show (Y.posLine errpos) ++ - " column " ++ show (Y.posColumn errpos) ++ - ")\n" ++ errmsg + "Error parsing " ++ fp' ++ " line " ++ + show (Y.posLine errpos) ++ " column " ++ + show (Y.posColumn errpos) ++ ":\n" ++ errmsg + ) "FILE") "" @@ -219,9 +217,9 @@ options = (ReqArg (\arg opt -> case arg of - "auto" -> return opt{ optWrapText = WrapAuto } - "none" -> return opt{ optWrapText = WrapNone } - "preserve" -> return opt{ optWrapText = WrapPreserve } + "auto" -> return opt{ optWrap = WrapAuto } + "none" -> return opt{ optWrap = WrapNone } + "preserve" -> return opt{ optWrap = WrapPreserve } _ -> E.throwIO $ PandocOptionError "--wrap must be auto, none, or preserve") "auto|none|preserve") @@ -409,8 +407,8 @@ options = , Option "" ["pdf-engine-opt"] (ReqArg (\arg opt -> do - let oldArgs = optPdfEngineArgs opt - return opt { optPdfEngineArgs = oldArgs ++ [arg]}) + let oldArgs = optPdfEngineOpts opt + return opt { optPdfEngineOpts = oldArgs ++ [arg]}) "STRING") "" -- "Flags to pass to the PDF-engine, all instances of this option are accumulated and used" @@ -655,10 +653,12 @@ options = , Option "" ["ipynb-output"] (ReqArg (\arg opt -> - if arg `notElem` ["all","none","best"] - then E.throwIO $ PandocOptionError $ - "ipynb-output must be all, none, or best" - else return opt { optIpynbOutput = arg }) + case arg of + "all" -> return opt{ optIpynbOutput = IpynbOutputAll } + "best" -> return opt{ optIpynbOutput = IpynbOutputBest } + "none" -> return opt{ optIpynbOutput = IpynbOutputNone } + _ -> E.throwIO $ PandocOptionError $ + "ipynb-output must be all, none, or best") "all|none|best") "" -- "Starting number for sections, subsections, etc." diff --git a/src/Text/Pandoc/App/Opt.hs b/src/Text/Pandoc/App/Opt.hs index c491d8ae2..d14365e85 100644 --- a/src/Text/Pandoc/App/Opt.hs +++ b/src/Text/Pandoc/App/Opt.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE CPP #-} @@ -17,6 +18,7 @@ Options for pandoc when used as an app. module Text.Pandoc.App.Opt ( Opt(..) , LineEnding (..) + , IpynbOutput (..) , defaultOpts ) where import Prelude @@ -31,15 +33,43 @@ import Text.Pandoc.Options (TopLevelDivision (TopLevelDefault), ObfuscationMethod (NoObfuscation), CiteMethod (Citeproc)) import Text.Pandoc.Shared (camelCaseToHyphenated) -import Text.DocTemplates (Context(..)) -import Data.Text (Text) +import Text.DocTemplates (Context(..), Val(..)) +import Data.Text (Text, unpack) +import qualified Data.Text as T +import qualified Data.Map as M +import Text.Pandoc.Definition (Meta(..), MetaValue(..)) import Data.Aeson (defaultOptions, Options(..)) import Data.Aeson.TH (deriveJSON) -import Text.Pandoc.Definition (Meta) +import Control.Monad (foldM) +import Control.Applicative ((<|>)) +import Data.YAML -- | The type of line-endings to be used when writing plain-text. data LineEnding = LF | CRLF | Native deriving (Show, Generic) +instance FromYAML LineEnding where + parseYAML = withStr "LineEnding" $ \t -> + case T.toLower t of + "lf" -> return LF + "crlf" -> return CRLF + "native" -> return Native + _ -> fail $ "Unknown line ending type " ++ show t + +-- | How to handle output blocks in ipynb. +data IpynbOutput = + IpynbOutputAll + | IpynbOutputNone + | IpynbOutputBest + deriving (Show, Generic) + +instance FromYAML IpynbOutput where + parseYAML = withStr "LineEnding" $ \t -> + case t of + "none" -> return IpynbOutputNone + "all" -> return IpynbOutputAll + "best" -> return IpynbOutputBest + _ -> fail $ "Unknown ipynb output type " ++ show t + -- | Data structure for command line options. data Opt = Opt { optTabStop :: Int -- ^ Number of spaces per tab @@ -52,7 +82,7 @@ data Opt = Opt , optTemplate :: Maybe FilePath -- ^ Custom template , optVariables :: Context Text -- ^ Template variables to set , optMetadata :: Meta -- ^ Metadata fields to set - , optMetadataFile :: [FilePath] -- ^ Name of YAML metadata file + , optMetadataFiles :: [FilePath] -- ^ Name of YAML metadata files , optOutputFile :: Maybe FilePath -- ^ Name of output file , optInputFiles :: [FilePath] -- ^ Names of input files , optNumberSections :: Bool -- ^ Number sections in LaTeX @@ -82,7 +112,7 @@ data Opt = Opt , optReferenceLinks :: Bool -- ^ Use reference links in writing markdown, rst , optReferenceLocation :: ReferenceLocation -- ^ location for footnotes and link references in markdown output , optDpi :: Int -- ^ Dpi - , optWrapText :: WrapOption -- ^ Options for wrapping text + , optWrap :: WrapOption -- ^ Options for wrapping text , optColumns :: Int -- ^ Line length in characters , optFilters :: [Filter] -- ^ Filters to apply , optEmailObfuscation :: ObfuscationMethod @@ -93,7 +123,7 @@ data Opt = Opt , optCiteMethod :: CiteMethod -- ^ Method to output cites , optListings :: Bool -- ^ Use listings package for code blocks , optPdfEngine :: Maybe String -- ^ Program to use for latex/html -> pdf - , optPdfEngineArgs :: [String] -- ^ Flags to pass to the engine + , optPdfEngineOpts :: [String] -- ^ Flags to pass to the engine , optSlideLevel :: Maybe Int -- ^ Header level that creates slides , optSetextHeaders :: Bool -- ^ Use atx headers for markdown level 1-2 , optAscii :: Bool -- ^ Prefer ascii output @@ -103,7 +133,7 @@ data Opt = Opt , optFileScope :: Bool -- ^ Parse input files before combining , optTitlePrefix :: Maybe String -- ^ Prefix for title , optCss :: [FilePath] -- ^ CSS files to link to - , optIpynbOutput :: String -- ^ Maybe f to use best data; Nothing to omit + , optIpynbOutput :: IpynbOutput -- ^ How to treat ipynb output blocks , optIncludeBeforeBody :: [FilePath] -- ^ Files to include before , optIncludeAfterBody :: [FilePath] -- ^ Files to include after body , optIncludeInHeader :: [FilePath] -- ^ Files to include in header @@ -113,6 +143,186 @@ data Opt = Opt , optStripComments :: Bool -- ^ Skip HTML comments } deriving (Generic, Show) +instance FromYAML Opt where + parseYAML (Mapping _ _ m) = + foldM doOpt defaultOpts (M.toList m) + parseYAML n = failAtNode n "Expected a mapping" + +doOpt :: Opt -> (Node Pos, Node Pos) -> Parser Opt +doOpt opt (k',v) = do + k <- case k' of + Scalar _ (SStr t) -> return t + Scalar _ _ -> failAtNode k' "Non-string key" + _ -> failAtNode k' "Non-scalar key" + case k of + "tab-stop" -> + parseYAML v >>= \x -> return opt{ optTabStop = x } + "preserve-tabs" -> + parseYAML v >>= \x -> return opt { optPreserveTabs = x } + "standalone" -> + parseYAML v >>= \x -> return opt { optStandalone = x } + "table-of-contents" -> + parseYAML v >>= \x -> return opt { optTableOfContents = x } + "toc" -> + parseYAML v >>= \x -> return opt { optTableOfContents = x } + "from" -> + parseYAML v >>= \x -> return opt { optFrom = unpack <$> x } + "reader" -> + parseYAML v >>= \x -> return opt { optFrom = unpack <$> x } + "to" -> + parseYAML v >>= \x -> return opt { optTo = unpack <$> x } + "writer" -> + parseYAML v >>= \x -> return opt { optTo = unpack <$> x } + "shift-heading-level-by" -> + parseYAML v >>= \x -> return opt { optShiftHeadingLevelBy = x } + "template" -> + parseYAML v >>= \x -> return opt { optTemplate = unpack <$> x } + "variables" -> + parseYAML v >>= \x -> return opt { optVariables = x } + "metadata" -> + parseYAML v >>= \x -> return opt { optMetadata = contextToMeta x } + "metadata-files" -> + (parseYAML v >>= \x -> return opt { optMetadataFiles = map unpack x }) + "metadata-file" -> -- allow either a list or a single value + (parseYAML v >>= \x -> return opt { optMetadataFiles = map unpack x }) + <|> + (parseYAML v >>= \x -> return opt { optMetadataFiles = [unpack x] }) + "output-file" -> + parseYAML v >>= \x -> return opt { optOutputFile = Just $ unpack x } + "input-files" -> + parseYAML v >>= \x -> return opt { optInputFiles = map unpack x } + "number-sections" -> + parseYAML v >>= \x -> return opt { optNumberSections = x } + "number-offset" -> + parseYAML v >>= \x -> return opt { optNumberOffset = x } + "section-divs" -> + parseYAML v >>= \x -> return opt { optSectionDivs = x } + "incremental" -> + parseYAML v >>= \x -> return opt { optIncremental = x } + "self-contained" -> + parseYAML v >>= \x -> return opt { optSelfContained = x } + "html-q-tags" -> + parseYAML v >>= \x -> return opt { optHtmlQTags = x } + "highlight-style" -> + parseYAML v >>= \x -> return opt { optHighlightStyle = unpack <$> x } + "syntax-definition" -> + (parseYAML v >>= \x -> return opt { optSyntaxDefinitions = map unpack x }) + <|> + (parseYAML v >>= \x -> return opt { optSyntaxDefinitions = [unpack x] }) + "syntax-definitions" -> + parseYAML v >>= \x -> return opt { optSyntaxDefinitions = map unpack x } + "top-level-division" -> + parseYAML v >>= \x -> return opt { optTopLevelDivision = x } + "html-math-method" -> + parseYAML v >>= \x -> return opt { optHTMLMathMethod = x } + "abbreviations" -> + parseYAML v >>= \x -> return opt { optAbbreviations = unpack <$> x } + "reference-doc" -> + parseYAML v >>= \x -> return opt { optReferenceDoc = unpack <$> x } + "epub-subdirectory" -> + parseYAML v >>= \x -> return opt { optEpubSubdirectory = unpack x } + "epub-metadata" -> + parseYAML v >>= \x -> return opt { optEpubMetadata = unpack <$> x } + "epub-fonts" -> + parseYAML v >>= \x -> return opt { optEpubFonts = map unpack x } + "epub-chapter-level" -> + parseYAML v >>= \x -> return opt { optEpubChapterLevel = x } + "epub-cover-image" -> + parseYAML v >>= \x -> return opt { optEpubCoverImage = unpack <$> x } + "toc-depth" -> + parseYAML v >>= \x -> return opt { optTOCDepth = x } + "dump-args" -> + parseYAML v >>= \x -> return opt { optDumpArgs = x } + "ignore-args" -> + parseYAML v >>= \x -> return opt { optIgnoreArgs = x } + "verbosity" -> + parseYAML v >>= \x -> return opt { optVerbosity = x } + "trace" -> + parseYAML v >>= \x -> return opt { optTrace = x } + "log-file" -> + parseYAML v >>= \x -> return opt { optLogFile = unpack <$> x } + "fail-if-warnings" -> + parseYAML v >>= \x -> return opt { optFailIfWarnings = x } + "reference-links" -> + parseYAML v >>= \x -> return opt { optReferenceLinks = x } + "reference-location" -> + parseYAML v >>= \x -> return opt { optReferenceLocation = x } + "dpi" -> + parseYAML v >>= \x -> return opt { optDpi = x } + "wrap" -> + parseYAML v >>= \x -> return opt { optWrap = x } + "columns" -> + parseYAML v >>= \x -> return opt { optColumns = x } + "filters" -> + parseYAML v >>= \x -> return opt { optFilters = x } + "email-obfuscation" -> + parseYAML v >>= \x -> return opt { optEmailObfuscation = x } + "identifier-prefix" -> + parseYAML v >>= \x -> return opt { optIdentifierPrefix = unpack x } + "strip-empty-paragraphs" -> + parseYAML v >>= \x -> return opt { optStripEmptyParagraphs = x } + "indented-code-classes" -> + parseYAML v >>= \x -> return opt { optIndentedCodeClasses = map unpack x } + "data-dir" -> + parseYAML v >>= \x -> return opt { optDataDir = unpack <$> x } + "cite-method" -> + parseYAML v >>= \x -> return opt { optCiteMethod = x } + "listings" -> + parseYAML v >>= \x -> return opt { optListings = x } + "pdf-engine" -> + parseYAML v >>= \x -> return opt { optPdfEngine = unpack <$> x } + "pdf-engine-opts" -> + parseYAML v >>= \x -> return opt { optPdfEngineOpts = map unpack x } + "pdf-engine-opt" -> + (parseYAML v >>= \x -> return opt { optPdfEngineOpts = map unpack x }) + <|> + (parseYAML v >>= \x -> return opt { optPdfEngineOpts = [unpack x] }) + "slide-level" -> + parseYAML v >>= \x -> return opt { optSlideLevel = x } + "setext-headers" -> + parseYAML v >>= \x -> return opt { optSetextHeaders = x } + "ascii" -> + parseYAML v >>= \x -> return opt { optAscii = x } + "default-image-extension" -> + parseYAML v >>= \x -> return opt { optDefaultImageExtension = unpack x } + "extract-media" -> + parseYAML v >>= \x -> return opt { optExtractMedia = unpack <$> x } + "track-changes" -> + parseYAML v >>= \x -> return opt { optTrackChanges = x } + "file-scope" -> + parseYAML v >>= \x -> return opt { optFileScope = x } + "title-prefix" -> + parseYAML v >>= \x -> return opt { optTitlePrefix = unpack <$> x } + "css" -> + (parseYAML v >>= \x -> return opt { optCss = map unpack x }) + <|> + (parseYAML v >>= \x -> return opt { optCss = [unpack x] }) + "ipynb-output" -> + parseYAML v >>= \x -> return opt { optIpynbOutput = x } + "include-before-body" -> + (parseYAML v >>= \x -> return opt { optIncludeBeforeBody = map unpack x }) + <|> + (parseYAML v >>= \x -> return opt { optIncludeBeforeBody = [unpack x] }) + "include-after-body" -> + (parseYAML v >>= \x -> return opt { optIncludeAfterBody = map unpack x }) + <|> + (parseYAML v >>= \x -> return opt { optIncludeAfterBody = [unpack x] }) + "include-in-header" -> + (parseYAML v >>= \x -> return opt { optIncludeInHeader = map unpack x }) + <|> + (parseYAML v >>= \x -> return opt { optIncludeInHeader = [unpack x] }) + "resource-path" -> + parseYAML v >>= \x -> return opt { optResourcePath = map unpack x } + "request-headers" -> + parseYAML v >>= \x -> return opt { optRequestHeaders = + map (\(key,val) -> + (unpack key, unpack val)) x } + "eol" -> + parseYAML v >>= \x -> return opt { optEol = x } + "strip-comments" -> + parseYAML v >>= \x -> return opt { optStripComments = x } + _ -> failAtNode k' $ "Unknown option " ++ show k + -- | Defaults for command-line options. defaultOpts :: Opt defaultOpts = Opt @@ -126,7 +336,7 @@ defaultOpts = Opt , optTemplate = Nothing , optVariables = mempty , optMetadata = mempty - , optMetadataFile = [] + , optMetadataFiles = [] , optOutputFile = Nothing , optInputFiles = [] , optNumberSections = False @@ -156,7 +366,7 @@ defaultOpts = Opt , optReferenceLinks = False , optReferenceLocation = EndOfDocument , optDpi = 96 - , optWrapText = WrapAuto + , optWrap = WrapAuto , optColumns = 72 , optFilters = [] , optEmailObfuscation = NoObfuscation @@ -167,7 +377,7 @@ defaultOpts = Opt , optCiteMethod = Citeproc , optListings = False , optPdfEngine = Nothing - , optPdfEngineArgs = [] + , optPdfEngineOpts = [] , optSlideLevel = Nothing , optSetextHeaders = True , optAscii = False @@ -177,7 +387,7 @@ defaultOpts = Opt , optFileScope = False , optTitlePrefix = Nothing , optCss = [] - , optIpynbOutput = "best" + , optIpynbOutput = IpynbOutputBest , optIncludeBeforeBody = [] , optIncludeAfterBody = [] , optIncludeInHeader = [] @@ -187,9 +397,22 @@ defaultOpts = Opt , optStripComments = False } +contextToMeta :: Context Text -> Meta +contextToMeta (Context m) = + Meta . M.mapKeys unpack . M.map valToMetaVal $ m + +valToMetaVal :: Val Text -> MetaValue +valToMetaVal (MapVal (Context m)) = + MetaMap . M.mapKeys unpack . M.map valToMetaVal $ m +valToMetaVal (ListVal xs) = MetaList $ map valToMetaVal xs +valToMetaVal (SimpleVal t) = MetaString (unpack t) +valToMetaVal NullVal = MetaString "" + -- see https://github.com/jgm/pandoc/pull/4083 -- using generic deriving caused long compilation times $(deriveJSON + defaultOptions{ fieldLabelModifier = drop 11 . map toLower } ''IpynbOutput) +$(deriveJSON defaultOptions{ fieldLabelModifier = map toLower } ''LineEnding) $(deriveJSON defaultOptions{ fieldLabelModifier = diff --git a/src/Text/Pandoc/App/OutputSettings.hs b/src/Text/Pandoc/App/OutputSettings.hs index bdfb4cde2..3edeea1a1 100644 --- a/src/Text/Pandoc/App/OutputSettings.hs +++ b/src/Text/Pandoc/App/OutputSettings.hs @@ -211,7 +211,7 @@ optToOutputSettings opts = do , writerReferenceLinks = optReferenceLinks opts , writerReferenceLocation = optReferenceLocation opts , writerDpi = optDpi opts - , writerWrapText = optWrapText opts + , writerWrapText = optWrap opts , writerColumns = optColumns opts , writerEmailObfuscation = optEmailObfuscation opts , writerIdentifierPrefix = optIdentifierPrefix opts diff --git a/src/Text/Pandoc/Filter.hs b/src/Text/Pandoc/Filter.hs index a32c26fbd..5670d028e 100644 --- a/src/Text/Pandoc/Filter.hs +++ b/src/Text/Pandoc/Filter.hs @@ -2,6 +2,7 @@ {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE OverloadedStrings #-} {- | Module : Text.Pandoc.Filter Copyright : Copyright (C) 2006-2019 John MacFarlane @@ -28,12 +29,32 @@ import Text.Pandoc.Options (ReaderOptions) import qualified Text.Pandoc.Filter.JSON as JSONFilter import qualified Text.Pandoc.Filter.Lua as LuaFilter import qualified Text.Pandoc.Filter.Path as Path +import Data.YAML +import qualified Data.Text as T +import System.FilePath (takeExtension) +import Control.Applicative ((<|>)) -- | Type of filter and path to filter file. data Filter = LuaFilter FilePath | JSONFilter FilePath deriving (Show, Generic) +instance FromYAML Filter where + parseYAML node = + (withMap "Filter" $ \m -> do + ty <- m .: "type" + fp <- m .: "path" + case ty of + "lua" -> return $ LuaFilter $ T.unpack fp + "json" -> return $ JSONFilter $ T.unpack fp + _ -> fail $ "Unknown filter type " ++ show (ty :: T.Text)) node + <|> + (withStr "Filter" $ \t -> do + let fp = T.unpack t + case takeExtension fp of + ".lua" -> return $ LuaFilter fp + _ -> return $ JSONFilter fp) node + -- | Modify the given document using a filter. applyFilters :: ReaderOptions -> [Filter] diff --git a/src/Text/Pandoc/Logging.hs b/src/Text/Pandoc/Logging.hs index fad236dd3..74b8e1bb2 100644 --- a/src/Text/Pandoc/Logging.hs +++ b/src/Text/Pandoc/Logging.hs @@ -25,6 +25,7 @@ module Text.Pandoc.Logging ( import Prelude import Control.Monad (mzero) +import Data.YAML (withStr, FromYAML(..)) import Data.Aeson import Data.Aeson.Encode.Pretty (Config (..), defConfig, encodePretty', keyOrder) @@ -52,6 +53,14 @@ instance FromJSON Verbosity where _ -> mzero parseJSON _ = mzero +instance FromYAML Verbosity where + parseYAML = withStr "Verbosity" $ \t -> + case t of + "ERROR" -> return ERROR + "WARNING" -> return WARNING + "INFO" -> return INFO + _ -> mzero + data LogMessage = SkippedContent String SourcePos | IgnoredElement String diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs index 5dc94b2ad..5ff4504df 100644 --- a/src/Text/Pandoc/Options.hs +++ b/src/Text/Pandoc/Options.hs @@ -3,6 +3,7 @@ {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE OverloadedStrings #-} {- | Module : Text.Pandoc.Options Copyright : Copyright (C) 2012-2019 John MacFarlane @@ -29,12 +30,15 @@ module Text.Pandoc.Options ( module Text.Pandoc.Extensions , ReferenceLocation (..) , def , isEnabled + , defaultMathJaxURL + , defaultKaTeXURL ) where import Prelude +import Control.Applicative ((<|>)) import Data.Char (toLower) import Data.Data (Data) import Data.Default -import Data.Text (Text) +import Data.Text (Text, unpack) import Text.DocTemplates (Context(..)) import qualified Data.Set as Set import Data.Typeable (Typeable) @@ -46,6 +50,7 @@ import Text.Pandoc.Shared (camelCaseToHyphenated) import Text.DocTemplates (Template) import Data.Aeson.TH (deriveJSON, defaultOptions, Options(..), SumEncoding(..)) +import Data.YAML class HasSyntaxExtensions a where getExtensions :: a -> Extensions @@ -101,17 +106,58 @@ data HTMLMathMethod = PlainMath | KaTeX String -- url of KaTeX files deriving (Show, Read, Eq, Data, Typeable, Generic) +instance FromYAML HTMLMathMethod where + parseYAML node = + (withMap "HTMLMathMethod" $ \m -> do + method <- m .: "method" + mburl <- m .:? "url" + case unpack method of + "plain" -> return PlainMath + "webtex" -> return $ WebTeX $ maybe "" unpack mburl + "gladtex" -> return GladTeX + "mathml" -> return MathML + "mathjax" -> return $ MathJax $ + maybe defaultMathJaxURL unpack mburl + "katex" -> return $ KaTeX $ + maybe defaultKaTeXURL unpack mburl + _ -> fail $ "Unknown HTML math method " ++ show method) node + <|> (withStr "HTMLMathMethod" $ \method -> + case unpack method of + "plain" -> return PlainMath + "webtex" -> return $ WebTeX "" + "gladtex" -> return GladTeX + "mathml" -> return MathML + "mathjax" -> return $ MathJax defaultMathJaxURL + "katex" -> return $ KaTeX defaultKaTeXURL + _ -> fail $ "Unknown HTML math method " ++ show method) node + data CiteMethod = Citeproc -- use citeproc to render them | Natbib -- output natbib cite commands | Biblatex -- output biblatex cite commands deriving (Show, Read, Eq, Data, Typeable, Generic) +instance FromYAML CiteMethod where + parseYAML = withStr "Citeproc" $ \t -> + case t of + "citeproc" -> return Citeproc + "natbib" -> return Natbib + "biblatex" -> return Biblatex + _ -> fail $ "Unknown citation method " ++ show t + -- | Methods for obfuscating email addresses in HTML. data ObfuscationMethod = NoObfuscation | ReferenceObfuscation | JavascriptObfuscation deriving (Show, Read, Eq, Data, Typeable, Generic) +instance FromYAML ObfuscationMethod where + parseYAML = withStr "Citeproc" $ \t -> + case t of + "none" -> return NoObfuscation + "references" -> return ReferenceObfuscation + "javascript" -> return JavascriptObfuscation + _ -> fail $ "Unknown obfuscation method " ++ show t + -- | Varieties of HTML slide shows. data HTMLSlideVariant = S5Slides | SlidySlides @@ -127,12 +173,29 @@ data TrackChanges = AcceptChanges | AllChanges deriving (Show, Read, Eq, Data, Typeable, Generic) +instance FromYAML TrackChanges where + parseYAML = withStr "TrackChanges" $ \t -> + case t of + "accept" -> return AcceptChanges + "reject" -> return RejectChanges + "all" -> return AllChanges + _ -> fail $ "Unknown track changes method " ++ show t + -- | Options for wrapping text in the output. data WrapOption = WrapAuto -- ^ Automatically wrap to width | WrapNone -- ^ No non-semantic newlines | WrapPreserve -- ^ Preserve wrapping of input source deriving (Show, Read, Eq, Data, Typeable, Generic) +instance FromYAML WrapOption where + parseYAML = withStr "WrapOption" $ \t -> + case t of + "auto" -> return WrapAuto + "none" -> return WrapNone + "preserve" -> return WrapPreserve + _ -> fail $ "Unknown wrap method " ++ show t + + -- | Options defining the type of top-level headers. data TopLevelDivision = TopLevelPart -- ^ Top-level headers become parts | TopLevelChapter -- ^ Top-level headers become chapters @@ -141,12 +204,31 @@ data TopLevelDivision = TopLevelPart -- ^ Top-level headers become parts -- heuristics deriving (Show, Read, Eq, Data, Typeable, Generic) +instance FromYAML TopLevelDivision where + parseYAML = withStr "TopLevelDivision" $ \t -> + case t of + "part" -> return TopLevelPart + "chapter" -> return TopLevelChapter + "section" -> return TopLevelSection + "default" -> return TopLevelDefault + _ -> fail $ "Unknown top level division " ++ show t + + -- | Locations for footnotes and references in markdown output data ReferenceLocation = EndOfBlock -- ^ End of block | EndOfSection -- ^ prior to next section header (or end of document) | EndOfDocument -- ^ at end of document deriving (Show, Read, Eq, Data, Typeable, Generic) +instance FromYAML ReferenceLocation where + parseYAML = withStr "ReferenceLocation" $ \t -> + case t of + "block" -> return EndOfBlock + "section" -> return EndOfSection + "document" -> return EndOfDocument + _ -> fail $ "Unknown reference location " ++ show t + + -- | Options for writers data WriterOptions = WriterOptions { writerTemplate :: Maybe Template -- ^ Template to use @@ -227,16 +309,25 @@ instance HasSyntaxExtensions WriterOptions where isEnabled :: HasSyntaxExtensions a => Extension -> a -> Bool isEnabled ext opts = ext `extensionEnabled` getExtensions opts +defaultMathJaxURL :: String +defaultMathJaxURL = "https://cdn.jsdelivr.net/npm/mathjax@3/es5/" + +defaultKaTeXURL :: String +defaultKaTeXURL = "https://cdnjs.cloudflare.com/ajax/libs/KaTeX/0.9.0/" + $(deriveJSON defaultOptions ''ReaderOptions) + $(deriveJSON defaultOptions{ constructorTagModifier = map toLower, sumEncoding = TaggedObject{ tagFieldName = "method", contentsFieldName = "url" } } ''HTMLMathMethod) + $(deriveJSON defaultOptions{ constructorTagModifier = camelCaseToHyphenated } ''CiteMethod) + $(deriveJSON defaultOptions{ constructorTagModifier = \t -> case t of "NoObfuscation" -> "none" @@ -244,16 +335,21 @@ $(deriveJSON defaultOptions{ constructorTagModifier = "JavascriptObfuscation" -> "javascript" _ -> "none" } ''ObfuscationMethod) + $(deriveJSON defaultOptions ''HTMLSlideVariant) + $(deriveJSON defaultOptions{ constructorTagModifier = camelCaseToHyphenated } ''TrackChanges) + $(deriveJSON defaultOptions{ constructorTagModifier = camelCaseToHyphenated } ''WrapOption) + $(deriveJSON defaultOptions{ constructorTagModifier = camelCaseToHyphenated . drop 8 } ''TopLevelDivision) + $(deriveJSON defaultOptions{ constructorTagModifier = camelCaseToHyphenated } ''ReferenceLocation) diff --git a/src/Text/Pandoc/Writers/Math.hs b/src/Text/Pandoc/Writers/Math.hs index a84f74f00..3905a3abc 100644 --- a/src/Text/Pandoc/Writers/Math.hs +++ b/src/Text/Pandoc/Writers/Math.hs @@ -12,6 +12,7 @@ import Text.Pandoc.Class import Text.Pandoc.Definition import Text.Pandoc.Logging import Text.TeXMath (DisplayType (..), Exp, readTeX, writePandoc) +import Text.Pandoc.Options (defaultMathJaxURL, defaultKaTeXURL) -- | Converts a raw TeX math formula to a list of 'Pandoc' inlines. -- Defaults to raw formula between @$@ or @$$@ characters if entire formula @@ -51,8 +52,3 @@ convertMath writer mt str = DisplayMath -> DisplayBlock InlineMath -> DisplayInline -defaultMathJaxURL :: String -defaultMathJaxURL = "https://cdn.jsdelivr.net/npm/mathjax@3/es5/" - -defaultKaTeXURL :: String -defaultKaTeXURL = "https://cdnjs.cloudflare.com/ajax/libs/KaTeX/0.9.0/" |