aboutsummaryrefslogtreecommitdiff
path: root/tests/Tests/Readers/Docx.hs
diff options
context:
space:
mode:
Diffstat (limited to 'tests/Tests/Readers/Docx.hs')
-rw-r--r--tests/Tests/Readers/Docx.hs127
1 files changed, 125 insertions, 2 deletions
diff --git a/tests/Tests/Readers/Docx.hs b/tests/Tests/Readers/Docx.hs
index ffb079eee..c310cc8d7 100644
--- a/tests/Tests/Readers/Docx.hs
+++ b/tests/Tests/Readers/Docx.hs
@@ -5,10 +5,15 @@ import Text.Pandoc.Readers.Native
import Text.Pandoc.Definition
import Tests.Helpers
import Test.Framework
+import Test.HUnit (assertBool)
+import Test.Framework.Providers.HUnit
import qualified Data.ByteString.Lazy as B
import Text.Pandoc.Readers.Docx
import Text.Pandoc.Writers.Native (writeNative)
import qualified Data.Map as M
+import Text.Pandoc.MediaBag (MediaBag, lookupMedia, mediaDirectory)
+import Codec.Archive.Zip
+import System.FilePath (combine)
-- We define a wrapper around pandoc that doesn't normalize in the
-- tests. Since we do our own normalization, we want to make sure
@@ -37,7 +42,8 @@ compareOutput :: ReaderOptions
compareOutput opts docxFile nativeFile = do
df <- B.readFile docxFile
nf <- Prelude.readFile nativeFile
- return $ (noNorm (readDocx opts df), noNorm (readNative nf))
+ let (p, _) = readDocx opts df
+ return $ (noNorm p, noNorm (readNative nf))
testCompareWithOptsIO :: ReaderOptions -> String -> FilePath -> FilePath -> IO Test
testCompareWithOptsIO opts name docxFile nativeFile = do
@@ -51,6 +57,44 @@ testCompareWithOpts opts name docxFile nativeFile =
testCompare :: String -> FilePath -> FilePath -> Test
testCompare = testCompareWithOpts def
+getMedia :: FilePath -> FilePath -> IO (Maybe B.ByteString)
+getMedia archivePath mediaPath = do
+ zf <- B.readFile archivePath >>= return . toArchive
+ return $ findEntryByPath (combine "word" mediaPath) zf >>= (Just . fromEntry)
+
+compareMediaPathIO :: FilePath -> MediaBag -> FilePath -> IO Bool
+compareMediaPathIO mediaPath mediaBag docxPath = do
+ docxMedia <- getMedia docxPath mediaPath
+ let mbBS = case lookupMedia mediaPath mediaBag of
+ Just (_, bs) -> bs
+ Nothing -> error ("couldn't find " ++
+ mediaPath ++
+ " in media bag")
+ docxBS = case docxMedia of
+ Just bs -> bs
+ Nothing -> error ("couldn't find " ++
+ mediaPath ++
+ " in media bag")
+ return $ mbBS == docxBS
+
+compareMediaBagIO :: FilePath -> IO Bool
+compareMediaBagIO docxFile = do
+ df <- B.readFile docxFile
+ let (_, mb) = readDocx def df
+ bools <- mapM
+ (\(fp, _, _) -> compareMediaPathIO fp mb docxFile)
+ (mediaDirectory mb)
+ return $ and bools
+
+testMediaBagIO :: String -> FilePath -> IO Test
+testMediaBagIO name docxFile = do
+ outcome <- compareMediaBagIO docxFile
+ return $ testCase name (assertBool
+ ("Media didn't match media bag in file " ++ docxFile)
+ outcome)
+
+testMediaBag :: String -> FilePath -> Test
+testMediaBag name docxFile = buildTest $ testMediaBagIO name docxFile
tests :: [Test]
tests = [ testGroup "inlines"
@@ -63,10 +107,14 @@ tests = [ testGroup "inlines"
"docx.links.docx"
"docx.links.native"
, testCompare
- "inline image with reference output"
+ "inline image"
"docx.image.docx"
"docx.image_no_embed.native"
, testCompare
+ "inline image in links"
+ "docx.inline_images.docx"
+ "docx.inline_images.native"
+ , testCompare
"handling unicode input"
"docx.unicode.docx"
"docx.unicode.native"
@@ -82,6 +130,14 @@ tests = [ testGroup "inlines"
"normalizing inlines deep inside blocks"
"docx.deep_normalize.docx"
"docx.deep_normalize.native"
+ , testCompare
+ "move trailing spaces outside of formatting"
+ "docx.trailing_spaces_in_formatting.docx"
+ "docx.trailing_spaces_in_formatting.native"
+ , testCompare
+ "inline code (with VerbatimChar style)"
+ "docx.inline_code.docx"
+ "docx.inline_code.native"
]
, testGroup "blocks"
[ testCompare
@@ -89,10 +145,18 @@ tests = [ testGroup "inlines"
"docx.headers.docx"
"docx.headers.native"
, testCompare
+ "headers already having auto identifiers"
+ "docx.already_auto_ident.docx"
+ "docx.already_auto_ident.native"
+ , testCompare
"lists"
"docx.lists.docx"
"docx.lists.native"
, testCompare
+ "definition lists"
+ "docx.definition_list.docx"
+ "docx.definition_list.native"
+ , testCompare
"footnotes and endnotes"
"docx.notes.docx"
"docx.notes.native"
@@ -101,9 +165,68 @@ tests = [ testGroup "inlines"
"docx.block_quotes.docx"
"docx.block_quotes_parse_indent.native"
, testCompare
+ "hanging indents"
+ "docx.hanging_indent.docx"
+ "docx.hanging_indent.native"
+ , testCompare
"tables"
"docx.tables.docx"
"docx.tables.native"
+ , testCompare
+ "code block"
+ "docx.codeblock.docx"
+ "docx.codeblock.native"
+
+ ]
+ , testGroup "track changes"
+ [ testCompare
+ "insertion (default)"
+ "docx.track_changes_insertion.docx"
+ "docx.track_changes_insertion_accept.native"
+ , testCompareWithOpts def{readerTrackChanges=AcceptChanges}
+ "insert insertion (accept)"
+ "docx.track_changes_insertion.docx"
+ "docx.track_changes_insertion_accept.native"
+ , testCompareWithOpts def{readerTrackChanges=RejectChanges}
+ "remove insertion (reject)"
+ "docx.track_changes_insertion.docx"
+ "docx.track_changes_insertion_reject.native"
+ , testCompare
+ "deletion (default)"
+ "docx.track_changes_deletion.docx"
+ "docx.track_changes_deletion_accept.native"
+ , testCompareWithOpts def{readerTrackChanges=AcceptChanges}
+ "remove deletion (accept)"
+ "docx.track_changes_deletion.docx"
+ "docx.track_changes_deletion_accept.native"
+ , testCompareWithOpts def{readerTrackChanges=RejectChanges}
+ "insert deletion (reject)"
+ "docx.track_changes_deletion.docx"
+ "docx.track_changes_deletion_reject.native"
+ , testCompareWithOpts def{readerTrackChanges=AllChanges}
+ "keep insertion (all)"
+ "docx.track_changes_deletion.docx"
+ "docx.track_changes_deletion_all.native"
+ , testCompareWithOpts def{readerTrackChanges=AllChanges}
+ "keep deletion (all)"
+ "docx.track_changes_deletion.docx"
+ "docx.track_changes_deletion_all.native"
]
+ , testGroup "media"
+ [ testMediaBag
+ "image extraction"
+ "docx.image.docx"
+ ]
+ , testGroup "metadata"
+ [ testCompareWithOpts def{readerStandalone=True}
+ "metadata fields"
+ "docx.metadata.docx"
+ "docx.metadata.native"
+ , testCompareWithOpts def{readerStandalone=True}
+ "stop recording metadata with normal text"
+ "docx.metadata_after_normal.docx"
+ "docx.metadata_after_normal.native"
+ ]
+
]