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.hs51
1 files changed, 33 insertions, 18 deletions
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index fddec91cc..63bb8a5ae 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -4,7 +4,7 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE ViewPatterns #-}
{-
-Copyright (C) 2012-2015 John MacFarlane <jgm@berkeley.edu>
+Copyright (C) 2012-2017 John MacFarlane <jgm@berkeley.edu>
This program is free software; you can redistribute it and/or modify
it under the terms of the GNU General Public License as published by
@@ -23,7 +23,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
{- |
Module : Text.Pandoc.Writers.Docx
- Copyright : Copyright (C) 2012-2015 John MacFarlane
+ Copyright : Copyright (C) 2012-2017 John MacFarlane
License : GNU GPL, version 2 or above
Maintainer : John MacFarlane <jgm@berkeley.edu>
@@ -55,7 +55,6 @@ import Text.Pandoc.Class (PandocMonad, report)
import qualified Text.Pandoc.Class as P
import Text.Pandoc.Compat.Time
import Text.Pandoc.Definition
-import Text.Pandoc.Error
import Text.Pandoc.Generic
import Text.Pandoc.Highlighting (highlight)
import Text.Pandoc.ImageSize
@@ -497,6 +496,11 @@ writeDocx opts doc@(Pandoc meta _) = do
, qName (elName e) == "abstractNum" ] ++
[Elem e | e <- allElts
, qName (elName e) == "num" ] }
+
+ let keywords = case lookupMeta "keywords" meta of
+ Just (MetaList xs) -> map stringify xs
+ _ -> []
+
let docPropsPath = "docProps/core.xml"
let docProps = mknode "cp:coreProperties"
[("xmlns:cp","http://schemas.openxmlformats.org/package/2006/metadata/core-properties")
@@ -506,6 +510,7 @@ writeDocx opts doc@(Pandoc meta _) = do
,("xmlns:xsi","http://www.w3.org/2001/XMLSchema-instance")]
$ mknode "dc:title" [] (stringify $ docTitle meta)
: mknode "dc:creator" [] (intercalate "; " (map stringify $ docAuthors meta))
+ : mknode "cp:keywords" [] (intercalate ", " keywords)
: (\x -> [ mknode "dcterms:created" [("xsi:type","dcterms:W3CDTF")] x
, mknode "dcterms:modified" [("xsi:type","dcterms:W3CDTF")] x
]) (formatTime defaultTimeLocale "%FT%XZ" utctime)
@@ -876,7 +881,7 @@ blockToOpenXML' opts (Para [Image attr alt (src,'f':'i':'g':':':tit)]) = do
let prop = pCustomStyle $
if null alt
then "Figure"
- else "FigureWithCaption"
+ else "CaptionedFigure"
paraProps <- local (\env -> env { envParaProperties = prop : envParaProperties env }) (getParaProps False)
contents <- inlinesToOpenXML opts [Image attr alt (src,tit)]
captionNode <- withParaProp (pCustomStyle "ImageCaption")
@@ -954,7 +959,7 @@ blockToOpenXML' opts (Table caption aligns widths headers rows) = do
caption' ++
[mknode "w:tbl" []
( mknode "w:tblPr" []
- ( mknode "w:tblStyle" [("w:val","TableNormal")] () :
+ ( mknode "w:tblStyle" [("w:val","Table")] () :
mknode "w:tblW" [("w:type", "pct"), ("w:w", show rowwidth)] () :
mknode "w:tblLook" [("w:firstRow","1") | hasHeader ] () :
[ mknode "w:tblCaption" [("w:val", captionStr)] ()
@@ -1060,13 +1065,24 @@ withParaPropM :: PandocMonad m => WS m Element -> WS m a -> WS m a
withParaPropM = (. flip withParaProp) . (>>=)
formattedString :: PandocMonad m => String -> WS m [Element]
-formattedString str = do
- props <- getTextProps
+formattedString str =
+ -- properly handle soft hyphens
+ case splitBy (=='\173') str of
+ [w] -> formattedString' w
+ ws -> do
+ sh <- formattedRun [mknode "w:softHyphen" [] ()]
+ (intercalate sh) <$> mapM formattedString' ws
+
+formattedString' :: PandocMonad m => String -> WS m [Element]
+formattedString' str = do
inDel <- asks envInDel
- return [ mknode "w:r" [] $
- props ++
- [ mknode (if inDel then "w:delText" else "w:t")
- [("xml:space","preserve")] (stripInvalidChars str) ] ]
+ formattedRun [ mknode (if inDel then "w:delText" else "w:t")
+ [("xml:space","preserve")] (stripInvalidChars str) ]
+
+formattedRun :: PandocMonad m => [Element] -> WS m [Element]
+formattedRun els = do
+ props <- getTextProps
+ return [ mknode "w:r" [] $ props ++ els ]
setFirstPara :: PandocMonad m => WS m ()
setFirstPara = modify $ \s -> s { stFirstPara = True }
@@ -1076,7 +1092,8 @@ inlineToOpenXML :: PandocMonad m => WriterOptions -> Inline -> WS m [Element]
inlineToOpenXML opts il = withDirection $ inlineToOpenXML' opts il
inlineToOpenXML' :: PandocMonad m => WriterOptions -> Inline -> WS m [Element]
-inlineToOpenXML' _ (Str str) = formattedString str
+inlineToOpenXML' _ (Str str) =
+ formattedString str
inlineToOpenXML' opts Space = inlineToOpenXML opts (Str " ")
inlineToOpenXML' opts SoftBreak = inlineToOpenXML opts (Str " ")
inlineToOpenXML' opts (Span (ident,classes,kvs) ils) = do
@@ -1303,12 +1320,10 @@ inlineToOpenXML' opts (Image attr alt (src, title)) = do
M.insert src (ident, imgpath, mbMimeType, imgElt, img)
$ stImages st }
return [imgElt])
- (\e -> do case e of
- PandocIOError _ e' ->
- report $ CouldNotFetchResource src (show e')
- e' -> report $ CouldNotFetchResource src (show e')
- -- emit alt text
- inlinesToOpenXML opts alt)
+ (\e -> do
+ report $ CouldNotFetchResource src (show e)
+ -- emit alt text
+ inlinesToOpenXML opts alt)
br :: Element
br = breakElement "textWrapping"