module Test.QuickCheck.Instances.List
       (anyList,nonEmpty
       ,infiniteList
       ,setLength
       ,increasing,nondecreasing
       ,increasingInf,nondecreasingInf
       ,decreasing,nonincreasing
       ,decreasingInf,nonincreasingInf
       ) where
import Test.QuickCheck hiding (infiniteList)
import Test.QuickCheck.Instances.Num
import Control.Applicative
nonEmpty :: Gen a -> Gen [a]
nonEmpty x = liftA2 (:) x (anyList x)
anyList :: Gen a -> Gen [a]
anyList x = frequency [(1, pure []), (4, nonEmpty x)]
infiniteList :: Gen a -> Gen [a]
infiniteList x = liftA2 (:) x (infiniteList x)
setLength :: Int -> Gen a -> Gen [a]
setLength 0 _ = pure []
setLength n g = (:) <$> g <*> setLength (n1) g
sumA :: (Applicative f, Num a) => f a -> f [a] -> f [a]
sumA = liftA2 (scanl (+))
monotonic_ :: (Arbitrary a, Num a) => (Gen a -> Gen [a]) -> Gen a -> Gen [a]
monotonic_ listGen gen = sumA arbitrary (listGen gen)
monotonic :: (Arbitrary a, Num a) => Gen a -> Gen [a]
monotonic gen = monotonic_ anyList gen
increasing :: (Arbitrary a, Eq a, Num a) => Gen [a]
increasing = monotonic positive
increasingInf :: (Arbitrary a, Eq a, Num a) => Gen [a]
increasingInf = monotonic_ infiniteList positive
nondecreasing :: (Arbitrary a, Num a) => Gen [a]
nondecreasing = monotonic nonNegative
nondecreasingInf :: (Arbitrary a, Num a) => Gen [a]
nondecreasingInf = monotonic_ infiniteList nonNegative
decreasing :: (Arbitrary a, Eq a, Num a) => Gen [a]
decreasing = monotonic negative
decreasingInf :: (Arbitrary a, Eq a, Num a) => Gen [a]
decreasingInf = monotonic_ infiniteList negative
nonincreasing :: (Arbitrary a, Num a) => Gen [a]
nonincreasing = monotonic nonPositive
nonincreasingInf :: (Arbitrary a, Num a) => Gen [a]
nonincreasingInf = monotonic_ infiniteList nonPositive