pandoc/test/Tests/Command.hs

96 lines
3.7 KiB
Haskell
Raw Normal View History

2017-02-04 17:38:03 +01:00
module Tests.Command (findPandoc, runTest, tests)
where
import Data.Algorithm.Diff
import qualified Data.ByteString as BS
import Data.List (isSuffixOf)
import Prelude hiding (readFile)
2017-02-04 17:38:03 +01:00
import System.Directory
import System.Exit
import System.FilePath (joinPath, splitDirectories, takeDirectory, (</>))
import System.IO (hPutStr, stderr)
import System.IO.Unsafe (unsafePerformIO)
import System.Process
import Test.Tasty
import Test.Tasty.HUnit
import Tests.Helpers
import Text.Pandoc
import qualified Text.Pandoc.UTF8 as UTF8
2017-02-04 17:38:03 +01:00
-- | Run a test with normalize function, return True if test passed.
runTest :: String -- ^ Title of test
-> FilePath -- ^ Path to pandoc
-> String -- ^ Shell command
2017-02-04 17:38:03 +01:00
-> String -- ^ Input text
-> String -- ^ Expected output
-> TestTree
runTest testname pandocpath cmd inp norm = testCase testname $ do
let findDynlibDir [] = Nothing
2017-02-04 17:38:03 +01:00
findDynlibDir ("build":xs) = Just $ joinPath (reverse xs) </> "build"
findDynlibDir (_:xs) = findDynlibDir xs
let mbDynlibDir = findDynlibDir (reverse $ splitDirectories $
takeDirectory $ takeWhile (/=' ') cmd)
2017-02-04 17:38:03 +01:00
let dynlibEnv = case mbDynlibDir of
Nothing -> []
Just d -> [("DYLD_LIBRARY_PATH", d),
("LD_LIBRARY_PATH", d)]
let env' = dynlibEnv ++ [("PATH",takeDirectory pandocpath),("TMP","."),("LANG","en_US.UTF-8"),("HOME", "./"),("pandoc_datadir", "..")]
let pr = (shell cmd){ env = Just env' }
(ec, out', err') <- readCreateProcessWithExitCode pr inp
2017-02-04 17:38:03 +01:00
-- filter \r so the tests will work on Windows machines
let out = filter (/= '\r') $ err' ++ out'
2017-02-04 17:38:03 +01:00
result <- if ec == ExitSuccess
2018-01-20 06:25:24 +01:00
then
2017-02-04 17:38:03 +01:00
if out == norm
then return TestPassed
else return
$ TestFailed cmd "expected"
$ getDiff (lines out) (lines norm)
else do
hPutStr stderr err'
return $ TestError ec
2017-02-04 17:38:03 +01:00
assertBool (show result) (result == TestPassed)
tests :: TestTree
2018-01-20 06:25:24 +01:00
{-# NOINLINE tests #-}
tests = unsafePerformIO $ do
2017-03-14 23:39:28 +01:00
pandocpath <- findPandoc
files <- filter (".md" `isSuffixOf`) <$>
getDirectoryContents "command"
2017-03-14 23:39:28 +01:00
let cmds = map (extractCommandTest pandocpath) files
return $ testGroup "Command:" cmds
isCodeBlock :: Block -> Bool
isCodeBlock (CodeBlock _ _) = True
isCodeBlock _ = False
extractCode :: Block -> String
extractCode (CodeBlock _ code) = code
extractCode _ = ""
dropPercent :: String -> String
dropPercent ('%':xs) = dropWhile (== ' ') xs
dropPercent xs = xs
2017-03-14 17:27:30 +01:00
runCommandTest :: FilePath -> (Int, String) -> TestTree
runCommandTest pandocpath (num, code) =
let codelines = lines code
2017-03-14 17:27:30 +01:00
(continuations, r1) = span ("\\" `isSuffixOf`) codelines
(cmd, r2) = (dropPercent (unwords (map init continuations ++ take 1 r1)),
drop 1 r1)
2017-03-14 17:27:30 +01:00
(inplines, r3) = break (=="^D") r2
normlines = takeWhile (/=".") (drop 1 r3)
input = unlines inplines
norm = unlines normlines
shcmd = cmd -- trimr $ takeDirectory pandocpath </> cmd
in runTest ("#" ++ show num) pandocpath shcmd input norm
2017-03-14 23:39:28 +01:00
extractCommandTest :: FilePath -> FilePath -> TestTree
extractCommandTest pandocpath fp = unsafePerformIO $ do
contents <- UTF8.toText <$> BS.readFile ("command" </> fp)
Pandoc _ blocks <- runIOorExplode (readMarkdown
def{ readerExtensions = pandocExtensions } contents)
2018-01-20 06:25:24 +01:00
let codeblocks = map extractCode $ filter isCodeBlock blocks
2017-03-14 17:27:30 +01:00
let cases = map (runCommandTest pandocpath) $ zip [1..] codeblocks
return $ testGroup fp cases