diff options
Diffstat (limited to 'tests/RunTests.hs')
-rw-r--r-- | tests/RunTests.hs | 15 |
1 files changed, 9 insertions, 6 deletions
diff --git a/tests/RunTests.hs b/tests/RunTests.hs index 0b5555ed1..1715400fd 100644 --- a/tests/RunTests.hs +++ b/tests/RunTests.hs @@ -13,9 +13,7 @@ -- cabal install Diff module Main where -import System.IO.UTF8 import System.IO ( openTempFile, stderr, stdout, hFlush ) -import Prelude hiding ( putStrLn, putStr, readFile ) import System.Process ( runProcess, waitForProcess ) import System.FilePath ( (</>), (<.>) ) import System.Directory @@ -23,6 +21,12 @@ import System.Environment import System.Exit import Text.Printf import Data.Algorithm.Diff +import Prelude hiding ( readFile ) +import qualified Data.ByteString.Lazy as B +import Data.ByteString.Lazy.UTF8 (toString, fromString) + +readFileUTF8 :: FilePath -> IO String +readFileUTF8 f = B.readFile f >>= return . toString pandocPath :: FilePath pandocPath = ".." </> "dist" </> "build" </> "pandoc" </> "pandoc" @@ -127,7 +131,7 @@ main = do -- makes sure file is fully closed after reading readFile' :: FilePath -> IO String -readFile' f = do s <- readFile f +readFile' f = do s <- readFileUTF8 f return $! (length s `seq` s) runLhsWriterTest :: String -> IO Bool @@ -161,8 +165,7 @@ runTest testname opts inp norm = do let normPath = norm hFlush stdout -- Note: COLUMNS must be set for markdown table reader - -- and we need LANG set for ghc 6.12 - ph <- runProcess pandocPath (opts ++ [inpPath] ++ ["--data-dir", ".."]) Nothing (Just [("COLUMNS", "80"),("LANG","en_US.UTF-8")]) Nothing (Just hOut) (Just stderr) + ph <- runProcess pandocPath (opts ++ [inpPath] ++ ["--data-dir", ".."]) Nothing (Just [("COLUMNS", "80")]) Nothing (Just hOut) (Just stderr) ec <- waitForProcess ph result <- if ec == ExitSuccess then do @@ -174,5 +177,5 @@ runTest testname opts inp norm = do else return $ TestFailed $ getDiff (lines outputContents) (lines normContents) else return $ TestError ec removeFile outputPath - putStrLn (show result) + B.putStrLn (fromString $ show result) return (result == TestPassed) |