Metadata changes: Variables now completely shadow metadata.
Previously if you set a value both in metadata and with a variable, they'd be combined into a list. Now the variable replaces the value in document metadata. If many variables with the same name are set, a list is created. Shared: metaToJSON now has an argument for a variable list.
This commit is contained in:
parent
5cb0f0bbf1
commit
a1f010de78
16 changed files with 41 additions and 37 deletions
|
@ -526,13 +526,20 @@ makeMeta title authors date =
|
|||
-- | Create JSON value for template from a 'Meta' and an association list
|
||||
-- of variables, specified at the command line or in the writer.
|
||||
-- Variables overwrite metadata fields with the same names.
|
||||
-- If multiple variables are set with the same name, a list is
|
||||
-- assigned.
|
||||
metaToJSON :: Monad m
|
||||
=> ([Block] -> m String) -- ^ Writer for output format
|
||||
-> ([Inline] -> m String) -- ^ Writer for output format
|
||||
-> [(String, String)] -- ^ Variables
|
||||
-> Meta -- ^ Metadata
|
||||
-> m Value
|
||||
metaToJSON blockWriter inlineWriter (Meta metamap) = liftM toJSON $
|
||||
Traversable.mapM (metaValueToJSON blockWriter inlineWriter) metamap
|
||||
metaToJSON blockWriter inlineWriter vars (Meta metamap) = do
|
||||
let baseContext = foldl (\acc (x,y) -> setField x y acc) (Object H.empty) vars
|
||||
renderedMap <- Traversable.mapM (metaValueToJSON blockWriter inlineWriter)
|
||||
metamap
|
||||
return $ M.foldWithKey (\key val obj -> defField key val obj)
|
||||
baseContext renderedMap
|
||||
|
||||
metaValueToJSON :: Monad m
|
||||
=> ([Block] -> m String)
|
||||
|
|
|
@ -74,6 +74,7 @@ pandocToAsciiDoc opts (Pandoc meta blocks) = do
|
|||
metadata <- metaToJSON
|
||||
(fmap (render colwidth) . blockListToAsciiDoc opts)
|
||||
(fmap (render colwidth) . inlineListToAsciiDoc opts)
|
||||
(writerVariables opts)
|
||||
meta
|
||||
let addTitleLine (String t) = String $
|
||||
t <> "\n" <> T.replicate (T.length t) "="
|
||||
|
@ -88,8 +89,7 @@ pandocToAsciiDoc opts (Pandoc meta blocks) = do
|
|||
$ defField "toc"
|
||||
(writerTableOfContents opts && writerStandalone opts)
|
||||
$ defField "titleblock" titleblock
|
||||
$ foldl (\acc (x,y) -> setField x y acc)
|
||||
metadata' (writerVariables opts)
|
||||
$ metadata'
|
||||
if writerStandalone opts
|
||||
then return $ renderTemplate' (writerTemplate opts) context
|
||||
else return main
|
||||
|
|
|
@ -66,6 +66,7 @@ pandocToConTeXt options (Pandoc meta blocks) = do
|
|||
metadata <- metaToJSON
|
||||
(fmap (render colwidth) . blockListToConTeXt)
|
||||
(fmap (render colwidth) . inlineListToConTeXt)
|
||||
(writerVariables options)
|
||||
meta
|
||||
body <- mapM (elementToConTeXt options) $ hierarchicalize blocks
|
||||
let main = (render colwidth . vcat) body
|
||||
|
@ -81,8 +82,7 @@ pandocToConTeXt options (Pandoc meta blocks) = do
|
|||
$ defField "mainlang" (maybe ""
|
||||
(reverse . takeWhile (/=',') . reverse)
|
||||
(lookup "lang" $ writerVariables options))
|
||||
$ foldl (\acc (x,y) -> setField x y acc)
|
||||
metadata (writerVariables options)
|
||||
$ metadata
|
||||
return $ if writerStandalone options
|
||||
then renderTemplate' (writerTemplate options) context
|
||||
else main
|
||||
|
|
|
@ -85,14 +85,14 @@ writeDocbook opts (Pandoc meta blocks) =
|
|||
Just metadata = metaToJSON
|
||||
(Just . render colwidth . blocksToDocbook opts)
|
||||
(Just . render colwidth . inlinesToDocbook opts)
|
||||
(writerVariables opts)
|
||||
meta'
|
||||
main = render' $ vcat (map (elementToDocbook opts' startLvl) elements)
|
||||
context = defField "body" main
|
||||
$ defField "mathml" (case writerHTMLMathMethod opts of
|
||||
MathML _ -> True
|
||||
_ -> False)
|
||||
$ foldl (\acc (x,y) -> setField x y acc)
|
||||
metadata (writerVariables opts)
|
||||
$ metadata
|
||||
in if writerStandalone opts
|
||||
then renderTemplate' (writerTemplate opts) context
|
||||
else main
|
||||
|
|
|
@ -113,6 +113,7 @@ pandocToHtml opts (Pandoc meta blocks) = do
|
|||
metadata <- metaToJSON
|
||||
(fmap renderHtml . blockListToHtml opts)
|
||||
(fmap renderHtml . inlineListToHtml opts)
|
||||
(writerVariables opts)
|
||||
meta
|
||||
let authsMeta = map stringify $ docAuthors meta
|
||||
let dateMeta = stringify $ docDate meta
|
||||
|
@ -175,8 +176,7 @@ pandocToHtml opts (Pandoc meta blocks) = do
|
|||
defField "revealjs-url" ("reveal.js" :: String) $
|
||||
defField "s5-url" ("s5/default" :: String) $
|
||||
defField "html5" (writerHtml5 opts) $
|
||||
foldl (\acc (x,y) -> setField x y acc)
|
||||
metadata (writerVariables opts)
|
||||
metadata
|
||||
return (thebody, context)
|
||||
|
||||
inTemplate :: TemplateTarget a
|
||||
|
|
|
@ -106,6 +106,7 @@ pandocToLaTeX options (Pandoc meta blocks) = do
|
|||
metadata <- metaToJSON
|
||||
(fmap (render colwidth) . blockListToLaTeX)
|
||||
(fmap (render colwidth) . inlineListToLaTeX)
|
||||
(writerVariables options)
|
||||
meta
|
||||
let (blocks', lastHeader) = if writerCiteMethod options == Citeproc then
|
||||
(blocks, [])
|
||||
|
@ -158,8 +159,7 @@ pandocToLaTeX options (Pandoc meta blocks) = do
|
|||
defField "biblio-title" biblioTitle .
|
||||
defField "biblatex" True
|
||||
_ -> id) $
|
||||
foldl (\acc (x,y) -> setField x y acc)
|
||||
metadata (writerVariables options)
|
||||
metadata
|
||||
return $ if writerStandalone options
|
||||
then renderTemplate' template context
|
||||
else main
|
||||
|
|
|
@ -74,6 +74,7 @@ pandocToMan opts (Pandoc meta blocks) = do
|
|||
metadata <- metaToJSON
|
||||
(fmap (render colwidth) . blockListToMan opts)
|
||||
(fmap (render colwidth) . inlineListToMan opts)
|
||||
(writerVariables opts)
|
||||
$ deleteMeta "title" meta
|
||||
body <- blockListToMan opts blocks
|
||||
notes <- liftM stNotes get
|
||||
|
@ -83,8 +84,7 @@ pandocToMan opts (Pandoc meta blocks) = do
|
|||
let context = defField "body" main
|
||||
$ setFieldsFromTitle
|
||||
$ defField "has-tables" hasTables
|
||||
$ foldl (\acc (x,y) -> setField x y acc)
|
||||
metadata (writerVariables opts)
|
||||
$ metadata
|
||||
if writerStandalone opts
|
||||
then return $ renderTemplate' (writerTemplate opts) context
|
||||
else return main
|
||||
|
|
|
@ -134,6 +134,7 @@ pandocToMarkdown opts (Pandoc meta blocks) = do
|
|||
metadata <- metaToJSON
|
||||
(fmap (render colwidth) . blockListToMarkdown opts)
|
||||
(fmap (render colwidth) . inlineListToMarkdown opts)
|
||||
(writerVariables opts)
|
||||
meta
|
||||
body <- blockListToMarkdown opts blocks
|
||||
st <- get
|
||||
|
@ -151,8 +152,7 @@ pandocToMarkdown opts (Pandoc meta blocks) = do
|
|||
&& null (docDate meta))
|
||||
then defField "titleblock" (render' titleblock)
|
||||
else id)
|
||||
$ foldl (\acc (x,y) -> setField x y acc)
|
||||
metadata (writerVariables opts)
|
||||
$ metadata
|
||||
if writerStandalone opts
|
||||
then return $ renderTemplate' (writerTemplate opts) context
|
||||
else return main
|
||||
|
|
|
@ -57,6 +57,7 @@ pandocToMediaWiki opts (Pandoc meta blocks) = do
|
|||
metadata <- metaToJSON
|
||||
(fmap trimr . blockListToMediaWiki opts)
|
||||
(inlineListToMediaWiki opts)
|
||||
(writerVariables opts)
|
||||
meta
|
||||
body <- blockListToMediaWiki opts blocks
|
||||
notesExist <- get >>= return . stNotes
|
||||
|
@ -66,8 +67,7 @@ pandocToMediaWiki opts (Pandoc meta blocks) = do
|
|||
let main = body ++ notes
|
||||
let context = defField "body" main
|
||||
$ defField "toc" (writerTableOfContents opts)
|
||||
$ foldl (\acc (x,y) -> setField x y acc)
|
||||
metadata (writerVariables opts)
|
||||
$ metadata
|
||||
if writerStandalone opts
|
||||
then return $ renderTemplate' (writerTemplate opts) context
|
||||
else return main
|
||||
|
|
|
@ -52,11 +52,10 @@ writeOPML opts (Pandoc meta blocks) =
|
|||
(Just . writeMarkdown def . Pandoc nullMeta)
|
||||
(Just . trimr . writeMarkdown def . Pandoc nullMeta .
|
||||
(\ils -> [Plain ils]))
|
||||
(writerVariables opts)
|
||||
meta'
|
||||
main = render colwidth $ vcat (map (elementToOPML opts) elements)
|
||||
context = defField "body" main
|
||||
$ foldl (\acc (x,y) -> setField x y acc)
|
||||
metadata (writerVariables opts)
|
||||
context = defField "body" main metadata
|
||||
in if writerStandalone opts
|
||||
then renderTemplate' (writerTemplate opts) context
|
||||
else main
|
||||
|
|
|
@ -42,7 +42,7 @@ import Control.Arrow ( (***), (>>>) )
|
|||
import Control.Monad.State hiding ( when )
|
||||
import Data.Char (chr, isDigit)
|
||||
import qualified Data.Map as Map
|
||||
import Text.Pandoc.Shared (metaToJSON, defField, setField)
|
||||
import Text.Pandoc.Shared (metaToJSON, defField)
|
||||
|
||||
-- | Auxiliary function to convert Plain block to Para.
|
||||
plainToPara :: Block -> Block
|
||||
|
@ -183,6 +183,7 @@ writeOpenDocument opts (Pandoc meta blocks) =
|
|||
m <- metaToJSON
|
||||
(fmap (render colwidth) . blocksToOpenDocument opts)
|
||||
(fmap (render colwidth) . inlinesToOpenDocument opts)
|
||||
(writerVariables opts)
|
||||
meta
|
||||
b <- render' `fmap` blocksToOpenDocument opts blocks
|
||||
return (b, m)
|
||||
|
@ -194,8 +195,7 @@ writeOpenDocument opts (Pandoc meta blocks) =
|
|||
reverse $ styles ++ listStyles
|
||||
context = defField "body" body
|
||||
$ defField "automatic-styles" (render' automaticStyles)
|
||||
$ foldl (\acc (x,y) -> setField x y acc)
|
||||
metadata (writerVariables opts)
|
||||
$ metadata
|
||||
in if writerStandalone opts
|
||||
then renderTemplate' (writerTemplate opts) context
|
||||
else body
|
||||
|
|
|
@ -66,6 +66,7 @@ pandocToOrg (Pandoc meta blocks) = do
|
|||
metadata <- metaToJSON
|
||||
(fmap (render colwidth) . blockListToOrg)
|
||||
(fmap (render colwidth) . inlineListToOrg)
|
||||
(writerVariables opts)
|
||||
meta
|
||||
body <- blockListToOrg blocks
|
||||
notes <- liftM (reverse . stNotes) get >>= notesToOrg
|
||||
|
@ -74,8 +75,7 @@ pandocToOrg (Pandoc meta blocks) = do
|
|||
let main = render colwidth $ foldl ($+$) empty $ [body, notes]
|
||||
let context = defField "body" main
|
||||
$ defField "math" hasMath
|
||||
$ foldl (\acc (x,y) -> setField x y acc)
|
||||
metadata (writerVariables opts)
|
||||
$ metadata
|
||||
if writerStandalone opts
|
||||
then return $ renderTemplate' (writerTemplate opts) context
|
||||
else return main
|
||||
|
|
|
@ -74,6 +74,7 @@ pandocToRST (Pandoc meta blocks) = do
|
|||
title <- titleToRST (docTitle meta) subtit
|
||||
metadata <- metaToJSON (fmap (render colwidth) . blockListToRST)
|
||||
(fmap (trimr . render colwidth) . inlineListToRST)
|
||||
(writerVariables opts)
|
||||
$ deleteMeta "title" $ deleteMeta "subtitle" meta
|
||||
body <- blockListToRST blocks
|
||||
notes <- liftM (reverse . stNotes) get >>= notesToRST
|
||||
|
@ -88,8 +89,7 @@ pandocToRST (Pandoc meta blocks) = do
|
|||
$ defField "math" hasMath
|
||||
$ defField "title" (render Nothing title :: String)
|
||||
$ defField "math" hasMath
|
||||
$ foldl (\acc (x,y) -> setField x y acc)
|
||||
metadata (writerVariables opts)
|
||||
$ metadata
|
||||
if writerStandalone opts
|
||||
then return $ renderTemplate' (writerTemplate opts) context
|
||||
else return main
|
||||
|
|
|
@ -78,6 +78,7 @@ writeRTF options (Pandoc meta blocks) =
|
|||
Just metadata = metaToJSON
|
||||
(Just . concatMap (blockToRTF 0 AlignDefault))
|
||||
(Just . inlineListToRTF)
|
||||
(writerVariables options)
|
||||
meta
|
||||
body = concatMap (blockToRTF 0 AlignDefault) blocks
|
||||
isTOCHeader (Header lev _ _) = lev <= writerTOCDepth options
|
||||
|
@ -88,8 +89,7 @@ writeRTF options (Pandoc meta blocks) =
|
|||
then defField "toc"
|
||||
(tableOfContents $ filter isTOCHeader blocks)
|
||||
else id)
|
||||
$ foldl (\acc (x,y) -> setField x y acc)
|
||||
metadata (writerVariables options)
|
||||
$ metadata
|
||||
in if writerStandalone options
|
||||
then renderTemplate' (writerTemplate options) context
|
||||
else body
|
||||
|
|
|
@ -76,7 +76,7 @@ pandocToTexinfo options (Pandoc meta blocks) = do
|
|||
metadata <- metaToJSON
|
||||
(fmap (render colwidth) . blockListToTexinfo)
|
||||
(fmap (render colwidth) . inlineListToTexinfo)
|
||||
meta
|
||||
(writerVariables options) meta
|
||||
main <- blockListToTexinfo blocks
|
||||
st <- get
|
||||
let body = render colwidth main
|
||||
|
@ -86,8 +86,7 @@ pandocToTexinfo options (Pandoc meta blocks) = do
|
|||
$ defField "subscript" (stSubscript st)
|
||||
$ defField "superscript" (stSuperscript st)
|
||||
$ defField "strikeout" (stStrikeout st)
|
||||
$ foldl (\acc (x,y) -> setField x y acc)
|
||||
metadata (writerVariables options)
|
||||
$ metadata
|
||||
if writerStandalone options
|
||||
then return $ renderTemplate' (writerTemplate options) context
|
||||
else return body
|
||||
|
|
|
@ -55,13 +55,12 @@ writeTextile opts document =
|
|||
pandocToTextile :: WriterOptions -> Pandoc -> State WriterState String
|
||||
pandocToTextile opts (Pandoc meta blocks) = do
|
||||
metadata <- metaToJSON
|
||||
(blockListToTextile opts) (inlineListToTextile opts) meta
|
||||
(blockListToTextile opts) (inlineListToTextile opts)
|
||||
(writerVariables opts) meta
|
||||
body <- blockListToTextile opts blocks
|
||||
notes <- liftM (unlines . reverse . stNotes) get
|
||||
let main = body ++ if null notes then "" else ("\n\n" ++ notes)
|
||||
let context = defField "body" main
|
||||
$ foldl (\acc (x,y) -> setField x y acc)
|
||||
metadata (writerVariables opts)
|
||||
let context = defField "body" main metadata
|
||||
if writerStandalone opts
|
||||
then return $ renderTemplate' (writerTemplate opts) context
|
||||
else return main
|
||||
|
|
Loading…
Reference in a new issue