2018-03-18 18:46:28 +01:00
|
|
|
{-# LANGUAGE NoImplicitPrelude #-}
|
2019-02-04 22:52:31 +01:00
|
|
|
{- |
|
|
|
|
Module : Tests.Command
|
2021-01-08 18:38:20 +01:00
|
|
|
Copyright : © 2006-2021 John MacFarlane
|
2019-02-04 22:52:31 +01:00
|
|
|
License : GNU GPL, version 2 or above
|
|
|
|
|
|
|
|
Maintainer : John MacFarlane <jgm@berkeley@edu>
|
|
|
|
Stability : alpha
|
|
|
|
Portability : portable
|
|
|
|
|
|
|
|
Run commands, and test results, defined in markdown files.
|
|
|
|
-}
|
2017-02-04 17:38:03 +01:00
|
|
|
module Tests.Command (findPandoc, runTest, tests)
|
|
|
|
where
|
|
|
|
|
2018-03-18 18:46:28 +01:00
|
|
|
import Prelude
|
2017-03-04 13:03:41 +01:00
|
|
|
import Data.Algorithm.Diff
|
2017-10-28 05:28:29 +02:00
|
|
|
import qualified Data.ByteString as BS
|
Switch to new pandoc-types and use Text instead of String [API change].
PR #5884.
+ Use pandoc-types 1.20 and texmath 0.12.
+ Text is now used instead of String, with a few exceptions.
+ In the MediaBag module, some of the types using Strings
were switched to use FilePath instead (not Text).
+ In the Parsing module, new parsers `manyChar`, `many1Char`,
`manyTillChar`, `many1TillChar`, `many1Till`, `manyUntil`,
`mantyUntilChar` have been added: these are like their
unsuffixed counterparts but pack some or all of their output.
+ `glob` in Text.Pandoc.Class still takes String since it seems
to be intended as an interface to Glob, which uses strings.
It seems to be used only once in the package, in the EPUB writer,
so that is not hard to change.
2019-11-04 22:12:37 +01:00
|
|
|
import qualified Data.Text as T
|
2020-05-19 07:46:14 +02:00
|
|
|
import Data.List (isSuffixOf, intercalate)
|
|
|
|
import Data.Maybe (catMaybes)
|
2017-02-04 17:38:03 +01:00
|
|
|
import System.Directory
|
2020-05-19 07:46:14 +02:00
|
|
|
import qualified System.Environment as Env
|
2017-02-04 17:38:03 +01:00
|
|
|
import System.Exit
|
2017-03-04 13:03:41 +01:00
|
|
|
import System.FilePath (joinPath, splitDirectories, takeDirectory, (</>))
|
2017-10-28 05:28:29 +02:00
|
|
|
import System.IO (hPutStr, stderr)
|
|
|
|
import System.IO.Unsafe (unsafePerformIO)
|
2017-03-04 13:03:41 +01:00
|
|
|
import System.Process
|
2017-03-14 17:05:36 +01:00
|
|
|
import Test.Tasty
|
|
|
|
import Test.Tasty.HUnit
|
2020-10-08 07:04:29 +02:00
|
|
|
import Test.Tasty.Golden.Advanced (goldenTest)
|
2017-03-04 13:03:41 +01:00
|
|
|
import Tests.Helpers
|
2017-02-04 21:07:03 +01:00
|
|
|
import Text.Pandoc
|
2017-03-04 13:03:41 +01:00
|
|
|
import qualified Text.Pandoc.UTF8 as UTF8
|
2017-02-04 17:38:03 +01:00
|
|
|
|
2020-10-08 07:04:29 +02:00
|
|
|
-- | Run a test with and return output.
|
|
|
|
execTest :: FilePath -- ^ Path to pandoc
|
|
|
|
-> String -- ^ Shell command
|
|
|
|
-> String -- ^ Input text
|
|
|
|
-> IO (ExitCode, String) -- ^ Exit code and actual output
|
|
|
|
execTest pandocpath cmd inp = do
|
2020-05-19 07:46:14 +02:00
|
|
|
mldpath <- Env.lookupEnv "LD_LIBRARY_PATH"
|
|
|
|
mdyldpath <- Env.lookupEnv "DYLD_LIBRARY_PATH"
|
2017-03-04 13:03:41 +01:00
|
|
|
let findDynlibDir [] = Nothing
|
2017-02-04 17:38:03 +01:00
|
|
|
findDynlibDir ("build":xs) = Just $ joinPath (reverse xs) </> "build"
|
2017-03-04 13:03:41 +01:00
|
|
|
findDynlibDir (_:xs) = findDynlibDir xs
|
2017-02-04 21:07:03 +01:00
|
|
|
let mbDynlibDir = findDynlibDir (reverse $ splitDirectories $
|
|
|
|
takeDirectory $ takeWhile (/=' ') cmd)
|
2020-10-08 07:04:29 +02:00
|
|
|
let dynlibEnv = [("DYLD_LIBRARY_PATH",
|
|
|
|
intercalate ":" $ catMaybes [mbDynlibDir, mdyldpath])
|
|
|
|
,("LD_LIBRARY_PATH",
|
|
|
|
intercalate ":" $ catMaybes [mbDynlibDir, mldpath])]
|
|
|
|
let env' = dynlibEnv ++ [("PATH",takeDirectory pandocpath),("TMP","."),
|
|
|
|
("LANG","en_US.UTF-8"),
|
|
|
|
("HOME", "./"),
|
|
|
|
("pandoc_datadir", "..")]
|
2017-08-14 22:02:34 +02:00
|
|
|
let pr = (shell cmd){ env = Just env' }
|
2017-05-25 11:51:50 +02:00
|
|
|
(ec, out', err') <- readCreateProcessWithExitCode pr inp
|
2017-02-04 17:38:03 +01:00
|
|
|
-- filter \r so the tests will work on Windows machines
|
2017-05-25 11:51:50 +02:00
|
|
|
let out = filter (/= '\r') $ err' ++ out'
|
2020-10-08 07:04:29 +02:00
|
|
|
case ec of
|
|
|
|
ExitFailure _ -> hPutStr stderr err'
|
|
|
|
ExitSuccess -> return ()
|
|
|
|
return (ec, out)
|
|
|
|
|
|
|
|
-- | Run a test, return True if test passed.
|
|
|
|
runTest :: String -- ^ Title of test
|
|
|
|
-> FilePath -- ^ Path to pandoc
|
|
|
|
-> String -- ^ Shell command
|
|
|
|
-> String -- ^ Input text
|
|
|
|
-> String -- ^ Expected output
|
|
|
|
-> TestTree
|
|
|
|
runTest testname pandocpath cmd inp norm = testCase testname $ do
|
|
|
|
(ec, out) <- execTest pandocpath cmd inp
|
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)
|
2020-10-08 07:04:29 +02:00
|
|
|
else return $ TestError ec
|
2017-02-04 17:38:03 +01:00
|
|
|
assertBool (show result) (result == TestPassed)
|
|
|
|
|
2019-02-01 05:56:20 +01:00
|
|
|
tests :: FilePath -> TestTree
|
2018-01-20 06:25:24 +01:00
|
|
|
{-# NOINLINE tests #-}
|
2019-02-01 05:56:20 +01:00
|
|
|
tests pandocPath = unsafePerformIO $ do
|
2017-02-04 21:07:03 +01:00
|
|
|
files <- filter (".md" `isSuffixOf`) <$>
|
|
|
|
getDirectoryContents "command"
|
2019-02-01 05:56:20 +01:00
|
|
|
let cmds = map (extractCommandTest pandocPath) files
|
2017-02-04 21:07:03 +01:00
|
|
|
return $ testGroup "Command:" cmds
|
|
|
|
|
|
|
|
isCodeBlock :: Block -> Bool
|
|
|
|
isCodeBlock (CodeBlock _ _) = True
|
2017-03-04 13:03:41 +01:00
|
|
|
isCodeBlock _ = False
|
2017-02-04 21:07:03 +01:00
|
|
|
|
|
|
|
extractCode :: Block -> String
|
Switch to new pandoc-types and use Text instead of String [API change].
PR #5884.
+ Use pandoc-types 1.20 and texmath 0.12.
+ Text is now used instead of String, with a few exceptions.
+ In the MediaBag module, some of the types using Strings
were switched to use FilePath instead (not Text).
+ In the Parsing module, new parsers `manyChar`, `many1Char`,
`manyTillChar`, `many1TillChar`, `many1Till`, `manyUntil`,
`mantyUntilChar` have been added: these are like their
unsuffixed counterparts but pack some or all of their output.
+ `glob` in Text.Pandoc.Class still takes String since it seems
to be intended as an interface to Glob, which uses strings.
It seems to be used only once in the package, in the EPUB writer,
so that is not hard to change.
2019-11-04 22:12:37 +01:00
|
|
|
extractCode (CodeBlock _ code) = T.unpack code
|
2017-03-04 13:03:41 +01:00
|
|
|
extractCode _ = ""
|
2017-02-04 21:07:03 +01:00
|
|
|
|
|
|
|
dropPercent :: String -> String
|
|
|
|
dropPercent ('%':xs) = dropWhile (== ' ') xs
|
2017-03-04 13:03:41 +01:00
|
|
|
dropPercent xs = xs
|
2017-02-04 21:07:03 +01:00
|
|
|
|
2020-10-08 07:04:29 +02:00
|
|
|
runCommandTest :: FilePath -> FilePath -> Int -> String -> TestTree
|
|
|
|
runCommandTest pandocpath fp num code =
|
|
|
|
goldenTest testname getExpected getActual compareValues updateGolden
|
|
|
|
where
|
|
|
|
testname = "#" <> show num
|
|
|
|
codelines = lines code
|
|
|
|
(continuations, r1) = span ("\\" `isSuffixOf`) codelines
|
|
|
|
cmd = dropPercent (unwords (map init continuations ++ take 1 r1))
|
|
|
|
r2 = drop 1 r1
|
|
|
|
(inplines, r3) = break (=="^D") r2
|
|
|
|
normlines = takeWhile (/=".") (drop 1 r3)
|
|
|
|
input = unlines inplines
|
|
|
|
norm = unlines normlines
|
|
|
|
getExpected = return norm
|
|
|
|
getActual = snd <$> execTest pandocpath cmd input
|
|
|
|
compareValues expected actual
|
|
|
|
| actual == expected = return Nothing
|
|
|
|
| otherwise = return $ Just $ "--- test/command/" ++ fp ++ "\n+++ " ++
|
|
|
|
cmd ++ "\n" ++ showDiff (1,1)
|
|
|
|
(getDiff (lines actual) (lines expected))
|
|
|
|
updateGolden newnorm = do
|
|
|
|
let fp' = "command" </> fp
|
|
|
|
raw <- UTF8.readFile fp'
|
|
|
|
let cmdline = "% " <> cmd
|
|
|
|
let x = cmdline <> "\n" <> input <> "^D\n" <> norm
|
|
|
|
let y = cmdline <> "\n" <> input <> "^D\n" <> newnorm
|
|
|
|
let updated = T.unpack $ T.replace (T.pack x) (T.pack y) (T.pack raw)
|
|
|
|
UTF8.writeFile fp' updated
|
2017-02-04 21:07:03 +01:00
|
|
|
|
2017-03-14 23:39:28 +01:00
|
|
|
extractCommandTest :: FilePath -> FilePath -> TestTree
|
|
|
|
extractCommandTest pandocpath fp = unsafePerformIO $ do
|
2017-06-11 21:18:42 +02:00
|
|
|
contents <- UTF8.toText <$> BS.readFile ("command" </> fp)
|
2017-02-04 21:07:03 +01:00
|
|
|
Pandoc _ blocks <- runIOorExplode (readMarkdown
|
2017-06-11 21:18:42 +02:00
|
|
|
def{ readerExtensions = pandocExtensions } contents)
|
2018-01-20 06:25:24 +01:00
|
|
|
let codeblocks = map extractCode $ filter isCodeBlock blocks
|
2020-10-08 07:04:29 +02:00
|
|
|
let cases = zipWith (runCommandTest pandocpath fp) [1..] codeblocks
|
2017-02-04 21:07:03 +01:00
|
|
|
return $ testGroup fp cases
|