aboutsummaryrefslogtreecommitdiff
path: root/test/Tests/Old.hs
diff options
context:
space:
mode:
Diffstat (limited to 'test/Tests/Old.hs')
-rw-r--r--test/Tests/Old.hs21
1 files changed, 12 insertions, 9 deletions
diff --git a/test/Tests/Old.hs b/test/Tests/Old.hs
index 638620a36..528388c51 100644
--- a/test/Tests/Old.hs
+++ b/test/Tests/Old.hs
@@ -1,4 +1,5 @@
{-# LANGUAGE NoImplicitPrelude #-}
+{-# LANGUAGE TupleSections #-}
{- |
Module : Tests.Old
Copyright : © 2006-2021 John MacFarlane
@@ -19,6 +20,7 @@ import Data.Maybe (catMaybes)
import System.Exit
import System.FilePath (joinPath, splitDirectories, (<.>), (</>))
import qualified System.Environment as Env
+import System.Environment.Executable (getExecutablePath)
import Text.Pandoc.Process (pipeProcess)
import Test.Tasty (TestTree, testGroup)
import Test.Tasty.Golden.Advanced (goldenTest)
@@ -322,13 +324,14 @@ testWithNormalize normalizer pandocPath testname opts inp norm =
getActual = do
mldpath <- Env.lookupEnv "LD_LIBRARY_PATH"
mdyldpath <- Env.lookupEnv "DYLD_LIBRARY_PATH"
- let mbDynlibDir = findDynlibDir (reverse $
- splitDirectories pandocPath)
- let dynlibEnv = [("DYLD_LIBRARY_PATH", intercalate ":" $ catMaybes [mbDynlibDir, mdyldpath])
- ,("LD_LIBRARY_PATH", intercalate ":" $ catMaybes [mbDynlibDir, mldpath])]
- let env = dynlibEnv ++
- [("TMP","."),("LANG","en_US.UTF-8"),("HOME", "./")]
- (ec, out) <- pipeProcess (Just env) pandocPath options mempty
+ let env = ("TMP",".") :
+ ("LANG","en_US.UTF-8") :
+ ("HOME", "./") :
+ maybe [] ((:[]) . ("LD_LIBRARY_PATH",)) mldpath ++
+ maybe [] ((:[]) . ("DYLD_LIBRARY_PATH",)) mdyldpath
+
+ (ec, out) <- pipeProcess (Just env) pandocPath
+ ("--emulate":options) mempty
if ec == ExitSuccess
then return $ filter (/='\r') . normalizer
$ UTF8.toStringLazy out
@@ -339,8 +342,8 @@ testWithNormalize normalizer pandocPath testname opts inp norm =
compareValues :: FilePath -> [String] -> String -> String -> IO (Maybe String)
compareValues norm options expected actual = do
- pandocPath <- findPandoc
- let cmd = pandocPath ++ " " ++ unwords options
+ testExePath <- getExecutablePath
+ let cmd = testExePath ++ " --emulate " ++ unwords options
let dash = replicate 72 '-'
let diff = getDiff (lines actual) (lines expected)
if expected == actual