Safe Haskell | None |
---|---|
Language | GHC2021 |
Skeletest.Prop.Internal
Synopsis
- type Property = PropertyM ()
- data PropertyM a
- runProperty :: Property -> IO TestResult
- forAll :: (HasCallStack, Show a) => Gen a -> PropertyM a
- discard :: PropertyM a
- setDiscardLimit :: Int -> Property
- setShrinkLimit :: Int -> Property
- setShrinkRetries :: Int -> Property
- setConfidence :: Int -> Property
- setVerifiedTermination :: Property
- setTestLimit :: Int -> Property
- classify :: HasCallStack => String -> Bool -> Property
- cover :: HasCallStack => Double -> String -> Bool -> Property
- label :: HasCallStack => String -> Property
- collect :: (Show a, HasCallStack) => a -> Property
- data PropSeedFlag
- data PropLimitFlag
Documentation
type Property = PropertyM () Source #
A property to run, with optional configuration settings specified up front.
Settings should be specified before any other Property
calls; any settings
specified afterwards are ignored.
Instances
MonadIO PropertyM Source # | |
Defined in Skeletest.Prop.Internal | |
Applicative PropertyM Source # | |
Functor PropertyM Source # | |
Monad PropertyM Source # | |
Testable PropertyM Source # | |
Defined in Skeletest.Prop.Internal Methods runTestable :: PropertyM () -> IO TestResult Source # context :: String -> PropertyM a -> PropertyM a Source # throwFailure :: AssertionFail -> PropertyM a Source # |
runProperty :: Property -> IO TestResult Source #
Test
Configuring properties
setDiscardLimit :: Int -> Property Source #
setShrinkLimit :: Int -> Property Source #
setShrinkRetries :: Int -> Property Source #
setConfidence :: Int -> Property Source #
setTestLimit :: Int -> Property Source #
Coverage
classify :: HasCallStack => String -> Bool -> Property Source #
Record the propotion of tests which satisfy a given condition
xs <- forAll $ Gen.list (Range.linear 0 100) $ Gen.int (Range.linear 0 100) for_ xs $ x -> do classify "newborns" $ x == 0 classify "children" $ x > 0 && x < 13 classify "teens" $ x > 12 && x < 20
cover :: HasCallStack => Double -> String -> Bool -> Property Source #
Require a certain percentage of the tests to be covered by the classifier.
In the following example, if the condition does not have at least 30% coverage, the test will fail.
match <- forAll Gen.bool cover 30 "true" $ match cover 30 "false" $ not match
label :: HasCallStack => String -> Property Source #
Add a label for each test run. It produces a table showing the percentage of test runs that produced each label.
CLI flags
data PropSeedFlag Source #