aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers/Org.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Writers/Org.hs')
-rw-r--r--src/Text/Pandoc/Writers/Org.hs35
1 files changed, 14 insertions, 21 deletions
diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs
index 4e7b21e35..49af8124a 100644
--- a/src/Text/Pandoc/Writers/Org.hs
+++ b/src/Text/Pandoc/Writers/Org.hs
@@ -35,7 +35,7 @@ import Text.Pandoc.Definition
import Text.Pandoc.Options
import Text.Pandoc.Shared
import Text.Pandoc.Pretty
-import Text.Pandoc.Templates (renderTemplate)
+import Text.Pandoc.Templates (renderTemplate')
import Data.List ( intersect, intersperse, transpose )
import Control.Monad.State
import Control.Applicative ( (<$>) )
@@ -58,27 +58,26 @@ writeOrg opts document =
-- | Return Org representation of document.
pandocToOrg :: Pandoc -> State WriterState String
-pandocToOrg (Pandoc (Meta tit auth dat) blocks) = do
+pandocToOrg (Pandoc meta blocks) = do
opts <- liftM stOptions get
- title <- titleToOrg tit
- authors <- mapM inlineListToOrg auth
- date <- inlineListToOrg dat
+ let colwidth = if writerWrapText opts
+ then Just $ writerColumns opts
+ else Nothing
+ metadata <- metaToJSON
+ (fmap (render colwidth) . blockListToOrg)
+ (fmap (render colwidth) . inlineListToOrg)
+ meta
body <- blockListToOrg blocks
notes <- liftM (reverse . stNotes) get >>= notesToOrg
-- note that the notes may contain refs, so we do them first
hasMath <- liftM stHasMath get
- let colwidth = if writerWrapText opts
- then Just $ writerColumns opts
- else Nothing
let main = render colwidth $ foldl ($+$) empty $ [body, notes]
- let context = writerVariables opts ++
- [ ("body", main)
- , ("title", render Nothing title)
- , ("date", render Nothing date) ] ++
- [ ("math", "yes") | hasMath ] ++
- [ ("author", render Nothing a) | a <- authors ]
+ let context = setField "body" main
+ $ setField "math" hasMath
+ $ foldl (\acc (x,y) -> setField x y acc)
+ metadata (writerVariables opts)
if writerStandalone opts
- then return $ renderTemplate context $ writerTemplate opts
+ then return $ renderTemplate' (writerTemplate opts) context
else return main
-- | Return Org representation of notes.
@@ -103,12 +102,6 @@ escapeString = escapeStringUsing $
, ('\x2026',"...")
] ++ backslashEscapes "^_"
-titleToOrg :: [Inline] -> State WriterState Doc
-titleToOrg [] = return empty
-titleToOrg lst = do
- contents <- inlineListToOrg lst
- return $ "#+TITLE: " <> contents
-
-- | Convert Pandoc block element to Org.
blockToOrg :: Block -- ^ Block element
-> State WriterState Doc