{-# LANGUAGE GADTs, PartialTypeSignatures #-} module Tests_07(runTests, boolTests) where import Prelude hiding (sequence) import Template_07(count, filterCount, oddSquares, sequence, collatz, collatzLength, fastestSequence) import Test.LeanCheck import Data.List (nub) -- Generic Setup data Test = forall a. Testable a => Test String String a runTests = flip mapM_ tests (\ (Test ex name t) -> putStrLn ("running " ++ ex ++ "(" ++ name ++ ")" ++ "-tests") >> checkFor 1000 t) -- Tests for this week newtype SmallNums = SNum { snum :: Int } deriving (Ord, Eq, Num, Enum) instance Show SmallNums where show = show . snum instance Listable SmallNums where tiers = [map SNum [0..20]] -- 2.1 countNTest :: (Eq a) => SmallNums -> a -> Bool countNTest n x = let list = replicate (snum n) x in count (head list) list == snum n count1toNTest :: SmallNums -> Bool count1toNTest n = let list = concat [replicate (snum x) x | x <- [1..n]] in all (\x -> count x list == snum x) (nub list) -- 2.2 filterCount1toNTest :: SmallNums -> SmallNums -> Bool filterCount1toNTest n m = let list = concat [replicate (snum x) x | x <- [1..n]] filteredList = filterCount (snum m) list in filteredList == filter (>= m) filteredList filterCountNegativeTest :: SmallNums -> Bool filterCountNegativeTest n = let list = [1..(snum n)] in filterCount (-1) list == list --2.3 oddSquaresEvenTest :: SmallNums -> Bool oddSquaresEvenTest n = oddSquares (filter even [1..(snum n)]) == [] oddSquaresTest :: SmallNums -> Bool oddSquaresTest n = let list = filter odd [1..(snum n)] in oddSquares list == [x*x | x <- list] -- 3.1 test31 = Test "3.1" "examples on sheet" (sequence (+ 1) (== 6) 0 == [0, 1, 2, 3, 4, 5] && sequence succ (> 'z') 'a' == "abcdefghijklmnopqrstuvwxyz") -- 3.2 collatzRec x | x <= 1 = [] | even x = x : collatzRec (x `div` 2) | otherwise = x : collatzRec (3 * x + 1) -- 3.3 test33a = Test "3.3" "collatzLength 100000 100010 == [128,89,53,53,53,53,53,53,128,309,128]" (collatzLength 100000 100010 == [128,89,53,53,53,53,53,53,128,309,128]) test33b = Test "3.3" "collatzLength 100 115 == [25,25,25,87,12,38,12,100,113,113,113,69,20,12,33,33]" (collatzLength 100 115 == [25,25,25,87,12,38,12,100,113,113,113,69,20,12,33,33]) -- 3.4 data StepFun = SFun {descStep :: String, sfun :: Integer -> Integer} data AbortFun = AFun {descAbort :: String, afun :: Integer -> Bool} instance Show StepFun where show = descStep instance Show AbortFun where show = descAbort instance Listable StepFun where tiers = [[ SFun "(* 2)" (* 2), SFun "(+ 1)" (+ 1), SFun "(+ 7)" (+ 7), SFun "(\\ x -> if x < 5 then 2 * x else x - 3)" (\ x -> if x < 5 then 2 * x else x - 3), SFun "(^ 2)" (^ 2), SFun "(\\ x -> x)" (\x -> x) ]] instance Listable AbortFun where tiers = [[ AFun "(< 1000)" (< 1000), AFun "(\\ _ -> False)" (\ _ -> False), AFun "(> 20000)" (> 20000), AFun "(< 0)" (< 0) ]] shorter [] _ = True shorter (_ : xs) (_ : ys) = shorter xs ys shorter (_ : _) [] = False convertToInput pxs = let safety = ( (+1), (> 500), 1) in safety : map (\ (n,a,s) -> (sfun n, afun a, s)) pxs test34fastest pxs = let xs = convertToInput pxs res = fastestSequence xs seqs = map ( \(n,a,s) -> sequence n a s) xs in all (shorter res) seqs test34occurs pxs = let xs = convertToInput pxs res = fastestSequence xs seqs = map ( \(n,a,s) -> sequence n a s) xs in any (== res) seqs tests :: [Test] tests = [ Test "2.1" "count x [x_1,...,x_n] == n (x :: Int)" (countNTest :: SmallNums -> Int -> Bool), Test "2.1" "count x [x_1,...,x_n] == n (x :: Char)" (countNTest :: SmallNums -> Char -> Bool), Test "2.1" "count x [1,2,2,3,3,3, ..., n_1,...n_n] == x" count1toNTest, Test "2.2" "filterCount m [1,2,2,3,3,3, ..., n_1,...,n_n] == [m_1,...,m_m, ..., n_1,...,n_n]" filterCount1toNTest, Test "2.2" "filterCount (-1) [1,...,n] == [1,...,n]" filterCountNegativeTest, Test "2.3" "oddSquares [2,4,6,...,n] == []" oddSquaresEvenTest, Test "2.3" "oddSquares [1,3,5,...,n] == [1,9,25,...]" oddSquaresTest, test31, Test "3.2" "collatz is correct" (\ x -> collatz x == collatzRec x), test33a, test33b, Test "3.4" "fastestSequence is fastest" test34fastest, Test "3.4" "fastestSequence is a valid sequence" test34occurs ] boolTests :: [((String,String), Bool)] boolTests = map (\ (Test ex n t) -> ((ex,n), holds 1000 t)) tests