module Week4 where import Test.QuickCheck import System.Directory import List ------------------------------------------------------------------------- -- 1. Properties of the look function type Table a b = [(a,b)] look :: Eq a => a -> Table a b -> Maybe b look x [] = Nothing look x ((x',y):xys) | x == x' = Just y | otherwise = look x xys prop_LookJust :: Integer -> [(Integer,Integer)] -> Property prop_LookJust x xys = look_x /= Nothing ==> (x,y) `elem` xys where look_x = look x xys Just y = look_x prop_Look :: Integer -> [(Integer,Integer)] -> Bool prop_Look x xys = examine (look x xys) where examine Nothing = x `notElem` [ x | (x,_) <- xys ] examine (Just y) = (x,y) `elem` xys ------------------------------------------------------------------------- -- 2. Monadic helper functions {- sequence_ :: Monad m => [m ()] -> m () sequence_ [] = do return () sequence_ (m:ms) = do m sequence_ ms -- or: (less efficient) sequence_ xs = do sequence xs return () -} onlyIf :: Monad m => Bool -> m () -> m () onlyIf True m = m onlyIf False _ = return () ------------------------------------------------------------------------- -- 3. The Number Game game :: IO () game = do putStrLn "Think of a number 1 -- 100." play 1 100 putStrLn "I won!" play :: Int -> Int -> IO () play a b = do putStr ("Is it " ++ show guess ++ "? ") s <- getLine case s of "higher" -> play (guess+1) b "lower" -> play a (guess-1) _ -> return () where guess = (a+b) `div` 2 ------------------------------------------------------------------------- -- 4. A Backup Script backup :: IO () backup = do files <- getDirectoryContents "." createDirectory "backup" sequence_ [ copyFile' file ("backup/" ++ file) | file <- files ] -- copyFile' file file' copies file to file', if file is a real file -- (and not a directory) copyFile' :: FilePath -> FilePath -> IO () copyFile' file file' = do isFile <- doesFileExist file if isFile then copyFile file file' else return () ------------------------------------------------------------------------- -- 5. Generating Lists listOfLength :: Int -> Gen a -> Gen [a] listOfLength n gen = sequence [ gen | i <- [1..n] ] pairsOfEqualLengthLists :: Gen a -> Gen ([a],[a]) pairsOfEqualLengthLists gen = do n <- choose (0,100) xs <- listOfLength (abs n) gen ys <- listOfLength (abs n) gen return (xs,ys) prop_ZipUnzip :: [(Int,Int)] -> Bool prop_ZipUnzip xys = zip xs ys == xys where (xs,ys) = unzip xys -- simple, but bad, solution prop_UnzipZip :: [Int] -> [Int] -> Property prop_UnzipZip xs ys = length xs == length ys ==> unzip (zip xs ys) == (xs,ys) -- alternative solution 1 data TwoSameLengthLists a = SameLength [a] [a] deriving (Show) instance Arbitrary a => Arbitrary (TwoSameLengthLists a) where arbitrary = do (xs,ys) <- pairsOfEqualLengthLists arbitrary return (SameLength xs ys) prop_UnzipZip1 :: TwoSameLengthLists Int -> Bool prop_UnzipZip1 (SameLength xs ys) = unzip (zip xs ys) == (xs,ys) -- alternative solution 2 prop_UnzipZip2 :: Property prop_UnzipZip2 = forAll (pairsOfEqualLengthLists arbitrary) $ \(xs,ys) -> unzip (zip xs ys) == (xs :: [Int],ys :: [Int]) ------------------------------------------------------------------------- -- 6. Generating Ordered Lists orderedList :: Gen [Integer] orderedList = do x <- arbitrary ds <- arbitrary return (make x ds) where make x [] = [] make x (d:ds) = x : make (x+abs d) ds -------------------------------------------------------------------------