module Exercise_5_Sol where import Data.Char (toUpper) import Data.List {-G5.1-} {- Berechnet "gg (xx, yy)". -} {-G5.2-} iter :: Int -> (a -> a) -> a -> a iter n f x | n <= 0 = x | otherwise = iter (n - 1) f (f x) pow :: Int -> Int -> Int pow n k = iter k mul 1 where mul x = n * x drop' :: Int -> [a] -> [a] drop' n xs = iter n tail xs replicate' :: Int -> a -> [a] replicate' n x = iter n cons [] where cons xs = x : xs {-G5.3-} -- rekursiv partition_rec :: (a -> Bool) -> [a] -> ([a], [a]) partition_rec _ [] = ([], []) partition_rec p (x : xs) = if p x then (x : ts, fs) else (ts, x : fs) where (ts, fs) = partition_rec p xs -- mit filter partition_filter :: (a -> Bool) -> [a] -> ([a], [a]) partition_filter p xs = (filter p xs, filter help xs) where help x = not (p x) prop_partition_rec xs = partition_rec even xs == partition even xs prop_partition_filter xs = partition_filter even xs == partition even xs prop_partitionDistrib xs ys = partition even (xs ++ ys) == (xs1 ++ ys1, xs2 ++ ys2) where (xs1, xs2) = partition even xs (ys1, ys2) = partition even ys {- Die ersten Implementierung ist effizienter als die zweite, weil "p" nur einmal pro Element angewandt wird statt zweimal. Die zweite Version ist wahrscheinlich die einfachste. Statt "help" zu definieren kann man auch "not . p" schreiben (vgl. 6.7 in den Folien). -} {-G5.4-} {- Die Evaluierung von "zeros" terminiert nicht: zeros = 0 : zeros = 0 : 0 : zeros = 0 : 0 : 0 : zeros = ... Das sieht man deutlich, wenn man versucht, die Funktion in "ghci" auszuwerten. -} {-H5.1-} while :: (a -> Bool) -> (a -> a) -> a -> a while p f x = if p x then while p f (f x) else x removeFactorPred :: Integer -> Integer -> Bool removeFactorPred k n = n `mod` k == 0 removeFactorStep :: Integer -> Integer -> Integer removeFactorStep k n = n `div` k removeFactor :: Integer -> Integer -> Integer removeFactor k n = while (removeFactorPred k) (removeFactorStep k) n ldPred :: (Integer, Integer) -> Bool ldPred (n,_) = n > 1 ldStep :: (Integer, Integer) -> (Integer, Integer) ldStep (n,k) = (n `div` 2, k + 1) ld :: Integer -> Integer ld n = snd (while ldPred ldStep (n, 0)) {-H5.2-} reachable :: Eq a => [(a, a)] -> a -> a -> Bool reachable g s1 s2 = (s1, s2) `elem` g || or [ reachable (purge next) next s2 | next <- candidates ] where candidates = [ y | (x, y) <- g, x == s1 ] purge next = delete (s1, next) g {-H5.3-} mapState :: (b -> a -> (c,b)) -> b -> [a] -> ([c], b) mapState f s [] = ([], s) mapState f s (x:xs) = (x':xs', s'') where (x', s') = f s x (xs', s'') = mapState f s' xs f :: String -> Char -> (Char, String) f s x = if x `elem` s then (x, s) else (toUpper x, x : s) {-H5.4-} splitSubmissions :: [(a, Integer)] -> ([(a, Integer)], [(a, Integer)]) splitSubmissions xs = splitSubmissionsAux xs (0, 0) where splitSubmissionsAux [] _ = ([], []) splitSubmissionsAux ((s, k):xs) (m, n) | m <= n = let (ys, zs) = splitSubmissionsAux xs (m + k, n) in ((s, k) : ys, zs) | otherwise = let (ys, zs) = splitSubmissionsAux xs (m, n + k) in (ys, (s,k) : zs)