module Foundation.Check.Types
( Test(..)
, testName
, fqTestName
, groupHasSubGroup
, Check(..)
, PlanState(..)
, PropertyResult(..)
, TestResult(..)
, HasFailures
) where
import Foundation.Primitive.Imports
import Foundation.Collection
import Foundation.Monad.State
import Foundation.Check.Property
import Foundation.Check.Gen
data PropertyResult =
PropertySuccess
| PropertyFailed String
deriving (Show,Eq)
data TestResult =
PropertyResult String HasTests PropertyResult
| GroupResult String HasFailures HasTests [TestResult]
deriving (Show)
type HasTests = CountOf TestResult
type HasFailures = CountOf TestResult
data PlanState = PlanState
{ planRng :: Word64 -> GenRng
, planValidations :: CountOf TestResult
, planParams :: GenParams
, planFailures :: [TestResult]
}
newtype Check a = Check { runCheck :: StateT PlanState IO a }
deriving (Functor, Applicative, Monad)
instance MonadState Check where
type State Check = PlanState
withState f = Check (withState f)
data Test where
Unit :: String -> IO () -> Test
Property :: IsProperty prop => String -> prop -> Test
Group :: String -> [Test] -> Test
CheckPlan :: String -> Check () -> Test
testName :: Test -> String
testName (Unit s _) = s
testName (Property s _) = s
testName (Group s _) = s
testName (CheckPlan s _) = s
fqTestName :: [String] -> String
fqTestName = intercalate "/" . reverse
groupHasSubGroup :: [Test] -> Bool
groupHasSubGroup [] = False
groupHasSubGroup (Group{}:_) = True
groupHasSubGroup (_:xs) = groupHasSubGroup xs