Writers: Use defField for defaults.

This way explicitly specified fields not overridden.

Fixes a problem e.g. with specifying a documentclass via
the command line using -V.
This commit is contained in:
John MacFarlane 2013-06-27 22:42:55 -07:00
parent 9ab60a4d15
commit 899a65b7d1
15 changed files with 83 additions and 83 deletions

View file

@ -84,10 +84,10 @@ pandocToAsciiDoc opts (Pandoc meta blocks) = do
_ -> metadata
body <- blockListToAsciiDoc opts blocks
let main = render colwidth body
let context = setField "body" main
$ setField "toc"
let context = defField "body" main
$ defField "toc"
(writerTableOfContents opts && writerStandalone opts)
$ setField "titleblock" titleblock
$ defField "titleblock" titleblock
$ foldl (\acc (x,y) -> setField x y acc)
metadata' (writerVariables opts)
if writerStandalone opts

View file

@ -69,16 +69,16 @@ pandocToConTeXt options (Pandoc meta blocks) = do
meta
body <- mapM (elementToConTeXt options) $ hierarchicalize blocks
let main = (render colwidth . vcat) body
let context = setField "toc" (writerTableOfContents options)
$ setField "placelist" (intercalate ("," :: String) $
let context = defField "toc" (writerTableOfContents options)
$ defField "placelist" (intercalate ("," :: String) $
take (writerTOCDepth options + if writerChapters options
then 0
else 1)
["chapter","section","subsection","subsubsection",
"subsubsubsection","subsubsubsubsection"])
$ setField "body" main
$ setField "number-sections" (writerNumberSections options)
$ setField "mainlang" (maybe ""
$ defField "body" main
$ defField "number-sections" (writerNumberSections options)
$ defField "mainlang" (maybe ""
(reverse . takeWhile (/=',') . reverse)
(lookup "lang" $ writerVariables options))
$ foldl (\acc (x,y) -> setField x y acc)

View file

@ -87,8 +87,8 @@ writeDocbook opts (Pandoc meta blocks) =
(Just . render colwidth . inlinesToDocbook opts)
meta'
main = render' $ vcat (map (elementToDocbook opts' startLvl) elements)
context = setField "body" main
$ setField "mathml" (case writerHTMLMathMethod opts of
context = defField "body" main
$ defField "mathml" (case writerHTMLMathMethod opts of
MathML _ -> True
_ -> False)
$ foldl (\acc (x,y) -> setField x y acc)

View file

@ -156,25 +156,25 @@ pandocToHtml opts (Pandoc meta blocks) = do
Nothing -> mempty
else mempty
let context = (if stHighlighting st
then setField "highlighting-css"
then defField "highlighting-css"
(styleToCss $ writerHighlightStyle opts)
else id) $
(if stMath st
then setField "math" (renderHtml math)
then defField "math" (renderHtml math)
else id) $
setField "quotes" (stQuotes st) $
maybe id (setField "toc" . renderHtml) toc $
setField "author-meta" authsMeta $
maybe id (setField "date-meta") (normalizeDate dateMeta) $
setField "pagetitle" (stringify $ docTitle meta) $
setField "idprefix" (writerIdentifierPrefix opts) $
defField "quotes" (stQuotes st) $
maybe id (defField "toc" . renderHtml) toc $
defField "author-meta" authsMeta $
maybe id (defField "date-meta") (normalizeDate dateMeta) $
defField "pagetitle" (stringify $ docTitle meta) $
defField "idprefix" (writerIdentifierPrefix opts) $
-- these should maybe be set in pandoc.hs
setField "slidy-url"
defField "slidy-url"
("http://www.w3.org/Talks/Tools/Slidy2" :: String) $
setField "slideous-url" ("slideous" :: String) $
setField "revealjs-url" ("reveal.js" :: String) $
setField "s5-url" ("s5/default" :: String) $
setField "html5" (writerHtml5 opts) $
defField "slideous-url" ("slideous" :: String) $
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)
return (thebody, context)
@ -185,7 +185,7 @@ inTemplate :: TemplateTarget a
-> Html
-> a
inTemplate opts context body = renderTemplate' (writerTemplate opts)
$ setField "body" (renderHtml body) context
$ defField "body" (renderHtml body) context
-- | Like Text.XHtml's identifier, but adds the writerIdentifierPrefix
prefixedId :: WriterOptions -> String -> Attribute

View file

@ -120,43 +120,43 @@ pandocToLaTeX options (Pandoc meta blocks) = do
let main = render colwidth $ vsep body
st <- get
let biblioFiles = intercalate "," $ map dropExtension $ writerBiblioFiles options
let context = setField "toc" (writerTableOfContents options) $
setField "toc-depth" (show (writerTOCDepth options -
let context = defField "toc" (writerTableOfContents options) $
defField "toc-depth" (show (writerTOCDepth options -
if writerChapters options
then 1
else 0)) $
setField "body" main $
setField "title-meta" (stringify $ docTitle meta) $
setField "author-meta" (intercalate "; " $ map stringify $ docAuthors meta) $
setField "documentclass" (if writerBeamer options
defField "body" main $
defField "title-meta" (stringify $ docTitle meta) $
defField "author-meta" (intercalate "; " $ map stringify $ docAuthors meta) $
defField "documentclass" (if writerBeamer options
then ("beamer" :: String)
else if writerChapters options
then "book"
else "article") $
setField "verbatim-in-note" (stVerbInNote st) $
setField "tables" (stTable st) $
setField "strikeout" (stStrikeout st) $
setField "url" (stUrl st) $
setField "numbersections" (writerNumberSections options) $
setField "lhs" (stLHS st) $
setField "graphics" (stGraphics st) $
setField "book-class" (stBook st) $
setField "euro" (stUsesEuro st) $
setField "listings" (writerListings options || stLHS st) $
setField "beamer" (writerBeamer options) $
setField "mainlang" (maybe "" (reverse . takeWhile (/=',') . reverse)
defField "verbatim-in-note" (stVerbInNote st) $
defField "tables" (stTable st) $
defField "strikeout" (stStrikeout st) $
defField "url" (stUrl st) $
defField "numbersections" (writerNumberSections options) $
defField "lhs" (stLHS st) $
defField "graphics" (stGraphics st) $
defField "book-class" (stBook st) $
defField "euro" (stUsesEuro st) $
defField "listings" (writerListings options || stLHS st) $
defField "beamer" (writerBeamer options) $
defField "mainlang" (maybe "" (reverse . takeWhile (/=',') . reverse)
(lookup "lang" $ writerVariables options)) $
(if stHighlighting st
then setField "highlighting-macros" (styleToLaTeX
then defField "highlighting-macros" (styleToLaTeX
$ writerHighlightStyle options )
else id) $
(case writerCiteMethod options of
Natbib -> setField "biblio-files" biblioFiles .
setField "biblio-title" biblioTitle .
setField "natbib" True
Biblatex -> setField "biblio-files" biblioFiles .
setField "biblio-title" biblioTitle .
setField "biblatex" True
Natbib -> defField "biblio-files" biblioFiles .
defField "biblio-title" biblioTitle .
defField "natbib" True
Biblatex -> defField "biblio-files" biblioFiles .
defField "biblio-title" biblioTitle .
defField "biblatex" True
_ -> id) $
foldl (\acc (x,y) -> setField x y acc)
metadata (writerVariables options)

View file

@ -62,15 +62,15 @@ pandocToMan opts (Pandoc meta blocks) = do
case break (== ' ') title' of
(cmdName, rest) -> case reverse cmdName of
(')':d:'(':xs) | isDigit d ->
setField "title" (reverse xs) .
setField "section" [d] .
defField "title" (reverse xs) .
defField "section" [d] .
case splitBy (=='|') rest of
(ft:hds) ->
setField "footer" (trim ft) .
setField "header"
defField "footer" (trim ft) .
defField "header"
(trim $ concat hds)
[] -> id
_ -> setField "title" title'
_ -> defField "title" title'
metadata <- metaToJSON
(fmap (render colwidth) . blockListToMan opts)
(fmap (render colwidth) . inlineListToMan opts)
@ -80,9 +80,9 @@ pandocToMan opts (Pandoc meta blocks) = do
notes' <- notesToMan opts (reverse notes)
let main = render' $ body $$ notes' $$ text ""
hasTables <- liftM stHasTables get
let context = setField "body" main
let context = defField "body" main
$ setFieldsFromTitle
$ setField "has-tables" hasTables
$ defField "has-tables" hasTables
$ foldl (\acc (x,y) -> setField x y acc)
metadata (writerVariables opts)
if writerStandalone opts

View file

@ -145,11 +145,11 @@ pandocToMarkdown opts (Pandoc meta blocks) = do
let main = render' $ body <>
(if isEmpty notes' then empty else blankline <> notes') <>
(if isEmpty refs' then empty else blankline <> refs')
let context = setField "toc" (render' toc)
$ setField "body" main
let context = defField "toc" (render' toc)
$ defField "body" main
$ (if not (null (docTitle meta) && null (docAuthors meta)
&& null (docDate meta))
then setField "titleblock" (render' titleblock)
then defField "titleblock" (render' titleblock)
else id)
$ foldl (\acc (x,y) -> setField x y acc)
metadata (writerVariables opts)

View file

@ -64,8 +64,8 @@ pandocToMediaWiki opts (Pandoc meta blocks) = do
then "\n<references />"
else ""
let main = body ++ notes
let context = setField "body" main
$ setField "toc" (writerTableOfContents opts)
let context = defField "body" main
$ defField "toc" (writerTableOfContents opts)
$ foldl (\acc (x,y) -> setField x y acc)
metadata (writerVariables opts)
if writerStandalone opts

View file

@ -54,7 +54,7 @@ writeOPML opts (Pandoc meta blocks) =
(\ils -> [Plain ils]))
meta'
main = render colwidth $ vcat (map (elementToOPML opts) elements)
context = setField "body" main
context = defField "body" main
$ foldl (\acc (x,y) -> setField x y acc)
metadata (writerVariables opts)
in if writerStandalone opts

View file

@ -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, setField)
import Text.Pandoc.Shared (metaToJSON, defField, setField)
-- | Auxiliary function to convert Plain block to Para.
plainToPara :: Block -> Block
@ -192,8 +192,8 @@ writeOpenDocument opts (Pandoc meta blocks) =
listStyles = map listStyle (stListStyles s)
automaticStyles = inTagsIndented "office:automatic-styles" $ vcat $
reverse $ styles ++ listStyles
context = setField "body" body
$ setField "automatic-styles" (render' automaticStyles)
context = defField "body" body
$ defField "automatic-styles" (render' automaticStyles)
$ foldl (\acc (x,y) -> setField x y acc)
metadata (writerVariables opts)
in if writerStandalone opts

View file

@ -72,8 +72,8 @@ pandocToOrg (Pandoc meta blocks) = do
-- note that the notes may contain refs, so we do them first
hasMath <- liftM stHasMath get
let main = render colwidth $ foldl ($+$) empty $ [body, notes]
let context = setField "body" main
$ setField "math" hasMath
let context = defField "body" main
$ defField "math" hasMath
$ foldl (\acc (x,y) -> setField x y acc)
metadata (writerVariables opts)
if writerStandalone opts

View file

@ -82,12 +82,12 @@ pandocToRST (Pandoc meta blocks) = do
pics <- liftM (reverse . stImages) get >>= pictRefsToRST
hasMath <- liftM stHasMath get
let main = render colwidth $ foldl ($+$) empty $ [body, notes, refs, pics]
let context = setField "body" main
$ setField "toc" (writerTableOfContents opts)
$ setField "toc-depth" (writerTOCDepth opts)
$ setField "math" hasMath
$ setField "title" (render Nothing title :: String)
$ setField "math" hasMath
let context = defField "body" main
$ defField "toc" (writerTableOfContents opts)
$ defField "toc-depth" (writerTOCDepth opts)
$ defField "math" hasMath
$ defField "title" (render Nothing title :: String)
$ defField "math" hasMath
$ foldl (\acc (x,y) -> setField x y acc)
metadata (writerVariables opts)
if writerStandalone opts

View file

@ -82,10 +82,10 @@ writeRTF options (Pandoc meta blocks) =
body = concatMap (blockToRTF 0 AlignDefault) blocks
isTOCHeader (Header lev _ _) = lev <= writerTOCDepth options
isTOCHeader _ = False
context = setField "body" body
$ setField "spacer" spacer
context = defField "body" body
$ defField "spacer" spacer
$ (if writerTableOfContents options
then setField "toc"
then defField "toc"
(tableOfContents $ filter isTOCHeader blocks)
else id)
$ foldl (\acc (x,y) -> setField x y acc)

View file

@ -80,12 +80,12 @@ pandocToTexinfo options (Pandoc meta blocks) = do
main <- blockListToTexinfo blocks
st <- get
let body = render colwidth main
let context = setField "body" body
$ setField "toc" (writerTableOfContents options)
$ setField "titlepage" titlePage
$ setField "subscript" (stSubscript st)
$ setField "superscript" (stSuperscript st)
$ setField "strikeout" (stStrikeout st)
let context = defField "body" body
$ defField "toc" (writerTableOfContents options)
$ defField "titlepage" titlePage
$ defField "subscript" (stSubscript st)
$ defField "superscript" (stSuperscript st)
$ defField "strikeout" (stStrikeout st)
$ foldl (\acc (x,y) -> setField x y acc)
metadata (writerVariables options)
if writerStandalone options

View file

@ -59,7 +59,7 @@ pandocToTextile opts (Pandoc meta blocks) = do
body <- blockListToTextile opts blocks
notes <- liftM (unlines . reverse . stNotes) get
let main = body ++ if null notes then "" else ("\n\n" ++ notes)
let context = setField "body" main
let context = defField "body" main
$ foldl (\acc (x,y) -> setField x y acc)
metadata (writerVariables opts)
if writerStandalone opts