aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/App/OutputSettings.hs
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2019-10-08 23:47:19 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2019-10-09 11:01:33 -0700
commit3aa069e1d5853966964471e36b0099ddba0489fd (patch)
tree4001a2798ecb6c0698355f8c6fd2f17c4238d8ab /src/Text/Pandoc/App/OutputSettings.hs
parentaceee9ca48484c300ac3519fb7991e3d22768312 (diff)
downloadpandoc-3aa069e1d5853966964471e36b0099ddba0489fd.tar.gz
Change optVariables from [(String, String)] to Context Text.
In Text.Pandoc.App.Opt [API change].
Diffstat (limited to 'src/Text/Pandoc/App/OutputSettings.hs')
-rw-r--r--src/Text/Pandoc/App/OutputSettings.hs33
1 files changed, 15 insertions, 18 deletions
diff --git a/src/Text/Pandoc/App/OutputSettings.hs b/src/Text/Pandoc/App/OutputSettings.hs
index 264eb4a65..cd591ce18 100644
--- a/src/Text/Pandoc/App/OutputSettings.hs
+++ b/src/Text/Pandoc/App/OutputSettings.hs
@@ -20,9 +20,6 @@ module Text.Pandoc.App.OutputSettings
) where
import Prelude
import qualified Control.Exception as E
-import qualified Data.Text as T
-import qualified Data.Map as M
-import Text.DocTemplates (Context(..), ToContext(toVal))
import Control.Monad
import Control.Monad.Except (catchError, throwError)
import Control.Monad.Trans
@@ -38,7 +35,8 @@ 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)
+import Text.Pandoc.App.CommandLineOptions (engines, lookupHighlightStyle,
+ setVariable)
import Text.Pandoc.BCP47 (Lang (..), parseBCP47)
import qualified Text.Pandoc.UTF8 as UTF8
@@ -97,8 +95,6 @@ optToOutputSettings opts = do
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
@@ -117,21 +113,24 @@ optToOutputSettings opts = do
let withList _ [] vars = return vars
withList f (x:xs) vars = f x vars >>= withList f xs
+ let setVariableM k v = return . setVariable k v
+
let addContentsAsVariable varname fp vars = do
s <- UTF8.toString . fst <$> fetchItem fp
- return $ (varname, s) : vars
+ setVariableM varname s vars
curdir <- liftIO getCurrentDirectory
variables <-
- withList (addStringAsVariable "sourcefile")
- (reverse $ optInputFiles opts)
- (("outputfile", fromMaybe "-" (optOutputFile opts))
- : optVariables opts)
+ withList (setVariableM "sourcefile")
-- we reverse this list because, unlike
-- the other option lists here, it is
-- not reversed when parsed from CLI arguments.
-- See withList, above.
+ (reverse $ optInputFiles opts)
+ (optVariables opts)
+ >>=
+ setVariableM "outputfile" (fromMaybe "-" (optOutputFile opts))
>>=
withList (addContentsAsVariable "include-before")
(optIncludeBeforeBody opts)
@@ -142,15 +141,15 @@ optToOutputSettings opts = do
withList (addContentsAsVariable "header-includes")
(optIncludeInHeader opts)
>>=
- withList (addStringAsVariable "css") (optCss opts)
+ withList (setVariableM "css") (optCss opts)
>>=
- maybe return (addStringAsVariable "title-prefix")
+ maybe return (setVariableM "title-prefix")
(optTitlePrefix opts)
>>=
- maybe return (addStringAsVariable "epub-cover-image")
+ maybe return (setVariableM "epub-cover-image")
(optEpubCoverImage opts)
>>=
- addStringAsVariable "curdir" curdir
+ setVariableM "curdir" curdir
>>=
(\vars -> if format == "dzslides"
then do
@@ -160,10 +159,8 @@ optToOutputSettings opts = do
let dzcore = unlines
$ dropWhile (not . (dzline `isPrefixOf`))
$ lines dztempl
- return $ ("dzslides-core", dzcore) : vars
+ setVariableM "dzslides-core" dzcore vars
else return vars)
- >>= fmap (Context . M.fromList) .
- traverse (\(x,y) -> return (T.pack x, toVal (T.pack y)))
templStr <- case optTemplate opts of
_ | not standalone -> return Nothing