Changed the test harness to get some tests inside the IO monad. This allows all the tests to be run, not just until the first failure

This commit is contained in:
Neil Brown 2008-01-16 11:15:05 +00:00
parent 90fb5e2182
commit a14a866502
3 changed files with 32 additions and 24 deletions

View File

@ -39,6 +39,7 @@ with this program. If not, see <http://www.gnu.org/licenses/>.
-- * "RainUsageCheckTest" -- * "RainUsageCheckTest"
module TestMain () where module TestMain () where
import Control.Monad
import System.Console.GetOpt import System.Console.GetOpt
import System.Environment import System.Environment
import Test.HUnit import Test.HUnit
@ -68,9 +69,10 @@ main = do opts <- getArgs >>* getOpt RequireOrder options
([Left unknownLevel], [], []) -> err ("Unknown level: " ++ unknownLevel) ([Left unknownLevel], [], []) -> err ("Unknown level: " ++ unknownLevel)
(_,_,errs) -> err (concat errs) (_,_,errs) -> err (concat errs)
runTestTT hunitTests hunitTests >>= runTestTT
case qcLevel of case qcLevel of
Just level -> sequence_ $ applyAll level qcTests -- Monadic mess!
Just level -> join $ liftM sequence_ $ (liftM $ applyAll level) qcTests
Nothing -> return () Nothing -> return ()
where where
err msg = ioError (userError (msg ++ usageInfo header options)) err msg = ioError (userError (msg ++ usageInfo header options))
@ -87,14 +89,16 @@ main = do opts <- getArgs >>* getOpt RequireOrder options
"extensive" -> Right $ Just QC_Extensive "extensive" -> Right $ Just QC_Extensive
unknown -> Left unknown unknown -> Left unknown
hunitTests = TestList $ map fst tests hunitTests :: IO Test
qcTests = concatMap snd tests hunitTests = sequence tests >>* (TestList . fst . unzip)
qcTests :: IO [QuickCheckTest]
qcTests = concatMapM (liftM snd) tests
tests = [ tests = [
ArrayUsageCheckTest.qcTests ArrayUsageCheckTest.qcTests
,noqc BackendPassesTest.tests ,noqc BackendPassesTest.tests
,noqc CommonTest.tests ,noqc CommonTest.tests
,FlowGraphTest.qcTests ,return FlowGraphTest.qcTests
,noqc GenerateCTest.tests ,noqc GenerateCTest.tests
,noqc ParseRainTest.tests ,noqc ParseRainTest.tests
,noqc PassTest.tests ,noqc PassTest.tests
@ -103,5 +107,6 @@ main = do opts <- getArgs >>* getOpt RequireOrder options
,noqc RainUsageCheckTest.tests ,noqc RainUsageCheckTest.tests
] ]
noqc :: Test -> (Test, [QuickCheckTest]) noqc :: Test -> IO (Test, [QuickCheckTest])
noqc t = (t,[]) noqc t = return (t,[])

View File

@ -46,8 +46,8 @@ import PassList
import PreprocessOccam import PreprocessOccam
import Utils import Utils
automaticTest :: FilePath -> Test automaticTest :: FilePath -> IO Test
automaticTest fileName = TestCase $ readFile fileName >>= performTest automaticTest fileName = readFile fileName >>* performTest
-- Bit of a hard-hack, until usage-checking is on by default: -- Bit of a hard-hack, until usage-checking is on by default:
defaultState :: CompState defaultState :: CompState
@ -63,20 +63,21 @@ testOccam source = do result <- evalStateT (runErrorT compilation) defaultState
where where
compilation = preprocessOccamSource source >>= parseOccamProgram >>= runPasses (getPassList defaultState) compilation = preprocessOccamSource source >>= parseOccamProgram >>= runPasses (getPassList defaultState)
-- | Given a file's contents, tests it -- | Given a file's contents, tests it
performTest :: String -> Assertion performTest :: String -> Test
performTest fileName performTest fileName
= case parseTestFile fileName of = case parseTestFile fileName of
Left err -> assertFailure $ "Error processing file \"" ++ fileName ++ "\": " ++ err Left err -> TestCase $ assertFailure $ "Error processing file \"" ++ fileName ++ "\": " ++ err
Right (prologue,tests) -> mapM_ performTest' (substitute prologue tests) Right (prologue,tests) -> TestList $ map performTest' (substitute prologue tests)
where where
-- Substitutes each substitution into the prologue -- Substitutes each substitution into the prologue
substitute :: String -> [(Bool, String, String)] -> [(Bool, String, String)] substitute :: String -> [(Bool, String, String)] -> [(Bool, String, String)]
substitute prologue = map (\(a,b,subst) -> (a,b,subRegex (mkRegex "%%") prologue subst)) substitute prologue = map (\(a,b,subst) -> (a,b,subRegex (mkRegex "%%") prologue subst))
performTest' :: (Bool, String, String) -> Assertion performTest' :: (Bool, String, String) -> Test
performTest' (expPass, testName, testText) performTest' (expPass, testName, testText)
= do result <- testOccam testText = TestCase $
do result <- testOccam testText
case result of case result of
Just err -> if expPass then assertFailure (testName ++ " failed with error: " ++ err) else return () Just err -> if expPass then assertFailure (testName ++ " failed with error: " ++ err) else return ()
Nothing -> if expPass then return () else assertFailure (testName ++ " expected to fail but passed") Nothing -> if expPass then return () else assertFailure (testName ++ " expected to fail but passed")

View File

@ -31,7 +31,6 @@ import Test.QuickCheck hiding (check)
import ArrayUsageCheck import ArrayUsageCheck
import qualified AST as A import qualified AST as A
import PrettyShow
import TestHarness import TestHarness
import TestUtils hiding (m) import TestUtils hiding (m)
import Utils import Utils
@ -713,15 +712,18 @@ qcOmegaPrune = [scaleQC (100,1000,10000,50000) prop]
result = undefined -- TODO replace solveAndPrune: solveProblem [] inp result = undefined -- TODO replace solveAndPrune: solveProblem [] inp
-} -}
qcTests :: (Test, [QuickCheckTest]) qcTests :: IO (Test, [QuickCheckTest])
qcTests = (TestList qcTests
[ = do usageCheckTest <- automaticTest "testcases/automatic/usage-check-1.occ.test"
testArrayCheck return
,testIndexes (TestList
,testMakeEquations [
,automaticTest "testcases/automatic/usage-check-1.occ.test" testArrayCheck
] ,testIndexes
,qcOmegaEquality ++ qcOmegaPrune) ,testMakeEquations
,usageCheckTest
]
,qcOmegaEquality ++ qcOmegaPrune)