aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/Docx.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Readers/Docx.hs')
-rw-r--r--src/Text/Pandoc/Readers/Docx.hs53
1 files changed, 47 insertions, 6 deletions
diff --git a/src/Text/Pandoc/Readers/Docx.hs b/src/Text/Pandoc/Readers/Docx.hs
index a2f22c1ea..f01a94550 100644
--- a/src/Text/Pandoc/Readers/Docx.hs
+++ b/src/Text/Pandoc/Readers/Docx.hs
@@ -1,7 +1,6 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternGuards #-}
-
{-
Copyright (C) 2014-2017 Jesse Rosenthal <jrosenthal@jhu.edu>
@@ -127,6 +126,7 @@ data DState = DState { docxAnchorMap :: M.Map String String
-- keep track of (numId, lvl) values for
-- restarting
, docxListState :: M.Map (String, String) Integer
+ , docxPrevPara :: Inlines
}
instance Default DState where
@@ -137,6 +137,7 @@ instance Default DState where
, docxDropCap = mempty
, docxWarnings = []
, docxListState = M.empty
+ , docxPrevPara = mempty
}
data DEnv = DEnv { docxOptions :: ReaderOptions
@@ -364,7 +365,7 @@ parPartToInlines parPart =
parPartToInlines' :: PandocMonad m => ParPart -> DocxContext m Inlines
parPartToInlines' (PlainRun r) = runToInlines r
-parPartToInlines' (Insertion _ author date runs) = do
+parPartToInlines' (ChangedRuns (TrackedChange Insertion (ChangeInfo _ author date)) runs) = do
opts <- asks docxOptions
case readerTrackChanges opts of
AcceptChanges -> smushInlines <$> mapM runToInlines runs
@@ -373,7 +374,7 @@ parPartToInlines' (Insertion _ author date runs) = do
ils <- smushInlines <$> mapM runToInlines runs
let attr = ("", ["insertion"], [("author", author), ("date", date)])
return $ spanWith attr ils
-parPartToInlines' (Deletion _ author date runs) = do
+parPartToInlines' (ChangedRuns (TrackedChange Deletion (ChangeInfo _ author date)) runs) = do
opts <- asks docxOptions
case readerTrackChanges opts of
AcceptChanges -> return mempty
@@ -562,16 +563,56 @@ bodyPartToBlocks (Paragraph pPr parparts)
headerWith ("", delete style (pStyle pPr), []) n ils
| otherwise = do
ils <- (trimSps . smushInlines) <$> mapM parPartToInlines parparts
+ prevParaIls <- gets docxPrevPara
dropIls <- gets docxDropCap
let ils' = dropIls <> ils
if dropCap pPr
then do modify $ \s -> s { docxDropCap = ils' }
return mempty
else do modify $ \s -> s { docxDropCap = mempty }
+ let ils'' = prevParaIls <>
+ (if isNull prevParaIls then mempty else space) <>
+ ils'
opts <- asks docxOptions
- if isNull ils' && not (isEnabled Ext_empty_paragraphs opts)
- then return mempty
- else return $ parStyleToTransform pPr $ para ils'
+ case () of
+
+ _ | isNull ils'' && not (isEnabled Ext_empty_paragraphs opts) ->
+ return mempty
+ _ | Just (TrackedChange Insertion _) <- pChange pPr
+ , AcceptChanges <- readerTrackChanges opts -> do
+ modify $ \s -> s {docxPrevPara = mempty}
+ return $ parStyleToTransform pPr $ para ils''
+ _ | Just (TrackedChange Insertion _) <- pChange pPr
+ , RejectChanges <- readerTrackChanges opts -> do
+ modify $ \s -> s {docxPrevPara = ils''}
+ return mempty
+ _ | Just (TrackedChange Insertion cInfo) <- pChange pPr
+ , AllChanges <- readerTrackChanges opts
+ , ChangeInfo _ cAuthor cDate <- cInfo -> do
+ let attr = ("", ["paragraph-insertion"], [("author", cAuthor), ("date", cDate)])
+ insertMark = spanWith attr mempty
+ return $
+ parStyleToTransform pPr $
+ para $ ils'' <> insertMark
+ _ | Just (TrackedChange Deletion _) <- pChange pPr
+ , AcceptChanges <- readerTrackChanges opts -> do
+ modify $ \s -> s {docxPrevPara = ils''}
+ return mempty
+ _ | Just (TrackedChange Deletion _) <- pChange pPr
+ , RejectChanges <- readerTrackChanges opts -> do
+ modify $ \s -> s {docxPrevPara = mempty}
+ return $ parStyleToTransform pPr $ para ils''
+ _ | Just (TrackedChange Deletion cInfo) <- pChange pPr
+ , AllChanges <- readerTrackChanges opts
+ , ChangeInfo _ cAuthor cDate <- cInfo -> do
+ let attr = ("", ["paragraph-deletion"], [("author", cAuthor), ("date", cDate)])
+ insertMark = spanWith attr mempty
+ return $
+ parStyleToTransform pPr $
+ para $ ils'' <> insertMark
+ _ | otherwise -> do
+ modify $ \s -> s {docxPrevPara = mempty}
+ return $ parStyleToTransform pPr $ para ils''
bodyPartToBlocks (ListItem pPr numId lvl (Just levelInfo) parparts) = do
-- We check whether this current numId has previously been used,
-- since Docx expects us to pick up where we left off.