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.hs38
1 files changed, 16 insertions, 22 deletions
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index 639818f2e..827d32620 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -60,6 +60,7 @@ import Data.Unique (hashUnique, newUnique)
import System.Random (randomRIO)
import Text.Printf (printf)
import qualified Control.Exception as E
+import Text.Pandoc.Compat.Monoid ((<>))
import Text.Pandoc.MIME (MimeType, getMimeType, getMimeTypeDef,
extensionFromMimeType)
import Control.Applicative ((<|>))
@@ -244,7 +245,7 @@ writeDocx opts doc@(Pandoc meta _) = do
let tocTitle = fromMaybe (stTocTitle defaultWriterState) $
metaValueToInlines <$> lookupMeta "toc-title" meta
- ((contents, footnotes), st) <- runStateT (writeOpenXML opts{writerWrapText = False} doc')
+ ((contents, footnotes), st) <- runStateT (writeOpenXML opts{writerWrapText = WrapNone} doc')
defaultWriterState{ stChangesAuthor = fromMaybe "unknown" username
, stChangesDate = formatTime defaultTimeLocale "%FT%XZ" utctime
, stPrintWidth = (maybe 420 (\x -> quot x 20) pgContentWidth)
@@ -535,7 +536,6 @@ styleToOpenXml sm style =
, mknode "w:link" [("w:val","VerbatimChar")] ()
, mknode "w:pPr" []
$ mknode "w:wordWrap" [("w:val","off")] ()
- : mknode "w:noProof" [] ()
: ( maybe [] (\col -> [mknode "w:shd" [("w:val","clear"),("w:fill",drop 1 $ fromColor col)] ()])
$ backgroundColor style )
]
@@ -751,7 +751,7 @@ blockToOpenXML opts (Header lev (ident,_,_) lst) = do
blockToOpenXML opts (Plain lst) = withParaProp (pCustomStyle "Compact")
$ blockToOpenXML opts (Para lst)
-- title beginning with fig: indicates that the image is a figure
-blockToOpenXML opts (Para [Image alt (src,'f':'i':'g':':':tit)]) = do
+blockToOpenXML opts (Para [Image attr alt (src,'f':'i':'g':':':tit)]) = do
setFirstPara
pushParaProp $ pCustomStyle $
if null alt
@@ -759,7 +759,7 @@ blockToOpenXML opts (Para [Image alt (src,'f':'i':'g':':':tit)]) = do
else "FigureWithCaption"
paraProps <- getParaProps False
popParaProp
- contents <- inlinesToOpenXML opts [Image alt (src,tit)]
+ contents <- inlinesToOpenXML opts [Image attr alt (src,tit)]
captionNode <- withParaProp (pCustomStyle "ImageCaption")
$ blockToOpenXML opts (Para alt)
return $ mknode "w:p" [] (paraProps ++ contents) : captionNode
@@ -981,6 +981,7 @@ setFirstPara = modify $ \s -> s { stFirstPara = True }
inlineToOpenXML :: WriterOptions -> Inline -> WS [Element]
inlineToOpenXML _ (Str str) = formattedString str
inlineToOpenXML opts Space = inlineToOpenXML opts (Str " ")
+inlineToOpenXML opts SoftBreak = inlineToOpenXML opts (Str " ")
inlineToOpenXML opts (Span (_,classes,kvs) ils)
| "insertion" `elem` classes = do
defaultAuthor <- gets stChangesAuthor
@@ -1069,8 +1070,8 @@ inlineToOpenXML opts (Note bs) = do
[ mknode "w:rPr" [] footnoteStyle
, mknode "w:footnoteRef" [] () ]
let notemarkerXml = RawInline (Format "openxml") $ ppElement notemarker
- let insertNoteRef (Plain ils : xs) = Plain (notemarkerXml : ils) : xs
- insertNoteRef (Para ils : xs) = Para (notemarkerXml : ils) : xs
+ let insertNoteRef (Plain ils : xs) = Plain (notemarkerXml : Space : ils) : xs
+ insertNoteRef (Para ils : xs) = Para (notemarkerXml : Space : ils) : xs
insertNoteRef xs = Para [notemarkerXml] : xs
oldListLevel <- gets stListLevel
oldParaProperties <- gets stParaProperties
@@ -1086,11 +1087,11 @@ inlineToOpenXML opts (Note bs) = do
[ mknode "w:rPr" [] footnoteStyle
, mknode "w:footnoteReference" [("w:id", notenum)] () ] ]
-- internal link:
-inlineToOpenXML opts (Link txt ('#':xs,_)) = do
+inlineToOpenXML opts (Link _ txt ('#':xs,_)) = do
contents <- withTextPropM (rStyleM "Hyperlink") $ inlinesToOpenXML opts txt
return [ mknode "w:hyperlink" [("w:anchor",xs)] contents ]
-- external link:
-inlineToOpenXML opts (Link txt (src,_)) = do
+inlineToOpenXML opts (Link _ txt (src,_)) = do
contents <- withTextPropM (rStyleM "Hyperlink") $ inlinesToOpenXML opts txt
extlinks <- gets stExternalLinks
id' <- case M.lookup src extlinks of
@@ -1101,7 +1102,7 @@ inlineToOpenXML opts (Link txt (src,_)) = do
M.insert src i extlinks }
return i
return [ mknode "w:hyperlink" [("r:id",id')] contents ]
-inlineToOpenXML opts (Image alt (src, tit)) = do
+inlineToOpenXML opts (Image attr alt (src, tit)) = do
-- first, check to see if we've already done this image
pageWidth <- gets stPrintWidth
imgs <- gets stImages
@@ -1117,13 +1118,8 @@ inlineToOpenXML opts (Image alt (src, tit)) = do
inlinesToOpenXML opts alt
Right (img, mt) -> do
ident <- ("rId"++) `fmap` getUniqueId
- (xpt,ypt) <- case imageSize img of
- Right size -> return $ sizeInPoints size
- Left msg -> do
- liftIO $ warn $
- "Could not determine image size in `" ++
- src ++ "': " ++ msg
- return (120,120)
+ let (xpt,ypt) = desiredSizeInPoints opts attr
+ (either (const def) id (imageSize img))
-- 12700 emu = 1 pt
let (xemu,yemu) = fitToPage (xpt * 12700, ypt * 12700) (pageWidth * 12700)
let cNvPicPr = mknode "pic:cNvPicPr" [] $
@@ -1210,11 +1206,9 @@ parseXml refArchive distArchive relpath =
-- | Scales the image to fit the page
-- sizes are passed in emu
-fitToPage :: (Integer, Integer) -> Integer -> (Integer, Integer)
+fitToPage :: (Double, Double) -> Integer -> (Integer, Integer)
fitToPage (x, y) pageWidth
-- Fixes width to the page width and scales the height
- | x > pageWidth =
- (pageWidth, round $
- ((fromIntegral pageWidth) / ((fromIntegral :: Integer -> Double) x)) * (fromIntegral y))
- | otherwise = (x, y)
-
+ | x > fromIntegral pageWidth =
+ (pageWidth, floor $ ((fromIntegral pageWidth) / x) * y)
+ | otherwise = (floor x, floor y)