module Test.Data.List where import qualified Data.List.HT.Private as ListHT import qualified Data.List as List import Control.Monad (liftM2, ) import Test.Utility (equalLists, equalInfLists, ) import Test.QuickCheck (Property, test, (==>), ) import Prelude hiding (iterate, ) sieve :: Eq a => Int -> [a] -> Property sieve n x = n>0 ==> equalLists [ListHT.sieve n x, ListHT.sieve' n x, ListHT.sieve'' n x, ListHT.sieve''' n x] sliceHorizontal :: Eq a => Int -> [a] -> Property sliceHorizontal n x = n>0 ==> ListHT.sliceHorizontal n x == ListHT.sliceHorizontal' n x sliceVertical :: Eq a => Int -> [a] -> Property sliceVertical n x = n>0 ==> ListHT.sliceVertical n x == ListHT.sliceVertical' n x slice :: Eq a => Int -> [a] -> Property slice n x = 0 -- problems: ListHT.sliceHorizontal 4 [] == [[],[],[],[]] ListHT.sliceHorizontal n x == List.transpose (ListHT.sliceVertical n x) && ListHT.sliceVertical n x == List.transpose (ListHT.sliceHorizontal n x) shear :: Eq a => [[a]] -> Bool shear xs = ListHT.shearTranspose xs == map reverse (ListHT.shear xs) outerProduct :: (Eq a, Eq b) => [a] -> [b] -> Bool outerProduct xs ys = concat (ListHT.outerProduct (,) xs ys) == liftM2 (,) xs ys iterate :: Eq a => (a -> a -> a) -> a -> Bool iterate op a = let xs = List.iterate (op a) a ys = ListHT.iterateAssociative op a zs = ListHT.iterateLeaky op a in equalInfLists 1000 [xs, ys, zs] tests :: [(String, IO ())] tests = ("sieve", test (sieve :: Int -> [Integer] -> Property)) : ("sliceHorizontal", test (sliceHorizontal :: Int -> [Integer] -> Property)) : ("sliceVertical", test (sliceVertical :: Int -> [Integer] -> Property)) : ("slice", test (slice :: Int -> [Integer] -> Property)) : ("shear", test (shear :: [[Integer]] -> Bool)) : ("outerProduct", test (outerProduct :: [Integer] -> [Int] -> Bool)) : ("iterate", test (iterate (+) :: Integer -> Bool)) : []