aboutsummaryrefslogtreecommitdiff
path: root/test/Tests/Writers/OOXML.hs
diff options
context:
space:
mode:
Diffstat (limited to 'test/Tests/Writers/OOXML.hs')
-rw-r--r--test/Tests/Writers/OOXML.hs9
1 files changed, 5 insertions, 4 deletions
diff --git a/test/Tests/Writers/OOXML.hs b/test/Tests/Writers/OOXML.hs
index 628ea9409..83f05cfec 100644
--- a/test/Tests/Writers/OOXML.hs
+++ b/test/Tests/Writers/OOXML.hs
@@ -1,10 +1,8 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.OOXML (ooxmlTest) where
-import Prelude
import Text.Pandoc
import Test.Tasty
import Test.Tasty.Golden.Advanced
@@ -45,7 +43,8 @@ compareXMLBool _ _ = False
displayDiff :: Content -> Content -> String
displayDiff elemA elemB =
- showDiff (1,1) $ getDiff (lines $ ppContent elemA) (lines $ ppContent elemB)
+ showDiff (1,1)
+ (getDiff (lines $ showContent elemA) (lines $ showContent elemB))
goldenArchive :: FilePath -> IO Archive
goldenArchive fp = toArchive . BL.fromStrict <$> BS.readFile fp
@@ -56,7 +55,9 @@ testArchive :: (WriterOptions -> Pandoc -> PandocIO BL.ByteString)
-> IO Archive
testArchive writerFn opts fp = do
txt <- T.readFile fp
- bs <- runIOorExplode $ readNative def txt >>= writerFn opts
+ bs <- runIOorExplode $ do
+ setTranslations "en-US"
+ readNative def txt >>= writerFn opts
return $ toArchive bs
compareFileList :: FilePath -> Archive -> Archive -> Maybe String