module Test.NumericPrelude.List where import qualified NumericPrelude.List as NList import qualified Data.List as List import Control.Monad (liftM2) import Test.NumericPrelude.Utility (equalLists, equalInfLists, testUnit) import Test.QuickCheck (Property, quickCheck, (==>)) import qualified Test.HUnit as HUnit sieve :: Eq a => Int -> [a] -> Property sieve n x = n>0 ==> equalLists [NList.sieve n x, NList.sieve' n x, NList.sieve'' n x, NList.sieve''' n x] sliceHoriz :: Eq a => Int -> [a] -> Property sliceHoriz n x = n>0 ==> NList.sliceHoriz n x == NList.sliceHoriz' n x sliceVert :: Eq a => Int -> [a] -> Property sliceVert n x = n>0 ==> NList.sliceVert n x == NList.sliceVert' n x slice :: Eq a => Int -> [a] -> Property slice n x = 0 -- problems: NList.sliceHoriz 4 [] == [[],[],[],[]] NList.sliceHoriz n x == List.transpose (NList.sliceVert n x) && NList.sliceVert n x == List.transpose (NList.sliceHoriz n x) shear :: Eq a => [[a]] -> Bool shear xs = NList.shearTranspose xs == map reverse (NList.shear xs) outerProduct :: (Eq a, Eq b) => [a] -> [b] -> Bool outerProduct xs ys = equalLists [concat (NList.outerProduct (,) xs ys), liftM2 (,) xs ys] reduceRepeated :: Eq a => (a -> a -> a) -> a -> a -> Integer -> Property reduceRepeated op a0 a n = n>0 ==> NList.reduceRepeated op a0 a n == NList.reduceRepeatedSlow op a0 a n iterate' :: Eq a => (a -> a -> a) -> a -> Bool iterate' op a = let xs = List.iterate (op a) a ys = NList.iterateAssoc op a zs = NList.iterateLeaky op a in equalInfLists 1000 [xs, ys, zs] tests :: HUnit.Test tests = HUnit.TestLabel "list" $ HUnit.TestList $ map testUnit $ ("sieve", quickCheck (sieve :: Int -> [Integer] -> Property)) : ("sliceHoriz", quickCheck (sliceHoriz :: Int -> [Integer] -> Property)) : ("sliceVert", quickCheck (sliceVert :: Int -> [Integer] -> Property)) : ("slice", quickCheck (slice :: Int -> [Integer] -> Property)) : ("shear", quickCheck (shear :: [[Integer]] -> Bool)) : ("outerProduct", quickCheck (outerProduct :: [Integer] -> [Int] -> Bool)) : ("reduceRepeated", quickCheck (reduceRepeated (+) :: Integer -> Integer -> Integer -> Property)) : ("iterate", quickCheck (iterate' (+) :: Integer -> Bool)) : []