module Exc01 where import Prelude hiding (length,take,drop,(++),splitAt,elem,reverse,map,foldl,foldr) import qualified List -- only needed for testing the results -- Auxiliary functions -- could use reversel or reverser from H-1 below -- this version of reverse is more efficient revApp :: [a] -> [a] -> [a] revApp [] ys = ys revApp (x:xs) ys = revApp xs (x:ys) my_reverse :: [a] -> [a] my_reverse xs = revApp xs [] -- shorter: my_reverse = (flip revApp) [] -- more general type: my_elem :: (Eq a) => a -> [a] -> Bool my_elem :: Int -> [Int] -> Bool my_elem x [] = False my_elem x (y:ys) | x==y = True | otherwise = my_elem x ys my_take :: Int -> [a] -> [a] my_take 0 _ = [] my_take n (x:xs) = x:(my_take (n-1) xs) my_drop :: Int -> [a] -> [a] my_drop 0 ys = ys my_drop n (x:xs) = my_drop (n-1) xs -- Exercise P-1 nub :: [Int] -> [Int] nub [] = [] nub [x] = [x] nub (x:xs) | x `my_elem` xs = nub xs | otherwise = x:(nub xs) -- this deletes duplicates from the end (could use reverse library function) nub' :: [Int] -> [Int] nub' = my_reverse . nub . my_reverse -- Exercise P-2 halve :: [a] -> ([a],[a]) halve xs = (my_take (n `div` 2) xs, my_drop (n `div` 2) xs) where n = lengthl xs -- example or error handling halve' :: [a] -> ([a],[a]) halve' xs | even n = (my_take (n `div` 2) xs, my_drop (n `div` 2) xs) | otherwise = error "halve': odd lengthl of input list" where n = lengthl xs -- Exercise P-3 merge :: [Int] -> [Int] -> [Int] merge [] ys = ys merge xs [] = xs merge (x:xs) (y:ys) | x [Int] mergesort [] = [] mergesort [x] = [x] mergesort xs = merge left' right' where left' = mergesort left right' = mergesort right (left,right) = halve xs -- Exercise P-4 pyths :: Int -> [(Int,Int,Int)] pyths n = [(a,b,c) | a <- [1..n], b <- [1..n], c <- [1..n], a^2 + b^2 == c^2 ] pyths' :: Int -> [(Int,Int,Int)] pyths' n = [(a,b,c) | a <- [1..n], b <- [1..n], c <- [1..n], a^2 + b^2 == c^2, a Bool prime 1 = False prime 2 = True prime n = (n `mod` 2 /= 0) && prime' 3 n where prime' m n | m^2 > n = True | n `mod` m == 0 = False | otherwise = prime' (m+2) n -- Exercise H-1 -- from Types.hs (1st lecture) foldr' :: (a -> b -> b) -> b -> [a] -> b foldr' f v [] = v foldr' f v (x:xs) = f x (foldr' f v xs) -- from Types.hs (1st lecture) foldl' :: (b -> a -> b) -> b -> [a] -> b foldl' f v [] = v foldl' f v (x:xs) = foldl' f (f v x) xs lengthr = foldr' (\ _ n -> 1+n) 0 lengthl = foldl' (\ n _ -> 1+n) 0 reversel = foldl' (\ xs x -> x:xs) [] reverser = foldr' (\ x xs -> snoc x xs) [] where snoc x [] = [x] snoc x (y:ys) = y:(snoc x ys) -- Exercise H-2 data NTree a = Branch a [NTree a] deriving (Eq) my_map :: (a -> b) -> [a] -> [b] my_map f [] = [] my_map f (x:xs) = (f x):(my_map f xs) my_append :: [a] -> [a] -> [a] my_append [] ys = ys my_append (x:xs) ys = x:(my_append xs ys) my_concat :: [[a]] -> [a] my_concat = foldl' my_append [] my_intersperse :: a -> [a] -> [a] my_intersperse y [] = [] my_intersperse y [x] = [x] my_intersperse y (x:xs) = x:(y:(my_intersperse y xs)) -- build a binary tree; just for testing mkTree :: [a] -> NTree a mkTree [] = error "mkTree: empty input list" mkTree [x] = Branch x [] mkTree [x,y] = Branch x [Branch y []] mkTree (x:xs) = Branch x [left, right] where (l,r) = halve xs left = mkTree l right = mkTree r showTree :: (Eq a, Show a) => NTree a -> String showTree (Branch x []) = show x showTree (Branch x xs) = show x `my_append` "(" `my_append` my_concat (my_intersperse "," (my_map showTree xs)) `my_append` ")" -- using prelude functions {- showTree' :: (Eq a, Show a) => NTree a -> String showTree' (Branch x []) = show x showTree' (Branch x xs) = show x ++ "(" ++ List.concat (List.intersperse "," (map showTree xs)) ++ ")" -} -- TESTME: -- let t1 = mkTree [1..10] -- showTree t1