Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- check :: MonadIO m => Property -> m Bool
- recheck :: MonadIO m => Size -> Seed -> Property -> m ()
- data RunnerConfig = RunnerConfig {
- runnerWorkers :: !(Maybe WorkerCount)
- runnerColor :: !(Maybe UseColor)
- runnerSeed :: !(Maybe Seed)
- runnerVerbosity :: !(Maybe Verbosity)
- checkParallel :: MonadIO m => Group -> m Bool
- checkSequential :: MonadIO m => Group -> m Bool
- checkGroup :: MonadIO m => RunnerConfig -> Group -> m Bool
- checkReport :: forall m. MonadIO m => MonadCatch m => PropertyConfig -> Size -> Seed -> PropertyT m () -> (Report Progress -> m ()) -> m (Report Result)
- checkRegion :: MonadIO m => Region -> UseColor -> Maybe PropertyName -> Size -> Seed -> Property -> m (Report Result)
- checkNamed :: MonadIO m => Region -> UseColor -> Maybe PropertyName -> Maybe Seed -> Property -> m (Report Result)
Running Individual Properties
recheck :: MonadIO m => Size -> Seed -> Property -> m () Source #
Check a property using a specific size and seed.
Running Groups of Properties
data RunnerConfig Source #
Configuration for a property test run.
RunnerConfig | |
|
Instances
Eq RunnerConfig Source # | |
Defined in Hedgehog.Internal.Runner (==) :: RunnerConfig -> RunnerConfig -> Bool # (/=) :: RunnerConfig -> RunnerConfig -> Bool # | |
Ord RunnerConfig Source # | |
Defined in Hedgehog.Internal.Runner compare :: RunnerConfig -> RunnerConfig -> Ordering # (<) :: RunnerConfig -> RunnerConfig -> Bool # (<=) :: RunnerConfig -> RunnerConfig -> Bool # (>) :: RunnerConfig -> RunnerConfig -> Bool # (>=) :: RunnerConfig -> RunnerConfig -> Bool # max :: RunnerConfig -> RunnerConfig -> RunnerConfig # min :: RunnerConfig -> RunnerConfig -> RunnerConfig # | |
Show RunnerConfig Source # | |
Defined in Hedgehog.Internal.Runner showsPrec :: Int -> RunnerConfig -> ShowS # show :: RunnerConfig -> String # showList :: [RunnerConfig] -> ShowS # | |
Lift RunnerConfig Source # | |
Defined in Hedgehog.Internal.Runner lift :: RunnerConfig -> Q Exp # liftTyped :: RunnerConfig -> Q (TExp RunnerConfig) # |
checkParallel :: MonadIO m => Group -> m Bool Source #
Check a group of properties in parallel.
Warning: although this check function runs tests faster than
checkSequential
, it should be noted that it may cause problems with
properties that are not self-contained. For example, if you have a group
of tests which all use the same database table, you may find that they
interfere with each other when being run in parallel.
Using Template Haskell for property discovery:
tests :: IO Bool tests = checkParallel $$(discover)
With manually specified properties:
tests :: IO Bool tests = checkParallel $ Group "Test.Example" [ ("prop_reverse", prop_reverse) ]
checkSequential :: MonadIO m => Group -> m Bool Source #
Check a group of properties sequentially.
Using Template Haskell for property discovery:
tests :: IO Bool tests = checkSequential $$(discover)
With manually specified properties:
tests :: IO Bool tests = checkSequential $ Group "Test.Example" [ ("prop_reverse", prop_reverse) ]
checkGroup :: MonadIO m => RunnerConfig -> Group -> m Bool Source #
Check a group of properties using the specified runner config.
Internal
checkReport :: forall m. MonadIO m => MonadCatch m => PropertyConfig -> Size -> Seed -> PropertyT m () -> (Report Progress -> m ()) -> m (Report Result) Source #