aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers/Docx.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Writers/Docx.hs')
-rw-r--r--src/Text/Pandoc/Writers/Docx.hs37
1 files changed, 27 insertions, 10 deletions
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index 77ee51519..38031b7dc 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -58,7 +58,7 @@ import System.Random (randomRIO)
import Text.Printf (printf)
import qualified Control.Exception as E
import Text.Pandoc.MIME (getMimeType, extensionFromMimeType)
-import Control.Applicative ((<|>))
+import Control.Applicative ((<|>), (<$>))
import Data.Maybe (mapMaybe)
data ListMarker = NoMarker
@@ -481,17 +481,30 @@ writeOpenXML opts (Pandoc meta blocks) = do
_ -> []
let auths = docAuthors meta
let dat = docDate meta
+ let abstract' = case lookupMeta "abstract" meta of
+ Just (MetaBlocks bs) -> bs
+ Just (MetaInlines ils) -> [Plain ils]
+ _ -> []
+ let subtitle' = case lookupMeta "subtitle" meta of
+ Just (MetaBlocks [Plain xs]) -> xs
+ Just (MetaBlocks [Para xs]) -> xs
+ Just (MetaInlines xs) -> xs
+ _ -> []
title <- withParaProp (pStyle "Title") $ blocksToOpenXML opts [Para tit | not (null tit)]
- authors <- withParaProp (pStyle "Authors") $ blocksToOpenXML opts
- [Para (intercalate [LineBreak] auths) | not (null auths)]
+ subtitle <- withParaProp (pStyle "Subtitle") $ blocksToOpenXML opts [Para subtitle' | not (null subtitle')]
+ authors <- withParaProp (pStyle "Author") $ blocksToOpenXML opts $
+ map Para auths
date <- withParaProp (pStyle "Date") $ blocksToOpenXML opts [Para dat | not (null dat)]
+ abstract <- if null abstract'
+ then return []
+ else withParaProp (pStyle "Abstract") $ blocksToOpenXML opts abstract'
let convertSpace (Str x : Space : Str y : xs) = Str (x ++ " " ++ y) : xs
convertSpace (Str x : Str y : xs) = Str (x ++ y) : xs
convertSpace xs = xs
let blocks' = bottomUp convertSpace $ blocks
doc' <- blocksToOpenXML opts blocks'
notes' <- reverse `fmap` gets stFootnotes
- let meta' = title ++ authors ++ date
+ let meta' = title ++ subtitle ++ authors ++ date ++ abstract
return (meta' ++ doc', notes')
-- | Convert a list of Pandoc blocks to OpenXML.
@@ -514,8 +527,11 @@ blockToOpenXML :: WriterOptions -> Block -> WS [Element]
blockToOpenXML _ Null = return []
blockToOpenXML opts (Div _ bs) = blocksToOpenXML opts bs
blockToOpenXML opts (Header lev (ident,_,_) lst) = do
- contents <- withParaProp (pStyle $ "Heading" ++ show lev) $
- blockToOpenXML opts (Para lst)
+
+ paraProps <- withParaProp (pStyle $ "Heading" ++ show lev) $
+ getParaProps False
+ contents <- inlinesToOpenXML opts lst
+
usedIdents <- gets stSectionIds
let bookmarkName = if null ident
then uniqueIdent lst usedIdents
@@ -525,7 +541,7 @@ blockToOpenXML opts (Header lev (ident,_,_) lst) = do
let bookmarkStart = mknode "w:bookmarkStart" [("w:id", id')
,("w:name",bookmarkName)] ()
let bookmarkEnd = mknode "w:bookmarkEnd" [("w:id", id')] ()
- return $ [bookmarkStart] ++ contents ++ [bookmarkEnd]
+ return [mknode "w:p" [] (paraProps ++ [bookmarkStart, bookmarkEnd] ++ contents)]
blockToOpenXML opts (Plain lst) = withParaProp (pStyle "Compact")
$ blockToOpenXML opts (Para lst)
-- title beginning with fig: indicates that the image is a figure
@@ -751,9 +767,9 @@ inlineToOpenXML opts (Math mathType str) = do
let displayType = if mathType == DisplayMath
then DisplayBlock
else DisplayInline
- case texMathToOMML displayType str of
+ case writeOMML displayType <$> readTeX str of
Right r -> return [r]
- Left _ -> inlinesToOpenXML opts (readTeXMath' mathType str)
+ Left _ -> inlinesToOpenXML opts (texMathToInlines mathType str)
inlineToOpenXML opts (Cite _ lst) = inlinesToOpenXML opts lst
inlineToOpenXML opts (Code attrs str) =
withTextProp (rStyle "VerbatimChar")
@@ -814,7 +830,8 @@ inlineToOpenXML opts (Image alt (src, tit)) = do
case M.lookup src imgs of
Just (_,_,_,elt,_) -> return [elt]
Nothing -> do
- res <- liftIO $ fetchItem (writerSourceURL opts) src
+ res <- liftIO $
+ fetchItem' (writerMediaBag opts) (writerSourceURL opts) src
case res of
Left (_ :: E.SomeException) -> do
liftIO $ warn $ "Could not find image `" ++ src ++ "', skipping..."