aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers/OpenDocument.hs
diff options
context:
space:
mode:
authorJohn MacFarlane <fiddlosopher@gmail.com>2013-05-10 22:53:35 -0700
committerJohn MacFarlane <fiddlosopher@gmail.com>2013-06-24 20:29:41 -0700
commitf869f7e08dad315945d52be3fcacf6ff0c05c5c1 (patch)
tree4c426ebf5a30b51499859f9d41a890534b6a18a6 /src/Text/Pandoc/Writers/OpenDocument.hs
parente32a8f5981969bb6d0a11bd945188c35817e4d96 (diff)
downloadpandoc-f869f7e08dad315945d52be3fcacf6ff0c05c5c1.tar.gz
Use new flexible metadata type.
* Depend on pandoc 1.12. * Added yaml dependency. * `Text.Pandoc.XML`: Removed `stripTags`. (API change.) * `Text.Pandoc.Shared`: Added `metaToJSON`. This will be used in writers to create a JSON object for use in the templates from the pandoc metadata. * Revised readers and writers to use the new Meta type. * `Text.Pandoc.Options`: Added `Ext_yaml_title_block`. * Markdown reader: Added support for YAML metadata block. Note that it must come at the beginning of the document. * `Text.Pandoc.Parsing.ParserState`: Replace `stateTitle`, `stateAuthors`, `stateDate` with `stateMeta`. * RST reader: Improved metadata. Treat initial field list as metadata when standalone specified. Previously ALL fields "title", "author", "date" in field lists were treated as metadata, even if not at the beginning. Use `subtitle` metadata field for subtitle. * `Text.Pandoc.Templates`: Export `renderTemplate'` that takes a string instead of a compiled template.. * OPML template: Use 'for' loop for authors. * Org template: '#+TITLE:' is inserted before the title. Previously the writer did this.
Diffstat (limited to 'src/Text/Pandoc/Writers/OpenDocument.hs')
-rw-r--r--src/Text/Pandoc/Writers/OpenDocument.hs37
1 files changed, 18 insertions, 19 deletions
diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs
index b59e096c9..0c09cde99 100644
--- a/src/Text/Pandoc/Writers/OpenDocument.hs
+++ b/src/Text/Pandoc/Writers/OpenDocument.hs
@@ -33,7 +33,7 @@ module Text.Pandoc.Writers.OpenDocument ( writeOpenDocument ) where
import Text.Pandoc.Definition
import Text.Pandoc.Options
import Text.Pandoc.XML
-import Text.Pandoc.Templates (renderTemplate)
+import Text.Pandoc.Templates (renderTemplate')
import Text.Pandoc.Readers.TeXMath
import Text.Pandoc.Pretty
import Text.Printf ( printf )
@@ -42,6 +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)
-- | Auxiliary function to convert Plain block to Para.
plainToPara :: Block -> Block
@@ -172,34 +173,32 @@ handleSpaces s
-- | Convert Pandoc document to string in OpenDocument format.
writeOpenDocument :: WriterOptions -> Pandoc -> String
-writeOpenDocument opts (Pandoc (Meta title authors date) blocks) =
- let ((doc, title', authors', date'),s) = flip runState
- defaultWriterState $ do
- title'' <- inlinesToOpenDocument opts title
- authors'' <- mapM (inlinesToOpenDocument opts) authors
- date'' <- inlinesToOpenDocument opts date
- doc'' <- blocksToOpenDocument opts blocks
- return (doc'', title'', authors'', date'')
- colwidth = if writerWrapText opts
+writeOpenDocument opts (Pandoc meta blocks) =
+ let colwidth = if writerWrapText opts
then Just $ writerColumns opts
else Nothing
render' = render colwidth
- body' = render' doc
+ ((body, metadata),s) = flip runState
+ defaultWriterState $ do
+ m <- metaToJSON
+ (fmap (render colwidth) . blocksToOpenDocument opts)
+ (fmap (render colwidth) . inlinesToOpenDocument opts)
+ meta
+ b <- render' `fmap` blocksToOpenDocument opts blocks
+ return (b, m)
styles = stTableStyles s ++ stParaStyles s ++ stTextStyles s
listStyle (n,l) = inTags True "text:list-style"
[("style:name", "L" ++ show n)] (vcat l)
listStyles = map listStyle (stListStyles s)
automaticStyles = inTagsIndented "office:automatic-styles" $ vcat $
reverse $ styles ++ listStyles
- context = writerVariables opts ++
- [ ("body", body')
- , ("automatic-styles", render' automaticStyles)
- , ("title", render' title')
- , ("date", render' date') ] ++
- [ ("author", render' a) | a <- authors' ]
+ context = setField "body" body
+ $ setField "automatic-styles" (render' automaticStyles)
+ $ foldl (\acc (x,y) -> setField x y acc)
+ metadata (writerVariables opts)
in if writerStandalone opts
- then renderTemplate context $ writerTemplate opts
- else body'
+ then renderTemplate' (writerTemplate opts) context
+ else body
withParagraphStyle :: WriterOptions -> String -> [Block] -> State WriterState Doc
withParagraphStyle o s (b:bs)