{-# OPTIONS_GHC -fno-warn-missing-signatures #-} -- | Cartel properties. For the time being, most (maybe all) of these -- properties test the generators, rather than Cartel itself. I had -- to debug generators that were stuck in an infinite loop. module Cartel.Properties where import Cartel import Cartel.Ast import Control.Monad import Test.QuickCheck import qualified Cartel.Generators as G seconds :: Int -> Int seconds = (* 10 ^ (6 :: Int)) newtype Little = Little Word deriving (Eq, Ord, Show) instance Arbitrary Little where arbitrary = sized f where f sz = fmap Little (choose (0, min (fromIntegral sz) 10)) completesInSecs :: Show a => Int -- ^ How many seconds -> G.Gen a -> Little -- ^ How many flags -> Little -- ^ Size -> Int -- ^ Seed -> Property completesInSecs time gen (Little nFlags) (Little sz) sd = within (seconds time) $ length (show (G.genResult gen nFlags sz sd)) >= 0 prop_vcsCompletesInSecs = completesInSecs 10 (G.arbitrary :: G.Gen Vcs) prop_constraintCompletesInSecs = completesInSecs 10 (G.arbitrary :: G.Gen Constraint) mainIsCompletesInSecs a = completesInSecs 10 (G.genMainIs `asTypeOf` a) prop_conditionCompletesInSecs = completesInSecs 10 (G.arbitrary :: G.Gen Condition) buildInfoCompletesInSecs a = completesInSecs 10 (G.genBuildInfo `asTypeOf` a) -- ExecutableField contents prop_buildInfoExeCompletesInSecs = buildInfoCompletesInSecs (undefined :: G.Gen ExecutableField) prop_condBlockExeCompletesInSecs = completesInSecs 10 (G.genCondBlock :: G.Gen ExecutableField) prop_exeMainIsCompletesInSecs = mainIsCompletesInSecs (undefined :: G.Gen ExecutableField) prop_cabalCompletesInSecs = completesInSecs 10 (G.arbitrary :: G.Gen Cabal) prop_propertiesCompletesInSecs = completesInSecs 10 (G.arbitrary :: G.Gen Properties) prop_repositoryCompletesInSecs = completesInSecs 10 (G.arbitrary :: G.Gen Repository) prop_sectionCompletesInSecs = completesInSecs 10 (G.arbitrary :: G.Gen Section) prop_executableCompletesInSecs = completesInSecs 10 (liftM2 executable G.genNonEmptyString G.arbitrary) prop_benchmarkCompletesInSecs = completesInSecs 10 (liftM2 benchmark G.genNonEmptyString G.arbitrary) prop_testSuiteCompletesInSecs = completesInSecs 10 (liftM2 testSuite G.genNonEmptyString G.arbitrary)