aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Text/Pandoc/Readers/Docx.hs3
-rw-r--r--src/Text/Pandoc/Readers/Docx/Parse.hs33
-rw-r--r--tests/Tests/Readers/Docx.hs10
-rw-r--r--tests/docx.track_changes_deletion.docxbin0 -> 13350 bytes
-rw-r--r--tests/docx.track_changes_deletion_only_ins.native1
-rw-r--r--tests/docx.track_changes_insertion.docxbin0 -> 12956 bytes
-rw-r--r--tests/docx.track_changes_insertion_only_ins.native1
7 files changed, 39 insertions, 9 deletions
diff --git a/src/Text/Pandoc/Readers/Docx.hs b/src/Text/Pandoc/Readers/Docx.hs
index b787ca9fb..130e2a1e2 100644
--- a/src/Text/Pandoc/Readers/Docx.hs
+++ b/src/Text/Pandoc/Readers/Docx.hs
@@ -234,6 +234,9 @@ runToInlines opts docx@(Docx _ notes _ _ _) (Endnote fnId) =
parPartToInlines :: ReaderOptions -> Docx -> ParPart -> [Inline]
parPartToInlines opts docx (PlainRun r) = runToInlines opts docx r
+parPartToInlines opts docx (Insertion _ _ _ runs) =
+ concatMap (runToInlines opts docx) runs
+parPartToInlines _ _ (Deletion _ _ _ _) = []
parPartToInlines _ _ (BookMark _ anchor) | anchor `elem` dummyAnchors = []
parPartToInlines _ _ (BookMark _ anchor) = [Span (anchor, ["anchor"], []) []]
parPartToInlines _ (Docx _ _ _ rels _) (Drawing relid) =
diff --git a/src/Text/Pandoc/Readers/Docx/Parse.hs b/src/Text/Pandoc/Readers/Docx/Parse.hs
index 18200bcf9..dbbd65681 100644
--- a/src/Text/Pandoc/Readers/Docx/Parse.hs
+++ b/src/Text/Pandoc/Readers/Docx/Parse.hs
@@ -281,10 +281,6 @@ elemToBody ns element | qName (elName element) == "body" && qURI (elName element
$ map (elemToBodyPart ns) $ filterChildrenName (isParOrTbl ns) element
elemToBody _ _ = Nothing
-isRunOrLinkOrBookmark :: NameSpaces -> QName -> Bool
-isRunOrLinkOrBookmark ns q = qName q `elem` ["r", "hyperlink", "bookmarkStart"] &&
- qURI q == (lookup "w" ns)
-
elemToNumInfo :: NameSpaces -> Element -> Maybe (String, String)
elemToNumInfo ns element
| qName (elName element) == "p" &&
@@ -319,9 +315,8 @@ elemToBodyPart ns element
| qName (elName element) == "p" &&
qURI (elName element) == (lookup "w" ns) =
let parstyle = elemToParagraphStyle ns element
- parparts = mapMaybe id
- $ map (elemToParPart ns)
- $ filterChildrenName (isRunOrLinkOrBookmark ns) element
+ parparts = mapMaybe (elemToParPart ns)
+ $ elChildren element
in
case elemToNumInfo ns element of
Just (numId, lvl) -> Just $ ListItem parstyle numId lvl parparts
@@ -455,6 +450,8 @@ elemToCell ns element
elemToCell _ _ = Nothing
data ParPart = PlainRun Run
+ | Insertion ChangeId Author ChangeDate [Run]
+ | Deletion ChangeId Author ChangeDate [Run]
| BookMark BookMarkId Anchor
| InternalHyperLink Anchor [Run]
| ExternalHyperLink RelId [Run]
@@ -539,7 +536,7 @@ elemToRun _ _ = Nothing
elemToRunElem :: NameSpaces -> Element -> Maybe RunElem
elemToRunElem ns element
- | qName (elName element) == "t" &&
+ | (qName (elName element) == "t" || qName (elName element) == "delText") &&
qURI (elName element) == (lookup "w" ns) =
Just $ TextRun (strContent element)
| qName (elName element) == "br" &&
@@ -580,6 +577,22 @@ elemToParPart ns element
r <- elemToRun ns element
return $ PlainRun r
elemToParPart ns element
+ | qName (elName element) == "ins" &&
+ qURI (elName element) == (lookup "w" ns) = do
+ cId <- findAttr (QName "id" (lookup "w" ns) (Just "w")) element
+ cAuthor <- findAttr (QName "author" (lookup "w" ns) (Just "w")) element
+ cDate <- findAttr (QName "date" (lookup "w" ns) (Just "w")) element
+ let runs = mapMaybe (elemToRun ns) (elChildren element)
+ return $ Insertion cId cAuthor cDate runs
+elemToParPart ns element
+ | qName (elName element) == "del" &&
+ qURI (elName element) == (lookup "w" ns) = do
+ cId <- findAttr (QName "id" (lookup "w" ns) (Just "w")) element
+ cAuthor <- findAttr (QName "author" (lookup "w" ns) (Just "w")) element
+ cDate <- findAttr (QName "date" (lookup "w" ns) (Just "w")) element
+ let runs = mapMaybe (elemToRun ns) (elChildren element)
+ return $ Deletion cId cAuthor cDate runs
+elemToParPart ns element
| qName (elName element) == "bookmarkStart" &&
qURI (elName element) == (lookup "w" ns) = do
bmId <- findAttr (QName "id" (lookup "w" ns) (Just "w")) element
@@ -604,4 +617,6 @@ type Target = String
type Anchor = String
type BookMarkId = String
type RelId = String
-
+type ChangeId = String
+type Author = String
+type ChangeDate = String
diff --git a/tests/Tests/Readers/Docx.hs b/tests/Tests/Readers/Docx.hs
index 4d062bbc0..f34e123ed 100644
--- a/tests/Tests/Readers/Docx.hs
+++ b/tests/Tests/Readers/Docx.hs
@@ -122,5 +122,15 @@ tests = [ testGroup "inlines"
"docx.codeblock.native"
]
+ , testGroup "track changes"
+ [ testCompare
+ "insert insertion (insertions only)"
+ "docx.track_changes_insertion.docx"
+ "docx.track_changes_insertion_only_ins.native"
+ , testCompare
+ "skip deletion (insertions only)"
+ "docx.track_changes_deletion.docx"
+ "docx.track_changes_deletion_only_ins.native"
+ ]
]
diff --git a/tests/docx.track_changes_deletion.docx b/tests/docx.track_changes_deletion.docx
new file mode 100644
index 000000000..5cfdbeed8
--- /dev/null
+++ b/tests/docx.track_changes_deletion.docx
Binary files differ
diff --git a/tests/docx.track_changes_deletion_only_ins.native b/tests/docx.track_changes_deletion_only_ins.native
new file mode 100644
index 000000000..205c67810
--- /dev/null
+++ b/tests/docx.track_changes_deletion_only_ins.native
@@ -0,0 +1 @@
+[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "text",Space,Str "with",Space,Str "a",Space,Str "deletion."]]
diff --git a/tests/docx.track_changes_insertion.docx b/tests/docx.track_changes_insertion.docx
new file mode 100644
index 000000000..fbdc9003e
--- /dev/null
+++ b/tests/docx.track_changes_insertion.docx
Binary files differ
diff --git a/tests/docx.track_changes_insertion_only_ins.native b/tests/docx.track_changes_insertion_only_ins.native
new file mode 100644
index 000000000..ca2e46df0
--- /dev/null
+++ b/tests/docx.track_changes_insertion_only_ins.native
@@ -0,0 +1 @@
+[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "text",Space,Str "with",Space,Str "two",Space,Str "exciting",Space,Str "insertions."]]