Stability | experimental |
---|---|
Maintainer | [email protected] |
Test.QuickCheck.Classes
Description
Some QuickCheck properties for standard type classes
- ordRel :: forall a. (Ord a, Show a, Arbitrary a, EqProp a) => BinRel a -> (a -> Gen a) -> TestBatch
- ord :: forall a. (Ord a, Show a, Arbitrary a, EqProp a) => (a -> Gen a) -> TestBatch
- ordMorphism :: (Ord a, Ord b, EqProp b, Show a, Arbitrary a) => (a -> b) -> TestBatch
- semanticOrd :: forall a b. (Model a b, Ord a, Ord b, Show a, Arbitrary a, EqProp b) => a -> TestBatch
- monoid :: forall a. (Monoid a, Show a, Arbitrary a, EqProp a) => a -> TestBatch
- monoidMorphism :: (Monoid a, Monoid b, EqProp b, Show a, Arbitrary a) => (a -> b) -> TestBatch
- semanticMonoid :: forall a b. (Model a b, Monoid a, Monoid b, Show a, Arbitrary a, EqProp b) => a -> TestBatch
- functor :: forall m a b c. (Functor m, Arbitrary a, Arbitrary b, Arbitrary c, Show (m a), Arbitrary (m a), EqProp (m a), EqProp (m c)) => m (a, b, c) -> TestBatch
- functorMorphism :: forall f g. (Functor f, Functor g, Arbitrary (f NumT), Show (f NumT), EqProp (g T)) => (forall a. f a -> g a) -> TestBatch
- semanticFunctor :: forall f g. (Model1 f g, Functor f, Functor g, Arbitrary (f NumT), Show (f NumT), EqProp (g T)) => f () -> TestBatch
- functorMonoid :: forall m a b. (Functor m, Monoid (m a), Monoid (m b), Arbitrary (a -> b), Arbitrary (m a), Show (m a), EqProp (m b)) => m (a, b) -> TestBatch
- applicative :: forall m a b c. (Applicative m, Arbitrary a, Arbitrary b, Arbitrary (m a), Arbitrary (m (b -> c)), Show (m (b -> c)), Arbitrary (m (a -> b)), Show (m (a -> b)), Show a, Show (m a), EqProp (m a), EqProp (m b), EqProp (m c)) => m (a, b, c) -> TestBatch
- applicativeMorphism :: forall f g. (Applicative f, Applicative g, Show (f NumT), Arbitrary (f NumT), EqProp (g NumT), EqProp (g T), Show (f (NumT -> T)), Arbitrary (f (NumT -> T))) => (forall a. f a -> g a) -> TestBatch
- semanticApplicative :: forall f g. (Model1 f g, Applicative f, Applicative g, Arbitrary (f NumT), Arbitrary (f (NumT -> T)), EqProp (g NumT), EqProp (g T), Show (f NumT), Show (f (NumT -> T))) => f () -> TestBatch
- monad :: forall m a b c. (Monad m, Show a, Arbitrary a, Arbitrary b, Arbitrary (m a), EqProp (m a), Show (m a), Arbitrary (m b), EqProp (m b), Arbitrary (m c), EqProp (m c)) => m (a, b, c) -> TestBatch
- monadMorphism :: forall f g. (Monad f, Monad g, Functor g, Show (f NumT), Show (f (NumT -> T)), Show (f (f (NumT -> T))), Arbitrary (f NumT), Arbitrary (f T), Arbitrary (f (NumT -> T)), Arbitrary (f (f (NumT -> T))), EqProp (g NumT), EqProp (g T), EqProp (g (NumT -> T))) => (forall a. f a -> g a) -> TestBatch
- semanticMonad :: forall f g. (Model1 f g, Monad f, Monad g, EqProp (g T), EqProp (g NumT), EqProp (g (NumT -> T)), Arbitrary (f T), Arbitrary (f NumT), Arbitrary (f (f (NumT -> T))), Arbitrary (f (NumT -> T)), Show (f (f (NumT -> T))), Show (f (NumT -> T)), Show (f NumT), Functor g) => f () -> TestBatch
- monadFunctor :: forall m a b. (Functor m, Monad m, Arbitrary a, Arbitrary b, Arbitrary (m a), Show (m a), EqProp (m b)) => m (a, b) -> TestBatch
- monadApplicative :: forall m a b. (Applicative m, Monad m, EqProp (m a), EqProp (m b), Show a, Arbitrary a, Show (m a), Arbitrary (m a), Show (m (a -> b)), Arbitrary (m (a -> b))) => m (a, b) -> TestBatch
- arrow :: forall (~>) b c d e. (Arrow ~>, Show (d ~> e), Show (c ~> d), Show (b ~> c), Show b, Show c, Show d, Show e, Arbitrary (d ~> e), Arbitrary (c ~> d), Arbitrary (b ~> c), Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e, EqProp (b ~> e), EqProp (b ~> d), EqProp ((b, d) ~> c), EqProp ((b, d) ~> (c, d)), EqProp ((b, e) ~> (d, e)), EqProp ((b, d) ~> (c, e)), EqProp b, EqProp c, EqProp d, EqProp e) => (b ~> (c, d, e)) -> TestBatch
- arrowChoice :: forall (~>) b c d e. (ArrowChoice ~>, Show (b ~> c), Arbitrary (b ~> c), Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e, EqProp (Either b d ~> Either c e), EqProp (Either b d ~> Either c d)) => (b ~> (c, d, e)) -> TestBatch
- traversable :: forall f a b m. (Traversable f, Monoid m, Show (f a), Arbitrary (f a), Arbitrary b, Arbitrary a, Arbitrary m, EqProp (f b), EqProp m) => f (a, b, m) -> TestBatch
- monadPlus :: forall m a b. (MonadPlus m, Show (m a), Arbitrary a, Arbitrary (m a), Arbitrary (m b), EqProp (m a), EqProp (m b)) => m (a, b) -> TestBatch
- monadOr :: forall m a b. (MonadPlus m, Show a, Show (m a), Arbitrary a, Arbitrary (m a), Arbitrary (m b), EqProp (m a), EqProp (m b)) => m (a, b) -> TestBatch
Documentation
ordRel :: forall a. (Ord a, Show a, Arbitrary a, EqProp a) => BinRel a -> (a -> Gen a) -> TestBatchSource
Total ordering. gen a
ought to generate values b
satisfying a
fairly often.
rel
b
ord :: forall a. (Ord a, Show a, Arbitrary a, EqProp a) => (a -> Gen a) -> TestBatchSource
Total ordering
semanticOrd :: forall a b. (Model a b, Ord a, Ord b, Show a, Arbitrary a, EqProp b) => a -> TestBatchSource
The semantic function (model
) for a
is an ordMorphism
.
monoid :: forall a. (Monoid a, Show a, Arbitrary a, EqProp a) => a -> TestBatchSource
Properties to check that the Monoid
a
satisfies the monoid
properties. The argument value is ignored and is present only for its
type.
monoidMorphism :: (Monoid a, Monoid b, EqProp b, Show a, Arbitrary a) => (a -> b) -> TestBatchSource
Monoid homomorphism properties. See also homomorphism
.
semanticMonoid :: forall a b. (Model a b, Monoid a, Monoid b, Show a, Arbitrary a, EqProp b) => a -> TestBatchSource
functor :: forall m a b c. (Functor m, Arbitrary a, Arbitrary b, Arbitrary c, Show (m a), Arbitrary (m a), EqProp (m a), EqProp (m c)) => m (a, b, c) -> TestBatchSource
Properties to check that the Functor
m
satisfies the functor
properties.
functorMorphism :: forall f g. (Functor f, Functor g, Arbitrary (f NumT), Show (f NumT), EqProp (g T)) => (forall a. f a -> g a) -> TestBatchSource
Functor
morphism (natural transformation) properties
semanticFunctor :: forall f g. (Model1 f g, Functor f, Functor g, Arbitrary (f NumT), Show (f NumT), EqProp (g T)) => f () -> TestBatchSource
The semantic function (model1
) for f
is a functorMorphism
.
functorMonoid :: forall m a b. (Functor m, Monoid (m a), Monoid (m b), Arbitrary (a -> b), Arbitrary (m a), Show (m a), EqProp (m b)) => m (a, b) -> TestBatchSource
The semantic function (model
) for a
is a monoidMorphism
.
applicative :: forall m a b c. (Applicative m, Arbitrary a, Arbitrary b, Arbitrary (m a), Arbitrary (m (b -> c)), Show (m (b -> c)), Arbitrary (m (a -> b)), Show (m (a -> b)), Show a, Show (m a), EqProp (m a), EqProp (m b), EqProp (m c)) => m (a, b, c) -> TestBatchSource
Properties to check that the Applicative
m
satisfies the monad
properties
applicativeMorphism :: forall f g. (Applicative f, Applicative g, Show (f NumT), Arbitrary (f NumT), EqProp (g NumT), EqProp (g T), Show (f (NumT -> T)), Arbitrary (f (NumT -> T))) => (forall a. f a -> g a) -> TestBatchSource
Applicative
morphism properties
semanticApplicative :: forall f g. (Model1 f g, Applicative f, Applicative g, Arbitrary (f NumT), Arbitrary (f (NumT -> T)), EqProp (g NumT), EqProp (g T), Show (f NumT), Show (f (NumT -> T))) => f () -> TestBatchSource
The semantic function (model1
) for f
is an applicativeMorphism
.
monad :: forall m a b c. (Monad m, Show a, Arbitrary a, Arbitrary b, Arbitrary (m a), EqProp (m a), Show (m a), Arbitrary (m b), EqProp (m b), Arbitrary (m c), EqProp (m c)) => m (a, b, c) -> TestBatchSource
Properties to check that the Monad
m
satisfies the monad properties
monadMorphism :: forall f g. (Monad f, Monad g, Functor g, Show (f NumT), Show (f (NumT -> T)), Show (f (f (NumT -> T))), Arbitrary (f NumT), Arbitrary (f T), Arbitrary (f (NumT -> T)), Arbitrary (f (f (NumT -> T))), EqProp (g NumT), EqProp (g T), EqProp (g (NumT -> T))) => (forall a. f a -> g a) -> TestBatchSource
Monad
morphism properties
Applicative
morphism properties
semanticMonad :: forall f g. (Model1 f g, Monad f, Monad g, EqProp (g T), EqProp (g NumT), EqProp (g (NumT -> T)), Arbitrary (f T), Arbitrary (f NumT), Arbitrary (f (f (NumT -> T))), Arbitrary (f (NumT -> T)), Show (f (f (NumT -> T))), Show (f (NumT -> T)), Show (f NumT), Functor g) => f () -> TestBatchSource
The semantic function (model1
) for f
is a monadMorphism
.
monadFunctor :: forall m a b. (Functor m, Monad m, Arbitrary a, Arbitrary b, Arbitrary (m a), Show (m a), EqProp (m b)) => m (a, b) -> TestBatchSource
Law for monads that are also instances of Functor
.
monadApplicative :: forall m a b. (Applicative m, Monad m, EqProp (m a), EqProp (m b), Show a, Arbitrary a, Show (m a), Arbitrary (m a), Show (m (a -> b)), Arbitrary (m (a -> b))) => m (a, b) -> TestBatchSource
arrow :: forall (~>) b c d e. (Arrow ~>, Show (d ~> e), Show (c ~> d), Show (b ~> c), Show b, Show c, Show d, Show e, Arbitrary (d ~> e), Arbitrary (c ~> d), Arbitrary (b ~> c), Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e, EqProp (b ~> e), EqProp (b ~> d), EqProp ((b, d) ~> c), EqProp ((b, d) ~> (c, d)), EqProp ((b, e) ~> (d, e)), EqProp ((b, d) ~> (c, e)), EqProp b, EqProp c, EqProp d, EqProp e) => (b ~> (c, d, e)) -> TestBatchSource
arrowChoice :: forall (~>) b c d e. (ArrowChoice ~>, Show (b ~> c), Arbitrary (b ~> c), Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e, EqProp (Either b d ~> Either c e), EqProp (Either b d ~> Either c d)) => (b ~> (c, d, e)) -> TestBatchSource
traversable :: forall f a b m. (Traversable f, Monoid m, Show (f a), Arbitrary (f a), Arbitrary b, Arbitrary a, Arbitrary m, EqProp (f b), EqProp m) => f (a, b, m) -> TestBatchSource