aboutsummaryrefslogtreecommitdiff
path: root/tests/Tests/Writers/Docx.hs
diff options
context:
space:
mode:
Diffstat (limited to 'tests/Tests/Writers/Docx.hs')
-rw-r--r--tests/Tests/Writers/Docx.hs14
1 files changed, 8 insertions, 6 deletions
diff --git a/tests/Tests/Writers/Docx.hs b/tests/Tests/Writers/Docx.hs
index 31fc3a47b..fd320d224 100644
--- a/tests/Tests/Writers/Docx.hs
+++ b/tests/Tests/Writers/Docx.hs
@@ -7,8 +7,8 @@ import Tests.Helpers
import Test.Framework
import Text.Pandoc.Readers.Docx
import Text.Pandoc.Writers.Docx
-import Text.Pandoc.Error
import System.FilePath ((</>))
+import Text.Pandoc.Class (runIOorExplode)
type Options = (WriterOptions, ReaderOptions)
@@ -20,10 +20,12 @@ compareOutput opts nativeFileIn nativeFileOut = do
nf <- Prelude.readFile nativeFileIn
nf' <- Prelude.readFile nativeFileOut
let wopts = fst opts
- df <- writeDocx wopts{writerUserDataDir = Just (".." </> "data")}
- (handleError $ readNative nf)
- let (p, _) = handleError $ readDocx (snd opts) df
- return (p, handleError $ readNative nf')
+ df <- runIOorExplode $ do
+ d <- readNative def nf
+ writeDocx wopts{writerUserDataDir = Just (".." </> "data")} d
+ df' <- runIOorExplode (readNative def nf')
+ p <- runIOorExplode $ readDocx (snd opts) df
+ return (p, df')
testCompareWithOptsIO :: Options -> String -> FilePath -> FilePath -> IO Test
testCompareWithOptsIO opts name nativeFileIn nativeFileOut = do
@@ -139,7 +141,7 @@ tests = [ testGroup "inlines"
]
, testGroup "customized styles"
[ testCompareWithOpts
- ( def{writerReferenceDocx=Just "docx/custom-style-reference.docx"}
+ ( def{writerReferenceDoc=Just "docx/custom-style-reference.docx"}
, def)
"simple customized blocks and inlines"
"docx/custom-style-roundtrip-start.native"