{-# LANGUAGE ScopedTypeVariables #-}
module Test.Util.Schedule.Tests (tests) where
import Test.QuickCheck
import Test.Tasty
import Test.Tasty.QuickCheck
import Test.Util.Schedule
tests :: TestTree
tests :: TestTree
tests = TestName -> [TestTree] -> TestTree
testGroup TestName
"Test.Util.Schedule"
[ TestName -> Property -> TestTree
forall a. Testable a => TestName -> a -> TestTree
testProperty TestName
"joinSchedule/genSchedule" (Property -> TestTree) -> Property -> TestTree
forall a b. (a -> b) -> a -> b
$ Property
prop_joinSchedule_genSchedule
]
prop_joinSchedule_genSchedule :: Property
prop_joinSchedule_genSchedule :: Property
prop_joinSchedule_genSchedule =
Gen ([Int], Schedule Int)
-> (([Int], Schedule Int) -> Property) -> Property
forall a prop.
(Show a, Testable prop) =>
Gen a -> (a -> prop) -> Property
forAll Gen ([Int], Schedule Int)
genElementsAndSpread ((([Int], Schedule Int) -> Property) -> Property)
-> (([Int], Schedule Int) -> Property) -> Property
forall a b. (a -> b) -> a -> b
$ \([Int]
as, Schedule Int
spread) ->
Schedule Int -> [Int]
forall a. Schedule a -> [a]
joinSchedule Schedule Int
spread [Int] -> [Int] -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== [Int]
as
where
genElementsAndSpread :: Gen ([Int], Schedule Int)
genElementsAndSpread = do
[Int]
as :: [Int] <- Gen [Int]
forall a. Arbitrary a => Gen a
arbitrary
Schedule Int
spread <- [Int] -> Gen (Schedule Int)
forall a. [a] -> Gen (Schedule a)
genSchedule [Int]
as
([Int], Schedule Int) -> Gen ([Int], Schedule Int)
forall a. a -> Gen a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Int]
as, Schedule Int
spread)