Change optVariables from [(String, String)] to Context Text.
In Text.Pandoc.App.Opt [API change].
This commit is contained in:
parent
aceee9ca48
commit
3aa069e1d5
4 changed files with 37 additions and 27 deletions
|
@ -18,6 +18,7 @@ module Text.Pandoc.App.CommandLineOptions (
|
|||
, options
|
||||
, engines
|
||||
, lookupHighlightStyle
|
||||
, setVariable
|
||||
) where
|
||||
import Prelude
|
||||
import Control.Monad
|
||||
|
@ -59,6 +60,8 @@ import qualified Data.ByteString as BS
|
|||
import qualified Data.ByteString.Lazy as B
|
||||
import qualified Data.Map as M
|
||||
import qualified Data.Text as T
|
||||
import Data.Text (Text)
|
||||
import Text.DocTemplates (ToContext(toVal), Context(..))
|
||||
import qualified Text.Pandoc.UTF8 as UTF8
|
||||
|
||||
parseOptions :: [OptDescr (Opt -> IO Opt)] -> Opt -> IO Opt
|
||||
|
@ -175,7 +178,8 @@ options =
|
|||
(ReqArg
|
||||
(\arg opt -> do
|
||||
let (key, val) = splitField arg
|
||||
return opt{ optVariables = (key, val) : optVariables opt })
|
||||
return opt{ optVariables =
|
||||
setVariable key val $ optVariables opt })
|
||||
"KEY[:VALUE]")
|
||||
""
|
||||
|
||||
|
@ -554,10 +558,11 @@ options =
|
|||
|
||||
, Option "T" ["title-prefix"]
|
||||
(ReqArg
|
||||
(\arg opt -> do
|
||||
let newvars = ("title-prefix", arg) : optVariables opt
|
||||
return opt { optVariables = newvars,
|
||||
optStandalone = True })
|
||||
(\arg opt ->
|
||||
return opt {
|
||||
optVariables =
|
||||
setVariable "title-prefix" arg $ optVariables opt,
|
||||
optStandalone = True })
|
||||
"STRING")
|
||||
"" -- "String to prefix to HTML window title"
|
||||
|
||||
|
@ -579,7 +584,8 @@ options =
|
|||
(ReqArg
|
||||
(\arg opt ->
|
||||
return opt { optVariables =
|
||||
("epub-cover-image", arg) : optVariables opt })
|
||||
setVariable "epub-cover-image" arg $
|
||||
optVariables opt })
|
||||
"FILE")
|
||||
"" -- "Path of epub cover image"
|
||||
|
||||
|
@ -970,6 +976,11 @@ deprecatedOption o msg =
|
|||
Right () -> return ()
|
||||
Left e -> E.throwIO e
|
||||
|
||||
-- | Set text value in text context.
|
||||
setVariable :: String -> String -> Context Text -> Context Text
|
||||
setVariable key val (Context ctx) =
|
||||
Context $ M.insert (T.pack key) (toVal (T.pack val)) ctx
|
||||
|
||||
-- On Windows with ghc 8.6+, we need to rewrite paths
|
||||
-- beginning with \\ to \\?\UNC\. -- See #5127.
|
||||
normalizePath :: FilePath -> FilePath
|
||||
|
|
|
@ -31,6 +31,8 @@ import Text.Pandoc.Options (TopLevelDivision (TopLevelDefault),
|
|||
ObfuscationMethod (NoObfuscation),
|
||||
CiteMethod (Citeproc))
|
||||
import Text.Pandoc.Shared (camelCaseToHyphenated)
|
||||
import Text.DocTemplates (Context(..))
|
||||
import Data.Text (Text)
|
||||
import Data.Aeson (defaultOptions, Options(..))
|
||||
import Data.Aeson.TH (deriveJSON)
|
||||
|
||||
|
@ -47,7 +49,7 @@ data Opt = Opt
|
|||
, optTableOfContents :: Bool -- ^ Include table of contents
|
||||
, optShiftHeadingLevelBy :: Int -- ^ Shift heading level by
|
||||
, optTemplate :: Maybe FilePath -- ^ Custom template
|
||||
, optVariables :: [(String,String)] -- ^ Template variables to set
|
||||
, optVariables :: Context Text -- ^ Template variables to set
|
||||
, optMetadata :: [(String, String)] -- ^ Metadata fields to set
|
||||
, optMetadataFile :: [FilePath] -- ^ Name of YAML metadata file
|
||||
, optOutputFile :: Maybe FilePath -- ^ Name of output file
|
||||
|
@ -121,7 +123,7 @@ defaultOpts = Opt
|
|||
, optTableOfContents = False
|
||||
, optShiftHeadingLevelBy = 0
|
||||
, optTemplate = Nothing
|
||||
, optVariables = []
|
||||
, optVariables = mempty
|
||||
, optMetadata = []
|
||||
, optMetadataFile = []
|
||||
, optOutputFile = Nothing
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -24,7 +24,7 @@ extra-deps:
|
|||
- HsYAML-aeson-0.2.0.0
|
||||
# - doctemplates-0.6.1
|
||||
- git: https://github.com/jgm/doctemplates.git
|
||||
commit: b0e92bd6e32eb1a8c021598b4e8a5f25b9c5cd40
|
||||
commit: 8c30b5955584ff96459999c4958e8a953fed214f
|
||||
ghc-options:
|
||||
"$locals": -fhide-source-paths -Wno-missing-home-modules
|
||||
resolver: lts-14.6
|
||||
|
|
Loading…
Add table
Reference in a new issue