{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Test.Byron.Spec.Ledger.Relation.Properties (testRelation) where
import Byron.Spec.Ledger.Core hiding ((<|))
import Data.Bimap (Bimap)
import qualified Data.Bimap as Bimap
import Data.Map.Strict (Map)
import Data.Set (Set, union, (\\))
import Hedgehog (Gen, MonadTest, Property, PropertyT, forAll, property, withTests, (===))
import qualified Hedgehog.Gen as Gen
import Hedgehog.Internal.Property (PropertyName (..))
import qualified Hedgehog.Range as Range
import Test.Tasty (TestName, TestTree, testGroup)
import Test.Tasty.Hedgehog hiding (testProperty)
testProperty :: TestName -> Property -> TestTree
testProperty :: TestName -> Property -> TestTree
testProperty TestName
s Property
p = TestName -> PropertyName -> Property -> TestTree
testPropertyNamed TestName
s (TestName -> PropertyName
Hedgehog.Internal.Property.PropertyName TestName
s) Property
p
propDomainRestrictionAndIntersection ::
(MonadTest m, Relation r, Ord (Domain r), Show (Domain r)) =>
Set (Domain r) ->
r ->
m ()
propDomainRestrictionAndIntersection :: forall (m :: * -> *) r.
(MonadTest m, Relation r, Ord (Domain r), Show (Domain r)) =>
Set (Domain r) -> r -> m ()
propDomainRestrictionAndIntersection Set (Domain r)
s r
r =
forall m. (Relation m, Ord (Domain m)) => m -> Set (Domain m)
dom r
r forall a. Ord a => Set a -> Set a -> Set a
∩ Set (Domain r)
s forall (m :: * -> *) a.
(MonadTest m, Eq a, Show a, HasCallStack) =>
a -> a -> m ()
=== forall m. (Relation m, Ord (Domain m)) => m -> Set (Domain m)
dom (Set (Domain r)
s forall m (f :: * -> *).
(Relation m, Ord (Domain m), Foldable f) =>
f (Domain m) -> m -> m
◁ r
r)
propDomainRestrictionAndIntersectionB ::
(MonadTest m, Relation r, Eq r, Show r, Ord (Domain r)) =>
Set (Domain r) ->
r ->
m ()
propDomainRestrictionAndIntersectionB :: forall (m :: * -> *) r.
(MonadTest m, Relation r, Eq r, Show r, Ord (Domain r)) =>
Set (Domain r) -> r -> m ()
propDomainRestrictionAndIntersectionB Set (Domain r)
s r
r =
(forall m. (Relation m, Ord (Domain m)) => m -> Set (Domain m)
dom r
r forall a. Ord a => Set a -> Set a -> Set a
∩ Set (Domain r)
s) forall m (f :: * -> *).
(Relation m, Ord (Domain m), Foldable f) =>
f (Domain m) -> m -> m
◁ r
r forall (m :: * -> *) a.
(MonadTest m, Eq a, Show a, HasCallStack) =>
a -> a -> m ()
=== Set (Domain r)
s forall m (f :: * -> *).
(Relation m, Ord (Domain m), Foldable f) =>
f (Domain m) -> m -> m
◁ r
r
propRangeRestrictionAndIntersection ::
(MonadTest m, Relation r, Eq r, Show r, Ord (Range r)) =>
Set (Range r) ->
r ->
m ()
propRangeRestrictionAndIntersection :: forall (m :: * -> *) r.
(MonadTest m, Relation r, Eq r, Show r, Ord (Range r)) =>
Set (Range r) -> r -> m ()
propRangeRestrictionAndIntersection Set (Range r)
s r
r =
r
r forall m. (Relation m, Ord (Range m)) => m -> Set (Range m) -> m
▷ (forall m. (Relation m, Ord (Range m)) => m -> Set (Range m)
range r
r forall a. Ord a => Set a -> Set a -> Set a
∩ Set (Range r)
s) forall (m :: * -> *) a.
(MonadTest m, Eq a, Show a, HasCallStack) =>
a -> a -> m ()
=== r
r forall m. (Relation m, Ord (Range m)) => m -> Set (Range m) -> m
▷ Set (Range r)
s
propRangeRestrictionAndIntersectionB ::
(MonadTest m, Relation r, Ord (Range r), Show (Range r)) =>
Set (Range r) ->
r ->
m ()
propRangeRestrictionAndIntersectionB :: forall (m :: * -> *) r.
(MonadTest m, Relation r, Ord (Range r), Show (Range r)) =>
Set (Range r) -> r -> m ()
propRangeRestrictionAndIntersectionB Set (Range r)
s r
r =
(forall m. (Relation m, Ord (Range m)) => m -> Set (Range m)
range r
r) forall a. Ord a => Set a -> Set a -> Set a
∩ Set (Range r)
s forall (m :: * -> *) a.
(MonadTest m, Eq a, Show a, HasCallStack) =>
a -> a -> m ()
=== forall m. (Relation m, Ord (Range m)) => m -> Set (Range m)
range (r
r forall m. (Relation m, Ord (Range m)) => m -> Set (Range m) -> m
▷ Set (Range r)
s)
propDomainExclusionAndSetDifference ::
(MonadTest m, Relation r, Eq r, Show r, Ord (Domain r)) =>
Set (Domain r) ->
r ->
m ()
propDomainExclusionAndSetDifference :: forall (m :: * -> *) r.
(MonadTest m, Relation r, Eq r, Show r, Ord (Domain r)) =>
Set (Domain r) -> r -> m ()
propDomainExclusionAndSetDifference Set (Domain r)
s r
r =
(forall m. (Relation m, Ord (Domain m)) => m -> Set (Domain m)
dom r
r forall a. Ord a => Set a -> Set a -> Set a
\\ Set (Domain r)
s) forall m (f :: * -> *).
(Relation m, Ord (Domain m), Foldable f) =>
f (Domain m) -> m -> m
◁ r
r forall (m :: * -> *) a.
(MonadTest m, Eq a, Show a, HasCallStack) =>
a -> a -> m ()
=== Set (Domain r)
s forall m (f :: * -> *).
(Relation m, Ord (Domain m), Foldable f) =>
f (Domain m) -> m -> m
⋪ r
r
propDomainExclusionAndUnion ::
( MonadTest m
, Relation r
, Eq r
, Show r
, Ord (Domain r)
, Ord (Range r)
) =>
Set (Domain r) ->
r ->
r ->
m ()
propDomainExclusionAndUnion :: forall (m :: * -> *) r.
(MonadTest m, Relation r, Eq r, Show r, Ord (Domain r),
Ord (Range r)) =>
Set (Domain r) -> r -> r -> m ()
propDomainExclusionAndUnion Set (Domain r)
s r
r1 r
r2 =
(forall m. (Relation m, Ord (Domain m)) => m -> Set (Domain m)
dom r
r1 forall a. Ord a => Set a -> Set a -> Set a
`union` Set (Domain r)
s)
forall m (f :: * -> *).
(Relation m, Ord (Domain m), Foldable f) =>
f (Domain m) -> m -> m
⋪ (r
r1 forall m.
(Relation m, Ord (Domain m), Ord (Range m)) =>
m -> m -> m
∪ r
r2)
forall (m :: * -> *) a.
(MonadTest m, Eq a, Show a, HasCallStack) =>
a -> a -> m ()
=== (forall m. (Relation m, Ord (Domain m)) => m -> Set (Domain m)
dom r
r1 forall a. Ord a => Set a -> Set a -> Set a
`union` Set (Domain r)
s)
forall m (f :: * -> *).
(Relation m, Ord (Domain m), Foldable f) =>
f (Domain m) -> m -> m
⋪ r
r2
propRelation ::
(Show r, Show (Domain r)) =>
Gen (Set (Domain r)) ->
Gen r ->
(Set (Domain r) -> r -> PropertyT IO ()) ->
Property
propRelation :: forall r.
(Show r, Show (Domain r)) =>
Gen (Set (Domain r))
-> Gen r -> (Set (Domain r) -> r -> PropertyT IO ()) -> Property
propRelation Gen (Set (Domain r))
genS Gen r
genR Set (Domain r) -> r -> PropertyT IO ()
prop =
TestLimit -> Property -> Property
withTests TestLimit
500 forall a b. (a -> b) -> a -> b
$
HasCallStack => PropertyT IO () -> Property
property forall a b. (a -> b) -> a -> b
$ do
(Set (Domain r)
s, r
r) <- (,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a.
(Monad m, Show a, HasCallStack) =>
Gen a -> PropertyT m a
forAll Gen (Set (Domain r))
genS forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (m :: * -> *) a.
(Monad m, Show a, HasCallStack) =>
Gen a -> PropertyT m a
forAll Gen r
genR
Set (Domain r) -> r -> PropertyT IO ()
prop Set (Domain r)
s r
r
propRelations ::
(Show r, Show (Domain r)) =>
Gen (Set (Domain r)) ->
Gen r ->
(Set (Domain r) -> r -> r -> PropertyT IO ()) ->
Property
propRelations :: forall r.
(Show r, Show (Domain r)) =>
Gen (Set (Domain r))
-> Gen r
-> (Set (Domain r) -> r -> r -> PropertyT IO ())
-> Property
propRelations Gen (Set (Domain r))
genS Gen r
genR Set (Domain r) -> r -> r -> PropertyT IO ()
prop =
TestLimit -> Property -> Property
withTests TestLimit
500 forall a b. (a -> b) -> a -> b
$
HasCallStack => PropertyT IO () -> Property
property forall a b. (a -> b) -> a -> b
$ do
(Set (Domain r)
s, r
r1, r
r2) <- (,,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a.
(Monad m, Show a, HasCallStack) =>
Gen a -> PropertyT m a
forAll Gen (Set (Domain r))
genS forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (m :: * -> *) a.
(Monad m, Show a, HasCallStack) =>
Gen a -> PropertyT m a
forAll Gen r
genR forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (m :: * -> *) a.
(Monad m, Show a, HasCallStack) =>
Gen a -> PropertyT m a
forAll Gen r
genR
Set (Domain r) -> r -> r -> PropertyT IO ()
prop Set (Domain r)
s r
r1 r
r2
genInt :: Gen Int
genInt :: Gen Int
genInt = forall (m :: * -> *) a. (MonadGen m, Integral a) => Range a -> m a
Gen.integral (forall a. a -> a -> Range a
Range.constant Int
0 Int
100)
genSetOf :: Ord a => Gen a -> Gen (Set a)
genSetOf :: forall a. Ord a => Gen a -> Gen (Set a)
genSetOf Gen a
genA = forall (m :: * -> *) a.
(MonadGen m, Ord a) =>
Range Int -> m a -> m (Set a)
Gen.set Range Int
aRange Gen a
genA
aRange :: Range.Range Int
aRange :: Range Int
aRange = forall a. a -> a -> Range a
Range.constant Int
0 Int
50
genIntS :: Gen (Set Int)
genIntS :: Gen (Set Int)
genIntS = forall a. Ord a => Gen a -> Gen (Set a)
genSetOf Gen Int
genInt
genMap :: Gen (Map Int Int)
genMap :: Gen (Map Int Int)
genMap = forall (m :: * -> *) k v.
(MonadGen m, Ord k) =>
Range Int -> m (k, v) -> m (Map k v)
Gen.map Range Int
aRange forall a b. (a -> b) -> a -> b
$ (,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Int
genInt forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Int
genInt
genSet :: Gen (Set (Int, Int))
genSet :: Gen (Set (Int, Int))
genSet = forall a. Ord a => Gen a -> Gen (Set a)
genSetOf ((,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Int
genInt forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Int
genInt)
genPairsList :: Gen [(Int, Int)]
genPairsList :: Gen [(Int, Int)]
genPairsList = forall (m :: * -> *) a. MonadGen m => Range Int -> m a -> m [a]
Gen.list Range Int
aRange ((,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Int
genInt forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Int
genInt)
genBimap :: Gen (Bimap Int Int)
genBimap :: Gen (Bimap Int Int)
genBimap = forall a b. (Ord a, Ord b) => [(a, b)] -> Bimap a b
Bimap.fromList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen [(Int, Int)]
genPairsList
testRelation :: TestTree
testRelation :: TestTree
testRelation =
TestName -> [TestTree] -> TestTree
testGroup
TestName
"Test Relation instances"
[ TestName -> [TestTree] -> TestTree
testGroup
TestName
"Relation - Set"
[ TestName -> Property -> TestTree
testProperty
TestName
"DomainRestrictionAndIntersection"
(forall r.
(Show r, Show (Domain r)) =>
Gen (Set (Domain r))
-> Gen r -> (Set (Domain r) -> r -> PropertyT IO ()) -> Property
propRelation Gen (Set Int)
genIntS Gen (Set (Int, Int))
genSet forall (m :: * -> *) r.
(MonadTest m, Relation r, Ord (Domain r), Show (Domain r)) =>
Set (Domain r) -> r -> m ()
propDomainRestrictionAndIntersection)
, TestName -> Property -> TestTree
testProperty
TestName
"DomainRestrictionAndIntersectionB"
(forall r.
(Show r, Show (Domain r)) =>
Gen (Set (Domain r))
-> Gen r -> (Set (Domain r) -> r -> PropertyT IO ()) -> Property
propRelation Gen (Set Int)
genIntS Gen (Set (Int, Int))
genSet forall (m :: * -> *) r.
(MonadTest m, Relation r, Eq r, Show r, Ord (Domain r)) =>
Set (Domain r) -> r -> m ()
propDomainRestrictionAndIntersectionB)
, TestName -> Property -> TestTree
testProperty
TestName
"DomainExclusionAndSetDifference"
(forall r.
(Show r, Show (Domain r)) =>
Gen (Set (Domain r))
-> Gen r -> (Set (Domain r) -> r -> PropertyT IO ()) -> Property
propRelation Gen (Set Int)
genIntS Gen (Set (Int, Int))
genSet forall (m :: * -> *) r.
(MonadTest m, Relation r, Eq r, Show r, Ord (Domain r)) =>
Set (Domain r) -> r -> m ()
propDomainExclusionAndSetDifference)
, TestName -> Property -> TestTree
testProperty
TestName
"RangeRestrictionAndIntersection"
(forall r.
(Show r, Show (Domain r)) =>
Gen (Set (Domain r))
-> Gen r -> (Set (Domain r) -> r -> PropertyT IO ()) -> Property
propRelation Gen (Set Int)
genIntS Gen (Set (Int, Int))
genSet forall (m :: * -> *) r.
(MonadTest m, Relation r, Eq r, Show r, Ord (Range r)) =>
Set (Range r) -> r -> m ()
propRangeRestrictionAndIntersection)
, TestName -> Property -> TestTree
testProperty
TestName
"RangeRestrictionAndIntersectionB"
(forall r.
(Show r, Show (Domain r)) =>
Gen (Set (Domain r))
-> Gen r -> (Set (Domain r) -> r -> PropertyT IO ()) -> Property
propRelation Gen (Set Int)
genIntS Gen (Set (Int, Int))
genSet forall (m :: * -> *) r.
(MonadTest m, Relation r, Ord (Range r), Show (Range r)) =>
Set (Range r) -> r -> m ()
propRangeRestrictionAndIntersectionB)
]
, TestName -> [TestTree] -> TestTree
testGroup
TestName
"Relation - Map"
[ TestName -> Property -> TestTree
testProperty
TestName
"DomainRestrictionAndIntersection"
(forall r.
(Show r, Show (Domain r)) =>
Gen (Set (Domain r))
-> Gen r -> (Set (Domain r) -> r -> PropertyT IO ()) -> Property
propRelation Gen (Set Int)
genIntS Gen (Map Int Int)
genMap forall (m :: * -> *) r.
(MonadTest m, Relation r, Ord (Domain r), Show (Domain r)) =>
Set (Domain r) -> r -> m ()
propDomainRestrictionAndIntersection)
, TestName -> Property -> TestTree
testProperty
TestName
"DomainRestrictionAndIntersectionB"
(forall r.
(Show r, Show (Domain r)) =>
Gen (Set (Domain r))
-> Gen r -> (Set (Domain r) -> r -> PropertyT IO ()) -> Property
propRelation Gen (Set Int)
genIntS Gen (Map Int Int)
genMap forall (m :: * -> *) r.
(MonadTest m, Relation r, Eq r, Show r, Ord (Domain r)) =>
Set (Domain r) -> r -> m ()
propDomainRestrictionAndIntersectionB)
, TestName -> Property -> TestTree
testProperty
TestName
"DomainExclusionAndSetDifference"
(forall r.
(Show r, Show (Domain r)) =>
Gen (Set (Domain r))
-> Gen r -> (Set (Domain r) -> r -> PropertyT IO ()) -> Property
propRelation Gen (Set Int)
genIntS Gen (Map Int Int)
genMap forall (m :: * -> *) r.
(MonadTest m, Relation r, Eq r, Show r, Ord (Domain r)) =>
Set (Domain r) -> r -> m ()
propDomainExclusionAndSetDifference)
, TestName -> Property -> TestTree
testProperty
TestName
"RangeRestrictionAndIntersection"
(forall r.
(Show r, Show (Domain r)) =>
Gen (Set (Domain r))
-> Gen r -> (Set (Domain r) -> r -> PropertyT IO ()) -> Property
propRelation Gen (Set Int)
genIntS Gen (Map Int Int)
genMap forall (m :: * -> *) r.
(MonadTest m, Relation r, Eq r, Show r, Ord (Range r)) =>
Set (Range r) -> r -> m ()
propRangeRestrictionAndIntersection)
, TestName -> Property -> TestTree
testProperty
TestName
"RangeRestrictionAndIntersectionB"
(forall r.
(Show r, Show (Domain r)) =>
Gen (Set (Domain r))
-> Gen r -> (Set (Domain r) -> r -> PropertyT IO ()) -> Property
propRelation Gen (Set Int)
genIntS Gen (Map Int Int)
genMap forall (m :: * -> *) r.
(MonadTest m, Relation r, Ord (Range r), Show (Range r)) =>
Set (Range r) -> r -> m ()
propRangeRestrictionAndIntersectionB)
]
, TestName -> [TestTree] -> TestTree
testGroup
TestName
"Relation - Bimap"
[ TestName -> Property -> TestTree
testProperty
TestName
"DomainRestrictionAndIntersection"
(forall r.
(Show r, Show (Domain r)) =>
Gen (Set (Domain r))
-> Gen r -> (Set (Domain r) -> r -> PropertyT IO ()) -> Property
propRelation Gen (Set Int)
genIntS Gen (Bimap Int Int)
genBimap forall (m :: * -> *) r.
(MonadTest m, Relation r, Ord (Domain r), Show (Domain r)) =>
Set (Domain r) -> r -> m ()
propDomainRestrictionAndIntersection)
, TestName -> Property -> TestTree
testProperty
TestName
"DomainRestrictionAndIntersectionB"
(forall r.
(Show r, Show (Domain r)) =>
Gen (Set (Domain r))
-> Gen r -> (Set (Domain r) -> r -> PropertyT IO ()) -> Property
propRelation Gen (Set Int)
genIntS Gen (Bimap Int Int)
genBimap forall (m :: * -> *) r.
(MonadTest m, Relation r, Eq r, Show r, Ord (Domain r)) =>
Set (Domain r) -> r -> m ()
propDomainRestrictionAndIntersectionB)
, TestName -> Property -> TestTree
testProperty
TestName
"DomainExclusionAndSetDifference"
(forall r.
(Show r, Show (Domain r)) =>
Gen (Set (Domain r))
-> Gen r -> (Set (Domain r) -> r -> PropertyT IO ()) -> Property
propRelation Gen (Set Int)
genIntS Gen (Bimap Int Int)
genBimap forall (m :: * -> *) r.
(MonadTest m, Relation r, Eq r, Show r, Ord (Domain r)) =>
Set (Domain r) -> r -> m ()
propDomainExclusionAndSetDifference)
, TestName -> Property -> TestTree
testProperty
TestName
"RangeRestrictionAndIntersection"
(forall r.
(Show r, Show (Domain r)) =>
Gen (Set (Domain r))
-> Gen r -> (Set (Domain r) -> r -> PropertyT IO ()) -> Property
propRelation Gen (Set Int)
genIntS Gen (Bimap Int Int)
genBimap forall (m :: * -> *) r.
(MonadTest m, Relation r, Eq r, Show r, Ord (Range r)) =>
Set (Range r) -> r -> m ()
propRangeRestrictionAndIntersection)
, TestName -> Property -> TestTree
testProperty
TestName
"RangeRestrictionAndIntersectionB"
(forall r.
(Show r, Show (Domain r)) =>
Gen (Set (Domain r))
-> Gen r -> (Set (Domain r) -> r -> PropertyT IO ()) -> Property
propRelation Gen (Set Int)
genIntS Gen (Bimap Int Int)
genBimap forall (m :: * -> *) r.
(MonadTest m, Relation r, Ord (Range r), Show (Range r)) =>
Set (Range r) -> r -> m ()
propRangeRestrictionAndIntersectionB)
]
, TestName -> [TestTree] -> TestTree
testGroup
TestName
"Relation - Pairs list"
[ TestName -> Property -> TestTree
testProperty
TestName
"DomainRestrictionAndIntersection"
(forall r.
(Show r, Show (Domain r)) =>
Gen (Set (Domain r))
-> Gen r -> (Set (Domain r) -> r -> PropertyT IO ()) -> Property
propRelation Gen (Set Int)
genIntS Gen [(Int, Int)]
genPairsList forall (m :: * -> *) r.
(MonadTest m, Relation r, Ord (Domain r), Show (Domain r)) =>
Set (Domain r) -> r -> m ()
propDomainRestrictionAndIntersection)
, TestName -> Property -> TestTree
testProperty
TestName
"DomainRestrictionAndIntersectionB"
(forall r.
(Show r, Show (Domain r)) =>
Gen (Set (Domain r))
-> Gen r -> (Set (Domain r) -> r -> PropertyT IO ()) -> Property
propRelation Gen (Set Int)
genIntS Gen [(Int, Int)]
genPairsList forall (m :: * -> *) r.
(MonadTest m, Relation r, Eq r, Show r, Ord (Domain r)) =>
Set (Domain r) -> r -> m ()
propDomainRestrictionAndIntersectionB)
, TestName -> Property -> TestTree
testProperty
TestName
"DomainExclusionAndSetDifference"
(forall r.
(Show r, Show (Domain r)) =>
Gen (Set (Domain r))
-> Gen r -> (Set (Domain r) -> r -> PropertyT IO ()) -> Property
propRelation Gen (Set Int)
genIntS Gen [(Int, Int)]
genPairsList forall (m :: * -> *) r.
(MonadTest m, Relation r, Eq r, Show r, Ord (Domain r)) =>
Set (Domain r) -> r -> m ()
propDomainExclusionAndSetDifference)
, TestName -> Property -> TestTree
testProperty
TestName
"RangeRestrictionAndIntersection"
(forall r.
(Show r, Show (Domain r)) =>
Gen (Set (Domain r))
-> Gen r -> (Set (Domain r) -> r -> PropertyT IO ()) -> Property
propRelation Gen (Set Int)
genIntS Gen [(Int, Int)]
genPairsList forall (m :: * -> *) r.
(MonadTest m, Relation r, Eq r, Show r, Ord (Range r)) =>
Set (Range r) -> r -> m ()
propRangeRestrictionAndIntersection)
, TestName -> Property -> TestTree
testProperty
TestName
"RangeRestrictionAndIntersectionB"
(forall r.
(Show r, Show (Domain r)) =>
Gen (Set (Domain r))
-> Gen r -> (Set (Domain r) -> r -> PropertyT IO ()) -> Property
propRelation Gen (Set Int)
genIntS Gen [(Int, Int)]
genPairsList forall (m :: * -> *) r.
(MonadTest m, Relation r, Ord (Range r), Show (Range r)) =>
Set (Range r) -> r -> m ()
propRangeRestrictionAndIntersectionB)
]
, TestName -> [TestTree] -> TestTree
testGroup
TestName
"Relations"
[ TestName -> Property -> TestTree
testProperty
TestName
"Set instance"
(forall r.
(Show r, Show (Domain r)) =>
Gen (Set (Domain r))
-> Gen r
-> (Set (Domain r) -> r -> r -> PropertyT IO ())
-> Property
propRelations Gen (Set Int)
genIntS Gen (Set (Int, Int))
genSet forall (m :: * -> *) r.
(MonadTest m, Relation r, Eq r, Show r, Ord (Domain r),
Ord (Range r)) =>
Set (Domain r) -> r -> r -> m ()
propDomainExclusionAndUnion)
, TestName -> Property -> TestTree
testProperty
TestName
"Map instance"
(forall r.
(Show r, Show (Domain r)) =>
Gen (Set (Domain r))
-> Gen r
-> (Set (Domain r) -> r -> r -> PropertyT IO ())
-> Property
propRelations Gen (Set Int)
genIntS Gen (Map Int Int)
genMap forall (m :: * -> *) r.
(MonadTest m, Relation r, Eq r, Show r, Ord (Domain r),
Ord (Range r)) =>
Set (Domain r) -> r -> r -> m ()
propDomainExclusionAndUnion)
, TestName -> Property -> TestTree
testProperty
TestName
"Bimap instance"
(forall r.
(Show r, Show (Domain r)) =>
Gen (Set (Domain r))
-> Gen r
-> (Set (Domain r) -> r -> r -> PropertyT IO ())
-> Property
propRelations Gen (Set Int)
genIntS Gen (Bimap Int Int)
genBimap forall (m :: * -> *) r.
(MonadTest m, Relation r, Eq r, Show r, Ord (Domain r),
Ord (Range r)) =>
Set (Domain r) -> r -> r -> m ()
propDomainExclusionAndUnion)
]
]