Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
PropUnit
Synopsis
- data DependencyType
- type Gen = GenT Identity
- class Monad m => MonadTest (m :: Type -> Type)
- data Property
- data PropertyT (m :: Type -> Type) a
- data Range a
- data TestLimit
- type TestName = String
- data TestT (m :: Type -> Type) a
- data TestTree
- (===) :: (MonadTest m, Eq a, Show a, HasCallStack) => a -> a -> m ()
- (/==) :: (MonadTest m, Eq a, Show a, HasCallStack) => a -> a -> m ()
- after :: DependencyType -> String -> TestTree -> TestTree
- assert :: (MonadTest m, HasCallStack) => Bool -> m ()
- forAll :: forall (m :: Type -> Type) a. (Monad m, Show a, HasCallStack) => Gen a -> PropertyT m a
- testProp :: TestName -> TestLimit -> PropertyT IO () -> TestTree
- testUnit :: TestName -> TestT IO () -> TestTree
- defaultTestLimit :: TestLimit
- setupTests :: IO TestLimit
- testGroup :: TestName -> [TestTree] -> TestTree
- testMain :: (TestLimit -> TestTree) -> IO ()
- withResource :: IO a -> (a -> IO ()) -> (IO a -> TestTree) -> TestTree
- class GenDefault tag a where
- genDefault :: Proxy tag -> Gen a
- genDefaultTag :: forall tag a tag'. GenDefault tag' a => Proxy tag' -> Proxy tag -> Gen a
- genDefaultIntegral :: forall tag a. (Integral a, Bounded a) => Proxy tag -> Gen a
- genDefaultEnum :: forall tag a. (Enum a, Bounded a) => Proxy tag -> Gen a
- genDefaultList :: forall tag a mn mx. (IsList a, KnownNat mn, KnownNat mx, GenDefault tag (Item a)) => Proxy mn -> Proxy mx -> Proxy tag -> Gen a
- genDefaultString :: forall tag a mn mx. (IsString a, KnownNat mn, KnownNat mx, GenDefault tag Char) => Proxy mn -> Proxy mx -> Proxy tag -> Gen a
- genDefaultGeneric :: forall tag a. (Generic a, GGenDefault tag (Rep a)) => Proxy tag -> Gen a
- data StdTag
Documentation
data DependencyType #
These are the two ways in which one test may depend on the others.
This is the same distinction as the hard vs soft dependencies in TestNG.
Since: tasty-1.2
Constructors
AllSucceed | The current test tree will be executed after its dependencies finish, and only if all of the dependencies succeed. |
AllFinish | The current test tree will be executed after its dependencies finish, regardless of whether they succeed or not. |
Instances
Read DependencyType | Since: tasty-1.5 |
Defined in Test.Tasty.Core Methods readsPrec :: Int -> ReadS DependencyType # readList :: ReadS [DependencyType] # | |
Show DependencyType | |
Defined in Test.Tasty.Core Methods showsPrec :: Int -> DependencyType -> ShowS # show :: DependencyType -> String # showList :: [DependencyType] -> ShowS # | |
Eq DependencyType | |
Defined in Test.Tasty.Core Methods (==) :: DependencyType -> DependencyType -> Bool # (/=) :: DependencyType -> DependencyType -> Bool # |
class Monad m => MonadTest (m :: Type -> Type) #
Minimal complete definition
Instances
A property test, along with some configurable limits like how many times to run the test.
data PropertyT (m :: Type -> Type) a #
The property monad transformer allows both the generation of test inputs and the assertion of expectations.
Instances
The number of successful tests that need to be run before a property test is considered successful.
Can be constructed using numeric literals:
200 :: TestLimit
Instances
Enum TestLimit | |
Defined in Hedgehog.Internal.Property Methods succ :: TestLimit -> TestLimit # pred :: TestLimit -> TestLimit # fromEnum :: TestLimit -> Int # enumFrom :: TestLimit -> [TestLimit] # enumFromThen :: TestLimit -> TestLimit -> [TestLimit] # enumFromTo :: TestLimit -> TestLimit -> [TestLimit] # enumFromThenTo :: TestLimit -> TestLimit -> TestLimit -> [TestLimit] # | |
Num TestLimit | |
Defined in Hedgehog.Internal.Property | |
Integral TestLimit | |
Defined in Hedgehog.Internal.Property Methods quot :: TestLimit -> TestLimit -> TestLimit # rem :: TestLimit -> TestLimit -> TestLimit # div :: TestLimit -> TestLimit -> TestLimit # mod :: TestLimit -> TestLimit -> TestLimit # quotRem :: TestLimit -> TestLimit -> (TestLimit, TestLimit) # divMod :: TestLimit -> TestLimit -> (TestLimit, TestLimit) # | |
Real TestLimit | |
Defined in Hedgehog.Internal.Property Methods toRational :: TestLimit -> Rational # | |
Show TestLimit | |
Eq TestLimit | |
Ord TestLimit | |
Lift TestLimit | |
data TestT (m :: Type -> Type) a #
A test monad transformer allows the assertion of expectations.
Instances
The main data structure defining a test suite.
It consists of individual test cases and properties, organized in named groups which form a tree-like hierarchy.
There is no generic way to create a test case. Instead, every test
provider (tasty-hunit, tasty-smallcheck etc.) provides a function to
turn a test case into a TestTree
.
Groups can be created using testGroup
.
Since: tasty-0.1
(===) :: (MonadTest m, Eq a, Show a, HasCallStack) => a -> a -> m () infix 4 #
Fails the test if the two arguments provided are not equal.
(/==) :: (MonadTest m, Eq a, Show a, HasCallStack) => a -> a -> m () infix 4 #
Fails the test if the two arguments provided are equal.
Arguments
:: DependencyType | whether to run the tests even if some of the dependencies fail |
-> String | the pattern |
-> TestTree | the subtree that depends on other tests |
-> TestTree | the subtree annotated with dependency information |
The after
combinator declares dependencies between tests.
If a TestTree
is wrapped in after
, the tests in this tree will not run
until certain other tests («dependencies») have finished. These
dependencies are specified using an AWK pattern (see the «Patterns» section
in the README).
Moreover, if the DependencyType
argument is set to AllSucceed
and
at least one dependency has failed, this test tree will not run at all.
Tasty does not check that the pattern matches any tests (let alone the correct set of tests), so it is on you to supply the right pattern.
Examples
The following test will be executed only after all tests that contain
Foo
anywhere in their path finish.
after
AllFinish
"Foo" $
testCase "A test that depends on Foo.Bar" $ ...
Note, however, that our test also happens to contain Foo
as part of its name,
so it also matches the pattern and becomes a dependency of itself. This
will result in a DependencyLoop
exception. To avoid this, either
change the test name so that it doesn't mention Foo
or make the
pattern more specific.
You can use AWK patterns, for instance, to specify the full path to the dependency.
after
AllFinish
"$0 == \"Tests.Foo.Bar\"" $
testCase "A test that depends on Foo.Bar" $ ...
Or only specify the dependency's own name, ignoring the group names:
after
AllFinish
"$NF == \"Bar\"" $
testCase "A test that depends on Foo.Bar" $ ...
Since: tasty-1.2
assert :: (MonadTest m, HasCallStack) => Bool -> m () #
Fails the test if the condition provided is False
.
forAll :: forall (m :: Type -> Type) a. (Monad m, Show a, HasCallStack) => Gen a -> PropertyT m a #
Generates a random input for the test by running the provided generator.
setupTests :: IO TestLimit Source #
testGroup :: TestName -> [TestTree] -> TestTree #
Create a named group of test cases or other groups. Tests are executed in
parallel. For sequential execution, see sequentialTestGroup
.
Since: tasty-0.1
Arguments
:: IO a | initialize the resource |
-> (a -> IO ()) | free the resource |
-> (IO a -> TestTree) |
|
-> TestTree |
Acquire the resource to run this test (sub)tree and release it afterwards.
Since: tasty-0.5
class GenDefault tag a where Source #
Methods
genDefault :: Proxy tag -> Gen a Source #
Default generator for a
The type-level tag
allows types a
to have multiple defaults.
Instances
genDefaultTag :: forall tag a tag'. GenDefault tag' a => Proxy tag' -> Proxy tag -> Gen a Source #
genDefaultList :: forall tag a mn mx. (IsList a, KnownNat mn, KnownNat mx, GenDefault tag (Item a)) => Proxy mn -> Proxy mx -> Proxy tag -> Gen a Source #
genDefaultString :: forall tag a mn mx. (IsString a, KnownNat mn, KnownNat mx, GenDefault tag Char) => Proxy mn -> Proxy mx -> Proxy tag -> Gen a Source #
genDefaultGeneric :: forall tag a. (Generic a, GGenDefault tag (Rep a)) => Proxy tag -> Gen a Source #
Type tag for these "standard" default generators.
You can use this tag directly or choose type-by-type with genDefaultTag
.