Safe Haskell | None |
---|---|
Language | Haskell2010 |
An alternative to Testable
Synopsis
- data Equation a = (:=:) a a
- data Implication a b = (:==>) a b
- type EqImpl a b = Implication (Equation a) (Equation b)
- class Decidable a where
- quickCheck' :: Testable' prop => prop -> IO ()
- quickCheckWith' :: Testable' prop => Args -> prop -> IO ()
- ok :: Testable' prop => String -> prop -> (String, Property)
- ko :: Testable' prop => String -> prop -> (String, Property)
- quickChecks :: [(String, Property)] -> IO Bool
Syntax for properties
Equation: an equals sign between two values.
(:=:) a a infix 5 |
Instances
Eq a => Eq (Equation a) Source # | |
Ord a => Ord (Equation a) Source # | |
Show a => Show (Equation a) Source # | |
TestEq a => Testable (Equation a) Source # | |
TestEq a => Testable' (Equation a) Source # | |
Eq a => Decidable (Equation a) Source # | |
data Implication a b Source #
Expressions denoting a logical implication.
(:==>) a b infixr 2 |
Instances
(Decidable a, Testable b) => Testable (Implication a b) Source # | Just use |
Defined in Test.QuickCheck.HigherOrder.Internal.Testable property :: Implication a b -> Property # propertyForAllShrinkShow :: Gen a0 -> (a0 -> [a0]) -> (a0 -> [String]) -> (a0 -> Implication a b) -> Property # | |
(Decidable a, Testable' b) => Testable' (Implication a b) Source # | Just use |
Defined in Test.QuickCheck.HigherOrder.Internal.Testable property' :: Implication a b -> Property Source # |
class Decidable a where Source #
Decidable property.
The definition of decidability: we can compute whether a property is true.
Auxiliary functions
quickCheck' :: Testable' prop => prop -> IO () Source #
Variant of quickCheck
using the alternative Testable'
.
quickCheckWith' :: Testable' prop => Args -> prop -> IO () Source #
Variant of quickCheckWith
using the alternative Testable'
.
ok :: Testable' prop => String -> prop -> (String, Property) Source #
A named property that should pass.
Use ok
and ko
to construct lists of named properties
[(
, which can be run using String
, Property
)]quickChecks
,
or testProperties
from tasty-quickcheck.