testwrap.hs revision afc52bfaabee38c4d55cee9f35b1a0028ba3854a
306763c67bb99228487345b32ab8c5c6cd41f23cChristian Maeder{- |
306763c67bb99228487345b32ab8c5c6cd41f23cChristian MaederModule : $Header$
306763c67bb99228487345b32ab8c5c6cd41f23cChristian MaederCopyright : (c) Andy Gimblett and Markus Roggenbach and Uni Bremen 2004
306763c67bb99228487345b32ab8c5c6cd41f23cChristian MaederLicense : similar to LGPL, see HetCATS/LICENSE.txt or LIZENZ.txt
306763c67bb99228487345b32ab8c5c6cd41f23cChristian Maeder
e9249d3ecd51a2b6a966a58669953e58d703adc6Till MossakowskiMaintainer : a.m.gimblett@swan.ac.uk
306763c67bb99228487345b32ab8c5c6cd41f23cChristian MaederStability : provisional
306763c67bb99228487345b32ab8c5c6cd41f23cChristian MaederPortability : portable
306763c67bb99228487345b32ab8c5c6cd41f23cChristian Maeder
e9249d3ecd51a2b6a966a58669953e58d703adc6Till MossakowskiTest case wrapper for CspCASL specs and fragments.
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski
e9249d3ecd51a2b6a966a58669953e58d703adc6Till MossakowskiThis is a standalone `main' wrapper for CspCASL-related tests
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowskiperformed locally to the CspCASL codebase. It's probably only of
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowskiinterest to the CspCASL maintainers.
306763c67bb99228487345b32ab8c5c6cd41f23cChristian Maeder
306763c67bb99228487345b32ab8c5c6cd41f23cChristian MaederUsage:
306763c67bb99228487345b32ab8c5c6cd41f23cChristian Maeder
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski testwrap [options] targets
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski
e9249d3ecd51a2b6a966a58669953e58d703adc6Till MossakowskiOptions:
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski -t Don't parse any .cspcasl files; useful for just running tests.
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski -c Don't run any tests; useful for just parsing .cspcasl files.
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski Obviously, specifying both of these options stops this program from
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski doing anything useful.
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski
d85e3f253f6af237c4b70bbfacb1bfecb5cfa678Christian MaederParameters:
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski
38f350357e92da312d2c344352180b3dc5c1fc8aTill Mossakowski targets - a list of targets, where each target can be:
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski
425b287f28abf82702d46c176a38b668fb017ce4Felix Reckers - a .cspcasl file; parse the file as a Core-CspCASL specification,
425b287f28abf82702d46c176a38b668fb017ce4Felix Reckers unparse the parse tree, and print out the result of the unparse.
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski In case of parse error, report the error.
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski - a .testcase file; execute the test and report the outcome. A
59fa9b1349ae1e001d996da732c4ac805c2938e2Christian Maeder testcase file specifies one test case, whose source is contained
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski in another file, and whose output we will check against expected
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski contents. See below for the file format.
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski - a .testcases file; execute the tests and report their outcomes.
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski A testcases file specifies multiple test cases, with source
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski integrated with each test case, and outputs we will check
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski against expected contents. See below for the file format.
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski - a directory; find all .cspcasl, .testcase and .testcases files
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski in the directory (recursively) and operate on them as described
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski above.
d85e3f253f6af237c4b70bbfacb1bfecb5cfa678Christian Maeder
d85e3f253f6af237c4b70bbfacb1bfecb5cfa678Christian MaederPostive and negative tests:
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski
4184cb191a9081cb2a9cf3ef5f060f56f0ca5922Till Mossakowski A positive test is one where we expect the parse to succeed; here
8731f7b93b26083dc34a2c0937cd6493b42f2c2cTill Mossakowski the expected output is the result of unparsing the resultant parse
4184cb191a9081cb2a9cf3ef5f060f56f0ca5922Till Mossakowski tree. The test can fail with a parse error, or with unexpected
8731f7b93b26083dc34a2c0937cd6493b42f2c2cTill Mossakowski output.
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski A negative test is one where we expect the parse to fail; here the
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski expected output is the error message produced. The test can fail
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski with a successful parse, or with unexpected output.
38f350357e92da312d2c344352180b3dc5c1fc8aTill Mossakowski
5d6e7ea3bd14fc987436cff0f542393ea9ba34bbTill MossakowskiFormat of .testcase files:
5d6e7ea3bd14fc987436cff0f542393ea9ba34bbTill Mossakowski
9a36df4f63e0214bc0b4aef9b388c8d4e48632bbTill Mossakowski A .testcase file contains a single test case. The first line is the
9a36df4f63e0214bc0b4aef9b388c8d4e48632bbTill Mossakowski path to the file containing the source to be parsed/tested, relative
5d6e7ea3bd14fc987436cff0f542393ea9ba34bbTill Mossakowski to the .testcase file; it also acts as the name of the test case.
5d6e7ea3bd14fc987436cff0f542393ea9ba34bbTill Mossakowski The second line identifies the test sense ("++" is positive, "--" is
5d6e7ea3bd14fc987436cff0f542393ea9ba34bbTill Mossakowski negative). The third line is the name of the parser to be used. The
5d6e7ea3bd14fc987436cff0f542393ea9ba34bbTill Mossakowski remaining lines contain the expected output of the test.
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski
e9249d3ecd51a2b6a966a58669953e58d703adc6Till MossakowskiFormat of .testcases files:
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski A .testcases file contains multiple test cases including their
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski source. Individual test cases are separated by lines containing
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski twenty '-' characters and nothing else. The format of an individual
425b287f28abf82702d46c176a38b668fb017ce4Felix Reckers test case is similar but not identical to the format of a standalone
d85e3f253f6af237c4b70bbfacb1bfecb5cfa678Christian Maeder test case (above). The first line is the name of the test (used for
425b287f28abf82702d46c176a38b668fb017ce4Felix Reckers reporting). The second line identifies the test sense ("++" is
d85e3f253f6af237c4b70bbfacb1bfecb5cfa678Christian Maeder positive, "--" is negative). The third line is the name of the
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski parser to be used. This is followed by the expected outcome of the
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski test and the source (input) of the test, in that order, both of
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski which may span multiple lines; they are separated by a line
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski containing ten '-' characters and nothing else.
8db2d2c5a8df6dd6d7302bc59577150b87237940Till Mossakowski
8db2d2c5a8df6dd6d7302bc59577150b87237940Till Mossakowski-}
8db2d2c5a8df6dd6d7302bc59577150b87237940Till Mossakowski
59fa9b1349ae1e001d996da732c4ac805c2938e2Christian Maedermodule Main where
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowskiimport Data.List
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowskiimport Control.Monad
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowskiimport System.Directory
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowskiimport System.Environment (getArgs)
230a51f3c282a3222d1cf40c2040fee19259964eTill Mossakowskiimport System.FilePath (combine, dropFileName)
230a51f3c282a3222d1cf40c2040fee19259964eTill Mossakowskiimport System.IO
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowskiimport Text.ParserCombinators.Parsec
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowskiimport Common.AnnoState (emptyAnnos)
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowskiimport Common.DocUtils
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowskiimport CspCASL.Parse_CspCASL(basicCspCaslSpec)
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowskiimport CspCASL.Parse_CspCASL_Process(csp_casl_process)
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowskiimport CspCASL.Print_CspCASL()
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowskimain :: IO ()
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowskimain = do args <- getArgs
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski dirs <- filterM doesDirectoryExist args
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski dir_contents <- (liftM concat) (mapM listFilesR dirs)
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski files <- filterM doesFileExist (sort $ nub (args ++ dir_contents))
5e21bb46b24f477dafad6fdeff51aed7aaad0a47Till Mossakowski doIf ("-t" `notElem` args) (parseCspCASLs (filter isCspCASL files))
5e21bb46b24f477dafad6fdeff51aed7aaad0a47Till Mossakowski doIf ("-c" `notElem` args) (performTests (filter isTest files))
8731f7b93b26083dc34a2c0937cd6493b42f2c2cTill Mossakowski where isCspCASL = (".cspcasl" `isSuffixOf`)
8731f7b93b26083dc34a2c0937cd6493b42f2c2cTill Mossakowski isTest f = (isSuffixOf ".testcase" f) || (isSuffixOf ".testcases" f)
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski doIf c f = if c then f else putStr ""
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski-- | Given a list of paths to .cspcasl files, parse each in turn,
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski-- printing results as you go.
e9249d3ecd51a2b6a966a58669953e58d703adc6Till MossakowskiparseCspCASLs :: [FilePath] -> IO ()
e9249d3ecd51a2b6a966a58669953e58d703adc6Till MossakowskiparseCspCASLs [] = do putStr ""
d85e3f253f6af237c4b70bbfacb1bfecb5cfa678Christian MaederparseCspCASLs (f:fs) = do putStrLn dash20
d85e3f253f6af237c4b70bbfacb1bfecb5cfa678Christian Maeder prettyCspCASLFromFile f
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski parseCspCASLs fs
8db2d2c5a8df6dd6d7302bc59577150b87237940Till Mossakowski
d85e3f253f6af237c4b70bbfacb1bfecb5cfa678Christian Maeder-- | Parse one .cspcasl file; print error or pretty print parse tree.
59fa9b1349ae1e001d996da732c4ac805c2938e2Christian MaederprettyCspCASLFromFile :: FilePath -> IO ()
e9249d3ecd51a2b6a966a58669953e58d703adc6Till MossakowskiprettyCspCASLFromFile fname
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski = do putStrLn ("Parsing " ++ fname)
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski input <- readFile fname
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski case (runParser basicCspCaslSpec (emptyAnnos ()) fname input) of
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski Left err -> do putStr "parse error at "
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski print err
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski Right x -> do putStrLn $ showDoc x ""
d85e3f253f6af237c4b70bbfacb1bfecb5cfa678Christian Maeder putStrLn $ (show x)
d85e3f253f6af237c4b70bbfacb1bfecb5cfa678Christian Maeder
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski-- | Test sense: do we expect parse success or failure? What is the
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski-- nature of the expected output?
d85e3f253f6af237c4b70bbfacb1bfecb5cfa678Christian Maederdata TestSense = Positive | Negative
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski deriving (Eq, Ord)
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowskiinstance Show TestSense where
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski show Positive = "++"
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski show Negative = "--"
d85e3f253f6af237c4b70bbfacb1bfecb5cfa678Christian Maeder
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski-- | Test case details: where is source, what is it, which parser, etc.
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowskidata TestCase = TestCase {
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski -- | @name@ - test name
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski name :: String,
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski -- | @parser@ - name of parser to apply
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski parser :: String,
d85e3f253f6af237c4b70bbfacb1bfecb5cfa678Christian Maeder -- | @sense@ - sense of test (positive or negative)
d85e3f253f6af237c4b70bbfacb1bfecb5cfa678Christian Maeder sense :: TestSense,
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski -- | @src@ - source to be parsed
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski src :: String,
d85e3f253f6af237c4b70bbfacb1bfecb5cfa678Christian Maeder -- | @expected@ - expected output of test
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski expected :: String
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski} deriving (Eq, Ord)
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowskiinstance Show TestCase where
d85e3f253f6af237c4b70bbfacb1bfecb5cfa678Christian Maeder show a = (name a) ++ " (" ++ (show (sense a)) ++ (parser a) ++ ")"
f7819aa9d183836144a98c70d4fa7d65e31cb513Till Mossakowski
f7819aa9d183836144a98c70d4fa7d65e31cb513Till Mossakowski-- | Given a list of paths of test case files, read & perform them.
f7819aa9d183836144a98c70d4fa7d65e31cb513Till MossakowskiperformTests :: [FilePath] -> IO ()
f7819aa9d183836144a98c70d4fa7d65e31cb513Till MossakowskiperformTests tcs = do putStrLn "Performing tests"
8731f7b93b26083dc34a2c0937cd6493b42f2c2cTill Mossakowski tests <- (liftM concat) (mapM readTestFile tcs)
8731f7b93b26083dc34a2c0937cd6493b42f2c2cTill Mossakowski doTests tests
8731f7b93b26083dc34a2c0937cd6493b42f2c2cTill Mossakowski
8731f7b93b26083dc34a2c0937cd6493b42f2c2cTill Mossakowski-- | Turn a .testcase or .testcases file into list of test cases therein.
e9249d3ecd51a2b6a966a58669953e58d703adc6Till MossakowskireadTestFile :: FilePath -> IO [TestCase]
e9249d3ecd51a2b6a966a58669953e58d703adc6Till MossakowskireadTestFile f
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski | ".testcase" `isSuffixOf` f = readTestCaseFile f
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski | ".testcases" `isSuffixOf` f = readTestCasesFile f
d85e3f253f6af237c4b70bbfacb1bfecb5cfa678Christian Maeder | otherwise = do return []
d85e3f253f6af237c4b70bbfacb1bfecb5cfa678Christian Maeder
d85e3f253f6af237c4b70bbfacb1bfecb5cfa678Christian Maeder-- | Turn a .testcase file into the test case therein.
e9249d3ecd51a2b6a966a58669953e58d703adc6Till MossakowskireadTestCaseFile :: FilePath -> IO [TestCase]
e9249d3ecd51a2b6a966a58669953e58d703adc6Till MossakowskireadTestCaseFile f =
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski do hdl <- openFile f ReadMode
d85e3f253f6af237c4b70bbfacb1bfecb5cfa678Christian Maeder contents <- hGetContents hdl
d85e3f253f6af237c4b70bbfacb1bfecb5cfa678Christian Maeder let (a, b, c, d) = (testCaseParts contents)
d85e3f253f6af237c4b70bbfacb1bfecb5cfa678Christian Maeder hdl_s <- openFile (combine (dropFileName f) a) ReadMode
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski e <- hGetContents hdl_s
38f350357e92da312d2c344352180b3dc5c1fc8aTill Mossakowski return [TestCase { name=a, parser=b, sense=c, expected=d, src=e }]
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski
5bb3727ef464d9f08ab0decb2d4a59c1352a389eChristian Maeder-- | Turn a .testcases file into the test cases therein.
5bb3727ef464d9f08ab0decb2d4a59c1352a389eChristian MaederreadTestCasesFile :: FilePath -> IO [TestCase]
5bb3727ef464d9f08ab0decb2d4a59c1352a389eChristian MaederreadTestCasesFile f =
5bb3727ef464d9f08ab0decb2d4a59c1352a389eChristian Maeder do hdl <- openFile f ReadMode
5bb3727ef464d9f08ab0decb2d4a59c1352a389eChristian Maeder s <- hGetContents hdl
5bb3727ef464d9f08ab0decb2d4a59c1352a389eChristian Maeder let tests = map interpretTestCasesOne (map strip (split dash20 s))
d85e3f253f6af237c4b70bbfacb1bfecb5cfa678Christian Maeder return tests
d85e3f253f6af237c4b70bbfacb1bfecb5cfa678Christian Maeder
d85e3f253f6af237c4b70bbfacb1bfecb5cfa678Christian Maeder-- | Turn test case string from a .testcases file into its test case.
d85e3f253f6af237c4b70bbfacb1bfecb5cfa678Christian MaederinterpretTestCasesOne :: String -> TestCase
e9249d3ecd51a2b6a966a58669953e58d703adc6Till MossakowskiinterpretTestCasesOne s
d85e3f253f6af237c4b70bbfacb1bfecb5cfa678Christian Maeder | (length parts) == 2 = TestCase { name=a, parser=b, sense=c,
d85e3f253f6af237c4b70bbfacb1bfecb5cfa678Christian Maeder expected=d, src=e }
d85e3f253f6af237c4b70bbfacb1bfecb5cfa678Christian Maeder | otherwise = error s
d85e3f253f6af237c4b70bbfacb1bfecb5cfa678Christian Maeder where parts = map strip (split dash10 s)
e9249d3ecd51a2b6a966a58669953e58d703adc6Till Mossakowski (a, b, c, d) = testCaseParts (parts !! 0)
e = parts !! 1
-- | Turn test case string into its constituent parts (except source).
testCaseParts :: String -> (String, String, TestSense, String)
testCaseParts s = (head ls,
head (tail ls),
interpretSense (head (tail (tail ls))),
unlines (tail (tail (tail ls))))
where ls = lines s
-- | Interpret a test case sense (++ or --, positive or negative)
interpretSense :: String -> TestSense
interpretSense s = case s of
"++" -> Positive
"--" -> Negative
_ -> error ("Bad test sense " ++ s)
-- | Given a list of test cases, perform the tests in turn, printing
-- results as you go.
doTests :: [TestCase] -> IO ()
doTests [] = do putStr ""
doTests (tc:ts) = do --putStrLn dash20
let output = parseTestCase tc
putStr ((show tc) ++ " ")
printOutcome tc output
doTests ts
-- | Perform a test and report its outcome. There are six
-- possibilities: 1) positive test succeeds; 2) postive test
-- fail/non-parse (parse fails); 3) positive test error (unparse not
-- as expected); 4) negative test succeeds; 5) negative test
-- fail/parse (parse succeeds); 6) negative test error (error not as
-- expected).
printOutcome :: TestCase -> Either ParseError (String, String) -> IO ()
printOutcome tc out =
case (sense tc, out) of
(Positive, Right (o, tree)) ->
if (strip o) == (strip $ expected tc)
then testPass -- case 1
else do testFail "unparse" (expected tc) o -- case 3
putStrLn ("-> tree:\n" ++ tree)
(Positive, Left err) ->
testFail "parse failure" "" (show err) -- case 2
(Negative, Right (o, _)) ->
testFail "parse success" (expected tc) o -- case 5
(Negative, Left err) ->
if (strip $ show $ err) == (strip $ expected tc)
then testPass -- case 4
else testFail "error" (expected tc) (show err) -- case 6
-- Report on a test pass
testPass :: IO ()
testPass = do putStrLn "passed"
-- Report on a test failure
testFail :: String -> String -> String -> IO()
testFail nature expect got =
do putStrLn ("failed - unexpected " ++ nature)
if expect /= ""
then putStrLn ("-> expected:\n" ++ (strip expect))
else putStr ""
putStrLn "-> got:"
putStrLn $ strip got
runWithEof f fn s = runParser f' es fn s
where es = emptyAnnos ()
f' = do n <- f
eof
return n
-- | Run a test case through its parser.
parseTestCase :: TestCase -> Either ParseError (String, String)
parseTestCase t =
case (parser t) of
"CoreCspCASL" -> case (runWithEof basicCspCaslSpec fn s) of
Left err -> Left err
Right x -> Right ((showDoc x ""), (show x))
"Process" -> case (runWithEof csp_casl_process fn s) of
Left err -> Left err
Right x -> Right ((showDoc x ""), (show x))
_ -> error "Parser name"
where fn = name t
s = src t
-- The above implemenation is horrible. There must be a nice way to
-- abstract the parser out from the code to run it and collect/unparse
-- the result. Alas, I don't know it, or don't know that I know it.
dash20, dash10 :: String
dash10 = "----------"
dash20 = dash10 ++ dash10
-- Utility functions which really should be in the standard library!
-- | Recursive file lister adapted from
-- http://therning.org/magnus/archives/228
listFilesR :: FilePath -> IO [FilePath]
listFilesR path =
do allfiles <- getDirectoryContents path
nodots <- filterM (return . isDODD) (map (combine path) allfiles)
dirs <- filterM doesDirectoryExist nodots
subdirfiles <- (mapM listFilesR dirs >>= return . concat)
files <- filterM doesFileExist nodots
return $ files ++ subdirfiles
where
isDODD f = not $ ("/." `isSuffixOf` f) || ("/.." `isSuffixOf` f)
-- | A function inspired by python's string.split(). A list is split
-- on a separator which is itself a list (not a single element).
split :: Eq a => [a] -> [a] -> [[a]]
split tok splitme = unfoldr (sp1 tok) splitme
where sp1 _ [] = Nothing
sp1 t s = case find (t `isSuffixOf`) $ (inits s) of
Nothing -> Just (s, [])
Just p -> Just (take (length p - length t) p,
drop (length p) s)
-- | String strip in style of python string.strip()
strip :: String -> String
strip s = dropWhile ws $ reverse $ dropWhile ws $ reverse s
where ws = (`elem` [' ', '\n', '\t', '\r'])