Separated the QuickCheck tests from the HUnit tests and made the number of test-cases configurable for the QuickCheck tests

This commit is contained in:
Neil Brown 2007-12-13 18:21:53 +00:00
parent 54721cd19b
commit 337f189b8a
3 changed files with 58 additions and 31 deletions

View File

@ -41,25 +41,40 @@ import Test.HUnit
import qualified BackendPassesTest (tests) import qualified BackendPassesTest (tests)
import qualified CommonTest (tests) import qualified CommonTest (tests)
import qualified FlowGraphTest (tests) import qualified FlowGraphTest (qcTests)
import qualified GenerateCTest (tests) import qualified GenerateCTest (tests)
import qualified ParseRainTest (tests) import qualified ParseRainTest (tests)
import qualified PassTest (tests) import qualified PassTest (tests)
import qualified RainPassesTest (tests) import qualified RainPassesTest (tests)
import qualified RainTypesTest (tests) import qualified RainTypesTest (tests)
import qualified RainUsageCheckTest (tests) import qualified RainUsageCheckTest (qcTests)
import TestUtil
import Utils
-- We run all the HUnit tests before all the QuickCheck tests.
-- We run them apart so that the output from QuickCheck doesn't get
-- confusing by being amongst the HUnit output,
-- and we run HUnit first because these are typically the more
-- interesting (and most worked on tests) so we see failures earlier.
main :: IO () main :: IO ()
main = do runTestTT $ TestList main = do runTestTT hunitTests
[ sequence $ applyAll QC_Medium qcTests
BackendPassesTest.tests
,CommonTest.tests
,FlowGraphTest.tests
,GenerateCTest.tests
,ParseRainTest.tests
,PassTest.tests
,RainPassesTest.tests
,RainTypesTest.tests
,RainUsageCheckTest.tests
]
return () return ()
where
hunitTests = TestList $ map fst tests
qcTests = concatMap snd tests
tests = [
noqc BackendPassesTest.tests
,noqc CommonTest.tests
,FlowGraphTest.qcTests
,noqc GenerateCTest.tests
,noqc ParseRainTest.tests
,noqc PassTest.tests
,noqc RainPassesTest.tests
,noqc RainTypesTest.tests
,RainUsageCheckTest.qcTests
]
noqc :: Test -> (Test, [QuickCheckTest])
noqc t = (t,[])

View File

@ -19,7 +19,7 @@ with this program. If not, see <http://www.gnu.org/licenses/>.
-- #ignore-exports -- #ignore-exports
-- | A module for testing building a control flow-graph from an AST. -- | A module for testing building a control flow-graph from an AST.
module FlowGraphTest (tests) where module FlowGraphTest (qcTests) where
import Control.Monad.Identity import Control.Monad.Identity
import Control.Monad.State import Control.Monad.State
@ -30,7 +30,7 @@ import Data.List
import qualified Data.Map as Map import qualified Data.Map as Map
import Data.Maybe import Data.Maybe
import System.Random import System.Random
import Test.HUnit hiding (Node, State) import Test.HUnit hiding (Node, State, Testable)
import Test.QuickCheck import Test.QuickCheck
import qualified AST as A import qualified AST as A
@ -554,14 +554,25 @@ pickFuncRep gr = Map.fromList $ map (helpApplyFunc . getMetaFunc) (labNodes gr)
-- | It is important to have these functions in the right ratio. The number of possible trees is -- | It is important to have these functions in the right ratio. The number of possible trees is
-- 2^N, where N is the test size. Therefore I suggest keeping N <= 10 as a sensible limit. -- 2^N, where N is the test size. Therefore I suggest keeping N <= 10 as a sensible limit.
-- Hence, if there are 1000 tests, we divide the test number by 100 to get the test size. -- Hence, if there are 1000 tests, we divide the test number by 100 to get the test size.
deepCheck p = check (defaultConfig { configMaxTest = 1000, configSize = \x -> div x 100}) p configForSize :: Int -> Config
configForSize n = defaultConfig { configMaxTest = n, configSize = \x -> x `div` scale }
where
scale = n `div` 10
testModify :: Test deepCheck :: Testable a => a -> QuickCheckTest
testModify = TestList deepCheck test level = (flip check) test $ configForSize $
case level of
QC_Low -> 100
QC_Medium -> 1000
QC_High -> 5000
QC_Extensive -> 10000
testModify :: [QuickCheckTest]
testModify =
[ [
TestCase $ deepCheck prop_Id deepCheck prop_Id
,TestCase $ deepCheck prop_Rep ,deepCheck prop_Rep
,TestCase $ deepCheck prop_gennums ,deepCheck prop_gennums
] ]
where where
-- | Checks that applying any set (from the powerset of identity functions) of identity functions -- | Checks that applying any set (from the powerset of identity functions) of identity functions
@ -598,13 +609,14 @@ testModify = TestList
collectAll' r0 r1 | ok r0 == Just False = r0 collectAll' r0 r1 | ok r0 == Just False = r0
| otherwise = r1 | otherwise = r1
-- | Returns the list of tests: -- | Returns the list of tests:
tests :: Test qcTests :: (Test, [QuickCheckTest])
tests = TestList qcTests = (TestList
[ [
testCase testCase
,testIf ,testIf
,testModify
,testPar ,testPar
,testSeq ,testSeq
,testWhile ,testWhile
] ]
,testModify)

View File

@ -16,7 +16,7 @@ You should have received a copy of the GNU General Public License along
with this program. If not, see <http://www.gnu.org/licenses/>. with this program. If not, see <http://www.gnu.org/licenses/>.
-} -}
module RainUsageCheckTest (tests) where module RainUsageCheckTest (qcTests) where
import Control.Monad.Identity import Control.Monad.Identity
import Data.Graph.Inductive import Data.Graph.Inductive
@ -397,8 +397,8 @@ generateProblem = (choose (1,10) >>= (\n -> replicateM n $ choose (-20,20)) >>=
instance Arbitrary OmegaTestInput where instance Arbitrary OmegaTestInput where
arbitrary = generateProblem arbitrary = generateProblem
qcOmegaEquality :: Test qcOmegaEquality :: [QuickCheckTest]
qcOmegaEquality = TestCase $ check (defaultConfig { configMaxTest = 1000}) prop qcOmegaEquality = [scaleQC (40,200,2000,10000) prop]
where where
prop (OMI (eq,ineq)) = omegaCheck actAnswer prop (OMI (eq,ineq)) = omegaCheck actAnswer
where where
@ -406,16 +406,16 @@ qcOmegaEquality = TestCase $ check (defaultConfig { configMaxTest = 1000}) prop
omegaCheck (Just ineqs) = all (all (== 0) . elems) ineqs omegaCheck (Just ineqs) = all (all (== 0) . elems) ineqs
omegaCheck Nothing = False omegaCheck Nothing = False
tests :: Test qcTests :: (Test, [QuickCheckTest])
tests = TestList qcTests = (TestList
[ [
testGetVarProc testGetVarProc
,testInitVar ,testInitVar
-- ,testParUsageCheck -- ,testParUsageCheck
,testReachDef ,testReachDef
,testArrayCheck ,testArrayCheck
,qcOmegaEquality
] ]
,qcOmegaEquality)